OSDN Git Service

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