OSDN Git Service

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