OSDN Git Service

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