OSDN Git Service

2006-08-30 Paul Thomas <pault@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 Free Software Foundation, 
3    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 2, 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 COPYING.  If not, write to the Free
20 Software Foundation, 51 Franklin Street, Fifth Floor,Boston, MA
21 02110-1301, USA.  */
22
23
24 #include "config.h"
25 #include "system.h"
26 #include "flags.h"
27 #include "gfortran.h"
28 #include "arith.h"  /* For gfc_compare_expr().  */
29 #include "dependency.h"
30
31 /* Types used in equivalence statements.  */
32
33 typedef enum seq_type
34 {
35   SEQ_NONDEFAULT, SEQ_NUMERIC, SEQ_CHARACTER, SEQ_MIXED
36 }
37 seq_type;
38
39 /* Stack to push the current if we descend into a block during
40    resolution.  See resolve_branch() and resolve_code().  */
41
42 typedef struct code_stack
43 {
44   struct gfc_code *head, *current;
45   struct code_stack *prev;
46 }
47 code_stack;
48
49 static code_stack *cs_base = NULL;
50
51
52 /* Nonzero if we're inside a FORALL block.  */
53
54 static int forall_flag;
55
56 /* Nonzero if we're inside a OpenMP WORKSHARE or PARALLEL WORKSHARE block.  */
57
58 static int omp_workshare_flag;
59
60 /* Nonzero if we are processing a formal arglist. The corresponding function
61    resets the flag each time that it is read.  */
62 static int formal_arg_flag = 0;
63
64 /* True if we are resolving a specification expression.  */
65 static int specification_expr = 0;
66
67 /* The id of the last entry seen.  */
68 static int current_entry_id;
69
70 int
71 gfc_is_formal_arg (void)
72 {
73   return formal_arg_flag;
74 }
75
76 /* Resolve types of formal argument lists.  These have to be done early so that
77    the formal argument lists of module procedures can be copied to the
78    containing module before the individual procedures are resolved
79    individually.  We also resolve argument lists of procedures in interface
80    blocks because they are self-contained scoping units.
81
82    Since a dummy argument cannot be a non-dummy procedure, the only
83    resort left for untyped names are the IMPLICIT types.  */
84
85 static void
86 resolve_formal_arglist (gfc_symbol * proc)
87 {
88   gfc_formal_arglist *f;
89   gfc_symbol *sym;
90   int i;
91
92   /* TODO: Procedures whose return character length parameter is not constant
93      or assumed must also have explicit interfaces.  */
94   if (proc->result != NULL)
95     sym = proc->result;
96   else
97     sym = proc;
98
99   if (gfc_elemental (proc)
100       || sym->attr.pointer || sym->attr.allocatable
101       || (sym->as && sym->as->rank > 0))
102     proc->attr.always_explicit = 1;
103
104   formal_arg_flag = 1;
105
106   for (f = proc->formal; f; f = f->next)
107     {
108       sym = f->sym;
109
110       if (sym == NULL)
111         {
112           /* Alternate return placeholder.  */
113           if (gfc_elemental (proc))
114             gfc_error ("Alternate return specifier in elemental subroutine "
115                        "'%s' at %L is not allowed", proc->name,
116                        &proc->declared_at);
117           if (proc->attr.function)
118             gfc_error ("Alternate return specifier in function "
119                        "'%s' at %L is not allowed", proc->name,
120                        &proc->declared_at);
121           continue;
122         }
123
124       if (sym->attr.if_source != IFSRC_UNKNOWN)
125         resolve_formal_arglist (sym);
126
127       if (sym->attr.subroutine || sym->attr.external || sym->attr.intrinsic)
128         {
129           if (gfc_pure (proc) && !gfc_pure (sym))
130             {
131               gfc_error
132                 ("Dummy procedure '%s' of PURE procedure at %L must also "
133                  "be PURE", sym->name, &sym->declared_at);
134               continue;
135             }
136
137           if (gfc_elemental (proc))
138             {
139               gfc_error
140                 ("Dummy procedure at %L not allowed in ELEMENTAL procedure",
141                  &sym->declared_at);
142               continue;
143             }
144
145           continue;
146         }
147
148       if (sym->ts.type == BT_UNKNOWN)
149         {
150           if (!sym->attr.function || sym->result == sym)
151             gfc_set_default_type (sym, 1, sym->ns);
152         }
153
154       gfc_resolve_array_spec (sym->as, 0);
155
156       /* We can't tell if an array with dimension (:) is assumed or deferred
157          shape until we know if it has the pointer or allocatable attributes.
158       */
159       if (sym->as && sym->as->rank > 0 && sym->as->type == AS_DEFERRED
160           && !(sym->attr.pointer || sym->attr.allocatable))
161         {
162           sym->as->type = AS_ASSUMED_SHAPE;
163           for (i = 0; i < sym->as->rank; i++)
164             sym->as->lower[i] = gfc_int_expr (1);
165         }
166
167       if ((sym->as && sym->as->rank > 0 && sym->as->type == AS_ASSUMED_SHAPE)
168           || sym->attr.pointer || sym->attr.allocatable || sym->attr.target
169           || sym->attr.optional)
170         proc->attr.always_explicit = 1;
171
172       /* If the flavor is unknown at this point, it has to be a variable.
173          A procedure specification would have already set the type.  */
174
175       if (sym->attr.flavor == FL_UNKNOWN)
176         gfc_add_flavor (&sym->attr, FL_VARIABLE, sym->name, &sym->declared_at);
177
178       if (gfc_pure (proc))
179         {
180           if (proc->attr.function && !sym->attr.pointer
181               && sym->attr.flavor != FL_PROCEDURE
182               && sym->attr.intent != INTENT_IN)
183
184             gfc_error ("Argument '%s' of pure function '%s' at %L must be "
185                        "INTENT(IN)", sym->name, proc->name,
186                        &sym->declared_at);
187
188           if (proc->attr.subroutine && !sym->attr.pointer
189               && sym->attr.intent == INTENT_UNKNOWN)
190
191             gfc_error
192               ("Argument '%s' of pure subroutine '%s' at %L must have "
193                "its INTENT specified", sym->name, proc->name,
194                &sym->declared_at);
195         }
196
197
198       if (gfc_elemental (proc))
199         {
200           if (sym->as != NULL)
201             {
202               gfc_error
203                 ("Argument '%s' of elemental procedure at %L must be scalar",
204                  sym->name, &sym->declared_at);
205               continue;
206             }
207
208           if (sym->attr.pointer)
209             {
210               gfc_error
211                 ("Argument '%s' of elemental procedure at %L cannot have "
212                  "the POINTER attribute", sym->name, &sym->declared_at);
213               continue;
214             }
215         }
216
217       /* Each dummy shall be specified to be scalar.  */
218       if (proc->attr.proc == PROC_ST_FUNCTION)
219         {
220           if (sym->as != NULL)
221             {
222               gfc_error
223                 ("Argument '%s' of statement function at %L must be scalar",
224                  sym->name, &sym->declared_at);
225               continue;
226             }
227
228           if (sym->ts.type == BT_CHARACTER)
229             {
230               gfc_charlen *cl = sym->ts.cl;
231               if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
232                 {
233                   gfc_error
234                     ("Character-valued argument '%s' of statement function at "
235                      "%L must has constant length",
236                      sym->name, &sym->declared_at);
237                   continue;
238                 }
239             }
240         }
241     }
242   formal_arg_flag = 0;
243 }
244
245
246 /* Work function called when searching for symbols that have argument lists
247    associated with them.  */
248
249 static void
250 find_arglists (gfc_symbol * sym)
251 {
252
253   if (sym->attr.if_source == IFSRC_UNKNOWN || sym->ns != gfc_current_ns)
254     return;
255
256   resolve_formal_arglist (sym);
257 }
258
259
260 /* Given a namespace, resolve all formal argument lists within the namespace.
261  */
262
263 static void
264 resolve_formal_arglists (gfc_namespace * ns)
265 {
266
267   if (ns == NULL)
268     return;
269
270   gfc_traverse_ns (ns, find_arglists);
271 }
272
273
274 static void
275 resolve_contained_fntype (gfc_symbol * sym, gfc_namespace * ns)
276 {
277   try t;
278   
279   /* If this namespace is not a function, ignore it.  */
280   if (! sym
281       || !(sym->attr.function
282            || sym->attr.flavor == FL_VARIABLE))
283     return;
284
285   /* Try to find out of what the return type is.  */
286   if (sym->result != NULL)
287     sym = sym->result;
288
289   if (sym->ts.type == BT_UNKNOWN)
290     {
291       t = gfc_set_default_type (sym, 0, ns);
292
293       if (t == FAILURE && !sym->attr.untyped)
294         {
295           gfc_error ("Contained function '%s' at %L has no IMPLICIT type",
296                      sym->name, &sym->declared_at); /* FIXME */
297           sym->attr.untyped = 1;
298         }
299     }
300
301   /*Fortran 95 Draft Standard, page 51, Section 5.1.1.5, on the Character type,
302     lists the only ways a character length value of * can be used: dummy arguments
303     of procedures, named constants, and function results in external functions.
304     Internal function results are not on that list; ergo, not permitted.  */
305
306   if (sym->ts.type == BT_CHARACTER)
307     {
308       gfc_charlen *cl = sym->ts.cl;
309       if (!cl || !cl->length)
310         gfc_error ("Character-valued internal function '%s' at %L must "
311                    "not be assumed length", sym->name, &sym->declared_at);
312     }
313 }
314
315
316 /* Add NEW_ARGS to the formal argument list of PROC, taking care not to
317    introduce duplicates.  */
318
319 static void
320 merge_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
321 {
322   gfc_formal_arglist *f, *new_arglist;
323   gfc_symbol *new_sym;
324
325   for (; new_args != NULL; new_args = new_args->next)
326     {
327       new_sym = new_args->sym;
328       /* See if ths arg is already in the formal argument list.  */
329       for (f = proc->formal; f; f = f->next)
330         {
331           if (new_sym == f->sym)
332             break;
333         }
334
335       if (f)
336         continue;
337
338       /* Add a new argument.  Argument order is not important.  */
339       new_arglist = gfc_get_formal_arglist ();
340       new_arglist->sym = new_sym;
341       new_arglist->next = proc->formal;
342       proc->formal  = new_arglist;
343     }
344 }
345
346
347 /* Resolve alternate entry points.  If a symbol has multiple entry points we
348    create a new master symbol for the main routine, and turn the existing
349    symbol into an entry point.  */
350
351 static void
352 resolve_entries (gfc_namespace * ns)
353 {
354   gfc_namespace *old_ns;
355   gfc_code *c;
356   gfc_symbol *proc;
357   gfc_entry_list *el;
358   char name[GFC_MAX_SYMBOL_LEN + 1];
359   static int master_count = 0;
360
361   if (ns->proc_name == NULL)
362     return;
363
364   /* No need to do anything if this procedure doesn't have alternate entry
365      points.  */
366   if (!ns->entries)
367     return;
368
369   /* We may already have resolved alternate entry points.  */
370   if (ns->proc_name->attr.entry_master)
371     return;
372
373   /* If this isn't a procedure something has gone horribly wrong.  */
374   gcc_assert (ns->proc_name->attr.flavor == FL_PROCEDURE);
375   
376   /* Remember the current namespace.  */
377   old_ns = gfc_current_ns;
378
379   gfc_current_ns = ns;
380
381   /* Add the main entry point to the list of entry points.  */
382   el = gfc_get_entry_list ();
383   el->sym = ns->proc_name;
384   el->id = 0;
385   el->next = ns->entries;
386   ns->entries = el;
387   ns->proc_name->attr.entry = 1;
388
389   /* If it is a module function, it needs to be in the right namespace
390      so that gfc_get_fake_result_decl can gather up the results. The
391      need for this arose in get_proc_name, where these beasts were
392      left in their own namespace, to keep prior references linked to
393      the entry declaration.*/
394   if (ns->proc_name->attr.function
395         && ns->parent
396         && ns->parent->proc_name->attr.flavor == FL_MODULE)
397     el->sym->ns = ns;
398
399   /* Add an entry statement for it.  */
400   c = gfc_get_code ();
401   c->op = EXEC_ENTRY;
402   c->ext.entry = el;
403   c->next = ns->code;
404   ns->code = c;
405
406   /* Create a new symbol for the master function.  */
407   /* Give the internal function a unique name (within this file).
408      Also include the function name so the user has some hope of figuring
409      out what is going on.  */
410   snprintf (name, GFC_MAX_SYMBOL_LEN, "master.%d.%s",
411             master_count++, ns->proc_name->name);
412   gfc_get_ha_symbol (name, &proc);
413   gcc_assert (proc != NULL);
414
415   gfc_add_procedure (&proc->attr, PROC_INTERNAL, proc->name, NULL);
416   if (ns->proc_name->attr.subroutine)
417     gfc_add_subroutine (&proc->attr, proc->name, NULL);
418   else
419     {
420       gfc_symbol *sym;
421       gfc_typespec *ts, *fts;
422
423       gfc_add_function (&proc->attr, proc->name, NULL);
424       proc->result = proc;
425       fts = &ns->entries->sym->result->ts;
426       if (fts->type == BT_UNKNOWN)
427         fts = gfc_get_default_type (ns->entries->sym->result, NULL);
428       for (el = ns->entries->next; el; el = el->next)
429         {
430           ts = &el->sym->result->ts;
431           if (ts->type == BT_UNKNOWN)
432             ts = gfc_get_default_type (el->sym->result, NULL);
433           if (! gfc_compare_types (ts, fts)
434               || (el->sym->result->attr.dimension
435                   != ns->entries->sym->result->attr.dimension)
436               || (el->sym->result->attr.pointer
437                   != ns->entries->sym->result->attr.pointer))
438             break;
439         }
440
441       if (el == NULL)
442         {
443           sym = ns->entries->sym->result;
444           /* All result types the same.  */
445           proc->ts = *fts;
446           if (sym->attr.dimension)
447             gfc_set_array_spec (proc, gfc_copy_array_spec (sym->as), NULL);
448           if (sym->attr.pointer)
449             gfc_add_pointer (&proc->attr, NULL);
450         }
451       else
452         {
453           /* Otherwise the result will be passed through a union by
454              reference.  */
455           proc->attr.mixed_entry_master = 1;
456           for (el = ns->entries; el; el = el->next)
457             {
458               sym = el->sym->result;
459               if (sym->attr.dimension)
460               {
461                 if (el == ns->entries)
462                   gfc_error
463                   ("FUNCTION result %s can't be an array in FUNCTION %s at %L",
464                    sym->name, ns->entries->sym->name, &sym->declared_at);
465                 else
466                   gfc_error
467                     ("ENTRY result %s can't be an array in FUNCTION %s at %L",
468                      sym->name, ns->entries->sym->name, &sym->declared_at);
469               }
470               else if (sym->attr.pointer)
471               {
472                 if (el == ns->entries)
473                   gfc_error
474                   ("FUNCTION result %s can't be a POINTER in FUNCTION %s at %L",
475                    sym->name, ns->entries->sym->name, &sym->declared_at);
476                 else
477                   gfc_error
478                     ("ENTRY result %s can't be a POINTER in FUNCTION %s at %L",
479                      sym->name, ns->entries->sym->name, &sym->declared_at);
480               }
481               else
482                 {
483                   ts = &sym->ts;
484                   if (ts->type == BT_UNKNOWN)
485                     ts = gfc_get_default_type (sym, NULL);
486                   switch (ts->type)
487                     {
488                     case BT_INTEGER:
489                       if (ts->kind == gfc_default_integer_kind)
490                         sym = NULL;
491                       break;
492                     case BT_REAL:
493                       if (ts->kind == gfc_default_real_kind
494                           || ts->kind == gfc_default_double_kind)
495                         sym = NULL;
496                       break;
497                     case BT_COMPLEX:
498                       if (ts->kind == gfc_default_complex_kind)
499                         sym = NULL;
500                       break;
501                     case BT_LOGICAL:
502                       if (ts->kind == gfc_default_logical_kind)
503                         sym = NULL;
504                       break;
505                     case BT_UNKNOWN:
506                       /* We will issue error elsewhere.  */
507                       sym = NULL;
508                       break;
509                     default:
510                       break;
511                     }
512                   if (sym)
513                   {
514                     if (el == ns->entries)
515                       gfc_error
516                         ("FUNCTION result %s can't be of type %s in FUNCTION %s at %L",
517                          sym->name, gfc_typename (ts), ns->entries->sym->name,
518                          &sym->declared_at);
519                     else
520                       gfc_error
521                         ("ENTRY result %s can't be of type %s in FUNCTION %s at %L",
522                          sym->name, gfc_typename (ts), ns->entries->sym->name,
523                          &sym->declared_at);
524                   }
525                 }
526             }
527         }
528     }
529   proc->attr.access = ACCESS_PRIVATE;
530   proc->attr.entry_master = 1;
531
532   /* Merge all the entry point arguments.  */
533   for (el = ns->entries; el; el = el->next)
534     merge_argument_lists (proc, el->sym->formal);
535
536   /* Use the master function for the function body.  */
537   ns->proc_name = proc;
538
539   /* Finalize the new symbols.  */
540   gfc_commit_symbols ();
541
542   /* Restore the original namespace.  */
543   gfc_current_ns = old_ns;
544 }
545
546
547 /* Resolve contained function types.  Because contained functions can call one
548    another, they have to be worked out before any of the contained procedures
549    can be resolved.
550
551    The good news is that if a function doesn't already have a type, the only
552    way it can get one is through an IMPLICIT type or a RESULT variable, because
553    by definition contained functions are contained namespace they're contained
554    in, not in a sibling or parent namespace.  */
555
556 static void
557 resolve_contained_functions (gfc_namespace * ns)
558 {
559   gfc_namespace *child;
560   gfc_entry_list *el;
561
562   resolve_formal_arglists (ns);
563
564   for (child = ns->contained; child; child = child->sibling)
565     {
566       /* Resolve alternate entry points first.  */
567       resolve_entries (child); 
568
569       /* Then check function return types.  */
570       resolve_contained_fntype (child->proc_name, child);
571       for (el = child->entries; el; el = el->next)
572         resolve_contained_fntype (el->sym, child);
573     }
574 }
575
576
577 /* Resolve all of the elements of a structure constructor and make sure that
578    the types are correct.  */
579
580 static try
581 resolve_structure_cons (gfc_expr * expr)
582 {
583   gfc_constructor *cons;
584   gfc_component *comp;
585   try t;
586
587   t = SUCCESS;
588   cons = expr->value.constructor;
589   /* A constructor may have references if it is the result of substituting a
590      parameter variable.  In this case we just pull out the component we
591      want.  */
592   if (expr->ref)
593     comp = expr->ref->u.c.sym->components;
594   else
595     comp = expr->ts.derived->components;
596
597   for (; comp; comp = comp->next, cons = cons->next)
598     {
599       if (! cons->expr)
600         {
601           t = FAILURE;
602           continue;
603         }
604
605       if (gfc_resolve_expr (cons->expr) == FAILURE)
606         {
607           t = FAILURE;
608           continue;
609         }
610
611       /* If we don't have the right type, try to convert it.  */
612
613       if (!gfc_compare_types (&cons->expr->ts, &comp->ts))
614         {
615           t = FAILURE;
616           if (comp->pointer && cons->expr->ts.type != BT_UNKNOWN)
617             gfc_error ("The element in the derived type constructor at %L, "
618                        "for pointer component '%s', is %s but should be %s",
619                        &cons->expr->where, comp->name,
620                        gfc_basic_typename (cons->expr->ts.type),
621                        gfc_basic_typename (comp->ts.type));
622           else
623             t = gfc_convert_type (cons->expr, &comp->ts, 1);
624         }
625     }
626
627   return t;
628 }
629
630
631
632 /****************** Expression name resolution ******************/
633
634 /* Returns 0 if a symbol was not declared with a type or
635    attribute declaration statement, nonzero otherwise.  */
636
637 static int
638 was_declared (gfc_symbol * sym)
639 {
640   symbol_attribute a;
641
642   a = sym->attr;
643
644   if (!a.implicit_type && sym->ts.type != BT_UNKNOWN)
645     return 1;
646
647   if (a.allocatable || a.dimension || a.dummy || a.external || a.intrinsic
648       || a.optional || a.pointer || a.save || a.target
649       || a.access != ACCESS_UNKNOWN || a.intent != INTENT_UNKNOWN)
650     return 1;
651
652   return 0;
653 }
654
655
656 /* Determine if a symbol is generic or not.  */
657
658 static int
659 generic_sym (gfc_symbol * sym)
660 {
661   gfc_symbol *s;
662
663   if (sym->attr.generic ||
664       (sym->attr.intrinsic && gfc_generic_intrinsic (sym->name)))
665     return 1;
666
667   if (was_declared (sym) || sym->ns->parent == NULL)
668     return 0;
669
670   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
671
672   return (s == NULL) ? 0 : generic_sym (s);
673 }
674
675
676 /* Determine if a symbol is specific or not.  */
677
678 static int
679 specific_sym (gfc_symbol * sym)
680 {
681   gfc_symbol *s;
682
683   if (sym->attr.if_source == IFSRC_IFBODY
684       || sym->attr.proc == PROC_MODULE
685       || sym->attr.proc == PROC_INTERNAL
686       || sym->attr.proc == PROC_ST_FUNCTION
687       || (sym->attr.intrinsic &&
688           gfc_specific_intrinsic (sym->name))
689       || sym->attr.external)
690     return 1;
691
692   if (was_declared (sym) || sym->ns->parent == NULL)
693     return 0;
694
695   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
696
697   return (s == NULL) ? 0 : specific_sym (s);
698 }
699
700
701 /* Figure out if the procedure is specific, generic or unknown.  */
702
703 typedef enum
704 { PTYPE_GENERIC = 1, PTYPE_SPECIFIC, PTYPE_UNKNOWN }
705 proc_type;
706
707 static proc_type
708 procedure_kind (gfc_symbol * sym)
709 {
710
711   if (generic_sym (sym))
712     return PTYPE_GENERIC;
713
714   if (specific_sym (sym))
715     return PTYPE_SPECIFIC;
716
717   return PTYPE_UNKNOWN;
718 }
719
720 /* Check references to assumed size arrays.  The flag need_full_assumed_size
721    is nonzero when matching actual arguments.  */
722
723 static int need_full_assumed_size = 0;
724
725 static bool
726 check_assumed_size_reference (gfc_symbol * sym, gfc_expr * e)
727 {
728   gfc_ref * ref;
729   int dim;
730   int last = 1;
731
732   if (need_full_assumed_size
733         || !(sym->as && sym->as->type == AS_ASSUMED_SIZE))
734       return false;
735
736   for (ref = e->ref; ref; ref = ref->next)
737     if (ref->type == REF_ARRAY)
738       for (dim = 0; dim < ref->u.ar.as->rank; dim++)
739         last = (ref->u.ar.end[dim] == NULL) && (ref->u.ar.type == DIMEN_ELEMENT);
740
741   if (last)
742     {
743       gfc_error ("The upper bound in the last dimension must "
744                  "appear in the reference to the assumed size "
745                  "array '%s' at %L.", sym->name, &e->where);
746       return true;
747     }
748   return false;
749 }
750
751
752 /* Look for bad assumed size array references in argument expressions
753   of elemental and array valued intrinsic procedures.  Since this is
754   called from procedure resolution functions, it only recurses at
755   operators.  */
756
757 static bool
758 resolve_assumed_size_actual (gfc_expr *e)
759 {
760   if (e == NULL)
761    return false;
762
763   switch (e->expr_type)
764     {
765     case EXPR_VARIABLE:
766       if (e->symtree
767             && check_assumed_size_reference (e->symtree->n.sym, e))
768         return true;
769       break;
770
771     case EXPR_OP:
772       if (resolve_assumed_size_actual (e->value.op.op1)
773             || resolve_assumed_size_actual (e->value.op.op2))
774         return true;
775       break;
776
777     default:
778       break;
779     }
780   return false;
781 }
782
783
784 /* Resolve an actual argument list.  Most of the time, this is just
785    resolving the expressions in the list.
786    The exception is that we sometimes have to decide whether arguments
787    that look like procedure arguments are really simple variable
788    references.  */
789
790 static try
791 resolve_actual_arglist (gfc_actual_arglist * arg)
792 {
793   gfc_symbol *sym;
794   gfc_symtree *parent_st;
795   gfc_expr *e;
796
797   for (; arg; arg = arg->next)
798     {
799
800       e = arg->expr;
801       if (e == NULL)
802         {
803           /* Check the label is a valid branching target.  */
804           if (arg->label)
805             {
806               if (arg->label->defined == ST_LABEL_UNKNOWN)
807                 {
808                   gfc_error ("Label %d referenced at %L is never defined",
809                              arg->label->value, &arg->label->where);
810                   return FAILURE;
811                 }
812             }
813           continue;
814         }
815
816       if (e->ts.type != BT_PROCEDURE)
817         {
818           if (gfc_resolve_expr (e) != SUCCESS)
819             return FAILURE;
820           continue;
821         }
822
823       /* See if the expression node should really be a variable
824          reference.  */
825
826       sym = e->symtree->n.sym;
827
828       if (sym->attr.flavor == FL_PROCEDURE
829           || sym->attr.intrinsic
830           || sym->attr.external)
831         {
832
833           /* If a procedure is not already determined to be something else
834              check if it is intrinsic.  */
835           if (!sym->attr.intrinsic
836                 && !(sym->attr.external || sym->attr.use_assoc
837                        || sym->attr.if_source == IFSRC_IFBODY)
838                 && gfc_intrinsic_name (sym->name, sym->attr.subroutine))
839             sym->attr.intrinsic = 1;
840
841           if (sym->attr.proc == PROC_ST_FUNCTION)
842             {
843               gfc_error ("Statement function '%s' at %L is not allowed as an "
844                          "actual argument", sym->name, &e->where);
845             }
846
847           if (sym->attr.contained && !sym->attr.use_assoc
848               && sym->ns->proc_name->attr.flavor != FL_MODULE)
849             {
850               gfc_error ("Internal procedure '%s' is not allowed as an "
851                          "actual argument at %L", sym->name, &e->where);
852             }
853
854           if (sym->attr.elemental && !sym->attr.intrinsic)
855             {
856               gfc_error ("ELEMENTAL non-INTRINSIC procedure '%s' is not "
857                          "allowed as an actual argument at %L", sym->name,
858                          &e->where);
859             }
860
861           if (sym->attr.generic)
862             {
863               gfc_error ("GENERIC non-INTRINSIC procedure '%s' is not "
864                          "allowed as an actual argument at %L", sym->name,
865                          &e->where);
866             }
867
868           /* If the symbol is the function that names the current (or
869              parent) scope, then we really have a variable reference.  */
870
871           if (sym->attr.function && sym->result == sym
872               && (sym->ns->proc_name == sym
873                   || (sym->ns->parent != NULL
874                       && sym->ns->parent->proc_name == sym)))
875             goto got_variable;
876
877           continue;
878         }
879
880       /* See if the name is a module procedure in a parent unit.  */
881
882       if (was_declared (sym) || sym->ns->parent == NULL)
883         goto got_variable;
884
885       if (gfc_find_sym_tree (sym->name, sym->ns->parent, 1, &parent_st))
886         {
887           gfc_error ("Symbol '%s' at %L is ambiguous", sym->name, &e->where);
888           return FAILURE;
889         }
890
891       if (parent_st == NULL)
892         goto got_variable;
893
894       sym = parent_st->n.sym;
895       e->symtree = parent_st;           /* Point to the right thing.  */
896
897       if (sym->attr.flavor == FL_PROCEDURE
898           || sym->attr.intrinsic
899           || sym->attr.external)
900         {
901           continue;
902         }
903
904     got_variable:
905       e->expr_type = EXPR_VARIABLE;
906       e->ts = sym->ts;
907       if (sym->as != NULL)
908         {
909           e->rank = sym->as->rank;
910           e->ref = gfc_get_ref ();
911           e->ref->type = REF_ARRAY;
912           e->ref->u.ar.type = AR_FULL;
913           e->ref->u.ar.as = sym->as;
914         }
915     }
916
917   return SUCCESS;
918 }
919
920
921 /* Do the checks of the actual argument list that are specific to elemental
922    procedures.  If called with c == NULL, we have a function, otherwise if
923    expr == NULL, we have a subroutine.  */
924 static try
925 resolve_elemental_actual (gfc_expr *expr, gfc_code *c)
926 {
927   gfc_actual_arglist *arg0;
928   gfc_actual_arglist *arg;
929   gfc_symbol *esym = NULL;
930   gfc_intrinsic_sym *isym = NULL;
931   gfc_expr *e = NULL;
932   gfc_intrinsic_arg *iformal = NULL;
933   gfc_formal_arglist *eformal = NULL;
934   bool formal_optional = false;
935   bool set_by_optional = false;
936   int i;
937   int rank = 0;
938
939   /* Is this an elemental procedure?  */
940   if (expr && expr->value.function.actual != NULL)
941     {
942       if (expr->value.function.esym != NULL
943             && expr->value.function.esym->attr.elemental)
944         {
945           arg0 = expr->value.function.actual;
946           esym = expr->value.function.esym;
947         }
948       else if (expr->value.function.isym != NULL
949                  && expr->value.function.isym->elemental)
950         {
951           arg0 = expr->value.function.actual;
952           isym = expr->value.function.isym;
953         }
954       else
955         return SUCCESS;
956     }
957   else if (c && c->ext.actual != NULL
958              && c->symtree->n.sym->attr.elemental)
959     {
960       arg0 = c->ext.actual;
961       esym = c->symtree->n.sym;
962     }
963   else
964     return SUCCESS;
965
966   /* The rank of an elemental is the rank of its array argument(s).  */
967   for (arg = arg0; arg; arg = arg->next)
968     {
969       if (arg->expr != NULL && arg->expr->rank > 0)
970         {
971           rank = arg->expr->rank;
972           if (arg->expr->expr_type == EXPR_VARIABLE
973                 && arg->expr->symtree->n.sym->attr.optional)
974             set_by_optional = true;
975
976           /* Function specific; set the result rank and shape.  */
977           if (expr)
978             {
979               expr->rank = rank;
980               if (!expr->shape && arg->expr->shape)
981                 {
982                   expr->shape = gfc_get_shape (rank);
983                   for (i = 0; i < rank; i++)
984                     mpz_init_set (expr->shape[i], arg->expr->shape[i]);
985                 }
986             }
987           break;
988         }
989     }
990
991   /* If it is an array, it shall not be supplied as an actual argument
992      to an elemental procedure unless an array of the same rank is supplied
993      as an actual argument corresponding to a nonoptional dummy argument of
994      that elemental procedure(12.4.1.5).  */
995   formal_optional = false;
996   if (isym)
997     iformal = isym->formal;
998   else
999     eformal = esym->formal;
1000
1001   for (arg = arg0; arg; arg = arg->next)
1002     {
1003       if (eformal)
1004         {
1005           if (eformal->sym && eformal->sym->attr.optional)
1006             formal_optional = true;
1007           eformal = eformal->next;
1008         }
1009       else if (isym && iformal)
1010         {
1011           if (iformal->optional)
1012             formal_optional = true;
1013           iformal = iformal->next;
1014         }
1015       else if (isym)
1016         formal_optional = true;
1017
1018       if (pedantic && arg->expr != NULL
1019             && arg->expr->expr_type == EXPR_VARIABLE
1020             && arg->expr->symtree->n.sym->attr.optional
1021             && formal_optional
1022             && arg->expr->rank
1023             && (set_by_optional || arg->expr->rank != rank)
1024             && !(isym && isym->generic_id == GFC_ISYM_CONVERSION)) 
1025         {
1026           gfc_warning ("'%s' at %L is an array and OPTIONAL; IF IT IS "
1027                        "MISSING, it cannot be the actual argument of an "
1028                        "ELEMENTAL procedure unless there is a non-optional"
1029                        "argument with the same rank (12.4.1.5)",
1030                        arg->expr->symtree->n.sym->name, &arg->expr->where);
1031           return FAILURE;
1032         }
1033     }
1034
1035   for (arg = arg0; arg; arg = arg->next)
1036     {
1037       if (arg->expr == NULL || arg->expr->rank == 0)
1038         continue;
1039
1040       /* Being elemental, the last upper bound of an assumed size array
1041          argument must be present.  */
1042       if (resolve_assumed_size_actual (arg->expr))
1043         return FAILURE;
1044
1045       if (expr)
1046         continue;
1047
1048       /* Elemental subroutine array actual arguments must conform.  */
1049       if (e != NULL)
1050         {
1051           if (gfc_check_conformance ("elemental subroutine", arg->expr, e)
1052                 == FAILURE)
1053             return FAILURE;
1054         }
1055       else
1056         e = arg->expr;
1057     }
1058
1059   return SUCCESS;
1060 }
1061
1062
1063 /* Go through each actual argument in ACTUAL and see if it can be
1064    implemented as an inlined, non-copying intrinsic.  FNSYM is the
1065    function being called, or NULL if not known.  */
1066
1067 static void
1068 find_noncopying_intrinsics (gfc_symbol * fnsym, gfc_actual_arglist * actual)
1069 {
1070   gfc_actual_arglist *ap;
1071   gfc_expr *expr;
1072
1073   for (ap = actual; ap; ap = ap->next)
1074     if (ap->expr
1075         && (expr = gfc_get_noncopying_intrinsic_argument (ap->expr))
1076         && !gfc_check_fncall_dependency (expr, INTENT_IN, fnsym, actual))
1077       ap->expr->inline_noncopying_intrinsic = 1;
1078 }
1079
1080 /* This function does the checking of references to global procedures
1081    as defined in sections 18.1 and 14.1, respectively, of the Fortran
1082    77 and 95 standards.  It checks for a gsymbol for the name, making
1083    one if it does not already exist.  If it already exists, then the
1084    reference being resolved must correspond to the type of gsymbol.
1085    Otherwise, the new symbol is equipped with the attributes of the 
1086    reference.  The corresponding code that is called in creating
1087    global entities is parse.c.  */
1088
1089 static void
1090 resolve_global_procedure (gfc_symbol *sym, locus *where, int sub)
1091 {
1092   gfc_gsymbol * gsym;
1093   unsigned int type;
1094
1095   type = sub ? GSYM_SUBROUTINE : GSYM_FUNCTION;
1096
1097   gsym = gfc_get_gsymbol (sym->name);
1098
1099   if ((gsym->type != GSYM_UNKNOWN && gsym->type != type))
1100     global_used (gsym, where);
1101
1102   if (gsym->type == GSYM_UNKNOWN)
1103     {
1104       gsym->type = type;
1105       gsym->where = *where;
1106     }
1107
1108   gsym->used = 1;
1109 }
1110
1111 /************* Function resolution *************/
1112
1113 /* Resolve a function call known to be generic.
1114    Section 14.1.2.4.1.  */
1115
1116 static match
1117 resolve_generic_f0 (gfc_expr * expr, gfc_symbol * sym)
1118 {
1119   gfc_symbol *s;
1120
1121   if (sym->attr.generic)
1122     {
1123       s =
1124         gfc_search_interface (sym->generic, 0, &expr->value.function.actual);
1125       if (s != NULL)
1126         {
1127           expr->value.function.name = s->name;
1128           expr->value.function.esym = s;
1129
1130           if (s->ts.type != BT_UNKNOWN)
1131             expr->ts = s->ts;
1132           else if (s->result != NULL && s->result->ts.type != BT_UNKNOWN)
1133             expr->ts = s->result->ts;
1134
1135           if (s->as != NULL)
1136             expr->rank = s->as->rank;
1137           else if (s->result != NULL && s->result->as != NULL)
1138             expr->rank = s->result->as->rank;
1139
1140           return MATCH_YES;
1141         }
1142
1143       /* TODO: Need to search for elemental references in generic interface */
1144     }
1145
1146   if (sym->attr.intrinsic)
1147     return gfc_intrinsic_func_interface (expr, 0);
1148
1149   return MATCH_NO;
1150 }
1151
1152
1153 static try
1154 resolve_generic_f (gfc_expr * expr)
1155 {
1156   gfc_symbol *sym;
1157   match m;
1158
1159   sym = expr->symtree->n.sym;
1160
1161   for (;;)
1162     {
1163       m = resolve_generic_f0 (expr, sym);
1164       if (m == MATCH_YES)
1165         return SUCCESS;
1166       else if (m == MATCH_ERROR)
1167         return FAILURE;
1168
1169 generic:
1170       if (sym->ns->parent == NULL)
1171         break;
1172       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
1173
1174       if (sym == NULL)
1175         break;
1176       if (!generic_sym (sym))
1177         goto generic;
1178     }
1179
1180   /* Last ditch attempt.  */
1181
1182   if (!gfc_generic_intrinsic (expr->symtree->n.sym->name))
1183     {
1184       gfc_error ("There is no specific function for the generic '%s' at %L",
1185                  expr->symtree->n.sym->name, &expr->where);
1186       return FAILURE;
1187     }
1188
1189   m = gfc_intrinsic_func_interface (expr, 0);
1190   if (m == MATCH_YES)
1191     return SUCCESS;
1192   if (m == MATCH_NO)
1193     gfc_error
1194       ("Generic function '%s' at %L is not consistent with a specific "
1195        "intrinsic interface", expr->symtree->n.sym->name, &expr->where);
1196
1197   return FAILURE;
1198 }
1199
1200
1201 /* Resolve a function call known to be specific.  */
1202
1203 static match
1204 resolve_specific_f0 (gfc_symbol * sym, gfc_expr * expr)
1205 {
1206   match m;
1207
1208   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
1209     {
1210       if (sym->attr.dummy)
1211         {
1212           sym->attr.proc = PROC_DUMMY;
1213           goto found;
1214         }
1215
1216       sym->attr.proc = PROC_EXTERNAL;
1217       goto found;
1218     }
1219
1220   if (sym->attr.proc == PROC_MODULE
1221       || sym->attr.proc == PROC_ST_FUNCTION
1222       || sym->attr.proc == PROC_INTERNAL)
1223     goto found;
1224
1225   if (sym->attr.intrinsic)
1226     {
1227       m = gfc_intrinsic_func_interface (expr, 1);
1228       if (m == MATCH_YES)
1229         return MATCH_YES;
1230       if (m == MATCH_NO)
1231         gfc_error
1232           ("Function '%s' at %L is INTRINSIC but is not compatible with "
1233            "an intrinsic", sym->name, &expr->where);
1234
1235       return MATCH_ERROR;
1236     }
1237
1238   return MATCH_NO;
1239
1240 found:
1241   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
1242
1243   expr->ts = sym->ts;
1244   expr->value.function.name = sym->name;
1245   expr->value.function.esym = sym;
1246   if (sym->as != NULL)
1247     expr->rank = sym->as->rank;
1248
1249   return MATCH_YES;
1250 }
1251
1252
1253 static try
1254 resolve_specific_f (gfc_expr * expr)
1255 {
1256   gfc_symbol *sym;
1257   match m;
1258
1259   sym = expr->symtree->n.sym;
1260
1261   for (;;)
1262     {
1263       m = resolve_specific_f0 (sym, expr);
1264       if (m == MATCH_YES)
1265         return SUCCESS;
1266       if (m == MATCH_ERROR)
1267         return FAILURE;
1268
1269       if (sym->ns->parent == NULL)
1270         break;
1271
1272       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
1273
1274       if (sym == NULL)
1275         break;
1276     }
1277
1278   gfc_error ("Unable to resolve the specific function '%s' at %L",
1279              expr->symtree->n.sym->name, &expr->where);
1280
1281   return SUCCESS;
1282 }
1283
1284
1285 /* Resolve a procedure call not known to be generic nor specific.  */
1286
1287 static try
1288 resolve_unknown_f (gfc_expr * expr)
1289 {
1290   gfc_symbol *sym;
1291   gfc_typespec *ts;
1292
1293   sym = expr->symtree->n.sym;
1294
1295   if (sym->attr.dummy)
1296     {
1297       sym->attr.proc = PROC_DUMMY;
1298       expr->value.function.name = sym->name;
1299       goto set_type;
1300     }
1301
1302   /* See if we have an intrinsic function reference.  */
1303
1304   if (gfc_intrinsic_name (sym->name, 0))
1305     {
1306       if (gfc_intrinsic_func_interface (expr, 1) == MATCH_YES)
1307         return SUCCESS;
1308       return FAILURE;
1309     }
1310
1311   /* The reference is to an external name.  */
1312
1313   sym->attr.proc = PROC_EXTERNAL;
1314   expr->value.function.name = sym->name;
1315   expr->value.function.esym = expr->symtree->n.sym;
1316
1317   if (sym->as != NULL)
1318     expr->rank = sym->as->rank;
1319
1320   /* Type of the expression is either the type of the symbol or the
1321      default type of the symbol.  */
1322
1323 set_type:
1324   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
1325
1326   if (sym->ts.type != BT_UNKNOWN)
1327     expr->ts = sym->ts;
1328   else
1329     {
1330       ts = gfc_get_default_type (sym, sym->ns);
1331
1332       if (ts->type == BT_UNKNOWN)
1333         {
1334           gfc_error ("Function '%s' at %L has no IMPLICIT type",
1335                      sym->name, &expr->where);
1336           return FAILURE;
1337         }
1338       else
1339         expr->ts = *ts;
1340     }
1341
1342   return SUCCESS;
1343 }
1344
1345
1346 /* Figure out if a function reference is pure or not.  Also set the name
1347    of the function for a potential error message.  Return nonzero if the
1348    function is PURE, zero if not.  */
1349
1350 static int
1351 pure_function (gfc_expr * e, const char **name)
1352 {
1353   int pure;
1354
1355   if (e->value.function.esym)
1356     {
1357       pure = gfc_pure (e->value.function.esym);
1358       *name = e->value.function.esym->name;
1359     }
1360   else if (e->value.function.isym)
1361     {
1362       pure = e->value.function.isym->pure
1363         || e->value.function.isym->elemental;
1364       *name = e->value.function.isym->name;
1365     }
1366   else
1367     {
1368       /* Implicit functions are not pure.  */
1369       pure = 0;
1370       *name = e->value.function.name;
1371     }
1372
1373   return pure;
1374 }
1375
1376
1377 /* Resolve a function call, which means resolving the arguments, then figuring
1378    out which entity the name refers to.  */
1379 /* TODO: Check procedure arguments so that an INTENT(IN) isn't passed
1380    to INTENT(OUT) or INTENT(INOUT).  */
1381
1382 static try
1383 resolve_function (gfc_expr * expr)
1384 {
1385   gfc_actual_arglist *arg;
1386   gfc_symbol * sym;
1387   const char *name;
1388   try t;
1389   int temp;
1390
1391   sym = NULL;
1392   if (expr->symtree)
1393     sym = expr->symtree->n.sym;
1394
1395   /* If the procedure is not internal, a statement function or a module
1396      procedure,it must be external and should be checked for usage.  */
1397   if (sym && !sym->attr.dummy && !sym->attr.contained
1398         && sym->attr.proc != PROC_ST_FUNCTION
1399         && !sym->attr.use_assoc)
1400     resolve_global_procedure (sym, &expr->where, 0);
1401
1402   /* Switch off assumed size checking and do this again for certain kinds
1403      of procedure, once the procedure itself is resolved.  */
1404   need_full_assumed_size++;
1405
1406   if (resolve_actual_arglist (expr->value.function.actual) == FAILURE)
1407     return FAILURE;
1408
1409   /* Resume assumed_size checking. */
1410   need_full_assumed_size--;
1411
1412   if (sym && sym->ts.type == BT_CHARACTER
1413         && sym->ts.cl
1414         && sym->ts.cl->length == NULL
1415         && !sym->attr.dummy
1416         && !sym->attr.contained)
1417     {
1418       /* Internal procedures are taken care of in resolve_contained_fntype.  */
1419       gfc_error ("Function '%s' is declared CHARACTER(*) and cannot "
1420                  "be used at %L since it is not a dummy argument",
1421                  sym->name, &expr->where);
1422       return FAILURE;
1423     }
1424
1425 /* See if function is already resolved.  */
1426
1427   if (expr->value.function.name != NULL)
1428     {
1429       if (expr->ts.type == BT_UNKNOWN)
1430         expr->ts = sym->ts;
1431       t = SUCCESS;
1432     }
1433   else
1434     {
1435       /* Apply the rules of section 14.1.2.  */
1436
1437       switch (procedure_kind (sym))
1438         {
1439         case PTYPE_GENERIC:
1440           t = resolve_generic_f (expr);
1441           break;
1442
1443         case PTYPE_SPECIFIC:
1444           t = resolve_specific_f (expr);
1445           break;
1446
1447         case PTYPE_UNKNOWN:
1448           t = resolve_unknown_f (expr);
1449           break;
1450
1451         default:
1452           gfc_internal_error ("resolve_function(): bad function type");
1453         }
1454     }
1455
1456   /* If the expression is still a function (it might have simplified),
1457      then we check to see if we are calling an elemental function.  */
1458
1459   if (expr->expr_type != EXPR_FUNCTION)
1460     return t;
1461
1462   temp = need_full_assumed_size;
1463   need_full_assumed_size = 0;
1464
1465   if (resolve_elemental_actual (expr, NULL) == FAILURE)
1466     return FAILURE;
1467
1468   if (omp_workshare_flag
1469       && expr->value.function.esym
1470       && ! gfc_elemental (expr->value.function.esym))
1471     {
1472       gfc_error ("User defined non-ELEMENTAL function '%s' at %L not allowed"
1473                  " in WORKSHARE construct", expr->value.function.esym->name,
1474                  &expr->where);
1475       t = FAILURE;
1476     }
1477
1478   else if (expr->value.function.actual != NULL
1479              && expr->value.function.isym != NULL
1480              && expr->value.function.isym->generic_id != GFC_ISYM_LBOUND
1481              && expr->value.function.isym->generic_id != GFC_ISYM_LOC
1482              && expr->value.function.isym->generic_id != GFC_ISYM_PRESENT)
1483     {
1484       /* Array instrinsics must also have the last upper bound of an
1485          assumed size array argument.  UBOUND and SIZE have to be
1486          excluded from the check if the second argument is anything
1487          than a constant.  */
1488       int inquiry;
1489       inquiry = expr->value.function.isym->generic_id == GFC_ISYM_UBOUND
1490                   || expr->value.function.isym->generic_id == GFC_ISYM_SIZE;
1491             
1492       for (arg = expr->value.function.actual; arg; arg = arg->next)
1493         {
1494           if (inquiry && arg->next != NULL && arg->next->expr
1495                 && arg->next->expr->expr_type != EXPR_CONSTANT)
1496             break;
1497           
1498           if (arg->expr != NULL
1499                 && arg->expr->rank > 0
1500                 && resolve_assumed_size_actual (arg->expr))
1501             return FAILURE;
1502         }
1503     }
1504
1505   need_full_assumed_size = temp;
1506
1507   if (!pure_function (expr, &name) && name)
1508     {
1509       if (forall_flag)
1510         {
1511           gfc_error
1512             ("reference to non-PURE function '%s' at %L inside a "
1513              "FORALL %s", name, &expr->where, forall_flag == 2 ?
1514              "mask" : "block");
1515           t = FAILURE;
1516         }
1517       else if (gfc_pure (NULL))
1518         {
1519           gfc_error ("Function reference to '%s' at %L is to a non-PURE "
1520                      "procedure within a PURE procedure", name, &expr->where);
1521           t = FAILURE;
1522         }
1523     }
1524
1525   /* Functions without the RECURSIVE attribution are not allowed to
1526    * call themselves.  */
1527   if (expr->value.function.esym && !expr->value.function.esym->attr.recursive)
1528     {
1529       gfc_symbol *esym, *proc;
1530       esym = expr->value.function.esym;
1531       proc = gfc_current_ns->proc_name;
1532       if (esym == proc)
1533       {
1534         gfc_error ("Function '%s' at %L cannot call itself, as it is not "
1535                    "RECURSIVE", name, &expr->where);
1536         t = FAILURE;
1537       }
1538
1539       if (esym->attr.entry && esym->ns->entries && proc->ns->entries
1540           && esym->ns->entries->sym == proc->ns->entries->sym)
1541       {
1542         gfc_error ("Call to ENTRY '%s' at %L is recursive, but function "
1543                    "'%s' is not declared as RECURSIVE",
1544                    esym->name, &expr->where, esym->ns->entries->sym->name);
1545         t = FAILURE;
1546       }
1547     }
1548
1549   /* Character lengths of use associated functions may contains references to
1550      symbols not referenced from the current program unit otherwise.  Make sure
1551      those symbols are marked as referenced.  */
1552
1553   if (expr->ts.type == BT_CHARACTER && expr->value.function.esym 
1554       && expr->value.function.esym->attr.use_assoc)
1555     {
1556       gfc_expr_set_symbols_referenced (expr->ts.cl->length);
1557     }
1558
1559   if (t == SUCCESS)
1560     find_noncopying_intrinsics (expr->value.function.esym,
1561                                 expr->value.function.actual);
1562   return t;
1563 }
1564
1565
1566 /************* Subroutine resolution *************/
1567
1568 static void
1569 pure_subroutine (gfc_code * c, gfc_symbol * sym)
1570 {
1571
1572   if (gfc_pure (sym))
1573     return;
1574
1575   if (forall_flag)
1576     gfc_error ("Subroutine call to '%s' in FORALL block at %L is not PURE",
1577                sym->name, &c->loc);
1578   else if (gfc_pure (NULL))
1579     gfc_error ("Subroutine call to '%s' at %L is not PURE", sym->name,
1580                &c->loc);
1581 }
1582
1583
1584 static match
1585 resolve_generic_s0 (gfc_code * c, gfc_symbol * sym)
1586 {
1587   gfc_symbol *s;
1588
1589   if (sym->attr.generic)
1590     {
1591       s = gfc_search_interface (sym->generic, 1, &c->ext.actual);
1592       if (s != NULL)
1593         {
1594           c->resolved_sym = s;
1595           pure_subroutine (c, s);
1596           return MATCH_YES;
1597         }
1598
1599       /* TODO: Need to search for elemental references in generic interface.  */
1600     }
1601
1602   if (sym->attr.intrinsic)
1603     return gfc_intrinsic_sub_interface (c, 0);
1604
1605   return MATCH_NO;
1606 }
1607
1608
1609 static try
1610 resolve_generic_s (gfc_code * c)
1611 {
1612   gfc_symbol *sym;
1613   match m;
1614
1615   sym = c->symtree->n.sym;
1616
1617   for (;;)
1618     {
1619       m = resolve_generic_s0 (c, sym);
1620       if (m == MATCH_YES)
1621         return SUCCESS;
1622       else if (m == MATCH_ERROR)
1623         return FAILURE;
1624
1625 generic:
1626       if (sym->ns->parent == NULL)
1627         break;
1628       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
1629
1630       if (sym == NULL)
1631         break;
1632       if (!generic_sym (sym))
1633         goto generic;
1634     }
1635
1636   /* Last ditch attempt.  */
1637   sym = c->symtree->n.sym;
1638   if (!gfc_generic_intrinsic (sym->name))
1639     {
1640       gfc_error
1641         ("There is no specific subroutine for the generic '%s' at %L",
1642          sym->name, &c->loc);
1643       return FAILURE;
1644     }
1645
1646   m = gfc_intrinsic_sub_interface (c, 0);
1647   if (m == MATCH_YES)
1648     return SUCCESS;
1649   if (m == MATCH_NO)
1650     gfc_error ("Generic subroutine '%s' at %L is not consistent with an "
1651                "intrinsic subroutine interface", sym->name, &c->loc);
1652
1653   return FAILURE;
1654 }
1655
1656
1657 /* Resolve a subroutine call known to be specific.  */
1658
1659 static match
1660 resolve_specific_s0 (gfc_code * c, gfc_symbol * sym)
1661 {
1662   match m;
1663
1664   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
1665     {
1666       if (sym->attr.dummy)
1667         {
1668           sym->attr.proc = PROC_DUMMY;
1669           goto found;
1670         }
1671
1672       sym->attr.proc = PROC_EXTERNAL;
1673       goto found;
1674     }
1675
1676   if (sym->attr.proc == PROC_MODULE || sym->attr.proc == PROC_INTERNAL)
1677     goto found;
1678
1679   if (sym->attr.intrinsic)
1680     {
1681       m = gfc_intrinsic_sub_interface (c, 1);
1682       if (m == MATCH_YES)
1683         return MATCH_YES;
1684       if (m == MATCH_NO)
1685         gfc_error ("Subroutine '%s' at %L is INTRINSIC but is not compatible "
1686                    "with an intrinsic", sym->name, &c->loc);
1687
1688       return MATCH_ERROR;
1689     }
1690
1691   return MATCH_NO;
1692
1693 found:
1694   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
1695
1696   c->resolved_sym = sym;
1697   pure_subroutine (c, sym);
1698
1699   return MATCH_YES;
1700 }
1701
1702
1703 static try
1704 resolve_specific_s (gfc_code * c)
1705 {
1706   gfc_symbol *sym;
1707   match m;
1708
1709   sym = c->symtree->n.sym;
1710
1711   for (;;)
1712     {
1713       m = resolve_specific_s0 (c, sym);
1714       if (m == MATCH_YES)
1715         return SUCCESS;
1716       if (m == MATCH_ERROR)
1717         return FAILURE;
1718
1719       if (sym->ns->parent == NULL)
1720         break;
1721
1722       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
1723
1724       if (sym == NULL)
1725         break;
1726     }
1727
1728   sym = c->symtree->n.sym;
1729   gfc_error ("Unable to resolve the specific subroutine '%s' at %L",
1730              sym->name, &c->loc);
1731
1732   return FAILURE;
1733 }
1734
1735
1736 /* Resolve a subroutine call not known to be generic nor specific.  */
1737
1738 static try
1739 resolve_unknown_s (gfc_code * c)
1740 {
1741   gfc_symbol *sym;
1742
1743   sym = c->symtree->n.sym;
1744
1745   if (sym->attr.dummy)
1746     {
1747       sym->attr.proc = PROC_DUMMY;
1748       goto found;
1749     }
1750
1751   /* See if we have an intrinsic function reference.  */
1752
1753   if (gfc_intrinsic_name (sym->name, 1))
1754     {
1755       if (gfc_intrinsic_sub_interface (c, 1) == MATCH_YES)
1756         return SUCCESS;
1757       return FAILURE;
1758     }
1759
1760   /* The reference is to an external name.  */
1761
1762 found:
1763   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
1764
1765   c->resolved_sym = sym;
1766
1767   pure_subroutine (c, sym);
1768
1769   return SUCCESS;
1770 }
1771
1772
1773 /* Resolve a subroutine call.  Although it was tempting to use the same code
1774    for functions, subroutines and functions are stored differently and this
1775    makes things awkward.  */
1776
1777 static try
1778 resolve_call (gfc_code * c)
1779 {
1780   try t;
1781
1782   if (c->symtree && c->symtree->n.sym
1783         && c->symtree->n.sym->ts.type != BT_UNKNOWN)
1784     {
1785       gfc_error ("'%s' at %L has a type, which is not consistent with "
1786                  "the CALL at %L", c->symtree->n.sym->name,
1787                  &c->symtree->n.sym->declared_at, &c->loc);
1788       return FAILURE;
1789     }
1790
1791   /* If the procedure is not internal or module, it must be external and
1792      should be checked for usage.  */
1793   if (c->symtree && c->symtree->n.sym
1794         && !c->symtree->n.sym->attr.dummy
1795         && !c->symtree->n.sym->attr.contained
1796         && !c->symtree->n.sym->attr.use_assoc)
1797     resolve_global_procedure (c->symtree->n.sym, &c->loc, 1);
1798
1799   /* Subroutines without the RECURSIVE attribution are not allowed to
1800    * call themselves.  */
1801   if (c->symtree && c->symtree->n.sym && !c->symtree->n.sym->attr.recursive)
1802     {
1803       gfc_symbol *csym, *proc;
1804       csym = c->symtree->n.sym;
1805       proc = gfc_current_ns->proc_name;
1806       if (csym == proc)
1807       {
1808         gfc_error ("SUBROUTINE '%s' at %L cannot call itself, as it is not "
1809                    "RECURSIVE", csym->name, &c->loc);
1810         t = FAILURE;
1811       }
1812
1813       if (csym->attr.entry && csym->ns->entries && proc->ns->entries
1814           && csym->ns->entries->sym == proc->ns->entries->sym)
1815       {
1816         gfc_error ("Call to ENTRY '%s' at %L is recursive, but subroutine "
1817                    "'%s' is not declared as RECURSIVE",
1818                    csym->name, &c->loc, csym->ns->entries->sym->name);
1819         t = FAILURE;
1820       }
1821     }
1822
1823   /* Switch off assumed size checking and do this again for certain kinds
1824      of procedure, once the procedure itself is resolved.  */
1825   need_full_assumed_size++;
1826
1827   if (resolve_actual_arglist (c->ext.actual) == FAILURE)
1828     return FAILURE;
1829
1830   /* Resume assumed_size checking. */
1831   need_full_assumed_size--;
1832
1833
1834   t = SUCCESS;
1835   if (c->resolved_sym == NULL)
1836     switch (procedure_kind (c->symtree->n.sym))
1837       {
1838       case PTYPE_GENERIC:
1839         t = resolve_generic_s (c);
1840         break;
1841
1842       case PTYPE_SPECIFIC:
1843         t = resolve_specific_s (c);
1844         break;
1845
1846       case PTYPE_UNKNOWN:
1847         t = resolve_unknown_s (c);
1848         break;
1849
1850       default:
1851         gfc_internal_error ("resolve_subroutine(): bad function type");
1852       }
1853
1854   /* Some checks of elemental subroutine actual arguments.  */
1855   if (resolve_elemental_actual (NULL, c) == FAILURE)
1856     return FAILURE;
1857
1858   if (t == SUCCESS)
1859     find_noncopying_intrinsics (c->resolved_sym, c->ext.actual);
1860   return t;
1861 }
1862
1863 /* Compare the shapes of two arrays that have non-NULL shapes.  If both
1864    op1->shape and op2->shape are non-NULL return SUCCESS if their shapes
1865    match.  If both op1->shape and op2->shape are non-NULL return FAILURE
1866    if their shapes do not match.  If either op1->shape or op2->shape is
1867    NULL, return SUCCESS.  */
1868
1869 static try
1870 compare_shapes (gfc_expr * op1, gfc_expr * op2)
1871 {
1872   try t;
1873   int i;
1874
1875   t = SUCCESS;
1876                   
1877   if (op1->shape != NULL && op2->shape != NULL)
1878     {
1879       for (i = 0; i < op1->rank; i++)
1880         {
1881           if (mpz_cmp (op1->shape[i], op2->shape[i]) != 0)
1882            {
1883              gfc_error ("Shapes for operands at %L and %L are not conformable",
1884                          &op1->where, &op2->where);
1885              t = FAILURE;
1886              break;
1887            }
1888         }
1889     }
1890
1891   return t;
1892 }
1893
1894 /* Resolve an operator expression node.  This can involve replacing the
1895    operation with a user defined function call.  */
1896
1897 static try
1898 resolve_operator (gfc_expr * e)
1899 {
1900   gfc_expr *op1, *op2;
1901   char msg[200];
1902   try t;
1903
1904   /* Resolve all subnodes-- give them types.  */
1905
1906   switch (e->value.op.operator)
1907     {
1908     default:
1909       if (gfc_resolve_expr (e->value.op.op2) == FAILURE)
1910         return FAILURE;
1911
1912     /* Fall through...  */
1913
1914     case INTRINSIC_NOT:
1915     case INTRINSIC_UPLUS:
1916     case INTRINSIC_UMINUS:
1917     case INTRINSIC_PARENTHESES:
1918       if (gfc_resolve_expr (e->value.op.op1) == FAILURE)
1919         return FAILURE;
1920       break;
1921     }
1922
1923   /* Typecheck the new node.  */
1924
1925   op1 = e->value.op.op1;
1926   op2 = e->value.op.op2;
1927
1928   switch (e->value.op.operator)
1929     {
1930     case INTRINSIC_UPLUS:
1931     case INTRINSIC_UMINUS:
1932       if (op1->ts.type == BT_INTEGER
1933           || op1->ts.type == BT_REAL
1934           || op1->ts.type == BT_COMPLEX)
1935         {
1936           e->ts = op1->ts;
1937           break;
1938         }
1939
1940       sprintf (msg, _("Operand of unary numeric operator '%s' at %%L is %s"),
1941                gfc_op2string (e->value.op.operator), gfc_typename (&e->ts));
1942       goto bad_op;
1943
1944     case INTRINSIC_PLUS:
1945     case INTRINSIC_MINUS:
1946     case INTRINSIC_TIMES:
1947     case INTRINSIC_DIVIDE:
1948     case INTRINSIC_POWER:
1949       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
1950         {
1951           gfc_type_convert_binary (e);
1952           break;
1953         }
1954
1955       sprintf (msg,
1956                _("Operands of binary numeric operator '%s' at %%L are %s/%s"),
1957                gfc_op2string (e->value.op.operator), gfc_typename (&op1->ts),
1958                gfc_typename (&op2->ts));
1959       goto bad_op;
1960
1961     case INTRINSIC_CONCAT:
1962       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER)
1963         {
1964           e->ts.type = BT_CHARACTER;
1965           e->ts.kind = op1->ts.kind;
1966           break;
1967         }
1968
1969       sprintf (msg,
1970                _("Operands of string concatenation operator at %%L are %s/%s"),
1971                gfc_typename (&op1->ts), gfc_typename (&op2->ts));
1972       goto bad_op;
1973
1974     case INTRINSIC_AND:
1975     case INTRINSIC_OR:
1976     case INTRINSIC_EQV:
1977     case INTRINSIC_NEQV:
1978       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
1979         {
1980           e->ts.type = BT_LOGICAL;
1981           e->ts.kind = gfc_kind_max (op1, op2);
1982           if (op1->ts.kind < e->ts.kind)
1983             gfc_convert_type (op1, &e->ts, 2);
1984           else if (op2->ts.kind < e->ts.kind)
1985             gfc_convert_type (op2, &e->ts, 2);
1986           break;
1987         }
1988
1989       sprintf (msg, _("Operands of logical operator '%s' at %%L are %s/%s"),
1990                gfc_op2string (e->value.op.operator), gfc_typename (&op1->ts),
1991                gfc_typename (&op2->ts));
1992
1993       goto bad_op;
1994
1995     case INTRINSIC_NOT:
1996       if (op1->ts.type == BT_LOGICAL)
1997         {
1998           e->ts.type = BT_LOGICAL;
1999           e->ts.kind = op1->ts.kind;
2000           break;
2001         }
2002
2003       sprintf (msg, _("Operand of .NOT. operator at %%L is %s"),
2004                gfc_typename (&op1->ts));
2005       goto bad_op;
2006
2007     case INTRINSIC_GT:
2008     case INTRINSIC_GE:
2009     case INTRINSIC_LT:
2010     case INTRINSIC_LE:
2011       if (op1->ts.type == BT_COMPLEX || op2->ts.type == BT_COMPLEX)
2012         {
2013           strcpy (msg, _("COMPLEX quantities cannot be compared at %L"));
2014           goto bad_op;
2015         }
2016
2017       /* Fall through...  */
2018
2019     case INTRINSIC_EQ:
2020     case INTRINSIC_NE:
2021       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER)
2022         {
2023           e->ts.type = BT_LOGICAL;
2024           e->ts.kind = gfc_default_logical_kind;
2025           break;
2026         }
2027
2028       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
2029         {
2030           gfc_type_convert_binary (e);
2031
2032           e->ts.type = BT_LOGICAL;
2033           e->ts.kind = gfc_default_logical_kind;
2034           break;
2035         }
2036
2037       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
2038         sprintf (msg,
2039                  _("Logicals at %%L must be compared with %s instead of %s"),
2040                  e->value.op.operator == INTRINSIC_EQ ? ".EQV." : ".NEQV.",
2041                  gfc_op2string (e->value.op.operator));
2042       else
2043         sprintf (msg,
2044                  _("Operands of comparison operator '%s' at %%L are %s/%s"),
2045                  gfc_op2string (e->value.op.operator), gfc_typename (&op1->ts),
2046                  gfc_typename (&op2->ts));
2047
2048       goto bad_op;
2049
2050     case INTRINSIC_USER:
2051       if (op2 == NULL)
2052         sprintf (msg, _("Operand of user operator '%s' at %%L is %s"),
2053                  e->value.op.uop->name, gfc_typename (&op1->ts));
2054       else
2055         sprintf (msg, _("Operands of user operator '%s' at %%L are %s/%s"),
2056                  e->value.op.uop->name, gfc_typename (&op1->ts),
2057                  gfc_typename (&op2->ts));
2058
2059       goto bad_op;
2060
2061     case INTRINSIC_PARENTHESES:
2062       break;
2063
2064     default:
2065       gfc_internal_error ("resolve_operator(): Bad intrinsic");
2066     }
2067
2068   /* Deal with arrayness of an operand through an operator.  */
2069
2070   t = SUCCESS;
2071
2072   switch (e->value.op.operator)
2073     {
2074     case INTRINSIC_PLUS:
2075     case INTRINSIC_MINUS:
2076     case INTRINSIC_TIMES:
2077     case INTRINSIC_DIVIDE:
2078     case INTRINSIC_POWER:
2079     case INTRINSIC_CONCAT:
2080     case INTRINSIC_AND:
2081     case INTRINSIC_OR:
2082     case INTRINSIC_EQV:
2083     case INTRINSIC_NEQV:
2084     case INTRINSIC_EQ:
2085     case INTRINSIC_NE:
2086     case INTRINSIC_GT:
2087     case INTRINSIC_GE:
2088     case INTRINSIC_LT:
2089     case INTRINSIC_LE:
2090
2091       if (op1->rank == 0 && op2->rank == 0)
2092         e->rank = 0;
2093
2094       if (op1->rank == 0 && op2->rank != 0)
2095         {
2096           e->rank = op2->rank;
2097
2098           if (e->shape == NULL)
2099             e->shape = gfc_copy_shape (op2->shape, op2->rank);
2100         }
2101
2102       if (op1->rank != 0 && op2->rank == 0)
2103         {
2104           e->rank = op1->rank;
2105
2106           if (e->shape == NULL)
2107             e->shape = gfc_copy_shape (op1->shape, op1->rank);
2108         }
2109
2110       if (op1->rank != 0 && op2->rank != 0)
2111         {
2112           if (op1->rank == op2->rank)
2113             {
2114               e->rank = op1->rank;
2115               if (e->shape == NULL)
2116                 {
2117                   t = compare_shapes(op1, op2);
2118                   if (t == FAILURE)
2119                     e->shape = NULL;
2120                   else
2121                 e->shape = gfc_copy_shape (op1->shape, op1->rank);
2122                 }
2123             }
2124           else
2125             {
2126               gfc_error ("Inconsistent ranks for operator at %L and %L",
2127                          &op1->where, &op2->where);
2128               t = FAILURE;
2129
2130               /* Allow higher level expressions to work.  */
2131               e->rank = 0;
2132             }
2133         }
2134
2135       break;
2136
2137     case INTRINSIC_NOT:
2138     case INTRINSIC_UPLUS:
2139     case INTRINSIC_UMINUS:
2140     case INTRINSIC_PARENTHESES:
2141       e->rank = op1->rank;
2142
2143       if (e->shape == NULL)
2144         e->shape = gfc_copy_shape (op1->shape, op1->rank);
2145
2146       /* Simply copy arrayness attribute */
2147       break;
2148
2149     default:
2150       break;
2151     }
2152
2153   /* Attempt to simplify the expression.  */
2154   if (t == SUCCESS)
2155     t = gfc_simplify_expr (e, 0);
2156   return t;
2157
2158 bad_op:
2159
2160   if (gfc_extend_expr (e) == SUCCESS)
2161     return SUCCESS;
2162
2163   gfc_error (msg, &e->where);
2164
2165   return FAILURE;
2166 }
2167
2168
2169 /************** Array resolution subroutines **************/
2170
2171
2172 typedef enum
2173 { CMP_LT, CMP_EQ, CMP_GT, CMP_UNKNOWN }
2174 comparison;
2175
2176 /* Compare two integer expressions.  */
2177
2178 static comparison
2179 compare_bound (gfc_expr * a, gfc_expr * b)
2180 {
2181   int i;
2182
2183   if (a == NULL || a->expr_type != EXPR_CONSTANT
2184       || b == NULL || b->expr_type != EXPR_CONSTANT)
2185     return CMP_UNKNOWN;
2186
2187   if (a->ts.type != BT_INTEGER || b->ts.type != BT_INTEGER)
2188     gfc_internal_error ("compare_bound(): Bad expression");
2189
2190   i = mpz_cmp (a->value.integer, b->value.integer);
2191
2192   if (i < 0)
2193     return CMP_LT;
2194   if (i > 0)
2195     return CMP_GT;
2196   return CMP_EQ;
2197 }
2198
2199
2200 /* Compare an integer expression with an integer.  */
2201
2202 static comparison
2203 compare_bound_int (gfc_expr * a, int b)
2204 {
2205   int i;
2206
2207   if (a == NULL || a->expr_type != EXPR_CONSTANT)
2208     return CMP_UNKNOWN;
2209
2210   if (a->ts.type != BT_INTEGER)
2211     gfc_internal_error ("compare_bound_int(): Bad expression");
2212
2213   i = mpz_cmp_si (a->value.integer, b);
2214
2215   if (i < 0)
2216     return CMP_LT;
2217   if (i > 0)
2218     return CMP_GT;
2219   return CMP_EQ;
2220 }
2221
2222
2223 /* Compare an integer expression with a mpz_t.  */
2224
2225 static comparison
2226 compare_bound_mpz_t (gfc_expr * a, mpz_t b)
2227 {
2228   int i;
2229
2230   if (a == NULL || a->expr_type != EXPR_CONSTANT)
2231     return CMP_UNKNOWN;
2232
2233   if (a->ts.type != BT_INTEGER)
2234     gfc_internal_error ("compare_bound_int(): Bad expression");
2235
2236   i = mpz_cmp (a->value.integer, b);
2237
2238   if (i < 0)
2239     return CMP_LT;
2240   if (i > 0)
2241     return CMP_GT;
2242   return CMP_EQ;
2243 }
2244
2245
2246 /* Compute the last value of a sequence given by a triplet.  
2247    Return 0 if it wasn't able to compute the last value, or if the
2248    sequence if empty, and 1 otherwise.  */
2249
2250 static int
2251 compute_last_value_for_triplet (gfc_expr * start, gfc_expr * end,
2252                                 gfc_expr * stride, mpz_t last)
2253 {
2254   mpz_t rem;
2255
2256   if (start == NULL || start->expr_type != EXPR_CONSTANT
2257       || end == NULL || end->expr_type != EXPR_CONSTANT
2258       || (stride != NULL && stride->expr_type != EXPR_CONSTANT))
2259     return 0;
2260
2261   if (start->ts.type != BT_INTEGER || end->ts.type != BT_INTEGER
2262       || (stride != NULL && stride->ts.type != BT_INTEGER))
2263     return 0;
2264
2265   if (stride == NULL || compare_bound_int(stride, 1) == CMP_EQ)
2266     {
2267       if (compare_bound (start, end) == CMP_GT)
2268         return 0;
2269       mpz_set (last, end->value.integer);
2270       return 1;
2271     }
2272   
2273   if (compare_bound_int (stride, 0) == CMP_GT)
2274     {
2275       /* Stride is positive */
2276       if (mpz_cmp (start->value.integer, end->value.integer) > 0)
2277         return 0;
2278     }
2279   else
2280     {
2281       /* Stride is negative */
2282       if (mpz_cmp (start->value.integer, end->value.integer) < 0)
2283         return 0;
2284     }
2285
2286   mpz_init (rem);
2287   mpz_sub (rem, end->value.integer, start->value.integer);
2288   mpz_tdiv_r (rem, rem, stride->value.integer);
2289   mpz_sub (last, end->value.integer, rem);
2290   mpz_clear (rem);
2291
2292   return 1;
2293 }
2294
2295
2296 /* Compare a single dimension of an array reference to the array
2297    specification.  */
2298
2299 static try
2300 check_dimension (int i, gfc_array_ref * ar, gfc_array_spec * as)
2301 {
2302   mpz_t last_value;
2303
2304 /* Given start, end and stride values, calculate the minimum and
2305    maximum referenced indexes.  */
2306
2307   switch (ar->type)
2308     {
2309     case AR_FULL:
2310       break;
2311
2312     case AR_ELEMENT:
2313       if (compare_bound (ar->start[i], as->lower[i]) == CMP_LT)
2314         goto bound;
2315       if (compare_bound (ar->start[i], as->upper[i]) == CMP_GT)
2316         goto bound;
2317
2318       break;
2319
2320     case AR_SECTION:
2321       if (compare_bound_int (ar->stride[i], 0) == CMP_EQ)
2322         {
2323           gfc_error ("Illegal stride of zero at %L", &ar->c_where[i]);
2324           return FAILURE;
2325         }
2326
2327 #define AR_START (ar->start[i] ? ar->start[i] : as->lower[i])
2328 #define AR_END (ar->end[i] ? ar->end[i] : as->upper[i])
2329
2330       if (compare_bound (AR_START, AR_END) == CMP_EQ
2331           && (compare_bound (AR_START, as->lower[i]) == CMP_LT
2332               || compare_bound (AR_START, as->upper[i]) == CMP_GT))
2333         goto bound;
2334
2335       if (((compare_bound_int (ar->stride[i], 0) == CMP_GT
2336             || ar->stride[i] == NULL)
2337            && compare_bound (AR_START, AR_END) != CMP_GT)
2338           || (compare_bound_int (ar->stride[i], 0) == CMP_LT
2339               && compare_bound (AR_START, AR_END) != CMP_LT))
2340         {
2341           if (compare_bound (AR_START, as->lower[i]) == CMP_LT)
2342             goto bound;
2343           if (compare_bound (AR_START, as->upper[i]) == CMP_GT)
2344             goto bound;
2345         }
2346
2347       mpz_init (last_value);
2348       if (compute_last_value_for_triplet (AR_START, AR_END, ar->stride[i],
2349                                           last_value))
2350         {
2351           if (compare_bound_mpz_t (as->lower[i], last_value) == CMP_GT
2352               || compare_bound_mpz_t (as->upper[i], last_value) == CMP_LT)
2353             {
2354               mpz_clear (last_value);
2355               goto bound;
2356             }
2357         }
2358       mpz_clear (last_value);
2359
2360 #undef AR_START
2361 #undef AR_END
2362
2363       break;
2364
2365     default:
2366       gfc_internal_error ("check_dimension(): Bad array reference");
2367     }
2368
2369   return SUCCESS;
2370
2371 bound:
2372   gfc_warning ("Array reference at %L is out of bounds", &ar->c_where[i]);
2373   return SUCCESS;
2374 }
2375
2376
2377 /* Compare an array reference with an array specification.  */
2378
2379 static try
2380 compare_spec_to_ref (gfc_array_ref * ar)
2381 {
2382   gfc_array_spec *as;
2383   int i;
2384
2385   as = ar->as;
2386   i = as->rank - 1;
2387   /* TODO: Full array sections are only allowed as actual parameters.  */
2388   if (as->type == AS_ASSUMED_SIZE
2389       && (/*ar->type == AR_FULL
2390           ||*/ (ar->type == AR_SECTION
2391               && ar->dimen_type[i] == DIMEN_RANGE && ar->end[i] == NULL)))
2392     {
2393       gfc_error ("Rightmost upper bound of assumed size array section"
2394                  " not specified at %L", &ar->where);
2395       return FAILURE;
2396     }
2397
2398   if (ar->type == AR_FULL)
2399     return SUCCESS;
2400
2401   if (as->rank != ar->dimen)
2402     {
2403       gfc_error ("Rank mismatch in array reference at %L (%d/%d)",
2404                  &ar->where, ar->dimen, as->rank);
2405       return FAILURE;
2406     }
2407
2408   for (i = 0; i < as->rank; i++)
2409     if (check_dimension (i, ar, as) == FAILURE)
2410       return FAILURE;
2411
2412   return SUCCESS;
2413 }
2414
2415
2416 /* Resolve one part of an array index.  */
2417
2418 try
2419 gfc_resolve_index (gfc_expr * index, int check_scalar)
2420 {
2421   gfc_typespec ts;
2422
2423   if (index == NULL)
2424     return SUCCESS;
2425
2426   if (gfc_resolve_expr (index) == FAILURE)
2427     return FAILURE;
2428
2429   if (check_scalar && index->rank != 0)
2430     {
2431       gfc_error ("Array index at %L must be scalar", &index->where);
2432       return FAILURE;
2433     }
2434
2435   if (index->ts.type != BT_INTEGER && index->ts.type != BT_REAL)
2436     {
2437       gfc_error ("Array index at %L must be of INTEGER type",
2438                  &index->where);
2439       return FAILURE;
2440     }
2441
2442   if (index->ts.type == BT_REAL)
2443     if (gfc_notify_std (GFC_STD_LEGACY, "Extension: REAL array index at %L",
2444                         &index->where) == FAILURE)
2445       return FAILURE;
2446
2447   if (index->ts.kind != gfc_index_integer_kind
2448       || index->ts.type != BT_INTEGER)
2449     {
2450       gfc_clear_ts (&ts);
2451       ts.type = BT_INTEGER;
2452       ts.kind = gfc_index_integer_kind;
2453
2454       gfc_convert_type_warn (index, &ts, 2, 0);
2455     }
2456
2457   return SUCCESS;
2458 }
2459
2460 /* Resolve a dim argument to an intrinsic function.  */
2461
2462 try
2463 gfc_resolve_dim_arg (gfc_expr *dim)
2464 {
2465   if (dim == NULL)
2466     return SUCCESS;
2467
2468   if (gfc_resolve_expr (dim) == FAILURE)
2469     return FAILURE;
2470
2471   if (dim->rank != 0)
2472     {
2473       gfc_error ("Argument dim at %L must be scalar", &dim->where);
2474       return FAILURE;
2475   
2476     }
2477   if (dim->ts.type != BT_INTEGER)
2478     {
2479       gfc_error ("Argument dim at %L must be of INTEGER type", &dim->where);
2480       return FAILURE;
2481     }
2482   if (dim->ts.kind != gfc_index_integer_kind)
2483     {
2484       gfc_typespec ts;
2485
2486       ts.type = BT_INTEGER;
2487       ts.kind = gfc_index_integer_kind;
2488
2489       gfc_convert_type_warn (dim, &ts, 2, 0);
2490     }
2491
2492   return SUCCESS;
2493 }
2494
2495 /* Given an expression that contains array references, update those array
2496    references to point to the right array specifications.  While this is
2497    filled in during matching, this information is difficult to save and load
2498    in a module, so we take care of it here.
2499
2500    The idea here is that the original array reference comes from the
2501    base symbol.  We traverse the list of reference structures, setting
2502    the stored reference to references.  Component references can
2503    provide an additional array specification.  */
2504
2505 static void
2506 find_array_spec (gfc_expr * e)
2507 {
2508   gfc_array_spec *as;
2509   gfc_component *c;
2510   gfc_symbol *derived;
2511   gfc_ref *ref;
2512
2513   as = e->symtree->n.sym->as;
2514   derived = NULL;
2515
2516   for (ref = e->ref; ref; ref = ref->next)
2517     switch (ref->type)
2518       {
2519       case REF_ARRAY:
2520         if (as == NULL)
2521           gfc_internal_error ("find_array_spec(): Missing spec");
2522
2523         ref->u.ar.as = as;
2524         as = NULL;
2525         break;
2526
2527       case REF_COMPONENT:
2528         if (derived == NULL)
2529           derived = e->symtree->n.sym->ts.derived;
2530
2531         c = derived->components;
2532
2533         for (; c; c = c->next)
2534           if (c == ref->u.c.component)
2535             {
2536               /* Track the sequence of component references.  */
2537               if (c->ts.type == BT_DERIVED)
2538                 derived = c->ts.derived;
2539               break;
2540             }
2541
2542         if (c == NULL)
2543           gfc_internal_error ("find_array_spec(): Component not found");
2544
2545         if (c->dimension)
2546           {
2547             if (as != NULL)
2548               gfc_internal_error ("find_array_spec(): unused as(1)");
2549             as = c->as;
2550           }
2551
2552         break;
2553
2554       case REF_SUBSTRING:
2555         break;
2556       }
2557
2558   if (as != NULL)
2559     gfc_internal_error ("find_array_spec(): unused as(2)");
2560 }
2561
2562
2563 /* Resolve an array reference.  */
2564
2565 static try
2566 resolve_array_ref (gfc_array_ref * ar)
2567 {
2568   int i, check_scalar;
2569   gfc_expr *e;
2570
2571   for (i = 0; i < ar->dimen; i++)
2572     {
2573       check_scalar = ar->dimen_type[i] == DIMEN_RANGE;
2574
2575       if (gfc_resolve_index (ar->start[i], check_scalar) == FAILURE)
2576         return FAILURE;
2577       if (gfc_resolve_index (ar->end[i], check_scalar) == FAILURE)
2578         return FAILURE;
2579       if (gfc_resolve_index (ar->stride[i], check_scalar) == FAILURE)
2580         return FAILURE;
2581
2582       e = ar->start[i];
2583
2584       if (ar->dimen_type[i] == DIMEN_UNKNOWN)
2585         switch (e->rank)
2586           {
2587           case 0:
2588             ar->dimen_type[i] = DIMEN_ELEMENT;
2589             break;
2590
2591           case 1:
2592             ar->dimen_type[i] = DIMEN_VECTOR;
2593             if (e->expr_type == EXPR_VARIABLE
2594                    && e->symtree->n.sym->ts.type == BT_DERIVED)
2595               ar->start[i] = gfc_get_parentheses (e);
2596             break;
2597
2598           default:
2599             gfc_error ("Array index at %L is an array of rank %d",
2600                        &ar->c_where[i], e->rank);
2601             return FAILURE;
2602           }
2603     }
2604
2605   /* If the reference type is unknown, figure out what kind it is.  */
2606
2607   if (ar->type == AR_UNKNOWN)
2608     {
2609       ar->type = AR_ELEMENT;
2610       for (i = 0; i < ar->dimen; i++)
2611         if (ar->dimen_type[i] == DIMEN_RANGE
2612             || ar->dimen_type[i] == DIMEN_VECTOR)
2613           {
2614             ar->type = AR_SECTION;
2615             break;
2616           }
2617     }
2618
2619   if (!ar->as->cray_pointee && compare_spec_to_ref (ar) == FAILURE)
2620     return FAILURE;
2621
2622   return SUCCESS;
2623 }
2624
2625
2626 static try
2627 resolve_substring (gfc_ref * ref)
2628 {
2629
2630   if (ref->u.ss.start != NULL)
2631     {
2632       if (gfc_resolve_expr (ref->u.ss.start) == FAILURE)
2633         return FAILURE;
2634
2635       if (ref->u.ss.start->ts.type != BT_INTEGER)
2636         {
2637           gfc_error ("Substring start index at %L must be of type INTEGER",
2638                      &ref->u.ss.start->where);
2639           return FAILURE;
2640         }
2641
2642       if (ref->u.ss.start->rank != 0)
2643         {
2644           gfc_error ("Substring start index at %L must be scalar",
2645                      &ref->u.ss.start->where);
2646           return FAILURE;
2647         }
2648
2649       if (compare_bound_int (ref->u.ss.start, 1) == CMP_LT
2650           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
2651               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
2652         {
2653           gfc_error ("Substring start index at %L is less than one",
2654                      &ref->u.ss.start->where);
2655           return FAILURE;
2656         }
2657     }
2658
2659   if (ref->u.ss.end != NULL)
2660     {
2661       if (gfc_resolve_expr (ref->u.ss.end) == FAILURE)
2662         return FAILURE;
2663
2664       if (ref->u.ss.end->ts.type != BT_INTEGER)
2665         {
2666           gfc_error ("Substring end index at %L must be of type INTEGER",
2667                      &ref->u.ss.end->where);
2668           return FAILURE;
2669         }
2670
2671       if (ref->u.ss.end->rank != 0)
2672         {
2673           gfc_error ("Substring end index at %L must be scalar",
2674                      &ref->u.ss.end->where);
2675           return FAILURE;
2676         }
2677
2678       if (ref->u.ss.length != NULL
2679           && compare_bound (ref->u.ss.end, ref->u.ss.length->length) == CMP_GT
2680           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
2681               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
2682         {
2683           gfc_error ("Substring end index at %L exceeds the string length",
2684                      &ref->u.ss.start->where);
2685           return FAILURE;
2686         }
2687     }
2688
2689   return SUCCESS;
2690 }
2691
2692
2693 /* Resolve subtype references.  */
2694
2695 static try
2696 resolve_ref (gfc_expr * expr)
2697 {
2698   int current_part_dimension, n_components, seen_part_dimension;
2699   gfc_ref *ref;
2700
2701   for (ref = expr->ref; ref; ref = ref->next)
2702     if (ref->type == REF_ARRAY && ref->u.ar.as == NULL)
2703       {
2704         find_array_spec (expr);
2705         break;
2706       }
2707
2708   for (ref = expr->ref; ref; ref = ref->next)
2709     switch (ref->type)
2710       {
2711       case REF_ARRAY:
2712         if (resolve_array_ref (&ref->u.ar) == FAILURE)
2713           return FAILURE;
2714         break;
2715
2716       case REF_COMPONENT:
2717         break;
2718
2719       case REF_SUBSTRING:
2720         resolve_substring (ref);
2721         break;
2722       }
2723
2724   /* Check constraints on part references.  */
2725
2726   current_part_dimension = 0;
2727   seen_part_dimension = 0;
2728   n_components = 0;
2729
2730   for (ref = expr->ref; ref; ref = ref->next)
2731     {
2732       switch (ref->type)
2733         {
2734         case REF_ARRAY:
2735           switch (ref->u.ar.type)
2736             {
2737             case AR_FULL:
2738             case AR_SECTION:
2739               current_part_dimension = 1;
2740               break;
2741
2742             case AR_ELEMENT:
2743               current_part_dimension = 0;
2744               break;
2745
2746             case AR_UNKNOWN:
2747               gfc_internal_error ("resolve_ref(): Bad array reference");
2748             }
2749
2750           break;
2751
2752         case REF_COMPONENT:
2753           if ((current_part_dimension || seen_part_dimension)
2754               && ref->u.c.component->pointer)
2755             {
2756               gfc_error
2757                 ("Component to the right of a part reference with nonzero "
2758                  "rank must not have the POINTER attribute at %L",
2759                  &expr->where);
2760               return FAILURE;
2761             }
2762
2763           n_components++;
2764           break;
2765
2766         case REF_SUBSTRING:
2767           break;
2768         }
2769
2770       if (((ref->type == REF_COMPONENT && n_components > 1)
2771            || ref->next == NULL)
2772           && current_part_dimension
2773           && seen_part_dimension)
2774         {
2775
2776           gfc_error ("Two or more part references with nonzero rank must "
2777                      "not be specified at %L", &expr->where);
2778           return FAILURE;
2779         }
2780
2781       if (ref->type == REF_COMPONENT)
2782         {
2783           if (current_part_dimension)
2784             seen_part_dimension = 1;
2785
2786           /* reset to make sure */
2787           current_part_dimension = 0;
2788         }
2789     }
2790
2791   return SUCCESS;
2792 }
2793
2794
2795 /* Given an expression, determine its shape.  This is easier than it sounds.
2796    Leaves the shape array NULL if it is not possible to determine the shape.  */
2797
2798 static void
2799 expression_shape (gfc_expr * e)
2800 {
2801   mpz_t array[GFC_MAX_DIMENSIONS];
2802   int i;
2803
2804   if (e->rank == 0 || e->shape != NULL)
2805     return;
2806
2807   for (i = 0; i < e->rank; i++)
2808     if (gfc_array_dimen_size (e, i, &array[i]) == FAILURE)
2809       goto fail;
2810
2811   e->shape = gfc_get_shape (e->rank);
2812
2813   memcpy (e->shape, array, e->rank * sizeof (mpz_t));
2814
2815   return;
2816
2817 fail:
2818   for (i--; i >= 0; i--)
2819     mpz_clear (array[i]);
2820 }
2821
2822
2823 /* Given a variable expression node, compute the rank of the expression by
2824    examining the base symbol and any reference structures it may have.  */
2825
2826 static void
2827 expression_rank (gfc_expr * e)
2828 {
2829   gfc_ref *ref;
2830   int i, rank;
2831
2832   if (e->ref == NULL)
2833     {
2834       if (e->expr_type == EXPR_ARRAY)
2835         goto done;
2836       /* Constructors can have a rank different from one via RESHAPE().  */
2837
2838       if (e->symtree == NULL)
2839         {
2840           e->rank = 0;
2841           goto done;
2842         }
2843
2844       e->rank = (e->symtree->n.sym->as == NULL)
2845                   ? 0 : e->symtree->n.sym->as->rank;
2846       goto done;
2847     }
2848
2849   rank = 0;
2850
2851   for (ref = e->ref; ref; ref = ref->next)
2852     {
2853       if (ref->type != REF_ARRAY)
2854         continue;
2855
2856       if (ref->u.ar.type == AR_FULL)
2857         {
2858           rank = ref->u.ar.as->rank;
2859           break;
2860         }
2861
2862       if (ref->u.ar.type == AR_SECTION)
2863         {
2864           /* Figure out the rank of the section.  */
2865           if (rank != 0)
2866             gfc_internal_error ("expression_rank(): Two array specs");
2867
2868           for (i = 0; i < ref->u.ar.dimen; i++)
2869             if (ref->u.ar.dimen_type[i] == DIMEN_RANGE
2870                 || ref->u.ar.dimen_type[i] == DIMEN_VECTOR)
2871               rank++;
2872
2873           break;
2874         }
2875     }
2876
2877   e->rank = rank;
2878
2879 done:
2880   expression_shape (e);
2881 }
2882
2883
2884 /* Resolve a variable expression.  */
2885
2886 static try
2887 resolve_variable (gfc_expr * e)
2888 {
2889   gfc_symbol *sym;
2890   try t;
2891
2892   t = SUCCESS;
2893
2894   if (e->symtree == NULL)
2895     return FAILURE;
2896
2897   if (e->ref && resolve_ref (e) == FAILURE)
2898     return FAILURE;
2899
2900   sym = e->symtree->n.sym;
2901   if (sym->attr.flavor == FL_PROCEDURE && !sym->attr.function)
2902     {
2903       e->ts.type = BT_PROCEDURE;
2904       return SUCCESS;
2905     }
2906
2907   if (sym->ts.type != BT_UNKNOWN)
2908     gfc_variable_attr (e, &e->ts);
2909   else
2910     {
2911       /* Must be a simple variable reference.  */
2912       if (gfc_set_default_type (sym, 1, NULL) == FAILURE)
2913         return FAILURE;
2914       e->ts = sym->ts;
2915     }
2916
2917   if (check_assumed_size_reference (sym, e))
2918     return FAILURE;
2919
2920   /* Deal with forward references to entries during resolve_code, to
2921      satisfy, at least partially, 12.5.2.5.  */
2922   if (gfc_current_ns->entries
2923         && current_entry_id == sym->entry_id
2924         && cs_base
2925         && cs_base->current
2926         && cs_base->current->op != EXEC_ENTRY)
2927     {
2928       gfc_entry_list *entry;
2929       gfc_formal_arglist *formal;
2930       int n;
2931       bool seen;
2932
2933       /* If the symbol is a dummy...  */
2934       if (sym->attr.dummy)
2935         {
2936           entry = gfc_current_ns->entries;
2937           seen = false;
2938
2939           /* ...test if the symbol is a parameter of previous entries.  */
2940           for (; entry && entry->id <= current_entry_id; entry = entry->next)
2941             for (formal = entry->sym->formal; formal; formal = formal->next)
2942               {
2943                 if (formal->sym && sym->name == formal->sym->name)
2944                   seen = true;
2945               }
2946
2947           /*  If it has not been seen as a dummy, this is an error.  */
2948           if (!seen)
2949             {
2950               if (specification_expr)
2951                 gfc_error ("Variable '%s',used in a specification expression, "
2952                            "is referenced at %L before the ENTRY statement "
2953                            "in which it is a parameter",
2954                            sym->name, &cs_base->current->loc);
2955               else
2956                 gfc_error ("Variable '%s' is used at %L before the ENTRY "
2957                            "statement in which it is a parameter",
2958                            sym->name, &cs_base->current->loc);
2959               t = FAILURE;
2960             }
2961         }
2962
2963       /* Now do the same check on the specification expressions.  */
2964       specification_expr = 1;
2965       if (sym->ts.type == BT_CHARACTER
2966             && gfc_resolve_expr (sym->ts.cl->length) == FAILURE)
2967         t = FAILURE;
2968
2969       if (sym->as)
2970         for (n = 0; n < sym->as->rank; n++)
2971           {
2972              specification_expr = 1;
2973              if (gfc_resolve_expr (sym->as->lower[n]) == FAILURE)
2974                t = FAILURE;
2975              specification_expr = 1;
2976              if (gfc_resolve_expr (sym->as->upper[n]) == FAILURE)
2977                t = FAILURE;
2978           }
2979       specification_expr = 0;
2980
2981       if (t == SUCCESS)
2982         /* Update the symbol's entry level.  */
2983         sym->entry_id = current_entry_id + 1;
2984     }
2985
2986   return t;
2987 }
2988
2989
2990 /* Resolve an expression.  That is, make sure that types of operands agree
2991    with their operators, intrinsic operators are converted to function calls
2992    for overloaded types and unresolved function references are resolved.  */
2993
2994 try
2995 gfc_resolve_expr (gfc_expr * e)
2996 {
2997   try t;
2998
2999   if (e == NULL)
3000     return SUCCESS;
3001
3002   switch (e->expr_type)
3003     {
3004     case EXPR_OP:
3005       t = resolve_operator (e);
3006       break;
3007
3008     case EXPR_FUNCTION:
3009       t = resolve_function (e);
3010       break;
3011
3012     case EXPR_VARIABLE:
3013       t = resolve_variable (e);
3014       if (t == SUCCESS)
3015         expression_rank (e);
3016       break;
3017
3018     case EXPR_SUBSTRING:
3019       t = resolve_ref (e);
3020       break;
3021
3022     case EXPR_CONSTANT:
3023     case EXPR_NULL:
3024       t = SUCCESS;
3025       break;
3026
3027     case EXPR_ARRAY:
3028       t = FAILURE;
3029       if (resolve_ref (e) == FAILURE)
3030         break;
3031
3032       t = gfc_resolve_array_constructor (e);
3033       /* Also try to expand a constructor.  */
3034       if (t == SUCCESS)
3035         {
3036           expression_rank (e);
3037           gfc_expand_constructor (e);
3038         }
3039
3040       /* This provides the opportunity for the length of constructors with character
3041         valued function elements to propogate the string length to the expression.  */
3042       if (e->ts.type == BT_CHARACTER)
3043         gfc_resolve_character_array_constructor (e);
3044
3045       break;
3046
3047     case EXPR_STRUCTURE:
3048       t = resolve_ref (e);
3049       if (t == FAILURE)
3050         break;
3051
3052       t = resolve_structure_cons (e);
3053       if (t == FAILURE)
3054         break;
3055
3056       t = gfc_simplify_expr (e, 0);
3057       break;
3058
3059     default:
3060       gfc_internal_error ("gfc_resolve_expr(): Bad expression type");
3061     }
3062
3063   return t;
3064 }
3065
3066
3067 /* Resolve an expression from an iterator.  They must be scalar and have
3068    INTEGER or (optionally) REAL type.  */
3069
3070 static try
3071 gfc_resolve_iterator_expr (gfc_expr * expr, bool real_ok,
3072                            const char * name_msgid)
3073 {
3074   if (gfc_resolve_expr (expr) == FAILURE)
3075     return FAILURE;
3076
3077   if (expr->rank != 0)
3078     {
3079       gfc_error ("%s at %L must be a scalar", _(name_msgid), &expr->where);
3080       return FAILURE;
3081     }
3082
3083   if (!(expr->ts.type == BT_INTEGER
3084         || (expr->ts.type == BT_REAL && real_ok)))
3085     {
3086       if (real_ok)
3087         gfc_error ("%s at %L must be INTEGER or REAL", _(name_msgid),
3088                    &expr->where);
3089       else
3090         gfc_error ("%s at %L must be INTEGER", _(name_msgid), &expr->where);
3091       return FAILURE;
3092     }
3093   return SUCCESS;
3094 }
3095
3096
3097 /* Resolve the expressions in an iterator structure.  If REAL_OK is
3098    false allow only INTEGER type iterators, otherwise allow REAL types.  */
3099
3100 try
3101 gfc_resolve_iterator (gfc_iterator * iter, bool real_ok)
3102 {
3103
3104   if (iter->var->ts.type == BT_REAL)
3105     gfc_notify_std (GFC_STD_F95_DEL,
3106                     "Obsolete: REAL DO loop iterator at %L",
3107                     &iter->var->where);
3108
3109   if (gfc_resolve_iterator_expr (iter->var, real_ok, "Loop variable")
3110       == FAILURE)
3111     return FAILURE;
3112
3113   if (gfc_pure (NULL) && gfc_impure_variable (iter->var->symtree->n.sym))
3114     {
3115       gfc_error ("Cannot assign to loop variable in PURE procedure at %L",
3116                  &iter->var->where);
3117       return FAILURE;
3118     }
3119
3120   if (gfc_resolve_iterator_expr (iter->start, real_ok,
3121                                  "Start expression in DO loop") == FAILURE)
3122     return FAILURE;
3123
3124   if (gfc_resolve_iterator_expr (iter->end, real_ok,
3125                                  "End expression in DO loop") == FAILURE)
3126     return FAILURE;
3127
3128   if (gfc_resolve_iterator_expr (iter->step, real_ok,
3129                                  "Step expression in DO loop") == FAILURE)
3130     return FAILURE;
3131
3132   if (iter->step->expr_type == EXPR_CONSTANT)
3133     {
3134       if ((iter->step->ts.type == BT_INTEGER
3135            && mpz_cmp_ui (iter->step->value.integer, 0) == 0)
3136           || (iter->step->ts.type == BT_REAL
3137               && mpfr_sgn (iter->step->value.real) == 0))
3138         {
3139           gfc_error ("Step expression in DO loop at %L cannot be zero",
3140                      &iter->step->where);
3141           return FAILURE;
3142         }
3143     }
3144
3145   /* Convert start, end, and step to the same type as var.  */
3146   if (iter->start->ts.kind != iter->var->ts.kind
3147       || iter->start->ts.type != iter->var->ts.type)
3148     gfc_convert_type (iter->start, &iter->var->ts, 2);
3149
3150   if (iter->end->ts.kind != iter->var->ts.kind
3151       || iter->end->ts.type != iter->var->ts.type)
3152     gfc_convert_type (iter->end, &iter->var->ts, 2);
3153
3154   if (iter->step->ts.kind != iter->var->ts.kind
3155       || iter->step->ts.type != iter->var->ts.type)
3156     gfc_convert_type (iter->step, &iter->var->ts, 2);
3157
3158   return SUCCESS;
3159 }
3160
3161
3162 /* Resolve a list of FORALL iterators.  The FORALL index-name is constrained
3163    to be a scalar INTEGER variable.  The subscripts and stride are scalar
3164    INTEGERs, and if stride is a constant it must be nonzero.  */
3165
3166 static void
3167 resolve_forall_iterators (gfc_forall_iterator * iter)
3168 {
3169
3170   while (iter)
3171     {
3172       if (gfc_resolve_expr (iter->var) == SUCCESS
3173           && (iter->var->ts.type != BT_INTEGER || iter->var->rank != 0))
3174         gfc_error ("FORALL index-name at %L must be a scalar INTEGER",
3175                    &iter->var->where);
3176
3177       if (gfc_resolve_expr (iter->start) == SUCCESS
3178           && (iter->start->ts.type != BT_INTEGER || iter->start->rank != 0))
3179         gfc_error ("FORALL start expression at %L must be a scalar INTEGER",
3180                    &iter->start->where);
3181       if (iter->var->ts.kind != iter->start->ts.kind)
3182         gfc_convert_type (iter->start, &iter->var->ts, 2);
3183
3184       if (gfc_resolve_expr (iter->end) == SUCCESS
3185           && (iter->end->ts.type != BT_INTEGER || iter->end->rank != 0))
3186         gfc_error ("FORALL end expression at %L must be a scalar INTEGER",
3187                    &iter->end->where);
3188       if (iter->var->ts.kind != iter->end->ts.kind)
3189         gfc_convert_type (iter->end, &iter->var->ts, 2);
3190
3191       if (gfc_resolve_expr (iter->stride) == SUCCESS)
3192         {
3193           if (iter->stride->ts.type != BT_INTEGER || iter->stride->rank != 0)
3194             gfc_error ("FORALL stride expression at %L must be a scalar %s",
3195                         &iter->stride->where, "INTEGER");
3196
3197           if (iter->stride->expr_type == EXPR_CONSTANT
3198               && mpz_cmp_ui(iter->stride->value.integer, 0) == 0)
3199             gfc_error ("FORALL stride expression at %L cannot be zero",
3200                        &iter->stride->where);
3201         }
3202       if (iter->var->ts.kind != iter->stride->ts.kind)
3203         gfc_convert_type (iter->stride, &iter->var->ts, 2);
3204
3205       iter = iter->next;
3206     }
3207 }
3208
3209
3210 /* Given a pointer to a symbol that is a derived type, see if any components
3211    have the POINTER attribute.  The search is recursive if necessary.
3212    Returns zero if no pointer components are found, nonzero otherwise.  */
3213
3214 static int
3215 derived_pointer (gfc_symbol * sym)
3216 {
3217   gfc_component *c;
3218
3219   for (c = sym->components; c; c = c->next)
3220     {
3221       if (c->pointer)
3222         return 1;
3223
3224       if (c->ts.type == BT_DERIVED && derived_pointer (c->ts.derived))
3225         return 1;
3226     }
3227
3228   return 0;
3229 }
3230
3231
3232 /* Given a pointer to a symbol that is a derived type, see if it's
3233    inaccessible, i.e. if it's defined in another module and the components are
3234    PRIVATE.  The search is recursive if necessary.  Returns zero if no
3235    inaccessible components are found, nonzero otherwise.  */
3236
3237 static int
3238 derived_inaccessible (gfc_symbol *sym)
3239 {
3240   gfc_component *c;
3241
3242   if (sym->attr.use_assoc && sym->component_access == ACCESS_PRIVATE)
3243     return 1;
3244
3245   for (c = sym->components; c; c = c->next)
3246     {
3247         if (c->ts.type == BT_DERIVED && derived_inaccessible (c->ts.derived))
3248           return 1;
3249     }
3250
3251   return 0;
3252 }
3253
3254
3255 /* Resolve the argument of a deallocate expression.  The expression must be
3256    a pointer or a full array.  */
3257
3258 static try
3259 resolve_deallocate_expr (gfc_expr * e)
3260 {
3261   symbol_attribute attr;
3262   int allocatable;
3263   gfc_ref *ref;
3264
3265   if (gfc_resolve_expr (e) == FAILURE)
3266     return FAILURE;
3267
3268   attr = gfc_expr_attr (e);
3269   if (attr.pointer)
3270     return SUCCESS;
3271
3272   if (e->expr_type != EXPR_VARIABLE)
3273     goto bad;
3274
3275   allocatable = e->symtree->n.sym->attr.allocatable;
3276   for (ref = e->ref; ref; ref = ref->next)
3277     switch (ref->type)
3278       {
3279       case REF_ARRAY:
3280         if (ref->u.ar.type != AR_FULL)
3281           allocatable = 0;
3282         break;
3283
3284       case REF_COMPONENT:
3285         allocatable = (ref->u.c.component->as != NULL
3286                        && ref->u.c.component->as->type == AS_DEFERRED);
3287         break;
3288
3289       case REF_SUBSTRING:
3290         allocatable = 0;
3291         break;
3292       }
3293
3294   if (allocatable == 0)
3295     {
3296     bad:
3297       gfc_error ("Expression in DEALLOCATE statement at %L must be "
3298                  "ALLOCATABLE or a POINTER", &e->where);
3299     }
3300
3301   if (e->symtree->n.sym->attr.intent == INTENT_IN)
3302     {
3303       gfc_error ("Can't deallocate INTENT(IN) variable '%s' at %L",
3304                  e->symtree->n.sym->name, &e->where);
3305       return FAILURE;
3306     }
3307
3308   return SUCCESS;
3309 }
3310
3311
3312 /* Given the expression node e for an allocatable/pointer of derived type to be
3313    allocated, get the expression node to be initialized afterwards (needed for
3314    derived types with default initializers).  */
3315
3316 static gfc_expr *
3317 expr_to_initialize (gfc_expr * e)
3318 {
3319   gfc_expr *result;
3320   gfc_ref *ref;
3321   int i;
3322
3323   result = gfc_copy_expr (e);
3324
3325   /* Change the last array reference from AR_ELEMENT to AR_FULL.  */
3326   for (ref = result->ref; ref; ref = ref->next)
3327     if (ref->type == REF_ARRAY && ref->next == NULL)
3328       {
3329         ref->u.ar.type = AR_FULL;
3330
3331         for (i = 0; i < ref->u.ar.dimen; i++)
3332           ref->u.ar.start[i] = ref->u.ar.end[i] = ref->u.ar.stride[i] = NULL;
3333
3334         result->rank = ref->u.ar.dimen; 
3335         break;
3336       }
3337
3338   return result;
3339 }
3340
3341
3342 /* Resolve the expression in an ALLOCATE statement, doing the additional
3343    checks to see whether the expression is OK or not.  The expression must
3344    have a trailing array reference that gives the size of the array.  */
3345
3346 static try
3347 resolve_allocate_expr (gfc_expr * e, gfc_code * code)
3348 {
3349   int i, pointer, allocatable, dimension;
3350   symbol_attribute attr;
3351   gfc_ref *ref, *ref2;
3352   gfc_array_ref *ar;
3353   gfc_code *init_st;
3354   gfc_expr *init_e;
3355
3356   if (gfc_resolve_expr (e) == FAILURE)
3357     return FAILURE;
3358
3359   /* Make sure the expression is allocatable or a pointer.  If it is
3360      pointer, the next-to-last reference must be a pointer.  */
3361
3362   ref2 = NULL;
3363
3364   if (e->expr_type != EXPR_VARIABLE)
3365     {
3366       allocatable = 0;
3367
3368       attr = gfc_expr_attr (e);
3369       pointer = attr.pointer;
3370       dimension = attr.dimension;
3371
3372     }
3373   else
3374     {
3375       allocatable = e->symtree->n.sym->attr.allocatable;
3376       pointer = e->symtree->n.sym->attr.pointer;
3377       dimension = e->symtree->n.sym->attr.dimension;
3378
3379       for (ref = e->ref; ref; ref2 = ref, ref = ref->next)
3380         switch (ref->type)
3381           {
3382           case REF_ARRAY:
3383             if (ref->next != NULL)
3384               pointer = 0;
3385             break;
3386
3387           case REF_COMPONENT:
3388             allocatable = (ref->u.c.component->as != NULL
3389                            && ref->u.c.component->as->type == AS_DEFERRED);
3390
3391             pointer = ref->u.c.component->pointer;
3392             dimension = ref->u.c.component->dimension;
3393             break;
3394
3395           case REF_SUBSTRING:
3396             allocatable = 0;
3397             pointer = 0;
3398             break;
3399           }
3400     }
3401
3402   if (allocatable == 0 && pointer == 0)
3403     {
3404       gfc_error ("Expression in ALLOCATE statement at %L must be "
3405                  "ALLOCATABLE or a POINTER", &e->where);
3406       return FAILURE;
3407     }
3408
3409   if (e->symtree->n.sym->attr.intent == INTENT_IN)
3410     {
3411       gfc_error ("Can't allocate INTENT(IN) variable '%s' at %L",
3412                  e->symtree->n.sym->name, &e->where);
3413       return FAILURE;
3414     }
3415
3416   /* Add default initializer for those derived types that need them.  */
3417   if (e->ts.type == BT_DERIVED && (init_e = gfc_default_initializer (&e->ts)))
3418     {
3419         init_st = gfc_get_code ();
3420         init_st->loc = code->loc;
3421         init_st->op = EXEC_ASSIGN;
3422         init_st->expr = expr_to_initialize (e);
3423         init_st->expr2 = init_e;
3424
3425         init_st->next = code->next;
3426         code->next = init_st;
3427     }
3428
3429   if (pointer && dimension == 0)
3430     return SUCCESS;
3431
3432   /* Make sure the next-to-last reference node is an array specification.  */
3433
3434   if (ref2 == NULL || ref2->type != REF_ARRAY || ref2->u.ar.type == AR_FULL)
3435     {
3436       gfc_error ("Array specification required in ALLOCATE statement "
3437                  "at %L", &e->where);
3438       return FAILURE;
3439     }
3440
3441   if (ref2->u.ar.type == AR_ELEMENT)
3442     return SUCCESS;
3443
3444   /* Make sure that the array section reference makes sense in the
3445     context of an ALLOCATE specification.  */
3446
3447   ar = &ref2->u.ar;
3448
3449   for (i = 0; i < ar->dimen; i++)
3450     switch (ar->dimen_type[i])
3451       {
3452       case DIMEN_ELEMENT:
3453         break;
3454
3455       case DIMEN_RANGE:
3456         if (ar->start[i] != NULL
3457             && ar->end[i] != NULL
3458             && ar->stride[i] == NULL)
3459           break;
3460
3461         /* Fall Through...  */
3462
3463       case DIMEN_UNKNOWN:
3464       case DIMEN_VECTOR:
3465         gfc_error ("Bad array specification in ALLOCATE statement at %L",
3466                    &e->where);
3467         return FAILURE;
3468       }
3469
3470   return SUCCESS;
3471 }
3472
3473
3474 /************ SELECT CASE resolution subroutines ************/
3475
3476 /* Callback function for our mergesort variant.  Determines interval
3477    overlaps for CASEs. Return <0 if op1 < op2, 0 for overlap, >0 for
3478    op1 > op2.  Assumes we're not dealing with the default case.  
3479    We have op1 = (:L), (K:L) or (K:) and op2 = (:N), (M:N) or (M:).
3480    There are nine situations to check.  */
3481
3482 static int
3483 compare_cases (const gfc_case * op1, const gfc_case * op2)
3484 {
3485   int retval;
3486
3487   if (op1->low == NULL) /* op1 = (:L)  */
3488     {
3489       /* op2 = (:N), so overlap.  */
3490       retval = 0;
3491       /* op2 = (M:) or (M:N),  L < M  */
3492       if (op2->low != NULL
3493           && gfc_compare_expr (op1->high, op2->low) < 0)
3494         retval = -1;
3495     }
3496   else if (op1->high == NULL) /* op1 = (K:)  */
3497     {
3498       /* op2 = (M:), so overlap.  */
3499       retval = 0;
3500       /* op2 = (:N) or (M:N), K > N  */
3501       if (op2->high != NULL
3502           && gfc_compare_expr (op1->low, op2->high) > 0)
3503         retval = 1;
3504     }
3505   else /* op1 = (K:L)  */
3506     {
3507       if (op2->low == NULL)       /* op2 = (:N), K > N  */
3508         retval = (gfc_compare_expr (op1->low, op2->high) > 0) ? 1 : 0;
3509       else if (op2->high == NULL) /* op2 = (M:), L < M  */
3510         retval = (gfc_compare_expr (op1->high, op2->low) < 0) ? -1 : 0;
3511       else                        /* op2 = (M:N)  */
3512         {
3513           retval =  0;
3514           /* L < M  */
3515           if (gfc_compare_expr (op1->high, op2->low) < 0)
3516             retval =  -1;
3517           /* K > N  */
3518           else if (gfc_compare_expr (op1->low, op2->high) > 0)
3519             retval =  1;
3520         }
3521     }
3522
3523   return retval;
3524 }
3525
3526
3527 /* Merge-sort a double linked case list, detecting overlap in the
3528    process.  LIST is the head of the double linked case list before it
3529    is sorted.  Returns the head of the sorted list if we don't see any
3530    overlap, or NULL otherwise.  */
3531
3532 static gfc_case *
3533 check_case_overlap (gfc_case * list)
3534 {
3535   gfc_case *p, *q, *e, *tail;
3536   int insize, nmerges, psize, qsize, cmp, overlap_seen;
3537
3538   /* If the passed list was empty, return immediately.  */
3539   if (!list)
3540     return NULL;
3541
3542   overlap_seen = 0;
3543   insize = 1;
3544
3545   /* Loop unconditionally.  The only exit from this loop is a return
3546      statement, when we've finished sorting the case list.  */
3547   for (;;)
3548     {
3549       p = list;
3550       list = NULL;
3551       tail = NULL;
3552
3553       /* Count the number of merges we do in this pass.  */
3554       nmerges = 0;
3555
3556       /* Loop while there exists a merge to be done.  */
3557       while (p)
3558         {
3559           int i;
3560
3561           /* Count this merge.  */
3562           nmerges++;
3563
3564           /* Cut the list in two pieces by stepping INSIZE places
3565              forward in the list, starting from P.  */
3566           psize = 0;
3567           q = p;
3568           for (i = 0; i < insize; i++)
3569             {
3570               psize++;
3571               q = q->right;
3572               if (!q)
3573                 break;
3574             }
3575           qsize = insize;
3576
3577           /* Now we have two lists.  Merge them!  */
3578           while (psize > 0 || (qsize > 0 && q != NULL))
3579             {
3580
3581               /* See from which the next case to merge comes from.  */
3582               if (psize == 0)
3583                 {
3584                   /* P is empty so the next case must come from Q.  */
3585                   e = q;
3586                   q = q->right;
3587                   qsize--;
3588                 }
3589               else if (qsize == 0 || q == NULL)
3590                 {
3591                   /* Q is empty.  */
3592                   e = p;
3593                   p = p->right;
3594                   psize--;
3595                 }
3596               else
3597                 {
3598                   cmp = compare_cases (p, q);
3599                   if (cmp < 0)
3600                     {
3601                       /* The whole case range for P is less than the
3602                          one for Q.  */
3603                       e = p;
3604                       p = p->right;
3605                       psize--;
3606                     }
3607                   else if (cmp > 0)
3608                     {
3609                       /* The whole case range for Q is greater than
3610                          the case range for P.  */
3611                       e = q;
3612                       q = q->right;
3613                       qsize--;
3614                     }
3615                   else
3616                     {
3617                       /* The cases overlap, or they are the same
3618                          element in the list.  Either way, we must
3619                          issue an error and get the next case from P.  */
3620                       /* FIXME: Sort P and Q by line number.  */
3621                       gfc_error ("CASE label at %L overlaps with CASE "
3622                                  "label at %L", &p->where, &q->where);
3623                       overlap_seen = 1;
3624                       e = p;
3625                       p = p->right;
3626                       psize--;
3627                     }
3628                 }
3629
3630                 /* Add the next element to the merged list.  */
3631               if (tail)
3632                 tail->right = e;
3633               else
3634                 list = e;
3635               e->left = tail;
3636               tail = e;
3637             }
3638
3639           /* P has now stepped INSIZE places along, and so has Q.  So
3640              they're the same.  */
3641           p = q;
3642         }
3643       tail->right = NULL;
3644
3645       /* If we have done only one merge or none at all, we've
3646          finished sorting the cases.  */
3647       if (nmerges <= 1)
3648         {
3649           if (!overlap_seen)
3650             return list;
3651           else
3652             return NULL;
3653         }
3654
3655       /* Otherwise repeat, merging lists twice the size.  */
3656       insize *= 2;
3657     }
3658 }
3659
3660
3661 /* Check to see if an expression is suitable for use in a CASE statement.
3662    Makes sure that all case expressions are scalar constants of the same
3663    type.  Return FAILURE if anything is wrong.  */
3664
3665 static try
3666 validate_case_label_expr (gfc_expr * e, gfc_expr * case_expr)
3667 {
3668   if (e == NULL) return SUCCESS;
3669
3670   if (e->ts.type != case_expr->ts.type)
3671     {
3672       gfc_error ("Expression in CASE statement at %L must be of type %s",
3673                  &e->where, gfc_basic_typename (case_expr->ts.type));
3674       return FAILURE;
3675     }
3676
3677   /* C805 (R808) For a given case-construct, each case-value shall be of
3678      the same type as case-expr.  For character type, length differences
3679      are allowed, but the kind type parameters shall be the same.  */
3680
3681   if (case_expr->ts.type == BT_CHARACTER && e->ts.kind != case_expr->ts.kind)
3682     {
3683       gfc_error("Expression in CASE statement at %L must be kind %d",
3684                 &e->where, case_expr->ts.kind);
3685       return FAILURE;
3686     }
3687
3688   /* Convert the case value kind to that of case expression kind, if needed.
3689      FIXME:  Should a warning be issued?  */
3690   if (e->ts.kind != case_expr->ts.kind)
3691     gfc_convert_type_warn (e, &case_expr->ts, 2, 0);
3692
3693   if (e->rank != 0)
3694     {
3695       gfc_error ("Expression in CASE statement at %L must be scalar",
3696                  &e->where);
3697       return FAILURE;
3698     }
3699
3700   return SUCCESS;
3701 }
3702
3703
3704 /* Given a completely parsed select statement, we:
3705
3706      - Validate all expressions and code within the SELECT.
3707      - Make sure that the selection expression is not of the wrong type.
3708      - Make sure that no case ranges overlap.
3709      - Eliminate unreachable cases and unreachable code resulting from
3710        removing case labels.
3711
3712    The standard does allow unreachable cases, e.g. CASE (5:3).  But
3713    they are a hassle for code generation, and to prevent that, we just
3714    cut them out here.  This is not necessary for overlapping cases
3715    because they are illegal and we never even try to generate code.
3716
3717    We have the additional caveat that a SELECT construct could have
3718    been a computed GOTO in the source code. Fortunately we can fairly
3719    easily work around that here: The case_expr for a "real" SELECT CASE
3720    is in code->expr1, but for a computed GOTO it is in code->expr2. All
3721    we have to do is make sure that the case_expr is a scalar integer
3722    expression.  */
3723
3724 static void
3725 resolve_select (gfc_code * code)
3726 {
3727   gfc_code *body;
3728   gfc_expr *case_expr;
3729   gfc_case *cp, *default_case, *tail, *head;
3730   int seen_unreachable;
3731   int seen_logical;
3732   int ncases;
3733   bt type;
3734   try t;
3735
3736   if (code->expr == NULL)
3737     {
3738       /* This was actually a computed GOTO statement.  */
3739       case_expr = code->expr2;
3740       if (case_expr->ts.type != BT_INTEGER
3741           || case_expr->rank != 0)
3742         gfc_error ("Selection expression in computed GOTO statement "
3743                    "at %L must be a scalar integer expression",
3744                    &case_expr->where);
3745
3746       /* Further checking is not necessary because this SELECT was built
3747          by the compiler, so it should always be OK.  Just move the
3748          case_expr from expr2 to expr so that we can handle computed
3749          GOTOs as normal SELECTs from here on.  */
3750       code->expr = code->expr2;
3751       code->expr2 = NULL;
3752       return;
3753     }
3754
3755   case_expr = code->expr;
3756
3757   type = case_expr->ts.type;
3758   if (type != BT_LOGICAL && type != BT_INTEGER && type != BT_CHARACTER)
3759     {
3760       gfc_error ("Argument of SELECT statement at %L cannot be %s",
3761                  &case_expr->where, gfc_typename (&case_expr->ts));
3762
3763       /* Punt. Going on here just produce more garbage error messages.  */
3764       return;
3765     }
3766
3767   if (case_expr->rank != 0)
3768     {
3769       gfc_error ("Argument of SELECT statement at %L must be a scalar "
3770                  "expression", &case_expr->where);
3771
3772       /* Punt.  */
3773       return;
3774     }
3775
3776   /* PR 19168 has a long discussion concerning a mismatch of the kinds
3777      of the SELECT CASE expression and its CASE values.  Walk the lists
3778      of case values, and if we find a mismatch, promote case_expr to
3779      the appropriate kind.  */
3780
3781   if (type == BT_LOGICAL || type == BT_INTEGER)
3782     {
3783       for (body = code->block; body; body = body->block)
3784         {
3785           /* Walk the case label list.  */
3786           for (cp = body->ext.case_list; cp; cp = cp->next)
3787             {
3788               /* Intercept the DEFAULT case.  It does not have a kind.  */
3789               if (cp->low == NULL && cp->high == NULL)
3790                 continue;
3791
3792               /* Unreachable case ranges are discarded, so ignore.  */  
3793               if (cp->low != NULL && cp->high != NULL
3794                   && cp->low != cp->high
3795                   && gfc_compare_expr (cp->low, cp->high) > 0)
3796                 continue;
3797
3798               /* FIXME: Should a warning be issued?  */
3799               if (cp->low != NULL
3800                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->low))
3801                 gfc_convert_type_warn (case_expr, &cp->low->ts, 2, 0);
3802
3803               if (cp->high != NULL
3804                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->high))
3805                 gfc_convert_type_warn (case_expr, &cp->high->ts, 2, 0);
3806             }
3807          }
3808     }
3809
3810   /* Assume there is no DEFAULT case.  */
3811   default_case = NULL;
3812   head = tail = NULL;
3813   ncases = 0;
3814   seen_logical = 0;
3815
3816   for (body = code->block; body; body = body->block)
3817     {
3818       /* Assume the CASE list is OK, and all CASE labels can be matched.  */
3819       t = SUCCESS;
3820       seen_unreachable = 0;
3821
3822       /* Walk the case label list, making sure that all case labels
3823          are legal.  */
3824       for (cp = body->ext.case_list; cp; cp = cp->next)
3825         {
3826           /* Count the number of cases in the whole construct.  */
3827           ncases++;
3828
3829           /* Intercept the DEFAULT case.  */
3830           if (cp->low == NULL && cp->high == NULL)
3831             {
3832               if (default_case != NULL)
3833                 {
3834                   gfc_error ("The DEFAULT CASE at %L cannot be followed "
3835                              "by a second DEFAULT CASE at %L",
3836                              &default_case->where, &cp->where);
3837                   t = FAILURE;
3838                   break;
3839                 }
3840               else
3841                 {
3842                   default_case = cp;
3843                   continue;
3844                 }
3845             }
3846
3847           /* Deal with single value cases and case ranges.  Errors are
3848              issued from the validation function.  */
3849           if(validate_case_label_expr (cp->low, case_expr) != SUCCESS
3850              || validate_case_label_expr (cp->high, case_expr) != SUCCESS)
3851             {
3852               t = FAILURE;
3853               break;
3854             }
3855
3856           if (type == BT_LOGICAL
3857               && ((cp->low == NULL || cp->high == NULL)
3858                   || cp->low != cp->high))
3859             {
3860               gfc_error
3861                 ("Logical range in CASE statement at %L is not allowed",
3862                  &cp->low->where);
3863               t = FAILURE;
3864               break;
3865             }
3866
3867           if (type == BT_LOGICAL && cp->low->expr_type == EXPR_CONSTANT)
3868             {
3869               int value;
3870               value = cp->low->value.logical == 0 ? 2 : 1;
3871               if (value & seen_logical)
3872                 {
3873                   gfc_error ("constant logical value in CASE statement "
3874                              "is repeated at %L",
3875                              &cp->low->where);
3876                   t = FAILURE;
3877                   break;
3878                 }
3879               seen_logical |= value;
3880             }
3881
3882           if (cp->low != NULL && cp->high != NULL
3883               && cp->low != cp->high
3884               && gfc_compare_expr (cp->low, cp->high) > 0)
3885             {
3886               if (gfc_option.warn_surprising)
3887                 gfc_warning ("Range specification at %L can never "
3888                              "be matched", &cp->where);
3889
3890               cp->unreachable = 1;
3891               seen_unreachable = 1;
3892             }
3893           else
3894             {
3895               /* If the case range can be matched, it can also overlap with
3896                  other cases.  To make sure it does not, we put it in a
3897                  double linked list here.  We sort that with a merge sort
3898                  later on to detect any overlapping cases.  */
3899               if (!head)
3900                 {
3901                   head = tail = cp;
3902                   head->right = head->left = NULL;
3903                 }
3904               else
3905                 {
3906                   tail->right = cp;
3907                   tail->right->left = tail;
3908                   tail = tail->right;
3909                   tail->right = NULL;
3910                 }
3911             }
3912         }
3913
3914       /* It there was a failure in the previous case label, give up
3915          for this case label list.  Continue with the next block.  */
3916       if (t == FAILURE)
3917         continue;
3918
3919       /* See if any case labels that are unreachable have been seen.
3920          If so, we eliminate them.  This is a bit of a kludge because
3921          the case lists for a single case statement (label) is a
3922          single forward linked lists.  */
3923       if (seen_unreachable)
3924       {
3925         /* Advance until the first case in the list is reachable.  */
3926         while (body->ext.case_list != NULL
3927                && body->ext.case_list->unreachable)
3928           {
3929             gfc_case *n = body->ext.case_list;
3930             body->ext.case_list = body->ext.case_list->next;
3931             n->next = NULL;
3932             gfc_free_case_list (n);
3933           }
3934
3935         /* Strip all other unreachable cases.  */
3936         if (body->ext.case_list)
3937           {
3938             for (cp = body->ext.case_list; cp->next; cp = cp->next)
3939               {
3940                 if (cp->next->unreachable)
3941                   {
3942                     gfc_case *n = cp->next;
3943                     cp->next = cp->next->next;
3944                     n->next = NULL;
3945                     gfc_free_case_list (n);
3946                   }
3947               }
3948           }
3949       }
3950     }
3951
3952   /* See if there were overlapping cases.  If the check returns NULL,
3953      there was overlap.  In that case we don't do anything.  If head
3954      is non-NULL, we prepend the DEFAULT case.  The sorted list can
3955      then used during code generation for SELECT CASE constructs with
3956      a case expression of a CHARACTER type.  */
3957   if (head)
3958     {
3959       head = check_case_overlap (head);
3960
3961       /* Prepend the default_case if it is there.  */
3962       if (head != NULL && default_case)
3963         {
3964           default_case->left = NULL;
3965           default_case->right = head;
3966           head->left = default_case;
3967         }
3968     }
3969
3970   /* Eliminate dead blocks that may be the result if we've seen
3971      unreachable case labels for a block.  */
3972   for (body = code; body && body->block; body = body->block)
3973     {
3974       if (body->block->ext.case_list == NULL)
3975         {
3976           /* Cut the unreachable block from the code chain.  */
3977           gfc_code *c = body->block;
3978           body->block = c->block;
3979
3980           /* Kill the dead block, but not the blocks below it.  */
3981           c->block = NULL;
3982           gfc_free_statements (c);
3983         }
3984     }
3985
3986   /* More than two cases is legal but insane for logical selects.
3987      Issue a warning for it.  */
3988   if (gfc_option.warn_surprising && type == BT_LOGICAL
3989       && ncases > 2)
3990     gfc_warning ("Logical SELECT CASE block at %L has more that two cases",
3991                  &code->loc);
3992 }
3993
3994
3995 /* Resolve a transfer statement. This is making sure that:
3996    -- a derived type being transferred has only non-pointer components
3997    -- a derived type being transferred doesn't have private components, unless 
3998       it's being transferred from the module where the type was defined
3999    -- we're not trying to transfer a whole assumed size array.  */
4000
4001 static void
4002 resolve_transfer (gfc_code * code)
4003 {
4004   gfc_typespec *ts;
4005   gfc_symbol *sym;
4006   gfc_ref *ref;
4007   gfc_expr *exp;
4008
4009   exp = code->expr;
4010
4011   if (exp->expr_type != EXPR_VARIABLE)
4012     return;
4013
4014   sym = exp->symtree->n.sym;
4015   ts = &sym->ts;
4016
4017   /* Go to actual component transferred.  */
4018   for (ref = code->expr->ref; ref; ref = ref->next)
4019     if (ref->type == REF_COMPONENT)
4020       ts = &ref->u.c.component->ts;
4021
4022   if (ts->type == BT_DERIVED)
4023     {
4024       /* Check that transferred derived type doesn't contain POINTER
4025          components.  */
4026       if (derived_pointer (ts->derived))
4027         {
4028           gfc_error ("Data transfer element at %L cannot have "
4029                      "POINTER components", &code->loc);
4030           return;
4031         }
4032
4033       if (derived_inaccessible (ts->derived))
4034         {
4035           gfc_error ("Data transfer element at %L cannot have "
4036                      "PRIVATE components",&code->loc);
4037           return;
4038         }
4039     }
4040
4041   if (sym->as != NULL && sym->as->type == AS_ASSUMED_SIZE
4042       && exp->ref->type == REF_ARRAY && exp->ref->u.ar.type == AR_FULL)
4043     {
4044       gfc_error ("Data transfer element at %L cannot be a full reference to "
4045                  "an assumed-size array", &code->loc);
4046       return;
4047     }
4048 }
4049
4050
4051 /*********** Toplevel code resolution subroutines ***********/
4052
4053 /* Given a branch to a label and a namespace, if the branch is conforming.
4054    The code node described where the branch is located.  */
4055
4056 static void
4057 resolve_branch (gfc_st_label * label, gfc_code * code)
4058 {
4059   gfc_code *block, *found;
4060   code_stack *stack;
4061   gfc_st_label *lp;
4062
4063   if (label == NULL)
4064     return;
4065   lp = label;
4066
4067   /* Step one: is this a valid branching target?  */
4068
4069   if (lp->defined == ST_LABEL_UNKNOWN)
4070     {
4071       gfc_error ("Label %d referenced at %L is never defined", lp->value,
4072                  &lp->where);
4073       return;
4074     }
4075
4076   if (lp->defined != ST_LABEL_TARGET)
4077     {
4078       gfc_error ("Statement at %L is not a valid branch target statement "
4079                  "for the branch statement at %L", &lp->where, &code->loc);
4080       return;
4081     }
4082
4083   /* Step two: make sure this branch is not a branch to itself ;-)  */
4084
4085   if (code->here == label)
4086     {
4087       gfc_warning ("Branch at %L causes an infinite loop", &code->loc);
4088       return;
4089     }
4090
4091   /* Step three: Try to find the label in the parse tree. To do this,
4092      we traverse the tree block-by-block: first the block that
4093      contains this GOTO, then the block that it is nested in, etc.  We
4094      can ignore other blocks because branching into another block is
4095      not allowed.  */
4096
4097   found = NULL;
4098
4099   for (stack = cs_base; stack; stack = stack->prev)
4100     {
4101       for (block = stack->head; block; block = block->next)
4102         {
4103           if (block->here == label)
4104             {
4105               found = block;
4106               break;
4107             }
4108         }
4109
4110       if (found)
4111         break;
4112     }
4113
4114   if (found == NULL)
4115     {
4116       /* The label is not in an enclosing block, so illegal.  This was
4117          allowed in Fortran 66, so we allow it as extension.  We also 
4118          forego further checks if we run into this.  */
4119       gfc_notify_std (GFC_STD_LEGACY,
4120                       "Label at %L is not in the same block as the "
4121                       "GOTO statement at %L", &lp->where, &code->loc);
4122       return;
4123     }
4124
4125   /* Step four: Make sure that the branching target is legal if
4126      the statement is an END {SELECT,DO,IF}.  */
4127
4128   if (found->op == EXEC_NOP)
4129     {
4130       for (stack = cs_base; stack; stack = stack->prev)
4131         if (stack->current->next == found)
4132           break;
4133
4134       if (stack == NULL)
4135         gfc_notify_std (GFC_STD_F95_DEL,
4136                         "Obsolete: GOTO at %L jumps to END of construct at %L",
4137                         &code->loc, &found->loc);
4138     }
4139 }
4140
4141
4142 /* Check whether EXPR1 has the same shape as EXPR2.  */
4143
4144 static try
4145 resolve_where_shape (gfc_expr *expr1, gfc_expr *expr2)
4146 {
4147   mpz_t shape[GFC_MAX_DIMENSIONS];
4148   mpz_t shape2[GFC_MAX_DIMENSIONS];
4149   try result = FAILURE;
4150   int i;
4151
4152   /* Compare the rank.  */
4153   if (expr1->rank != expr2->rank)
4154     return result;
4155
4156   /* Compare the size of each dimension.  */
4157   for (i=0; i<expr1->rank; i++)
4158     {
4159       if (gfc_array_dimen_size (expr1, i, &shape[i]) == FAILURE)
4160         goto ignore;
4161
4162       if (gfc_array_dimen_size (expr2, i, &shape2[i]) == FAILURE)
4163         goto ignore;
4164
4165       if (mpz_cmp (shape[i], shape2[i]))
4166         goto over;
4167     }
4168
4169   /* When either of the two expression is an assumed size array, we
4170      ignore the comparison of dimension sizes.  */
4171 ignore:
4172   result = SUCCESS;
4173
4174 over:
4175   for (i--; i>=0; i--)
4176     {
4177       mpz_clear (shape[i]);
4178       mpz_clear (shape2[i]);
4179     }
4180   return result;
4181 }
4182
4183
4184 /* Check whether a WHERE assignment target or a WHERE mask expression
4185    has the same shape as the outmost WHERE mask expression.  */
4186
4187 static void
4188 resolve_where (gfc_code *code, gfc_expr *mask)
4189 {
4190   gfc_code *cblock;
4191   gfc_code *cnext;
4192   gfc_expr *e = NULL;
4193
4194   cblock = code->block;
4195
4196   /* Store the first WHERE mask-expr of the WHERE statement or construct.
4197      In case of nested WHERE, only the outmost one is stored.  */
4198   if (mask == NULL) /* outmost WHERE */
4199     e = cblock->expr;
4200   else /* inner WHERE */
4201     e = mask;
4202
4203   while (cblock)
4204     {
4205       if (cblock->expr)
4206         {
4207           /* Check if the mask-expr has a consistent shape with the
4208              outmost WHERE mask-expr.  */
4209           if (resolve_where_shape (cblock->expr, e) == FAILURE)
4210             gfc_error ("WHERE mask at %L has inconsistent shape",
4211                        &cblock->expr->where);
4212          }
4213
4214       /* the assignment statement of a WHERE statement, or the first
4215          statement in where-body-construct of a WHERE construct */
4216       cnext = cblock->next;
4217       while (cnext)
4218         {
4219           switch (cnext->op)
4220             {
4221             /* WHERE assignment statement */
4222             case EXEC_ASSIGN:
4223
4224               /* Check shape consistent for WHERE assignment target.  */
4225               if (e && resolve_where_shape (cnext->expr, e) == FAILURE)
4226                gfc_error ("WHERE assignment target at %L has "
4227                           "inconsistent shape", &cnext->expr->where);
4228               break;
4229
4230             /* WHERE or WHERE construct is part of a where-body-construct */
4231             case EXEC_WHERE:
4232               resolve_where (cnext, e);
4233               break;
4234
4235             default:
4236               gfc_error ("Unsupported statement inside WHERE at %L",
4237                          &cnext->loc);
4238             }
4239          /* the next statement within the same where-body-construct */
4240          cnext = cnext->next;
4241        }
4242     /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
4243     cblock = cblock->block;
4244   }
4245 }
4246
4247
4248 /* Check whether the FORALL index appears in the expression or not.  */
4249
4250 static try
4251 gfc_find_forall_index (gfc_expr *expr, gfc_symbol *symbol)
4252 {
4253   gfc_array_ref ar;
4254   gfc_ref *tmp;
4255   gfc_actual_arglist *args;
4256   int i;
4257
4258   switch (expr->expr_type)
4259     {
4260     case EXPR_VARIABLE:
4261       gcc_assert (expr->symtree->n.sym);
4262
4263       /* A scalar assignment  */
4264       if (!expr->ref)
4265         {
4266           if (expr->symtree->n.sym == symbol)
4267             return SUCCESS;
4268           else
4269             return FAILURE;
4270         }
4271
4272       /* the expr is array ref, substring or struct component.  */
4273       tmp = expr->ref;
4274       while (tmp != NULL)
4275         {
4276           switch (tmp->type)
4277             {
4278             case  REF_ARRAY:
4279               /* Check if the symbol appears in the array subscript.  */
4280               ar = tmp->u.ar;
4281               for (i = 0; i < GFC_MAX_DIMENSIONS; i++)
4282                 {
4283                   if (ar.start[i])
4284                     if (gfc_find_forall_index (ar.start[i], symbol) == SUCCESS)
4285                       return SUCCESS;
4286
4287                   if (ar.end[i])
4288                     if (gfc_find_forall_index (ar.end[i], symbol) == SUCCESS)
4289                       return SUCCESS;
4290
4291                   if (ar.stride[i])
4292                     if (gfc_find_forall_index (ar.stride[i], symbol) == SUCCESS)
4293                       return SUCCESS;
4294                 }  /* end for  */
4295               break;
4296
4297             case REF_SUBSTRING:
4298               if (expr->symtree->n.sym == symbol)
4299                 return SUCCESS;
4300               tmp = expr->ref;
4301               /* Check if the symbol appears in the substring section.  */
4302               if (gfc_find_forall_index (tmp->u.ss.start, symbol) == SUCCESS)
4303                 return SUCCESS;
4304               if (gfc_find_forall_index (tmp->u.ss.end, symbol) == SUCCESS)
4305                 return SUCCESS;
4306               break;
4307
4308             case REF_COMPONENT:
4309               break;
4310
4311             default:
4312               gfc_error("expression reference type error at %L", &expr->where);
4313             }
4314           tmp = tmp->next;
4315         }
4316       break;
4317
4318     /* If the expression is a function call, then check if the symbol
4319        appears in the actual arglist of the function.  */
4320     case EXPR_FUNCTION:
4321       for (args = expr->value.function.actual; args; args = args->next)
4322         {
4323           if (gfc_find_forall_index(args->expr,symbol) == SUCCESS)
4324             return SUCCESS;
4325         }
4326       break;
4327
4328     /* It seems not to happen.  */
4329     case EXPR_SUBSTRING:
4330       if (expr->ref)
4331         {
4332           tmp = expr->ref;
4333           gcc_assert (expr->ref->type == REF_SUBSTRING);
4334           if (gfc_find_forall_index (tmp->u.ss.start, symbol) == SUCCESS)
4335             return SUCCESS;
4336           if (gfc_find_forall_index (tmp->u.ss.end, symbol) == SUCCESS)
4337             return SUCCESS;
4338         }
4339       break;
4340
4341     /* It seems not to happen.  */
4342     case EXPR_STRUCTURE:
4343     case EXPR_ARRAY:
4344       gfc_error ("Unsupported statement while finding forall index in "
4345                  "expression");
4346       break;
4347
4348     case EXPR_OP:
4349       /* Find the FORALL index in the first operand.  */
4350       if (expr->value.op.op1)
4351         {
4352           if (gfc_find_forall_index (expr->value.op.op1, symbol) == SUCCESS)
4353             return SUCCESS;
4354         }
4355
4356       /* Find the FORALL index in the second operand.  */
4357       if (expr->value.op.op2)
4358         {
4359           if (gfc_find_forall_index (expr->value.op.op2, symbol) == SUCCESS)
4360             return SUCCESS;
4361         }
4362       break;
4363
4364     default:
4365       break;
4366     }
4367
4368   return FAILURE;
4369 }
4370
4371
4372 /* Resolve assignment in FORALL construct.
4373    NVAR is the number of FORALL index variables, and VAR_EXPR records the
4374    FORALL index variables.  */
4375
4376 static void
4377 gfc_resolve_assign_in_forall (gfc_code *code, int nvar, gfc_expr **var_expr)
4378 {
4379   int n;
4380
4381   for (n = 0; n < nvar; n++)
4382     {
4383       gfc_symbol *forall_index;
4384
4385       forall_index = var_expr[n]->symtree->n.sym;
4386
4387       /* Check whether the assignment target is one of the FORALL index
4388          variable.  */
4389       if ((code->expr->expr_type == EXPR_VARIABLE)
4390           && (code->expr->symtree->n.sym == forall_index))
4391         gfc_error ("Assignment to a FORALL index variable at %L",
4392                    &code->expr->where);
4393       else
4394         {
4395           /* If one of the FORALL index variables doesn't appear in the
4396              assignment target, then there will be a many-to-one
4397              assignment.  */
4398           if (gfc_find_forall_index (code->expr, forall_index) == FAILURE)
4399             gfc_error ("The FORALL with index '%s' cause more than one "
4400                        "assignment to this object at %L",
4401                        var_expr[n]->symtree->name, &code->expr->where);
4402         }
4403     }
4404 }
4405
4406
4407 /* Resolve WHERE statement in FORALL construct.  */
4408
4409 static void
4410 gfc_resolve_where_code_in_forall (gfc_code *code, int nvar, gfc_expr **var_expr){
4411   gfc_code *cblock;
4412   gfc_code *cnext;
4413
4414   cblock = code->block;
4415   while (cblock)
4416     {
4417       /* the assignment statement of a WHERE statement, or the first
4418          statement in where-body-construct of a WHERE construct */
4419       cnext = cblock->next;
4420       while (cnext)
4421         {
4422           switch (cnext->op)
4423             {
4424             /* WHERE assignment statement */
4425             case EXEC_ASSIGN:
4426               gfc_resolve_assign_in_forall (cnext, nvar, var_expr);
4427               break;
4428
4429             /* WHERE or WHERE construct is part of a where-body-construct */
4430             case EXEC_WHERE:
4431               gfc_resolve_where_code_in_forall (cnext, nvar, var_expr);
4432               break;
4433
4434             default:
4435               gfc_error ("Unsupported statement inside WHERE at %L",
4436                          &cnext->loc);
4437             }
4438           /* the next statement within the same where-body-construct */
4439           cnext = cnext->next;
4440         }
4441       /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
4442       cblock = cblock->block;
4443     }
4444 }
4445
4446
4447 /* Traverse the FORALL body to check whether the following errors exist:
4448    1. For assignment, check if a many-to-one assignment happens.
4449    2. For WHERE statement, check the WHERE body to see if there is any
4450       many-to-one assignment.  */
4451
4452 static void
4453 gfc_resolve_forall_body (gfc_code *code, int nvar, gfc_expr **var_expr)
4454 {
4455   gfc_code *c;
4456
4457   c = code->block->next;
4458   while (c)
4459     {
4460       switch (c->op)
4461         {
4462         case EXEC_ASSIGN:
4463         case EXEC_POINTER_ASSIGN:
4464           gfc_resolve_assign_in_forall (c, nvar, var_expr);
4465           break;
4466
4467         /* Because the gfc_resolve_blocks() will handle the nested FORALL,
4468            there is no need to handle it here.  */
4469         case EXEC_FORALL:
4470           break;
4471         case EXEC_WHERE:
4472           gfc_resolve_where_code_in_forall(c, nvar, var_expr);
4473           break;
4474         default:
4475           break;
4476         }
4477       /* The next statement in the FORALL body.  */
4478       c = c->next;
4479     }
4480 }
4481
4482
4483 /* Given a FORALL construct, first resolve the FORALL iterator, then call
4484    gfc_resolve_forall_body to resolve the FORALL body.  */
4485
4486 static void
4487 gfc_resolve_forall (gfc_code *code, gfc_namespace *ns, int forall_save)
4488 {
4489   static gfc_expr **var_expr;
4490   static int total_var = 0;
4491   static int nvar = 0;
4492   gfc_forall_iterator *fa;
4493   gfc_symbol *forall_index;
4494   gfc_code *next;
4495   int i;
4496
4497   /* Start to resolve a FORALL construct   */
4498   if (forall_save == 0)
4499     {
4500       /* Count the total number of FORALL index in the nested FORALL
4501          construct in order to allocate the VAR_EXPR with proper size.  */
4502       next = code;
4503       while ((next != NULL) && (next->op == EXEC_FORALL))
4504         {
4505           for (fa = next->ext.forall_iterator; fa; fa = fa->next)
4506             total_var ++;
4507           next = next->block->next;
4508         }
4509
4510       /* Allocate VAR_EXPR with NUMBER_OF_FORALL_INDEX elements.  */
4511       var_expr = (gfc_expr **) gfc_getmem (total_var * sizeof (gfc_expr *));
4512     }
4513
4514   /* The information about FORALL iterator, including FORALL index start, end
4515      and stride. The FORALL index can not appear in start, end or stride.  */
4516   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
4517     {
4518       /* Check if any outer FORALL index name is the same as the current
4519          one.  */
4520       for (i = 0; i < nvar; i++)
4521         {
4522           if (fa->var->symtree->n.sym == var_expr[i]->symtree->n.sym)
4523             {
4524               gfc_error ("An outer FORALL construct already has an index "
4525                          "with this name %L", &fa->var->where);
4526             }
4527         }
4528
4529       /* Record the current FORALL index.  */
4530       var_expr[nvar] = gfc_copy_expr (fa->var);
4531
4532       forall_index = fa->var->symtree->n.sym;
4533
4534       /* Check if the FORALL index appears in start, end or stride.  */
4535       if (gfc_find_forall_index (fa->start, forall_index) == SUCCESS)
4536         gfc_error ("A FORALL index must not appear in a limit or stride "
4537                    "expression in the same FORALL at %L", &fa->start->where);
4538       if (gfc_find_forall_index (fa->end, forall_index) == SUCCESS)
4539         gfc_error ("A FORALL index must not appear in a limit or stride "
4540                    "expression in the same FORALL at %L", &fa->end->where);
4541       if (gfc_find_forall_index (fa->stride, forall_index) == SUCCESS)
4542         gfc_error ("A FORALL index must not appear in a limit or stride "
4543                    "expression in the same FORALL at %L", &fa->stride->where);
4544       nvar++;
4545     }
4546
4547   /* Resolve the FORALL body.  */
4548   gfc_resolve_forall_body (code, nvar, var_expr);
4549
4550   /* May call gfc_resolve_forall to resolve the inner FORALL loop.  */
4551   gfc_resolve_blocks (code->block, ns);
4552
4553   /* Free VAR_EXPR after the whole FORALL construct resolved.  */
4554   for (i = 0; i < total_var; i++)
4555     gfc_free_expr (var_expr[i]);
4556
4557   /* Reset the counters.  */
4558   total_var = 0;
4559   nvar = 0;
4560 }
4561
4562
4563 /* Resolve lists of blocks found in IF, SELECT CASE, WHERE, FORALL ,GOTO and
4564    DO code nodes.  */
4565
4566 static void resolve_code (gfc_code *, gfc_namespace *);
4567
4568 void
4569 gfc_resolve_blocks (gfc_code * b, gfc_namespace * ns)
4570 {
4571   try t;
4572
4573   for (; b; b = b->block)
4574     {
4575       t = gfc_resolve_expr (b->expr);
4576       if (gfc_resolve_expr (b->expr2) == FAILURE)
4577         t = FAILURE;
4578
4579       switch (b->op)
4580         {
4581         case EXEC_IF:
4582           if (t == SUCCESS && b->expr != NULL
4583               && (b->expr->ts.type != BT_LOGICAL || b->expr->rank != 0))
4584             gfc_error
4585               ("ELSE IF clause at %L requires a scalar LOGICAL expression",
4586                &b->expr->where);
4587           break;
4588
4589         case EXEC_WHERE:
4590           if (t == SUCCESS
4591               && b->expr != NULL
4592               && (b->expr->ts.type != BT_LOGICAL
4593                   || b->expr->rank == 0))
4594             gfc_error
4595               ("WHERE/ELSEWHERE clause at %L requires a LOGICAL array",
4596                &b->expr->where);
4597           break;
4598
4599         case EXEC_GOTO:
4600           resolve_branch (b->label, b);
4601           break;
4602
4603         case EXEC_SELECT:
4604         case EXEC_FORALL:
4605         case EXEC_DO:
4606         case EXEC_DO_WHILE:
4607         case EXEC_READ:
4608         case EXEC_WRITE:
4609         case EXEC_IOLENGTH:
4610           break;
4611
4612         case EXEC_OMP_ATOMIC:
4613         case EXEC_OMP_CRITICAL:
4614         case EXEC_OMP_DO:
4615         case EXEC_OMP_MASTER:
4616         case EXEC_OMP_ORDERED:
4617         case EXEC_OMP_PARALLEL:
4618         case EXEC_OMP_PARALLEL_DO:
4619         case EXEC_OMP_PARALLEL_SECTIONS:
4620         case EXEC_OMP_PARALLEL_WORKSHARE:
4621         case EXEC_OMP_SECTIONS:
4622         case EXEC_OMP_SINGLE:
4623         case EXEC_OMP_WORKSHARE:
4624           break;
4625
4626         default:
4627           gfc_internal_error ("resolve_block(): Bad block type");
4628         }
4629
4630       resolve_code (b->next, ns);
4631     }
4632 }
4633
4634
4635 /* Given a block of code, recursively resolve everything pointed to by this
4636    code block.  */
4637
4638 static void
4639 resolve_code (gfc_code * code, gfc_namespace * ns)
4640 {
4641   int omp_workshare_save;
4642   int forall_save;
4643   code_stack frame;
4644   gfc_alloc *a;
4645   try t;
4646
4647   frame.prev = cs_base;
4648   frame.head = code;
4649   cs_base = &frame;
4650
4651   for (; code; code = code->next)
4652     {
4653       frame.current = code;
4654       forall_save = forall_flag;
4655
4656       if (code->op == EXEC_FORALL)
4657         {
4658           forall_flag = 1;
4659           gfc_resolve_forall (code, ns, forall_save);
4660           forall_flag = 2;
4661         }
4662       else if (code->block)
4663         {
4664           omp_workshare_save = -1;
4665           switch (code->op)
4666             {
4667             case EXEC_OMP_PARALLEL_WORKSHARE:
4668               omp_workshare_save = omp_workshare_flag;
4669               omp_workshare_flag = 1;
4670               gfc_resolve_omp_parallel_blocks (code, ns);
4671               break;
4672             case EXEC_OMP_PARALLEL:
4673             case EXEC_OMP_PARALLEL_DO:
4674             case EXEC_OMP_PARALLEL_SECTIONS:
4675               omp_workshare_save = omp_workshare_flag;
4676               omp_workshare_flag = 0;
4677               gfc_resolve_omp_parallel_blocks (code, ns);
4678               break;
4679             case EXEC_OMP_DO:
4680               gfc_resolve_omp_do_blocks (code, ns);
4681               break;
4682             case EXEC_OMP_WORKSHARE:
4683               omp_workshare_save = omp_workshare_flag;
4684               omp_workshare_flag = 1;
4685               /* FALLTHROUGH */
4686             default:
4687               gfc_resolve_blocks (code->block, ns);
4688               break;
4689             }
4690
4691           if (omp_workshare_save != -1)
4692             omp_workshare_flag = omp_workshare_save;
4693         }
4694
4695       t = gfc_resolve_expr (code->expr);
4696       forall_flag = forall_save;
4697
4698       if (gfc_resolve_expr (code->expr2) == FAILURE)
4699         t = FAILURE;
4700
4701       switch (code->op)
4702         {
4703         case EXEC_NOP:
4704         case EXEC_CYCLE:
4705         case EXEC_PAUSE:
4706         case EXEC_STOP:
4707         case EXEC_EXIT:
4708         case EXEC_CONTINUE:
4709         case EXEC_DT_END:
4710           break;
4711
4712         case EXEC_ENTRY:
4713           /* Keep track of which entry we are up to.  */
4714           current_entry_id = code->ext.entry->id;
4715           break;
4716
4717         case EXEC_WHERE:
4718           resolve_where (code, NULL);
4719           break;
4720
4721         case EXEC_GOTO:
4722           if (code->expr != NULL)
4723             {
4724               if (code->expr->ts.type != BT_INTEGER)
4725                 gfc_error ("ASSIGNED GOTO statement at %L requires an INTEGER "
4726                        "variable", &code->expr->where);
4727               else if (code->expr->symtree->n.sym->attr.assign != 1)
4728                 gfc_error ("Variable '%s' has not been assigned a target label "
4729                         "at %L", code->expr->symtree->n.sym->name,
4730                         &code->expr->where);
4731             }
4732           else
4733             resolve_branch (code->label, code);
4734           break;
4735
4736         case EXEC_RETURN:
4737           if (code->expr != NULL
4738                 && (code->expr->ts.type != BT_INTEGER || code->expr->rank))
4739             gfc_error ("Alternate RETURN statement at %L requires a SCALAR-"
4740                        "INTEGER return specifier", &code->expr->where);
4741           break;
4742
4743         case EXEC_ASSIGN:
4744           if (t == FAILURE)
4745             break;
4746
4747           if (gfc_extend_assign (code, ns) == SUCCESS)
4748             {
4749               if (gfc_pure (NULL) && !gfc_pure (code->symtree->n.sym))
4750                 {
4751                   gfc_error ("Subroutine '%s' called instead of assignment at "
4752                              "%L must be PURE", code->symtree->n.sym->name,
4753                              &code->loc);
4754                   break;
4755                 }
4756               goto call;
4757             }
4758
4759           if (gfc_pure (NULL))
4760             {
4761               if (gfc_impure_variable (code->expr->symtree->n.sym))
4762                 {
4763                   gfc_error
4764                     ("Cannot assign to variable '%s' in PURE procedure at %L",
4765                      code->expr->symtree->n.sym->name, &code->expr->where);
4766                   break;
4767                 }
4768
4769               if (code->expr2->ts.type == BT_DERIVED
4770                   && derived_pointer (code->expr2->ts.derived))
4771                 {
4772                   gfc_error
4773                     ("Right side of assignment at %L is a derived type "
4774                      "containing a POINTER in a PURE procedure",
4775                      &code->expr2->where);
4776                   break;
4777                 }
4778             }
4779
4780           gfc_check_assign (code->expr, code->expr2, 1);
4781           break;
4782
4783         case EXEC_LABEL_ASSIGN:
4784           if (code->label->defined == ST_LABEL_UNKNOWN)
4785             gfc_error ("Label %d referenced at %L is never defined",
4786                        code->label->value, &code->label->where);
4787           if (t == SUCCESS
4788               && (code->expr->expr_type != EXPR_VARIABLE
4789                   || code->expr->symtree->n.sym->ts.type != BT_INTEGER
4790                   || code->expr->symtree->n.sym->ts.kind 
4791                         != gfc_default_integer_kind
4792                   || code->expr->symtree->n.sym->as != NULL))
4793             gfc_error ("ASSIGN statement at %L requires a scalar "
4794                        "default INTEGER variable", &code->expr->where);
4795           break;
4796
4797         case EXEC_POINTER_ASSIGN:
4798           if (t == FAILURE)
4799             break;
4800
4801           gfc_check_pointer_assign (code->expr, code->expr2);
4802           break;
4803
4804         case EXEC_ARITHMETIC_IF:
4805           if (t == SUCCESS
4806               && code->expr->ts.type != BT_INTEGER
4807               && code->expr->ts.type != BT_REAL)
4808             gfc_error ("Arithmetic IF statement at %L requires a numeric "
4809                        "expression", &code->expr->where);
4810
4811           resolve_branch (code->label, code);
4812           resolve_branch (code->label2, code);
4813           resolve_branch (code->label3, code);
4814           break;
4815
4816         case EXEC_IF:
4817           if (t == SUCCESS && code->expr != NULL
4818               && (code->expr->ts.type != BT_LOGICAL
4819                   || code->expr->rank != 0))
4820             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
4821                        &code->expr->where);
4822           break;
4823
4824         case EXEC_CALL:
4825         call:
4826           resolve_call (code);
4827           break;
4828
4829         case EXEC_SELECT:
4830           /* Select is complicated. Also, a SELECT construct could be
4831              a transformed computed GOTO.  */
4832           resolve_select (code);
4833           break;
4834
4835         case EXEC_DO:
4836           if (code->ext.iterator != NULL)
4837             {
4838               gfc_iterator *iter = code->ext.iterator;
4839               if (gfc_resolve_iterator (iter, true) != FAILURE)
4840                 gfc_resolve_do_iterator (code, iter->var->symtree->n.sym);
4841             }
4842           break;
4843
4844         case EXEC_DO_WHILE:
4845           if (code->expr == NULL)
4846             gfc_internal_error ("resolve_code(): No expression on DO WHILE");
4847           if (t == SUCCESS
4848               && (code->expr->rank != 0
4849                   || code->expr->ts.type != BT_LOGICAL))
4850             gfc_error ("Exit condition of DO WHILE loop at %L must be "
4851                        "a scalar LOGICAL expression", &code->expr->where);
4852           break;
4853
4854         case EXEC_ALLOCATE:
4855           if (t == SUCCESS && code->expr != NULL
4856               && code->expr->ts.type != BT_INTEGER)
4857             gfc_error ("STAT tag in ALLOCATE statement at %L must be "
4858                        "of type INTEGER", &code->expr->where);
4859
4860           for (a = code->ext.alloc_list; a; a = a->next)
4861             resolve_allocate_expr (a->expr, code);
4862
4863           break;
4864
4865         case EXEC_DEALLOCATE:
4866           if (t == SUCCESS && code->expr != NULL
4867               && code->expr->ts.type != BT_INTEGER)
4868             gfc_error
4869               ("STAT tag in DEALLOCATE statement at %L must be of type "
4870                "INTEGER", &code->expr->where);
4871
4872           for (a = code->ext.alloc_list; a; a = a->next)
4873             resolve_deallocate_expr (a->expr);
4874
4875           break;
4876
4877         case EXEC_OPEN:
4878           if (gfc_resolve_open (code->ext.open) == FAILURE)
4879             break;
4880
4881           resolve_branch (code->ext.open->err, code);
4882           break;
4883
4884         case EXEC_CLOSE:
4885           if (gfc_resolve_close (code->ext.close) == FAILURE)
4886             break;
4887
4888           resolve_branch (code->ext.close->err, code);
4889           break;
4890
4891         case EXEC_BACKSPACE:
4892         case EXEC_ENDFILE:
4893         case EXEC_REWIND:
4894         case EXEC_FLUSH:
4895           if (gfc_resolve_filepos (code->ext.filepos) == FAILURE)
4896             break;
4897
4898           resolve_branch (code->ext.filepos->err, code);
4899           break;
4900
4901         case EXEC_INQUIRE:
4902           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
4903               break;
4904
4905           resolve_branch (code->ext.inquire->err, code);
4906           break;
4907
4908         case EXEC_IOLENGTH:
4909           gcc_assert (code->ext.inquire != NULL);
4910           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
4911             break;
4912
4913           resolve_branch (code->ext.inquire->err, code);
4914           break;
4915
4916         case EXEC_READ:
4917         case EXEC_WRITE:
4918           if (gfc_resolve_dt (code->ext.dt) == FAILURE)
4919             break;
4920
4921           resolve_branch (code->ext.dt->err, code);
4922           resolve_branch (code->ext.dt->end, code);
4923           resolve_branch (code->ext.dt->eor, code);
4924           break;
4925
4926         case EXEC_TRANSFER:
4927           resolve_transfer (code);
4928           break;
4929
4930         case EXEC_FORALL:
4931           resolve_forall_iterators (code->ext.forall_iterator);
4932
4933           if (code->expr != NULL && code->expr->ts.type != BT_LOGICAL)
4934             gfc_error
4935               ("FORALL mask clause at %L requires a LOGICAL expression",
4936                &code->expr->where);
4937           break;
4938
4939         case EXEC_OMP_ATOMIC:
4940         case EXEC_OMP_BARRIER:
4941         case EXEC_OMP_CRITICAL:
4942         case EXEC_OMP_FLUSH:
4943         case EXEC_OMP_DO:
4944         case EXEC_OMP_MASTER:
4945         case EXEC_OMP_ORDERED:
4946         case EXEC_OMP_SECTIONS:
4947         case EXEC_OMP_SINGLE:
4948         case EXEC_OMP_WORKSHARE:
4949           gfc_resolve_omp_directive (code, ns);
4950           break;
4951
4952         case EXEC_OMP_PARALLEL:
4953         case EXEC_OMP_PARALLEL_DO:
4954         case EXEC_OMP_PARALLEL_SECTIONS:
4955         case EXEC_OMP_PARALLEL_WORKSHARE:
4956           omp_workshare_save = omp_workshare_flag;
4957           omp_workshare_flag = 0;
4958           gfc_resolve_omp_directive (code, ns);
4959           omp_workshare_flag = omp_workshare_save;
4960           break;
4961
4962         default:
4963           gfc_internal_error ("resolve_code(): Bad statement code");
4964         }
4965     }
4966
4967   cs_base = frame.prev;
4968 }
4969
4970
4971 /* Resolve initial values and make sure they are compatible with
4972    the variable.  */
4973
4974 static void
4975 resolve_values (gfc_symbol * sym)
4976 {
4977
4978   if (sym->value == NULL)
4979     return;
4980
4981   if (gfc_resolve_expr (sym->value) == FAILURE)
4982     return;
4983
4984   gfc_check_assign_symbol (sym, sym->value);
4985 }
4986
4987
4988 /* Resolve an index expression.  */
4989
4990 static try
4991 resolve_index_expr (gfc_expr * e)
4992 {
4993   if (gfc_resolve_expr (e) == FAILURE)
4994     return FAILURE;
4995
4996   if (gfc_simplify_expr (e, 0) == FAILURE)
4997     return FAILURE;
4998
4999   if (gfc_specification_expr (e) == FAILURE)
5000     return FAILURE;
5001
5002   return SUCCESS;
5003 }
5004
5005 /* Resolve a charlen structure.  */
5006
5007 static try
5008 resolve_charlen (gfc_charlen *cl)
5009 {
5010   if (cl->resolved)
5011     return SUCCESS;
5012
5013   cl->resolved = 1;
5014
5015   specification_expr = 1;
5016
5017   if (resolve_index_expr (cl->length) == FAILURE)
5018     {
5019       specification_expr = 0;
5020       return FAILURE;
5021     }
5022
5023   return SUCCESS;
5024 }
5025
5026
5027 /* Test for non-constant shape arrays. */
5028
5029 static bool
5030 is_non_constant_shape_array (gfc_symbol *sym)
5031 {
5032   gfc_expr *e;
5033   int i;
5034   bool not_constant;
5035
5036   not_constant = false;
5037   if (sym->as != NULL)
5038     {
5039       /* Unfortunately, !gfc_is_compile_time_shape hits a legal case that
5040          has not been simplified; parameter array references.  Do the
5041          simplification now.  */
5042       for (i = 0; i < sym->as->rank; i++)
5043         {
5044           e = sym->as->lower[i];
5045           if (e && (resolve_index_expr (e) == FAILURE
5046                 || !gfc_is_constant_expr (e)))
5047             not_constant = true;
5048
5049           e = sym->as->upper[i];
5050           if (e && (resolve_index_expr (e) == FAILURE
5051                 || !gfc_is_constant_expr (e)))
5052             not_constant = true;
5053         }
5054     }
5055   return not_constant;
5056 }
5057
5058 /* Resolution of common features of flavors variable and procedure. */
5059
5060 static try
5061 resolve_fl_var_and_proc (gfc_symbol *sym, int mp_flag)
5062 {
5063   /* Constraints on deferred shape variable.  */
5064   if (sym->as == NULL || sym->as->type != AS_DEFERRED)
5065     {
5066       if (sym->attr.allocatable)
5067         {
5068           if (sym->attr.dimension)
5069             gfc_error ("Allocatable array '%s' at %L must have "
5070                        "a deferred shape", sym->name, &sym->declared_at);
5071           else
5072             gfc_error ("Scalar object '%s' at %L may not be ALLOCATABLE",
5073                        sym->name, &sym->declared_at);
5074             return FAILURE;
5075         }
5076
5077       if (sym->attr.pointer && sym->attr.dimension)
5078         {
5079           gfc_error ("Array pointer '%s' at %L must have a deferred shape",
5080                      sym->name, &sym->declared_at);
5081           return FAILURE;
5082         }
5083
5084     }
5085   else
5086     {
5087       if (!mp_flag && !sym->attr.allocatable
5088              && !sym->attr.pointer && !sym->attr.dummy)
5089         {
5090           gfc_error ("Array '%s' at %L cannot have a deferred shape",
5091                      sym->name, &sym->declared_at);
5092           return FAILURE;
5093          }
5094     }
5095   return SUCCESS;
5096 }
5097
5098 /* Resolve symbols with flavor variable.  */
5099
5100 static try
5101 resolve_fl_variable (gfc_symbol *sym, int mp_flag)
5102 {
5103   int flag;
5104   int i;
5105   gfc_expr *e;
5106   gfc_expr *constructor_expr;
5107   const char * auto_save_msg;
5108
5109   auto_save_msg = "automatic object '%s' at %L cannot have the "
5110                   "SAVE attribute";
5111
5112   if (resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
5113     return FAILURE;
5114
5115   /* Set this flag to check that variables are parameters of all entries.
5116      This check is effected by the call to gfc_resolve_expr through
5117      is_non_constant_shape_array.  */
5118   specification_expr = 1;
5119
5120   if (!sym->attr.use_assoc
5121         && !sym->attr.allocatable
5122         && !sym->attr.pointer
5123         && is_non_constant_shape_array (sym))
5124     {
5125         /* The shape of a main program or module array needs to be constant.  */
5126         if (sym->ns->proc_name
5127               && (sym->ns->proc_name->attr.flavor == FL_MODULE
5128                     || sym->ns->proc_name->attr.is_main_program))
5129           {
5130             gfc_error ("The module or main program array '%s' at %L must "
5131                        "have constant shape", sym->name, &sym->declared_at);
5132             specification_expr = 0;
5133             return FAILURE;
5134           }
5135     }
5136
5137   if (sym->ts.type == BT_CHARACTER)
5138     {
5139       /* Make sure that character string variables with assumed length are
5140          dummy arguments.  */
5141       e = sym->ts.cl->length;
5142       if (e == NULL && !sym->attr.dummy && !sym->attr.result)
5143         {
5144           gfc_error ("Entity with assumed character length at %L must be a "
5145                      "dummy argument or a PARAMETER", &sym->declared_at);
5146           return FAILURE;
5147         }
5148
5149       if (e && sym->attr.save && !gfc_is_constant_expr (e))
5150         {
5151           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
5152           return FAILURE;
5153         }
5154
5155       if (!gfc_is_constant_expr (e)
5156             && !(e->expr_type == EXPR_VARIABLE
5157             && e->symtree->n.sym->attr.flavor == FL_PARAMETER)
5158             && sym->ns->proc_name
5159             && (sym->ns->proc_name->attr.flavor == FL_MODULE
5160                   || sym->ns->proc_name->attr.is_main_program)
5161             && !sym->attr.use_assoc)
5162         {
5163           gfc_error ("'%s' at %L must have constant character length "
5164                      "in this context", sym->name, &sym->declared_at);
5165           return FAILURE;
5166         }
5167     }
5168
5169   /* Can the symbol have an initializer?  */
5170   flag = 0;
5171   if (sym->attr.allocatable || sym->attr.external || sym->attr.dummy
5172         || sym->attr.intrinsic || sym->attr.result)
5173     flag = 1;
5174   else if (sym->attr.dimension && !sym->attr.pointer)
5175     {
5176       /* Don't allow initialization of automatic arrays.  */
5177       for (i = 0; i < sym->as->rank; i++)
5178         {
5179           if (sym->as->lower[i] == NULL
5180                 || sym->as->lower[i]->expr_type != EXPR_CONSTANT
5181                 || sym->as->upper[i] == NULL
5182                 || sym->as->upper[i]->expr_type != EXPR_CONSTANT)
5183             {
5184               flag = 1;
5185               break;
5186             }
5187         }
5188
5189       /* Also, they must not have the SAVE attribute.  */
5190       if (flag && sym->attr.save)
5191         {
5192           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
5193           return FAILURE;
5194         }
5195   }
5196
5197   /* Reject illegal initializers.  */
5198   if (sym->value && flag)
5199     {
5200       if (sym->attr.allocatable)
5201         gfc_error ("Allocatable '%s' at %L cannot have an initializer",
5202                    sym->name, &sym->declared_at);
5203       else if (sym->attr.external)
5204         gfc_error ("External '%s' at %L cannot have an initializer",
5205                    sym->name, &sym->declared_at);
5206       else if (sym->attr.dummy)
5207         gfc_error ("Dummy '%s' at %L cannot have an initializer",
5208                    sym->name, &sym->declared_at);
5209       else if (sym->attr.intrinsic)
5210         gfc_error ("Intrinsic '%s' at %L cannot have an initializer",
5211                    sym->name, &sym->declared_at);
5212       else if (sym->attr.result)
5213         gfc_error ("Function result '%s' at %L cannot have an initializer",
5214                    sym->name, &sym->declared_at);
5215       else
5216         gfc_error ("Automatic array '%s' at %L cannot have an initializer",
5217                    sym->name, &sym->declared_at);
5218       return FAILURE;
5219     }
5220
5221   /* 4th constraint in section 11.3:  "If an object of a type for which
5222      component-initialization is specified (R429) appears in the
5223      specification-part of a module and does not have the ALLOCATABLE
5224      or POINTER attribute, the object shall have the SAVE attribute."  */
5225
5226   constructor_expr = NULL;
5227   if (sym->ts.type == BT_DERIVED && !(sym->value || flag))
5228         constructor_expr = gfc_default_initializer (&sym->ts);
5229
5230   if (sym->ns->proc_name
5231         && sym->ns->proc_name->attr.flavor == FL_MODULE
5232         && constructor_expr
5233         && !sym->ns->save_all && !sym->attr.save
5234         && !sym->attr.pointer && !sym->attr.allocatable)
5235     {
5236       gfc_error("Object '%s' at %L must have the SAVE attribute %s",
5237                 sym->name, &sym->declared_at,
5238                 "for default initialization of a component");
5239       return FAILURE;
5240     }
5241
5242   /* Assign default initializer.  */
5243   if (sym->ts.type == BT_DERIVED && !sym->value && !sym->attr.pointer
5244       && !sym->attr.allocatable && (!flag || sym->attr.intent == INTENT_OUT))
5245     sym->value = gfc_default_initializer (&sym->ts);
5246
5247   return SUCCESS;
5248 }
5249
5250
5251 /* Resolve a procedure.  */
5252
5253 static try
5254 resolve_fl_procedure (gfc_symbol *sym, int mp_flag)
5255 {
5256   gfc_formal_arglist *arg;
5257
5258   if (sym->attr.function
5259         && resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
5260     return FAILURE;
5261
5262   if (sym->attr.proc == PROC_ST_FUNCTION)
5263     {
5264       if (sym->ts.type == BT_CHARACTER)
5265         {
5266           gfc_charlen *cl = sym->ts.cl;
5267           if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
5268             {
5269               gfc_error ("Character-valued statement function '%s' at %L must "
5270                          "have constant length", sym->name, &sym->declared_at);
5271               return FAILURE;
5272             }
5273         }
5274     }
5275
5276   /* Ensure that derived type for are not of a private type.  Internal
5277      module procedures are excluded by 2.2.3.3 - ie. they are not
5278      externally accessible and can access all the objects accessible in
5279      the host. */
5280   if (!(sym->ns->parent
5281             && sym->ns->parent->proc_name->attr.flavor == FL_MODULE)
5282         && gfc_check_access(sym->attr.access, sym->ns->default_access))
5283     {
5284       for (arg = sym->formal; arg; arg = arg->next)
5285         {
5286           if (arg->sym
5287                 && arg->sym->ts.type == BT_DERIVED
5288                 && !arg->sym->ts.derived->attr.use_assoc
5289                 && !gfc_check_access(arg->sym->ts.derived->attr.access,
5290                         arg->sym->ts.derived->ns->default_access))
5291             {
5292               gfc_error_now ("'%s' is of a PRIVATE type and cannot be "
5293                              "a dummy argument of '%s', which is "
5294                              "PUBLIC at %L", arg->sym->name, sym->name,
5295                              &sym->declared_at);
5296               /* Stop this message from recurring.  */
5297               arg->sym->ts.derived->attr.access = ACCESS_PUBLIC;
5298               return FAILURE;
5299             }
5300         }
5301     }
5302
5303   /* An external symbol may not have an initializer because it is taken to be
5304      a procedure.  */
5305   if (sym->attr.external && sym->value)
5306     {
5307       gfc_error ("External object '%s' at %L may not have an initializer",
5308                  sym->name, &sym->declared_at);
5309       return FAILURE;
5310     }
5311
5312   /* An elemental function is required to return a scalar 12.7.1  */
5313   if (sym->attr.elemental && sym->attr.function && sym->as)
5314     {
5315       gfc_error ("ELEMENTAL function '%s' at %L must have a scalar "
5316                  "result", sym->name, &sym->declared_at);
5317       /* Reset so that the error only occurs once.  */
5318       sym->attr.elemental = 0;
5319       return FAILURE;
5320     }
5321
5322   /* 5.1.1.5 of the Standard: A function name declared with an asterisk
5323      char-len-param shall not be array-valued, pointer-valued, recursive
5324      or pure.  ....snip... A character value of * may only be used in the
5325      following ways: (i) Dummy arg of procedure - dummy associates with
5326      actual length; (ii) To declare a named constant; or (iii) External
5327      function - but length must be declared in calling scoping unit.  */
5328   if (sym->attr.function
5329         && sym->ts.type == BT_CHARACTER
5330         && sym->ts.cl && sym->ts.cl->length == NULL)
5331     {
5332       if ((sym->as && sym->as->rank) || (sym->attr.pointer)
5333              || (sym->attr.recursive) || (sym->attr.pure))
5334         {
5335           if (sym->as && sym->as->rank)
5336             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
5337                        "array-valued", sym->name, &sym->declared_at);
5338
5339           if (sym->attr.pointer)
5340             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
5341                        "pointer-valued", sym->name, &sym->declared_at);
5342
5343           if (sym->attr.pure)
5344             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
5345                        "pure", sym->name, &sym->declared_at);
5346
5347           if (sym->attr.recursive)
5348             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
5349                        "recursive", sym->name, &sym->declared_at);
5350
5351           return FAILURE;
5352         }
5353
5354       /* Appendix B.2 of the standard.  Contained functions give an
5355          error anyway.  Fixed-form is likely to be F77/legacy.  */
5356       if (!sym->attr.contained && gfc_current_form != FORM_FIXED)
5357         gfc_notify_std (GFC_STD_F95_OBS, "CHARACTER(*) function "
5358                         "'%s' at %L is obsolescent in fortran 95",
5359                         sym->name, &sym->declared_at);
5360     }
5361   return SUCCESS;
5362 }
5363
5364
5365 /* Resolve the components of a derived type.  */
5366
5367 static try
5368 resolve_fl_derived (gfc_symbol *sym)
5369 {
5370   gfc_component *c;
5371   int i;
5372
5373   for (c = sym->components; c != NULL; c = c->next)
5374     {
5375       if (c->ts.type == BT_CHARACTER)
5376         {
5377          if (c->ts.cl->length == NULL
5378              || (resolve_charlen (c->ts.cl) == FAILURE)
5379              || !gfc_is_constant_expr (c->ts.cl->length))
5380            {
5381              gfc_error ("Character length of component '%s' needs to "
5382                         "be a constant specification expression at %L.",
5383                         c->name,
5384                         c->ts.cl->length ? &c->ts.cl->length->where : &c->loc);
5385              return FAILURE;
5386            }
5387         }
5388
5389       if (c->ts.type == BT_DERIVED
5390             && sym->component_access != ACCESS_PRIVATE
5391             && gfc_check_access(sym->attr.access, sym->ns->default_access)
5392             && !c->ts.derived->attr.use_assoc
5393             && !gfc_check_access(c->ts.derived->attr.access,
5394                                  c->ts.derived->ns->default_access))
5395         {
5396           gfc_error ("The component '%s' is a PRIVATE type and cannot be "
5397                      "a component of '%s', which is PUBLIC at %L",
5398                       c->name, sym->name, &sym->declared_at);
5399           return FAILURE;
5400         }
5401
5402       if (sym->attr.sequence)
5403         {
5404           if (c->ts.type == BT_DERIVED && c->ts.derived->attr.sequence == 0)
5405             {
5406               gfc_error ("Component %s of SEQUENCE type declared at %L does "
5407                          "not have the SEQUENCE attribute",
5408                          c->ts.derived->name, &sym->declared_at);
5409               return FAILURE;
5410             }
5411         }
5412
5413       if (c->pointer || c->as == NULL)
5414         continue;
5415
5416       for (i = 0; i < c->as->rank; i++)
5417         {
5418           if (c->as->lower[i] == NULL
5419                 || !gfc_is_constant_expr (c->as->lower[i])
5420                 || (resolve_index_expr (c->as->lower[i]) == FAILURE)
5421                 || c->as->upper[i] == NULL
5422                 || (resolve_index_expr (c->as->upper[i]) == FAILURE)
5423                 || !gfc_is_constant_expr (c->as->upper[i]))
5424             {
5425               gfc_error ("Component '%s' of '%s' at %L must have "
5426                          "constant array bounds.",
5427                          c->name, sym->name, &c->loc);
5428               return FAILURE;
5429             }
5430         }
5431     }
5432     
5433   return SUCCESS;
5434 }
5435
5436
5437 static try
5438 resolve_fl_namelist (gfc_symbol *sym)
5439 {
5440   gfc_namelist *nl;
5441   gfc_symbol *nlsym;
5442
5443   /* Reject PRIVATE objects in a PUBLIC namelist.  */
5444   if (gfc_check_access(sym->attr.access, sym->ns->default_access))
5445     {
5446       for (nl = sym->namelist; nl; nl = nl->next)
5447         {
5448           if (!nl->sym->attr.use_assoc
5449                 && !(sym->ns->parent == nl->sym->ns)
5450                        && !gfc_check_access(nl->sym->attr.access,
5451                                             nl->sym->ns->default_access))
5452             {
5453               gfc_error ("PRIVATE symbol '%s' cannot be member of "
5454                          "PUBLIC namelist at %L", nl->sym->name,
5455                          &sym->declared_at);
5456               return FAILURE;
5457             }
5458         }
5459     }
5460
5461     /* Reject namelist arrays that are not constant shape.  */
5462     for (nl = sym->namelist; nl; nl = nl->next)
5463       {
5464         if (is_non_constant_shape_array (nl->sym))
5465           {
5466             gfc_error ("The array '%s' must have constant shape to be "
5467                        "a NAMELIST object at %L", nl->sym->name,
5468                        &sym->declared_at);
5469             return FAILURE;
5470           }
5471     }
5472
5473   /* 14.1.2 A module or internal procedure represent local entities
5474      of the same type as a namelist member and so are not allowed.
5475      Note that this is sometimes caught by check_conflict so the
5476      same message has been used.  */
5477   for (nl = sym->namelist; nl; nl = nl->next)
5478     {
5479       nlsym = NULL;
5480         if (sym->ns->parent && nl->sym && nl->sym->name)
5481           gfc_find_symbol (nl->sym->name, sym->ns->parent, 0, &nlsym);
5482         if (nlsym && nlsym->attr.flavor == FL_PROCEDURE)
5483           {
5484             gfc_error ("PROCEDURE attribute conflicts with NAMELIST "
5485                        "attribute in '%s' at %L", nlsym->name,
5486                        &sym->declared_at);
5487             return FAILURE;
5488           }
5489     }
5490
5491   return SUCCESS;
5492 }
5493
5494
5495 static try
5496 resolve_fl_parameter (gfc_symbol *sym)
5497 {
5498   /* A parameter array's shape needs to be constant.  */
5499   if (sym->as != NULL && !gfc_is_compile_time_shape (sym->as))
5500     {
5501       gfc_error ("Parameter array '%s' at %L cannot be automatic "
5502                  "or assumed shape", sym->name, &sym->declared_at);
5503       return FAILURE;
5504     }
5505
5506   /* Make sure a parameter that has been implicitly typed still
5507      matches the implicit type, since PARAMETER statements can precede
5508      IMPLICIT statements.  */
5509   if (sym->attr.implicit_type
5510         && !gfc_compare_types (&sym->ts,
5511                                gfc_get_default_type (sym, sym->ns)))
5512     {
5513       gfc_error ("Implicitly typed PARAMETER '%s' at %L doesn't match a "
5514                  "later IMPLICIT type", sym->name, &sym->declared_at);
5515       return FAILURE;
5516     }
5517
5518   /* Make sure the types of derived parameters are consistent.  This
5519      type checking is deferred until resolution because the type may
5520      refer to a derived type from the host.  */
5521   if (sym->ts.type == BT_DERIVED
5522         && !gfc_compare_types (&sym->ts, &sym->value->ts))
5523     {
5524       gfc_error ("Incompatible derived type in PARAMETER at %L",
5525                  &sym->value->where);
5526       return FAILURE;
5527     }
5528   return SUCCESS;
5529 }
5530
5531
5532 /* Do anything necessary to resolve a symbol.  Right now, we just
5533    assume that an otherwise unknown symbol is a variable.  This sort
5534    of thing commonly happens for symbols in module.  */
5535
5536 static void
5537 resolve_symbol (gfc_symbol * sym)
5538 {
5539   /* Zero if we are checking a formal namespace.  */
5540   static int formal_ns_flag = 1;
5541   int formal_ns_save, check_constant, mp_flag;
5542   gfc_symtree *symtree;
5543   gfc_symtree *this_symtree;
5544   gfc_namespace *ns;
5545   gfc_component *c;
5546
5547   if (sym->attr.flavor == FL_UNKNOWN)
5548     {
5549
5550     /* If we find that a flavorless symbol is an interface in one of the
5551        parent namespaces, find its symtree in this namespace, free the
5552        symbol and set the symtree to point to the interface symbol.  */
5553       for (ns = gfc_current_ns->parent; ns; ns = ns->parent)
5554         {
5555           symtree = gfc_find_symtree (ns->sym_root, sym->name);
5556           if (symtree && symtree->n.sym->generic)
5557             {
5558               this_symtree = gfc_find_symtree (gfc_current_ns->sym_root,
5559                                                sym->name);
5560               sym->refs--;
5561               if (!sym->refs)
5562                 gfc_free_symbol (sym);
5563               symtree->n.sym->refs++;
5564               this_symtree->n.sym = symtree->n.sym;
5565               return;
5566             }
5567         }
5568
5569       /* Otherwise give it a flavor according to such attributes as
5570          it has.  */
5571       if (sym->attr.external == 0 && sym->attr.intrinsic == 0)
5572         sym->attr.flavor = FL_VARIABLE;
5573       else
5574         {
5575           sym->attr.flavor = FL_PROCEDURE;
5576           if (sym->attr.dimension)
5577             sym->attr.function = 1;
5578         }
5579     }
5580
5581   if (sym->attr.flavor == FL_DERIVED && resolve_fl_derived (sym) == FAILURE)
5582     return;
5583
5584   /* Symbols that are module procedures with results (functions) have
5585      the types and array specification copied for type checking in
5586      procedures that call them, as well as for saving to a module
5587      file.  These symbols can't stand the scrutiny that their results
5588      can.  */
5589   mp_flag = (sym->result != NULL && sym->result != sym);
5590
5591   /* Assign default type to symbols that need one and don't have one.  */
5592   if (sym->ts.type == BT_UNKNOWN)
5593     {
5594       if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER)
5595         gfc_set_default_type (sym, 1, NULL);
5596
5597       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.function)
5598         {
5599           /* The specific case of an external procedure should emit an error
5600              in the case that there is no implicit type.  */
5601           if (!mp_flag)
5602             gfc_set_default_type (sym, sym->attr.external, NULL);
5603           else
5604             {
5605               /* Result may be in another namespace.  */
5606               resolve_symbol (sym->result);
5607
5608               sym->ts = sym->result->ts;
5609               sym->as = gfc_copy_array_spec (sym->result->as);
5610               sym->attr.dimension = sym->result->attr.dimension;
5611               sym->attr.pointer = sym->result->attr.pointer;
5612               sym->attr.allocatable = sym->result->attr.allocatable;
5613             }
5614         }
5615     }
5616
5617   /* Assumed size arrays and assumed shape arrays must be dummy
5618      arguments.  */ 
5619
5620   if (sym->as != NULL
5621       && (sym->as->type == AS_ASSUMED_SIZE
5622           || sym->as->type == AS_ASSUMED_SHAPE)
5623       && sym->attr.dummy == 0)
5624     {
5625       if (sym->as->type == AS_ASSUMED_SIZE)
5626         gfc_error ("Assumed size array at %L must be a dummy argument",
5627                    &sym->declared_at);
5628       else
5629         gfc_error ("Assumed shape array at %L must be a dummy argument",
5630                    &sym->declared_at);
5631       return;
5632     }
5633
5634   /* Make sure symbols with known intent or optional are really dummy
5635      variable.  Because of ENTRY statement, this has to be deferred
5636      until resolution time.  */
5637
5638   if (!sym->attr.dummy
5639       && (sym->attr.optional
5640           || sym->attr.intent != INTENT_UNKNOWN))
5641     {
5642       gfc_error ("Symbol at %L is not a DUMMY variable", &sym->declared_at);
5643       return;
5644     }
5645
5646   /* If a derived type symbol has reached this point, without its
5647      type being declared, we have an error.  Notice that most
5648      conditions that produce undefined derived types have already
5649      been dealt with.  However, the likes of:
5650      implicit type(t) (t) ..... call foo (t) will get us here if
5651      the type is not declared in the scope of the implicit
5652      statement. Change the type to BT_UNKNOWN, both because it is so
5653      and to prevent an ICE.  */
5654   if (sym->ts.type == BT_DERIVED
5655         && sym->ts.derived->components == NULL)
5656     {
5657       gfc_error ("The derived type '%s' at %L is of type '%s', "
5658                  "which has not been defined.", sym->name,
5659                   &sym->declared_at, sym->ts.derived->name);
5660       sym->ts.type = BT_UNKNOWN;
5661       return;
5662     }
5663
5664   /* An assumed-size array with INTENT(OUT) shall not be of a type for which
5665      default initialization is defined (5.1.2.4.4).  */
5666   if (sym->ts.type == BT_DERIVED
5667         && sym->attr.dummy
5668         && sym->attr.intent == INTENT_OUT
5669         && sym->as
5670         && sym->as->type == AS_ASSUMED_SIZE)
5671     {
5672       for (c = sym->ts.derived->components; c; c = c->next)
5673         {
5674           if (c->initializer)
5675             {
5676               gfc_error ("The INTENT(OUT) dummy argument '%s' at %L is "
5677                          "ASSUMED SIZE and so cannot have a default initializer",
5678                          sym->name, &sym->declared_at);
5679               return;
5680             }
5681         }
5682     }
5683
5684   switch (sym->attr.flavor)
5685     {
5686     case FL_VARIABLE:
5687       if (resolve_fl_variable (sym, mp_flag) == FAILURE)
5688         return;
5689       break;
5690
5691     case FL_PROCEDURE:
5692       if (resolve_fl_procedure (sym, mp_flag) == FAILURE)
5693         return;
5694       break;
5695
5696     case FL_NAMELIST:
5697       if (resolve_fl_namelist (sym) == FAILURE)
5698         return;
5699       break;
5700
5701     case FL_PARAMETER:
5702       if (resolve_fl_parameter (sym) == FAILURE)
5703         return;
5704
5705       break;
5706
5707     default:
5708
5709       break;
5710     }
5711
5712   /* Make sure that intrinsic exist */
5713   if (sym->attr.intrinsic
5714       && ! gfc_intrinsic_name(sym->name, 0)
5715       && ! gfc_intrinsic_name(sym->name, 1))
5716     gfc_error("Intrinsic at %L does not exist", &sym->declared_at);
5717
5718   /* Resolve array specifier. Check as well some constraints
5719      on COMMON blocks.  */
5720
5721   check_constant = sym->attr.in_common && !sym->attr.pointer;
5722   gfc_resolve_array_spec (sym->as, check_constant);
5723
5724   /* Resolve formal namespaces.  */
5725
5726   if (formal_ns_flag && sym != NULL && sym->formal_ns != NULL)
5727     {
5728       formal_ns_save = formal_ns_flag;
5729       formal_ns_flag = 0;
5730       gfc_resolve (sym->formal_ns);
5731       formal_ns_flag = formal_ns_save;
5732     }
5733
5734   /* Check threadprivate restrictions.  */
5735   if (sym->attr.threadprivate && !sym->attr.save
5736       && (!sym->attr.in_common
5737           && sym->module == NULL
5738           && (sym->ns->proc_name == NULL
5739               || sym->ns->proc_name->attr.flavor != FL_MODULE)))
5740     gfc_error ("Threadprivate at %L isn't SAVEd", &sym->declared_at);
5741 }
5742
5743
5744
5745 /************* Resolve DATA statements *************/
5746
5747 static struct
5748 {
5749   gfc_data_value *vnode;
5750   unsigned int left;
5751 }
5752 values;
5753
5754
5755 /* Advance the values structure to point to the next value in the data list.  */
5756
5757 static try
5758 next_data_value (void)
5759 {
5760   while (values.left == 0)
5761     {
5762       if (values.vnode->next == NULL)
5763         return FAILURE;
5764
5765       values.vnode = values.vnode->next;
5766       values.left = values.vnode->repeat;
5767     }
5768
5769   return SUCCESS;
5770 }
5771
5772
5773 static try
5774 check_data_variable (gfc_data_variable * var, locus * where)
5775 {
5776   gfc_expr *e;
5777   mpz_t size;
5778   mpz_t offset;
5779   try t;
5780   ar_type mark = AR_UNKNOWN;
5781   int i;
5782   mpz_t section_index[GFC_MAX_DIMENSIONS];
5783   gfc_ref *ref;
5784   gfc_array_ref *ar;
5785
5786   if (gfc_resolve_expr (var->expr) == FAILURE)
5787     return FAILURE;
5788
5789   ar = NULL;
5790   mpz_init_set_si (offset, 0);
5791   e = var->expr;
5792
5793   if (e->expr_type != EXPR_VARIABLE)
5794     gfc_internal_error ("check_data_variable(): Bad expression");
5795
5796   if (e->symtree->n.sym->ns->is_block_data
5797         && !e->symtree->n.sym->attr.in_common)
5798     {
5799       gfc_error ("BLOCK DATA element '%s' at %L must be in COMMON",
5800                  e->symtree->n.sym->name, &e->symtree->n.sym->declared_at);
5801     }
5802
5803   if (e->rank == 0)
5804     {
5805       mpz_init_set_ui (size, 1);
5806       ref = NULL;
5807     }
5808   else
5809     {
5810       ref = e->ref;
5811
5812       /* Find the array section reference.  */
5813       for (ref = e->ref; ref; ref = ref->next)
5814         {
5815           if (ref->type != REF_ARRAY)
5816             continue;
5817           if (ref->u.ar.type == AR_ELEMENT)
5818             continue;
5819           break;
5820         }
5821       gcc_assert (ref);
5822
5823       /* Set marks according to the reference pattern.  */
5824       switch (ref->u.ar.type)
5825         {
5826         case AR_FULL:
5827           mark = AR_FULL;
5828           break;
5829
5830         case AR_SECTION:
5831           ar = &ref->u.ar;
5832           /* Get the start position of array section.  */
5833           gfc_get_section_index (ar, section_index, &offset);
5834           mark = AR_SECTION;
5835           break;
5836
5837         default:
5838           gcc_unreachable ();
5839         }
5840
5841       if (gfc_array_size (e, &size) == FAILURE)
5842         {
5843           gfc_error ("Nonconstant array section at %L in DATA statement",
5844                      &e->where);
5845           mpz_clear (offset);
5846           return FAILURE;
5847         }
5848     }
5849
5850   t = SUCCESS;
5851
5852   while (mpz_cmp_ui (size, 0) > 0)
5853     {
5854       if (next_data_value () == FAILURE)
5855         {
5856           gfc_error ("DATA statement at %L has more variables than values",
5857                      where);
5858           t = FAILURE;
5859           break;
5860         }
5861
5862       t = gfc_check_assign (var->expr, values.vnode->expr, 0);
5863       if (t == FAILURE)
5864         break;
5865
5866       /* If we have more than one element left in the repeat count,
5867          and we have more than one element left in the target variable,
5868          then create a range assignment.  */
5869       /* ??? Only done for full arrays for now, since array sections
5870          seem tricky.  */
5871       if (mark == AR_FULL && ref && ref->next == NULL
5872           && values.left > 1 && mpz_cmp_ui (size, 1) > 0)
5873         {
5874           mpz_t range;
5875
5876           if (mpz_cmp_ui (size, values.left) >= 0)
5877             {
5878               mpz_init_set_ui (range, values.left);
5879               mpz_sub_ui (size, size, values.left);
5880               values.left = 0;
5881             }
5882           else
5883             {
5884               mpz_init_set (range, size);
5885               values.left -= mpz_get_ui (size);
5886               mpz_set_ui (size, 0);
5887             }
5888
5889           gfc_assign_data_value_range (var->expr, values.vnode->expr,
5890                                        offset, range);
5891
5892           mpz_add (offset, offset, range);
5893           mpz_clear (range);
5894         }
5895
5896       /* Assign initial value to symbol.  */
5897       else
5898         {
5899           values.left -= 1;
5900           mpz_sub_ui (size, size, 1);
5901
5902           gfc_assign_data_value (var->expr, values.vnode->expr, offset);
5903
5904           if (mark == AR_FULL)
5905             mpz_add_ui (offset, offset, 1);
5906
5907           /* Modify the array section indexes and recalculate the offset
5908              for next element.  */
5909           else if (mark == AR_SECTION)
5910             gfc_advance_section (section_index, ar, &offset);
5911         }
5912     }
5913
5914   if (mark == AR_SECTION)
5915     {
5916       for (i = 0; i < ar->dimen; i++)
5917         mpz_clear (section_index[i]);
5918     }
5919
5920   mpz_clear (size);
5921   mpz_clear (offset);
5922
5923   return t;
5924 }
5925
5926
5927 static try traverse_data_var (gfc_data_variable *, locus *);
5928
5929 /* Iterate over a list of elements in a DATA statement.  */
5930
5931 static try
5932 traverse_data_list (gfc_data_variable * var, locus * where)
5933 {
5934   mpz_t trip;
5935   iterator_stack frame;
5936   gfc_expr *e;
5937
5938   mpz_init (frame.value);
5939
5940   mpz_init_set (trip, var->iter.end->value.integer);
5941   mpz_sub (trip, trip, var->iter.start->value.integer);
5942   mpz_add (trip, trip, var->iter.step->value.integer);
5943
5944   mpz_div (trip, trip, var->iter.step->value.integer);
5945
5946   mpz_set (frame.value, var->iter.start->value.integer);
5947
5948   frame.prev = iter_stack;
5949   frame.variable = var->iter.var->symtree;
5950   iter_stack = &frame;
5951
5952   while (mpz_cmp_ui (trip, 0) > 0)
5953     {
5954       if (traverse_data_var (var->list, where) == FAILURE)
5955         {
5956           mpz_clear (trip);
5957           return FAILURE;
5958         }
5959
5960       e = gfc_copy_expr (var->expr);
5961       if (gfc_simplify_expr (e, 1) == FAILURE)
5962         {
5963           gfc_free_expr (e);
5964           return FAILURE;
5965         }
5966
5967       mpz_add (frame.value, frame.value, var->iter.step->value.integer);
5968
5969       mpz_sub_ui (trip, trip, 1);
5970     }
5971
5972   mpz_clear (trip);
5973   mpz_clear (frame.value);
5974
5975   iter_stack = frame.prev;
5976   return SUCCESS;
5977 }
5978
5979
5980 /* Type resolve variables in the variable list of a DATA statement.  */
5981
5982 static try
5983 traverse_data_var (gfc_data_variable * var, locus * where)
5984 {
5985   try t;
5986
5987   for (; var; var = var->next)
5988     {
5989       if (var->expr == NULL)
5990         t = traverse_data_list (var, where);
5991       else
5992         t = check_data_variable (var, where);
5993
5994       if (t == FAILURE)
5995         return FAILURE;
5996     }
5997
5998   return SUCCESS;
5999 }
6000
6001
6002 /* Resolve the expressions and iterators associated with a data statement.
6003    This is separate from the assignment checking because data lists should
6004    only be resolved once.  */
6005
6006 static try
6007 resolve_data_variables (gfc_data_variable * d)
6008 {
6009   for (; d; d = d->next)
6010     {
6011       if (d->list == NULL)
6012         {
6013           if (gfc_resolve_expr (d->expr) == FAILURE)
6014             return FAILURE;
6015         }
6016       else
6017         {
6018           if (gfc_resolve_iterator (&d->iter, false) == FAILURE)
6019             return FAILURE;
6020
6021           if (d->iter.start->expr_type != EXPR_CONSTANT
6022               || d->iter.end->expr_type != EXPR_CONSTANT
6023               || d->iter.step->expr_type != EXPR_CONSTANT)
6024             gfc_internal_error ("resolve_data_variables(): Bad iterator");
6025
6026           if (resolve_data_variables (d->list) == FAILURE)
6027             return FAILURE;
6028         }
6029     }
6030
6031   return SUCCESS;
6032 }
6033
6034
6035 /* Resolve a single DATA statement.  We implement this by storing a pointer to
6036    the value list into static variables, and then recursively traversing the
6037    variables list, expanding iterators and such.  */
6038
6039 static void
6040 resolve_data (gfc_data * d)
6041 {
6042   if (resolve_data_variables (d->var) == FAILURE)
6043     return;
6044
6045   values.vnode = d->value;
6046   values.left = (d->value == NULL) ? 0 : d->value->repeat;
6047
6048   if (traverse_data_var (d->var, &d->where) == FAILURE)
6049     return;
6050
6051   /* At this point, we better not have any values left.  */
6052
6053   if (next_data_value () == SUCCESS)
6054     gfc_error ("DATA statement at %L has more values than variables",
6055                &d->where);
6056 }
6057
6058
6059 /* Determines if a variable is not 'pure', ie not assignable within a pure
6060    procedure.  Returns zero if assignment is OK, nonzero if there is a problem.
6061  */
6062
6063 int
6064 gfc_impure_variable (gfc_symbol * sym)
6065 {
6066   if (sym->attr.use_assoc || sym->attr.in_common)
6067     return 1;
6068
6069   if (sym->ns != gfc_current_ns)
6070     return !sym->attr.function;
6071
6072   /* TODO: Check storage association through EQUIVALENCE statements */
6073
6074   return 0;
6075 }
6076
6077
6078 /* Test whether a symbol is pure or not.  For a NULL pointer, checks the
6079    symbol of the current procedure.  */
6080
6081 int
6082 gfc_pure (gfc_symbol * sym)
6083 {
6084   symbol_attribute attr;
6085
6086   if (sym == NULL)
6087     sym = gfc_current_ns->proc_name;
6088   if (sym == NULL)
6089     return 0;
6090
6091   attr = sym->attr;
6092
6093   return attr.flavor == FL_PROCEDURE && (attr.pure || attr.elemental);
6094 }
6095
6096
6097 /* Test whether the current procedure is elemental or not.  */
6098
6099 int
6100 gfc_elemental (gfc_symbol * sym)
6101 {
6102   symbol_attribute attr;
6103
6104   if (sym == NULL)
6105     sym = gfc_current_ns->proc_name;
6106   if (sym == NULL)
6107     return 0;
6108   attr = sym->attr;
6109
6110   return attr.flavor == FL_PROCEDURE && attr.elemental;
6111 }
6112
6113
6114 /* Warn about unused labels.  */
6115
6116 static void
6117 warn_unused_fortran_label (gfc_st_label * label)
6118 {
6119   if (label == NULL)
6120     return;
6121
6122   warn_unused_fortran_label (label->left);
6123
6124   if (label->defined == ST_LABEL_UNKNOWN)
6125     return;
6126
6127   switch (label->referenced)
6128     {
6129     case ST_LABEL_UNKNOWN:
6130       gfc_warning ("Label %d at %L defined but not used", label->value,
6131                    &label->where);
6132       break;
6133
6134     case ST_LABEL_BAD_TARGET:
6135       gfc_warning ("Label %d at %L defined but cannot be used",
6136                    label->value, &label->where);
6137       break;
6138
6139     default:
6140       break;
6141     }
6142
6143   warn_unused_fortran_label (label->right);
6144 }
6145
6146
6147 /* Returns the sequence type of a symbol or sequence.  */
6148
6149 static seq_type
6150 sequence_type (gfc_typespec ts)
6151 {
6152   seq_type result;
6153   gfc_component *c;
6154
6155   switch (ts.type)
6156   {
6157     case BT_DERIVED:
6158
6159       if (ts.derived->components == NULL)
6160         return SEQ_NONDEFAULT;
6161
6162       result = sequence_type (ts.derived->components->ts);
6163       for (c = ts.derived->components->next; c; c = c->next)
6164         if (sequence_type (c->ts) != result)
6165           return SEQ_MIXED;
6166
6167       return result;
6168
6169     case BT_CHARACTER:
6170       if (ts.kind != gfc_default_character_kind)
6171           return SEQ_NONDEFAULT;
6172
6173       return SEQ_CHARACTER;
6174
6175     case BT_INTEGER:
6176       if (ts.kind != gfc_default_integer_kind)
6177           return SEQ_NONDEFAULT;
6178
6179       return SEQ_NUMERIC;
6180
6181     case BT_REAL:
6182       if (!(ts.kind == gfc_default_real_kind
6183              || ts.kind == gfc_default_double_kind))
6184           return SEQ_NONDEFAULT;
6185
6186       return SEQ_NUMERIC;
6187
6188     case BT_COMPLEX:
6189       if (ts.kind != gfc_default_complex_kind)
6190           return SEQ_NONDEFAULT;
6191
6192       return SEQ_NUMERIC;
6193
6194     case BT_LOGICAL:
6195       if (ts.kind != gfc_default_logical_kind)
6196           return SEQ_NONDEFAULT;
6197
6198       return SEQ_NUMERIC;
6199
6200     default:
6201       return SEQ_NONDEFAULT;
6202   }
6203 }
6204
6205
6206 /* Resolve derived type EQUIVALENCE object.  */
6207
6208 static try
6209 resolve_equivalence_derived (gfc_symbol *derived, gfc_symbol *sym, gfc_expr *e)
6210 {
6211   gfc_symbol *d;
6212   gfc_component *c = derived->components;
6213
6214   if (!derived)
6215     return SUCCESS;
6216
6217   /* Shall not be an object of nonsequence derived type.  */
6218   if (!derived->attr.sequence)
6219     {
6220       gfc_error ("Derived type variable '%s' at %L must have SEQUENCE "
6221                  "attribute to be an EQUIVALENCE object", sym->name, &e->where);
6222       return FAILURE;
6223     }
6224
6225   for (; c ; c = c->next)
6226     {
6227       d = c->ts.derived;
6228       if (d && (resolve_equivalence_derived (c->ts.derived, sym, e) == FAILURE))
6229         return FAILURE;
6230         
6231       /* Shall not be an object of sequence derived type containing a pointer
6232          in the structure.  */
6233       if (c->pointer)
6234         {
6235           gfc_error ("Derived type variable '%s' at %L with pointer component(s) "
6236                      "cannot be an EQUIVALENCE object", sym->name, &e->where);
6237           return FAILURE;
6238         }
6239
6240       if (c->initializer)
6241         {
6242           gfc_error ("Derived type variable '%s' at %L with default initializer "
6243                      "cannot be an EQUIVALENCE object", sym->name, &e->where);
6244           return FAILURE;
6245         }
6246     }
6247   return SUCCESS;
6248 }
6249
6250
6251 /* Resolve equivalence object. 
6252    An EQUIVALENCE object shall not be a dummy argument, a pointer, a target,
6253    an allocatable array, an object of nonsequence derived type, an object of
6254    sequence derived type containing a pointer at any level of component
6255    selection, an automatic object, a function name, an entry name, a result
6256    name, a named constant, a structure component, or a subobject of any of
6257    the preceding objects.  A substring shall not have length zero.  A
6258    derived type shall not have components with default initialization nor
6259    shall two objects of an equivalence group be initialized.
6260    The simple constraints are done in symbol.c(check_conflict) and the rest
6261    are implemented here.  */
6262
6263 static void
6264 resolve_equivalence (gfc_equiv *eq)
6265 {
6266   gfc_symbol *sym;
6267   gfc_symbol *derived;
6268   gfc_symbol *first_sym;
6269   gfc_expr *e;
6270   gfc_ref *r;
6271   locus *last_where = NULL;
6272   seq_type eq_type, last_eq_type;
6273   gfc_typespec *last_ts;
6274   int object;
6275   const char *value_name;
6276   const char *msg;
6277
6278   value_name = NULL;
6279   last_ts = &eq->expr->symtree->n.sym->ts;
6280
6281   first_sym = eq->expr->symtree->n.sym;
6282
6283   for (object = 1; eq; eq = eq->eq, object++)
6284     {
6285       e = eq->expr;
6286
6287       e->ts = e->symtree->n.sym->ts;
6288       /* match_varspec might not know yet if it is seeing
6289          array reference or substring reference, as it doesn't
6290          know the types.  */
6291       if (e->ref && e->ref->type == REF_ARRAY)
6292         {
6293           gfc_ref *ref = e->ref;
6294           sym = e->symtree->n.sym;
6295
6296           if (sym->attr.dimension)
6297             {
6298               ref->u.ar.as = sym->as;
6299               ref = ref->next;
6300             }
6301
6302           /* For substrings, convert REF_ARRAY into REF_SUBSTRING.  */
6303           if (e->ts.type == BT_CHARACTER
6304               && ref
6305               && ref->type == REF_ARRAY
6306               && ref->u.ar.dimen == 1
6307               && ref->u.ar.dimen_type[0] == DIMEN_RANGE
6308               && ref->u.ar.stride[0] == NULL)
6309             {
6310               gfc_expr *start = ref->u.ar.start[0];
6311               gfc_expr *end = ref->u.ar.end[0];
6312               void *mem = NULL;
6313
6314               /* Optimize away the (:) reference.  */
6315               if (start == NULL && end == NULL)
6316                 {
6317                   if (e->ref == ref)
6318                     e->ref = ref->next;
6319                   else
6320                     e->ref->next = ref->next;
6321                   mem = ref;
6322                 }
6323               else
6324                 {
6325                   ref->type = REF_SUBSTRING;
6326                   if (start == NULL)
6327                     start = gfc_int_expr (1);
6328                   ref->u.ss.start = start;
6329                   if (end == NULL && e->ts.cl)
6330                     end = gfc_copy_expr (e->ts.cl->length);
6331                   ref->u.ss.end = end;
6332                   ref->u.ss.length = e->ts.cl;
6333                   e->ts.cl = NULL;
6334                 }
6335               ref = ref->next;
6336               gfc_free (mem);
6337             }
6338
6339           /* Any further ref is an error.  */
6340           if (ref)
6341             {
6342               gcc_assert (ref->type == REF_ARRAY);
6343               gfc_error ("Syntax error in EQUIVALENCE statement at %L",
6344                          &ref->u.ar.where);
6345               continue;
6346             }
6347         }
6348
6349       if (gfc_resolve_expr (e) == FAILURE)
6350         continue;
6351
6352       sym = e->symtree->n.sym;
6353
6354       /* An equivalence statement cannot have more than one initialized
6355          object.  */
6356       if (sym->value)
6357         {
6358           if (value_name != NULL)
6359             {
6360               gfc_error ("Initialized objects '%s' and '%s'  cannot both "
6361                          "be in the EQUIVALENCE statement at %L",
6362                          value_name, sym->name, &e->where);
6363               continue;
6364             }
6365           else
6366             value_name = sym->name;
6367         }
6368
6369       /* Shall not equivalence common block variables in a PURE procedure.  */
6370       if (sym->ns->proc_name 
6371             && sym->ns->proc_name->attr.pure
6372             && sym->attr.in_common)
6373         {
6374           gfc_error ("Common block member '%s' at %L cannot be an EQUIVALENCE "
6375                      "object in the pure procedure '%s'",
6376                      sym->name, &e->where, sym->ns->proc_name->name);
6377           break;
6378         }
6379  
6380       /* Shall not be a named constant.  */      
6381       if (e->expr_type == EXPR_CONSTANT)
6382         {
6383           gfc_error ("Named constant '%s' at %L cannot be an EQUIVALENCE "
6384                      "object", sym->name, &e->where);
6385           continue;
6386         }
6387
6388       derived = e->ts.derived;
6389       if (derived && resolve_equivalence_derived (derived, sym, e) == FAILURE)
6390         continue;
6391
6392       /* Check that the types correspond correctly:
6393          Note 5.28:
6394          A numeric sequence structure may be equivalenced to another sequence
6395          structure, an object of default integer type, default real type, double
6396          precision real type, default logical type such that components of the
6397          structure ultimately only become associated to objects of the same
6398          kind. A character sequence structure may be equivalenced to an object
6399          of default character kind or another character sequence structure.
6400          Other objects may be equivalenced only to objects of the same type and
6401          kind parameters.  */
6402
6403       /* Identical types are unconditionally OK.  */
6404       if (object == 1 || gfc_compare_types (last_ts, &sym->ts))
6405         goto identical_types;
6406
6407       last_eq_type = sequence_type (*last_ts);
6408       eq_type = sequence_type (sym->ts);
6409
6410       /* Since the pair of objects is not of the same type, mixed or
6411          non-default sequences can be rejected.  */
6412
6413       msg = "Sequence %s with mixed components in EQUIVALENCE "
6414             "statement at %L with different type objects";
6415       if ((object ==2
6416                && last_eq_type == SEQ_MIXED
6417                && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name,
6418                                   last_where) == FAILURE)
6419            ||  (eq_type == SEQ_MIXED
6420                && gfc_notify_std (GFC_STD_GNU, msg,sym->name,
6421                                   &e->where) == FAILURE))
6422         continue;
6423
6424       msg = "Non-default type object or sequence %s in EQUIVALENCE "
6425             "statement at %L with objects of different type";
6426       if ((object ==2
6427                && last_eq_type == SEQ_NONDEFAULT
6428                && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name,
6429                                   last_where) == FAILURE)
6430            ||  (eq_type == SEQ_NONDEFAULT
6431                && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
6432                                   &e->where) == FAILURE))
6433         continue;
6434
6435       msg ="Non-CHARACTER object '%s' in default CHARACTER "
6436            "EQUIVALENCE statement at %L";
6437       if (last_eq_type == SEQ_CHARACTER
6438             && eq_type != SEQ_CHARACTER
6439             && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
6440                                   &e->where) == FAILURE)
6441                 continue;
6442
6443       msg ="Non-NUMERIC object '%s' in default NUMERIC "
6444            "EQUIVALENCE statement at %L";
6445       if (last_eq_type == SEQ_NUMERIC
6446             && eq_type != SEQ_NUMERIC
6447             && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
6448                                   &e->where) == FAILURE)
6449                 continue;
6450
6451   identical_types:
6452       last_ts =&sym->ts;
6453       last_where = &e->where;
6454
6455       if (!e->ref)
6456         continue;
6457
6458       /* Shall not be an automatic array.  */
6459       if (e->ref->type == REF_ARRAY
6460           && gfc_resolve_array_spec (e->ref->u.ar.as, 1) == FAILURE)
6461         {
6462           gfc_error ("Array '%s' at %L with non-constant bounds cannot be "
6463                      "an EQUIVALENCE object", sym->name, &e->where);
6464           continue;
6465         }
6466
6467       r = e->ref;
6468       while (r)
6469         {
6470           /* Shall not be a structure component.  */
6471           if (r->type == REF_COMPONENT)
6472             {
6473               gfc_error ("Structure component '%s' at %L cannot be an "
6474                          "EQUIVALENCE object",
6475                          r->u.c.component->name, &e->where);
6476               break;
6477             }
6478
6479           /* A substring shall not have length zero.  */
6480           if (r->type == REF_SUBSTRING)
6481             {
6482               if (compare_bound (r->u.ss.start, r->u.ss.end) == CMP_GT)
6483                 {
6484                   gfc_error ("Substring at %L has length zero",
6485                              &r->u.ss.start->where);
6486                   break;
6487                 }
6488             }
6489           r = r->next;
6490         }
6491     }    
6492 }      
6493
6494
6495 /* Resolve function and ENTRY types, issue diagnostics if needed. */
6496
6497 static void
6498 resolve_fntype (gfc_namespace * ns)
6499 {
6500   gfc_entry_list *el;
6501   gfc_symbol *sym;
6502
6503   if (ns->proc_name == NULL || !ns->proc_name->attr.function)
6504     return;
6505
6506   /* If there are any entries, ns->proc_name is the entry master
6507      synthetic symbol and ns->entries->sym actual FUNCTION symbol.  */
6508   if (ns->entries)
6509     sym = ns->entries->sym;
6510   else
6511     sym = ns->proc_name;
6512   if (sym->result == sym
6513       && sym->ts.type == BT_UNKNOWN
6514       && gfc_set_default_type (sym, 0, NULL) == FAILURE
6515       && !sym->attr.untyped)
6516     {
6517       gfc_error ("Function '%s' at %L has no IMPLICIT type",
6518                  sym->name, &sym->declared_at);
6519       sym->attr.untyped = 1;
6520     }
6521
6522   if (sym->ts.type == BT_DERIVED && !sym->ts.derived->attr.use_assoc
6523       && !gfc_check_access (sym->ts.derived->attr.access,
6524                             sym->ts.derived->ns->default_access)
6525       && gfc_check_access (sym->attr.access, sym->ns->default_access))
6526     {
6527       gfc_error ("PUBLIC function '%s' at %L cannot be of PRIVATE type '%s'",
6528                  sym->name, &sym->declared_at, sym->ts.derived->name);
6529     }
6530
6531   if (ns->entries)
6532     for (el = ns->entries->next; el; el = el->next)
6533       {
6534         if (el->sym->result == el->sym
6535             && el->sym->ts.type == BT_UNKNOWN
6536             && gfc_set_default_type (el->sym, 0, NULL) == FAILURE
6537             && !el->sym->attr.untyped)
6538           {
6539             gfc_error ("ENTRY '%s' at %L has no IMPLICIT type",
6540                        el->sym->name, &el->sym->declared_at);
6541             el->sym->attr.untyped = 1;
6542           }
6543       }
6544 }
6545
6546 /* 12.3.2.1.1 Defined operators.  */
6547
6548 static void
6549 gfc_resolve_uops(gfc_symtree *symtree)
6550 {
6551   gfc_interface *itr;
6552   gfc_symbol *sym;
6553   gfc_formal_arglist *formal;
6554
6555   if (symtree == NULL) 
6556     return; 
6557  
6558   gfc_resolve_uops (symtree->left);
6559   gfc_resolve_uops (symtree->right);
6560
6561   for (itr = symtree->n.uop->operator; itr; itr = itr->next)
6562     {
6563       sym = itr->sym;
6564       if (!sym->attr.function)
6565         gfc_error("User operator procedure '%s' at %L must be a FUNCTION",
6566                   sym->name, &sym->declared_at);
6567
6568       if (sym->ts.type == BT_CHARACTER
6569             && !(sym->ts.cl && sym->ts.cl->length)
6570             && !(sym->result && sym->result->ts.cl && sym->result->ts.cl->length))
6571         gfc_error("User operator procedure '%s' at %L cannot be assumed character "
6572                   "length", sym->name, &sym->declared_at);
6573
6574       formal = sym->formal;
6575       if (!formal || !formal->sym)
6576         {
6577           gfc_error("User operator procedure '%s' at %L must have at least "
6578                     "one argument", sym->name, &sym->declared_at);
6579           continue;
6580         }
6581
6582       if (formal->sym->attr.intent != INTENT_IN)
6583         gfc_error ("First argument of operator interface at %L must be "
6584                    "INTENT(IN)", &sym->declared_at);
6585
6586       if (formal->sym->attr.optional)
6587         gfc_error ("First argument of operator interface at %L cannot be "
6588                    "optional", &sym->declared_at);
6589
6590       formal = formal->next;
6591       if (!formal || !formal->sym)
6592         continue;
6593
6594       if (formal->sym->attr.intent != INTENT_IN)
6595         gfc_error ("Second argument of operator interface at %L must be "
6596                    "INTENT(IN)", &sym->declared_at);
6597
6598       if (formal->sym->attr.optional)
6599         gfc_error ("Second argument of operator interface at %L cannot be "
6600                    "optional", &sym->declared_at);
6601
6602       if (formal->next)
6603         gfc_error ("Operator interface at %L must have, at most, two "
6604                    "arguments", &sym->declared_at);
6605     }
6606 }
6607
6608
6609 /* Examine all of the expressions associated with a program unit,
6610    assign types to all intermediate expressions, make sure that all
6611    assignments are to compatible types and figure out which names
6612    refer to which functions or subroutines.  It doesn't check code
6613    block, which is handled by resolve_code.  */
6614
6615 static void
6616 resolve_types (gfc_namespace * ns)
6617 {
6618   gfc_namespace *n;
6619   gfc_charlen *cl;
6620   gfc_data *d;
6621   gfc_equiv *eq;
6622
6623   gfc_current_ns = ns;
6624
6625   resolve_entries (ns);
6626
6627   resolve_contained_functions (ns);
6628
6629   gfc_traverse_ns (ns, resolve_symbol);
6630
6631   resolve_fntype (ns);
6632
6633   for (n = ns->contained; n; n = n->sibling)
6634     {
6635       if (gfc_pure (ns->proc_name) && !gfc_pure (n->proc_name))
6636         gfc_error ("Contained procedure '%s' at %L of a PURE procedure must "
6637                    "also be PURE", n->proc_name->name,
6638                    &n->proc_name->declared_at);
6639
6640       resolve_types (n);
6641     }
6642
6643   forall_flag = 0;
6644   gfc_check_interfaces (ns);
6645
6646   for (cl = ns->cl_list; cl; cl = cl->next)
6647     resolve_charlen (cl);
6648
6649   gfc_traverse_ns (ns, resolve_values);
6650
6651   if (ns->save_all)
6652     gfc_save_all (ns);
6653
6654   iter_stack = NULL;
6655   for (d = ns->data; d; d = d->next)
6656     resolve_data (d);
6657
6658   iter_stack = NULL;
6659   gfc_traverse_ns (ns, gfc_formalize_init_value);
6660
6661   for (eq = ns->equiv; eq; eq = eq->next)
6662     resolve_equivalence (eq);
6663
6664   /* Warn about unused labels.  */
6665   if (gfc_option.warn_unused_labels)
6666     warn_unused_fortran_label (ns->st_labels);
6667
6668   gfc_resolve_uops (ns->uop_root);
6669     
6670 }
6671
6672
6673 /* Call resolve_code recursively.  */
6674
6675 static void
6676 resolve_codes (gfc_namespace * ns)
6677 {
6678   gfc_namespace *n;
6679
6680   for (n = ns->contained; n; n = n->sibling)
6681     resolve_codes (n);
6682
6683   gfc_current_ns = ns;
6684   cs_base = NULL;
6685   /* Set to an out of range value.  */
6686   current_entry_id = -1;
6687   resolve_code (ns->code, ns);
6688 }
6689
6690
6691 /* This function is called after a complete program unit has been compiled.
6692    Its purpose is to examine all of the expressions associated with a program
6693    unit, assign types to all intermediate expressions, make sure that all
6694    assignments are to compatible types and figure out which names refer to
6695    which functions or subroutines.  */
6696
6697 void
6698 gfc_resolve (gfc_namespace * ns)
6699 {
6700   gfc_namespace *old_ns;
6701
6702   old_ns = gfc_current_ns;
6703
6704   resolve_types (ns);
6705   resolve_codes (ns);
6706
6707   gfc_current_ns = old_ns;
6708 }