OSDN Git Service

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