OSDN Git Service

2007-12-05 Tobias Burnus <burnus@net-b.de>
[pf3gnuchains/gcc-fork.git] / gcc / fortran / resolve.c
1 /* Perform type resolution on the various stuctures.
2    Copyright (C) 2001, 2002, 2003, 2004, 2005, 2006, 2007
3    Free Software Foundation, Inc.
4    Contributed by Andy Vaught
5
6 This file is part of GCC.
7
8 GCC is free software; you can redistribute it and/or modify it under
9 the terms of the GNU General Public License as published by the Free
10 Software Foundation; either version 3, or (at your option) any later
11 version.
12
13 GCC is distributed in the hope that it will be useful, but WITHOUT ANY
14 WARRANTY; without even the implied warranty of MERCHANTABILITY or
15 FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
16 for more details.
17
18 You should have received a copy of the GNU General Public License
19 along with GCC; see the file COPYING3.  If not see
20 <http://www.gnu.org/licenses/>.  */
21
22 #include "config.h"
23 #include "system.h"
24 #include "flags.h"
25 #include "gfortran.h"
26 #include "obstack.h"
27 #include "bitmap.h"
28 #include "arith.h"  /* For gfc_compare_expr().  */
29 #include "dependency.h"
30 #include "data.h"
31
32 /* Types used in equivalence statements.  */
33
34 typedef enum seq_type
35 {
36   SEQ_NONDEFAULT, SEQ_NUMERIC, SEQ_CHARACTER, SEQ_MIXED
37 }
38 seq_type;
39
40 /* Stack to keep track of the nesting of blocks as we move through the
41    code.  See resolve_branch() and resolve_code().  */
42
43 typedef struct code_stack
44 {
45   struct gfc_code *head, *current, *tail;
46   struct code_stack *prev;
47
48   /* This bitmap keeps track of the targets valid for a branch from
49      inside this block.  */
50   bitmap reachable_labels;
51 }
52 code_stack;
53
54 static code_stack *cs_base = NULL;
55
56
57 /* Nonzero if we're inside a FORALL block.  */
58
59 static int forall_flag;
60
61 /* Nonzero if we're inside a OpenMP WORKSHARE or PARALLEL WORKSHARE block.  */
62
63 static int omp_workshare_flag;
64
65 /* Nonzero if we are processing a formal arglist. The corresponding function
66    resets the flag each time that it is read.  */
67 static int formal_arg_flag = 0;
68
69 /* True if we are resolving a specification expression.  */
70 static int specification_expr = 0;
71
72 /* The id of the last entry seen.  */
73 static int current_entry_id;
74
75 /* We use bitmaps to determine if a branch target is valid.  */
76 static bitmap_obstack labels_obstack;
77
78 int
79 gfc_is_formal_arg (void)
80 {
81   return formal_arg_flag;
82 }
83
84 /* Resolve types of formal argument lists.  These have to be done early so that
85    the formal argument lists of module procedures can be copied to the
86    containing module before the individual procedures are resolved
87    individually.  We also resolve argument lists of procedures in interface
88    blocks because they are self-contained scoping units.
89
90    Since a dummy argument cannot be a non-dummy procedure, the only
91    resort left for untyped names are the IMPLICIT types.  */
92
93 static void
94 resolve_formal_arglist (gfc_symbol *proc)
95 {
96   gfc_formal_arglist *f;
97   gfc_symbol *sym;
98   int i;
99
100   if (proc->result != NULL)
101     sym = proc->result;
102   else
103     sym = proc;
104
105   if (gfc_elemental (proc)
106       || sym->attr.pointer || sym->attr.allocatable
107       || (sym->as && sym->as->rank > 0))
108     proc->attr.always_explicit = 1;
109
110   formal_arg_flag = 1;
111
112   for (f = proc->formal; f; f = f->next)
113     {
114       sym = f->sym;
115
116       if (sym == NULL)
117         {
118           /* Alternate return placeholder.  */
119           if (gfc_elemental (proc))
120             gfc_error ("Alternate return specifier in elemental subroutine "
121                        "'%s' at %L is not allowed", proc->name,
122                        &proc->declared_at);
123           if (proc->attr.function)
124             gfc_error ("Alternate return specifier in function "
125                        "'%s' at %L is not allowed", proc->name,
126                        &proc->declared_at);
127           continue;
128         }
129
130       if (sym->attr.if_source != IFSRC_UNKNOWN)
131         resolve_formal_arglist (sym);
132
133       if (sym->attr.subroutine || sym->attr.external || sym->attr.intrinsic)
134         {
135           if (gfc_pure (proc) && !gfc_pure (sym))
136             {
137               gfc_error ("Dummy procedure '%s' of PURE procedure at %L must "
138                          "also be PURE", sym->name, &sym->declared_at);
139               continue;
140             }
141
142           if (gfc_elemental (proc))
143             {
144               gfc_error ("Dummy procedure at %L not allowed in ELEMENTAL "
145                          "procedure", &sym->declared_at);
146               continue;
147             }
148
149           if (sym->attr.function
150                 && sym->ts.type == BT_UNKNOWN
151                 && sym->attr.intrinsic)
152             {
153               gfc_intrinsic_sym *isym;
154               isym = gfc_find_function (sym->name);
155               if (isym == NULL || !isym->specific)
156                 {
157                   gfc_error ("Unable to find a specific INTRINSIC procedure "
158                              "for the reference '%s' at %L", sym->name,
159                              &sym->declared_at);
160                 }
161               sym->ts = isym->ts;
162             }
163
164           continue;
165         }
166
167       if (sym->ts.type == BT_UNKNOWN)
168         {
169           if (!sym->attr.function || sym->result == sym)
170             gfc_set_default_type (sym, 1, sym->ns);
171         }
172
173       gfc_resolve_array_spec (sym->as, 0);
174
175       /* We can't tell if an array with dimension (:) is assumed or deferred
176          shape until we know if it has the pointer or allocatable attributes.
177       */
178       if (sym->as && sym->as->rank > 0 && sym->as->type == AS_DEFERRED
179           && !(sym->attr.pointer || sym->attr.allocatable))
180         {
181           sym->as->type = AS_ASSUMED_SHAPE;
182           for (i = 0; i < sym->as->rank; i++)
183             sym->as->lower[i] = gfc_int_expr (1);
184         }
185
186       if ((sym->as && sym->as->rank > 0 && sym->as->type == AS_ASSUMED_SHAPE)
187           || sym->attr.pointer || sym->attr.allocatable || sym->attr.target
188           || sym->attr.optional)
189         proc->attr.always_explicit = 1;
190
191       /* If the flavor is unknown at this point, it has to be a variable.
192          A procedure specification would have already set the type.  */
193
194       if (sym->attr.flavor == FL_UNKNOWN)
195         gfc_add_flavor (&sym->attr, FL_VARIABLE, sym->name, &sym->declared_at);
196
197       if (gfc_pure (proc) && !sym->attr.pointer
198           && sym->attr.flavor != FL_PROCEDURE)
199         {
200           if (proc->attr.function && sym->attr.intent != INTENT_IN)
201             gfc_error ("Argument '%s' of pure function '%s' at %L must be "
202                        "INTENT(IN)", sym->name, proc->name,
203                        &sym->declared_at);
204
205           if (proc->attr.subroutine && sym->attr.intent == INTENT_UNKNOWN)
206             gfc_error ("Argument '%s' of pure subroutine '%s' at %L must "
207                        "have its INTENT specified", sym->name, proc->name,
208                        &sym->declared_at);
209         }
210
211       if (gfc_elemental (proc))
212         {
213           if (sym->as != NULL)
214             {
215               gfc_error ("Argument '%s' of elemental procedure at %L must "
216                          "be scalar", sym->name, &sym->declared_at);
217               continue;
218             }
219
220           if (sym->attr.pointer)
221             {
222               gfc_error ("Argument '%s' of elemental procedure at %L cannot "
223                          "have the POINTER attribute", sym->name,
224                          &sym->declared_at);
225               continue;
226             }
227         }
228
229       /* Each dummy shall be specified to be scalar.  */
230       if (proc->attr.proc == PROC_ST_FUNCTION)
231         {
232           if (sym->as != NULL)
233             {
234               gfc_error ("Argument '%s' of statement function at %L must "
235                          "be scalar", sym->name, &sym->declared_at);
236               continue;
237             }
238
239           if (sym->ts.type == BT_CHARACTER)
240             {
241               gfc_charlen *cl = sym->ts.cl;
242               if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
243                 {
244                   gfc_error ("Character-valued argument '%s' of statement "
245                              "function at %L must have constant length",
246                              sym->name, &sym->declared_at);
247                   continue;
248                 }
249             }
250         }
251     }
252   formal_arg_flag = 0;
253 }
254
255
256 /* Work function called when searching for symbols that have argument lists
257    associated with them.  */
258
259 static void
260 find_arglists (gfc_symbol *sym)
261 {
262   if (sym->attr.if_source == IFSRC_UNKNOWN || sym->ns != gfc_current_ns)
263     return;
264
265   resolve_formal_arglist (sym);
266 }
267
268
269 /* Given a namespace, resolve all formal argument lists within the namespace.
270  */
271
272 static void
273 resolve_formal_arglists (gfc_namespace *ns)
274 {
275   if (ns == NULL)
276     return;
277
278   gfc_traverse_ns (ns, find_arglists);
279 }
280
281
282 static void
283 resolve_contained_fntype (gfc_symbol *sym, gfc_namespace *ns)
284 {
285   try t;
286
287   /* If this namespace is not a function or an entry master function,
288      ignore it.  */
289   if (! sym || !(sym->attr.function || sym->attr.flavor == FL_VARIABLE)
290       || sym->attr.entry_master)
291     return;
292
293   /* Try to find out of what the return type is.  */
294   if (sym->result->ts.type == BT_UNKNOWN)
295     {
296       t = gfc_set_default_type (sym->result, 0, ns);
297
298       if (t == FAILURE && !sym->result->attr.untyped)
299         {
300           if (sym->result == sym)
301             gfc_error ("Contained function '%s' at %L has no IMPLICIT type",
302                        sym->name, &sym->declared_at);
303           else
304             gfc_error ("Result '%s' of contained function '%s' at %L has "
305                        "no IMPLICIT type", sym->result->name, sym->name,
306                        &sym->result->declared_at);
307           sym->result->attr.untyped = 1;
308         }
309     }
310
311   /* Fortran 95 Draft Standard, page 51, Section 5.1.1.5, on the Character 
312      type, lists the only ways a character length value of * can be used:
313      dummy arguments of procedures, named constants, and function results
314      in external functions.  Internal function results are not on that list;
315      ergo, not permitted.  */
316
317   if (sym->result->ts.type == BT_CHARACTER)
318     {
319       gfc_charlen *cl = sym->result->ts.cl;
320       if (!cl || !cl->length)
321         gfc_error ("Character-valued internal function '%s' at %L must "
322                    "not be assumed length", sym->name, &sym->declared_at);
323     }
324 }
325
326
327 /* Add NEW_ARGS to the formal argument list of PROC, taking care not to
328    introduce duplicates.  */
329
330 static void
331 merge_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
332 {
333   gfc_formal_arglist *f, *new_arglist;
334   gfc_symbol *new_sym;
335
336   for (; new_args != NULL; new_args = new_args->next)
337     {
338       new_sym = new_args->sym;
339       /* See if this arg is already in the formal argument list.  */
340       for (f = proc->formal; f; f = f->next)
341         {
342           if (new_sym == f->sym)
343             break;
344         }
345
346       if (f)
347         continue;
348
349       /* Add a new argument.  Argument order is not important.  */
350       new_arglist = gfc_get_formal_arglist ();
351       new_arglist->sym = new_sym;
352       new_arglist->next = proc->formal;
353       proc->formal  = new_arglist;
354     }
355 }
356
357
358 /* Flag the arguments that are not present in all entries.  */
359
360 static void
361 check_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
362 {
363   gfc_formal_arglist *f, *head;
364   head = new_args;
365
366   for (f = proc->formal; f; f = f->next)
367     {
368       if (f->sym == NULL)
369         continue;
370
371       for (new_args = head; new_args; new_args = new_args->next)
372         {
373           if (new_args->sym == f->sym)
374             break;
375         }
376
377       if (new_args)
378         continue;
379
380       f->sym->attr.not_always_present = 1;
381     }
382 }
383
384
385 /* Resolve alternate entry points.  If a symbol has multiple entry points we
386    create a new master symbol for the main routine, and turn the existing
387    symbol into an entry point.  */
388
389 static void
390 resolve_entries (gfc_namespace *ns)
391 {
392   gfc_namespace *old_ns;
393   gfc_code *c;
394   gfc_symbol *proc;
395   gfc_entry_list *el;
396   char name[GFC_MAX_SYMBOL_LEN + 1];
397   static int master_count = 0;
398
399   if (ns->proc_name == NULL)
400     return;
401
402   /* No need to do anything if this procedure doesn't have alternate entry
403      points.  */
404   if (!ns->entries)
405     return;
406
407   /* We may already have resolved alternate entry points.  */
408   if (ns->proc_name->attr.entry_master)
409     return;
410
411   /* If this isn't a procedure something has gone horribly wrong.  */
412   gcc_assert (ns->proc_name->attr.flavor == FL_PROCEDURE);
413
414   /* Remember the current namespace.  */
415   old_ns = gfc_current_ns;
416
417   gfc_current_ns = ns;
418
419   /* Add the main entry point to the list of entry points.  */
420   el = gfc_get_entry_list ();
421   el->sym = ns->proc_name;
422   el->id = 0;
423   el->next = ns->entries;
424   ns->entries = el;
425   ns->proc_name->attr.entry = 1;
426
427   /* If it is a module function, it needs to be in the right namespace
428      so that gfc_get_fake_result_decl can gather up the results. The
429      need for this arose in get_proc_name, where these beasts were
430      left in their own namespace, to keep prior references linked to
431      the entry declaration.*/
432   if (ns->proc_name->attr.function
433       && ns->parent && ns->parent->proc_name->attr.flavor == FL_MODULE)
434     el->sym->ns = ns;
435
436   /* Do the same for entries where the master is not a module
437      procedure.  These are retained in the module namespace because
438      of the module procedure declaration.  */
439   for (el = el->next; el; el = el->next)
440     if (el->sym->ns->proc_name->attr.flavor == FL_MODULE
441           && el->sym->attr.mod_proc)
442       el->sym->ns = ns;
443   el = ns->entries;
444
445   /* Add an entry statement for it.  */
446   c = gfc_get_code ();
447   c->op = EXEC_ENTRY;
448   c->ext.entry = el;
449   c->next = ns->code;
450   ns->code = c;
451
452   /* Create a new symbol for the master function.  */
453   /* Give the internal function a unique name (within this file).
454      Also include the function name so the user has some hope of figuring
455      out what is going on.  */
456   snprintf (name, GFC_MAX_SYMBOL_LEN, "master.%d.%s",
457             master_count++, ns->proc_name->name);
458   gfc_get_ha_symbol (name, &proc);
459   gcc_assert (proc != NULL);
460
461   gfc_add_procedure (&proc->attr, PROC_INTERNAL, proc->name, NULL);
462   if (ns->proc_name->attr.subroutine)
463     gfc_add_subroutine (&proc->attr, proc->name, NULL);
464   else
465     {
466       gfc_symbol *sym;
467       gfc_typespec *ts, *fts;
468       gfc_array_spec *as, *fas;
469       gfc_add_function (&proc->attr, proc->name, NULL);
470       proc->result = proc;
471       fas = ns->entries->sym->as;
472       fas = fas ? fas : ns->entries->sym->result->as;
473       fts = &ns->entries->sym->result->ts;
474       if (fts->type == BT_UNKNOWN)
475         fts = gfc_get_default_type (ns->entries->sym->result, NULL);
476       for (el = ns->entries->next; el; el = el->next)
477         {
478           ts = &el->sym->result->ts;
479           as = el->sym->as;
480           as = as ? as : el->sym->result->as;
481           if (ts->type == BT_UNKNOWN)
482             ts = gfc_get_default_type (el->sym->result, NULL);
483
484           if (! gfc_compare_types (ts, fts)
485               || (el->sym->result->attr.dimension
486                   != ns->entries->sym->result->attr.dimension)
487               || (el->sym->result->attr.pointer
488                   != ns->entries->sym->result->attr.pointer))
489             break;
490
491           else if (as && fas && gfc_compare_array_spec (as, fas) == 0)
492             gfc_error ("Procedure %s at %L has entries with mismatched "
493                        "array specifications", ns->entries->sym->name,
494                        &ns->entries->sym->declared_at);
495         }
496
497       if (el == NULL)
498         {
499           sym = ns->entries->sym->result;
500           /* All result types the same.  */
501           proc->ts = *fts;
502           if (sym->attr.dimension)
503             gfc_set_array_spec (proc, gfc_copy_array_spec (sym->as), NULL);
504           if (sym->attr.pointer)
505             gfc_add_pointer (&proc->attr, NULL);
506         }
507       else
508         {
509           /* Otherwise the result will be passed through a union by
510              reference.  */
511           proc->attr.mixed_entry_master = 1;
512           for (el = ns->entries; el; el = el->next)
513             {
514               sym = el->sym->result;
515               if (sym->attr.dimension)
516                 {
517                   if (el == ns->entries)
518                     gfc_error ("FUNCTION result %s can't be an array in "
519                                "FUNCTION %s at %L", sym->name,
520                                ns->entries->sym->name, &sym->declared_at);
521                   else
522                     gfc_error ("ENTRY result %s can't be an array in "
523                                "FUNCTION %s at %L", sym->name,
524                                ns->entries->sym->name, &sym->declared_at);
525                 }
526               else if (sym->attr.pointer)
527                 {
528                   if (el == ns->entries)
529                     gfc_error ("FUNCTION result %s can't be a POINTER in "
530                                "FUNCTION %s at %L", sym->name,
531                                ns->entries->sym->name, &sym->declared_at);
532                   else
533                     gfc_error ("ENTRY result %s can't be a POINTER in "
534                                "FUNCTION %s at %L", sym->name,
535                                ns->entries->sym->name, &sym->declared_at);
536                 }
537               else
538                 {
539                   ts = &sym->ts;
540                   if (ts->type == BT_UNKNOWN)
541                     ts = gfc_get_default_type (sym, NULL);
542                   switch (ts->type)
543                     {
544                     case BT_INTEGER:
545                       if (ts->kind == gfc_default_integer_kind)
546                         sym = NULL;
547                       break;
548                     case BT_REAL:
549                       if (ts->kind == gfc_default_real_kind
550                           || ts->kind == gfc_default_double_kind)
551                         sym = NULL;
552                       break;
553                     case BT_COMPLEX:
554                       if (ts->kind == gfc_default_complex_kind)
555                         sym = NULL;
556                       break;
557                     case BT_LOGICAL:
558                       if (ts->kind == gfc_default_logical_kind)
559                         sym = NULL;
560                       break;
561                     case BT_UNKNOWN:
562                       /* We will issue error elsewhere.  */
563                       sym = NULL;
564                       break;
565                     default:
566                       break;
567                     }
568                   if (sym)
569                     {
570                       if (el == ns->entries)
571                         gfc_error ("FUNCTION result %s can't be of type %s "
572                                    "in FUNCTION %s at %L", sym->name,
573                                    gfc_typename (ts), ns->entries->sym->name,
574                                    &sym->declared_at);
575                       else
576                         gfc_error ("ENTRY result %s can't be of type %s "
577                                    "in FUNCTION %s at %L", sym->name,
578                                    gfc_typename (ts), ns->entries->sym->name,
579                                    &sym->declared_at);
580                     }
581                 }
582             }
583         }
584     }
585   proc->attr.access = ACCESS_PRIVATE;
586   proc->attr.entry_master = 1;
587
588   /* Merge all the entry point arguments.  */
589   for (el = ns->entries; el; el = el->next)
590     merge_argument_lists (proc, el->sym->formal);
591
592   /* Check the master formal arguments for any that are not
593      present in all entry points.  */
594   for (el = ns->entries; el; el = el->next)
595     check_argument_lists (proc, el->sym->formal);
596
597   /* Use the master function for the function body.  */
598   ns->proc_name = proc;
599
600   /* Finalize the new symbols.  */
601   gfc_commit_symbols ();
602
603   /* Restore the original namespace.  */
604   gfc_current_ns = old_ns;
605 }
606
607
608 static bool
609 has_default_initializer (gfc_symbol *der)
610 {
611   gfc_component *c;
612
613   gcc_assert (der->attr.flavor == FL_DERIVED);
614   for (c = der->components; c; c = c->next)
615     if ((c->ts.type != BT_DERIVED && c->initializer)
616         || (c->ts.type == BT_DERIVED
617             && (!c->pointer && has_default_initializer (c->ts.derived))))
618       break;
619
620   return c != NULL;
621 }
622
623
624 /* Resolve common blocks.  */
625 static void
626 resolve_common_blocks (gfc_symtree *common_root)
627 {
628   gfc_symbol *sym, *csym;
629
630   if (common_root == NULL)
631     return;
632
633   if (common_root->left)
634     resolve_common_blocks (common_root->left);
635   if (common_root->right)
636     resolve_common_blocks (common_root->right);
637
638   for (csym = common_root->n.common->head; csym; csym = csym->common_next)
639     {
640       if (csym->ts.type != BT_DERIVED)
641         continue;
642
643       if (!(csym->ts.derived->attr.sequence
644             || csym->ts.derived->attr.is_bind_c))
645         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
646                        "has neither the SEQUENCE nor the BIND(C) "
647                        "attribute", csym->name, &csym->declared_at);
648       if (csym->ts.derived->attr.alloc_comp)
649         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
650                        "has an ultimate component that is "
651                        "allocatable", csym->name, &csym->declared_at);
652       if (has_default_initializer (csym->ts.derived))
653         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
654                        "may not have default initializer", csym->name,
655                        &csym->declared_at);
656     }
657
658   gfc_find_symbol (common_root->name, gfc_current_ns, 0, &sym);
659   if (sym == NULL)
660     return;
661
662   if (sym->attr.flavor == FL_PARAMETER)
663     gfc_error ("COMMON block '%s' at %L is used as PARAMETER at %L",
664                sym->name, &common_root->n.common->where, &sym->declared_at);
665
666   if (sym->attr.intrinsic)
667     gfc_error ("COMMON block '%s' at %L is also an intrinsic procedure",
668                sym->name, &common_root->n.common->where);
669   else if (sym->attr.result
670            ||(sym->attr.function && gfc_current_ns->proc_name == sym))
671     gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
672                     "that is also a function result", sym->name,
673                     &common_root->n.common->where);
674   else if (sym->attr.flavor == FL_PROCEDURE && sym->attr.proc != PROC_INTERNAL
675            && sym->attr.proc != PROC_ST_FUNCTION)
676     gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
677                     "that is also a global procedure", sym->name,
678                     &common_root->n.common->where);
679 }
680
681
682 /* Resolve contained function types.  Because contained functions can call one
683    another, they have to be worked out before any of the contained procedures
684    can be resolved.
685
686    The good news is that if a function doesn't already have a type, the only
687    way it can get one is through an IMPLICIT type or a RESULT variable, because
688    by definition contained functions are contained namespace they're contained
689    in, not in a sibling or parent namespace.  */
690
691 static void
692 resolve_contained_functions (gfc_namespace *ns)
693 {
694   gfc_namespace *child;
695   gfc_entry_list *el;
696
697   resolve_formal_arglists (ns);
698
699   for (child = ns->contained; child; child = child->sibling)
700     {
701       /* Resolve alternate entry points first.  */
702       resolve_entries (child);
703
704       /* Then check function return types.  */
705       resolve_contained_fntype (child->proc_name, child);
706       for (el = child->entries; el; el = el->next)
707         resolve_contained_fntype (el->sym, child);
708     }
709 }
710
711
712 /* Resolve all of the elements of a structure constructor and make sure that
713    the types are correct.  */
714
715 static try
716 resolve_structure_cons (gfc_expr *expr)
717 {
718   gfc_constructor *cons;
719   gfc_component *comp;
720   try t;
721   symbol_attribute a;
722
723   t = SUCCESS;
724   cons = expr->value.constructor;
725   /* A constructor may have references if it is the result of substituting a
726      parameter variable.  In this case we just pull out the component we
727      want.  */
728   if (expr->ref)
729     comp = expr->ref->u.c.sym->components;
730   else
731     comp = expr->ts.derived->components;
732
733   /* See if the user is trying to invoke a structure constructor for one of
734      the iso_c_binding derived types.  */
735   if (expr->ts.derived && expr->ts.derived->ts.is_iso_c && cons
736       && cons->expr != NULL)
737     {
738       gfc_error ("Components of structure constructor '%s' at %L are PRIVATE",
739                  expr->ts.derived->name, &(expr->where));
740       return FAILURE;
741     }
742
743   for (; comp; comp = comp->next, cons = cons->next)
744     {
745       int rank;
746
747       if (!cons->expr)
748         continue;
749
750       if (gfc_resolve_expr (cons->expr) == FAILURE)
751         {
752           t = FAILURE;
753           continue;
754         }
755
756       rank = comp->as ? comp->as->rank : 0;
757       if (cons->expr->expr_type != EXPR_NULL && rank != cons->expr->rank
758           && (comp->allocatable || cons->expr->rank))
759         {
760           gfc_error ("The rank of the element in the derived type "
761                      "constructor at %L does not match that of the "
762                      "component (%d/%d)", &cons->expr->where,
763                      cons->expr->rank, rank);
764           t = FAILURE;
765         }
766
767       /* If we don't have the right type, try to convert it.  */
768
769       if (!gfc_compare_types (&cons->expr->ts, &comp->ts))
770         {
771           t = FAILURE;
772           if (comp->pointer && cons->expr->ts.type != BT_UNKNOWN)
773             gfc_error ("The element in the derived type constructor at %L, "
774                        "for pointer component '%s', is %s but should be %s",
775                        &cons->expr->where, comp->name,
776                        gfc_basic_typename (cons->expr->ts.type),
777                        gfc_basic_typename (comp->ts.type));
778           else
779             t = gfc_convert_type (cons->expr, &comp->ts, 1);
780         }
781
782       if (!comp->pointer || cons->expr->expr_type == EXPR_NULL)
783         continue;
784
785       a = gfc_expr_attr (cons->expr);
786
787       if (!a.pointer && !a.target)
788         {
789           t = FAILURE;
790           gfc_error ("The element in the derived type constructor at %L, "
791                      "for pointer component '%s' should be a POINTER or "
792                      "a TARGET", &cons->expr->where, comp->name);
793         }
794     }
795
796   return t;
797 }
798
799
800 /****************** Expression name resolution ******************/
801
802 /* Returns 0 if a symbol was not declared with a type or
803    attribute declaration statement, nonzero otherwise.  */
804
805 static int
806 was_declared (gfc_symbol *sym)
807 {
808   symbol_attribute a;
809
810   a = sym->attr;
811
812   if (!a.implicit_type && sym->ts.type != BT_UNKNOWN)
813     return 1;
814
815   if (a.allocatable || a.dimension || a.dummy || a.external || a.intrinsic
816       || a.optional || a.pointer || a.save || a.target || a.volatile_
817       || a.value || a.access != ACCESS_UNKNOWN || a.intent != INTENT_UNKNOWN)
818     return 1;
819
820   return 0;
821 }
822
823
824 /* Determine if a symbol is generic or not.  */
825
826 static int
827 generic_sym (gfc_symbol *sym)
828 {
829   gfc_symbol *s;
830
831   if (sym->attr.generic ||
832       (sym->attr.intrinsic && gfc_generic_intrinsic (sym->name)))
833     return 1;
834
835   if (was_declared (sym) || sym->ns->parent == NULL)
836     return 0;
837
838   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
839   
840   if (s != NULL)
841     {
842       if (s == sym)
843         return 0;
844       else
845         return generic_sym (s);
846     }
847
848   return 0;
849 }
850
851
852 /* Determine if a symbol is specific or not.  */
853
854 static int
855 specific_sym (gfc_symbol *sym)
856 {
857   gfc_symbol *s;
858
859   if (sym->attr.if_source == IFSRC_IFBODY
860       || sym->attr.proc == PROC_MODULE
861       || sym->attr.proc == PROC_INTERNAL
862       || sym->attr.proc == PROC_ST_FUNCTION
863       || (sym->attr.intrinsic && gfc_specific_intrinsic (sym->name))
864       || sym->attr.external)
865     return 1;
866
867   if (was_declared (sym) || sym->ns->parent == NULL)
868     return 0;
869
870   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
871
872   return (s == NULL) ? 0 : specific_sym (s);
873 }
874
875
876 /* Figure out if the procedure is specific, generic or unknown.  */
877
878 typedef enum
879 { PTYPE_GENERIC = 1, PTYPE_SPECIFIC, PTYPE_UNKNOWN }
880 proc_type;
881
882 static proc_type
883 procedure_kind (gfc_symbol *sym)
884 {
885   if (generic_sym (sym))
886     return PTYPE_GENERIC;
887
888   if (specific_sym (sym))
889     return PTYPE_SPECIFIC;
890
891   return PTYPE_UNKNOWN;
892 }
893
894 /* Check references to assumed size arrays.  The flag need_full_assumed_size
895    is nonzero when matching actual arguments.  */
896
897 static int need_full_assumed_size = 0;
898
899 static bool
900 check_assumed_size_reference (gfc_symbol *sym, gfc_expr *e)
901 {
902   gfc_ref *ref;
903   int dim;
904   int last = 1;
905
906   if (need_full_assumed_size || !(sym->as && sym->as->type == AS_ASSUMED_SIZE))
907       return false;
908
909   for (ref = e->ref; ref; ref = ref->next)
910     if (ref->type == REF_ARRAY)
911       for (dim = 0; dim < ref->u.ar.as->rank; dim++)
912         last = (ref->u.ar.end[dim] == NULL)
913                && (ref->u.ar.type == DIMEN_ELEMENT);
914
915   if (last)
916     {
917       gfc_error ("The upper bound in the last dimension must "
918                  "appear in the reference to the assumed size "
919                  "array '%s' at %L", sym->name, &e->where);
920       return true;
921     }
922   return false;
923 }
924
925
926 /* Look for bad assumed size array references in argument expressions
927   of elemental and array valued intrinsic procedures.  Since this is
928   called from procedure resolution functions, it only recurses at
929   operators.  */
930
931 static bool
932 resolve_assumed_size_actual (gfc_expr *e)
933 {
934   if (e == NULL)
935    return false;
936
937   switch (e->expr_type)
938     {
939     case EXPR_VARIABLE:
940       if (e->symtree && check_assumed_size_reference (e->symtree->n.sym, e))
941         return true;
942       break;
943
944     case EXPR_OP:
945       if (resolve_assumed_size_actual (e->value.op.op1)
946           || resolve_assumed_size_actual (e->value.op.op2))
947         return true;
948       break;
949
950     default:
951       break;
952     }
953   return false;
954 }
955
956
957 /* Resolve an actual argument list.  Most of the time, this is just
958    resolving the expressions in the list.
959    The exception is that we sometimes have to decide whether arguments
960    that look like procedure arguments are really simple variable
961    references.  */
962
963 static try
964 resolve_actual_arglist (gfc_actual_arglist *arg, procedure_type ptype)
965 {
966   gfc_symbol *sym;
967   gfc_symtree *parent_st;
968   gfc_expr *e;
969
970   for (; arg; arg = arg->next)
971     {
972       e = arg->expr;
973       if (e == NULL)
974         {
975           /* Check the label is a valid branching target.  */
976           if (arg->label)
977             {
978               if (arg->label->defined == ST_LABEL_UNKNOWN)
979                 {
980                   gfc_error ("Label %d referenced at %L is never defined",
981                              arg->label->value, &arg->label->where);
982                   return FAILURE;
983                 }
984             }
985           continue;
986         }
987
988       if (e->expr_type == FL_VARIABLE && e->symtree->ambiguous)
989         {
990           gfc_error ("'%s' at %L is ambiguous", e->symtree->n.sym->name,
991                      &e->where);
992           return FAILURE;
993         }
994
995       if (e->ts.type != BT_PROCEDURE)
996         {
997           if (gfc_resolve_expr (e) != SUCCESS)
998             return FAILURE;
999           goto argument_list;
1000         }
1001
1002       /* See if the expression node should really be a variable reference.  */
1003
1004       sym = e->symtree->n.sym;
1005
1006       if (sym->attr.flavor == FL_PROCEDURE
1007           || sym->attr.intrinsic
1008           || sym->attr.external)
1009         {
1010           int actual_ok;
1011
1012           /* If a procedure is not already determined to be something else
1013              check if it is intrinsic.  */
1014           if (!sym->attr.intrinsic
1015               && !(sym->attr.external || sym->attr.use_assoc
1016                    || sym->attr.if_source == IFSRC_IFBODY)
1017               && gfc_intrinsic_name (sym->name, sym->attr.subroutine))
1018             sym->attr.intrinsic = 1;
1019
1020           if (sym->attr.proc == PROC_ST_FUNCTION)
1021             {
1022               gfc_error ("Statement function '%s' at %L is not allowed as an "
1023                          "actual argument", sym->name, &e->where);
1024             }
1025
1026           actual_ok = gfc_intrinsic_actual_ok (sym->name,
1027                                                sym->attr.subroutine);
1028           if (sym->attr.intrinsic && actual_ok == 0)
1029             {
1030               gfc_error ("Intrinsic '%s' at %L is not allowed as an "
1031                          "actual argument", sym->name, &e->where);
1032             }
1033
1034           if (sym->attr.contained && !sym->attr.use_assoc
1035               && sym->ns->proc_name->attr.flavor != FL_MODULE)
1036             {
1037               gfc_error ("Internal procedure '%s' is not allowed as an "
1038                          "actual argument at %L", sym->name, &e->where);
1039             }
1040
1041           if (sym->attr.elemental && !sym->attr.intrinsic)
1042             {
1043               gfc_error ("ELEMENTAL non-INTRINSIC procedure '%s' is not "
1044                          "allowed as an actual argument at %L", sym->name,
1045                          &e->where);
1046             }
1047
1048           /* Check if a generic interface has a specific procedure
1049             with the same name before emitting an error.  */
1050           if (sym->attr.generic)
1051             {
1052               gfc_interface *p;
1053               for (p = sym->generic; p; p = p->next)
1054                 if (strcmp (sym->name, p->sym->name) == 0)
1055                   {
1056                     e->symtree = gfc_find_symtree
1057                                            (p->sym->ns->sym_root, sym->name);
1058                     sym = p->sym;
1059                     break;
1060                   }
1061
1062               if (p == NULL || e->symtree == NULL)
1063                 gfc_error ("GENERIC procedure '%s' is not "
1064                            "allowed as an actual argument at %L", sym->name,
1065                            &e->where);
1066             }
1067
1068           /* If the symbol is the function that names the current (or
1069              parent) scope, then we really have a variable reference.  */
1070
1071           if (sym->attr.function && sym->result == sym
1072               && (sym->ns->proc_name == sym
1073                   || (sym->ns->parent != NULL
1074                       && sym->ns->parent->proc_name == sym)))
1075             goto got_variable;
1076
1077           /* If all else fails, see if we have a specific intrinsic.  */
1078           if (sym->ts.type == BT_UNKNOWN && sym->attr.intrinsic)
1079             {
1080               gfc_intrinsic_sym *isym;
1081
1082               isym = gfc_find_function (sym->name);
1083               if (isym == NULL || !isym->specific)
1084                 {
1085                   gfc_error ("Unable to find a specific INTRINSIC procedure "
1086                              "for the reference '%s' at %L", sym->name,
1087                              &e->where);
1088                   return FAILURE;
1089                 }
1090               sym->ts = isym->ts;
1091               sym->attr.intrinsic = 1;
1092               sym->attr.function = 1;
1093             }
1094           goto argument_list;
1095         }
1096
1097       /* See if the name is a module procedure in a parent unit.  */
1098
1099       if (was_declared (sym) || sym->ns->parent == NULL)
1100         goto got_variable;
1101
1102       if (gfc_find_sym_tree (sym->name, sym->ns->parent, 1, &parent_st))
1103         {
1104           gfc_error ("Symbol '%s' at %L is ambiguous", sym->name, &e->where);
1105           return FAILURE;
1106         }
1107
1108       if (parent_st == NULL)
1109         goto got_variable;
1110
1111       sym = parent_st->n.sym;
1112       e->symtree = parent_st;           /* Point to the right thing.  */
1113
1114       if (sym->attr.flavor == FL_PROCEDURE
1115           || sym->attr.intrinsic
1116           || sym->attr.external)
1117         {
1118           goto argument_list;
1119         }
1120
1121     got_variable:
1122       e->expr_type = EXPR_VARIABLE;
1123       e->ts = sym->ts;
1124       if (sym->as != NULL)
1125         {
1126           e->rank = sym->as->rank;
1127           e->ref = gfc_get_ref ();
1128           e->ref->type = REF_ARRAY;
1129           e->ref->u.ar.type = AR_FULL;
1130           e->ref->u.ar.as = sym->as;
1131         }
1132
1133       /* Expressions are assigned a default ts.type of BT_PROCEDURE in
1134          primary.c (match_actual_arg). If above code determines that it
1135          is a  variable instead, it needs to be resolved as it was not
1136          done at the beginning of this function.  */
1137       if (gfc_resolve_expr (e) != SUCCESS)
1138         return FAILURE;
1139
1140     argument_list:
1141       /* Check argument list functions %VAL, %LOC and %REF.  There is
1142          nothing to do for %REF.  */
1143       if (arg->name && arg->name[0] == '%')
1144         {
1145           if (strncmp ("%VAL", arg->name, 4) == 0)
1146             {
1147               if (e->ts.type == BT_CHARACTER || e->ts.type == BT_DERIVED)
1148                 {
1149                   gfc_error ("By-value argument at %L is not of numeric "
1150                              "type", &e->where);
1151                   return FAILURE;
1152                 }
1153
1154               if (e->rank)
1155                 {
1156                   gfc_error ("By-value argument at %L cannot be an array or "
1157                              "an array section", &e->where);
1158                 return FAILURE;
1159                 }
1160
1161               /* Intrinsics are still PROC_UNKNOWN here.  However,
1162                  since same file external procedures are not resolvable
1163                  in gfortran, it is a good deal easier to leave them to
1164                  intrinsic.c.  */
1165               if (ptype != PROC_UNKNOWN
1166                   && ptype != PROC_DUMMY
1167                   && ptype != PROC_EXTERNAL
1168                   && ptype != PROC_MODULE)
1169                 {
1170                   gfc_error ("By-value argument at %L is not allowed "
1171                              "in this context", &e->where);
1172                   return FAILURE;
1173                 }
1174             }
1175
1176           /* Statement functions have already been excluded above.  */
1177           else if (strncmp ("%LOC", arg->name, 4) == 0
1178                    && e->ts.type == BT_PROCEDURE)
1179             {
1180               if (e->symtree->n.sym->attr.proc == PROC_INTERNAL)
1181                 {
1182                   gfc_error ("Passing internal procedure at %L by location "
1183                              "not allowed", &e->where);
1184                   return FAILURE;
1185                 }
1186             }
1187         }
1188     }
1189
1190   return SUCCESS;
1191 }
1192
1193
1194 /* Do the checks of the actual argument list that are specific to elemental
1195    procedures.  If called with c == NULL, we have a function, otherwise if
1196    expr == NULL, we have a subroutine.  */
1197
1198 static try
1199 resolve_elemental_actual (gfc_expr *expr, gfc_code *c)
1200 {
1201   gfc_actual_arglist *arg0;
1202   gfc_actual_arglist *arg;
1203   gfc_symbol *esym = NULL;
1204   gfc_intrinsic_sym *isym = NULL;
1205   gfc_expr *e = NULL;
1206   gfc_intrinsic_arg *iformal = NULL;
1207   gfc_formal_arglist *eformal = NULL;
1208   bool formal_optional = false;
1209   bool set_by_optional = false;
1210   int i;
1211   int rank = 0;
1212
1213   /* Is this an elemental procedure?  */
1214   if (expr && expr->value.function.actual != NULL)
1215     {
1216       if (expr->value.function.esym != NULL
1217           && expr->value.function.esym->attr.elemental)
1218         {
1219           arg0 = expr->value.function.actual;
1220           esym = expr->value.function.esym;
1221         }
1222       else if (expr->value.function.isym != NULL
1223                && expr->value.function.isym->elemental)
1224         {
1225           arg0 = expr->value.function.actual;
1226           isym = expr->value.function.isym;
1227         }
1228       else
1229         return SUCCESS;
1230     }
1231   else if (c && c->ext.actual != NULL && c->symtree->n.sym->attr.elemental)
1232     {
1233       arg0 = c->ext.actual;
1234       esym = c->symtree->n.sym;
1235     }
1236   else
1237     return SUCCESS;
1238
1239   /* The rank of an elemental is the rank of its array argument(s).  */
1240   for (arg = arg0; arg; arg = arg->next)
1241     {
1242       if (arg->expr != NULL && arg->expr->rank > 0)
1243         {
1244           rank = arg->expr->rank;
1245           if (arg->expr->expr_type == EXPR_VARIABLE
1246               && arg->expr->symtree->n.sym->attr.optional)
1247             set_by_optional = true;
1248
1249           /* Function specific; set the result rank and shape.  */
1250           if (expr)
1251             {
1252               expr->rank = rank;
1253               if (!expr->shape && arg->expr->shape)
1254                 {
1255                   expr->shape = gfc_get_shape (rank);
1256                   for (i = 0; i < rank; i++)
1257                     mpz_init_set (expr->shape[i], arg->expr->shape[i]);
1258                 }
1259             }
1260           break;
1261         }
1262     }
1263
1264   /* If it is an array, it shall not be supplied as an actual argument
1265      to an elemental procedure unless an array of the same rank is supplied
1266      as an actual argument corresponding to a nonoptional dummy argument of
1267      that elemental procedure(12.4.1.5).  */
1268   formal_optional = false;
1269   if (isym)
1270     iformal = isym->formal;
1271   else
1272     eformal = esym->formal;
1273
1274   for (arg = arg0; arg; arg = arg->next)
1275     {
1276       if (eformal)
1277         {
1278           if (eformal->sym && eformal->sym->attr.optional)
1279             formal_optional = true;
1280           eformal = eformal->next;
1281         }
1282       else if (isym && iformal)
1283         {
1284           if (iformal->optional)
1285             formal_optional = true;
1286           iformal = iformal->next;
1287         }
1288       else if (isym)
1289         formal_optional = true;
1290
1291       if (pedantic && arg->expr != NULL
1292           && arg->expr->expr_type == EXPR_VARIABLE
1293           && arg->expr->symtree->n.sym->attr.optional
1294           && formal_optional
1295           && arg->expr->rank
1296           && (set_by_optional || arg->expr->rank != rank)
1297           && !(isym && isym->id == GFC_ISYM_CONVERSION))
1298         {
1299           gfc_warning ("'%s' at %L is an array and OPTIONAL; IF IT IS "
1300                        "MISSING, it cannot be the actual argument of an "
1301                        "ELEMENTAL procedure unless there is a non-optional "
1302                        "argument with the same rank (12.4.1.5)",
1303                        arg->expr->symtree->n.sym->name, &arg->expr->where);
1304           return FAILURE;
1305         }
1306     }
1307
1308   for (arg = arg0; arg; arg = arg->next)
1309     {
1310       if (arg->expr == NULL || arg->expr->rank == 0)
1311         continue;
1312
1313       /* Being elemental, the last upper bound of an assumed size array
1314          argument must be present.  */
1315       if (resolve_assumed_size_actual (arg->expr))
1316         return FAILURE;
1317
1318       /* Elemental procedure's array actual arguments must conform.  */
1319       if (e != NULL)
1320         {
1321           if (gfc_check_conformance ("elemental procedure", arg->expr, e)
1322               == FAILURE)
1323             return FAILURE;
1324         }
1325       else
1326         e = arg->expr;
1327     }
1328
1329   /* INTENT(OUT) is only allowed for subroutines; if any actual argument
1330      is an array, the intent inout/out variable needs to be also an array.  */
1331   if (rank > 0 && esym && expr == NULL)
1332     for (eformal = esym->formal, arg = arg0; arg && eformal;
1333          arg = arg->next, eformal = eformal->next)
1334       if ((eformal->sym->attr.intent == INTENT_OUT
1335            || eformal->sym->attr.intent == INTENT_INOUT)
1336           && arg->expr && arg->expr->rank == 0)
1337         {
1338           gfc_error ("Actual argument at %L for INTENT(%s) dummy '%s' of "
1339                      "ELEMENTAL subroutine '%s' is a scalar, but another "
1340                      "actual argument is an array", &arg->expr->where,
1341                      (eformal->sym->attr.intent == INTENT_OUT) ? "OUT"
1342                      : "INOUT", eformal->sym->name, esym->name);
1343           return FAILURE;
1344         }
1345   return SUCCESS;
1346 }
1347
1348
1349 /* Go through each actual argument in ACTUAL and see if it can be
1350    implemented as an inlined, non-copying intrinsic.  FNSYM is the
1351    function being called, or NULL if not known.  */
1352
1353 static void
1354 find_noncopying_intrinsics (gfc_symbol *fnsym, gfc_actual_arglist *actual)
1355 {
1356   gfc_actual_arglist *ap;
1357   gfc_expr *expr;
1358
1359   for (ap = actual; ap; ap = ap->next)
1360     if (ap->expr
1361         && (expr = gfc_get_noncopying_intrinsic_argument (ap->expr))
1362         && !gfc_check_fncall_dependency (expr, INTENT_IN, fnsym, actual))
1363       ap->expr->inline_noncopying_intrinsic = 1;
1364 }
1365
1366
1367 /* This function does the checking of references to global procedures
1368    as defined in sections 18.1 and 14.1, respectively, of the Fortran
1369    77 and 95 standards.  It checks for a gsymbol for the name, making
1370    one if it does not already exist.  If it already exists, then the
1371    reference being resolved must correspond to the type of gsymbol.
1372    Otherwise, the new symbol is equipped with the attributes of the
1373    reference.  The corresponding code that is called in creating
1374    global entities is parse.c.  */
1375
1376 static void
1377 resolve_global_procedure (gfc_symbol *sym, locus *where, int sub)
1378 {
1379   gfc_gsymbol * gsym;
1380   unsigned int type;
1381
1382   type = sub ? GSYM_SUBROUTINE : GSYM_FUNCTION;
1383
1384   gsym = gfc_get_gsymbol (sym->name);
1385
1386   if ((gsym->type != GSYM_UNKNOWN && gsym->type != type))
1387     gfc_global_used (gsym, where);
1388
1389   if (gsym->type == GSYM_UNKNOWN)
1390     {
1391       gsym->type = type;
1392       gsym->where = *where;
1393     }
1394
1395   gsym->used = 1;
1396 }
1397
1398
1399 /************* Function resolution *************/
1400
1401 /* Resolve a function call known to be generic.
1402    Section 14.1.2.4.1.  */
1403
1404 static match
1405 resolve_generic_f0 (gfc_expr *expr, gfc_symbol *sym)
1406 {
1407   gfc_symbol *s;
1408
1409   if (sym->attr.generic)
1410     {
1411       s = gfc_search_interface (sym->generic, 0, &expr->value.function.actual);
1412       if (s != NULL)
1413         {
1414           expr->value.function.name = s->name;
1415           expr->value.function.esym = s;
1416
1417           if (s->ts.type != BT_UNKNOWN)
1418             expr->ts = s->ts;
1419           else if (s->result != NULL && s->result->ts.type != BT_UNKNOWN)
1420             expr->ts = s->result->ts;
1421
1422           if (s->as != NULL)
1423             expr->rank = s->as->rank;
1424           else if (s->result != NULL && s->result->as != NULL)
1425             expr->rank = s->result->as->rank;
1426
1427           return MATCH_YES;
1428         }
1429
1430       /* TODO: Need to search for elemental references in generic
1431          interface.  */
1432     }
1433
1434   if (sym->attr.intrinsic)
1435     return gfc_intrinsic_func_interface (expr, 0);
1436
1437   return MATCH_NO;
1438 }
1439
1440
1441 static try
1442 resolve_generic_f (gfc_expr *expr)
1443 {
1444   gfc_symbol *sym;
1445   match m;
1446
1447   sym = expr->symtree->n.sym;
1448
1449   for (;;)
1450     {
1451       m = resolve_generic_f0 (expr, sym);
1452       if (m == MATCH_YES)
1453         return SUCCESS;
1454       else if (m == MATCH_ERROR)
1455         return FAILURE;
1456
1457 generic:
1458       if (sym->ns->parent == NULL)
1459         break;
1460       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
1461
1462       if (sym == NULL)
1463         break;
1464       if (!generic_sym (sym))
1465         goto generic;
1466     }
1467
1468   /* Last ditch attempt.  See if the reference is to an intrinsic
1469      that possesses a matching interface.  14.1.2.4  */
1470   if (sym && !gfc_intrinsic_name (sym->name, 0))
1471     {
1472       gfc_error ("There is no specific function for the generic '%s' at %L",
1473                  expr->symtree->n.sym->name, &expr->where);
1474       return FAILURE;
1475     }
1476
1477   m = gfc_intrinsic_func_interface (expr, 0);
1478   if (m == MATCH_YES)
1479     return SUCCESS;
1480   if (m == MATCH_NO)
1481     gfc_error ("Generic function '%s' at %L is not consistent with a "
1482                "specific intrinsic interface", expr->symtree->n.sym->name,
1483                &expr->where);
1484
1485   return FAILURE;
1486 }
1487
1488
1489 /* Resolve a function call known to be specific.  */
1490
1491 static match
1492 resolve_specific_f0 (gfc_symbol *sym, gfc_expr *expr)
1493 {
1494   match m;
1495
1496   /* See if we have an intrinsic interface.  */
1497
1498   if (sym->interface != NULL && sym->interface->attr.intrinsic)
1499     {
1500       gfc_intrinsic_sym *isym;
1501       isym = gfc_find_function (sym->interface->name);
1502
1503       /* Existance of isym should be checked already.  */
1504       gcc_assert (isym);
1505
1506       sym->ts = isym->ts;
1507       sym->attr.function = 1;
1508       sym->attr.proc = PROC_EXTERNAL;
1509       goto found;
1510     }
1511
1512   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
1513     {
1514       if (sym->attr.dummy)
1515         {
1516           sym->attr.proc = PROC_DUMMY;
1517           goto found;
1518         }
1519
1520       sym->attr.proc = PROC_EXTERNAL;
1521       goto found;
1522     }
1523
1524   if (sym->attr.proc == PROC_MODULE
1525       || sym->attr.proc == PROC_ST_FUNCTION
1526       || sym->attr.proc == PROC_INTERNAL)
1527     goto found;
1528
1529   if (sym->attr.intrinsic)
1530     {
1531       m = gfc_intrinsic_func_interface (expr, 1);
1532       if (m == MATCH_YES)
1533         return MATCH_YES;
1534       if (m == MATCH_NO)
1535         gfc_error ("Function '%s' at %L is INTRINSIC but is not compatible "
1536                    "with an intrinsic", sym->name, &expr->where);
1537
1538       return MATCH_ERROR;
1539     }
1540
1541   return MATCH_NO;
1542
1543 found:
1544   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
1545
1546   expr->ts = sym->ts;
1547   expr->value.function.name = sym->name;
1548   expr->value.function.esym = sym;
1549   if (sym->as != NULL)
1550     expr->rank = sym->as->rank;
1551
1552   return MATCH_YES;
1553 }
1554
1555
1556 static try
1557 resolve_specific_f (gfc_expr *expr)
1558 {
1559   gfc_symbol *sym;
1560   match m;
1561
1562   sym = expr->symtree->n.sym;
1563
1564   for (;;)
1565     {
1566       m = resolve_specific_f0 (sym, expr);
1567       if (m == MATCH_YES)
1568         return SUCCESS;
1569       if (m == MATCH_ERROR)
1570         return FAILURE;
1571
1572       if (sym->ns->parent == NULL)
1573         break;
1574
1575       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
1576
1577       if (sym == NULL)
1578         break;
1579     }
1580
1581   gfc_error ("Unable to resolve the specific function '%s' at %L",
1582              expr->symtree->n.sym->name, &expr->where);
1583
1584   return SUCCESS;
1585 }
1586
1587
1588 /* Resolve a procedure call not known to be generic nor specific.  */
1589
1590 static try
1591 resolve_unknown_f (gfc_expr *expr)
1592 {
1593   gfc_symbol *sym;
1594   gfc_typespec *ts;
1595
1596   sym = expr->symtree->n.sym;
1597
1598   if (sym->attr.dummy)
1599     {
1600       sym->attr.proc = PROC_DUMMY;
1601       expr->value.function.name = sym->name;
1602       goto set_type;
1603     }
1604
1605   /* See if we have an intrinsic function reference.  */
1606
1607   if (gfc_intrinsic_name (sym->name, 0))
1608     {
1609       if (gfc_intrinsic_func_interface (expr, 1) == MATCH_YES)
1610         return SUCCESS;
1611       return FAILURE;
1612     }
1613
1614   /* The reference is to an external name.  */
1615
1616   sym->attr.proc = PROC_EXTERNAL;
1617   expr->value.function.name = sym->name;
1618   expr->value.function.esym = expr->symtree->n.sym;
1619
1620   if (sym->as != NULL)
1621     expr->rank = sym->as->rank;
1622
1623   /* Type of the expression is either the type of the symbol or the
1624      default type of the symbol.  */
1625
1626 set_type:
1627   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
1628
1629   if (sym->ts.type != BT_UNKNOWN)
1630     expr->ts = sym->ts;
1631   else
1632     {
1633       ts = gfc_get_default_type (sym, sym->ns);
1634
1635       if (ts->type == BT_UNKNOWN)
1636         {
1637           gfc_error ("Function '%s' at %L has no IMPLICIT type",
1638                      sym->name, &expr->where);
1639           return FAILURE;
1640         }
1641       else
1642         expr->ts = *ts;
1643     }
1644
1645   return SUCCESS;
1646 }
1647
1648
1649 /* Return true, if the symbol is an external procedure.  */
1650 static bool
1651 is_external_proc (gfc_symbol *sym)
1652 {
1653   if (!sym->attr.dummy && !sym->attr.contained
1654         && !(sym->attr.intrinsic
1655               || gfc_intrinsic_name (sym->name, sym->attr.subroutine))
1656         && sym->attr.proc != PROC_ST_FUNCTION
1657         && !sym->attr.use_assoc
1658         && sym->name)
1659     return true;
1660   else
1661     return false;
1662 }
1663
1664
1665 /* Figure out if a function reference is pure or not.  Also set the name
1666    of the function for a potential error message.  Return nonzero if the
1667    function is PURE, zero if not.  */
1668 static int
1669 pure_stmt_function (gfc_expr *, gfc_symbol *);
1670
1671 static int
1672 pure_function (gfc_expr *e, const char **name)
1673 {
1674   int pure;
1675
1676   *name = NULL;
1677
1678   if (e->symtree != NULL
1679         && e->symtree->n.sym != NULL
1680         && e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
1681     return pure_stmt_function (e, e->symtree->n.sym);
1682
1683   if (e->value.function.esym)
1684     {
1685       pure = gfc_pure (e->value.function.esym);
1686       *name = e->value.function.esym->name;
1687     }
1688   else if (e->value.function.isym)
1689     {
1690       pure = e->value.function.isym->pure
1691              || e->value.function.isym->elemental;
1692       *name = e->value.function.isym->name;
1693     }
1694   else
1695     {
1696       /* Implicit functions are not pure.  */
1697       pure = 0;
1698       *name = e->value.function.name;
1699     }
1700
1701   return pure;
1702 }
1703
1704
1705 static bool
1706 impure_stmt_fcn (gfc_expr *e, gfc_symbol *sym,
1707                  int *f ATTRIBUTE_UNUSED)
1708 {
1709   const char *name;
1710
1711   /* Don't bother recursing into other statement functions
1712      since they will be checked individually for purity.  */
1713   if (e->expr_type != EXPR_FUNCTION
1714         || !e->symtree
1715         || e->symtree->n.sym == sym
1716         || e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
1717     return false;
1718
1719   return pure_function (e, &name) ? false : true;
1720 }
1721
1722
1723 static int
1724 pure_stmt_function (gfc_expr *e, gfc_symbol *sym)
1725 {
1726   return gfc_traverse_expr (e, sym, impure_stmt_fcn, 0) ? 0 : 1;
1727 }
1728
1729
1730 static try
1731 is_scalar_expr_ptr (gfc_expr *expr)
1732 {
1733   try retval = SUCCESS;
1734   gfc_ref *ref;
1735   int start;
1736   int end;
1737
1738   /* See if we have a gfc_ref, which means we have a substring, array
1739      reference, or a component.  */
1740   if (expr->ref != NULL)
1741     {
1742       ref = expr->ref;
1743       while (ref->next != NULL)
1744         ref = ref->next;
1745
1746       switch (ref->type)
1747         {
1748         case REF_SUBSTRING:
1749           if (ref->u.ss.length != NULL 
1750               && ref->u.ss.length->length != NULL
1751               && ref->u.ss.start
1752               && ref->u.ss.start->expr_type == EXPR_CONSTANT 
1753               && ref->u.ss.end
1754               && ref->u.ss.end->expr_type == EXPR_CONSTANT)
1755             {
1756               start = (int) mpz_get_si (ref->u.ss.start->value.integer);
1757               end = (int) mpz_get_si (ref->u.ss.end->value.integer);
1758               if (end - start + 1 != 1)
1759                 retval = FAILURE;
1760             }
1761           else
1762             retval = FAILURE;
1763           break;
1764         case REF_ARRAY:
1765           if (ref->u.ar.type == AR_ELEMENT)
1766             retval = SUCCESS;
1767           else if (ref->u.ar.type == AR_FULL)
1768             {
1769               /* The user can give a full array if the array is of size 1.  */
1770               if (ref->u.ar.as != NULL
1771                   && ref->u.ar.as->rank == 1
1772                   && ref->u.ar.as->type == AS_EXPLICIT
1773                   && ref->u.ar.as->lower[0] != NULL
1774                   && ref->u.ar.as->lower[0]->expr_type == EXPR_CONSTANT
1775                   && ref->u.ar.as->upper[0] != NULL
1776                   && ref->u.ar.as->upper[0]->expr_type == EXPR_CONSTANT)
1777                 {
1778                   /* If we have a character string, we need to check if
1779                      its length is one.  */
1780                   if (expr->ts.type == BT_CHARACTER)
1781                     {
1782                       if (expr->ts.cl == NULL
1783                           || expr->ts.cl->length == NULL
1784                           || mpz_cmp_si (expr->ts.cl->length->value.integer, 1)
1785                           != 0)
1786                         retval = FAILURE;
1787                     }
1788                   else
1789                     {
1790                   /* We have constant lower and upper bounds.  If the
1791                      difference between is 1, it can be considered a
1792                      scalar.  */
1793                   start = (int) mpz_get_si
1794                                 (ref->u.ar.as->lower[0]->value.integer);
1795                   end = (int) mpz_get_si
1796                               (ref->u.ar.as->upper[0]->value.integer);
1797                   if (end - start + 1 != 1)
1798                     retval = FAILURE;
1799                 }
1800                 }
1801               else
1802                 retval = FAILURE;
1803             }
1804           else
1805             retval = FAILURE;
1806           break;
1807         default:
1808           retval = SUCCESS;
1809           break;
1810         }
1811     }
1812   else if (expr->ts.type == BT_CHARACTER && expr->rank == 0)
1813     {
1814       /* Character string.  Make sure it's of length 1.  */
1815       if (expr->ts.cl == NULL
1816           || expr->ts.cl->length == NULL
1817           || mpz_cmp_si (expr->ts.cl->length->value.integer, 1) != 0)
1818         retval = FAILURE;
1819     }
1820   else if (expr->rank != 0)
1821     retval = FAILURE;
1822
1823   return retval;
1824 }
1825
1826
1827 /* Match one of the iso_c_binding functions (c_associated or c_loc)
1828    and, in the case of c_associated, set the binding label based on
1829    the arguments.  */
1830
1831 static try
1832 gfc_iso_c_func_interface (gfc_symbol *sym, gfc_actual_arglist *args,
1833                           gfc_symbol **new_sym)
1834 {
1835   char name[GFC_MAX_SYMBOL_LEN + 1];
1836   char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
1837   int optional_arg = 0;
1838   try retval = SUCCESS;
1839   gfc_symbol *args_sym;
1840   gfc_typespec *arg_ts;
1841   gfc_ref *parent_ref;
1842   gfc_ref *curr_ref;
1843
1844   if (args->expr->expr_type == EXPR_CONSTANT
1845       || args->expr->expr_type == EXPR_OP
1846       || args->expr->expr_type == EXPR_NULL)
1847     {
1848       gfc_error ("Argument to '%s' at %L is not a variable",
1849                  sym->name, &(args->expr->where));
1850       return FAILURE;
1851     }
1852
1853   args_sym = args->expr->symtree->n.sym;
1854
1855   /* The typespec for the actual arg should be that stored in the expr
1856      and not necessarily that of the expr symbol (args_sym), because
1857      the actual expression could be a part-ref of the expr symbol.  */
1858   arg_ts = &(args->expr->ts);
1859
1860   /* Get the parent reference (if any) for the expression.  This happens for
1861      cases such as a%b%c.  */
1862   parent_ref = args->expr->ref;
1863   curr_ref = NULL;
1864   if (parent_ref != NULL)
1865     {
1866       curr_ref = parent_ref->next;
1867       while (curr_ref != NULL && curr_ref->next != NULL)
1868         {
1869           parent_ref = curr_ref;
1870           curr_ref = curr_ref->next;
1871         }
1872     }
1873
1874   /* If curr_ref is non-NULL, we had a part-ref expression.  If the curr_ref
1875      is for a REF_COMPONENT, then we need to use it as the parent_ref for
1876      the name, etc.  Otherwise, the current parent_ref should be correct.  */
1877   if (curr_ref != NULL && curr_ref->type == REF_COMPONENT)
1878     parent_ref = curr_ref;
1879
1880   if (parent_ref == args->expr->ref)
1881     parent_ref = NULL;
1882   else if (parent_ref != NULL && parent_ref->type != REF_COMPONENT)
1883     gfc_internal_error ("Unexpected expression reference type in "
1884                         "gfc_iso_c_func_interface");
1885
1886   if (sym->intmod_sym_id == ISOCBINDING_ASSOCIATED)
1887     {
1888       /* If the user gave two args then they are providing something for
1889          the optional arg (the second cptr).  Therefore, set the name and
1890          binding label to the c_associated for two cptrs.  Otherwise,
1891          set c_associated to expect one cptr.  */
1892       if (args->next)
1893         {
1894           /* two args.  */
1895           sprintf (name, "%s_2", sym->name);
1896           sprintf (binding_label, "%s_2", sym->binding_label);
1897           optional_arg = 1;
1898         }
1899       else
1900         {
1901           /* one arg.  */
1902           sprintf (name, "%s_1", sym->name);
1903           sprintf (binding_label, "%s_1", sym->binding_label);
1904           optional_arg = 0;
1905         }
1906
1907       /* Get a new symbol for the version of c_associated that
1908          will get called.  */
1909       *new_sym = get_iso_c_sym (sym, name, binding_label, optional_arg);
1910     }
1911   else if (sym->intmod_sym_id == ISOCBINDING_LOC
1912            || sym->intmod_sym_id == ISOCBINDING_FUNLOC)
1913     {
1914       sprintf (name, "%s", sym->name);
1915       sprintf (binding_label, "%s", sym->binding_label);
1916
1917       /* Error check the call.  */
1918       if (args->next != NULL)
1919         {
1920           gfc_error_now ("More actual than formal arguments in '%s' "
1921                          "call at %L", name, &(args->expr->where));
1922           retval = FAILURE;
1923         }
1924       else if (sym->intmod_sym_id == ISOCBINDING_LOC)
1925         {
1926           /* Make sure we have either the target or pointer attribute.  */
1927           if (!(args_sym->attr.target)
1928               && !(args_sym->attr.pointer)
1929               && (parent_ref == NULL ||
1930                   !parent_ref->u.c.component->pointer))
1931             {
1932               gfc_error_now ("Parameter '%s' to '%s' at %L must be either "
1933                              "a TARGET or an associated pointer",
1934                              args_sym->name,
1935                              sym->name, &(args->expr->where));
1936               retval = FAILURE;
1937             }
1938
1939           /* See if we have interoperable type and type param.  */
1940           if (verify_c_interop (arg_ts,
1941                                 (parent_ref ? parent_ref->u.c.component->name 
1942                                  : args_sym->name), 
1943                                 &(args->expr->where)) == SUCCESS
1944               || gfc_check_any_c_kind (arg_ts) == SUCCESS)
1945             {
1946               if (args_sym->attr.target == 1)
1947                 {
1948                   /* Case 1a, section 15.1.2.5, J3/04-007: variable that
1949                      has the target attribute and is interoperable.  */
1950                   /* Case 1b, section 15.1.2.5, J3/04-007: allocated
1951                      allocatable variable that has the TARGET attribute and
1952                      is not an array of zero size.  */
1953                   if (args_sym->attr.allocatable == 1)
1954                     {
1955                       if (args_sym->attr.dimension != 0 
1956                           && (args_sym->as && args_sym->as->rank == 0))
1957                         {
1958                           gfc_error_now ("Allocatable variable '%s' used as a "
1959                                          "parameter to '%s' at %L must not be "
1960                                          "an array of zero size",
1961                                          args_sym->name, sym->name,
1962                                          &(args->expr->where));
1963                           retval = FAILURE;
1964                         }
1965                     }
1966                   else
1967                     {
1968                       /* A non-allocatable target variable with C
1969                          interoperable type and type parameters must be
1970                          interoperable.  */
1971                       if (args_sym && args_sym->attr.dimension)
1972                         {
1973                           if (args_sym->as->type == AS_ASSUMED_SHAPE)
1974                             {
1975                               gfc_error ("Assumed-shape array '%s' at %L "
1976                                          "cannot be an argument to the "
1977                                          "procedure '%s' because "
1978                                          "it is not C interoperable",
1979                                          args_sym->name,
1980                                          &(args->expr->where), sym->name);
1981                               retval = FAILURE;
1982                             }
1983                           else if (args_sym->as->type == AS_DEFERRED)
1984                             {
1985                               gfc_error ("Deferred-shape array '%s' at %L "
1986                                          "cannot be an argument to the "
1987                                          "procedure '%s' because "
1988                                          "it is not C interoperable",
1989                                          args_sym->name,
1990                                          &(args->expr->where), sym->name);
1991                               retval = FAILURE;
1992                             }
1993                         }
1994                               
1995                       /* Make sure it's not a character string.  Arrays of
1996                          any type should be ok if the variable is of a C
1997                          interoperable type.  */
1998                       if (arg_ts->type == BT_CHARACTER)
1999                         if (arg_ts->cl != NULL
2000                             && (arg_ts->cl->length == NULL
2001                                 || arg_ts->cl->length->expr_type
2002                                    != EXPR_CONSTANT
2003                                 || mpz_cmp_si
2004                                     (arg_ts->cl->length->value.integer, 1)
2005                                    != 0)
2006                             && is_scalar_expr_ptr (args->expr) != SUCCESS)
2007                           {
2008                             gfc_error_now ("CHARACTER argument '%s' to '%s' "
2009                                            "at %L must have a length of 1",
2010                                            args_sym->name, sym->name,
2011                                            &(args->expr->where));
2012                             retval = FAILURE;
2013                           }
2014                     }
2015                 }
2016               else if ((args_sym->attr.pointer == 1 ||
2017                         (parent_ref != NULL 
2018                          && parent_ref->u.c.component->pointer))
2019                        && is_scalar_expr_ptr (args->expr) != SUCCESS)
2020                 {
2021                   /* Case 1c, section 15.1.2.5, J3/04-007: an associated
2022                      scalar pointer.  */
2023                   gfc_error_now ("Argument '%s' to '%s' at %L must be an "
2024                                  "associated scalar POINTER", args_sym->name,
2025                                  sym->name, &(args->expr->where));
2026                   retval = FAILURE;
2027                 }
2028             }
2029           else
2030             {
2031               /* The parameter is not required to be C interoperable.  If it
2032                  is not C interoperable, it must be a nonpolymorphic scalar
2033                  with no length type parameters.  It still must have either
2034                  the pointer or target attribute, and it can be
2035                  allocatable (but must be allocated when c_loc is called).  */
2036               if (args->expr->rank != 0 
2037                   && is_scalar_expr_ptr (args->expr) != SUCCESS)
2038                 {
2039                   gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2040                                  "scalar", args_sym->name, sym->name,
2041                                  &(args->expr->where));
2042                   retval = FAILURE;
2043                 }
2044               else if (arg_ts->type == BT_CHARACTER 
2045                        && is_scalar_expr_ptr (args->expr) != SUCCESS)
2046                 {
2047                   gfc_error_now ("CHARACTER argument '%s' to '%s' at "
2048                                  "%L must have a length of 1",
2049                                  args_sym->name, sym->name,
2050                                  &(args->expr->where));
2051                   retval = FAILURE;
2052                 }
2053             }
2054         }
2055       else if (sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2056         {
2057           if (args_sym->attr.flavor != FL_PROCEDURE)
2058             {
2059               /* TODO: Update this error message to allow for procedure
2060                  pointers once they are implemented.  */
2061               gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2062                              "procedure",
2063                              args_sym->name, sym->name,
2064                              &(args->expr->where));
2065               retval = FAILURE;
2066             }
2067           else if (args_sym->attr.is_bind_c != 1)
2068             {
2069               gfc_error_now ("Parameter '%s' to '%s' at %L must be "
2070                              "BIND(C)",
2071                              args_sym->name, sym->name,
2072                              &(args->expr->where));
2073               retval = FAILURE;
2074             }
2075         }
2076       
2077       /* for c_loc/c_funloc, the new symbol is the same as the old one */
2078       *new_sym = sym;
2079     }
2080   else
2081     {
2082       gfc_internal_error ("gfc_iso_c_func_interface(): Unhandled "
2083                           "iso_c_binding function: '%s'!\n", sym->name);
2084     }
2085
2086   return retval;
2087 }
2088
2089
2090 /* Resolve a function call, which means resolving the arguments, then figuring
2091    out which entity the name refers to.  */
2092 /* TODO: Check procedure arguments so that an INTENT(IN) isn't passed
2093    to INTENT(OUT) or INTENT(INOUT).  */
2094
2095 static try
2096 resolve_function (gfc_expr *expr)
2097 {
2098   gfc_actual_arglist *arg;
2099   gfc_symbol *sym;
2100   const char *name;
2101   try t;
2102   int temp;
2103   procedure_type p = PROC_INTRINSIC;
2104
2105   sym = NULL;
2106   if (expr->symtree)
2107     sym = expr->symtree->n.sym;
2108
2109   if (sym && sym->attr.flavor == FL_VARIABLE)
2110     {
2111       gfc_error ("'%s' at %L is not a function", sym->name, &expr->where);
2112       return FAILURE;
2113     }
2114
2115   if (sym && sym->attr.abstract)
2116     {
2117       gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
2118                  sym->name, &expr->where);
2119       return FAILURE;
2120     }
2121
2122   /* If the procedure is external, check for usage.  */
2123   if (sym && is_external_proc (sym))
2124     resolve_global_procedure (sym, &expr->where, 0);
2125
2126   /* Switch off assumed size checking and do this again for certain kinds
2127      of procedure, once the procedure itself is resolved.  */
2128   need_full_assumed_size++;
2129
2130   if (expr->symtree && expr->symtree->n.sym)
2131     p = expr->symtree->n.sym->attr.proc;
2132
2133   if (resolve_actual_arglist (expr->value.function.actual, p) == FAILURE)
2134       return FAILURE;
2135
2136   /* Need to setup the call to the correct c_associated, depending on
2137      the number of cptrs to user gives to compare.  */
2138   if (sym && sym->attr.is_iso_c == 1)
2139     {
2140       if (gfc_iso_c_func_interface (sym, expr->value.function.actual, &sym)
2141           == FAILURE)
2142         return FAILURE;
2143       
2144       /* Get the symtree for the new symbol (resolved func).
2145          the old one will be freed later, when it's no longer used.  */
2146       gfc_find_sym_tree (sym->name, sym->ns, 1, &(expr->symtree));
2147     }
2148   
2149   /* Resume assumed_size checking.  */
2150   need_full_assumed_size--;
2151
2152   if (sym && sym->ts.type == BT_CHARACTER
2153       && sym->ts.cl
2154       && sym->ts.cl->length == NULL
2155       && !sym->attr.dummy
2156       && expr->value.function.esym == NULL
2157       && !sym->attr.contained)
2158     {
2159       /* Internal procedures are taken care of in resolve_contained_fntype.  */
2160       gfc_error ("Function '%s' is declared CHARACTER(*) and cannot "
2161                  "be used at %L since it is not a dummy argument",
2162                  sym->name, &expr->where);
2163       return FAILURE;
2164     }
2165
2166   /* See if function is already resolved.  */
2167
2168   if (expr->value.function.name != NULL)
2169     {
2170       if (expr->ts.type == BT_UNKNOWN)
2171         expr->ts = sym->ts;
2172       t = SUCCESS;
2173     }
2174   else
2175     {
2176       /* Apply the rules of section 14.1.2.  */
2177
2178       switch (procedure_kind (sym))
2179         {
2180         case PTYPE_GENERIC:
2181           t = resolve_generic_f (expr);
2182           break;
2183
2184         case PTYPE_SPECIFIC:
2185           t = resolve_specific_f (expr);
2186           break;
2187
2188         case PTYPE_UNKNOWN:
2189           t = resolve_unknown_f (expr);
2190           break;
2191
2192         default:
2193           gfc_internal_error ("resolve_function(): bad function type");
2194         }
2195     }
2196
2197   /* If the expression is still a function (it might have simplified),
2198      then we check to see if we are calling an elemental function.  */
2199
2200   if (expr->expr_type != EXPR_FUNCTION)
2201     return t;
2202
2203   temp = need_full_assumed_size;
2204   need_full_assumed_size = 0;
2205
2206   if (resolve_elemental_actual (expr, NULL) == FAILURE)
2207     return FAILURE;
2208
2209   if (omp_workshare_flag
2210       && expr->value.function.esym
2211       && ! gfc_elemental (expr->value.function.esym))
2212     {
2213       gfc_error ("User defined non-ELEMENTAL function '%s' at %L not allowed "
2214                  "in WORKSHARE construct", expr->value.function.esym->name,
2215                  &expr->where);
2216       t = FAILURE;
2217     }
2218
2219 #define GENERIC_ID expr->value.function.isym->id
2220   else if (expr->value.function.actual != NULL
2221            && expr->value.function.isym != NULL
2222            && GENERIC_ID != GFC_ISYM_LBOUND
2223            && GENERIC_ID != GFC_ISYM_LEN
2224            && GENERIC_ID != GFC_ISYM_LOC
2225            && GENERIC_ID != GFC_ISYM_PRESENT)
2226     {
2227       /* Array intrinsics must also have the last upper bound of an
2228          assumed size array argument.  UBOUND and SIZE have to be
2229          excluded from the check if the second argument is anything
2230          than a constant.  */
2231       int inquiry;
2232       inquiry = GENERIC_ID == GFC_ISYM_UBOUND
2233                   || GENERIC_ID == GFC_ISYM_SIZE;
2234
2235       for (arg = expr->value.function.actual; arg; arg = arg->next)
2236         {
2237           if (inquiry && arg->next != NULL && arg->next->expr)
2238             {
2239               if (arg->next->expr->expr_type != EXPR_CONSTANT)
2240                 break;
2241
2242               if ((int)mpz_get_si (arg->next->expr->value.integer)
2243                         < arg->expr->rank)
2244                 break;
2245             }
2246
2247           if (arg->expr != NULL
2248               && arg->expr->rank > 0
2249               && resolve_assumed_size_actual (arg->expr))
2250             return FAILURE;
2251         }
2252     }
2253 #undef GENERIC_ID
2254
2255   need_full_assumed_size = temp;
2256   name = NULL;
2257
2258   if (!pure_function (expr, &name) && name)
2259     {
2260       if (forall_flag)
2261         {
2262           gfc_error ("reference to non-PURE function '%s' at %L inside a "
2263                      "FORALL %s", name, &expr->where,
2264                      forall_flag == 2 ? "mask" : "block");
2265           t = FAILURE;
2266         }
2267       else if (gfc_pure (NULL))
2268         {
2269           gfc_error ("Function reference to '%s' at %L is to a non-PURE "
2270                      "procedure within a PURE procedure", name, &expr->where);
2271           t = FAILURE;
2272         }
2273     }
2274
2275   /* Functions without the RECURSIVE attribution are not allowed to
2276    * call themselves.  */
2277   if (expr->value.function.esym && !expr->value.function.esym->attr.recursive)
2278     {
2279       gfc_symbol *esym, *proc;
2280       esym = expr->value.function.esym;
2281       proc = gfc_current_ns->proc_name;
2282       if (esym == proc)
2283       {
2284         gfc_error ("Function '%s' at %L cannot call itself, as it is not "
2285                    "RECURSIVE", name, &expr->where);
2286         t = FAILURE;
2287       }
2288
2289       if (esym->attr.entry && esym->ns->entries && proc->ns->entries
2290           && esym->ns->entries->sym == proc->ns->entries->sym)
2291       {
2292         gfc_error ("Call to ENTRY '%s' at %L is recursive, but function "
2293                    "'%s' is not declared as RECURSIVE",
2294                    esym->name, &expr->where, esym->ns->entries->sym->name);
2295         t = FAILURE;
2296       }
2297     }
2298
2299   /* Character lengths of use associated functions may contains references to
2300      symbols not referenced from the current program unit otherwise.  Make sure
2301      those symbols are marked as referenced.  */
2302
2303   if (expr->ts.type == BT_CHARACTER && expr->value.function.esym
2304       && expr->value.function.esym->attr.use_assoc)
2305     {
2306       gfc_expr_set_symbols_referenced (expr->ts.cl->length);
2307     }
2308
2309   if (t == SUCCESS)
2310     find_noncopying_intrinsics (expr->value.function.esym,
2311                                 expr->value.function.actual);
2312
2313   /* Make sure that the expression has a typespec that works.  */
2314   if (expr->ts.type == BT_UNKNOWN)
2315     {
2316       if (expr->symtree->n.sym->result
2317             && expr->symtree->n.sym->result->ts.type != BT_UNKNOWN)
2318         expr->ts = expr->symtree->n.sym->result->ts;
2319     }
2320
2321   return t;
2322 }
2323
2324
2325 /************* Subroutine resolution *************/
2326
2327 static void
2328 pure_subroutine (gfc_code *c, gfc_symbol *sym)
2329 {
2330   if (gfc_pure (sym))
2331     return;
2332
2333   if (forall_flag)
2334     gfc_error ("Subroutine call to '%s' in FORALL block at %L is not PURE",
2335                sym->name, &c->loc);
2336   else if (gfc_pure (NULL))
2337     gfc_error ("Subroutine call to '%s' at %L is not PURE", sym->name,
2338                &c->loc);
2339 }
2340
2341
2342 static match
2343 resolve_generic_s0 (gfc_code *c, gfc_symbol *sym)
2344 {
2345   gfc_symbol *s;
2346
2347   if (sym->attr.generic)
2348     {
2349       s = gfc_search_interface (sym->generic, 1, &c->ext.actual);
2350       if (s != NULL)
2351         {
2352           c->resolved_sym = s;
2353           pure_subroutine (c, s);
2354           return MATCH_YES;
2355         }
2356
2357       /* TODO: Need to search for elemental references in generic interface.  */
2358     }
2359
2360   if (sym->attr.intrinsic)
2361     return gfc_intrinsic_sub_interface (c, 0);
2362
2363   return MATCH_NO;
2364 }
2365
2366
2367 static try
2368 resolve_generic_s (gfc_code *c)
2369 {
2370   gfc_symbol *sym;
2371   match m;
2372
2373   sym = c->symtree->n.sym;
2374
2375   for (;;)
2376     {
2377       m = resolve_generic_s0 (c, sym);
2378       if (m == MATCH_YES)
2379         return SUCCESS;
2380       else if (m == MATCH_ERROR)
2381         return FAILURE;
2382
2383 generic:
2384       if (sym->ns->parent == NULL)
2385         break;
2386       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2387
2388       if (sym == NULL)
2389         break;
2390       if (!generic_sym (sym))
2391         goto generic;
2392     }
2393
2394   /* Last ditch attempt.  See if the reference is to an intrinsic
2395      that possesses a matching interface.  14.1.2.4  */
2396   sym = c->symtree->n.sym;
2397
2398   if (!gfc_intrinsic_name (sym->name, 1))
2399     {
2400       gfc_error ("There is no specific subroutine for the generic '%s' at %L",
2401                  sym->name, &c->loc);
2402       return FAILURE;
2403     }
2404
2405   m = gfc_intrinsic_sub_interface (c, 0);
2406   if (m == MATCH_YES)
2407     return SUCCESS;
2408   if (m == MATCH_NO)
2409     gfc_error ("Generic subroutine '%s' at %L is not consistent with an "
2410                "intrinsic subroutine interface", sym->name, &c->loc);
2411
2412   return FAILURE;
2413 }
2414
2415
2416 /* Set the name and binding label of the subroutine symbol in the call
2417    expression represented by 'c' to include the type and kind of the
2418    second parameter.  This function is for resolving the appropriate
2419    version of c_f_pointer() and c_f_procpointer().  For example, a
2420    call to c_f_pointer() for a default integer pointer could have a
2421    name of c_f_pointer_i4.  If no second arg exists, which is an error
2422    for these two functions, it defaults to the generic symbol's name
2423    and binding label.  */
2424
2425 static void
2426 set_name_and_label (gfc_code *c, gfc_symbol *sym,
2427                     char *name, char *binding_label)
2428 {
2429   gfc_expr *arg = NULL;
2430   char type;
2431   int kind;
2432
2433   /* The second arg of c_f_pointer and c_f_procpointer determines
2434      the type and kind for the procedure name.  */
2435   arg = c->ext.actual->next->expr;
2436
2437   if (arg != NULL)
2438     {
2439       /* Set up the name to have the given symbol's name,
2440          plus the type and kind.  */
2441       /* a derived type is marked with the type letter 'u' */
2442       if (arg->ts.type == BT_DERIVED)
2443         {
2444           type = 'd';
2445           kind = 0; /* set the kind as 0 for now */
2446         }
2447       else
2448         {
2449           type = gfc_type_letter (arg->ts.type);
2450           kind = arg->ts.kind;
2451         }
2452
2453       if (arg->ts.type == BT_CHARACTER)
2454         /* Kind info for character strings not needed.  */
2455         kind = 0;
2456
2457       sprintf (name, "%s_%c%d", sym->name, type, kind);
2458       /* Set up the binding label as the given symbol's label plus
2459          the type and kind.  */
2460       sprintf (binding_label, "%s_%c%d", sym->binding_label, type, kind);
2461     }
2462   else
2463     {
2464       /* If the second arg is missing, set the name and label as
2465          was, cause it should at least be found, and the missing
2466          arg error will be caught by compare_parameters().  */
2467       sprintf (name, "%s", sym->name);
2468       sprintf (binding_label, "%s", sym->binding_label);
2469     }
2470    
2471   return;
2472 }
2473
2474
2475 /* Resolve a generic version of the iso_c_binding procedure given
2476    (sym) to the specific one based on the type and kind of the
2477    argument(s).  Currently, this function resolves c_f_pointer() and
2478    c_f_procpointer based on the type and kind of the second argument
2479    (FPTR).  Other iso_c_binding procedures aren't specially handled.
2480    Upon successfully exiting, c->resolved_sym will hold the resolved
2481    symbol.  Returns MATCH_ERROR if an error occurred; MATCH_YES
2482    otherwise.  */
2483
2484 match
2485 gfc_iso_c_sub_interface (gfc_code *c, gfc_symbol *sym)
2486 {
2487   gfc_symbol *new_sym;
2488   /* this is fine, since we know the names won't use the max */
2489   char name[GFC_MAX_SYMBOL_LEN + 1];
2490   char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
2491   /* default to success; will override if find error */
2492   match m = MATCH_YES;
2493
2494   /* Make sure the actual arguments are in the necessary order (based on the 
2495      formal args) before resolving.  */
2496   gfc_procedure_use (sym, &c->ext.actual, &(c->loc));
2497
2498   if ((sym->intmod_sym_id == ISOCBINDING_F_POINTER) ||
2499       (sym->intmod_sym_id == ISOCBINDING_F_PROCPOINTER))
2500     {
2501       set_name_and_label (c, sym, name, binding_label);
2502       
2503       if (sym->intmod_sym_id == ISOCBINDING_F_POINTER)
2504         {
2505           if (c->ext.actual != NULL && c->ext.actual->next != NULL)
2506             {
2507               /* Make sure we got a third arg if the second arg has non-zero
2508                  rank.  We must also check that the type and rank are
2509                  correct since we short-circuit this check in
2510                  gfc_procedure_use() (called above to sort actual args).  */
2511               if (c->ext.actual->next->expr->rank != 0)
2512                 {
2513                   if(c->ext.actual->next->next == NULL 
2514                      || c->ext.actual->next->next->expr == NULL)
2515                     {
2516                       m = MATCH_ERROR;
2517                       gfc_error ("Missing SHAPE parameter for call to %s "
2518                                  "at %L", sym->name, &(c->loc));
2519                     }
2520                   else if (c->ext.actual->next->next->expr->ts.type
2521                            != BT_INTEGER
2522                            || c->ext.actual->next->next->expr->rank != 1)
2523                     {
2524                       m = MATCH_ERROR;
2525                       gfc_error ("SHAPE parameter for call to %s at %L must "
2526                                  "be a rank 1 INTEGER array", sym->name,
2527                                  &(c->loc));
2528                     }
2529                 }
2530             }
2531         }
2532       
2533       if (m != MATCH_ERROR)
2534         {
2535           /* the 1 means to add the optional arg to formal list */
2536           new_sym = get_iso_c_sym (sym, name, binding_label, 1);
2537          
2538           /* for error reporting, say it's declared where the original was */
2539           new_sym->declared_at = sym->declared_at;
2540         }
2541     }
2542   else
2543     {
2544       /* no differences for c_loc or c_funloc */
2545       new_sym = sym;
2546     }
2547
2548   /* set the resolved symbol */
2549   if (m != MATCH_ERROR)
2550     c->resolved_sym = new_sym;
2551   else
2552     c->resolved_sym = sym;
2553   
2554   return m;
2555 }
2556
2557
2558 /* Resolve a subroutine call known to be specific.  */
2559
2560 static match
2561 resolve_specific_s0 (gfc_code *c, gfc_symbol *sym)
2562 {
2563   match m;
2564
2565   /* See if we have an intrinsic interface.  */
2566   if (sym->interface != NULL && !sym->interface->attr.abstract
2567       && !sym->interface->attr.subroutine)
2568     {
2569       gfc_intrinsic_sym *isym;
2570
2571       isym = gfc_find_function (sym->interface->name);
2572
2573       /* Existance of isym should be checked already.  */
2574       gcc_assert (isym);
2575
2576       sym->ts = isym->ts;
2577       sym->attr.function = 1;
2578       goto found;
2579     }
2580
2581   if(sym->attr.is_iso_c)
2582     {
2583       m = gfc_iso_c_sub_interface (c,sym);
2584       return m;
2585     }
2586   
2587   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
2588     {
2589       if (sym->attr.dummy)
2590         {
2591           sym->attr.proc = PROC_DUMMY;
2592           goto found;
2593         }
2594
2595       sym->attr.proc = PROC_EXTERNAL;
2596       goto found;
2597     }
2598
2599   if (sym->attr.proc == PROC_MODULE || sym->attr.proc == PROC_INTERNAL)
2600     goto found;
2601
2602   if (sym->attr.intrinsic)
2603     {
2604       m = gfc_intrinsic_sub_interface (c, 1);
2605       if (m == MATCH_YES)
2606         return MATCH_YES;
2607       if (m == MATCH_NO)
2608         gfc_error ("Subroutine '%s' at %L is INTRINSIC but is not compatible "
2609                    "with an intrinsic", sym->name, &c->loc);
2610
2611       return MATCH_ERROR;
2612     }
2613
2614   return MATCH_NO;
2615
2616 found:
2617   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
2618
2619   c->resolved_sym = sym;
2620   pure_subroutine (c, sym);
2621
2622   return MATCH_YES;
2623 }
2624
2625
2626 static try
2627 resolve_specific_s (gfc_code *c)
2628 {
2629   gfc_symbol *sym;
2630   match m;
2631
2632   sym = c->symtree->n.sym;
2633
2634   for (;;)
2635     {
2636       m = resolve_specific_s0 (c, sym);
2637       if (m == MATCH_YES)
2638         return SUCCESS;
2639       if (m == MATCH_ERROR)
2640         return FAILURE;
2641
2642       if (sym->ns->parent == NULL)
2643         break;
2644
2645       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2646
2647       if (sym == NULL)
2648         break;
2649     }
2650
2651   sym = c->symtree->n.sym;
2652   gfc_error ("Unable to resolve the specific subroutine '%s' at %L",
2653              sym->name, &c->loc);
2654
2655   return FAILURE;
2656 }
2657
2658
2659 /* Resolve a subroutine call not known to be generic nor specific.  */
2660
2661 static try
2662 resolve_unknown_s (gfc_code *c)
2663 {
2664   gfc_symbol *sym;
2665
2666   sym = c->symtree->n.sym;
2667
2668   if (sym->attr.dummy)
2669     {
2670       sym->attr.proc = PROC_DUMMY;
2671       goto found;
2672     }
2673
2674   /* See if we have an intrinsic function reference.  */
2675
2676   if (gfc_intrinsic_name (sym->name, 1))
2677     {
2678       if (gfc_intrinsic_sub_interface (c, 1) == MATCH_YES)
2679         return SUCCESS;
2680       return FAILURE;
2681     }
2682
2683   /* The reference is to an external name.  */
2684
2685 found:
2686   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
2687
2688   c->resolved_sym = sym;
2689
2690   pure_subroutine (c, sym);
2691
2692   return SUCCESS;
2693 }
2694
2695
2696 /* Resolve a subroutine call.  Although it was tempting to use the same code
2697    for functions, subroutines and functions are stored differently and this
2698    makes things awkward.  */
2699
2700 static try
2701 resolve_call (gfc_code *c)
2702 {
2703   try t;
2704   procedure_type ptype = PROC_INTRINSIC;
2705
2706   if (c->symtree && c->symtree->n.sym
2707       && c->symtree->n.sym->ts.type != BT_UNKNOWN)
2708     {
2709       gfc_error ("'%s' at %L has a type, which is not consistent with "
2710                  "the CALL at %L", c->symtree->n.sym->name,
2711                  &c->symtree->n.sym->declared_at, &c->loc);
2712       return FAILURE;
2713     }
2714
2715   /* If external, check for usage.  */
2716   if (c->symtree && is_external_proc (c->symtree->n.sym))
2717     resolve_global_procedure (c->symtree->n.sym, &c->loc, 1);
2718
2719   /* Subroutines without the RECURSIVE attribution are not allowed to
2720    * call themselves.  */
2721   if (c->symtree && c->symtree->n.sym && !c->symtree->n.sym->attr.recursive)
2722     {
2723       gfc_symbol *csym, *proc;
2724       csym = c->symtree->n.sym;
2725       proc = gfc_current_ns->proc_name;
2726       if (csym == proc)
2727       {
2728         gfc_error ("SUBROUTINE '%s' at %L cannot call itself, as it is not "
2729                    "RECURSIVE", csym->name, &c->loc);
2730         t = FAILURE;
2731       }
2732
2733       if (csym->attr.entry && csym->ns->entries && proc->ns->entries
2734           && csym->ns->entries->sym == proc->ns->entries->sym)
2735       {
2736         gfc_error ("Call to ENTRY '%s' at %L is recursive, but subroutine "
2737                    "'%s' is not declared as RECURSIVE",
2738                    csym->name, &c->loc, csym->ns->entries->sym->name);
2739         t = FAILURE;
2740       }
2741     }
2742
2743   /* Switch off assumed size checking and do this again for certain kinds
2744      of procedure, once the procedure itself is resolved.  */
2745   need_full_assumed_size++;
2746
2747   if (c->symtree && c->symtree->n.sym)
2748     ptype = c->symtree->n.sym->attr.proc;
2749
2750   if (resolve_actual_arglist (c->ext.actual, ptype) == FAILURE)
2751     return FAILURE;
2752
2753   /* Resume assumed_size checking.  */
2754   need_full_assumed_size--;
2755
2756   t = SUCCESS;
2757   if (c->resolved_sym == NULL)
2758     switch (procedure_kind (c->symtree->n.sym))
2759       {
2760       case PTYPE_GENERIC:
2761         t = resolve_generic_s (c);
2762         break;
2763
2764       case PTYPE_SPECIFIC:
2765         t = resolve_specific_s (c);
2766         break;
2767
2768       case PTYPE_UNKNOWN:
2769         t = resolve_unknown_s (c);
2770         break;
2771
2772       default:
2773         gfc_internal_error ("resolve_subroutine(): bad function type");
2774       }
2775
2776   /* Some checks of elemental subroutine actual arguments.  */
2777   if (resolve_elemental_actual (NULL, c) == FAILURE)
2778     return FAILURE;
2779
2780   if (t == SUCCESS)
2781     find_noncopying_intrinsics (c->resolved_sym, c->ext.actual);
2782   return t;
2783 }
2784
2785
2786 /* Compare the shapes of two arrays that have non-NULL shapes.  If both
2787    op1->shape and op2->shape are non-NULL return SUCCESS if their shapes
2788    match.  If both op1->shape and op2->shape are non-NULL return FAILURE
2789    if their shapes do not match.  If either op1->shape or op2->shape is
2790    NULL, return SUCCESS.  */
2791
2792 static try
2793 compare_shapes (gfc_expr *op1, gfc_expr *op2)
2794 {
2795   try t;
2796   int i;
2797
2798   t = SUCCESS;
2799
2800   if (op1->shape != NULL && op2->shape != NULL)
2801     {
2802       for (i = 0; i < op1->rank; i++)
2803         {
2804           if (mpz_cmp (op1->shape[i], op2->shape[i]) != 0)
2805            {
2806              gfc_error ("Shapes for operands at %L and %L are not conformable",
2807                          &op1->where, &op2->where);
2808              t = FAILURE;
2809              break;
2810            }
2811         }
2812     }
2813
2814   return t;
2815 }
2816
2817
2818 /* Resolve an operator expression node.  This can involve replacing the
2819    operation with a user defined function call.  */
2820
2821 static try
2822 resolve_operator (gfc_expr *e)
2823 {
2824   gfc_expr *op1, *op2;
2825   char msg[200];
2826   bool dual_locus_error;
2827   try t;
2828
2829   /* Resolve all subnodes-- give them types.  */
2830
2831   switch (e->value.op.operator)
2832     {
2833     default:
2834       if (gfc_resolve_expr (e->value.op.op2) == FAILURE)
2835         return FAILURE;
2836
2837     /* Fall through...  */
2838
2839     case INTRINSIC_NOT:
2840     case INTRINSIC_UPLUS:
2841     case INTRINSIC_UMINUS:
2842     case INTRINSIC_PARENTHESES:
2843       if (gfc_resolve_expr (e->value.op.op1) == FAILURE)
2844         return FAILURE;
2845       break;
2846     }
2847
2848   /* Typecheck the new node.  */
2849
2850   op1 = e->value.op.op1;
2851   op2 = e->value.op.op2;
2852   dual_locus_error = false;
2853
2854   if ((op1 && op1->expr_type == EXPR_NULL)
2855       || (op2 && op2->expr_type == EXPR_NULL))
2856     {
2857       sprintf (msg, _("Invalid context for NULL() pointer at %%L"));
2858       goto bad_op;
2859     }
2860
2861   switch (e->value.op.operator)
2862     {
2863     case INTRINSIC_UPLUS:
2864     case INTRINSIC_UMINUS:
2865       if (op1->ts.type == BT_INTEGER
2866           || op1->ts.type == BT_REAL
2867           || op1->ts.type == BT_COMPLEX)
2868         {
2869           e->ts = op1->ts;
2870           break;
2871         }
2872
2873       sprintf (msg, _("Operand of unary numeric operator '%s' at %%L is %s"),
2874                gfc_op2string (e->value.op.operator), gfc_typename (&e->ts));
2875       goto bad_op;
2876
2877     case INTRINSIC_PLUS:
2878     case INTRINSIC_MINUS:
2879     case INTRINSIC_TIMES:
2880     case INTRINSIC_DIVIDE:
2881     case INTRINSIC_POWER:
2882       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
2883         {
2884           gfc_type_convert_binary (e);
2885           break;
2886         }
2887
2888       sprintf (msg,
2889                _("Operands of binary numeric operator '%s' at %%L are %s/%s"),
2890                gfc_op2string (e->value.op.operator), gfc_typename (&op1->ts),
2891                gfc_typename (&op2->ts));
2892       goto bad_op;
2893
2894     case INTRINSIC_CONCAT:
2895       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER)
2896         {
2897           e->ts.type = BT_CHARACTER;
2898           e->ts.kind = op1->ts.kind;
2899           break;
2900         }
2901
2902       sprintf (msg,
2903                _("Operands of string concatenation operator at %%L are %s/%s"),
2904                gfc_typename (&op1->ts), gfc_typename (&op2->ts));
2905       goto bad_op;
2906
2907     case INTRINSIC_AND:
2908     case INTRINSIC_OR:
2909     case INTRINSIC_EQV:
2910     case INTRINSIC_NEQV:
2911       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
2912         {
2913           e->ts.type = BT_LOGICAL;
2914           e->ts.kind = gfc_kind_max (op1, op2);
2915           if (op1->ts.kind < e->ts.kind)
2916             gfc_convert_type (op1, &e->ts, 2);
2917           else if (op2->ts.kind < e->ts.kind)
2918             gfc_convert_type (op2, &e->ts, 2);
2919           break;
2920         }
2921
2922       sprintf (msg, _("Operands of logical operator '%s' at %%L are %s/%s"),
2923                gfc_op2string (e->value.op.operator), gfc_typename (&op1->ts),
2924                gfc_typename (&op2->ts));
2925
2926       goto bad_op;
2927
2928     case INTRINSIC_NOT:
2929       if (op1->ts.type == BT_LOGICAL)
2930         {
2931           e->ts.type = BT_LOGICAL;
2932           e->ts.kind = op1->ts.kind;
2933           break;
2934         }
2935
2936       sprintf (msg, _("Operand of .not. operator at %%L is %s"),
2937                gfc_typename (&op1->ts));
2938       goto bad_op;
2939
2940     case INTRINSIC_GT:
2941     case INTRINSIC_GT_OS:
2942     case INTRINSIC_GE:
2943     case INTRINSIC_GE_OS:
2944     case INTRINSIC_LT:
2945     case INTRINSIC_LT_OS:
2946     case INTRINSIC_LE:
2947     case INTRINSIC_LE_OS:
2948       if (op1->ts.type == BT_COMPLEX || op2->ts.type == BT_COMPLEX)
2949         {
2950           strcpy (msg, _("COMPLEX quantities cannot be compared at %L"));
2951           goto bad_op;
2952         }
2953
2954       /* Fall through...  */
2955
2956     case INTRINSIC_EQ:
2957     case INTRINSIC_EQ_OS:
2958     case INTRINSIC_NE:
2959     case INTRINSIC_NE_OS:
2960       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER)
2961         {
2962           e->ts.type = BT_LOGICAL;
2963           e->ts.kind = gfc_default_logical_kind;
2964           break;
2965         }
2966
2967       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
2968         {
2969           gfc_type_convert_binary (e);
2970
2971           e->ts.type = BT_LOGICAL;
2972           e->ts.kind = gfc_default_logical_kind;
2973           break;
2974         }
2975
2976       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
2977         sprintf (msg,
2978                  _("Logicals at %%L must be compared with %s instead of %s"),
2979                  (e->value.op.operator == INTRINSIC_EQ 
2980                   || e->value.op.operator == INTRINSIC_EQ_OS)
2981                  ? ".eqv." : ".neqv.", gfc_op2string (e->value.op.operator));
2982       else
2983         sprintf (msg,
2984                  _("Operands of comparison operator '%s' at %%L are %s/%s"),
2985                  gfc_op2string (e->value.op.operator), gfc_typename (&op1->ts),
2986                  gfc_typename (&op2->ts));
2987
2988       goto bad_op;
2989
2990     case INTRINSIC_USER:
2991       if (e->value.op.uop->operator == NULL)
2992         sprintf (msg, _("Unknown operator '%s' at %%L"), e->value.op.uop->name);
2993       else if (op2 == NULL)
2994         sprintf (msg, _("Operand of user operator '%s' at %%L is %s"),
2995                  e->value.op.uop->name, gfc_typename (&op1->ts));
2996       else
2997         sprintf (msg, _("Operands of user operator '%s' at %%L are %s/%s"),
2998                  e->value.op.uop->name, gfc_typename (&op1->ts),
2999                  gfc_typename (&op2->ts));
3000
3001       goto bad_op;
3002
3003     case INTRINSIC_PARENTHESES:
3004       e->ts = op1->ts;
3005       if (e->ts.type == BT_CHARACTER)
3006         e->ts.cl = op1->ts.cl;
3007       break;
3008
3009     default:
3010       gfc_internal_error ("resolve_operator(): Bad intrinsic");
3011     }
3012
3013   /* Deal with arrayness of an operand through an operator.  */
3014
3015   t = SUCCESS;
3016
3017   switch (e->value.op.operator)
3018     {
3019     case INTRINSIC_PLUS:
3020     case INTRINSIC_MINUS:
3021     case INTRINSIC_TIMES:
3022     case INTRINSIC_DIVIDE:
3023     case INTRINSIC_POWER:
3024     case INTRINSIC_CONCAT:
3025     case INTRINSIC_AND:
3026     case INTRINSIC_OR:
3027     case INTRINSIC_EQV:
3028     case INTRINSIC_NEQV:
3029     case INTRINSIC_EQ:
3030     case INTRINSIC_EQ_OS:
3031     case INTRINSIC_NE:
3032     case INTRINSIC_NE_OS:
3033     case INTRINSIC_GT:
3034     case INTRINSIC_GT_OS:
3035     case INTRINSIC_GE:
3036     case INTRINSIC_GE_OS:
3037     case INTRINSIC_LT:
3038     case INTRINSIC_LT_OS:
3039     case INTRINSIC_LE:
3040     case INTRINSIC_LE_OS:
3041
3042       if (op1->rank == 0 && op2->rank == 0)
3043         e->rank = 0;
3044
3045       if (op1->rank == 0 && op2->rank != 0)
3046         {
3047           e->rank = op2->rank;
3048
3049           if (e->shape == NULL)
3050             e->shape = gfc_copy_shape (op2->shape, op2->rank);
3051         }
3052
3053       if (op1->rank != 0 && op2->rank == 0)
3054         {
3055           e->rank = op1->rank;
3056
3057           if (e->shape == NULL)
3058             e->shape = gfc_copy_shape (op1->shape, op1->rank);
3059         }
3060
3061       if (op1->rank != 0 && op2->rank != 0)
3062         {
3063           if (op1->rank == op2->rank)
3064             {
3065               e->rank = op1->rank;
3066               if (e->shape == NULL)
3067                 {
3068                   t = compare_shapes(op1, op2);
3069                   if (t == FAILURE)
3070                     e->shape = NULL;
3071                   else
3072                 e->shape = gfc_copy_shape (op1->shape, op1->rank);
3073                 }
3074             }
3075           else
3076             {
3077               /* Allow higher level expressions to work.  */
3078               e->rank = 0;
3079
3080               /* Try user-defined operators, and otherwise throw an error.  */
3081               dual_locus_error = true;
3082               sprintf (msg,
3083                        _("Inconsistent ranks for operator at %%L and %%L"));
3084               goto bad_op;
3085             }
3086         }
3087
3088       break;
3089
3090     case INTRINSIC_PARENTHESES:
3091     case INTRINSIC_NOT:
3092     case INTRINSIC_UPLUS:
3093     case INTRINSIC_UMINUS:
3094       /* Simply copy arrayness attribute */
3095       e->rank = op1->rank;
3096
3097       if (e->shape == NULL)
3098         e->shape = gfc_copy_shape (op1->shape, op1->rank);
3099
3100       break;
3101
3102     default:
3103       break;
3104     }
3105
3106   /* Attempt to simplify the expression.  */
3107   if (t == SUCCESS)
3108     {
3109       t = gfc_simplify_expr (e, 0);
3110       /* Some calls do not succeed in simplification and return FAILURE
3111          even though there is no error; eg. variable references to
3112          PARAMETER arrays.  */
3113       if (!gfc_is_constant_expr (e))
3114         t = SUCCESS;
3115     }
3116   return t;
3117
3118 bad_op:
3119
3120   if (gfc_extend_expr (e) == SUCCESS)
3121     return SUCCESS;
3122
3123   if (dual_locus_error)
3124     gfc_error (msg, &op1->where, &op2->where);
3125   else
3126     gfc_error (msg, &e->where);
3127
3128   return FAILURE;
3129 }
3130
3131
3132 /************** Array resolution subroutines **************/
3133
3134 typedef enum
3135 { CMP_LT, CMP_EQ, CMP_GT, CMP_UNKNOWN }
3136 comparison;
3137
3138 /* Compare two integer expressions.  */
3139
3140 static comparison
3141 compare_bound (gfc_expr *a, gfc_expr *b)
3142 {
3143   int i;
3144
3145   if (a == NULL || a->expr_type != EXPR_CONSTANT
3146       || b == NULL || b->expr_type != EXPR_CONSTANT)
3147     return CMP_UNKNOWN;
3148
3149   if (a->ts.type != BT_INTEGER || b->ts.type != BT_INTEGER)
3150     gfc_internal_error ("compare_bound(): Bad expression");
3151
3152   i = mpz_cmp (a->value.integer, b->value.integer);
3153
3154   if (i < 0)
3155     return CMP_LT;
3156   if (i > 0)
3157     return CMP_GT;
3158   return CMP_EQ;
3159 }
3160
3161
3162 /* Compare an integer expression with an integer.  */
3163
3164 static comparison
3165 compare_bound_int (gfc_expr *a, int b)
3166 {
3167   int i;
3168
3169   if (a == NULL || a->expr_type != EXPR_CONSTANT)
3170     return CMP_UNKNOWN;
3171
3172   if (a->ts.type != BT_INTEGER)
3173     gfc_internal_error ("compare_bound_int(): Bad expression");
3174
3175   i = mpz_cmp_si (a->value.integer, b);
3176
3177   if (i < 0)
3178     return CMP_LT;
3179   if (i > 0)
3180     return CMP_GT;
3181   return CMP_EQ;
3182 }
3183
3184
3185 /* Compare an integer expression with a mpz_t.  */
3186
3187 static comparison
3188 compare_bound_mpz_t (gfc_expr *a, mpz_t b)
3189 {
3190   int i;
3191
3192   if (a == NULL || a->expr_type != EXPR_CONSTANT)
3193     return CMP_UNKNOWN;
3194
3195   if (a->ts.type != BT_INTEGER)
3196     gfc_internal_error ("compare_bound_int(): Bad expression");
3197
3198   i = mpz_cmp (a->value.integer, b);
3199
3200   if (i < 0)
3201     return CMP_LT;
3202   if (i > 0)
3203     return CMP_GT;
3204   return CMP_EQ;
3205 }
3206
3207
3208 /* Compute the last value of a sequence given by a triplet.  
3209    Return 0 if it wasn't able to compute the last value, or if the
3210    sequence if empty, and 1 otherwise.  */
3211
3212 static int
3213 compute_last_value_for_triplet (gfc_expr *start, gfc_expr *end,
3214                                 gfc_expr *stride, mpz_t last)
3215 {
3216   mpz_t rem;
3217
3218   if (start == NULL || start->expr_type != EXPR_CONSTANT
3219       || end == NULL || end->expr_type != EXPR_CONSTANT
3220       || (stride != NULL && stride->expr_type != EXPR_CONSTANT))
3221     return 0;
3222
3223   if (start->ts.type != BT_INTEGER || end->ts.type != BT_INTEGER
3224       || (stride != NULL && stride->ts.type != BT_INTEGER))
3225     return 0;
3226
3227   if (stride == NULL || compare_bound_int(stride, 1) == CMP_EQ)
3228     {
3229       if (compare_bound (start, end) == CMP_GT)
3230         return 0;
3231       mpz_set (last, end->value.integer);
3232       return 1;
3233     }
3234
3235   if (compare_bound_int (stride, 0) == CMP_GT)
3236     {
3237       /* Stride is positive */
3238       if (mpz_cmp (start->value.integer, end->value.integer) > 0)
3239         return 0;
3240     }
3241   else
3242     {
3243       /* Stride is negative */
3244       if (mpz_cmp (start->value.integer, end->value.integer) < 0)
3245         return 0;
3246     }
3247
3248   mpz_init (rem);
3249   mpz_sub (rem, end->value.integer, start->value.integer);
3250   mpz_tdiv_r (rem, rem, stride->value.integer);
3251   mpz_sub (last, end->value.integer, rem);
3252   mpz_clear (rem);
3253
3254   return 1;
3255 }
3256
3257
3258 /* Compare a single dimension of an array reference to the array
3259    specification.  */
3260
3261 static try
3262 check_dimension (int i, gfc_array_ref *ar, gfc_array_spec *as)
3263 {
3264   mpz_t last_value;
3265
3266 /* Given start, end and stride values, calculate the minimum and
3267    maximum referenced indexes.  */
3268
3269   switch (ar->dimen_type[i])
3270     {
3271     case DIMEN_VECTOR:
3272       break;
3273
3274     case DIMEN_ELEMENT:
3275       if (compare_bound (ar->start[i], as->lower[i]) == CMP_LT)
3276         {
3277           gfc_warning ("Array reference at %L is out of bounds "
3278                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
3279                        mpz_get_si (ar->start[i]->value.integer),
3280                        mpz_get_si (as->lower[i]->value.integer), i+1);
3281           return SUCCESS;
3282         }
3283       if (compare_bound (ar->start[i], as->upper[i]) == CMP_GT)
3284         {
3285           gfc_warning ("Array reference at %L is out of bounds "
3286                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
3287                        mpz_get_si (ar->start[i]->value.integer),
3288                        mpz_get_si (as->upper[i]->value.integer), i+1);
3289           return SUCCESS;
3290         }
3291
3292       break;
3293
3294     case DIMEN_RANGE:
3295       {
3296 #define AR_START (ar->start[i] ? ar->start[i] : as->lower[i])
3297 #define AR_END (ar->end[i] ? ar->end[i] : as->upper[i])
3298
3299         comparison comp_start_end = compare_bound (AR_START, AR_END);
3300
3301         /* Check for zero stride, which is not allowed.  */
3302         if (compare_bound_int (ar->stride[i], 0) == CMP_EQ)
3303           {
3304             gfc_error ("Illegal stride of zero at %L", &ar->c_where[i]);
3305             return FAILURE;
3306           }
3307
3308         /* if start == len || (stride > 0 && start < len)
3309                            || (stride < 0 && start > len),
3310            then the array section contains at least one element.  In this
3311            case, there is an out-of-bounds access if
3312            (start < lower || start > upper).  */
3313         if (compare_bound (AR_START, AR_END) == CMP_EQ
3314             || ((compare_bound_int (ar->stride[i], 0) == CMP_GT
3315                  || ar->stride[i] == NULL) && comp_start_end == CMP_LT)
3316             || (compare_bound_int (ar->stride[i], 0) == CMP_LT
3317                 && comp_start_end == CMP_GT))
3318           {
3319             if (compare_bound (AR_START, as->lower[i]) == CMP_LT)
3320               {
3321                 gfc_warning ("Lower array reference at %L is out of bounds "
3322                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
3323                        mpz_get_si (AR_START->value.integer),
3324                        mpz_get_si (as->lower[i]->value.integer), i+1);
3325                 return SUCCESS;
3326               }
3327             if (compare_bound (AR_START, as->upper[i]) == CMP_GT)
3328               {
3329                 gfc_warning ("Lower array reference at %L is out of bounds "
3330                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
3331                        mpz_get_si (AR_START->value.integer),
3332                        mpz_get_si (as->upper[i]->value.integer), i+1);
3333                 return SUCCESS;
3334               }
3335           }
3336
3337         /* If we can compute the highest index of the array section,
3338            then it also has to be between lower and upper.  */
3339         mpz_init (last_value);
3340         if (compute_last_value_for_triplet (AR_START, AR_END, ar->stride[i],
3341                                             last_value))
3342           {
3343             if (compare_bound_mpz_t (as->lower[i], last_value) == CMP_GT)
3344               {
3345                 gfc_warning ("Upper array reference at %L is out of bounds "
3346                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
3347                        mpz_get_si (last_value),
3348                        mpz_get_si (as->lower[i]->value.integer), i+1);
3349                 mpz_clear (last_value);
3350                 return SUCCESS;
3351               }
3352             if (compare_bound_mpz_t (as->upper[i], last_value) == CMP_LT)
3353               {
3354                 gfc_warning ("Upper array reference at %L is out of bounds "
3355                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
3356                        mpz_get_si (last_value),
3357                        mpz_get_si (as->upper[i]->value.integer), i+1);
3358                 mpz_clear (last_value);
3359                 return SUCCESS;
3360               }
3361           }
3362         mpz_clear (last_value);
3363
3364 #undef AR_START
3365 #undef AR_END
3366       }
3367       break;
3368
3369     default:
3370       gfc_internal_error ("check_dimension(): Bad array reference");
3371     }
3372
3373   return SUCCESS;
3374 }
3375
3376
3377 /* Compare an array reference with an array specification.  */
3378
3379 static try
3380 compare_spec_to_ref (gfc_array_ref *ar)
3381 {
3382   gfc_array_spec *as;
3383   int i;
3384
3385   as = ar->as;
3386   i = as->rank - 1;
3387   /* TODO: Full array sections are only allowed as actual parameters.  */
3388   if (as->type == AS_ASSUMED_SIZE
3389       && (/*ar->type == AR_FULL
3390           ||*/ (ar->type == AR_SECTION
3391               && ar->dimen_type[i] == DIMEN_RANGE && ar->end[i] == NULL)))
3392     {
3393       gfc_error ("Rightmost upper bound of assumed size array section "
3394                  "not specified at %L", &ar->where);
3395       return FAILURE;
3396     }
3397
3398   if (ar->type == AR_FULL)
3399     return SUCCESS;
3400
3401   if (as->rank != ar->dimen)
3402     {
3403       gfc_error ("Rank mismatch in array reference at %L (%d/%d)",
3404                  &ar->where, ar->dimen, as->rank);
3405       return FAILURE;
3406     }
3407
3408   for (i = 0; i < as->rank; i++)
3409     if (check_dimension (i, ar, as) == FAILURE)
3410       return FAILURE;
3411
3412   return SUCCESS;
3413 }
3414
3415
3416 /* Resolve one part of an array index.  */
3417
3418 try
3419 gfc_resolve_index (gfc_expr *index, int check_scalar)
3420 {
3421   gfc_typespec ts;
3422
3423   if (index == NULL)
3424     return SUCCESS;
3425
3426   if (gfc_resolve_expr (index) == FAILURE)
3427     return FAILURE;
3428
3429   if (check_scalar && index->rank != 0)
3430     {
3431       gfc_error ("Array index at %L must be scalar", &index->where);
3432       return FAILURE;
3433     }
3434
3435   if (index->ts.type != BT_INTEGER && index->ts.type != BT_REAL)
3436     {
3437       gfc_error ("Array index at %L must be of INTEGER type",
3438                  &index->where);
3439       return FAILURE;
3440     }
3441
3442   if (index->ts.type == BT_REAL)
3443     if (gfc_notify_std (GFC_STD_LEGACY, "Extension: REAL array index at %L",
3444                         &index->where) == FAILURE)
3445       return FAILURE;
3446
3447   if (index->ts.kind != gfc_index_integer_kind
3448       || index->ts.type != BT_INTEGER)
3449     {
3450       gfc_clear_ts (&ts);
3451       ts.type = BT_INTEGER;
3452       ts.kind = gfc_index_integer_kind;
3453
3454       gfc_convert_type_warn (index, &ts, 2, 0);
3455     }
3456
3457   return SUCCESS;
3458 }
3459
3460 /* Resolve a dim argument to an intrinsic function.  */
3461
3462 try
3463 gfc_resolve_dim_arg (gfc_expr *dim)
3464 {
3465   if (dim == NULL)
3466     return SUCCESS;
3467
3468   if (gfc_resolve_expr (dim) == FAILURE)
3469     return FAILURE;
3470
3471   if (dim->rank != 0)
3472     {
3473       gfc_error ("Argument dim at %L must be scalar", &dim->where);
3474       return FAILURE;
3475
3476     }
3477
3478   if (dim->ts.type != BT_INTEGER)
3479     {
3480       gfc_error ("Argument dim at %L must be of INTEGER type", &dim->where);
3481       return FAILURE;
3482     }
3483
3484   if (dim->ts.kind != gfc_index_integer_kind)
3485     {
3486       gfc_typespec ts;
3487
3488       ts.type = BT_INTEGER;
3489       ts.kind = gfc_index_integer_kind;
3490
3491       gfc_convert_type_warn (dim, &ts, 2, 0);
3492     }
3493
3494   return SUCCESS;
3495 }
3496
3497 /* Given an expression that contains array references, update those array
3498    references to point to the right array specifications.  While this is
3499    filled in during matching, this information is difficult to save and load
3500    in a module, so we take care of it here.
3501
3502    The idea here is that the original array reference comes from the
3503    base symbol.  We traverse the list of reference structures, setting
3504    the stored reference to references.  Component references can
3505    provide an additional array specification.  */
3506
3507 static void
3508 find_array_spec (gfc_expr *e)
3509 {
3510   gfc_array_spec *as;
3511   gfc_component *c;
3512   gfc_symbol *derived;
3513   gfc_ref *ref;
3514
3515   as = e->symtree->n.sym->as;
3516   derived = NULL;
3517
3518   for (ref = e->ref; ref; ref = ref->next)
3519     switch (ref->type)
3520       {
3521       case REF_ARRAY:
3522         if (as == NULL)
3523           gfc_internal_error ("find_array_spec(): Missing spec");
3524
3525         ref->u.ar.as = as;
3526         as = NULL;
3527         break;
3528
3529       case REF_COMPONENT:
3530         if (derived == NULL)
3531           derived = e->symtree->n.sym->ts.derived;
3532
3533         c = derived->components;
3534
3535         for (; c; c = c->next)
3536           if (c == ref->u.c.component)
3537             {
3538               /* Track the sequence of component references.  */
3539               if (c->ts.type == BT_DERIVED)
3540                 derived = c->ts.derived;
3541               break;
3542             }
3543
3544         if (c == NULL)
3545           gfc_internal_error ("find_array_spec(): Component not found");
3546
3547         if (c->dimension)
3548           {
3549             if (as != NULL)
3550               gfc_internal_error ("find_array_spec(): unused as(1)");
3551             as = c->as;
3552           }
3553
3554         break;
3555
3556       case REF_SUBSTRING:
3557         break;
3558       }
3559
3560   if (as != NULL)
3561     gfc_internal_error ("find_array_spec(): unused as(2)");
3562 }
3563
3564
3565 /* Resolve an array reference.  */
3566
3567 static try
3568 resolve_array_ref (gfc_array_ref *ar)
3569 {
3570   int i, check_scalar;
3571   gfc_expr *e;
3572
3573   for (i = 0; i < ar->dimen; i++)
3574     {
3575       check_scalar = ar->dimen_type[i] == DIMEN_RANGE;
3576
3577       if (gfc_resolve_index (ar->start[i], check_scalar) == FAILURE)
3578         return FAILURE;
3579       if (gfc_resolve_index (ar->end[i], check_scalar) == FAILURE)
3580         return FAILURE;
3581       if (gfc_resolve_index (ar->stride[i], check_scalar) == FAILURE)
3582         return FAILURE;
3583
3584       e = ar->start[i];
3585
3586       if (ar->dimen_type[i] == DIMEN_UNKNOWN)
3587         switch (e->rank)
3588           {
3589           case 0:
3590             ar->dimen_type[i] = DIMEN_ELEMENT;
3591             break;
3592
3593           case 1:
3594             ar->dimen_type[i] = DIMEN_VECTOR;
3595             if (e->expr_type == EXPR_VARIABLE
3596                 && e->symtree->n.sym->ts.type == BT_DERIVED)
3597               ar->start[i] = gfc_get_parentheses (e);
3598             break;
3599
3600           default:
3601             gfc_error ("Array index at %L is an array of rank %d",
3602                        &ar->c_where[i], e->rank);
3603             return FAILURE;
3604           }
3605     }
3606
3607   /* If the reference type is unknown, figure out what kind it is.  */
3608
3609   if (ar->type == AR_UNKNOWN)
3610     {
3611       ar->type = AR_ELEMENT;
3612       for (i = 0; i < ar->dimen; i++)
3613         if (ar->dimen_type[i] == DIMEN_RANGE
3614             || ar->dimen_type[i] == DIMEN_VECTOR)
3615           {
3616             ar->type = AR_SECTION;
3617             break;
3618           }
3619     }
3620
3621   if (!ar->as->cray_pointee && compare_spec_to_ref (ar) == FAILURE)
3622     return FAILURE;
3623
3624   return SUCCESS;
3625 }
3626
3627
3628 static try
3629 resolve_substring (gfc_ref *ref)
3630 {
3631   if (ref->u.ss.start != NULL)
3632     {
3633       if (gfc_resolve_expr (ref->u.ss.start) == FAILURE)
3634         return FAILURE;
3635
3636       if (ref->u.ss.start->ts.type != BT_INTEGER)
3637         {
3638           gfc_error ("Substring start index at %L must be of type INTEGER",
3639                      &ref->u.ss.start->where);
3640           return FAILURE;
3641         }
3642
3643       if (ref->u.ss.start->rank != 0)
3644         {
3645           gfc_error ("Substring start index at %L must be scalar",
3646                      &ref->u.ss.start->where);
3647           return FAILURE;
3648         }
3649
3650       if (compare_bound_int (ref->u.ss.start, 1) == CMP_LT
3651           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
3652               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
3653         {
3654           gfc_error ("Substring start index at %L is less than one",
3655                      &ref->u.ss.start->where);
3656           return FAILURE;
3657         }
3658     }
3659
3660   if (ref->u.ss.end != NULL)
3661     {
3662       if (gfc_resolve_expr (ref->u.ss.end) == FAILURE)
3663         return FAILURE;
3664
3665       if (ref->u.ss.end->ts.type != BT_INTEGER)
3666         {
3667           gfc_error ("Substring end index at %L must be of type INTEGER",
3668                      &ref->u.ss.end->where);
3669           return FAILURE;
3670         }
3671
3672       if (ref->u.ss.end->rank != 0)
3673         {
3674           gfc_error ("Substring end index at %L must be scalar",
3675                      &ref->u.ss.end->where);
3676           return FAILURE;
3677         }
3678
3679       if (ref->u.ss.length != NULL
3680           && compare_bound (ref->u.ss.end, ref->u.ss.length->length) == CMP_GT
3681           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
3682               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
3683         {
3684           gfc_error ("Substring end index at %L exceeds the string length",
3685                      &ref->u.ss.start->where);
3686           return FAILURE;
3687         }
3688     }
3689
3690   return SUCCESS;
3691 }
3692
3693
3694 /* This function supplies missing substring charlens.  */
3695
3696 void
3697 gfc_resolve_substring_charlen (gfc_expr *e)
3698 {
3699   gfc_ref *char_ref;
3700   gfc_expr *start, *end;
3701
3702   for (char_ref = e->ref; char_ref; char_ref = char_ref->next)
3703     if (char_ref->type == REF_SUBSTRING)
3704       break;
3705
3706   if (!char_ref)
3707     return;
3708
3709   gcc_assert (char_ref->next == NULL);
3710
3711   if (e->ts.cl)
3712     {
3713       if (e->ts.cl->length)
3714         gfc_free_expr (e->ts.cl->length);
3715       else if (e->expr_type == EXPR_VARIABLE
3716                  && e->symtree->n.sym->attr.dummy)
3717         return;
3718     }
3719
3720   e->ts.type = BT_CHARACTER;
3721   e->ts.kind = gfc_default_character_kind;
3722
3723   if (!e->ts.cl)
3724     {
3725       e->ts.cl = gfc_get_charlen ();
3726       e->ts.cl->next = gfc_current_ns->cl_list;
3727       gfc_current_ns->cl_list = e->ts.cl;
3728     }
3729
3730   if (char_ref->u.ss.start)
3731     start = gfc_copy_expr (char_ref->u.ss.start);
3732   else
3733     start = gfc_int_expr (1);
3734
3735   if (char_ref->u.ss.end)
3736     end = gfc_copy_expr (char_ref->u.ss.end);
3737   else if (e->expr_type == EXPR_VARIABLE)
3738     end = gfc_copy_expr (e->symtree->n.sym->ts.cl->length);
3739   else
3740     end = NULL;
3741
3742   if (!start || !end)
3743     return;
3744
3745   /* Length = (end - start +1).  */
3746   e->ts.cl->length = gfc_subtract (end, start);
3747   e->ts.cl->length = gfc_add (e->ts.cl->length, gfc_int_expr (1));
3748
3749   e->ts.cl->length->ts.type = BT_INTEGER;
3750   e->ts.cl->length->ts.kind = gfc_charlen_int_kind;;
3751
3752   /* Make sure that the length is simplified.  */
3753   gfc_simplify_expr (e->ts.cl->length, 1);
3754   gfc_resolve_expr (e->ts.cl->length);
3755 }
3756
3757
3758 /* Resolve subtype references.  */
3759
3760 static try
3761 resolve_ref (gfc_expr *expr)
3762 {
3763   int current_part_dimension, n_components, seen_part_dimension;
3764   gfc_ref *ref;
3765
3766   for (ref = expr->ref; ref; ref = ref->next)
3767     if (ref->type == REF_ARRAY && ref->u.ar.as == NULL)
3768       {
3769         find_array_spec (expr);
3770         break;
3771       }
3772
3773   for (ref = expr->ref; ref; ref = ref->next)
3774     switch (ref->type)
3775       {
3776       case REF_ARRAY:
3777         if (resolve_array_ref (&ref->u.ar) == FAILURE)
3778           return FAILURE;
3779         break;
3780
3781       case REF_COMPONENT:
3782         break;
3783
3784       case REF_SUBSTRING:
3785         resolve_substring (ref);
3786         break;
3787       }
3788
3789   /* Check constraints on part references.  */
3790
3791   current_part_dimension = 0;
3792   seen_part_dimension = 0;
3793   n_components = 0;
3794
3795   for (ref = expr->ref; ref; ref = ref->next)
3796     {
3797       switch (ref->type)
3798         {
3799         case REF_ARRAY:
3800           switch (ref->u.ar.type)
3801             {
3802             case AR_FULL:
3803             case AR_SECTION:
3804               current_part_dimension = 1;
3805               break;
3806
3807             case AR_ELEMENT:
3808               current_part_dimension = 0;
3809               break;
3810
3811             case AR_UNKNOWN:
3812               gfc_internal_error ("resolve_ref(): Bad array reference");
3813             }
3814
3815           break;
3816
3817         case REF_COMPONENT:
3818           if (current_part_dimension || seen_part_dimension)
3819             {
3820               if (ref->u.c.component->pointer)
3821                 {
3822                   gfc_error ("Component to the right of a part reference "
3823                              "with nonzero rank must not have the POINTER "
3824                              "attribute at %L", &expr->where);
3825                   return FAILURE;
3826                 }
3827               else if (ref->u.c.component->allocatable)
3828                 {
3829                   gfc_error ("Component to the right of a part reference "
3830                              "with nonzero rank must not have the ALLOCATABLE "
3831                              "attribute at %L", &expr->where);
3832                   return FAILURE;
3833                 }
3834             }
3835
3836           n_components++;
3837           break;
3838
3839         case REF_SUBSTRING:
3840           break;
3841         }
3842
3843       if (((ref->type == REF_COMPONENT && n_components > 1)
3844            || ref->next == NULL)
3845           && current_part_dimension
3846           && seen_part_dimension)
3847         {
3848           gfc_error ("Two or more part references with nonzero rank must "
3849                      "not be specified at %L", &expr->where);
3850           return FAILURE;
3851         }
3852
3853       if (ref->type == REF_COMPONENT)
3854         {
3855           if (current_part_dimension)
3856             seen_part_dimension = 1;
3857
3858           /* reset to make sure */
3859           current_part_dimension = 0;
3860         }
3861     }
3862
3863   return SUCCESS;
3864 }
3865
3866
3867 /* Given an expression, determine its shape.  This is easier than it sounds.
3868    Leaves the shape array NULL if it is not possible to determine the shape.  */
3869
3870 static void
3871 expression_shape (gfc_expr *e)
3872 {
3873   mpz_t array[GFC_MAX_DIMENSIONS];
3874   int i;
3875
3876   if (e->rank == 0 || e->shape != NULL)
3877     return;
3878
3879   for (i = 0; i < e->rank; i++)
3880     if (gfc_array_dimen_size (e, i, &array[i]) == FAILURE)
3881       goto fail;
3882
3883   e->shape = gfc_get_shape (e->rank);
3884
3885   memcpy (e->shape, array, e->rank * sizeof (mpz_t));
3886
3887   return;
3888
3889 fail:
3890   for (i--; i >= 0; i--)
3891     mpz_clear (array[i]);
3892 }
3893
3894
3895 /* Given a variable expression node, compute the rank of the expression by
3896    examining the base symbol and any reference structures it may have.  */
3897
3898 static void
3899 expression_rank (gfc_expr *e)
3900 {
3901   gfc_ref *ref;
3902   int i, rank;
3903
3904   if (e->ref == NULL)
3905     {
3906       if (e->expr_type == EXPR_ARRAY)
3907         goto done;
3908       /* Constructors can have a rank different from one via RESHAPE().  */
3909
3910       if (e->symtree == NULL)
3911         {
3912           e->rank = 0;
3913           goto done;
3914         }
3915
3916       e->rank = (e->symtree->n.sym->as == NULL)
3917                 ? 0 : e->symtree->n.sym->as->rank;
3918       goto done;
3919     }
3920
3921   rank = 0;
3922
3923   for (ref = e->ref; ref; ref = ref->next)
3924     {
3925       if (ref->type != REF_ARRAY)
3926         continue;
3927
3928       if (ref->u.ar.type == AR_FULL)
3929         {
3930           rank = ref->u.ar.as->rank;
3931           break;
3932         }
3933
3934       if (ref->u.ar.type == AR_SECTION)
3935         {
3936           /* Figure out the rank of the section.  */
3937           if (rank != 0)
3938             gfc_internal_error ("expression_rank(): Two array specs");
3939
3940           for (i = 0; i < ref->u.ar.dimen; i++)
3941             if (ref->u.ar.dimen_type[i] == DIMEN_RANGE
3942                 || ref->u.ar.dimen_type[i] == DIMEN_VECTOR)
3943               rank++;
3944
3945           break;
3946         }
3947     }
3948
3949   e->rank = rank;
3950
3951 done:
3952   expression_shape (e);
3953 }
3954
3955
3956 /* Resolve a variable expression.  */
3957
3958 static try
3959 resolve_variable (gfc_expr *e)
3960 {
3961   gfc_symbol *sym;
3962   try t;
3963
3964   t = SUCCESS;
3965
3966   if (e->symtree == NULL)
3967     return FAILURE;
3968
3969   if (e->ref && resolve_ref (e) == FAILURE)
3970     return FAILURE;
3971
3972   sym = e->symtree->n.sym;
3973   if (sym->attr.flavor == FL_PROCEDURE && !sym->attr.function)
3974     {
3975       e->ts.type = BT_PROCEDURE;
3976       return SUCCESS;
3977     }
3978
3979   if (sym->ts.type != BT_UNKNOWN)
3980     gfc_variable_attr (e, &e->ts);
3981   else
3982     {
3983       /* Must be a simple variable reference.  */
3984       if (gfc_set_default_type (sym, 1, sym->ns) == FAILURE)
3985         return FAILURE;
3986       e->ts = sym->ts;
3987     }
3988
3989   if (check_assumed_size_reference (sym, e))
3990     return FAILURE;
3991
3992   /* Deal with forward references to entries during resolve_code, to
3993      satisfy, at least partially, 12.5.2.5.  */
3994   if (gfc_current_ns->entries
3995       && current_entry_id == sym->entry_id
3996       && cs_base
3997       && cs_base->current
3998       && cs_base->current->op != EXEC_ENTRY)
3999     {
4000       gfc_entry_list *entry;
4001       gfc_formal_arglist *formal;
4002       int n;
4003       bool seen;
4004
4005       /* If the symbol is a dummy...  */
4006       if (sym->attr.dummy && sym->ns == gfc_current_ns)
4007         {
4008           entry = gfc_current_ns->entries;
4009           seen = false;
4010
4011           /* ...test if the symbol is a parameter of previous entries.  */
4012           for (; entry && entry->id <= current_entry_id; entry = entry->next)
4013             for (formal = entry->sym->formal; formal; formal = formal->next)
4014               {
4015                 if (formal->sym && sym->name == formal->sym->name)
4016                   seen = true;
4017               }
4018
4019           /*  If it has not been seen as a dummy, this is an error.  */
4020           if (!seen)
4021             {
4022               if (specification_expr)
4023                 gfc_error ("Variable '%s', used in a specification expression"
4024                            ", is referenced at %L before the ENTRY statement "
4025                            "in which it is a parameter",
4026                            sym->name, &cs_base->current->loc);
4027               else
4028                 gfc_error ("Variable '%s' is used at %L before the ENTRY "
4029                            "statement in which it is a parameter",
4030                            sym->name, &cs_base->current->loc);
4031               t = FAILURE;
4032             }
4033         }
4034
4035       /* Now do the same check on the specification expressions.  */
4036       specification_expr = 1;
4037       if (sym->ts.type == BT_CHARACTER
4038           && gfc_resolve_expr (sym->ts.cl->length) == FAILURE)
4039         t = FAILURE;
4040
4041       if (sym->as)
4042         for (n = 0; n < sym->as->rank; n++)
4043           {
4044              specification_expr = 1;
4045              if (gfc_resolve_expr (sym->as->lower[n]) == FAILURE)
4046                t = FAILURE;
4047              specification_expr = 1;
4048              if (gfc_resolve_expr (sym->as->upper[n]) == FAILURE)
4049                t = FAILURE;
4050           }
4051       specification_expr = 0;
4052
4053       if (t == SUCCESS)
4054         /* Update the symbol's entry level.  */
4055         sym->entry_id = current_entry_id + 1;
4056     }
4057
4058   return t;
4059 }
4060
4061
4062 /* Checks to see that the correct symbol has been host associated.
4063    The only situation where this arises is that in which a twice
4064    contained function is parsed after the host association is made.
4065    Therefore, on detecting this, the line is rematched, having got
4066    rid of the existing references and actual_arg_list.  */
4067 static bool
4068 check_host_association (gfc_expr *e)
4069 {
4070   gfc_symbol *sym, *old_sym;
4071   locus temp_locus;
4072   gfc_expr *expr;
4073   int n;
4074   bool retval = e->expr_type == EXPR_FUNCTION;
4075
4076   if (e->symtree == NULL || e->symtree->n.sym == NULL)
4077     return retval;
4078
4079   old_sym = e->symtree->n.sym;
4080
4081   if (old_sym->attr.use_assoc)
4082     return retval;
4083
4084   if (gfc_current_ns->parent
4085         && old_sym->ns != gfc_current_ns)
4086     {
4087       gfc_find_symbol (old_sym->name, gfc_current_ns, 1, &sym);
4088       if (sym && old_sym != sym
4089               && sym->attr.flavor == FL_PROCEDURE
4090               && sym->attr.contained)
4091         {
4092           temp_locus = gfc_current_locus;
4093           gfc_current_locus = e->where;
4094
4095           gfc_buffer_error (1);
4096
4097           gfc_free_ref_list (e->ref);
4098           e->ref = NULL;
4099
4100           if (retval)
4101             {
4102               gfc_free_actual_arglist (e->value.function.actual);
4103               e->value.function.actual = NULL;
4104             }
4105
4106           if (e->shape != NULL)
4107             {
4108               for (n = 0; n < e->rank; n++)
4109                 mpz_clear (e->shape[n]);
4110
4111               gfc_free (e->shape);
4112             }
4113
4114           gfc_match_rvalue (&expr);
4115           gfc_clear_error ();
4116           gfc_buffer_error (0);
4117
4118           gcc_assert (expr && sym == expr->symtree->n.sym);
4119
4120           *e = *expr;
4121           gfc_free (expr);
4122           sym->refs++;
4123
4124           gfc_current_locus = temp_locus;
4125         }
4126     }
4127   /* This might have changed!  */
4128   return e->expr_type == EXPR_FUNCTION;
4129 }
4130
4131
4132 static void
4133 gfc_resolve_character_operator (gfc_expr *e)
4134 {
4135   gfc_expr *op1 = e->value.op.op1;
4136   gfc_expr *op2 = e->value.op.op2;
4137   gfc_expr *e1 = NULL;
4138   gfc_expr *e2 = NULL;
4139
4140   gcc_assert (e->value.op.operator == INTRINSIC_CONCAT);
4141
4142   if (op1->ts.cl && op1->ts.cl->length)
4143     e1 = gfc_copy_expr (op1->ts.cl->length);
4144   else if (op1->expr_type == EXPR_CONSTANT)
4145     e1 = gfc_int_expr (op1->value.character.length);
4146
4147   if (op2->ts.cl && op2->ts.cl->length)
4148     e2 = gfc_copy_expr (op2->ts.cl->length);
4149   else if (op2->expr_type == EXPR_CONSTANT)
4150     e2 = gfc_int_expr (op2->value.character.length);
4151
4152   e->ts.cl = gfc_get_charlen ();
4153   e->ts.cl->next = gfc_current_ns->cl_list;
4154   gfc_current_ns->cl_list = e->ts.cl;
4155
4156   if (!e1 || !e2)
4157     return;
4158
4159   e->ts.cl->length = gfc_add (e1, e2);
4160   e->ts.cl->length->ts.type = BT_INTEGER;
4161   e->ts.cl->length->ts.kind = gfc_charlen_int_kind;;
4162   gfc_simplify_expr (e->ts.cl->length, 0);
4163   gfc_resolve_expr (e->ts.cl->length);
4164
4165   return;
4166 }
4167
4168
4169 /*  Ensure that an character expression has a charlen and, if possible, a
4170     length expression.  */
4171
4172 static void
4173 fixup_charlen (gfc_expr *e)
4174 {
4175   /* The cases fall through so that changes in expression type and the need
4176      for multiple fixes are picked up.  In all circumstances, a charlen should
4177      be available for the middle end to hang a backend_decl on.  */
4178   switch (e->expr_type)
4179     {
4180     case EXPR_OP:
4181       gfc_resolve_character_operator (e);
4182
4183     case EXPR_ARRAY:
4184       if (e->expr_type == EXPR_ARRAY)
4185         gfc_resolve_character_array_constructor (e);
4186
4187     case EXPR_SUBSTRING:
4188       if (!e->ts.cl && e->ref)
4189         gfc_resolve_substring_charlen (e);
4190
4191     default:
4192       if (!e->ts.cl)
4193         {
4194           e->ts.cl = gfc_get_charlen ();
4195           e->ts.cl->next = gfc_current_ns->cl_list;
4196           gfc_current_ns->cl_list = e->ts.cl;
4197         }
4198
4199       break;
4200     }
4201 }
4202
4203
4204 /* Resolve an expression.  That is, make sure that types of operands agree
4205    with their operators, intrinsic operators are converted to function calls
4206    for overloaded types and unresolved function references are resolved.  */
4207
4208 try
4209 gfc_resolve_expr (gfc_expr *e)
4210 {
4211   try t;
4212
4213   if (e == NULL)
4214     return SUCCESS;
4215
4216   switch (e->expr_type)
4217     {
4218     case EXPR_OP:
4219       t = resolve_operator (e);
4220       break;
4221
4222     case EXPR_FUNCTION:
4223     case EXPR_VARIABLE:
4224
4225       if (check_host_association (e))
4226         t = resolve_function (e);
4227       else
4228         {
4229           t = resolve_variable (e);
4230           if (t == SUCCESS)
4231             expression_rank (e);
4232         }
4233
4234       if (e->ts.type == BT_CHARACTER && e->ts.cl == NULL && e->ref
4235           && e->ref->type != REF_SUBSTRING)
4236         gfc_resolve_substring_charlen (e);
4237
4238       break;
4239
4240     case EXPR_SUBSTRING:
4241       t = resolve_ref (e);
4242       break;
4243
4244     case EXPR_CONSTANT:
4245     case EXPR_NULL:
4246       t = SUCCESS;
4247       break;
4248
4249     case EXPR_ARRAY:
4250       t = FAILURE;
4251       if (resolve_ref (e) == FAILURE)
4252         break;
4253
4254       t = gfc_resolve_array_constructor (e);
4255       /* Also try to expand a constructor.  */
4256       if (t == SUCCESS)
4257         {
4258           expression_rank (e);
4259           gfc_expand_constructor (e);
4260         }
4261
4262       /* This provides the opportunity for the length of constructors with
4263          character valued function elements to propagate the string length
4264          to the expression.  */
4265       if (e->ts.type == BT_CHARACTER)
4266         gfc_resolve_character_array_constructor (e);
4267
4268       break;
4269
4270     case EXPR_STRUCTURE:
4271       t = resolve_ref (e);
4272       if (t == FAILURE)
4273         break;
4274
4275       t = resolve_structure_cons (e);
4276       if (t == FAILURE)
4277         break;
4278
4279       t = gfc_simplify_expr (e, 0);
4280       break;
4281
4282     default:
4283       gfc_internal_error ("gfc_resolve_expr(): Bad expression type");
4284     }
4285
4286   if (e->ts.type == BT_CHARACTER && t == SUCCESS && !e->ts.cl)
4287     fixup_charlen (e);
4288
4289   return t;
4290 }
4291
4292
4293 /* Resolve an expression from an iterator.  They must be scalar and have
4294    INTEGER or (optionally) REAL type.  */
4295
4296 static try
4297 gfc_resolve_iterator_expr (gfc_expr *expr, bool real_ok,
4298                            const char *name_msgid)
4299 {
4300   if (gfc_resolve_expr (expr) == FAILURE)
4301     return FAILURE;
4302
4303   if (expr->rank != 0)
4304     {
4305       gfc_error ("%s at %L must be a scalar", _(name_msgid), &expr->where);
4306       return FAILURE;
4307     }
4308
4309   if (expr->ts.type != BT_INTEGER)
4310     {
4311       if (expr->ts.type == BT_REAL)
4312         {
4313           if (real_ok)
4314             return gfc_notify_std (GFC_STD_F95_DEL,
4315                                    "Deleted feature: %s at %L must be integer",
4316                                    _(name_msgid), &expr->where);
4317           else
4318             {
4319               gfc_error ("%s at %L must be INTEGER", _(name_msgid),
4320                          &expr->where);
4321               return FAILURE;
4322             }
4323         }
4324       else
4325         {
4326           gfc_error ("%s at %L must be INTEGER", _(name_msgid), &expr->where);
4327           return FAILURE;
4328         }
4329     }
4330   return SUCCESS;
4331 }
4332
4333
4334 /* Resolve the expressions in an iterator structure.  If REAL_OK is
4335    false allow only INTEGER type iterators, otherwise allow REAL types.  */
4336
4337 try
4338 gfc_resolve_iterator (gfc_iterator *iter, bool real_ok)
4339 {
4340   if (gfc_resolve_iterator_expr (iter->var, real_ok, "Loop variable")
4341       == FAILURE)
4342     return FAILURE;
4343
4344   if (gfc_pure (NULL) && gfc_impure_variable (iter->var->symtree->n.sym))
4345     {
4346       gfc_error ("Cannot assign to loop variable in PURE procedure at %L",
4347                  &iter->var->where);
4348       return FAILURE;
4349     }
4350
4351   if (gfc_resolve_iterator_expr (iter->start, real_ok,
4352                                  "Start expression in DO loop") == FAILURE)
4353     return FAILURE;
4354
4355   if (gfc_resolve_iterator_expr (iter->end, real_ok,
4356                                  "End expression in DO loop") == FAILURE)
4357     return FAILURE;
4358
4359   if (gfc_resolve_iterator_expr (iter->step, real_ok,
4360                                  "Step expression in DO loop") == FAILURE)
4361     return FAILURE;
4362
4363   if (iter->step->expr_type == EXPR_CONSTANT)
4364     {
4365       if ((iter->step->ts.type == BT_INTEGER
4366            && mpz_cmp_ui (iter->step->value.integer, 0) == 0)
4367           || (iter->step->ts.type == BT_REAL
4368               && mpfr_sgn (iter->step->value.real) == 0))
4369         {
4370           gfc_error ("Step expression in DO loop at %L cannot be zero",
4371                      &iter->step->where);
4372           return FAILURE;
4373         }
4374     }
4375
4376   /* Convert start, end, and step to the same type as var.  */
4377   if (iter->start->ts.kind != iter->var->ts.kind
4378       || iter->start->ts.type != iter->var->ts.type)
4379     gfc_convert_type (iter->start, &iter->var->ts, 2);
4380
4381   if (iter->end->ts.kind != iter->var->ts.kind
4382       || iter->end->ts.type != iter->var->ts.type)
4383     gfc_convert_type (iter->end, &iter->var->ts, 2);
4384
4385   if (iter->step->ts.kind != iter->var->ts.kind
4386       || iter->step->ts.type != iter->var->ts.type)
4387     gfc_convert_type (iter->step, &iter->var->ts, 2);
4388
4389   return SUCCESS;
4390 }
4391
4392
4393 /* Traversal function for find_forall_index.  f == 2 signals that
4394    that variable itself is not to be checked - only the references.  */
4395
4396 static bool
4397 forall_index (gfc_expr *expr, gfc_symbol *sym, int *f)
4398 {
4399   if (expr->expr_type != EXPR_VARIABLE)
4400     return false;
4401   
4402   /* A scalar assignment  */
4403   if (!expr->ref || *f == 1)
4404     {
4405       if (expr->symtree->n.sym == sym)
4406         return true;
4407       else
4408         return false;
4409     }
4410
4411   if (*f == 2)
4412     *f = 1;
4413   return false;
4414 }
4415
4416
4417 /* Check whether the FORALL index appears in the expression or not.
4418    Returns SUCCESS if SYM is found in EXPR.  */
4419
4420 try
4421 find_forall_index (gfc_expr *expr, gfc_symbol *sym, int f)
4422 {
4423   if (gfc_traverse_expr (expr, sym, forall_index, f))
4424     return SUCCESS;
4425   else
4426     return FAILURE;
4427 }
4428
4429
4430 /* Resolve a list of FORALL iterators.  The FORALL index-name is constrained
4431    to be a scalar INTEGER variable.  The subscripts and stride are scalar
4432    INTEGERs, and if stride is a constant it must be nonzero.
4433    Furthermore "A subscript or stride in a forall-triplet-spec shall
4434    not contain a reference to any index-name in the
4435    forall-triplet-spec-list in which it appears." (7.5.4.1)  */
4436
4437 static void
4438 resolve_forall_iterators (gfc_forall_iterator *it)
4439 {
4440   gfc_forall_iterator *iter, *iter2;
4441
4442   for (iter = it; iter; iter = iter->next)
4443     {
4444       if (gfc_resolve_expr (iter->var) == SUCCESS
4445           && (iter->var->ts.type != BT_INTEGER || iter->var->rank != 0))
4446         gfc_error ("FORALL index-name at %L must be a scalar INTEGER",
4447                    &iter->var->where);
4448
4449       if (gfc_resolve_expr (iter->start) == SUCCESS
4450           && (iter->start->ts.type != BT_INTEGER || iter->start->rank != 0))
4451         gfc_error ("FORALL start expression at %L must be a scalar INTEGER",
4452                    &iter->start->where);
4453       if (iter->var->ts.kind != iter->start->ts.kind)
4454         gfc_convert_type (iter->start, &iter->var->ts, 2);
4455
4456       if (gfc_resolve_expr (iter->end) == SUCCESS
4457           && (iter->end->ts.type != BT_INTEGER || iter->end->rank != 0))
4458         gfc_error ("FORALL end expression at %L must be a scalar INTEGER",
4459                    &iter->end->where);
4460       if (iter->var->ts.kind != iter->end->ts.kind)
4461         gfc_convert_type (iter->end, &iter->var->ts, 2);
4462
4463       if (gfc_resolve_expr (iter->stride) == SUCCESS)
4464         {
4465           if (iter->stride->ts.type != BT_INTEGER || iter->stride->rank != 0)
4466             gfc_error ("FORALL stride expression at %L must be a scalar %s",
4467                        &iter->stride->where, "INTEGER");
4468
4469           if (iter->stride->expr_type == EXPR_CONSTANT
4470               && mpz_cmp_ui(iter->stride->value.integer, 0) == 0)
4471             gfc_error ("FORALL stride expression at %L cannot be zero",
4472                        &iter->stride->where);
4473         }
4474       if (iter->var->ts.kind != iter->stride->ts.kind)
4475         gfc_convert_type (iter->stride, &iter->var->ts, 2);
4476     }
4477
4478   for (iter = it; iter; iter = iter->next)
4479     for (iter2 = iter; iter2; iter2 = iter2->next)
4480       {
4481         if (find_forall_index (iter2->start,
4482                                iter->var->symtree->n.sym, 0) == SUCCESS
4483             || find_forall_index (iter2->end,
4484                                   iter->var->symtree->n.sym, 0) == SUCCESS
4485             || find_forall_index (iter2->stride,
4486                                   iter->var->symtree->n.sym, 0) == SUCCESS)
4487           gfc_error ("FORALL index '%s' may not appear in triplet "
4488                      "specification at %L", iter->var->symtree->name,
4489                      &iter2->start->where);
4490       }
4491 }
4492
4493
4494 /* Given a pointer to a symbol that is a derived type, see if it's
4495    inaccessible, i.e. if it's defined in another module and the components are
4496    PRIVATE.  The search is recursive if necessary.  Returns zero if no
4497    inaccessible components are found, nonzero otherwise.  */
4498
4499 static int
4500 derived_inaccessible (gfc_symbol *sym)
4501 {
4502   gfc_component *c;
4503
4504   if (sym->attr.use_assoc && sym->attr.private_comp)
4505     return 1;
4506
4507   for (c = sym->components; c; c = c->next)
4508     {
4509         if (c->ts.type == BT_DERIVED && derived_inaccessible (c->ts.derived))
4510           return 1;
4511     }
4512
4513   return 0;
4514 }
4515
4516
4517 /* Resolve the argument of a deallocate expression.  The expression must be
4518    a pointer or a full array.  */
4519
4520 static try
4521 resolve_deallocate_expr (gfc_expr *e)
4522 {
4523   symbol_attribute attr;
4524   int allocatable, pointer, check_intent_in;
4525   gfc_ref *ref;
4526
4527   /* Check INTENT(IN), unless the object is a sub-component of a pointer.  */
4528   check_intent_in = 1;
4529
4530   if (gfc_resolve_expr (e) == FAILURE)
4531     return FAILURE;
4532
4533   if (e->expr_type != EXPR_VARIABLE)
4534     goto bad;
4535
4536   allocatable = e->symtree->n.sym->attr.allocatable;
4537   pointer = e->symtree->n.sym->attr.pointer;
4538   for (ref = e->ref; ref; ref = ref->next)
4539     {
4540       if (pointer)
4541         check_intent_in = 0;
4542
4543       switch (ref->type)
4544         {
4545         case REF_ARRAY:
4546           if (ref->u.ar.type != AR_FULL)
4547             allocatable = 0;
4548           break;
4549
4550         case REF_COMPONENT:
4551           allocatable = (ref->u.c.component->as != NULL
4552                          && ref->u.c.component->as->type == AS_DEFERRED);
4553           pointer = ref->u.c.component->pointer;
4554           break;
4555
4556         case REF_SUBSTRING:
4557           allocatable = 0;
4558           break;
4559         }
4560     }
4561
4562   attr = gfc_expr_attr (e);
4563
4564   if (allocatable == 0 && attr.pointer == 0)
4565     {
4566     bad:
4567       gfc_error ("Expression in DEALLOCATE statement at %L must be "
4568                  "ALLOCATABLE or a POINTER", &e->where);
4569     }
4570
4571   if (check_intent_in
4572       && e->symtree->n.sym->attr.intent == INTENT_IN)
4573     {
4574       gfc_error ("Cannot deallocate INTENT(IN) variable '%s' at %L",
4575                  e->symtree->n.sym->name, &e->where);
4576       return FAILURE;
4577     }
4578
4579   return SUCCESS;
4580 }
4581
4582
4583 /* Returns true if the expression e contains a reference to the symbol sym.  */
4584 static bool
4585 sym_in_expr (gfc_expr *e, gfc_symbol *sym, int *f ATTRIBUTE_UNUSED)
4586 {
4587   if (e->expr_type == EXPR_VARIABLE && e->symtree->n.sym == sym)
4588     return true;
4589
4590   return false;
4591 }
4592
4593 static bool
4594 find_sym_in_expr (gfc_symbol *sym, gfc_expr *e)
4595 {
4596   return gfc_traverse_expr (e, sym, sym_in_expr, 0);
4597 }
4598
4599
4600 /* Given the expression node e for an allocatable/pointer of derived type to be
4601    allocated, get the expression node to be initialized afterwards (needed for
4602    derived types with default initializers, and derived types with allocatable
4603    components that need nullification.)  */
4604
4605 static gfc_expr *
4606 expr_to_initialize (gfc_expr *e)
4607 {
4608   gfc_expr *result;
4609   gfc_ref *ref;
4610   int i;
4611
4612   result = gfc_copy_expr (e);
4613
4614   /* Change the last array reference from AR_ELEMENT to AR_FULL.  */
4615   for (ref = result->ref; ref; ref = ref->next)
4616     if (ref->type == REF_ARRAY && ref->next == NULL)
4617       {
4618         ref->u.ar.type = AR_FULL;
4619
4620         for (i = 0; i < ref->u.ar.dimen; i++)
4621           ref->u.ar.start[i] = ref->u.ar.end[i] = ref->u.ar.stride[i] = NULL;
4622
4623         result->rank = ref->u.ar.dimen;
4624         break;
4625       }
4626
4627   return result;
4628 }
4629
4630
4631 /* Resolve the expression in an ALLOCATE statement, doing the additional
4632    checks to see whether the expression is OK or not.  The expression must
4633    have a trailing array reference that gives the size of the array.  */
4634
4635 static try
4636 resolve_allocate_expr (gfc_expr *e, gfc_code *code)
4637 {
4638   int i, pointer, allocatable, dimension, check_intent_in;
4639   symbol_attribute attr;
4640   gfc_ref *ref, *ref2;
4641   gfc_array_ref *ar;
4642   gfc_code *init_st;
4643   gfc_expr *init_e;
4644   gfc_symbol *sym;
4645   gfc_alloc *a;
4646
4647   /* Check INTENT(IN), unless the object is a sub-component of a pointer.  */
4648   check_intent_in = 1;
4649
4650   if (gfc_resolve_expr (e) == FAILURE)
4651     return FAILURE;
4652
4653   if (code->expr && code->expr->expr_type == EXPR_VARIABLE)
4654     sym = code->expr->symtree->n.sym;
4655   else
4656     sym = NULL;
4657
4658   /* Make sure the expression is allocatable or a pointer.  If it is
4659      pointer, the next-to-last reference must be a pointer.  */
4660
4661   ref2 = NULL;
4662
4663   if (e->expr_type != EXPR_VARIABLE)
4664     {
4665       allocatable = 0;
4666       attr = gfc_expr_attr (e);
4667       pointer = attr.pointer;
4668       dimension = attr.dimension;
4669     }
4670   else
4671     {
4672       allocatable = e->symtree->n.sym->attr.allocatable;
4673       pointer = e->symtree->n.sym->attr.pointer;
4674       dimension = e->symtree->n.sym->attr.dimension;
4675
4676       if (sym == e->symtree->n.sym && sym->ts.type != BT_DERIVED)
4677         {
4678           gfc_error ("The STAT variable '%s' in an ALLOCATE statement must "
4679                      "not be allocated in the same statement at %L",
4680                       sym->name, &e->where);
4681           return FAILURE;
4682         }
4683
4684       for (ref = e->ref; ref; ref2 = ref, ref = ref->next)
4685         {
4686           if (pointer)
4687             check_intent_in = 0;
4688
4689           switch (ref->type)
4690             {
4691               case REF_ARRAY:
4692                 if (ref->next != NULL)
4693                   pointer = 0;
4694                 break;
4695
4696               case REF_COMPONENT:
4697                 allocatable = (ref->u.c.component->as != NULL
4698                                && ref->u.c.component->as->type == AS_DEFERRED);
4699
4700                 pointer = ref->u.c.component->pointer;
4701                 dimension = ref->u.c.component->dimension;
4702                 break;
4703
4704               case REF_SUBSTRING:
4705                 allocatable = 0;
4706                 pointer = 0;
4707                 break;
4708             }
4709        }
4710     }
4711
4712   if (allocatable == 0 && pointer == 0)
4713     {
4714       gfc_error ("Expression in ALLOCATE statement at %L must be "
4715                  "ALLOCATABLE or a POINTER", &e->where);
4716       return FAILURE;
4717     }
4718
4719   if (check_intent_in
4720       && e->symtree->n.sym->attr.intent == INTENT_IN)
4721     {
4722       gfc_error ("Cannot allocate INTENT(IN) variable '%s' at %L",
4723                  e->symtree->n.sym->name, &e->where);
4724       return FAILURE;
4725     }
4726
4727   /* Add default initializer for those derived types that need them.  */
4728   if (e->ts.type == BT_DERIVED && (init_e = gfc_default_initializer (&e->ts)))
4729     {
4730       init_st = gfc_get_code ();
4731       init_st->loc = code->loc;
4732       init_st->op = EXEC_INIT_ASSIGN;
4733       init_st->expr = expr_to_initialize (e);
4734       init_st->expr2 = init_e;
4735       init_st->next = code->next;
4736       code->next = init_st;
4737     }
4738
4739   if (pointer && dimension == 0)
4740     return SUCCESS;
4741
4742   /* Make sure the next-to-last reference node is an array specification.  */
4743
4744   if (ref2 == NULL || ref2->type != REF_ARRAY || ref2->u.ar.type == AR_FULL)
4745     {
4746       gfc_error ("Array specification required in ALLOCATE statement "
4747                  "at %L", &e->where);
4748       return FAILURE;
4749     }
4750
4751   /* Make sure that the array section reference makes sense in the
4752     context of an ALLOCATE specification.  */
4753
4754   ar = &ref2->u.ar;
4755
4756   for (i = 0; i < ar->dimen; i++)
4757     {
4758       if (ref2->u.ar.type == AR_ELEMENT)
4759         goto check_symbols;
4760
4761       switch (ar->dimen_type[i])
4762         {
4763         case DIMEN_ELEMENT:
4764           break;
4765
4766         case DIMEN_RANGE:
4767           if (ar->start[i] != NULL
4768               && ar->end[i] != NULL
4769               && ar->stride[i] == NULL)
4770             break;
4771
4772           /* Fall Through...  */
4773
4774         case DIMEN_UNKNOWN:
4775         case DIMEN_VECTOR:
4776           gfc_error ("Bad array specification in ALLOCATE statement at %L",
4777                      &e->where);
4778           return FAILURE;
4779         }
4780
4781 check_symbols:
4782
4783       for (a = code->ext.alloc_list; a; a = a->next)
4784         {
4785           sym = a->expr->symtree->n.sym;
4786
4787           /* TODO - check derived type components.  */
4788           if (sym->ts.type == BT_DERIVED)
4789             continue;
4790
4791           if ((ar->start[i] != NULL && find_sym_in_expr (sym, ar->start[i]))
4792                  || (ar->end[i] != NULL && find_sym_in_expr (sym, ar->end[i])))
4793             {
4794               gfc_error ("'%s' must not appear an the array specification at "
4795                          "%L in the same ALLOCATE statement where it is "
4796                          "itself allocated", sym->name, &ar->where);
4797               return FAILURE;
4798             }
4799         }
4800     }
4801
4802   return SUCCESS;
4803 }
4804
4805
4806 /************ SELECT CASE resolution subroutines ************/
4807
4808 /* Callback function for our mergesort variant.  Determines interval
4809    overlaps for CASEs. Return <0 if op1 < op2, 0 for overlap, >0 for
4810    op1 > op2.  Assumes we're not dealing with the default case.  
4811    We have op1 = (:L), (K:L) or (K:) and op2 = (:N), (M:N) or (M:).
4812    There are nine situations to check.  */
4813
4814 static int
4815 compare_cases (const gfc_case *op1, const gfc_case *op2)
4816 {
4817   int retval;
4818
4819   if (op1->low == NULL) /* op1 = (:L)  */
4820     {
4821       /* op2 = (:N), so overlap.  */
4822       retval = 0;
4823       /* op2 = (M:) or (M:N),  L < M  */
4824       if (op2->low != NULL
4825           && gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
4826         retval = -1;
4827     }
4828   else if (op1->high == NULL) /* op1 = (K:)  */
4829     {
4830       /* op2 = (M:), so overlap.  */
4831       retval = 0;
4832       /* op2 = (:N) or (M:N), K > N  */
4833       if (op2->high != NULL
4834           && gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
4835         retval = 1;
4836     }
4837   else /* op1 = (K:L)  */
4838     {
4839       if (op2->low == NULL)       /* op2 = (:N), K > N  */
4840         retval = (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
4841                  ? 1 : 0;
4842       else if (op2->high == NULL) /* op2 = (M:), L < M  */
4843         retval = (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
4844                  ? -1 : 0;
4845       else                      /* op2 = (M:N)  */
4846         {
4847           retval =  0;
4848           /* L < M  */
4849           if (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
4850             retval =  -1;
4851           /* K > N  */
4852           else if (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
4853             retval =  1;
4854         }
4855     }
4856
4857   return retval;
4858 }
4859
4860
4861 /* Merge-sort a double linked case list, detecting overlap in the
4862    process.  LIST is the head of the double linked case list before it
4863    is sorted.  Returns the head of the sorted list if we don't see any
4864    overlap, or NULL otherwise.  */
4865
4866 static gfc_case *
4867 check_case_overlap (gfc_case *list)
4868 {
4869   gfc_case *p, *q, *e, *tail;
4870   int insize, nmerges, psize, qsize, cmp, overlap_seen;
4871
4872   /* If the passed list was empty, return immediately.  */
4873   if (!list)
4874     return NULL;
4875
4876   overlap_seen = 0;
4877   insize = 1;
4878
4879   /* Loop unconditionally.  The only exit from this loop is a return
4880      statement, when we've finished sorting the case list.  */
4881   for (;;)
4882     {
4883       p = list;
4884       list = NULL;
4885       tail = NULL;
4886
4887       /* Count the number of merges we do in this pass.  */
4888       nmerges = 0;
4889
4890       /* Loop while there exists a merge to be done.  */
4891       while (p)
4892         {
4893           int i;
4894
4895           /* Count this merge.  */
4896           nmerges++;
4897
4898           /* Cut the list in two pieces by stepping INSIZE places
4899              forward in the list, starting from P.  */
4900           psize = 0;
4901           q = p;
4902           for (i = 0; i < insize; i++)
4903             {
4904               psize++;
4905               q = q->right;
4906               if (!q)
4907                 break;
4908             }
4909           qsize = insize;
4910
4911           /* Now we have two lists.  Merge them!  */
4912           while (psize > 0 || (qsize > 0 && q != NULL))
4913             {
4914               /* See from which the next case to merge comes from.  */
4915               if (psize == 0)
4916                 {
4917                   /* P is empty so the next case must come from Q.  */
4918                   e = q;
4919                   q = q->right;
4920                   qsize--;
4921                 }
4922               else if (qsize == 0 || q == NULL)
4923                 {
4924                   /* Q is empty.  */
4925                   e = p;
4926                   p = p->right;
4927                   psize--;
4928                 }
4929               else
4930                 {
4931                   cmp = compare_cases (p, q);
4932                   if (cmp < 0)
4933                     {
4934                       /* The whole case range for P is less than the
4935                          one for Q.  */
4936                       e = p;
4937                       p = p->right;
4938                       psize--;
4939                     }
4940                   else if (cmp > 0)
4941                     {
4942                       /* The whole case range for Q is greater than
4943                          the case range for P.  */
4944                       e = q;
4945                       q = q->right;
4946                       qsize--;
4947                     }
4948                   else
4949                     {
4950                       /* The cases overlap, or they are the same
4951                          element in the list.  Either way, we must
4952                          issue an error and get the next case from P.  */
4953                       /* FIXME: Sort P and Q by line number.  */
4954                       gfc_error ("CASE label at %L overlaps with CASE "
4955                                  "label at %L", &p->where, &q->where);
4956                       overlap_seen = 1;
4957                       e = p;
4958                       p = p->right;
4959                       psize--;
4960                     }
4961                 }
4962
4963                 /* Add the next element to the merged list.  */
4964               if (tail)
4965                 tail->right = e;
4966               else
4967                 list = e;
4968               e->left = tail;
4969               tail = e;
4970             }
4971
4972           /* P has now stepped INSIZE places along, and so has Q.  So
4973              they're the same.  */
4974           p = q;
4975         }
4976       tail->right = NULL;
4977
4978       /* If we have done only one merge or none at all, we've
4979          finished sorting the cases.  */
4980       if (nmerges <= 1)
4981         {
4982           if (!overlap_seen)
4983             return list;
4984           else
4985             return NULL;
4986         }
4987
4988       /* Otherwise repeat, merging lists twice the size.  */
4989       insize *= 2;
4990     }
4991 }
4992
4993
4994 /* Check to see if an expression is suitable for use in a CASE statement.
4995    Makes sure that all case expressions are scalar constants of the same
4996    type.  Return FAILURE if anything is wrong.  */
4997
4998 static try
4999 validate_case_label_expr (gfc_expr *e, gfc_expr *case_expr)
5000 {
5001   if (e == NULL) return SUCCESS;
5002
5003   if (e->ts.type != case_expr->ts.type)
5004     {
5005       gfc_error ("Expression in CASE statement at %L must be of type %s",
5006                  &e->where, gfc_basic_typename (case_expr->ts.type));
5007       return FAILURE;
5008     }
5009
5010   /* C805 (R808) For a given case-construct, each case-value shall be of
5011      the same type as case-expr.  For character type, length differences
5012      are allowed, but the kind type parameters shall be the same.  */
5013
5014   if (case_expr->ts.type == BT_CHARACTER && e->ts.kind != case_expr->ts.kind)
5015     {
5016       gfc_error("Expression in CASE statement at %L must be kind %d",
5017                 &e->where, case_expr->ts.kind);
5018       return FAILURE;
5019     }
5020
5021   /* Convert the case value kind to that of case expression kind, if needed.
5022      FIXME:  Should a warning be issued?  */
5023   if (e->ts.kind != case_expr->ts.kind)
5024     gfc_convert_type_warn (e, &case_expr->ts, 2, 0);
5025
5026   if (e->rank != 0)
5027     {
5028       gfc_error ("Expression in CASE statement at %L must be scalar",
5029                  &e->where);
5030       return FAILURE;
5031     }
5032
5033   return SUCCESS;
5034 }
5035
5036
5037 /* Given a completely parsed select statement, we:
5038
5039      - Validate all expressions and code within the SELECT.
5040      - Make sure that the selection expression is not of the wrong type.
5041      - Make sure that no case ranges overlap.
5042      - Eliminate unreachable cases and unreachable code resulting from
5043        removing case labels.
5044
5045    The standard does allow unreachable cases, e.g. CASE (5:3).  But
5046    they are a hassle for code generation, and to prevent that, we just
5047    cut them out here.  This is not necessary for overlapping cases
5048    because they are illegal and we never even try to generate code.
5049
5050    We have the additional caveat that a SELECT construct could have
5051    been a computed GOTO in the source code. Fortunately we can fairly
5052    easily work around that here: The case_expr for a "real" SELECT CASE
5053    is in code->expr1, but for a computed GOTO it is in code->expr2. All
5054    we have to do is make sure that the case_expr is a scalar integer
5055    expression.  */
5056
5057 static void
5058 resolve_select (gfc_code *code)
5059 {
5060   gfc_code *body;
5061   gfc_expr *case_expr;
5062   gfc_case *cp, *default_case, *tail, *head;
5063   int seen_unreachable;
5064   int seen_logical;
5065   int ncases;
5066   bt type;
5067   try t;
5068
5069   if (code->expr == NULL)
5070     {
5071       /* This was actually a computed GOTO statement.  */
5072       case_expr = code->expr2;
5073       if (case_expr->ts.type != BT_INTEGER|| case_expr->rank != 0)
5074         gfc_error ("Selection expression in computed GOTO statement "
5075                    "at %L must be a scalar integer expression",
5076                    &case_expr->where);
5077
5078       /* Further checking is not necessary because this SELECT was built
5079          by the compiler, so it should always be OK.  Just move the
5080          case_expr from expr2 to expr so that we can handle computed
5081          GOTOs as normal SELECTs from here on.  */
5082       code->expr = code->expr2;
5083       code->expr2 = NULL;
5084       return;
5085     }
5086
5087   case_expr = code->expr;
5088
5089   type = case_expr->ts.type;
5090   if (type != BT_LOGICAL && type != BT_INTEGER && type != BT_CHARACTER)
5091     {
5092       gfc_error ("Argument of SELECT statement at %L cannot be %s",
5093                  &case_expr->where, gfc_typename (&case_expr->ts));
5094
5095       /* Punt. Going on here just produce more garbage error messages.  */
5096       return;
5097     }
5098
5099   if (case_expr->rank != 0)
5100     {
5101       gfc_error ("Argument of SELECT statement at %L must be a scalar "
5102                  "expression", &case_expr->where);
5103
5104       /* Punt.  */
5105       return;
5106     }
5107
5108   /* PR 19168 has a long discussion concerning a mismatch of the kinds
5109      of the SELECT CASE expression and its CASE values.  Walk the lists
5110      of case values, and if we find a mismatch, promote case_expr to
5111      the appropriate kind.  */
5112
5113   if (type == BT_LOGICAL || type == BT_INTEGER)
5114     {
5115       for (body = code->block; body; body = body->block)
5116         {
5117           /* Walk the case label list.  */
5118           for (cp = body->ext.case_list; cp; cp = cp->next)
5119             {
5120               /* Intercept the DEFAULT case.  It does not have a kind.  */
5121               if (cp->low == NULL && cp->high == NULL)
5122                 continue;
5123
5124               /* Unreachable case ranges are discarded, so ignore.  */
5125               if (cp->low != NULL && cp->high != NULL
5126                   && cp->low != cp->high
5127                   && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
5128                 continue;
5129
5130               /* FIXME: Should a warning be issued?  */
5131               if (cp->low != NULL
5132                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->low))
5133                 gfc_convert_type_warn (case_expr, &cp->low->ts, 2, 0);
5134
5135               if (cp->high != NULL
5136                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->high))
5137                 gfc_convert_type_warn (case_expr, &cp->high->ts, 2, 0);
5138             }
5139          }
5140     }
5141
5142   /* Assume there is no DEFAULT case.  */
5143   default_case = NULL;
5144   head = tail = NULL;
5145   ncases = 0;
5146   seen_logical = 0;
5147
5148   for (body = code->block; body; body = body->block)
5149     {
5150       /* Assume the CASE list is OK, and all CASE labels can be matched.  */
5151       t = SUCCESS;
5152       seen_unreachable = 0;
5153
5154       /* Walk the case label list, making sure that all case labels
5155          are legal.  */
5156       for (cp = body->ext.case_list; cp; cp = cp->next)
5157         {
5158           /* Count the number of cases in the whole construct.  */
5159           ncases++;
5160
5161           /* Intercept the DEFAULT case.  */
5162           if (cp->low == NULL && cp->high == NULL)
5163             {
5164               if (default_case != NULL)
5165                 {
5166                   gfc_error ("The DEFAULT CASE at %L cannot be followed "
5167                              "by a second DEFAULT CASE at %L",
5168                              &default_case->where, &cp->where);
5169                   t = FAILURE;
5170                   break;
5171                 }
5172               else
5173                 {
5174                   default_case = cp;
5175                   continue;
5176                 }
5177             }
5178
5179           /* Deal with single value cases and case ranges.  Errors are
5180              issued from the validation function.  */
5181           if(validate_case_label_expr (cp->low, case_expr) != SUCCESS
5182              || validate_case_label_expr (cp->high, case_expr) != SUCCESS)
5183             {
5184               t = FAILURE;
5185               break;
5186             }
5187
5188           if (type == BT_LOGICAL
5189               && ((cp->low == NULL || cp->high == NULL)
5190                   || cp->low != cp->high))
5191             {
5192               gfc_error ("Logical range in CASE statement at %L is not "
5193                          "allowed", &cp->low->where);
5194               t = FAILURE;
5195               break;
5196             }
5197
5198           if (type == BT_LOGICAL && cp->low->expr_type == EXPR_CONSTANT)
5199             {
5200               int value;
5201               value = cp->low->value.logical == 0 ? 2 : 1;
5202               if (value & seen_logical)
5203                 {
5204                   gfc_error ("constant logical value in CASE statement "
5205                              "is repeated at %L",
5206                              &cp->low->where);
5207                   t = FAILURE;
5208                   break;
5209                 }
5210               seen_logical |= value;
5211             }
5212
5213           if (cp->low != NULL && cp->high != NULL
5214               && cp->low != cp->high
5215               && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
5216             {
5217               if (gfc_option.warn_surprising)
5218                 gfc_warning ("Range specification at %L can never "
5219                              "be matched", &cp->where);
5220
5221               cp->unreachable = 1;
5222               seen_unreachable = 1;
5223             }
5224           else
5225             {
5226               /* If the case range can be matched, it can also overlap with
5227                  other cases.  To make sure it does not, we put it in a
5228                  double linked list here.  We sort that with a merge sort
5229                  later on to detect any overlapping cases.  */
5230               if (!head)
5231                 {
5232                   head = tail = cp;
5233                   head->right = head->left = NULL;
5234                 }
5235               else
5236                 {
5237                   tail->right = cp;
5238                   tail->right->left = tail;
5239                   tail = tail->right;
5240                   tail->right = NULL;
5241                 }
5242             }
5243         }
5244
5245       /* It there was a failure in the previous case label, give up
5246          for this case label list.  Continue with the next block.  */
5247       if (t == FAILURE)
5248         continue;
5249
5250       /* See if any case labels that are unreachable have been seen.
5251          If so, we eliminate them.  This is a bit of a kludge because
5252          the case lists for a single case statement (label) is a
5253          single forward linked lists.  */
5254       if (seen_unreachable)
5255       {
5256         /* Advance until the first case in the list is reachable.  */
5257         while (body->ext.case_list != NULL
5258                && body->ext.case_list->unreachable)
5259           {
5260             gfc_case *n = body->ext.case_list;
5261             body->ext.case_list = body->ext.case_list->next;
5262             n->next = NULL;
5263             gfc_free_case_list (n);
5264           }
5265
5266         /* Strip all other unreachable cases.  */
5267         if (body->ext.case_list)
5268           {
5269             for (cp = body->ext.case_list; cp->next; cp = cp->next)
5270               {
5271                 if (cp->next->unreachable)
5272                   {
5273                     gfc_case *n = cp->next;
5274                     cp->next = cp->next->next;
5275                     n->next = NULL;
5276                     gfc_free_case_list (n);
5277                   }
5278               }
5279           }
5280       }
5281     }
5282
5283   /* See if there were overlapping cases.  If the check returns NULL,
5284      there was overlap.  In that case we don't do anything.  If head
5285      is non-NULL, we prepend the DEFAULT case.  The sorted list can
5286      then used during code generation for SELECT CASE constructs with
5287      a case expression of a CHARACTER type.  */
5288   if (head)
5289     {
5290       head = check_case_overlap (head);
5291
5292       /* Prepend the default_case if it is there.  */
5293       if (head != NULL && default_case)
5294         {
5295           default_case->left = NULL;
5296           default_case->right = head;
5297           head->left = default_case;
5298         }
5299     }
5300
5301   /* Eliminate dead blocks that may be the result if we've seen
5302      unreachable case labels for a block.  */
5303   for (body = code; body && body->block; body = body->block)
5304     {
5305       if (body->block->ext.case_list == NULL)
5306         {
5307           /* Cut the unreachable block from the code chain.  */
5308           gfc_code *c = body->block;
5309           body->block = c->block;
5310
5311           /* Kill the dead block, but not the blocks below it.  */
5312           c->block = NULL;
5313           gfc_free_statements (c);
5314         }
5315     }
5316
5317   /* More than two cases is legal but insane for logical selects.
5318      Issue a warning for it.  */
5319   if (gfc_option.warn_surprising && type == BT_LOGICAL
5320       && ncases > 2)
5321     gfc_warning ("Logical SELECT CASE block at %L has more that two cases",
5322                  &code->loc);
5323 }
5324
5325
5326 /* Resolve a transfer statement. This is making sure that:
5327    -- a derived type being transferred has only non-pointer components
5328    -- a derived type being transferred doesn't have private components, unless 
5329       it's being transferred from the module where the type was defined
5330    -- we're not trying to transfer a whole assumed size array.  */
5331
5332 static void
5333 resolve_transfer (gfc_code *code)
5334 {
5335   gfc_typespec *ts;
5336   gfc_symbol *sym;
5337   gfc_ref *ref;
5338   gfc_expr *exp;
5339
5340   exp = code->expr;
5341
5342   if (exp->expr_type != EXPR_VARIABLE && exp->expr_type != EXPR_FUNCTION)
5343     return;
5344
5345   sym = exp->symtree->n.sym;
5346   ts = &sym->ts;
5347
5348   /* Go to actual component transferred.  */
5349   for (ref = code->expr->ref; ref; ref = ref->next)
5350     if (ref->type == REF_COMPONENT)
5351       ts = &ref->u.c.component->ts;
5352
5353   if (ts->type == BT_DERIVED)
5354     {
5355       /* Check that transferred derived type doesn't contain POINTER
5356          components.  */
5357       if (ts->derived->attr.pointer_comp)
5358         {
5359           gfc_error ("Data transfer element at %L cannot have "
5360                      "POINTER components", &code->loc);
5361           return;
5362         }
5363
5364       if (ts->derived->attr.alloc_comp)
5365         {
5366           gfc_error ("Data transfer element at %L cannot have "
5367                      "ALLOCATABLE components", &code->loc);
5368           return;
5369         }
5370
5371       if (derived_inaccessible (ts->derived))
5372         {
5373           gfc_error ("Data transfer element at %L cannot have "
5374                      "PRIVATE components",&code->loc);
5375           return;
5376         }
5377     }
5378
5379   if (sym->as != NULL && sym->as->type == AS_ASSUMED_SIZE
5380       && exp->ref->type == REF_ARRAY && exp->ref->u.ar.type == AR_FULL)
5381     {
5382       gfc_error ("Data transfer element at %L cannot be a full reference to "
5383                  "an assumed-size array", &code->loc);
5384       return;
5385     }
5386 }
5387
5388
5389 /*********** Toplevel code resolution subroutines ***********/
5390
5391 /* Find the set of labels that are reachable from this block.  We also
5392    record the last statement in each block so that we don't have to do
5393    a linear search to find the END DO statements of the blocks.  */
5394      
5395 static void
5396 reachable_labels (gfc_code *block)
5397 {
5398   gfc_code *c;
5399
5400   if (!block)
5401     return;
5402
5403   cs_base->reachable_labels = bitmap_obstack_alloc (&labels_obstack);
5404
5405   /* Collect labels in this block.  */
5406   for (c = block; c; c = c->next)
5407     {
5408       if (c->here)
5409         bitmap_set_bit (cs_base->reachable_labels, c->here->value);
5410
5411       if (!c->next && cs_base->prev)
5412         cs_base->prev->tail = c;
5413     }
5414
5415   /* Merge with labels from parent block.  */
5416   if (cs_base->prev)
5417     {
5418       gcc_assert (cs_base->prev->reachable_labels);
5419       bitmap_ior_into (cs_base->reachable_labels,
5420                        cs_base->prev->reachable_labels);
5421     }
5422 }
5423
5424 /* Given a branch to a label and a namespace, if the branch is conforming.
5425    The code node describes where the branch is located.  */
5426
5427 static void
5428 resolve_branch (gfc_st_label *label, gfc_code *code)
5429 {
5430   code_stack *stack;
5431
5432   if (label == NULL)
5433     return;
5434
5435   /* Step one: is this a valid branching target?  */
5436
5437   if (label->defined == ST_LABEL_UNKNOWN)
5438     {
5439       gfc_error ("Label %d referenced at %L is never defined", label->value,
5440                  &label->where);
5441       return;
5442     }
5443
5444   if (label->defined != ST_LABEL_TARGET)
5445     {
5446       gfc_error ("Statement at %L is not a valid branch target statement "
5447                  "for the branch statement at %L", &label->where, &code->loc);
5448       return;
5449     }
5450
5451   /* Step two: make sure this branch is not a branch to itself ;-)  */
5452
5453   if (code->here == label)
5454     {
5455       gfc_warning ("Branch at %L causes an infinite loop", &code->loc);
5456       return;
5457     }
5458
5459   /* Step three:  See if the label is in the same block as the
5460      branching statement.  The hard work has been done by setting up
5461      the bitmap reachable_labels.  */
5462
5463   if (!bitmap_bit_p (cs_base->reachable_labels, label->value))
5464     {
5465       /* The label is not in an enclosing block, so illegal.  This was
5466          allowed in Fortran 66, so we allow it as extension.  No
5467          further checks are necessary in this case.  */
5468       gfc_notify_std (GFC_STD_LEGACY, "Label at %L is not in the same block "
5469                       "as the GOTO statement at %L", &label->where,
5470                       &code->loc);
5471       return;
5472     }
5473
5474   /* Step four: Make sure that the branching target is legal if
5475      the statement is an END {SELECT,IF}.  */
5476
5477   for (stack = cs_base; stack; stack = stack->prev)
5478     if (stack->current->next && stack->current->next->here == label)
5479       break;
5480
5481   if (stack && stack->current->next->op == EXEC_NOP)
5482     {
5483       gfc_notify_std (GFC_STD_F95_DEL, "Deleted feature: GOTO at %L jumps to "
5484                       "END of construct at %L", &code->loc,
5485                       &stack->current->next->loc);
5486       return;  /* We know this is not an END DO.  */
5487     }
5488
5489   /* Step five: Make sure that we're not jumping to the end of a DO
5490      loop from within the loop.  */
5491
5492   for (stack = cs_base; stack; stack = stack->prev)
5493     if ((stack->current->op == EXEC_DO
5494          || stack->current->op == EXEC_DO_WHILE)
5495         && stack->tail->here == label && stack->tail->op == EXEC_NOP)
5496       {
5497         gfc_notify_std (GFC_STD_F95_DEL, "Deleted feature: GOTO at %L jumps "
5498                         "to END of construct at %L", &code->loc,
5499                         &stack->tail->loc);
5500         return;
5501
5502       }
5503 }
5504
5505
5506 /* Check whether EXPR1 has the same shape as EXPR2.  */
5507
5508 static try
5509 resolve_where_shape (gfc_expr *expr1, gfc_expr *expr2)
5510 {
5511   mpz_t shape[GFC_MAX_DIMENSIONS];
5512   mpz_t shape2[GFC_MAX_DIMENSIONS];
5513   try result = FAILURE;
5514   int i;
5515
5516   /* Compare the rank.  */
5517   if (expr1->rank != expr2->rank)
5518     return result;
5519
5520   /* Compare the size of each dimension.  */
5521   for (i=0; i<expr1->rank; i++)
5522     {
5523       if (gfc_array_dimen_size (expr1, i, &shape[i]) == FAILURE)
5524         goto ignore;
5525
5526       if (gfc_array_dimen_size (expr2, i, &shape2[i]) == FAILURE)
5527         goto ignore;
5528
5529       if (mpz_cmp (shape[i], shape2[i]))
5530         goto over;
5531     }
5532
5533   /* When either of the two expression is an assumed size array, we
5534      ignore the comparison of dimension sizes.  */
5535 ignore:
5536   result = SUCCESS;
5537
5538 over:
5539   for (i--; i >= 0; i--)
5540     {
5541       mpz_clear (shape[i]);
5542       mpz_clear (shape2[i]);
5543     }
5544   return result;
5545 }
5546
5547
5548 /* Check whether a WHERE assignment target or a WHERE mask expression
5549    has the same shape as the outmost WHERE mask expression.  */
5550
5551 static void
5552 resolve_where (gfc_code *code, gfc_expr *mask)
5553 {
5554   gfc_code *cblock;
5555   gfc_code *cnext;
5556   gfc_expr *e = NULL;
5557
5558   cblock = code->block;
5559
5560   /* Store the first WHERE mask-expr of the WHERE statement or construct.
5561      In case of nested WHERE, only the outmost one is stored.  */
5562   if (mask == NULL) /* outmost WHERE */
5563     e = cblock->expr;
5564   else /* inner WHERE */
5565     e = mask;
5566
5567   while (cblock)
5568     {
5569       if (cblock->expr)
5570         {
5571           /* Check if the mask-expr has a consistent shape with the
5572              outmost WHERE mask-expr.  */
5573           if (resolve_where_shape (cblock->expr, e) == FAILURE)
5574             gfc_error ("WHERE mask at %L has inconsistent shape",
5575                        &cblock->expr->where);
5576          }
5577
5578       /* the assignment statement of a WHERE statement, or the first
5579          statement in where-body-construct of a WHERE construct */
5580       cnext = cblock->next;
5581       while (cnext)
5582         {
5583           switch (cnext->op)
5584             {
5585             /* WHERE assignment statement */
5586             case EXEC_ASSIGN:
5587
5588               /* Check shape consistent for WHERE assignment target.  */
5589               if (e && resolve_where_shape (cnext->expr, e) == FAILURE)
5590                gfc_error ("WHERE assignment target at %L has "
5591                           "inconsistent shape", &cnext->expr->where);
5592               break;
5593
5594   
5595             case EXEC_ASSIGN_CALL:
5596               resolve_call (cnext);
5597               break;
5598
5599             /* WHERE or WHERE construct is part of a where-body-construct */
5600             case EXEC_WHERE:
5601               resolve_where (cnext, e);
5602               break;
5603
5604             default:
5605               gfc_error ("Unsupported statement inside WHERE at %L",
5606                          &cnext->loc);
5607             }
5608          /* the next statement within the same where-body-construct */
5609          cnext = cnext->next;
5610        }
5611     /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
5612     cblock = cblock->block;
5613   }
5614 }
5615
5616
5617 /* Resolve assignment in FORALL construct.
5618    NVAR is the number of FORALL index variables, and VAR_EXPR records the
5619    FORALL index variables.  */
5620
5621 static void
5622 gfc_resolve_assign_in_forall (gfc_code *code, int nvar, gfc_expr **var_expr)
5623 {
5624   int n;
5625
5626   for (n = 0; n < nvar; n++)
5627     {
5628       gfc_symbol *forall_index;
5629
5630       forall_index = var_expr[n]->symtree->n.sym;
5631
5632       /* Check whether the assignment target is one of the FORALL index
5633          variable.  */
5634       if ((code->expr->expr_type == EXPR_VARIABLE)
5635           && (code->expr->symtree->n.sym == forall_index))
5636         gfc_error ("Assignment to a FORALL index variable at %L",
5637                    &code->expr->where);
5638       else
5639         {
5640           /* If one of the FORALL index variables doesn't appear in the
5641              assignment target, then there will be a many-to-one
5642              assignment.  */
5643           if (find_forall_index (code->expr, forall_index, 0) == FAILURE)
5644             gfc_error ("The FORALL with index '%s' cause more than one "
5645                        "assignment to this object at %L",
5646                        var_expr[n]->symtree->name, &code->expr->where);
5647         }
5648     }
5649 }
5650
5651
5652 /* Resolve WHERE statement in FORALL construct.  */
5653
5654 static void
5655 gfc_resolve_where_code_in_forall (gfc_code *code, int nvar,
5656                                   gfc_expr **var_expr)
5657 {
5658   gfc_code *cblock;
5659   gfc_code *cnext;
5660
5661   cblock = code->block;
5662   while (cblock)
5663     {
5664       /* the assignment statement of a WHERE statement, or the first
5665          statement in where-body-construct of a WHERE construct */
5666       cnext = cblock->next;
5667       while (cnext)
5668         {
5669           switch (cnext->op)
5670             {
5671             /* WHERE assignment statement */
5672             case EXEC_ASSIGN:
5673               gfc_resolve_assign_in_forall (cnext, nvar, var_expr);
5674               break;
5675   
5676             /* WHERE operator assignment statement */
5677             case EXEC_ASSIGN_CALL:
5678               resolve_call (cnext);
5679               break;
5680
5681             /* WHERE or WHERE construct is part of a where-body-construct */
5682             case EXEC_WHERE:
5683               gfc_resolve_where_code_in_forall (cnext, nvar, var_expr);
5684               break;
5685
5686             default:
5687               gfc_error ("Unsupported statement inside WHERE at %L",
5688                          &cnext->loc);
5689             }
5690           /* the next statement within the same where-body-construct */
5691           cnext = cnext->next;
5692         }
5693       /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
5694       cblock = cblock->block;
5695     }
5696 }
5697
5698
5699 /* Traverse the FORALL body to check whether the following errors exist:
5700    1. For assignment, check if a many-to-one assignment happens.
5701    2. For WHERE statement, check the WHERE body to see if there is any
5702       many-to-one assignment.  */
5703
5704 static void
5705 gfc_resolve_forall_body (gfc_code *code, int nvar, gfc_expr **var_expr)
5706 {
5707   gfc_code *c;
5708
5709   c = code->block->next;
5710   while (c)
5711     {
5712       switch (c->op)
5713         {
5714         case EXEC_ASSIGN:
5715         case EXEC_POINTER_ASSIGN:
5716           gfc_resolve_assign_in_forall (c, nvar, var_expr);
5717           break;
5718
5719         case EXEC_ASSIGN_CALL:
5720           resolve_call (c);
5721           break;
5722
5723         /* Because the gfc_resolve_blocks() will handle the nested FORALL,
5724            there is no need to handle it here.  */
5725         case EXEC_FORALL:
5726           break;
5727         case EXEC_WHERE:
5728           gfc_resolve_where_code_in_forall(c, nvar, var_expr);
5729           break;
5730         default:
5731           break;
5732         }
5733       /* The next statement in the FORALL body.  */
5734       c = c->next;
5735     }
5736 }
5737
5738
5739 /* Given a FORALL construct, first resolve the FORALL iterator, then call
5740    gfc_resolve_forall_body to resolve the FORALL body.  */
5741
5742 static void
5743 gfc_resolve_forall (gfc_code *code, gfc_namespace *ns, int forall_save)
5744 {
5745   static gfc_expr **var_expr;
5746   static int total_var = 0;
5747   static int nvar = 0;
5748   gfc_forall_iterator *fa;
5749   gfc_code *next;
5750   int i;
5751
5752   /* Start to resolve a FORALL construct   */
5753   if (forall_save == 0)
5754     {
5755       /* Count the total number of FORALL index in the nested FORALL
5756          construct in order to allocate the VAR_EXPR with proper size.  */
5757       next = code;
5758       while ((next != NULL) && (next->op == EXEC_FORALL))
5759         {
5760           for (fa = next->ext.forall_iterator; fa; fa = fa->next)
5761             total_var ++;
5762           next = next->block->next;
5763         }
5764
5765       /* Allocate VAR_EXPR with NUMBER_OF_FORALL_INDEX elements.  */
5766       var_expr = (gfc_expr **) gfc_getmem (total_var * sizeof (gfc_expr *));
5767     }
5768
5769   /* The information about FORALL iterator, including FORALL index start, end
5770      and stride. The FORALL index can not appear in start, end or stride.  */
5771   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
5772     {
5773       /* Check if any outer FORALL index name is the same as the current
5774          one.  */
5775       for (i = 0; i < nvar; i++)
5776         {
5777           if (fa->var->symtree->n.sym == var_expr[i]->symtree->n.sym)
5778             {
5779               gfc_error ("An outer FORALL construct already has an index "
5780                          "with this name %L", &fa->var->where);
5781             }
5782         }
5783
5784       /* Record the current FORALL index.  */
5785       var_expr[nvar] = gfc_copy_expr (fa->var);
5786
5787       nvar++;
5788     }
5789
5790   /* Resolve the FORALL body.  */
5791   gfc_resolve_forall_body (code, nvar, var_expr);
5792
5793   /* May call gfc_resolve_forall to resolve the inner FORALL loop.  */
5794   gfc_resolve_blocks (code->block, ns);
5795
5796   /* Free VAR_EXPR after the whole FORALL construct resolved.  */
5797   for (i = 0; i < total_var; i++)
5798     gfc_free_expr (var_expr[i]);
5799
5800   /* Reset the counters.  */
5801   total_var = 0;
5802   nvar = 0;
5803 }
5804
5805
5806 /* Resolve lists of blocks found in IF, SELECT CASE, WHERE, FORALL ,GOTO and
5807    DO code nodes.  */
5808
5809 static void resolve_code (gfc_code *, gfc_namespace *);
5810
5811 void
5812 gfc_resolve_blocks (gfc_code *b, gfc_namespace *ns)
5813 {
5814   try t;
5815
5816   for (; b; b = b->block)
5817     {
5818       t = gfc_resolve_expr (b->expr);
5819       if (gfc_resolve_expr (b->expr2) == FAILURE)
5820         t = FAILURE;
5821
5822       switch (b->op)
5823         {
5824         case EXEC_IF:
5825           if (t == SUCCESS && b->expr != NULL
5826               && (b->expr->ts.type != BT_LOGICAL || b->expr->rank != 0))
5827             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
5828                        &b->expr->where);
5829           break;
5830
5831         case EXEC_WHERE:
5832           if (t == SUCCESS
5833               && b->expr != NULL
5834               && (b->expr->ts.type != BT_LOGICAL || b->expr->rank == 0))
5835             gfc_error ("WHERE/ELSEWHERE clause at %L requires a LOGICAL array",
5836                        &b->expr->where);
5837           break;
5838
5839         case EXEC_GOTO:
5840           resolve_branch (b->label, b);
5841           break;
5842
5843         case EXEC_SELECT:
5844         case EXEC_FORALL:
5845         case EXEC_DO:
5846         case EXEC_DO_WHILE:
5847         case EXEC_READ:
5848         case EXEC_WRITE:
5849         case EXEC_IOLENGTH:
5850           break;
5851
5852         case EXEC_OMP_ATOMIC:
5853         case EXEC_OMP_CRITICAL:
5854         case EXEC_OMP_DO:
5855         case EXEC_OMP_MASTER:
5856         case EXEC_OMP_ORDERED:
5857         case EXEC_OMP_PARALLEL:
5858         case EXEC_OMP_PARALLEL_DO:
5859         case EXEC_OMP_PARALLEL_SECTIONS:
5860         case EXEC_OMP_PARALLEL_WORKSHARE:
5861         case EXEC_OMP_SECTIONS:
5862         case EXEC_OMP_SINGLE:
5863         case EXEC_OMP_WORKSHARE:
5864           break;
5865
5866         default:
5867           gfc_internal_error ("resolve_block(): Bad block type");
5868         }
5869
5870       resolve_code (b->next, ns);
5871     }
5872 }
5873
5874
5875 /* Does everything to resolve an ordinary assignment.  Returns true
5876    if this is an interface asignment.  */
5877 static bool
5878 resolve_ordinary_assign (gfc_code *code, gfc_namespace *ns)
5879 {
5880   bool rval = false;
5881   gfc_expr *lhs;
5882   gfc_expr *rhs;
5883   int llen = 0;
5884   int rlen = 0;
5885   int n;
5886   gfc_ref *ref;
5887
5888
5889   if (gfc_extend_assign (code, ns) == SUCCESS)
5890     {
5891       lhs = code->ext.actual->expr;
5892       rhs = code->ext.actual->next->expr;
5893       if (gfc_pure (NULL) && !gfc_pure (code->symtree->n.sym))
5894         {
5895           gfc_error ("Subroutine '%s' called instead of assignment at "
5896                      "%L must be PURE", code->symtree->n.sym->name,
5897                      &code->loc);
5898           return rval;
5899         }
5900
5901       /* Make a temporary rhs when there is a default initializer
5902          and rhs is the same symbol as the lhs.  */
5903       if (rhs->expr_type == EXPR_VARIABLE
5904             && rhs->symtree->n.sym->ts.type == BT_DERIVED
5905             && has_default_initializer (rhs->symtree->n.sym->ts.derived)
5906             && (lhs->symtree->n.sym == rhs->symtree->n.sym))
5907         code->ext.actual->next->expr = gfc_get_parentheses (rhs);
5908
5909       return true;
5910     }
5911
5912   lhs = code->expr;
5913   rhs = code->expr2;
5914
5915   if (lhs->ts.type == BT_CHARACTER
5916         && gfc_option.warn_character_truncation)
5917     {
5918       if (lhs->ts.cl != NULL
5919             && lhs->ts.cl->length != NULL
5920             && lhs->ts.cl->length->expr_type == EXPR_CONSTANT)
5921         llen = mpz_get_si (lhs->ts.cl->length->value.integer);
5922
5923       if (rhs->expr_type == EXPR_CONSTANT)
5924         rlen = rhs->value.character.length;
5925
5926       else if (rhs->ts.cl != NULL
5927                  && rhs->ts.cl->length != NULL
5928                  && rhs->ts.cl->length->expr_type == EXPR_CONSTANT)
5929         rlen = mpz_get_si (rhs->ts.cl->length->value.integer);
5930
5931       if (rlen && llen && rlen > llen)
5932         gfc_warning_now ("CHARACTER expression will be truncated "
5933                          "in assignment (%d/%d) at %L",
5934                          llen, rlen, &code->loc);
5935     }
5936
5937   /* Ensure that a vector index expression for the lvalue is evaluated
5938      to a temporary if the lvalue symbol is referenced in it.  */
5939   if (lhs->rank)
5940     {
5941       for (ref = lhs->ref; ref; ref= ref->next)
5942         if (ref->type == REF_ARRAY)
5943           {
5944             for (n = 0; n < ref->u.ar.dimen; n++)
5945               if (ref->u.ar.dimen_type[n] == DIMEN_VECTOR
5946                     && find_sym_in_expr (lhs->symtree->n.sym,
5947                                          ref->u.ar.start[n]))
5948                 ref->u.ar.start[n]
5949                         = gfc_get_parentheses (ref->u.ar.start[n]);
5950           }
5951     }
5952
5953   if (gfc_pure (NULL))
5954     {
5955       if (gfc_impure_variable (lhs->symtree->n.sym))
5956         {
5957           gfc_error ("Cannot assign to variable '%s' in PURE "
5958                      "procedure at %L",
5959                       lhs->symtree->n.sym->name,
5960                       &lhs->where);
5961           return rval;
5962         }
5963
5964       if (lhs->ts.type == BT_DERIVED
5965             && lhs->expr_type == EXPR_VARIABLE
5966             && lhs->ts.derived->attr.pointer_comp
5967             && gfc_impure_variable (rhs->symtree->n.sym))
5968         {
5969           gfc_error ("The impure variable at %L is assigned to "
5970                      "a derived type variable with a POINTER "
5971                      "component in a PURE procedure (12.6)",
5972                      &rhs->where);
5973           return rval;
5974         }
5975     }
5976
5977   gfc_check_assign (lhs, rhs, 1);
5978   return false;
5979 }
5980
5981 /* Given a block of code, recursively resolve everything pointed to by this
5982    code block.  */
5983
5984 static void
5985 resolve_code (gfc_code *code, gfc_namespace *ns)
5986 {
5987   int omp_workshare_save;
5988   int forall_save;
5989   code_stack frame;
5990   gfc_alloc *a;
5991   try t;
5992
5993   frame.prev = cs_base;
5994   frame.head = code;
5995   cs_base = &frame;
5996
5997   reachable_labels (code);
5998
5999   for (; code; code = code->next)
6000     {
6001       frame.current = code;
6002       forall_save = forall_flag;
6003
6004       if (code->op == EXEC_FORALL)
6005         {
6006           forall_flag = 1;
6007           gfc_resolve_forall (code, ns, forall_save);
6008           forall_flag = 2;
6009         }
6010       else if (code->block)
6011         {
6012           omp_workshare_save = -1;
6013           switch (code->op)
6014             {
6015             case EXEC_OMP_PARALLEL_WORKSHARE:
6016               omp_workshare_save = omp_workshare_flag;
6017               omp_workshare_flag = 1;
6018               gfc_resolve_omp_parallel_blocks (code, ns);
6019               break;
6020             case EXEC_OMP_PARALLEL:
6021             case EXEC_OMP_PARALLEL_DO:
6022             case EXEC_OMP_PARALLEL_SECTIONS:
6023               omp_workshare_save = omp_workshare_flag;
6024               omp_workshare_flag = 0;
6025               gfc_resolve_omp_parallel_blocks (code, ns);
6026               break;
6027             case EXEC_OMP_DO:
6028               gfc_resolve_omp_do_blocks (code, ns);
6029               break;
6030             case EXEC_OMP_WORKSHARE:
6031               omp_workshare_save = omp_workshare_flag;
6032               omp_workshare_flag = 1;
6033               /* FALLTHROUGH */
6034             default:
6035               gfc_resolve_blocks (code->block, ns);
6036               break;
6037             }
6038
6039           if (omp_workshare_save != -1)
6040             omp_workshare_flag = omp_workshare_save;
6041         }
6042
6043       t = gfc_resolve_expr (code->expr);
6044       forall_flag = forall_save;
6045
6046       if (gfc_resolve_expr (code->expr2) == FAILURE)
6047         t = FAILURE;
6048
6049       switch (code->op)
6050         {
6051         case EXEC_NOP:
6052         case EXEC_CYCLE:
6053         case EXEC_PAUSE:
6054         case EXEC_STOP:
6055         case EXEC_EXIT:
6056         case EXEC_CONTINUE:
6057         case EXEC_DT_END:
6058           break;
6059
6060         case EXEC_ENTRY:
6061           /* Keep track of which entry we are up to.  */
6062           current_entry_id = code->ext.entry->id;
6063           break;
6064
6065         case EXEC_WHERE:
6066           resolve_where (code, NULL);
6067           break;
6068
6069         case EXEC_GOTO:
6070           if (code->expr != NULL)
6071             {
6072               if (code->expr->ts.type != BT_INTEGER)
6073                 gfc_error ("ASSIGNED GOTO statement at %L requires an "
6074                            "INTEGER variable", &code->expr->where);
6075               else if (code->expr->symtree->n.sym->attr.assign != 1)
6076                 gfc_error ("Variable '%s' has not been assigned a target "
6077                            "label at %L", code->expr->symtree->n.sym->name,
6078                            &code->expr->where);
6079             }
6080           else
6081             resolve_branch (code->label, code);
6082           break;
6083
6084         case EXEC_RETURN:
6085           if (code->expr != NULL
6086                 && (code->expr->ts.type != BT_INTEGER || code->expr->rank))
6087             gfc_error ("Alternate RETURN statement at %L requires a SCALAR-"
6088                        "INTEGER return specifier", &code->expr->where);
6089           break;
6090
6091         case EXEC_INIT_ASSIGN:
6092           break;
6093
6094         case EXEC_ASSIGN:
6095           if (t == FAILURE)
6096             break;
6097
6098           if (resolve_ordinary_assign (code, ns))
6099             goto call;
6100
6101           break;
6102
6103         case EXEC_LABEL_ASSIGN:
6104           if (code->label->defined == ST_LABEL_UNKNOWN)
6105             gfc_error ("Label %d referenced at %L is never defined",
6106                        code->label->value, &code->label->where);
6107           if (t == SUCCESS
6108               && (code->expr->expr_type != EXPR_VARIABLE
6109                   || code->expr->symtree->n.sym->ts.type != BT_INTEGER
6110                   || code->expr->symtree->n.sym->ts.kind
6111                      != gfc_default_integer_kind
6112                   || code->expr->symtree->n.sym->as != NULL))
6113             gfc_error ("ASSIGN statement at %L requires a scalar "
6114                        "default INTEGER variable", &code->expr->where);
6115           break;
6116
6117         case EXEC_POINTER_ASSIGN:
6118           if (t == FAILURE)
6119             break;
6120
6121           gfc_check_pointer_assign (code->expr, code->expr2);
6122           break;
6123
6124         case EXEC_ARITHMETIC_IF:
6125           if (t == SUCCESS
6126               && code->expr->ts.type != BT_INTEGER
6127               && code->expr->ts.type != BT_REAL)
6128             gfc_error ("Arithmetic IF statement at %L requires a numeric "
6129                        "expression", &code->expr->where);
6130
6131           resolve_branch (code->label, code);
6132           resolve_branch (code->label2, code);
6133           resolve_branch (code->label3, code);
6134           break;
6135
6136         case EXEC_IF:
6137           if (t == SUCCESS && code->expr != NULL
6138               && (code->expr->ts.type != BT_LOGICAL
6139                   || code->expr->rank != 0))
6140             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
6141                        &code->expr->where);
6142           break;
6143
6144         case EXEC_CALL:
6145         call:
6146           resolve_call (code);
6147           break;
6148
6149         case EXEC_SELECT:
6150           /* Select is complicated. Also, a SELECT construct could be
6151              a transformed computed GOTO.  */
6152           resolve_select (code);
6153           break;
6154
6155         case EXEC_DO:
6156           if (code->ext.iterator != NULL)
6157             {
6158               gfc_iterator *iter = code->ext.iterator;
6159               if (gfc_resolve_iterator (iter, true) != FAILURE)
6160                 gfc_resolve_do_iterator (code, iter->var->symtree->n.sym);
6161             }
6162           break;
6163
6164         case EXEC_DO_WHILE:
6165           if (code->expr == NULL)
6166             gfc_internal_error ("resolve_code(): No expression on DO WHILE");
6167           if (t == SUCCESS
6168               && (code->expr->rank != 0
6169                   || code->expr->ts.type != BT_LOGICAL))
6170             gfc_error ("Exit condition of DO WHILE loop at %L must be "
6171                        "a scalar LOGICAL expression", &code->expr->where);
6172           break;
6173
6174         case EXEC_ALLOCATE:
6175           if (t == SUCCESS && code->expr != NULL
6176               && code->expr->ts.type != BT_INTEGER)
6177             gfc_error ("STAT tag in ALLOCATE statement at %L must be "
6178                        "of type INTEGER", &code->expr->where);
6179
6180           for (a = code->ext.alloc_list; a; a = a->next)
6181             resolve_allocate_expr (a->expr, code);
6182
6183           break;
6184
6185         case EXEC_DEALLOCATE:
6186           if (t == SUCCESS && code->expr != NULL
6187               && code->expr->ts.type != BT_INTEGER)
6188             gfc_error
6189               ("STAT tag in DEALLOCATE statement at %L must be of type "
6190                "INTEGER", &code->expr->where);
6191
6192           for (a = code->ext.alloc_list; a; a = a->next)
6193             resolve_deallocate_expr (a->expr);
6194
6195           break;
6196
6197         case EXEC_OPEN:
6198           if (gfc_resolve_open (code->ext.open) == FAILURE)
6199             break;
6200
6201           resolve_branch (code->ext.open->err, code);
6202           break;
6203
6204         case EXEC_CLOSE:
6205           if (gfc_resolve_close (code->ext.close) == FAILURE)
6206             break;
6207
6208           resolve_branch (code->ext.close->err, code);
6209           break;
6210
6211         case EXEC_BACKSPACE:
6212         case EXEC_ENDFILE:
6213         case EXEC_REWIND:
6214         case EXEC_FLUSH:
6215           if (gfc_resolve_filepos (code->ext.filepos) == FAILURE)
6216             break;
6217
6218           resolve_branch (code->ext.filepos->err, code);
6219           break;
6220
6221         case EXEC_INQUIRE:
6222           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
6223               break;
6224
6225           resolve_branch (code->ext.inquire->err, code);
6226           break;
6227
6228         case EXEC_IOLENGTH:
6229           gcc_assert (code->ext.inquire != NULL);
6230           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
6231             break;
6232
6233           resolve_branch (code->ext.inquire->err, code);
6234           break;
6235
6236         case EXEC_READ:
6237         case EXEC_WRITE:
6238           if (gfc_resolve_dt (code->ext.dt) == FAILURE)
6239             break;
6240
6241           resolve_branch (code->ext.dt->err, code);
6242           resolve_branch (code->ext.dt->end, code);
6243           resolve_branch (code->ext.dt->eor, code);
6244           break;
6245
6246         case EXEC_TRANSFER:
6247           resolve_transfer (code);
6248           break;
6249
6250         case EXEC_FORALL:
6251           resolve_forall_iterators (code->ext.forall_iterator);
6252
6253           if (code->expr != NULL && code->expr->ts.type != BT_LOGICAL)
6254             gfc_error ("FORALL mask clause at %L requires a LOGICAL "
6255                        "expression", &code->expr->where);
6256           break;
6257
6258         case EXEC_OMP_ATOMIC:
6259         case EXEC_OMP_BARRIER:
6260         case EXEC_OMP_CRITICAL:
6261         case EXEC_OMP_FLUSH:
6262         case EXEC_OMP_DO:
6263         case EXEC_OMP_MASTER:
6264         case EXEC_OMP_ORDERED:
6265         case EXEC_OMP_SECTIONS:
6266         case EXEC_OMP_SINGLE:
6267         case EXEC_OMP_WORKSHARE:
6268           gfc_resolve_omp_directive (code, ns);
6269           break;
6270
6271         case EXEC_OMP_PARALLEL:
6272         case EXEC_OMP_PARALLEL_DO:
6273         case EXEC_OMP_PARALLEL_SECTIONS:
6274         case EXEC_OMP_PARALLEL_WORKSHARE:
6275           omp_workshare_save = omp_workshare_flag;
6276           omp_workshare_flag = 0;
6277           gfc_resolve_omp_directive (code, ns);
6278           omp_workshare_flag = omp_workshare_save;
6279           break;
6280
6281         default:
6282           gfc_internal_error ("resolve_code(): Bad statement code");
6283         }
6284     }
6285
6286   cs_base = frame.prev;
6287 }
6288
6289
6290 /* Resolve initial values and make sure they are compatible with
6291    the variable.  */
6292
6293 static void
6294 resolve_values (gfc_symbol *sym)
6295 {
6296   if (sym->value == NULL)
6297     return;
6298
6299   if (gfc_resolve_expr (sym->value) == FAILURE)
6300     return;
6301
6302   gfc_check_assign_symbol (sym, sym->value);
6303 }
6304
6305
6306 /* Verify the binding labels for common blocks that are BIND(C).  The label
6307    for a BIND(C) common block must be identical in all scoping units in which
6308    the common block is declared.  Further, the binding label can not collide
6309    with any other global entity in the program.  */
6310
6311 static void
6312 resolve_bind_c_comms (gfc_symtree *comm_block_tree)
6313 {
6314   if (comm_block_tree->n.common->is_bind_c == 1)
6315     {
6316       gfc_gsymbol *binding_label_gsym;
6317       gfc_gsymbol *comm_name_gsym;
6318
6319       /* See if a global symbol exists by the common block's name.  It may
6320          be NULL if the common block is use-associated.  */
6321       comm_name_gsym = gfc_find_gsymbol (gfc_gsym_root,
6322                                          comm_block_tree->n.common->name);
6323       if (comm_name_gsym != NULL && comm_name_gsym->type != GSYM_COMMON)
6324         gfc_error ("Binding label '%s' for common block '%s' at %L collides "
6325                    "with the global entity '%s' at %L",
6326                    comm_block_tree->n.common->binding_label,
6327                    comm_block_tree->n.common->name,
6328                    &(comm_block_tree->n.common->where),
6329                    comm_name_gsym->name, &(comm_name_gsym->where));
6330       else if (comm_name_gsym != NULL
6331                && strcmp (comm_name_gsym->name,
6332                           comm_block_tree->n.common->name) == 0)
6333         {
6334           /* TODO: Need to make sure the fields of gfc_gsymbol are initialized
6335              as expected.  */
6336           if (comm_name_gsym->binding_label == NULL)
6337             /* No binding label for common block stored yet; save this one.  */
6338             comm_name_gsym->binding_label =
6339               comm_block_tree->n.common->binding_label;
6340           else
6341             if (strcmp (comm_name_gsym->binding_label,
6342                         comm_block_tree->n.common->binding_label) != 0)
6343               {
6344                 /* Common block names match but binding labels do not.  */
6345                 gfc_error ("Binding label '%s' for common block '%s' at %L "
6346                            "does not match the binding label '%s' for common "
6347                            "block '%s' at %L",
6348                            comm_block_tree->n.common->binding_label,
6349                            comm_block_tree->n.common->name,
6350                            &(comm_block_tree->n.common->where),
6351                            comm_name_gsym->binding_label,
6352                            comm_name_gsym->name,
6353                            &(comm_name_gsym->where));
6354                 return;
6355               }
6356         }
6357
6358       /* There is no binding label (NAME="") so we have nothing further to
6359          check and nothing to add as a global symbol for the label.  */
6360       if (comm_block_tree->n.common->binding_label[0] == '\0' )
6361         return;
6362       
6363       binding_label_gsym =
6364         gfc_find_gsymbol (gfc_gsym_root,
6365                           comm_block_tree->n.common->binding_label);
6366       if (binding_label_gsym == NULL)
6367         {
6368           /* Need to make a global symbol for the binding label to prevent
6369              it from colliding with another.  */
6370           binding_label_gsym =
6371             gfc_get_gsymbol (comm_block_tree->n.common->binding_label);
6372           binding_label_gsym->sym_name = comm_block_tree->n.common->name;
6373           binding_label_gsym->type = GSYM_COMMON;
6374         }
6375       else
6376         {
6377           /* If comm_name_gsym is NULL, the name common block is use
6378              associated and the name could be colliding.  */
6379           if (binding_label_gsym->type != GSYM_COMMON)
6380             gfc_error ("Binding label '%s' for common block '%s' at %L "
6381                        "collides with the global entity '%s' at %L",
6382                        comm_block_tree->n.common->binding_label,
6383                        comm_block_tree->n.common->name,
6384                        &(comm_block_tree->n.common->where),
6385                        binding_label_gsym->name,
6386                        &(binding_label_gsym->where));
6387           else if (comm_name_gsym != NULL
6388                    && (strcmp (binding_label_gsym->name,
6389                                comm_name_gsym->binding_label) != 0)
6390                    && (strcmp (binding_label_gsym->sym_name,
6391                                comm_name_gsym->name) != 0))
6392             gfc_error ("Binding label '%s' for common block '%s' at %L "
6393                        "collides with global entity '%s' at %L",
6394                        binding_label_gsym->name, binding_label_gsym->sym_name,
6395                        &(comm_block_tree->n.common->where),
6396                        comm_name_gsym->name, &(comm_name_gsym->where));
6397         }
6398     }
6399   
6400   return;
6401 }
6402
6403
6404 /* Verify any BIND(C) derived types in the namespace so we can report errors
6405    for them once, rather than for each variable declared of that type.  */
6406
6407 static void
6408 resolve_bind_c_derived_types (gfc_symbol *derived_sym)
6409 {
6410   if (derived_sym != NULL && derived_sym->attr.flavor == FL_DERIVED
6411       && derived_sym->attr.is_bind_c == 1)
6412     verify_bind_c_derived_type (derived_sym);
6413   
6414   return;
6415 }
6416
6417
6418 /* Verify that any binding labels used in a given namespace do not collide 
6419    with the names or binding labels of any global symbols.  */
6420
6421 static void
6422 gfc_verify_binding_labels (gfc_symbol *sym)
6423 {
6424   int has_error = 0;
6425   
6426   if (sym != NULL && sym->attr.is_bind_c && sym->attr.is_iso_c == 0 
6427       && sym->attr.flavor != FL_DERIVED && sym->binding_label[0] != '\0')
6428     {
6429       gfc_gsymbol *bind_c_sym;
6430
6431       bind_c_sym = gfc_find_gsymbol (gfc_gsym_root, sym->binding_label);
6432       if (bind_c_sym != NULL 
6433           && strcmp (bind_c_sym->name, sym->binding_label) == 0)
6434         {
6435           if (sym->attr.if_source == IFSRC_DECL 
6436               && (bind_c_sym->type != GSYM_SUBROUTINE 
6437                   && bind_c_sym->type != GSYM_FUNCTION) 
6438               && ((sym->attr.contained == 1 
6439                    && strcmp (bind_c_sym->sym_name, sym->name) != 0) 
6440                   || (sym->attr.use_assoc == 1 
6441                       && (strcmp (bind_c_sym->mod_name, sym->module) != 0))))
6442             {
6443               /* Make sure global procedures don't collide with anything.  */
6444               gfc_error ("Binding label '%s' at %L collides with the global "
6445                          "entity '%s' at %L", sym->binding_label,
6446                          &(sym->declared_at), bind_c_sym->name,
6447                          &(bind_c_sym->where));
6448               has_error = 1;
6449             }
6450           else if (sym->attr.contained == 0 
6451                    && (sym->attr.if_source == IFSRC_IFBODY 
6452                        && sym->attr.flavor == FL_PROCEDURE) 
6453                    && (bind_c_sym->sym_name != NULL 
6454                        && strcmp (bind_c_sym->sym_name, sym->name) != 0))
6455             {
6456               /* Make sure procedures in interface bodies don't collide.  */
6457               gfc_error ("Binding label '%s' in interface body at %L collides "
6458                          "with the global entity '%s' at %L",
6459                          sym->binding_label,
6460                          &(sym->declared_at), bind_c_sym->name,
6461                          &(bind_c_sym->where));
6462               has_error = 1;
6463             }
6464           else if (sym->attr.contained == 0 
6465                    && (sym->attr.if_source == IFSRC_UNKNOWN))
6466             if ((sym->attr.use_assoc 
6467                  && (strcmp (bind_c_sym->mod_name, sym->module) != 0)) 
6468                 || sym->attr.use_assoc == 0)
6469               {
6470                 gfc_error ("Binding label '%s' at %L collides with global "
6471                            "entity '%s' at %L", sym->binding_label,
6472                            &(sym->declared_at), bind_c_sym->name,
6473                            &(bind_c_sym->where));
6474                 has_error = 1;
6475               }
6476
6477           if (has_error != 0)
6478             /* Clear the binding label to prevent checking multiple times.  */
6479             sym->binding_label[0] = '\0';
6480         }
6481       else if (bind_c_sym == NULL)
6482         {
6483           bind_c_sym = gfc_get_gsymbol (sym->binding_label);
6484           bind_c_sym->where = sym->declared_at;
6485           bind_c_sym->sym_name = sym->name;
6486
6487           if (sym->attr.use_assoc == 1)
6488             bind_c_sym->mod_name = sym->module;
6489           else
6490             if (sym->ns->proc_name != NULL)
6491               bind_c_sym->mod_name = sym->ns->proc_name->name;
6492
6493           if (sym->attr.contained == 0)
6494             {
6495               if (sym->attr.subroutine)
6496                 bind_c_sym->type = GSYM_SUBROUTINE;
6497               else if (sym->attr.function)
6498                 bind_c_sym->type = GSYM_FUNCTION;
6499             }
6500         }
6501     }
6502   return;
6503 }
6504
6505
6506 /* Resolve an index expression.  */
6507
6508 static try
6509 resolve_index_expr (gfc_expr *e)
6510 {
6511   if (gfc_resolve_expr (e) == FAILURE)
6512     return FAILURE;
6513
6514   if (gfc_simplify_expr (e, 0) == FAILURE)
6515     return FAILURE;
6516
6517   if (gfc_specification_expr (e) == FAILURE)
6518     return FAILURE;
6519
6520   return SUCCESS;
6521 }
6522
6523 /* Resolve a charlen structure.  */
6524
6525 static try
6526 resolve_charlen (gfc_charlen *cl)
6527 {
6528   int i;
6529
6530   if (cl->resolved)
6531     return SUCCESS;
6532
6533   cl->resolved = 1;
6534
6535   specification_expr = 1;
6536
6537   if (resolve_index_expr (cl->length) == FAILURE)
6538     {
6539       specification_expr = 0;
6540       return FAILURE;
6541     }
6542
6543   /* "If the character length parameter value evaluates to a negative
6544      value, the length of character entities declared is zero."  */
6545   if (cl->length && !gfc_extract_int (cl->length, &i) && i < 0)
6546     {
6547       gfc_warning_now ("CHARACTER variable has zero length at %L",
6548                        &cl->length->where);
6549       gfc_replace_expr (cl->length, gfc_int_expr (0));
6550     }
6551
6552   return SUCCESS;
6553 }
6554
6555
6556 /* Test for non-constant shape arrays.  */
6557
6558 static bool
6559 is_non_constant_shape_array (gfc_symbol *sym)
6560 {
6561   gfc_expr *e;
6562   int i;
6563   bool not_constant;
6564
6565   not_constant = false;
6566   if (sym->as != NULL)
6567     {
6568       /* Unfortunately, !gfc_is_compile_time_shape hits a legal case that
6569          has not been simplified; parameter array references.  Do the
6570          simplification now.  */
6571       for (i = 0; i < sym->as->rank; i++)
6572         {
6573           e = sym->as->lower[i];
6574           if (e && (resolve_index_expr (e) == FAILURE
6575                     || !gfc_is_constant_expr (e)))
6576             not_constant = true;
6577
6578           e = sym->as->upper[i];
6579           if (e && (resolve_index_expr (e) == FAILURE
6580                     || !gfc_is_constant_expr (e)))
6581             not_constant = true;
6582         }
6583     }
6584   return not_constant;
6585 }
6586
6587 /* Given a symbol and an initialization expression, add code to initialize
6588    the symbol to the function entry.  */
6589 static void
6590 build_init_assign (gfc_symbol *sym, gfc_expr *init)
6591 {
6592   gfc_expr *lval;
6593   gfc_code *init_st;
6594   gfc_namespace *ns = sym->ns;
6595
6596   /* Search for the function namespace if this is a contained
6597      function without an explicit result.  */
6598   if (sym->attr.function && sym == sym->result
6599       && sym->name != sym->ns->proc_name->name)
6600     {
6601       ns = ns->contained;
6602       for (;ns; ns = ns->sibling)
6603         if (strcmp (ns->proc_name->name, sym->name) == 0)
6604           break;
6605     }
6606
6607   if (ns == NULL)
6608     {
6609       gfc_free_expr (init);
6610       return;
6611     }
6612
6613   /* Build an l-value expression for the result.  */
6614   lval = gfc_lval_expr_from_sym (sym);
6615
6616   /* Add the code at scope entry.  */
6617   init_st = gfc_get_code ();
6618   init_st->next = ns->code;
6619   ns->code = init_st;
6620
6621   /* Assign the default initializer to the l-value.  */
6622   init_st->loc = sym->declared_at;
6623   init_st->op = EXEC_INIT_ASSIGN;
6624   init_st->expr = lval;
6625   init_st->expr2 = init;
6626 }
6627
6628 /* Assign the default initializer to a derived type variable or result.  */
6629
6630 static void
6631 apply_default_init (gfc_symbol *sym)
6632 {
6633   gfc_expr *init = NULL;
6634
6635   if (sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
6636     return;
6637
6638   if (sym->ts.type == BT_DERIVED && sym->ts.derived)
6639     init = gfc_default_initializer (&sym->ts);
6640
6641   if (init == NULL)
6642     return;
6643
6644   build_init_assign (sym, init);
6645 }
6646
6647 /* Build an initializer for a local integer, real, complex, logical, or
6648    character variable, based on the command line flags finit-local-zero,
6649    finit-integer=, finit-real=, finit-logical=, and finit-runtime.  Returns 
6650    null if the symbol should not have a default initialization.  */
6651 static gfc_expr *
6652 build_default_init_expr (gfc_symbol *sym)
6653 {
6654   int char_len;
6655   gfc_expr *init_expr;
6656   int i;
6657   char *ch;
6658
6659   /* These symbols should never have a default initialization.  */
6660   if ((sym->attr.dimension && !gfc_is_compile_time_shape (sym->as))
6661       || sym->attr.external
6662       || sym->attr.dummy
6663       || sym->attr.pointer
6664       || sym->attr.in_equivalence
6665       || sym->attr.in_common
6666       || sym->attr.data
6667       || sym->module
6668       || sym->attr.cray_pointee
6669       || sym->attr.cray_pointer)
6670     return NULL;
6671
6672   /* Now we'll try to build an initializer expression.  */
6673   init_expr = gfc_get_expr ();
6674   init_expr->expr_type = EXPR_CONSTANT;
6675   init_expr->ts.type = sym->ts.type;
6676   init_expr->ts.kind = sym->ts.kind;
6677   init_expr->where = sym->declared_at;
6678   
6679   /* We will only initialize integers, reals, complex, logicals, and
6680      characters, and only if the corresponding command-line flags
6681      were set.  Otherwise, we free init_expr and return null.  */
6682   switch (sym->ts.type)
6683     {    
6684     case BT_INTEGER:
6685       if (gfc_option.flag_init_integer != GFC_INIT_INTEGER_OFF)
6686         mpz_init_set_si (init_expr->value.integer, 
6687                          gfc_option.flag_init_integer_value);
6688       else
6689         {
6690           gfc_free_expr (init_expr);
6691           init_expr = NULL;
6692         }
6693       break;
6694
6695     case BT_REAL:
6696       mpfr_init (init_expr->value.real);
6697       switch (gfc_option.flag_init_real)
6698         {
6699         case GFC_INIT_REAL_NAN:
6700           mpfr_set_nan (init_expr->value.real);
6701           break;
6702
6703         case GFC_INIT_REAL_INF:
6704           mpfr_set_inf (init_expr->value.real, 1);
6705           break;
6706
6707         case GFC_INIT_REAL_NEG_INF:
6708           mpfr_set_inf (init_expr->value.real, -1);
6709           break;
6710
6711         case GFC_INIT_REAL_ZERO:
6712           mpfr_set_ui (init_expr->value.real, 0.0, GFC_RND_MODE);
6713           break;
6714
6715         default:
6716           gfc_free_expr (init_expr);
6717           init_expr = NULL;
6718           break;
6719         }
6720       break;
6721           
6722     case BT_COMPLEX:
6723       mpfr_init (init_expr->value.complex.r);
6724       mpfr_init (init_expr->value.complex.i);
6725       switch (gfc_option.flag_init_real)
6726         {
6727         case GFC_INIT_REAL_NAN:
6728           mpfr_set_nan (init_expr->value.complex.r);
6729           mpfr_set_nan (init_expr->value.complex.i);
6730           break;
6731
6732         case GFC_INIT_REAL_INF:
6733           mpfr_set_inf (init_expr->value.complex.r, 1);
6734           mpfr_set_inf (init_expr->value.complex.i, 1);
6735           break;
6736
6737         case GFC_INIT_REAL_NEG_INF:
6738           mpfr_set_inf (init_expr->value.complex.r, -1);
6739           mpfr_set_inf (init_expr->value.complex.i, -1);
6740           break;
6741
6742         case GFC_INIT_REAL_ZERO:
6743           mpfr_set_ui (init_expr->value.complex.r, 0.0, GFC_RND_MODE);
6744           mpfr_set_ui (init_expr->value.complex.i, 0.0, GFC_RND_MODE);
6745           break;
6746
6747         default:
6748           gfc_free_expr (init_expr);
6749           init_expr = NULL;
6750           break;
6751         }
6752       break;
6753           
6754     case BT_LOGICAL:
6755       if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_FALSE)
6756         init_expr->value.logical = 0;
6757       else if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_TRUE)
6758         init_expr->value.logical = 1;
6759       else
6760         {
6761           gfc_free_expr (init_expr);
6762           init_expr = NULL;
6763         }
6764       break;
6765           
6766     case BT_CHARACTER:
6767       /* For characters, the length must be constant in order to 
6768          create a default initializer.  */
6769       if (gfc_option.flag_init_character == GFC_INIT_CHARACTER_ON
6770           && sym->ts.cl->length
6771           && sym->ts.cl->length->expr_type == EXPR_CONSTANT)
6772         {
6773           char_len = mpz_get_si (sym->ts.cl->length->value.integer);
6774           init_expr->value.character.length = char_len;
6775           init_expr->value.character.string = gfc_getmem (char_len+1);
6776           ch = init_expr->value.character.string;
6777           for (i = 0; i < char_len; i++)
6778             *(ch++) = gfc_option.flag_init_character_value;
6779         }
6780       else
6781         {
6782           gfc_free_expr (init_expr);
6783           init_expr = NULL;
6784         }
6785       break;
6786           
6787     default:
6788      gfc_free_expr (init_expr);
6789      init_expr = NULL;
6790     }
6791   return init_expr;
6792 }
6793
6794 /* Add an initialization expression to a local variable.  */
6795 static void
6796 apply_default_init_local (gfc_symbol *sym)
6797 {
6798   gfc_expr *init = NULL;
6799
6800   /* The symbol should be a variable or a function return value.  */
6801   if ((sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
6802       || (sym->attr.function && sym->result != sym))
6803     return;
6804
6805   /* Try to build the initializer expression.  If we can't initialize
6806      this symbol, then init will be NULL.  */
6807   init = build_default_init_expr (sym);
6808   if (init == NULL)
6809     return;
6810
6811   /* For saved variables, we don't want to add an initializer at 
6812      function entry, so we just add a static initializer.  */
6813   if (sym->attr.save || sym->ns->save_all)
6814     {
6815       /* Don't clobber an existing initializer!  */
6816       gcc_assert (sym->value == NULL);
6817       sym->value = init;
6818       return;
6819     }
6820
6821   build_init_assign (sym, init);
6822 }
6823
6824 /* Resolution of common features of flavors variable and procedure.  */
6825
6826 static try
6827 resolve_fl_var_and_proc (gfc_symbol *sym, int mp_flag)
6828 {
6829   /* Constraints on deferred shape variable.  */
6830   if (sym->as == NULL || sym->as->type != AS_DEFERRED)
6831     {
6832       if (sym->attr.allocatable)
6833         {
6834           if (sym->attr.dimension)
6835             gfc_error ("Allocatable array '%s' at %L must have "
6836                        "a deferred shape", sym->name, &sym->declared_at);
6837           else
6838             gfc_error ("Scalar object '%s' at %L may not be ALLOCATABLE",
6839                        sym->name, &sym->declared_at);
6840             return FAILURE;
6841         }
6842
6843       if (sym->attr.pointer && sym->attr.dimension)
6844         {
6845           gfc_error ("Array pointer '%s' at %L must have a deferred shape",
6846                      sym->name, &sym->declared_at);
6847           return FAILURE;
6848         }
6849
6850     }
6851   else
6852     {
6853       if (!mp_flag && !sym->attr.allocatable
6854           && !sym->attr.pointer && !sym->attr.dummy)
6855         {
6856           gfc_error ("Array '%s' at %L cannot have a deferred shape",
6857                      sym->name, &sym->declared_at);
6858           return FAILURE;
6859          }
6860     }
6861   return SUCCESS;
6862 }
6863
6864
6865 /* Additional checks for symbols with flavor variable and derived
6866    type.  To be called from resolve_fl_variable.  */
6867
6868 static try
6869 resolve_fl_variable_derived (gfc_symbol *sym, int no_init_flag)
6870 {
6871   gcc_assert (sym->ts.type == BT_DERIVED);
6872
6873   /* Check to see if a derived type is blocked from being host
6874      associated by the presence of another class I symbol in the same
6875      namespace.  14.6.1.3 of the standard and the discussion on
6876      comp.lang.fortran.  */
6877   if (sym->ns != sym->ts.derived->ns
6878       && sym->ns->proc_name->attr.if_source != IFSRC_IFBODY)
6879     {
6880       gfc_symbol *s;
6881       gfc_find_symbol (sym->ts.derived->name, sym->ns, 0, &s);
6882       if (s && (s->attr.flavor != FL_DERIVED
6883                 || !gfc_compare_derived_types (s, sym->ts.derived)))
6884         {
6885           gfc_error ("The type '%s' cannot be host associated at %L "
6886                      "because it is blocked by an incompatible object "
6887                      "of the same name declared at %L",
6888                      sym->ts.derived->name, &sym->declared_at,
6889                      &s->declared_at);
6890           return FAILURE;
6891         }
6892     }
6893
6894   /* 4th constraint in section 11.3: "If an object of a type for which
6895      component-initialization is specified (R429) appears in the
6896      specification-part of a module and does not have the ALLOCATABLE
6897      or POINTER attribute, the object shall have the SAVE attribute."
6898
6899      The check for initializers is performed with
6900      has_default_initializer because gfc_default_initializer generates
6901      a hidden default for allocatable components.  */
6902   if (!(sym->value || no_init_flag) && sym->ns->proc_name
6903       && sym->ns->proc_name->attr.flavor == FL_MODULE
6904       && !sym->ns->save_all && !sym->attr.save
6905       && !sym->attr.pointer && !sym->attr.allocatable
6906       && has_default_initializer (sym->ts.derived))
6907     {
6908       gfc_error("Object '%s' at %L must have the SAVE attribute for "
6909                 "default initialization of a component",
6910                 sym->name, &sym->declared_at);
6911       return FAILURE;
6912     }
6913
6914   /* Assign default initializer.  */
6915   if (!(sym->value || sym->attr.pointer || sym->attr.allocatable)
6916       && (!no_init_flag || sym->attr.intent == INTENT_OUT))
6917     {
6918       sym->value = gfc_default_initializer (&sym->ts);
6919     }
6920
6921   return SUCCESS;
6922 }
6923
6924
6925 /* Resolve symbols with flavor variable.  */
6926
6927 static try
6928 resolve_fl_variable (gfc_symbol *sym, int mp_flag)
6929 {
6930   int no_init_flag, automatic_flag;
6931   gfc_expr *e;
6932   const char *auto_save_msg;
6933
6934   auto_save_msg = "Automatic object '%s' at %L cannot have the "
6935                   "SAVE attribute";
6936
6937   if (resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
6938     return FAILURE;
6939
6940   /* Set this flag to check that variables are parameters of all entries.
6941      This check is effected by the call to gfc_resolve_expr through
6942      is_non_constant_shape_array.  */
6943   specification_expr = 1;
6944
6945   if (sym->ns->proc_name
6946       && (sym->ns->proc_name->attr.flavor == FL_MODULE
6947           || sym->ns->proc_name->attr.is_main_program)
6948       && !sym->attr.use_assoc
6949       && !sym->attr.allocatable
6950       && !sym->attr.pointer
6951       && is_non_constant_shape_array (sym))
6952     {
6953       /* The shape of a main program or module array needs to be
6954          constant.  */
6955       gfc_error ("The module or main program array '%s' at %L must "
6956                  "have constant shape", sym->name, &sym->declared_at);
6957       specification_expr = 0;
6958       return FAILURE;
6959     }
6960
6961   if (sym->ts.type == BT_CHARACTER)
6962     {
6963       /* Make sure that character string variables with assumed length are
6964          dummy arguments.  */
6965       e = sym->ts.cl->length;
6966       if (e == NULL && !sym->attr.dummy && !sym->attr.result)
6967         {
6968           gfc_error ("Entity with assumed character length at %L must be a "
6969                      "dummy argument or a PARAMETER", &sym->declared_at);
6970           return FAILURE;
6971         }
6972
6973       if (e && sym->attr.save && !gfc_is_constant_expr (e))
6974         {
6975           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
6976           return FAILURE;
6977         }
6978
6979       if (!gfc_is_constant_expr (e)
6980           && !(e->expr_type == EXPR_VARIABLE
6981                && e->symtree->n.sym->attr.flavor == FL_PARAMETER)
6982           && sym->ns->proc_name
6983           && (sym->ns->proc_name->attr.flavor == FL_MODULE
6984               || sym->ns->proc_name->attr.is_main_program)
6985           && !sym->attr.use_assoc)
6986         {
6987           gfc_error ("'%s' at %L must have constant character length "
6988                      "in this context", sym->name, &sym->declared_at);
6989           return FAILURE;
6990         }
6991     }
6992
6993   if (sym->value == NULL && sym->attr.referenced)
6994     apply_default_init_local (sym); /* Try to apply a default initialization.  */
6995
6996   /* Determine if the symbol may not have an initializer.  */
6997   no_init_flag = automatic_flag = 0;
6998   if (sym->attr.allocatable || sym->attr.external || sym->attr.dummy
6999       || sym->attr.intrinsic || sym->attr.result)
7000     no_init_flag = 1;
7001   else if (sym->attr.dimension && !sym->attr.pointer
7002            && is_non_constant_shape_array (sym))
7003     {
7004       no_init_flag = automatic_flag = 1;
7005
7006       /* Also, they must not have the SAVE attribute.
7007          SAVE_IMPLICIT is checked below.  */
7008       if (sym->attr.save == SAVE_EXPLICIT)
7009         {
7010           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
7011           return FAILURE;
7012         }
7013     }
7014
7015   /* Reject illegal initializers.  */
7016   if (!sym->mark && sym->value)
7017     {
7018       if (sym->attr.allocatable)
7019         gfc_error ("Allocatable '%s' at %L cannot have an initializer",
7020                    sym->name, &sym->declared_at);
7021       else if (sym->attr.external)
7022         gfc_error ("External '%s' at %L cannot have an initializer",
7023                    sym->name, &sym->declared_at);
7024       else if (sym->attr.dummy
7025         && !(sym->ts.type == BT_DERIVED && sym->attr.intent == INTENT_OUT))
7026         gfc_error ("Dummy '%s' at %L cannot have an initializer",
7027                    sym->name, &sym->declared_at);
7028       else if (sym->attr.intrinsic)
7029         gfc_error ("Intrinsic '%s' at %L cannot have an initializer",
7030                    sym->name, &sym->declared_at);
7031       else if (sym->attr.result)
7032         gfc_error ("Function result '%s' at %L cannot have an initializer",
7033                    sym->name, &sym->declared_at);
7034       else if (automatic_flag)
7035         gfc_error ("Automatic array '%s' at %L cannot have an initializer",
7036                    sym->name, &sym->declared_at);
7037       else
7038         goto no_init_error;
7039       return FAILURE;
7040     }
7041
7042 no_init_error:
7043   if (sym->ts.type == BT_DERIVED)
7044     return resolve_fl_variable_derived (sym, no_init_flag);
7045
7046   return SUCCESS;
7047 }
7048
7049
7050 /* Resolve a procedure.  */
7051
7052 static try
7053 resolve_fl_procedure (gfc_symbol *sym, int mp_flag)
7054 {
7055   gfc_formal_arglist *arg;
7056
7057   if (sym->attr.ambiguous_interfaces && !sym->attr.referenced)
7058     gfc_warning ("Although not referenced, '%s' at %L has ambiguous "
7059                  "interfaces", sym->name, &sym->declared_at);
7060
7061   if (sym->attr.function
7062       && resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
7063     return FAILURE;
7064
7065   if (sym->ts.type == BT_CHARACTER)
7066     {
7067       gfc_charlen *cl = sym->ts.cl;
7068
7069       if (cl && cl->length && gfc_is_constant_expr (cl->length)
7070              && resolve_charlen (cl) == FAILURE)
7071         return FAILURE;
7072
7073       if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
7074         {
7075           if (sym->attr.proc == PROC_ST_FUNCTION)
7076             {
7077               gfc_error ("Character-valued statement function '%s' at %L must "
7078                          "have constant length", sym->name, &sym->declared_at);
7079               return FAILURE;
7080             }
7081
7082           if (sym->attr.external && sym->formal == NULL
7083               && cl && cl->length && cl->length->expr_type != EXPR_CONSTANT)
7084             {
7085               gfc_error ("Automatic character length function '%s' at %L must "
7086                          "have an explicit interface", sym->name,
7087                          &sym->declared_at);
7088               return FAILURE;
7089             }
7090         }
7091     }
7092
7093   /* Ensure that derived type for are not of a private type.  Internal
7094      module procedures are excluded by 2.2.3.3 - ie. they are not
7095      externally accessible and can access all the objects accessible in
7096      the host.  */
7097   if (!(sym->ns->parent
7098         && sym->ns->parent->proc_name->attr.flavor == FL_MODULE)
7099       && gfc_check_access(sym->attr.access, sym->ns->default_access))
7100     {
7101       gfc_interface *iface;
7102
7103       for (arg = sym->formal; arg; arg = arg->next)
7104         {
7105           if (arg->sym
7106               && arg->sym->ts.type == BT_DERIVED
7107               && !arg->sym->ts.derived->attr.use_assoc
7108               && !gfc_check_access (arg->sym->ts.derived->attr.access,
7109                                     arg->sym->ts.derived->ns->default_access)
7110               && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: '%s' is of a "
7111                                  "PRIVATE type and cannot be a dummy argument"
7112                                  " of '%s', which is PUBLIC at %L",
7113                                  arg->sym->name, sym->name, &sym->declared_at)
7114                  == FAILURE)
7115             {
7116               /* Stop this message from recurring.  */
7117               arg->sym->ts.derived->attr.access = ACCESS_PUBLIC;
7118               return FAILURE;
7119             }
7120         }
7121
7122       /* PUBLIC interfaces may expose PRIVATE procedures that take types
7123          PRIVATE to the containing module.  */
7124       for (iface = sym->generic; iface; iface = iface->next)
7125         {
7126           for (arg = iface->sym->formal; arg; arg = arg->next)
7127             {
7128               if (arg->sym
7129                   && arg->sym->ts.type == BT_DERIVED
7130                   && !arg->sym->ts.derived->attr.use_assoc
7131                   && !gfc_check_access (arg->sym->ts.derived->attr.access,
7132                                         arg->sym->ts.derived->ns->default_access)
7133                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
7134                                      "'%s' in PUBLIC interface '%s' at %L "
7135                                      "takes dummy arguments of '%s' which is "
7136                                      "PRIVATE", iface->sym->name, sym->name,
7137                                      &iface->sym->declared_at,
7138                                      gfc_typename (&arg->sym->ts)) == FAILURE)
7139                 {
7140                   /* Stop this message from recurring.  */
7141                   arg->sym->ts.derived->attr.access = ACCESS_PUBLIC;
7142                   return FAILURE;
7143                 }
7144              }
7145         }
7146
7147       /* PUBLIC interfaces may expose PRIVATE procedures that take types
7148          PRIVATE to the containing module.  */
7149       for (iface = sym->generic; iface; iface = iface->next)
7150         {
7151           for (arg = iface->sym->formal; arg; arg = arg->next)
7152             {
7153               if (arg->sym
7154                   && arg->sym->ts.type == BT_DERIVED
7155                   && !arg->sym->ts.derived->attr.use_assoc
7156                   && !gfc_check_access (arg->sym->ts.derived->attr.access,
7157                                         arg->sym->ts.derived->ns->default_access)
7158                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
7159                                      "'%s' in PUBLIC interface '%s' at %L "
7160                                      "takes dummy arguments of '%s' which is "
7161                                      "PRIVATE", iface->sym->name, sym->name,
7162                                      &iface->sym->declared_at,
7163                                      gfc_typename (&arg->sym->ts)) == FAILURE)
7164                 {
7165                   /* Stop this message from recurring.  */
7166                   arg->sym->ts.derived->attr.access = ACCESS_PUBLIC;
7167                   return FAILURE;
7168                 }
7169              }
7170         }
7171     }
7172
7173   if (sym->attr.function && sym->value && sym->attr.proc != PROC_ST_FUNCTION)
7174     {
7175       gfc_error ("Function '%s' at %L cannot have an initializer",
7176                  sym->name, &sym->declared_at);
7177       return FAILURE;
7178     }
7179
7180   /* An external symbol may not have an initializer because it is taken to be
7181      a procedure.  */
7182   if (sym->attr.external && sym->value)
7183     {
7184       gfc_error ("External object '%s' at %L may not have an initializer",
7185                  sym->name, &sym->declared_at);
7186       return FAILURE;
7187     }
7188
7189   /* An elemental function is required to return a scalar 12.7.1  */
7190   if (sym->attr.elemental && sym->attr.function && sym->as)
7191     {
7192       gfc_error ("ELEMENTAL function '%s' at %L must have a scalar "
7193                  "result", sym->name, &sym->declared_at);
7194       /* Reset so that the error only occurs once.  */
7195       sym->attr.elemental = 0;
7196       return FAILURE;
7197     }
7198
7199   /* 5.1.1.5 of the Standard: A function name declared with an asterisk
7200      char-len-param shall not be array-valued, pointer-valued, recursive
7201      or pure.  ....snip... A character value of * may only be used in the
7202      following ways: (i) Dummy arg of procedure - dummy associates with
7203      actual length; (ii) To declare a named constant; or (iii) External
7204      function - but length must be declared in calling scoping unit.  */
7205   if (sym->attr.function
7206       && sym->ts.type == BT_CHARACTER
7207       && sym->ts.cl && sym->ts.cl->length == NULL)
7208     {
7209       if ((sym->as && sym->as->rank) || (sym->attr.pointer)
7210           || (sym->attr.recursive) || (sym->attr.pure))
7211         {
7212           if (sym->as && sym->as->rank)
7213             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
7214                        "array-valued", sym->name, &sym->declared_at);
7215
7216           if (sym->attr.pointer)
7217             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
7218                        "pointer-valued", sym->name, &sym->declared_at);
7219
7220           if (sym->attr.pure)
7221             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
7222                        "pure", sym->name, &sym->declared_at);
7223
7224           if (sym->attr.recursive)
7225             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
7226                        "recursive", sym->name, &sym->declared_at);
7227
7228           return FAILURE;
7229         }
7230
7231       /* Appendix B.2 of the standard.  Contained functions give an
7232          error anyway.  Fixed-form is likely to be F77/legacy.  */
7233       if (!sym->attr.contained && gfc_current_form != FORM_FIXED)
7234         gfc_notify_std (GFC_STD_F95_OBS, "CHARACTER(*) function "
7235                         "'%s' at %L is obsolescent in fortran 95",
7236                         sym->name, &sym->declared_at);
7237     }
7238
7239   if (sym->attr.is_bind_c && sym->attr.is_c_interop != 1)
7240     {
7241       gfc_formal_arglist *curr_arg;
7242       int has_non_interop_arg = 0;
7243
7244       if (verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
7245                              sym->common_block) == FAILURE)
7246         {
7247           /* Clear these to prevent looking at them again if there was an
7248              error.  */
7249           sym->attr.is_bind_c = 0;
7250           sym->attr.is_c_interop = 0;
7251           sym->ts.is_c_interop = 0;
7252         }
7253       else
7254         {
7255           /* So far, no errors have been found.  */
7256           sym->attr.is_c_interop = 1;
7257           sym->ts.is_c_interop = 1;
7258         }
7259       
7260       curr_arg = sym->formal;
7261       while (curr_arg != NULL)
7262         {
7263           /* Skip implicitly typed dummy args here.  */
7264           if (curr_arg->sym->attr.implicit_type == 0)
7265             if (verify_c_interop_param (curr_arg->sym) == FAILURE)
7266               /* If something is found to fail, record the fact so we
7267                  can mark the symbol for the procedure as not being
7268                  BIND(C) to try and prevent multiple errors being
7269                  reported.  */
7270               has_non_interop_arg = 1;
7271           
7272           curr_arg = curr_arg->next;
7273         }
7274
7275       /* See if any of the arguments were not interoperable and if so, clear
7276          the procedure symbol to prevent duplicate error messages.  */
7277       if (has_non_interop_arg != 0)
7278         {
7279           sym->attr.is_c_interop = 0;
7280           sym->ts.is_c_interop = 0;
7281           sym->attr.is_bind_c = 0;
7282         }
7283     }
7284   
7285   return SUCCESS;
7286 }
7287
7288
7289 /* Resolve the components of a derived type.  */
7290
7291 static try
7292 resolve_fl_derived (gfc_symbol *sym)
7293 {
7294   gfc_component *c;
7295   gfc_dt_list * dt_list;
7296   int i;
7297
7298   for (c = sym->components; c != NULL; c = c->next)
7299     {
7300       if (c->ts.type == BT_CHARACTER)
7301         {
7302          if (c->ts.cl->length == NULL
7303              || (resolve_charlen (c->ts.cl) == FAILURE)
7304              || !gfc_is_constant_expr (c->ts.cl->length))
7305            {
7306              gfc_error ("Character length of component '%s' needs to "
7307                         "be a constant specification expression at %L",
7308                         c->name,
7309                         c->ts.cl->length ? &c->ts.cl->length->where : &c->loc);
7310              return FAILURE;
7311            }
7312         }
7313
7314       if (c->ts.type == BT_DERIVED
7315           && sym->component_access != ACCESS_PRIVATE
7316           && gfc_check_access (sym->attr.access, sym->ns->default_access)
7317           && !c->ts.derived->attr.use_assoc
7318           && !gfc_check_access (c->ts.derived->attr.access,
7319                                 c->ts.derived->ns->default_access))
7320         {
7321           gfc_error ("The component '%s' is a PRIVATE type and cannot be "
7322                      "a component of '%s', which is PUBLIC at %L",
7323                      c->name, sym->name, &sym->declared_at);
7324           return FAILURE;
7325         }
7326
7327       if (sym->attr.sequence)
7328         {
7329           if (c->ts.type == BT_DERIVED && c->ts.derived->attr.sequence == 0)
7330             {
7331               gfc_error ("Component %s of SEQUENCE type declared at %L does "
7332                          "not have the SEQUENCE attribute",
7333                          c->ts.derived->name, &sym->declared_at);
7334               return FAILURE;
7335             }
7336         }
7337
7338       if (c->ts.type == BT_DERIVED && c->pointer
7339           && c->ts.derived->components == NULL)
7340         {
7341           gfc_error ("The pointer component '%s' of '%s' at %L is a type "
7342                      "that has not been declared", c->name, sym->name,
7343                      &c->loc);
7344           return FAILURE;
7345         }
7346
7347       if (c->pointer || c->allocatable ||  c->as == NULL)
7348         continue;
7349
7350       for (i = 0; i < c->as->rank; i++)
7351         {
7352           if (c->as->lower[i] == NULL
7353               || !gfc_is_constant_expr (c->as->lower[i])
7354               || (resolve_index_expr (c->as->lower[i]) == FAILURE)
7355               || c->as->upper[i] == NULL
7356               || (resolve_index_expr (c->as->upper[i]) == FAILURE)
7357               || !gfc_is_constant_expr (c->as->upper[i]))
7358             {
7359               gfc_error ("Component '%s' of '%s' at %L must have "
7360                          "constant array bounds",
7361                          c->name, sym->name, &c->loc);
7362               return FAILURE;
7363             }
7364         }
7365     }
7366
7367   /* Add derived type to the derived type list.  */
7368   for (dt_list = gfc_derived_types; dt_list; dt_list = dt_list->next)
7369     if (sym == dt_list->derived)
7370       break;
7371
7372   if (dt_list == NULL)
7373     {
7374       dt_list = gfc_get_dt_list ();
7375       dt_list->next = gfc_derived_types;
7376       dt_list->derived = sym;
7377       gfc_derived_types = dt_list;
7378     }
7379
7380   return SUCCESS;
7381 }
7382
7383
7384 static try
7385 resolve_fl_namelist (gfc_symbol *sym)
7386 {
7387   gfc_namelist *nl;
7388   gfc_symbol *nlsym;
7389
7390   /* Reject PRIVATE objects in a PUBLIC namelist.  */
7391   if (gfc_check_access(sym->attr.access, sym->ns->default_access))
7392     {
7393       for (nl = sym->namelist; nl; nl = nl->next)
7394         {
7395           if (!nl->sym->attr.use_assoc
7396               && !(sym->ns->parent == nl->sym->ns)
7397               && !(sym->ns->parent
7398                    && sym->ns->parent->parent == nl->sym->ns)
7399               && !gfc_check_access(nl->sym->attr.access,
7400                                 nl->sym->ns->default_access))
7401             {
7402               gfc_error ("NAMELIST object '%s' was declared PRIVATE and "
7403                          "cannot be member of PUBLIC namelist '%s' at %L",
7404                          nl->sym->name, sym->name, &sym->declared_at);
7405               return FAILURE;
7406             }
7407
7408           /* Types with private components that came here by USE-association.  */
7409           if (nl->sym->ts.type == BT_DERIVED
7410               && derived_inaccessible (nl->sym->ts.derived))
7411             {
7412               gfc_error ("NAMELIST object '%s' has use-associated PRIVATE "
7413                          "components and cannot be member of namelist '%s' at %L",
7414                          nl->sym->name, sym->name, &sym->declared_at);
7415               return FAILURE;
7416             }
7417
7418           /* Types with private components that are defined in the same module.  */
7419           if (nl->sym->ts.type == BT_DERIVED
7420               && !(sym->ns->parent == nl->sym->ts.derived->ns)
7421               && !gfc_check_access (nl->sym->ts.derived->attr.private_comp
7422                                         ? ACCESS_PRIVATE : ACCESS_UNKNOWN,
7423                                         nl->sym->ns->default_access))
7424             {
7425               gfc_error ("NAMELIST object '%s' has PRIVATE components and "
7426                          "cannot be a member of PUBLIC namelist '%s' at %L",
7427                          nl->sym->name, sym->name, &sym->declared_at);
7428               return FAILURE;
7429             }
7430         }
7431     }
7432
7433   for (nl = sym->namelist; nl; nl = nl->next)
7434     {
7435       /* Reject namelist arrays of assumed shape.  */
7436       if (nl->sym->as && nl->sym->as->type == AS_ASSUMED_SHAPE
7437           && gfc_notify_std (GFC_STD_F2003, "NAMELIST array object '%s' "
7438                              "must not have assumed shape in namelist "
7439                              "'%s' at %L", nl->sym->name, sym->name,
7440                              &sym->declared_at) == FAILURE)
7441             return FAILURE;
7442
7443       /* Reject namelist arrays that are not constant shape.  */
7444       if (is_non_constant_shape_array (nl->sym))
7445         {
7446           gfc_error ("NAMELIST array object '%s' must have constant "
7447                      "shape in namelist '%s' at %L", nl->sym->name,
7448                      sym->name, &sym->declared_at);
7449           return FAILURE;
7450         }
7451
7452       /* Namelist objects cannot have allocatable or pointer components.  */
7453       if (nl->sym->ts.type != BT_DERIVED)
7454         continue;
7455
7456       if (nl->sym->ts.derived->attr.alloc_comp)
7457         {
7458           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L cannot "
7459                      "have ALLOCATABLE components",
7460                      nl->sym->name, sym->name, &sym->declared_at);
7461           return FAILURE;
7462         }
7463
7464       if (nl->sym->ts.derived->attr.pointer_comp)
7465         {
7466           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L cannot "
7467                      "have POINTER components", 
7468                      nl->sym->name, sym->name, &sym->declared_at);
7469           return FAILURE;
7470         }
7471     }
7472
7473
7474   /* 14.1.2 A module or internal procedure represent local entities
7475      of the same type as a namelist member and so are not allowed.  */
7476   for (nl = sym->namelist; nl; nl = nl->next)
7477     {
7478       if (nl->sym->ts.kind != 0 && nl->sym->attr.flavor == FL_VARIABLE)
7479         continue;
7480
7481       if (nl->sym->attr.function && nl->sym == nl->sym->result)
7482         if ((nl->sym == sym->ns->proc_name)
7483                ||
7484             (sym->ns->parent && nl->sym == sym->ns->parent->proc_name))
7485           continue;
7486
7487       nlsym = NULL;
7488       if (nl->sym && nl->sym->name)
7489         gfc_find_symbol (nl->sym->name, sym->ns, 1, &nlsym);
7490       if (nlsym && nlsym->attr.flavor == FL_PROCEDURE)
7491         {
7492           gfc_error ("PROCEDURE attribute conflicts with NAMELIST "
7493                      "attribute in '%s' at %L", nlsym->name,
7494                      &sym->declared_at);
7495           return FAILURE;
7496         }
7497     }
7498
7499   return SUCCESS;
7500 }
7501
7502
7503 static try
7504 resolve_fl_parameter (gfc_symbol *sym)
7505 {
7506   /* A parameter array's shape needs to be constant.  */
7507   if (sym->as != NULL 
7508       && (sym->as->type == AS_DEFERRED
7509           || is_non_constant_shape_array (sym)))
7510     {
7511       gfc_error ("Parameter array '%s' at %L cannot be automatic "
7512                  "or of deferred shape", sym->name, &sym->declared_at);
7513       return FAILURE;
7514     }
7515
7516   /* Make sure a parameter that has been implicitly typed still
7517      matches the implicit type, since PARAMETER statements can precede
7518      IMPLICIT statements.  */
7519   if (sym->attr.implicit_type
7520       && !gfc_compare_types (&sym->ts, gfc_get_default_type (sym, sym->ns)))
7521     {
7522       gfc_error ("Implicitly typed PARAMETER '%s' at %L doesn't match a "
7523                  "later IMPLICIT type", sym->name, &sym->declared_at);
7524       return FAILURE;
7525     }
7526
7527   /* Make sure the types of derived parameters are consistent.  This
7528      type checking is deferred until resolution because the type may
7529      refer to a derived type from the host.  */
7530   if (sym->ts.type == BT_DERIVED
7531       && !gfc_compare_types (&sym->ts, &sym->value->ts))
7532     {
7533       gfc_error ("Incompatible derived type in PARAMETER at %L",
7534                  &sym->value->where);
7535       return FAILURE;
7536     }
7537   return SUCCESS;
7538 }
7539
7540
7541 /* Do anything necessary to resolve a symbol.  Right now, we just
7542    assume that an otherwise unknown symbol is a variable.  This sort
7543    of thing commonly happens for symbols in module.  */
7544
7545 static void
7546 resolve_symbol (gfc_symbol *sym)
7547 {
7548   int check_constant, mp_flag;
7549   gfc_symtree *symtree;
7550   gfc_symtree *this_symtree;
7551   gfc_namespace *ns;
7552   gfc_component *c;
7553
7554   if (sym->attr.flavor == FL_UNKNOWN)
7555     {
7556
7557     /* If we find that a flavorless symbol is an interface in one of the
7558        parent namespaces, find its symtree in this namespace, free the
7559        symbol and set the symtree to point to the interface symbol.  */
7560       for (ns = gfc_current_ns->parent; ns; ns = ns->parent)
7561         {
7562           symtree = gfc_find_symtree (ns->sym_root, sym->name);
7563           if (symtree && symtree->n.sym->generic)
7564             {
7565               this_symtree = gfc_find_symtree (gfc_current_ns->sym_root,
7566                                                sym->name);
7567               sym->refs--;
7568               if (!sym->refs)
7569                 gfc_free_symbol (sym);
7570               symtree->n.sym->refs++;
7571               this_symtree->n.sym = symtree->n.sym;
7572               return;
7573             }
7574         }
7575
7576       /* Otherwise give it a flavor according to such attributes as
7577          it has.  */
7578       if (sym->attr.external == 0 && sym->attr.intrinsic == 0)
7579         sym->attr.flavor = FL_VARIABLE;
7580       else
7581         {
7582           sym->attr.flavor = FL_PROCEDURE;
7583           if (sym->attr.dimension)
7584             sym->attr.function = 1;
7585         }
7586     }
7587
7588   if (sym->attr.procedure && sym->interface
7589       && sym->attr.if_source != IFSRC_DECL)
7590     {
7591       if (sym->interface->attr.procedure)
7592         gfc_error ("Interface '%s', used by procedure '%s' at %L, is declared "
7593                    "in a later PROCEDURE statement", sym->interface->name,
7594                    sym->name,&sym->declared_at);
7595
7596       /* Get the attributes from the interface (now resolved).  */
7597       if (sym->interface->attr.if_source || sym->interface->attr.intrinsic)
7598         {
7599           sym->ts = sym->interface->ts;
7600           sym->attr.function = sym->interface->attr.function;
7601           sym->attr.subroutine = sym->interface->attr.subroutine;
7602           copy_formal_args (sym, sym->interface);
7603         }
7604       else if (sym->interface->name[0] != '\0')
7605         {
7606           gfc_error ("Interface '%s' of procedure '%s' at %L must be explicit",
7607                     sym->interface->name, sym->name, &sym->declared_at);
7608           return;
7609         }
7610     }
7611
7612   if (sym->attr.flavor == FL_DERIVED && resolve_fl_derived (sym) == FAILURE)
7613     return;
7614
7615   /* Symbols that are module procedures with results (functions) have
7616      the types and array specification copied for type checking in
7617      procedures that call them, as well as for saving to a module
7618      file.  These symbols can't stand the scrutiny that their results
7619      can.  */
7620   mp_flag = (sym->result != NULL && sym->result != sym);
7621
7622
7623   /* Make sure that the intrinsic is consistent with its internal 
7624      representation. This needs to be done before assigning a default 
7625      type to avoid spurious warnings.  */
7626   if (sym->attr.flavor != FL_MODULE && sym->attr.intrinsic)
7627     {
7628       if (gfc_intrinsic_name (sym->name, 0))
7629         {
7630           if (sym->ts.type != BT_UNKNOWN && gfc_option.warn_surprising)
7631             gfc_warning ("Type specified for intrinsic function '%s' at %L is ignored",
7632                          sym->name, &sym->declared_at);
7633         }
7634       else if (gfc_intrinsic_name (sym->name, 1))
7635         {
7636           if (sym->ts.type != BT_UNKNOWN)
7637             {
7638               gfc_error ("Intrinsic subroutine '%s' at %L shall not have a type specifier", 
7639                          sym->name, &sym->declared_at);
7640               return;
7641             }
7642         }
7643       else
7644         {
7645           gfc_error ("Intrinsic '%s' at %L does not exist", sym->name, &sym->declared_at);
7646           return;
7647         }
7648      }
7649
7650   /* Assign default type to symbols that need one and don't have one.  */
7651   if (sym->ts.type == BT_UNKNOWN)
7652     {
7653       if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER)
7654         gfc_set_default_type (sym, 1, NULL);
7655
7656       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.function)
7657         {
7658           /* The specific case of an external procedure should emit an error
7659              in the case that there is no implicit type.  */
7660           if (!mp_flag)
7661             gfc_set_default_type (sym, sym->attr.external, NULL);
7662           else
7663             {
7664               /* Result may be in another namespace.  */
7665               resolve_symbol (sym->result);
7666
7667               sym->ts = sym->result->ts;
7668               sym->as = gfc_copy_array_spec (sym->result->as);
7669               sym->attr.dimension = sym->result->attr.dimension;
7670               sym->attr.pointer = sym->result->attr.pointer;
7671               sym->attr.allocatable = sym->result->attr.allocatable;
7672             }
7673         }
7674     }
7675
7676   /* Assumed size arrays and assumed shape arrays must be dummy
7677      arguments.  */
7678
7679   if (sym->as != NULL
7680       && (sym->as->type == AS_ASSUMED_SIZE
7681           || sym->as->type == AS_ASSUMED_SHAPE)
7682       && sym->attr.dummy == 0)
7683     {
7684       if (sym->as->type == AS_ASSUMED_SIZE)
7685         gfc_error ("Assumed size array at %L must be a dummy argument",
7686                    &sym->declared_at);
7687       else
7688         gfc_error ("Assumed shape array at %L must be a dummy argument",
7689                    &sym->declared_at);
7690       return;
7691     }
7692
7693   /* Make sure symbols with known intent or optional are really dummy
7694      variable.  Because of ENTRY statement, this has to be deferred
7695      until resolution time.  */
7696
7697   if (!sym->attr.dummy
7698       && (sym->attr.optional || sym->attr.intent != INTENT_UNKNOWN))
7699     {
7700       gfc_error ("Symbol at %L is not a DUMMY variable", &sym->declared_at);
7701       return;
7702     }
7703
7704   if (sym->attr.value && !sym->attr.dummy)
7705     {
7706       gfc_error ("'%s' at %L cannot have the VALUE attribute because "
7707                  "it is not a dummy argument", sym->name, &sym->declared_at);
7708       return;
7709     }
7710
7711   if (sym->attr.value && sym->ts.type == BT_CHARACTER)
7712     {
7713       gfc_charlen *cl = sym->ts.cl;
7714       if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
7715         {
7716           gfc_error ("Character dummy variable '%s' at %L with VALUE "
7717                      "attribute must have constant length",
7718                      sym->name, &sym->declared_at);
7719           return;
7720         }
7721
7722       if (sym->ts.is_c_interop
7723           && mpz_cmp_si (cl->length->value.integer, 1) != 0)
7724         {
7725           gfc_error ("C interoperable character dummy variable '%s' at %L "
7726                      "with VALUE attribute must have length one",
7727                      sym->name, &sym->declared_at);
7728           return;
7729         }
7730     }
7731
7732   /* If the symbol is marked as bind(c), verify it's type and kind.  Do not
7733      do this for something that was implicitly typed because that is handled
7734      in gfc_set_default_type.  Handle dummy arguments and procedure
7735      definitions separately.  Also, anything that is use associated is not
7736      handled here but instead is handled in the module it is declared in.
7737      Finally, derived type definitions are allowed to be BIND(C) since that
7738      only implies that they're interoperable, and they are checked fully for
7739      interoperability when a variable is declared of that type.  */
7740   if (sym->attr.is_bind_c && sym->attr.implicit_type == 0 &&
7741       sym->attr.use_assoc == 0 && sym->attr.dummy == 0 &&
7742       sym->attr.flavor != FL_PROCEDURE && sym->attr.flavor != FL_DERIVED)
7743     {
7744       try t = SUCCESS;
7745       
7746       /* First, make sure the variable is declared at the
7747          module-level scope (J3/04-007, Section 15.3).  */
7748       if (sym->ns->proc_name->attr.flavor != FL_MODULE &&
7749           sym->attr.in_common == 0)
7750         {
7751           gfc_error ("Variable '%s' at %L cannot be BIND(C) because it "
7752                      "is neither a COMMON block nor declared at the "
7753                      "module level scope", sym->name, &(sym->declared_at));
7754           t = FAILURE;
7755         }
7756       else if (sym->common_head != NULL)
7757         {
7758           t = verify_com_block_vars_c_interop (sym->common_head);
7759         }
7760       else
7761         {
7762           /* If type() declaration, we need to verify that the components
7763              of the given type are all C interoperable, etc.  */
7764           if (sym->ts.type == BT_DERIVED &&
7765               sym->ts.derived->attr.is_c_interop != 1)
7766             {
7767               /* Make sure the user marked the derived type as BIND(C).  If
7768                  not, call the verify routine.  This could print an error
7769                  for the derived type more than once if multiple variables
7770                  of that type are declared.  */
7771               if (sym->ts.derived->attr.is_bind_c != 1)
7772                 verify_bind_c_derived_type (sym->ts.derived);
7773               t = FAILURE;
7774             }
7775           
7776           /* Verify the variable itself as C interoperable if it
7777              is BIND(C).  It is not possible for this to succeed if
7778              the verify_bind_c_derived_type failed, so don't have to handle
7779              any error returned by verify_bind_c_derived_type.  */
7780           t = verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
7781                                  sym->common_block);
7782         }
7783
7784       if (t == FAILURE)
7785         {
7786           /* clear the is_bind_c flag to prevent reporting errors more than
7787              once if something failed.  */
7788           sym->attr.is_bind_c = 0;
7789           return;
7790         }
7791     }
7792
7793   /* If a derived type symbol has reached this point, without its
7794      type being declared, we have an error.  Notice that most
7795      conditions that produce undefined derived types have already
7796      been dealt with.  However, the likes of:
7797      implicit type(t) (t) ..... call foo (t) will get us here if
7798      the type is not declared in the scope of the implicit
7799      statement. Change the type to BT_UNKNOWN, both because it is so
7800      and to prevent an ICE.  */
7801   if (sym->ts.type == BT_DERIVED && sym->ts.derived->components == NULL
7802       && !sym->ts.derived->attr.zero_comp)
7803     {
7804       gfc_error ("The derived type '%s' at %L is of type '%s', "
7805                  "which has not been defined", sym->name,
7806                   &sym->declared_at, sym->ts.derived->name);
7807       sym->ts.type = BT_UNKNOWN;
7808       return;
7809     }
7810
7811   /* Unless the derived-type declaration is use associated, Fortran 95
7812      does not allow public entries of private derived types.
7813      See 4.4.1 (F95) and 4.5.1.1 (F2003); and related interpretation
7814      161 in 95-006r3.  */
7815   if (sym->ts.type == BT_DERIVED
7816       && gfc_check_access (sym->attr.access, sym->ns->default_access)
7817       && !gfc_check_access (sym->ts.derived->attr.access,
7818                             sym->ts.derived->ns->default_access)
7819       && !sym->ts.derived->attr.use_assoc
7820       && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC %s '%s' at %L "
7821                          "of PRIVATE derived type '%s'",
7822                          (sym->attr.flavor == FL_PARAMETER) ? "parameter"
7823                          : "variable", sym->name, &sym->declared_at,
7824                          sym->ts.derived->name) == FAILURE)
7825     return;
7826
7827   /* An assumed-size array with INTENT(OUT) shall not be of a type for which
7828      default initialization is defined (5.1.2.4.4).  */
7829   if (sym->ts.type == BT_DERIVED
7830       && sym->attr.dummy
7831       && sym->attr.intent == INTENT_OUT
7832       && sym->as
7833       && sym->as->type == AS_ASSUMED_SIZE)
7834     {
7835       for (c = sym->ts.derived->components; c; c = c->next)
7836         {
7837           if (c->initializer)
7838             {
7839               gfc_error ("The INTENT(OUT) dummy argument '%s' at %L is "
7840                          "ASSUMED SIZE and so cannot have a default initializer",
7841                          sym->name, &sym->declared_at);
7842               return;
7843             }
7844         }
7845     }
7846
7847   switch (sym->attr.flavor)
7848     {
7849     case FL_VARIABLE:
7850       if (resolve_fl_variable (sym, mp_flag) == FAILURE)
7851         return;
7852       break;
7853
7854     case FL_PROCEDURE:
7855       if (resolve_fl_procedure (sym, mp_flag) == FAILURE)
7856         return;
7857       break;
7858
7859     case FL_NAMELIST:
7860       if (resolve_fl_namelist (sym) == FAILURE)
7861         return;
7862       break;
7863
7864     case FL_PARAMETER:
7865       if (resolve_fl_parameter (sym) == FAILURE)
7866         return;
7867       break;
7868
7869     default:
7870       break;
7871     }
7872
7873   /* Resolve array specifier. Check as well some constraints
7874      on COMMON blocks.  */
7875
7876   check_constant = sym->attr.in_common && !sym->attr.pointer;
7877
7878   /* Set the formal_arg_flag so that check_conflict will not throw
7879      an error for host associated variables in the specification
7880      expression for an array_valued function.  */
7881   if (sym->attr.function && sym->as)
7882     formal_arg_flag = 1;
7883
7884   gfc_resolve_array_spec (sym->as, check_constant);
7885
7886   formal_arg_flag = 0;
7887
7888   /* Resolve formal namespaces.  */
7889   if (sym->formal_ns && sym->formal_ns != gfc_current_ns)
7890     gfc_resolve (sym->formal_ns);
7891
7892   /* Check threadprivate restrictions.  */
7893   if (sym->attr.threadprivate && !sym->attr.save && !sym->ns->save_all
7894       && (!sym->attr.in_common
7895           && sym->module == NULL
7896           && (sym->ns->proc_name == NULL
7897               || sym->ns->proc_name->attr.flavor != FL_MODULE)))
7898     gfc_error ("Threadprivate at %L isn't SAVEd", &sym->declared_at);
7899
7900   /* If we have come this far we can apply default-initializers, as
7901      described in 14.7.5, to those variables that have not already
7902      been assigned one.  */
7903   if (sym->ts.type == BT_DERIVED
7904       && sym->attr.referenced
7905       && sym->ns == gfc_current_ns
7906       && !sym->value
7907       && !sym->attr.allocatable
7908       && !sym->attr.alloc_comp)
7909     {
7910       symbol_attribute *a = &sym->attr;
7911
7912       if ((!a->save && !a->dummy && !a->pointer
7913            && !a->in_common && !a->use_assoc
7914            && !(a->function && sym != sym->result))
7915           || (a->dummy && a->intent == INTENT_OUT))
7916         apply_default_init (sym);
7917     }
7918 }
7919
7920
7921 /************* Resolve DATA statements *************/
7922
7923 static struct
7924 {
7925   gfc_data_value *vnode;
7926   mpz_t left;
7927 }
7928 values;
7929
7930
7931 /* Advance the values structure to point to the next value in the data list.  */
7932
7933 static try
7934 next_data_value (void)
7935 {
7936
7937   while (mpz_cmp_ui (values.left, 0) == 0)
7938     {
7939       if (values.vnode->next == NULL)
7940         return FAILURE;
7941
7942       values.vnode = values.vnode->next;
7943       mpz_set (values.left, values.vnode->repeat);
7944     }
7945
7946   return SUCCESS;
7947 }
7948
7949
7950 static try
7951 check_data_variable (gfc_data_variable *var, locus *where)
7952 {
7953   gfc_expr *e;
7954   mpz_t size;
7955   mpz_t offset;
7956   try t;
7957   ar_type mark = AR_UNKNOWN;
7958   int i;
7959   mpz_t section_index[GFC_MAX_DIMENSIONS];
7960   gfc_ref *ref;
7961   gfc_array_ref *ar;
7962
7963   if (gfc_resolve_expr (var->expr) == FAILURE)
7964     return FAILURE;
7965
7966   ar = NULL;
7967   mpz_init_set_si (offset, 0);
7968   e = var->expr;
7969
7970   if (e->expr_type != EXPR_VARIABLE)
7971     gfc_internal_error ("check_data_variable(): Bad expression");
7972
7973   if (e->symtree->n.sym->ns->is_block_data
7974       && !e->symtree->n.sym->attr.in_common)
7975     {
7976       gfc_error ("BLOCK DATA element '%s' at %L must be in COMMON",
7977                  e->symtree->n.sym->name, &e->symtree->n.sym->declared_at);
7978     }
7979
7980   if (e->ref == NULL && e->symtree->n.sym->as)
7981     {
7982       gfc_error ("DATA array '%s' at %L must be specified in a previous"
7983                  " declaration", e->symtree->n.sym->name, where);
7984       return FAILURE;
7985     }
7986
7987   if (e->rank == 0)
7988     {
7989       mpz_init_set_ui (size, 1);
7990       ref = NULL;
7991     }
7992   else
7993     {
7994       ref = e->ref;
7995
7996       /* Find the array section reference.  */
7997       for (ref = e->ref; ref; ref = ref->next)
7998         {
7999           if (ref->type != REF_ARRAY)
8000             continue;
8001           if (ref->u.ar.type == AR_ELEMENT)
8002             continue;
8003           break;
8004         }
8005       gcc_assert (ref);
8006
8007       /* Set marks according to the reference pattern.  */
8008       switch (ref->u.ar.type)
8009         {
8010         case AR_FULL:
8011           mark = AR_FULL;
8012           break;
8013
8014         case AR_SECTION:
8015           ar = &ref->u.ar;
8016           /* Get the start position of array section.  */
8017           gfc_get_section_index (ar, section_index, &offset);
8018           mark = AR_SECTION;
8019           break;
8020
8021         default:
8022           gcc_unreachable ();
8023         }
8024
8025       if (gfc_array_size (e, &size) == FAILURE)
8026         {
8027           gfc_error ("Nonconstant array section at %L in DATA statement",
8028                      &e->where);
8029           mpz_clear (offset);
8030           return FAILURE;
8031         }
8032     }
8033
8034   t = SUCCESS;
8035
8036   while (mpz_cmp_ui (size, 0) > 0)
8037     {
8038       if (next_data_value () == FAILURE)
8039         {
8040           gfc_error ("DATA statement at %L has more variables than values",
8041                      where);
8042           t = FAILURE;
8043           break;
8044         }
8045
8046       t = gfc_check_assign (var->expr, values.vnode->expr, 0);
8047       if (t == FAILURE)
8048         break;
8049
8050       /* If we have more than one element left in the repeat count,
8051          and we have more than one element left in the target variable,
8052          then create a range assignment.  */
8053       /* FIXME: Only done for full arrays for now, since array sections
8054          seem tricky.  */
8055       if (mark == AR_FULL && ref && ref->next == NULL
8056           && mpz_cmp_ui (values.left, 1) > 0 && mpz_cmp_ui (size, 1) > 0)
8057         {
8058           mpz_t range;
8059
8060           if (mpz_cmp (size, values.left) >= 0)
8061             {
8062               mpz_init_set (range, values.left);
8063               mpz_sub (size, size, values.left);
8064               mpz_set_ui (values.left, 0);
8065             }
8066           else
8067             {
8068               mpz_init_set (range, size);
8069               mpz_sub (values.left, values.left, size);
8070               mpz_set_ui (size, 0);
8071             }
8072
8073           gfc_assign_data_value_range (var->expr, values.vnode->expr,
8074                                        offset, range);
8075
8076           mpz_add (offset, offset, range);
8077           mpz_clear (range);
8078         }
8079
8080       /* Assign initial value to symbol.  */
8081       else
8082         {
8083           mpz_sub_ui (values.left, values.left, 1);
8084           mpz_sub_ui (size, size, 1);
8085
8086           t = gfc_assign_data_value (var->expr, values.vnode->expr, offset);
8087           if (t == FAILURE)
8088             break;
8089
8090           if (mark == AR_FULL)
8091             mpz_add_ui (offset, offset, 1);
8092
8093           /* Modify the array section indexes and recalculate the offset
8094              for next element.  */
8095           else if (mark == AR_SECTION)
8096             gfc_advance_section (section_index, ar, &offset);
8097         }
8098     }
8099
8100   if (mark == AR_SECTION)
8101     {
8102       for (i = 0; i < ar->dimen; i++)
8103         mpz_clear (section_index[i]);
8104     }
8105
8106   mpz_clear (size);
8107   mpz_clear (offset);
8108
8109   return t;
8110 }
8111
8112
8113 static try traverse_data_var (gfc_data_variable *, locus *);
8114
8115 /* Iterate over a list of elements in a DATA statement.  */
8116
8117 static try
8118 traverse_data_list (gfc_data_variable *var, locus *where)
8119 {
8120   mpz_t trip;
8121   iterator_stack frame;
8122   gfc_expr *e, *start, *end, *step;
8123   try retval = SUCCESS;
8124
8125   mpz_init (frame.value);
8126
8127   start = gfc_copy_expr (var->iter.start);
8128   end = gfc_copy_expr (var->iter.end);
8129   step = gfc_copy_expr (var->iter.step);
8130
8131   if (gfc_simplify_expr (start, 1) == FAILURE
8132       || start->expr_type != EXPR_CONSTANT)
8133     {
8134       gfc_error ("iterator start at %L does not simplify", &start->where);
8135       retval = FAILURE;
8136       goto cleanup;
8137     }
8138   if (gfc_simplify_expr (end, 1) == FAILURE
8139       || end->expr_type != EXPR_CONSTANT)
8140     {
8141       gfc_error ("iterator end at %L does not simplify", &end->where);
8142       retval = FAILURE;
8143       goto cleanup;
8144     }
8145   if (gfc_simplify_expr (step, 1) == FAILURE
8146       || step->expr_type != EXPR_CONSTANT)
8147     {
8148       gfc_error ("iterator step at %L does not simplify", &step->where);
8149       retval = FAILURE;
8150       goto cleanup;
8151     }
8152
8153   mpz_init_set (trip, end->value.integer);
8154   mpz_sub (trip, trip, start->value.integer);
8155   mpz_add (trip, trip, step->value.integer);
8156
8157   mpz_div (trip, trip, step->value.integer);
8158
8159   mpz_set (frame.value, start->value.integer);
8160
8161   frame.prev = iter_stack;
8162   frame.variable = var->iter.var->symtree;
8163   iter_stack = &frame;
8164
8165   while (mpz_cmp_ui (trip, 0) > 0)
8166     {
8167       if (traverse_data_var (var->list, where) == FAILURE)
8168         {
8169           mpz_clear (trip);
8170           retval = FAILURE;
8171           goto cleanup;
8172         }
8173
8174       e = gfc_copy_expr (var->expr);
8175       if (gfc_simplify_expr (e, 1) == FAILURE)
8176         {
8177           gfc_free_expr (e);
8178           mpz_clear (trip);
8179           retval = FAILURE;
8180           goto cleanup;
8181         }
8182
8183       mpz_add (frame.value, frame.value, step->value.integer);
8184
8185       mpz_sub_ui (trip, trip, 1);
8186     }
8187
8188   mpz_clear (trip);
8189 cleanup:
8190   mpz_clear (frame.value);
8191
8192   gfc_free_expr (start);
8193   gfc_free_expr (end);
8194   gfc_free_expr (step);
8195
8196   iter_stack = frame.prev;
8197   return retval;
8198 }
8199
8200
8201 /* Type resolve variables in the variable list of a DATA statement.  */
8202
8203 static try
8204 traverse_data_var (gfc_data_variable *var, locus *where)
8205 {
8206   try t;
8207
8208   for (; var; var = var->next)
8209     {
8210       if (var->expr == NULL)
8211         t = traverse_data_list (var, where);
8212       else
8213         t = check_data_variable (var, where);
8214
8215       if (t == FAILURE)
8216         return FAILURE;
8217     }
8218
8219   return SUCCESS;
8220 }
8221
8222
8223 /* Resolve the expressions and iterators associated with a data statement.
8224    This is separate from the assignment checking because data lists should
8225    only be resolved once.  */
8226
8227 static try
8228 resolve_data_variables (gfc_data_variable *d)
8229 {
8230   for (; d; d = d->next)
8231     {
8232       if (d->list == NULL)
8233         {
8234           if (gfc_resolve_expr (d->expr) == FAILURE)
8235             return FAILURE;
8236         }
8237       else
8238         {
8239           if (gfc_resolve_iterator (&d->iter, false) == FAILURE)
8240             return FAILURE;
8241
8242           if (resolve_data_variables (d->list) == FAILURE)
8243             return FAILURE;
8244         }
8245     }
8246
8247   return SUCCESS;
8248 }
8249
8250
8251 /* Resolve a single DATA statement.  We implement this by storing a pointer to
8252    the value list into static variables, and then recursively traversing the
8253    variables list, expanding iterators and such.  */
8254
8255 static void
8256 resolve_data (gfc_data *d)
8257 {
8258
8259   if (resolve_data_variables (d->var) == FAILURE)
8260     return;
8261
8262   values.vnode = d->value;
8263   if (d->value == NULL)
8264     mpz_set_ui (values.left, 0);
8265   else
8266     mpz_set (values.left, d->value->repeat);
8267
8268   if (traverse_data_var (d->var, &d->where) == FAILURE)
8269     return;
8270
8271   /* At this point, we better not have any values left.  */
8272
8273   if (next_data_value () == SUCCESS)
8274     gfc_error ("DATA statement at %L has more values than variables",
8275                &d->where);
8276 }
8277
8278
8279 /* 12.6 Constraint: In a pure subprogram any variable which is in common or
8280    accessed by host or use association, is a dummy argument to a pure function,
8281    is a dummy argument with INTENT (IN) to a pure subroutine, or an object that
8282    is storage associated with any such variable, shall not be used in the
8283    following contexts: (clients of this function).  */
8284
8285 /* Determines if a variable is not 'pure', ie not assignable within a pure
8286    procedure.  Returns zero if assignment is OK, nonzero if there is a
8287    problem.  */
8288 int
8289 gfc_impure_variable (gfc_symbol *sym)
8290 {
8291   gfc_symbol *proc;
8292
8293   if (sym->attr.use_assoc || sym->attr.in_common)
8294     return 1;
8295
8296   if (sym->ns != gfc_current_ns)
8297     return !sym->attr.function;
8298
8299   proc = sym->ns->proc_name;
8300   if (sym->attr.dummy && gfc_pure (proc)
8301         && ((proc->attr.subroutine && sym->attr.intent == INTENT_IN)
8302                 ||
8303              proc->attr.function))
8304     return 1;
8305
8306   /* TODO: Sort out what can be storage associated, if anything, and include
8307      it here.  In principle equivalences should be scanned but it does not
8308      seem to be possible to storage associate an impure variable this way.  */
8309   return 0;
8310 }
8311
8312
8313 /* Test whether a symbol is pure or not.  For a NULL pointer, checks the
8314    symbol of the current procedure.  */
8315
8316 int
8317 gfc_pure (gfc_symbol *sym)
8318 {
8319   symbol_attribute attr;
8320
8321   if (sym == NULL)
8322     sym = gfc_current_ns->proc_name;
8323   if (sym == NULL)
8324     return 0;
8325
8326   attr = sym->attr;
8327
8328   return attr.flavor == FL_PROCEDURE && (attr.pure || attr.elemental);
8329 }
8330
8331
8332 /* Test whether the current procedure is elemental or not.  */
8333
8334 int
8335 gfc_elemental (gfc_symbol *sym)
8336 {
8337   symbol_attribute attr;
8338
8339   if (sym == NULL)
8340     sym = gfc_current_ns->proc_name;
8341   if (sym == NULL)
8342     return 0;
8343   attr = sym->attr;
8344
8345   return attr.flavor == FL_PROCEDURE && attr.elemental;
8346 }
8347
8348
8349 /* Warn about unused labels.  */
8350
8351 static void
8352 warn_unused_fortran_label (gfc_st_label *label)
8353 {
8354   if (label == NULL)
8355     return;
8356
8357   warn_unused_fortran_label (label->left);
8358
8359   if (label->defined == ST_LABEL_UNKNOWN)
8360     return;
8361
8362   switch (label->referenced)
8363     {
8364     case ST_LABEL_UNKNOWN:
8365       gfc_warning ("Label %d at %L defined but not used", label->value,
8366                    &label->where);
8367       break;
8368
8369     case ST_LABEL_BAD_TARGET:
8370       gfc_warning ("Label %d at %L defined but cannot be used",
8371                    label->value, &label->where);
8372       break;
8373
8374     default:
8375       break;
8376     }
8377
8378   warn_unused_fortran_label (label->right);
8379 }
8380
8381
8382 /* Returns the sequence type of a symbol or sequence.  */
8383
8384 static seq_type
8385 sequence_type (gfc_typespec ts)
8386 {
8387   seq_type result;
8388   gfc_component *c;
8389
8390   switch (ts.type)
8391   {
8392     case BT_DERIVED:
8393
8394       if (ts.derived->components == NULL)
8395         return SEQ_NONDEFAULT;
8396
8397       result = sequence_type (ts.derived->components->ts);
8398       for (c = ts.derived->components->next; c; c = c->next)
8399         if (sequence_type (c->ts) != result)
8400           return SEQ_MIXED;
8401
8402       return result;
8403
8404     case BT_CHARACTER:
8405       if (ts.kind != gfc_default_character_kind)
8406           return SEQ_NONDEFAULT;
8407
8408       return SEQ_CHARACTER;
8409
8410     case BT_INTEGER:
8411       if (ts.kind != gfc_default_integer_kind)
8412           return SEQ_NONDEFAULT;
8413
8414       return SEQ_NUMERIC;
8415
8416     case BT_REAL:
8417       if (!(ts.kind == gfc_default_real_kind
8418             || ts.kind == gfc_default_double_kind))
8419           return SEQ_NONDEFAULT;
8420
8421       return SEQ_NUMERIC;
8422
8423     case BT_COMPLEX:
8424       if (ts.kind != gfc_default_complex_kind)
8425           return SEQ_NONDEFAULT;
8426
8427       return SEQ_NUMERIC;
8428
8429     case BT_LOGICAL:
8430       if (ts.kind != gfc_default_logical_kind)
8431           return SEQ_NONDEFAULT;
8432
8433       return SEQ_NUMERIC;
8434
8435     default:
8436       return SEQ_NONDEFAULT;
8437   }
8438 }
8439
8440
8441 /* Resolve derived type EQUIVALENCE object.  */
8442
8443 static try
8444 resolve_equivalence_derived (gfc_symbol *derived, gfc_symbol *sym, gfc_expr *e)
8445 {
8446   gfc_symbol *d;
8447   gfc_component *c = derived->components;
8448
8449   if (!derived)
8450     return SUCCESS;
8451
8452   /* Shall not be an object of nonsequence derived type.  */
8453   if (!derived->attr.sequence)
8454     {
8455       gfc_error ("Derived type variable '%s' at %L must have SEQUENCE "
8456                  "attribute to be an EQUIVALENCE object", sym->name,
8457                  &e->where);
8458       return FAILURE;
8459     }
8460
8461   /* Shall not have allocatable components.  */
8462   if (derived->attr.alloc_comp)
8463     {
8464       gfc_error ("Derived type variable '%s' at %L cannot have ALLOCATABLE "
8465                  "components to be an EQUIVALENCE object",sym->name,
8466                  &e->where);
8467       return FAILURE;
8468     }
8469
8470   for (; c ; c = c->next)
8471     {
8472       d = c->ts.derived;
8473       if (d
8474           && (resolve_equivalence_derived (c->ts.derived, sym, e) == FAILURE))
8475         return FAILURE;
8476
8477       /* Shall not be an object of sequence derived type containing a pointer
8478          in the structure.  */
8479       if (c->pointer)
8480         {
8481           gfc_error ("Derived type variable '%s' at %L with pointer "
8482                      "component(s) cannot be an EQUIVALENCE object",
8483                      sym->name, &e->where);
8484           return FAILURE;
8485         }
8486     }
8487   return SUCCESS;
8488 }
8489
8490
8491 /* Resolve equivalence object. 
8492    An EQUIVALENCE object shall not be a dummy argument, a pointer, a target,
8493    an allocatable array, an object of nonsequence derived type, an object of
8494    sequence derived type containing a pointer at any level of component
8495    selection, an automatic object, a function name, an entry name, a result
8496    name, a named constant, a structure component, or a subobject of any of
8497    the preceding objects.  A substring shall not have length zero.  A
8498    derived type shall not have components with default initialization nor
8499    shall two objects of an equivalence group be initialized.
8500    Either all or none of the objects shall have an protected attribute.
8501    The simple constraints are done in symbol.c(check_conflict) and the rest
8502    are implemented here.  */
8503
8504 static void
8505 resolve_equivalence (gfc_equiv *eq)
8506 {
8507   gfc_symbol *sym;
8508   gfc_symbol *derived;
8509   gfc_symbol *first_sym;
8510   gfc_expr *e;
8511   gfc_ref *r;
8512   locus *last_where = NULL;
8513   seq_type eq_type, last_eq_type;
8514   gfc_typespec *last_ts;
8515   int object, cnt_protected;
8516   const char *value_name;
8517   const char *msg;
8518
8519   value_name = NULL;
8520   last_ts = &eq->expr->symtree->n.sym->ts;
8521
8522   first_sym = eq->expr->symtree->n.sym;
8523
8524   cnt_protected = 0;
8525
8526   for (object = 1; eq; eq = eq->eq, object++)
8527     {
8528       e = eq->expr;
8529
8530       e->ts = e->symtree->n.sym->ts;
8531       /* match_varspec might not know yet if it is seeing
8532          array reference or substring reference, as it doesn't
8533          know the types.  */
8534       if (e->ref && e->ref->type == REF_ARRAY)
8535         {
8536           gfc_ref *ref = e->ref;
8537           sym = e->symtree->n.sym;
8538
8539           if (sym->attr.dimension)
8540             {
8541               ref->u.ar.as = sym->as;
8542               ref = ref->next;
8543             }
8544
8545           /* For substrings, convert REF_ARRAY into REF_SUBSTRING.  */
8546           if (e->ts.type == BT_CHARACTER
8547               && ref
8548               && ref->type == REF_ARRAY
8549               && ref->u.ar.dimen == 1
8550               && ref->u.ar.dimen_type[0] == DIMEN_RANGE
8551               && ref->u.ar.stride[0] == NULL)
8552             {
8553               gfc_expr *start = ref->u.ar.start[0];
8554               gfc_expr *end = ref->u.ar.end[0];
8555               void *mem = NULL;
8556
8557               /* Optimize away the (:) reference.  */
8558               if (start == NULL && end == NULL)
8559                 {
8560                   if (e->ref == ref)
8561                     e->ref = ref->next;
8562                   else
8563                     e->ref->next = ref->next;
8564                   mem = ref;
8565                 }
8566               else
8567                 {
8568                   ref->type = REF_SUBSTRING;
8569                   if (start == NULL)
8570                     start = gfc_int_expr (1);
8571                   ref->u.ss.start = start;
8572                   if (end == NULL && e->ts.cl)
8573                     end = gfc_copy_expr (e->ts.cl->length);
8574                   ref->u.ss.end = end;
8575                   ref->u.ss.length = e->ts.cl;
8576                   e->ts.cl = NULL;
8577                 }
8578               ref = ref->next;
8579               gfc_free (mem);
8580             }
8581
8582           /* Any further ref is an error.  */
8583           if (ref)
8584             {
8585               gcc_assert (ref->type == REF_ARRAY);
8586               gfc_error ("Syntax error in EQUIVALENCE statement at %L",
8587                          &ref->u.ar.where);
8588               continue;
8589             }
8590         }
8591
8592       if (gfc_resolve_expr (e) == FAILURE)
8593         continue;
8594
8595       sym = e->symtree->n.sym;
8596
8597       if (sym->attr.protected)
8598         cnt_protected++;
8599       if (cnt_protected > 0 && cnt_protected != object)
8600         {
8601               gfc_error ("Either all or none of the objects in the "
8602                          "EQUIVALENCE set at %L shall have the "
8603                          "PROTECTED attribute",
8604                          &e->where);
8605               break;
8606         }
8607
8608       /* Shall not equivalence common block variables in a PURE procedure.  */
8609       if (sym->ns->proc_name
8610           && sym->ns->proc_name->attr.pure
8611           && sym->attr.in_common)
8612         {
8613           gfc_error ("Common block member '%s' at %L cannot be an EQUIVALENCE "
8614                      "object in the pure procedure '%s'",
8615                      sym->name, &e->where, sym->ns->proc_name->name);
8616           break;
8617         }
8618
8619       /* Shall not be a named constant.  */
8620       if (e->expr_type == EXPR_CONSTANT)
8621         {
8622           gfc_error ("Named constant '%s' at %L cannot be an EQUIVALENCE "
8623                      "object", sym->name, &e->where);
8624           continue;
8625         }
8626
8627       derived = e->ts.derived;
8628       if (derived && resolve_equivalence_derived (derived, sym, e) == FAILURE)
8629         continue;
8630
8631       /* Check that the types correspond correctly:
8632          Note 5.28:
8633          A numeric sequence structure may be equivalenced to another sequence
8634          structure, an object of default integer type, default real type, double
8635          precision real type, default logical type such that components of the
8636          structure ultimately only become associated to objects of the same
8637          kind. A character sequence structure may be equivalenced to an object
8638          of default character kind or another character sequence structure.
8639          Other objects may be equivalenced only to objects of the same type and
8640          kind parameters.  */
8641
8642       /* Identical types are unconditionally OK.  */
8643       if (object == 1 || gfc_compare_types (last_ts, &sym->ts))
8644         goto identical_types;
8645
8646       last_eq_type = sequence_type (*last_ts);
8647       eq_type = sequence_type (sym->ts);
8648
8649       /* Since the pair of objects is not of the same type, mixed or
8650          non-default sequences can be rejected.  */
8651
8652       msg = "Sequence %s with mixed components in EQUIVALENCE "
8653             "statement at %L with different type objects";
8654       if ((object ==2
8655            && last_eq_type == SEQ_MIXED
8656            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name, last_where)
8657               == FAILURE)
8658           || (eq_type == SEQ_MIXED
8659               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
8660                                  &e->where) == FAILURE))
8661         continue;
8662
8663       msg = "Non-default type object or sequence %s in EQUIVALENCE "
8664             "statement at %L with objects of different type";
8665       if ((object ==2
8666            && last_eq_type == SEQ_NONDEFAULT
8667            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name,
8668                               last_where) == FAILURE)
8669           || (eq_type == SEQ_NONDEFAULT
8670               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
8671                                  &e->where) == FAILURE))
8672         continue;
8673
8674       msg ="Non-CHARACTER object '%s' in default CHARACTER "
8675            "EQUIVALENCE statement at %L";
8676       if (last_eq_type == SEQ_CHARACTER
8677           && eq_type != SEQ_CHARACTER
8678           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
8679                              &e->where) == FAILURE)
8680                 continue;
8681
8682       msg ="Non-NUMERIC object '%s' in default NUMERIC "
8683            "EQUIVALENCE statement at %L";
8684       if (last_eq_type == SEQ_NUMERIC
8685           && eq_type != SEQ_NUMERIC
8686           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
8687                              &e->where) == FAILURE)
8688                 continue;
8689
8690   identical_types:
8691       last_ts =&sym->ts;
8692       last_where = &e->where;
8693
8694       if (!e->ref)
8695         continue;
8696
8697       /* Shall not be an automatic array.  */
8698       if (e->ref->type == REF_ARRAY
8699           && gfc_resolve_array_spec (e->ref->u.ar.as, 1) == FAILURE)
8700         {
8701           gfc_error ("Array '%s' at %L with non-constant bounds cannot be "
8702                      "an EQUIVALENCE object", sym->name, &e->where);
8703           continue;
8704         }
8705
8706       r = e->ref;
8707       while (r)
8708         {
8709           /* Shall not be a structure component.  */
8710           if (r->type == REF_COMPONENT)
8711             {
8712               gfc_error ("Structure component '%s' at %L cannot be an "
8713                          "EQUIVALENCE object",
8714                          r->u.c.component->name, &e->where);
8715               break;
8716             }
8717
8718           /* A substring shall not have length zero.  */
8719           if (r->type == REF_SUBSTRING)
8720             {
8721               if (compare_bound (r->u.ss.start, r->u.ss.end) == CMP_GT)
8722                 {
8723                   gfc_error ("Substring at %L has length zero",
8724                              &r->u.ss.start->where);
8725                   break;
8726                 }
8727             }
8728           r = r->next;
8729         }
8730     }
8731 }
8732
8733
8734 /* Resolve function and ENTRY types, issue diagnostics if needed.  */
8735
8736 static void
8737 resolve_fntype (gfc_namespace *ns)
8738 {
8739   gfc_entry_list *el;
8740   gfc_symbol *sym;
8741
8742   if (ns->proc_name == NULL || !ns->proc_name->attr.function)
8743     return;
8744
8745   /* If there are any entries, ns->proc_name is the entry master
8746      synthetic symbol and ns->entries->sym actual FUNCTION symbol.  */
8747   if (ns->entries)
8748     sym = ns->entries->sym;
8749   else
8750     sym = ns->proc_name;
8751   if (sym->result == sym
8752       && sym->ts.type == BT_UNKNOWN
8753       && gfc_set_default_type (sym, 0, NULL) == FAILURE
8754       && !sym->attr.untyped)
8755     {
8756       gfc_error ("Function '%s' at %L has no IMPLICIT type",
8757                  sym->name, &sym->declared_at);
8758       sym->attr.untyped = 1;
8759     }
8760
8761   if (sym->ts.type == BT_DERIVED && !sym->ts.derived->attr.use_assoc
8762       && !gfc_check_access (sym->ts.derived->attr.access,
8763                             sym->ts.derived->ns->default_access)
8764       && gfc_check_access (sym->attr.access, sym->ns->default_access))
8765     {
8766       gfc_error ("PUBLIC function '%s' at %L cannot be of PRIVATE type '%s'",
8767                  sym->name, &sym->declared_at, sym->ts.derived->name);
8768     }
8769
8770     if (ns->entries)
8771     for (el = ns->entries->next; el; el = el->next)
8772       {
8773         if (el->sym->result == el->sym
8774             && el->sym->ts.type == BT_UNKNOWN
8775             && gfc_set_default_type (el->sym, 0, NULL) == FAILURE
8776             && !el->sym->attr.untyped)
8777           {
8778             gfc_error ("ENTRY '%s' at %L has no IMPLICIT type",
8779                        el->sym->name, &el->sym->declared_at);
8780             el->sym->attr.untyped = 1;
8781           }
8782       }
8783 }
8784
8785 /* 12.3.2.1.1 Defined operators.  */
8786
8787 static void
8788 gfc_resolve_uops (gfc_symtree *symtree)
8789 {
8790   gfc_interface *itr;
8791   gfc_symbol *sym;
8792   gfc_formal_arglist *formal;
8793
8794   if (symtree == NULL)
8795     return;
8796
8797   gfc_resolve_uops (symtree->left);
8798   gfc_resolve_uops (symtree->right);
8799
8800   for (itr = symtree->n.uop->operator; itr; itr = itr->next)
8801     {
8802       sym = itr->sym;
8803       if (!sym->attr.function)
8804         gfc_error ("User operator procedure '%s' at %L must be a FUNCTION",
8805                    sym->name, &sym->declared_at);
8806
8807       if (sym->ts.type == BT_CHARACTER
8808           && !(sym->ts.cl && sym->ts.cl->length)
8809           && !(sym->result && sym->result->ts.cl
8810                && sym->result->ts.cl->length))
8811         gfc_error ("User operator procedure '%s' at %L cannot be assumed "
8812                    "character length", sym->name, &sym->declared_at);
8813
8814       formal = sym->formal;
8815       if (!formal || !formal->sym)
8816         {
8817           gfc_error ("User operator procedure '%s' at %L must have at least "
8818                      "one argument", sym->name, &sym->declared_at);
8819           continue;
8820         }
8821
8822       if (formal->sym->attr.intent != INTENT_IN)
8823         gfc_error ("First argument of operator interface at %L must be "
8824                    "INTENT(IN)", &sym->declared_at);
8825
8826       if (formal->sym->attr.optional)
8827         gfc_error ("First argument of operator interface at %L cannot be "
8828                    "optional", &sym->declared_at);
8829
8830       formal = formal->next;
8831       if (!formal || !formal->sym)
8832         continue;
8833
8834       if (formal->sym->attr.intent != INTENT_IN)
8835         gfc_error ("Second argument of operator interface at %L must be "
8836                    "INTENT(IN)", &sym->declared_at);
8837
8838       if (formal->sym->attr.optional)
8839         gfc_error ("Second argument of operator interface at %L cannot be "
8840                    "optional", &sym->declared_at);
8841
8842       if (formal->next)
8843         gfc_error ("Operator interface at %L must have, at most, two "
8844                    "arguments", &sym->declared_at);
8845     }
8846 }
8847
8848
8849 /* Examine all of the expressions associated with a program unit,
8850    assign types to all intermediate expressions, make sure that all
8851    assignments are to compatible types and figure out which names
8852    refer to which functions or subroutines.  It doesn't check code
8853    block, which is handled by resolve_code.  */
8854
8855 static void
8856 resolve_types (gfc_namespace *ns)
8857 {
8858   gfc_namespace *n;
8859   gfc_charlen *cl;
8860   gfc_data *d;
8861   gfc_equiv *eq;
8862
8863   gfc_current_ns = ns;
8864
8865   resolve_entries (ns);
8866
8867   resolve_common_blocks (ns->common_root);
8868
8869   resolve_contained_functions (ns);
8870
8871   gfc_traverse_ns (ns, resolve_bind_c_derived_types);
8872
8873   for (cl = ns->cl_list; cl; cl = cl->next)
8874     resolve_charlen (cl);
8875
8876   gfc_traverse_ns (ns, resolve_symbol);
8877
8878   resolve_fntype (ns);
8879
8880   for (n = ns->contained; n; n = n->sibling)
8881     {
8882       if (gfc_pure (ns->proc_name) && !gfc_pure (n->proc_name))
8883         gfc_error ("Contained procedure '%s' at %L of a PURE procedure must "
8884                    "also be PURE", n->proc_name->name,
8885                    &n->proc_name->declared_at);
8886
8887       resolve_types (n);
8888     }
8889
8890   forall_flag = 0;
8891   gfc_check_interfaces (ns);
8892
8893   gfc_traverse_ns (ns, resolve_values);
8894
8895   if (ns->save_all)
8896     gfc_save_all (ns);
8897
8898   iter_stack = NULL;
8899   for (d = ns->data; d; d = d->next)
8900     resolve_data (d);
8901
8902   iter_stack = NULL;
8903   gfc_traverse_ns (ns, gfc_formalize_init_value);
8904
8905   gfc_traverse_ns (ns, gfc_verify_binding_labels);
8906
8907   if (ns->common_root != NULL)
8908     gfc_traverse_symtree (ns->common_root, resolve_bind_c_comms);
8909
8910   for (eq = ns->equiv; eq; eq = eq->next)
8911     resolve_equivalence (eq);
8912
8913   /* Warn about unused labels.  */
8914   if (warn_unused_label)
8915     warn_unused_fortran_label (ns->st_labels);
8916
8917   gfc_resolve_uops (ns->uop_root);
8918 }
8919
8920
8921 /* Call resolve_code recursively.  */
8922
8923 static void
8924 resolve_codes (gfc_namespace *ns)
8925 {
8926   gfc_namespace *n;
8927
8928   for (n = ns->contained; n; n = n->sibling)
8929     resolve_codes (n);
8930
8931   gfc_current_ns = ns;
8932   cs_base = NULL;
8933   /* Set to an out of range value.  */
8934   current_entry_id = -1;
8935
8936   bitmap_obstack_initialize (&labels_obstack);
8937   resolve_code (ns->code, ns);
8938   bitmap_obstack_release (&labels_obstack);
8939 }
8940
8941
8942 /* This function is called after a complete program unit has been compiled.
8943    Its purpose is to examine all of the expressions associated with a program
8944    unit, assign types to all intermediate expressions, make sure that all
8945    assignments are to compatible types and figure out which names refer to
8946    which functions or subroutines.  */
8947
8948 void
8949 gfc_resolve (gfc_namespace *ns)
8950 {
8951   gfc_namespace *old_ns;
8952
8953   old_ns = gfc_current_ns;
8954
8955   resolve_types (ns);
8956   resolve_codes (ns);
8957
8958   gfc_current_ns = old_ns;
8959 }