OSDN Git Service

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