Merged with mainline at revision 126229.
[official-gcc.git] / gcc / fortran / resolve.c
blobfde5043403c416b9f6e03bebf9ae3415c3761f3b
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
6 This file is part of GCC.
8 GCC is free software; you can redistribute it and/or modify it under
9 the terms of the GNU General Public License as published by the Free
10 Software Foundation; either version 2, or (at your option) any later
11 version.
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.
18 You should have received a copy of the GNU General Public License
19 along with GCC; see the file COPYING. If not, write to the Free
20 Software Foundation, 51 Franklin Street, Fifth Floor,Boston, MA
21 02110-1301, USA. */
23 #include "config.h"
24 #include "system.h"
25 #include "flags.h"
26 #include "gfortran.h"
27 #include "obstack.h"
28 #include "bitmap.h"
29 #include "arith.h" /* For gfc_compare_expr(). */
30 #include "dependency.h"
32 /* Types used in equivalence statements. */
34 typedef enum seq_type
36 SEQ_NONDEFAULT, SEQ_NUMERIC, SEQ_CHARACTER, SEQ_MIXED
38 seq_type;
40 /* Stack to keep track of the nesting of blocks as we move through the
41 code. See resolve_branch() and resolve_code(). */
43 typedef struct code_stack
45 struct gfc_code *head, *current, *tail;
46 struct code_stack *prev;
48 /* This bitmap keeps track of the targets valid for a branch from
49 inside this block. */
50 bitmap reachable_labels;
52 code_stack;
54 static code_stack *cs_base = NULL;
57 /* Nonzero if we're inside a FORALL block. */
59 static int forall_flag;
61 /* Nonzero if we're inside a OpenMP WORKSHARE or PARALLEL WORKSHARE block. */
63 static int omp_workshare_flag;
65 /* Nonzero if we are processing a formal arglist. The corresponding function
66 resets the flag each time that it is read. */
67 static int formal_arg_flag = 0;
69 /* True if we are resolving a specification expression. */
70 static int specification_expr = 0;
72 /* The id of the last entry seen. */
73 static int current_entry_id;
75 /* We use bitmaps to determine if a branch target is valid. */
76 static bitmap_obstack labels_obstack;
78 int
79 gfc_is_formal_arg (void)
81 return formal_arg_flag;
84 /* Resolve types of formal argument lists. These have to be done early so that
85 the formal argument lists of module procedures can be copied to the
86 containing module before the individual procedures are resolved
87 individually. We also resolve argument lists of procedures in interface
88 blocks because they are self-contained scoping units.
90 Since a dummy argument cannot be a non-dummy procedure, the only
91 resort left for untyped names are the IMPLICIT types. */
93 static void
94 resolve_formal_arglist (gfc_symbol *proc)
96 gfc_formal_arglist *f;
97 gfc_symbol *sym;
98 int i;
100 if (proc->result != NULL)
101 sym = proc->result;
102 else
103 sym = proc;
105 if (gfc_elemental (proc)
106 || sym->attr.pointer || sym->attr.allocatable
107 || (sym->as && sym->as->rank > 0))
108 proc->attr.always_explicit = 1;
110 formal_arg_flag = 1;
112 for (f = proc->formal; f; f = f->next)
114 sym = f->sym;
116 if (sym == NULL)
118 /* Alternate return placeholder. */
119 if (gfc_elemental (proc))
120 gfc_error ("Alternate return specifier in elemental subroutine "
121 "'%s' at %L is not allowed", proc->name,
122 &proc->declared_at);
123 if (proc->attr.function)
124 gfc_error ("Alternate return specifier in function "
125 "'%s' at %L is not allowed", proc->name,
126 &proc->declared_at);
127 continue;
130 if (sym->attr.if_source != IFSRC_UNKNOWN)
131 resolve_formal_arglist (sym);
133 if (sym->attr.subroutine || sym->attr.external || sym->attr.intrinsic)
135 if (gfc_pure (proc) && !gfc_pure (sym))
137 gfc_error ("Dummy procedure '%s' of PURE procedure at %L must "
138 "also be PURE", sym->name, &sym->declared_at);
139 continue;
142 if (gfc_elemental (proc))
144 gfc_error ("Dummy procedure at %L not allowed in ELEMENTAL "
145 "procedure", &sym->declared_at);
146 continue;
149 if (sym->attr.function
150 && sym->ts.type == BT_UNKNOWN
151 && sym->attr.intrinsic)
153 gfc_intrinsic_sym *isym;
154 isym = gfc_find_function (sym->name);
155 if (isym == NULL || !isym->specific)
157 gfc_error ("Unable to find a specific INTRINSIC procedure "
158 "for the reference '%s' at %L", sym->name,
159 &sym->declared_at);
161 sym->ts = isym->ts;
164 continue;
167 if (sym->ts.type == BT_UNKNOWN)
169 if (!sym->attr.function || sym->result == sym)
170 gfc_set_default_type (sym, 1, sym->ns);
173 gfc_resolve_array_spec (sym->as, 0);
175 /* We can't tell if an array with dimension (:) is assumed or deferred
176 shape until we know if it has the pointer or allocatable attributes.
178 if (sym->as && sym->as->rank > 0 && sym->as->type == AS_DEFERRED
179 && !(sym->attr.pointer || sym->attr.allocatable))
181 sym->as->type = AS_ASSUMED_SHAPE;
182 for (i = 0; i < sym->as->rank; i++)
183 sym->as->lower[i] = gfc_int_expr (1);
186 if ((sym->as && sym->as->rank > 0 && sym->as->type == AS_ASSUMED_SHAPE)
187 || sym->attr.pointer || sym->attr.allocatable || sym->attr.target
188 || sym->attr.optional)
189 proc->attr.always_explicit = 1;
191 /* If the flavor is unknown at this point, it has to be a variable.
192 A procedure specification would have already set the type. */
194 if (sym->attr.flavor == FL_UNKNOWN)
195 gfc_add_flavor (&sym->attr, FL_VARIABLE, sym->name, &sym->declared_at);
197 if (gfc_pure (proc) && !sym->attr.pointer
198 && sym->attr.flavor != FL_PROCEDURE)
200 if (proc->attr.function && sym->attr.intent != INTENT_IN)
201 gfc_error ("Argument '%s' of pure function '%s' at %L must be "
202 "INTENT(IN)", sym->name, proc->name,
203 &sym->declared_at);
205 if (proc->attr.subroutine && sym->attr.intent == INTENT_UNKNOWN)
206 gfc_error ("Argument '%s' of pure subroutine '%s' at %L must "
207 "have its INTENT specified", sym->name, proc->name,
208 &sym->declared_at);
211 if (gfc_elemental (proc))
213 if (sym->as != NULL)
215 gfc_error ("Argument '%s' of elemental procedure at %L must "
216 "be scalar", sym->name, &sym->declared_at);
217 continue;
220 if (sym->attr.pointer)
222 gfc_error ("Argument '%s' of elemental procedure at %L cannot "
223 "have the POINTER attribute", sym->name,
224 &sym->declared_at);
225 continue;
229 /* Each dummy shall be specified to be scalar. */
230 if (proc->attr.proc == PROC_ST_FUNCTION)
232 if (sym->as != NULL)
234 gfc_error ("Argument '%s' of statement function at %L must "
235 "be scalar", sym->name, &sym->declared_at);
236 continue;
239 if (sym->ts.type == BT_CHARACTER)
241 gfc_charlen *cl = sym->ts.cl;
242 if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
244 gfc_error ("Character-valued argument '%s' of statement "
245 "function at %L must have constant length",
246 sym->name, &sym->declared_at);
247 continue;
252 formal_arg_flag = 0;
256 /* Work function called when searching for symbols that have argument lists
257 associated with them. */
259 static void
260 find_arglists (gfc_symbol *sym)
262 if (sym->attr.if_source == IFSRC_UNKNOWN || sym->ns != gfc_current_ns)
263 return;
265 resolve_formal_arglist (sym);
269 /* Given a namespace, resolve all formal argument lists within the namespace.
272 static void
273 resolve_formal_arglists (gfc_namespace *ns)
275 if (ns == NULL)
276 return;
278 gfc_traverse_ns (ns, find_arglists);
282 static void
283 resolve_contained_fntype (gfc_symbol *sym, gfc_namespace *ns)
285 try t;
287 /* If this namespace is not a function, ignore it. */
288 if (! sym || !(sym->attr.function || sym->attr.flavor == FL_VARIABLE))
289 return;
291 /* Try to find out of what the return type is. */
292 if (sym->result->ts.type == BT_UNKNOWN)
294 t = gfc_set_default_type (sym->result, 0, ns);
296 if (t == FAILURE && !sym->result->attr.untyped)
298 if (sym->result == sym)
299 gfc_error ("Contained function '%s' at %L has no IMPLICIT type",
300 sym->name, &sym->declared_at);
301 else
302 gfc_error ("Result '%s' of contained function '%s' at %L has "
303 "no IMPLICIT type", sym->result->name, sym->name,
304 &sym->result->declared_at);
305 sym->result->attr.untyped = 1;
309 /* Fortran 95 Draft Standard, page 51, Section 5.1.1.5, on the Character
310 type, lists the only ways a character length value of * can be used:
311 dummy arguments of procedures, named constants, and function results
312 in external functions. Internal function results are not on that list;
313 ergo, not permitted. */
315 if (sym->result->ts.type == BT_CHARACTER)
317 gfc_charlen *cl = sym->result->ts.cl;
318 if (!cl || !cl->length)
319 gfc_error ("Character-valued internal function '%s' at %L must "
320 "not be assumed length", sym->name, &sym->declared_at);
325 /* Add NEW_ARGS to the formal argument list of PROC, taking care not to
326 introduce duplicates. */
328 static void
329 merge_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
331 gfc_formal_arglist *f, *new_arglist;
332 gfc_symbol *new_sym;
334 for (; new_args != NULL; new_args = new_args->next)
336 new_sym = new_args->sym;
337 /* See if this arg is already in the formal argument list. */
338 for (f = proc->formal; f; f = f->next)
340 if (new_sym == f->sym)
341 break;
344 if (f)
345 continue;
347 /* Add a new argument. Argument order is not important. */
348 new_arglist = gfc_get_formal_arglist ();
349 new_arglist->sym = new_sym;
350 new_arglist->next = proc->formal;
351 proc->formal = new_arglist;
356 /* Flag the arguments that are not present in all entries. */
358 static void
359 check_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
361 gfc_formal_arglist *f, *head;
362 head = new_args;
364 for (f = proc->formal; f; f = f->next)
366 if (f->sym == NULL)
367 continue;
369 for (new_args = head; new_args; new_args = new_args->next)
371 if (new_args->sym == f->sym)
372 break;
375 if (new_args)
376 continue;
378 f->sym->attr.not_always_present = 1;
383 /* Resolve alternate entry points. If a symbol has multiple entry points we
384 create a new master symbol for the main routine, and turn the existing
385 symbol into an entry point. */
387 static void
388 resolve_entries (gfc_namespace *ns)
390 gfc_namespace *old_ns;
391 gfc_code *c;
392 gfc_symbol *proc;
393 gfc_entry_list *el;
394 char name[GFC_MAX_SYMBOL_LEN + 1];
395 static int master_count = 0;
397 if (ns->proc_name == NULL)
398 return;
400 /* No need to do anything if this procedure doesn't have alternate entry
401 points. */
402 if (!ns->entries)
403 return;
405 /* We may already have resolved alternate entry points. */
406 if (ns->proc_name->attr.entry_master)
407 return;
409 /* If this isn't a procedure something has gone horribly wrong. */
410 gcc_assert (ns->proc_name->attr.flavor == FL_PROCEDURE);
412 /* Remember the current namespace. */
413 old_ns = gfc_current_ns;
415 gfc_current_ns = ns;
417 /* Add the main entry point to the list of entry points. */
418 el = gfc_get_entry_list ();
419 el->sym = ns->proc_name;
420 el->id = 0;
421 el->next = ns->entries;
422 ns->entries = el;
423 ns->proc_name->attr.entry = 1;
425 /* If it is a module function, it needs to be in the right namespace
426 so that gfc_get_fake_result_decl can gather up the results. The
427 need for this arose in get_proc_name, where these beasts were
428 left in their own namespace, to keep prior references linked to
429 the entry declaration.*/
430 if (ns->proc_name->attr.function
431 && ns->parent && ns->parent->proc_name->attr.flavor == FL_MODULE)
432 el->sym->ns = ns;
434 /* Add an entry statement for it. */
435 c = gfc_get_code ();
436 c->op = EXEC_ENTRY;
437 c->ext.entry = el;
438 c->next = ns->code;
439 ns->code = c;
441 /* Create a new symbol for the master function. */
442 /* Give the internal function a unique name (within this file).
443 Also include the function name so the user has some hope of figuring
444 out what is going on. */
445 snprintf (name, GFC_MAX_SYMBOL_LEN, "master.%d.%s",
446 master_count++, ns->proc_name->name);
447 gfc_get_ha_symbol (name, &proc);
448 gcc_assert (proc != NULL);
450 gfc_add_procedure (&proc->attr, PROC_INTERNAL, proc->name, NULL);
451 if (ns->proc_name->attr.subroutine)
452 gfc_add_subroutine (&proc->attr, proc->name, NULL);
453 else
455 gfc_symbol *sym;
456 gfc_typespec *ts, *fts;
457 gfc_array_spec *as, *fas;
458 gfc_add_function (&proc->attr, proc->name, NULL);
459 proc->result = proc;
460 fas = ns->entries->sym->as;
461 fas = fas ? fas : ns->entries->sym->result->as;
462 fts = &ns->entries->sym->result->ts;
463 if (fts->type == BT_UNKNOWN)
464 fts = gfc_get_default_type (ns->entries->sym->result, NULL);
465 for (el = ns->entries->next; el; el = el->next)
467 ts = &el->sym->result->ts;
468 as = el->sym->as;
469 as = as ? as : el->sym->result->as;
470 if (ts->type == BT_UNKNOWN)
471 ts = gfc_get_default_type (el->sym->result, NULL);
473 if (! gfc_compare_types (ts, fts)
474 || (el->sym->result->attr.dimension
475 != ns->entries->sym->result->attr.dimension)
476 || (el->sym->result->attr.pointer
477 != ns->entries->sym->result->attr.pointer))
478 break;
480 else if (as && fas && gfc_compare_array_spec (as, fas) == 0)
481 gfc_error ("Procedure %s at %L has entries with mismatched "
482 "array specifications", ns->entries->sym->name,
483 &ns->entries->sym->declared_at);
486 if (el == NULL)
488 sym = ns->entries->sym->result;
489 /* All result types the same. */
490 proc->ts = *fts;
491 if (sym->attr.dimension)
492 gfc_set_array_spec (proc, gfc_copy_array_spec (sym->as), NULL);
493 if (sym->attr.pointer)
494 gfc_add_pointer (&proc->attr, NULL);
496 else
498 /* Otherwise the result will be passed through a union by
499 reference. */
500 proc->attr.mixed_entry_master = 1;
501 for (el = ns->entries; el; el = el->next)
503 sym = el->sym->result;
504 if (sym->attr.dimension)
506 if (el == ns->entries)
507 gfc_error ("FUNCTION result %s can't be an array in "
508 "FUNCTION %s at %L", sym->name,
509 ns->entries->sym->name, &sym->declared_at);
510 else
511 gfc_error ("ENTRY result %s can't be an array in "
512 "FUNCTION %s at %L", sym->name,
513 ns->entries->sym->name, &sym->declared_at);
515 else if (sym->attr.pointer)
517 if (el == ns->entries)
518 gfc_error ("FUNCTION result %s can't be a POINTER in "
519 "FUNCTION %s at %L", sym->name,
520 ns->entries->sym->name, &sym->declared_at);
521 else
522 gfc_error ("ENTRY result %s can't be a POINTER in "
523 "FUNCTION %s at %L", sym->name,
524 ns->entries->sym->name, &sym->declared_at);
526 else
528 ts = &sym->ts;
529 if (ts->type == BT_UNKNOWN)
530 ts = gfc_get_default_type (sym, NULL);
531 switch (ts->type)
533 case BT_INTEGER:
534 if (ts->kind == gfc_default_integer_kind)
535 sym = NULL;
536 break;
537 case BT_REAL:
538 if (ts->kind == gfc_default_real_kind
539 || ts->kind == gfc_default_double_kind)
540 sym = NULL;
541 break;
542 case BT_COMPLEX:
543 if (ts->kind == gfc_default_complex_kind)
544 sym = NULL;
545 break;
546 case BT_LOGICAL:
547 if (ts->kind == gfc_default_logical_kind)
548 sym = NULL;
549 break;
550 case BT_UNKNOWN:
551 /* We will issue error elsewhere. */
552 sym = NULL;
553 break;
554 default:
555 break;
557 if (sym)
559 if (el == ns->entries)
560 gfc_error ("FUNCTION result %s can't be of type %s "
561 "in FUNCTION %s at %L", sym->name,
562 gfc_typename (ts), ns->entries->sym->name,
563 &sym->declared_at);
564 else
565 gfc_error ("ENTRY result %s can't be of type %s "
566 "in FUNCTION %s at %L", sym->name,
567 gfc_typename (ts), ns->entries->sym->name,
568 &sym->declared_at);
574 proc->attr.access = ACCESS_PRIVATE;
575 proc->attr.entry_master = 1;
577 /* Merge all the entry point arguments. */
578 for (el = ns->entries; el; el = el->next)
579 merge_argument_lists (proc, el->sym->formal);
581 /* Check the master formal arguments for any that are not
582 present in all entry points. */
583 for (el = ns->entries; el; el = el->next)
584 check_argument_lists (proc, el->sym->formal);
586 /* Use the master function for the function body. */
587 ns->proc_name = proc;
589 /* Finalize the new symbols. */
590 gfc_commit_symbols ();
592 /* Restore the original namespace. */
593 gfc_current_ns = old_ns;
597 /* Resolve contained function types. Because contained functions can call one
598 another, they have to be worked out before any of the contained procedures
599 can be resolved.
601 The good news is that if a function doesn't already have a type, the only
602 way it can get one is through an IMPLICIT type or a RESULT variable, because
603 by definition contained functions are contained namespace they're contained
604 in, not in a sibling or parent namespace. */
606 static void
607 resolve_contained_functions (gfc_namespace *ns)
609 gfc_namespace *child;
610 gfc_entry_list *el;
612 resolve_formal_arglists (ns);
614 for (child = ns->contained; child; child = child->sibling)
616 /* Resolve alternate entry points first. */
617 resolve_entries (child);
619 /* Then check function return types. */
620 resolve_contained_fntype (child->proc_name, child);
621 for (el = child->entries; el; el = el->next)
622 resolve_contained_fntype (el->sym, child);
627 /* Resolve all of the elements of a structure constructor and make sure that
628 the types are correct. */
630 static try
631 resolve_structure_cons (gfc_expr *expr)
633 gfc_constructor *cons;
634 gfc_component *comp;
635 try t;
636 symbol_attribute a;
638 t = SUCCESS;
639 cons = expr->value.constructor;
640 /* A constructor may have references if it is the result of substituting a
641 parameter variable. In this case we just pull out the component we
642 want. */
643 if (expr->ref)
644 comp = expr->ref->u.c.sym->components;
645 else
646 comp = expr->ts.derived->components;
648 for (; comp; comp = comp->next, cons = cons->next)
650 if (!cons->expr)
651 continue;
653 if (gfc_resolve_expr (cons->expr) == FAILURE)
655 t = FAILURE;
656 continue;
659 if (cons->expr->expr_type != EXPR_NULL
660 && comp->as && comp->as->rank != cons->expr->rank
661 && (comp->allocatable || cons->expr->rank))
663 gfc_error ("The rank of the element in the derived type "
664 "constructor at %L does not match that of the "
665 "component (%d/%d)", &cons->expr->where,
666 cons->expr->rank, comp->as ? comp->as->rank : 0);
667 t = FAILURE;
670 /* If we don't have the right type, try to convert it. */
672 if (!gfc_compare_types (&cons->expr->ts, &comp->ts))
674 t = FAILURE;
675 if (comp->pointer && cons->expr->ts.type != BT_UNKNOWN)
676 gfc_error ("The element in the derived type constructor at %L, "
677 "for pointer component '%s', is %s but should be %s",
678 &cons->expr->where, comp->name,
679 gfc_basic_typename (cons->expr->ts.type),
680 gfc_basic_typename (comp->ts.type));
681 else
682 t = gfc_convert_type (cons->expr, &comp->ts, 1);
685 if (!comp->pointer || cons->expr->expr_type == EXPR_NULL)
686 continue;
688 a = gfc_expr_attr (cons->expr);
690 if (!a.pointer && !a.target)
692 t = FAILURE;
693 gfc_error ("The element in the derived type constructor at %L, "
694 "for pointer component '%s' should be a POINTER or "
695 "a TARGET", &cons->expr->where, comp->name);
699 return t;
703 /****************** Expression name resolution ******************/
705 /* Returns 0 if a symbol was not declared with a type or
706 attribute declaration statement, nonzero otherwise. */
708 static int
709 was_declared (gfc_symbol *sym)
711 symbol_attribute a;
713 a = sym->attr;
715 if (!a.implicit_type && sym->ts.type != BT_UNKNOWN)
716 return 1;
718 if (a.allocatable || a.dimension || a.dummy || a.external || a.intrinsic
719 || a.optional || a.pointer || a.save || a.target || a.volatile_
720 || a.value || a.access != ACCESS_UNKNOWN || a.intent != INTENT_UNKNOWN)
721 return 1;
723 return 0;
727 /* Determine if a symbol is generic or not. */
729 static int
730 generic_sym (gfc_symbol *sym)
732 gfc_symbol *s;
734 if (sym->attr.generic ||
735 (sym->attr.intrinsic && gfc_generic_intrinsic (sym->name)))
736 return 1;
738 if (was_declared (sym) || sym->ns->parent == NULL)
739 return 0;
741 gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
743 return (s == NULL) ? 0 : generic_sym (s);
747 /* Determine if a symbol is specific or not. */
749 static int
750 specific_sym (gfc_symbol *sym)
752 gfc_symbol *s;
754 if (sym->attr.if_source == IFSRC_IFBODY
755 || sym->attr.proc == PROC_MODULE
756 || sym->attr.proc == PROC_INTERNAL
757 || sym->attr.proc == PROC_ST_FUNCTION
758 || (sym->attr.intrinsic && gfc_specific_intrinsic (sym->name))
759 || sym->attr.external)
760 return 1;
762 if (was_declared (sym) || sym->ns->parent == NULL)
763 return 0;
765 gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
767 return (s == NULL) ? 0 : specific_sym (s);
771 /* Figure out if the procedure is specific, generic or unknown. */
773 typedef enum
774 { PTYPE_GENERIC = 1, PTYPE_SPECIFIC, PTYPE_UNKNOWN }
775 proc_type;
777 static proc_type
778 procedure_kind (gfc_symbol *sym)
780 if (generic_sym (sym))
781 return PTYPE_GENERIC;
783 if (specific_sym (sym))
784 return PTYPE_SPECIFIC;
786 return PTYPE_UNKNOWN;
789 /* Check references to assumed size arrays. The flag need_full_assumed_size
790 is nonzero when matching actual arguments. */
792 static int need_full_assumed_size = 0;
794 static bool
795 check_assumed_size_reference (gfc_symbol *sym, gfc_expr *e)
797 gfc_ref *ref;
798 int dim;
799 int last = 1;
801 if (need_full_assumed_size || !(sym->as && sym->as->type == AS_ASSUMED_SIZE))
802 return false;
804 for (ref = e->ref; ref; ref = ref->next)
805 if (ref->type == REF_ARRAY)
806 for (dim = 0; dim < ref->u.ar.as->rank; dim++)
807 last = (ref->u.ar.end[dim] == NULL)
808 && (ref->u.ar.type == DIMEN_ELEMENT);
810 if (last)
812 gfc_error ("The upper bound in the last dimension must "
813 "appear in the reference to the assumed size "
814 "array '%s' at %L", sym->name, &e->where);
815 return true;
817 return false;
821 /* Look for bad assumed size array references in argument expressions
822 of elemental and array valued intrinsic procedures. Since this is
823 called from procedure resolution functions, it only recurses at
824 operators. */
826 static bool
827 resolve_assumed_size_actual (gfc_expr *e)
829 if (e == NULL)
830 return false;
832 switch (e->expr_type)
834 case EXPR_VARIABLE:
835 if (e->symtree && check_assumed_size_reference (e->symtree->n.sym, e))
836 return true;
837 break;
839 case EXPR_OP:
840 if (resolve_assumed_size_actual (e->value.op.op1)
841 || resolve_assumed_size_actual (e->value.op.op2))
842 return true;
843 break;
845 default:
846 break;
848 return false;
852 /* Resolve an actual argument list. Most of the time, this is just
853 resolving the expressions in the list.
854 The exception is that we sometimes have to decide whether arguments
855 that look like procedure arguments are really simple variable
856 references. */
858 static try
859 resolve_actual_arglist (gfc_actual_arglist *arg, procedure_type ptype)
861 gfc_symbol *sym;
862 gfc_symtree *parent_st;
863 gfc_expr *e;
865 for (; arg; arg = arg->next)
867 e = arg->expr;
868 if (e == NULL)
870 /* Check the label is a valid branching target. */
871 if (arg->label)
873 if (arg->label->defined == ST_LABEL_UNKNOWN)
875 gfc_error ("Label %d referenced at %L is never defined",
876 arg->label->value, &arg->label->where);
877 return FAILURE;
880 continue;
883 if (e->ts.type != BT_PROCEDURE)
885 if (gfc_resolve_expr (e) != SUCCESS)
886 return FAILURE;
887 goto argument_list;
890 /* See if the expression node should really be a variable reference. */
892 sym = e->symtree->n.sym;
894 if (sym->attr.flavor == FL_PROCEDURE
895 || sym->attr.intrinsic
896 || sym->attr.external)
898 int actual_ok;
900 /* If a procedure is not already determined to be something else
901 check if it is intrinsic. */
902 if (!sym->attr.intrinsic
903 && !(sym->attr.external || sym->attr.use_assoc
904 || sym->attr.if_source == IFSRC_IFBODY)
905 && gfc_intrinsic_name (sym->name, sym->attr.subroutine))
906 sym->attr.intrinsic = 1;
908 if (sym->attr.proc == PROC_ST_FUNCTION)
910 gfc_error ("Statement function '%s' at %L is not allowed as an "
911 "actual argument", sym->name, &e->where);
914 actual_ok = gfc_intrinsic_actual_ok (sym->name,
915 sym->attr.subroutine);
916 if (sym->attr.intrinsic && actual_ok == 0)
918 gfc_error ("Intrinsic '%s' at %L is not allowed as an "
919 "actual argument", sym->name, &e->where);
922 if (sym->attr.contained && !sym->attr.use_assoc
923 && sym->ns->proc_name->attr.flavor != FL_MODULE)
925 gfc_error ("Internal procedure '%s' is not allowed as an "
926 "actual argument at %L", sym->name, &e->where);
929 if (sym->attr.elemental && !sym->attr.intrinsic)
931 gfc_error ("ELEMENTAL non-INTRINSIC procedure '%s' is not "
932 "allowed as an actual argument at %L", sym->name,
933 &e->where);
936 /* Check if a generic interface has a specific procedure
937 with the same name before emitting an error. */
938 if (sym->attr.generic)
940 gfc_interface *p;
941 for (p = sym->generic; p; p = p->next)
942 if (strcmp (sym->name, p->sym->name) == 0)
944 e->symtree = gfc_find_symtree
945 (p->sym->ns->sym_root, sym->name);
946 sym = p->sym;
947 break;
950 if (p == NULL || e->symtree == NULL)
951 gfc_error ("GENERIC non-INTRINSIC procedure '%s' is not "
952 "allowed as an actual argument at %L", sym->name,
953 &e->where);
956 /* If the symbol is the function that names the current (or
957 parent) scope, then we really have a variable reference. */
959 if (sym->attr.function && sym->result == sym
960 && (sym->ns->proc_name == sym
961 || (sym->ns->parent != NULL
962 && sym->ns->parent->proc_name == sym)))
963 goto got_variable;
965 /* If all else fails, see if we have a specific intrinsic. */
966 if (sym->attr.function
967 && sym->ts.type == BT_UNKNOWN && sym->attr.intrinsic)
969 gfc_intrinsic_sym *isym;
970 isym = gfc_find_function (sym->name);
971 if (isym == NULL || !isym->specific)
973 gfc_error ("Unable to find a specific INTRINSIC procedure "
974 "for the reference '%s' at %L", sym->name,
975 &e->where);
977 sym->ts = isym->ts;
979 goto argument_list;
982 /* See if the name is a module procedure in a parent unit. */
984 if (was_declared (sym) || sym->ns->parent == NULL)
985 goto got_variable;
987 if (gfc_find_sym_tree (sym->name, sym->ns->parent, 1, &parent_st))
989 gfc_error ("Symbol '%s' at %L is ambiguous", sym->name, &e->where);
990 return FAILURE;
993 if (parent_st == NULL)
994 goto got_variable;
996 sym = parent_st->n.sym;
997 e->symtree = parent_st; /* Point to the right thing. */
999 if (sym->attr.flavor == FL_PROCEDURE
1000 || sym->attr.intrinsic
1001 || sym->attr.external)
1003 goto argument_list;
1006 got_variable:
1007 e->expr_type = EXPR_VARIABLE;
1008 e->ts = sym->ts;
1009 if (sym->as != NULL)
1011 e->rank = sym->as->rank;
1012 e->ref = gfc_get_ref ();
1013 e->ref->type = REF_ARRAY;
1014 e->ref->u.ar.type = AR_FULL;
1015 e->ref->u.ar.as = sym->as;
1018 /* Expressions are assigned a default ts.type of BT_PROCEDURE in
1019 primary.c (match_actual_arg). If above code determines that it
1020 is a variable instead, it needs to be resolved as it was not
1021 done at the beginning of this function. */
1022 if (gfc_resolve_expr (e) != SUCCESS)
1023 return FAILURE;
1025 argument_list:
1026 /* Check argument list functions %VAL, %LOC and %REF. There is
1027 nothing to do for %REF. */
1028 if (arg->name && arg->name[0] == '%')
1030 if (strncmp ("%VAL", arg->name, 4) == 0)
1032 if (e->ts.type == BT_CHARACTER || e->ts.type == BT_DERIVED)
1034 gfc_error ("By-value argument at %L is not of numeric "
1035 "type", &e->where);
1036 return FAILURE;
1039 if (e->rank)
1041 gfc_error ("By-value argument at %L cannot be an array or "
1042 "an array section", &e->where);
1043 return FAILURE;
1046 /* Intrinsics are still PROC_UNKNOWN here. However,
1047 since same file external procedures are not resolvable
1048 in gfortran, it is a good deal easier to leave them to
1049 intrinsic.c. */
1050 if (ptype != PROC_UNKNOWN
1051 && ptype != PROC_DUMMY
1052 && ptype != PROC_EXTERNAL
1053 && ptype != PROC_MODULE)
1055 gfc_error ("By-value argument at %L is not allowed "
1056 "in this context", &e->where);
1057 return FAILURE;
1061 /* Statement functions have already been excluded above. */
1062 else if (strncmp ("%LOC", arg->name, 4) == 0
1063 && e->ts.type == BT_PROCEDURE)
1065 if (e->symtree->n.sym->attr.proc == PROC_INTERNAL)
1067 gfc_error ("Passing internal procedure at %L by location "
1068 "not allowed", &e->where);
1069 return FAILURE;
1075 return SUCCESS;
1079 /* Do the checks of the actual argument list that are specific to elemental
1080 procedures. If called with c == NULL, we have a function, otherwise if
1081 expr == NULL, we have a subroutine. */
1083 static try
1084 resolve_elemental_actual (gfc_expr *expr, gfc_code *c)
1086 gfc_actual_arglist *arg0;
1087 gfc_actual_arglist *arg;
1088 gfc_symbol *esym = NULL;
1089 gfc_intrinsic_sym *isym = NULL;
1090 gfc_expr *e = NULL;
1091 gfc_intrinsic_arg *iformal = NULL;
1092 gfc_formal_arglist *eformal = NULL;
1093 bool formal_optional = false;
1094 bool set_by_optional = false;
1095 int i;
1096 int rank = 0;
1098 /* Is this an elemental procedure? */
1099 if (expr && expr->value.function.actual != NULL)
1101 if (expr->value.function.esym != NULL
1102 && expr->value.function.esym->attr.elemental)
1104 arg0 = expr->value.function.actual;
1105 esym = expr->value.function.esym;
1107 else if (expr->value.function.isym != NULL
1108 && expr->value.function.isym->elemental)
1110 arg0 = expr->value.function.actual;
1111 isym = expr->value.function.isym;
1113 else
1114 return SUCCESS;
1116 else if (c && c->ext.actual != NULL && c->symtree->n.sym->attr.elemental)
1118 arg0 = c->ext.actual;
1119 esym = c->symtree->n.sym;
1121 else
1122 return SUCCESS;
1124 /* The rank of an elemental is the rank of its array argument(s). */
1125 for (arg = arg0; arg; arg = arg->next)
1127 if (arg->expr != NULL && arg->expr->rank > 0)
1129 rank = arg->expr->rank;
1130 if (arg->expr->expr_type == EXPR_VARIABLE
1131 && arg->expr->symtree->n.sym->attr.optional)
1132 set_by_optional = true;
1134 /* Function specific; set the result rank and shape. */
1135 if (expr)
1137 expr->rank = rank;
1138 if (!expr->shape && arg->expr->shape)
1140 expr->shape = gfc_get_shape (rank);
1141 for (i = 0; i < rank; i++)
1142 mpz_init_set (expr->shape[i], arg->expr->shape[i]);
1145 break;
1149 /* If it is an array, it shall not be supplied as an actual argument
1150 to an elemental procedure unless an array of the same rank is supplied
1151 as an actual argument corresponding to a nonoptional dummy argument of
1152 that elemental procedure(12.4.1.5). */
1153 formal_optional = false;
1154 if (isym)
1155 iformal = isym->formal;
1156 else
1157 eformal = esym->formal;
1159 for (arg = arg0; arg; arg = arg->next)
1161 if (eformal)
1163 if (eformal->sym && eformal->sym->attr.optional)
1164 formal_optional = true;
1165 eformal = eformal->next;
1167 else if (isym && iformal)
1169 if (iformal->optional)
1170 formal_optional = true;
1171 iformal = iformal->next;
1173 else if (isym)
1174 formal_optional = true;
1176 if (pedantic && arg->expr != NULL
1177 && arg->expr->expr_type == EXPR_VARIABLE
1178 && arg->expr->symtree->n.sym->attr.optional
1179 && formal_optional
1180 && arg->expr->rank
1181 && (set_by_optional || arg->expr->rank != rank)
1182 && !(isym && isym->id == GFC_ISYM_CONVERSION))
1184 gfc_warning ("'%s' at %L is an array and OPTIONAL; IF IT IS "
1185 "MISSING, it cannot be the actual argument of an "
1186 "ELEMENTAL procedure unless there is a non-optional "
1187 "argument with the same rank (12.4.1.5)",
1188 arg->expr->symtree->n.sym->name, &arg->expr->where);
1189 return FAILURE;
1193 for (arg = arg0; arg; arg = arg->next)
1195 if (arg->expr == NULL || arg->expr->rank == 0)
1196 continue;
1198 /* Being elemental, the last upper bound of an assumed size array
1199 argument must be present. */
1200 if (resolve_assumed_size_actual (arg->expr))
1201 return FAILURE;
1203 if (expr)
1204 continue;
1206 /* Elemental subroutine array actual arguments must conform. */
1207 if (e != NULL)
1209 if (gfc_check_conformance ("elemental subroutine", arg->expr, e)
1210 == FAILURE)
1211 return FAILURE;
1213 else
1214 e = arg->expr;
1217 return SUCCESS;
1221 /* Go through each actual argument in ACTUAL and see if it can be
1222 implemented as an inlined, non-copying intrinsic. FNSYM is the
1223 function being called, or NULL if not known. */
1225 static void
1226 find_noncopying_intrinsics (gfc_symbol *fnsym, gfc_actual_arglist *actual)
1228 gfc_actual_arglist *ap;
1229 gfc_expr *expr;
1231 for (ap = actual; ap; ap = ap->next)
1232 if (ap->expr
1233 && (expr = gfc_get_noncopying_intrinsic_argument (ap->expr))
1234 && !gfc_check_fncall_dependency (expr, INTENT_IN, fnsym, actual))
1235 ap->expr->inline_noncopying_intrinsic = 1;
1239 /* This function does the checking of references to global procedures
1240 as defined in sections 18.1 and 14.1, respectively, of the Fortran
1241 77 and 95 standards. It checks for a gsymbol for the name, making
1242 one if it does not already exist. If it already exists, then the
1243 reference being resolved must correspond to the type of gsymbol.
1244 Otherwise, the new symbol is equipped with the attributes of the
1245 reference. The corresponding code that is called in creating
1246 global entities is parse.c. */
1248 static void
1249 resolve_global_procedure (gfc_symbol *sym, locus *where, int sub)
1251 gfc_gsymbol * gsym;
1252 unsigned int type;
1254 type = sub ? GSYM_SUBROUTINE : GSYM_FUNCTION;
1256 gsym = gfc_get_gsymbol (sym->name);
1258 if ((gsym->type != GSYM_UNKNOWN && gsym->type != type))
1259 global_used (gsym, where);
1261 if (gsym->type == GSYM_UNKNOWN)
1263 gsym->type = type;
1264 gsym->where = *where;
1267 gsym->used = 1;
1271 /************* Function resolution *************/
1273 /* Resolve a function call known to be generic.
1274 Section 14.1.2.4.1. */
1276 static match
1277 resolve_generic_f0 (gfc_expr *expr, gfc_symbol *sym)
1279 gfc_symbol *s;
1281 if (sym->attr.generic)
1283 s = gfc_search_interface (sym->generic, 0, &expr->value.function.actual);
1284 if (s != NULL)
1286 expr->value.function.name = s->name;
1287 expr->value.function.esym = s;
1289 if (s->ts.type != BT_UNKNOWN)
1290 expr->ts = s->ts;
1291 else if (s->result != NULL && s->result->ts.type != BT_UNKNOWN)
1292 expr->ts = s->result->ts;
1294 if (s->as != NULL)
1295 expr->rank = s->as->rank;
1296 else if (s->result != NULL && s->result->as != NULL)
1297 expr->rank = s->result->as->rank;
1299 return MATCH_YES;
1302 /* TODO: Need to search for elemental references in generic
1303 interface. */
1306 if (sym->attr.intrinsic)
1307 return gfc_intrinsic_func_interface (expr, 0);
1309 return MATCH_NO;
1313 static try
1314 resolve_generic_f (gfc_expr *expr)
1316 gfc_symbol *sym;
1317 match m;
1319 sym = expr->symtree->n.sym;
1321 for (;;)
1323 m = resolve_generic_f0 (expr, sym);
1324 if (m == MATCH_YES)
1325 return SUCCESS;
1326 else if (m == MATCH_ERROR)
1327 return FAILURE;
1329 generic:
1330 if (sym->ns->parent == NULL)
1331 break;
1332 gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
1334 if (sym == NULL)
1335 break;
1336 if (!generic_sym (sym))
1337 goto generic;
1340 /* Last ditch attempt. See if the reference is to an intrinsic
1341 that possesses a matching interface. 14.1.2.4 */
1342 if (sym && !gfc_intrinsic_name (sym->name, 0))
1344 gfc_error ("There is no specific function for the generic '%s' at %L",
1345 expr->symtree->n.sym->name, &expr->where);
1346 return FAILURE;
1349 m = gfc_intrinsic_func_interface (expr, 0);
1350 if (m == MATCH_YES)
1351 return SUCCESS;
1352 if (m == MATCH_NO)
1353 gfc_error ("Generic function '%s' at %L is not consistent with a "
1354 "specific intrinsic interface", expr->symtree->n.sym->name,
1355 &expr->where);
1357 return FAILURE;
1361 /* Resolve a function call known to be specific. */
1363 static match
1364 resolve_specific_f0 (gfc_symbol *sym, gfc_expr *expr)
1366 match m;
1368 if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
1370 if (sym->attr.dummy)
1372 sym->attr.proc = PROC_DUMMY;
1373 goto found;
1376 sym->attr.proc = PROC_EXTERNAL;
1377 goto found;
1380 if (sym->attr.proc == PROC_MODULE
1381 || sym->attr.proc == PROC_ST_FUNCTION
1382 || sym->attr.proc == PROC_INTERNAL)
1383 goto found;
1385 if (sym->attr.intrinsic)
1387 m = gfc_intrinsic_func_interface (expr, 1);
1388 if (m == MATCH_YES)
1389 return MATCH_YES;
1390 if (m == MATCH_NO)
1391 gfc_error ("Function '%s' at %L is INTRINSIC but is not compatible "
1392 "with an intrinsic", sym->name, &expr->where);
1394 return MATCH_ERROR;
1397 return MATCH_NO;
1399 found:
1400 gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
1402 expr->ts = sym->ts;
1403 expr->value.function.name = sym->name;
1404 expr->value.function.esym = sym;
1405 if (sym->as != NULL)
1406 expr->rank = sym->as->rank;
1408 return MATCH_YES;
1412 static try
1413 resolve_specific_f (gfc_expr *expr)
1415 gfc_symbol *sym;
1416 match m;
1418 sym = expr->symtree->n.sym;
1420 for (;;)
1422 m = resolve_specific_f0 (sym, expr);
1423 if (m == MATCH_YES)
1424 return SUCCESS;
1425 if (m == MATCH_ERROR)
1426 return FAILURE;
1428 if (sym->ns->parent == NULL)
1429 break;
1431 gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
1433 if (sym == NULL)
1434 break;
1437 gfc_error ("Unable to resolve the specific function '%s' at %L",
1438 expr->symtree->n.sym->name, &expr->where);
1440 return SUCCESS;
1444 /* Resolve a procedure call not known to be generic nor specific. */
1446 static try
1447 resolve_unknown_f (gfc_expr *expr)
1449 gfc_symbol *sym;
1450 gfc_typespec *ts;
1452 sym = expr->symtree->n.sym;
1454 if (sym->attr.dummy)
1456 sym->attr.proc = PROC_DUMMY;
1457 expr->value.function.name = sym->name;
1458 goto set_type;
1461 /* See if we have an intrinsic function reference. */
1463 if (gfc_intrinsic_name (sym->name, 0))
1465 if (gfc_intrinsic_func_interface (expr, 1) == MATCH_YES)
1466 return SUCCESS;
1467 return FAILURE;
1470 /* The reference is to an external name. */
1472 sym->attr.proc = PROC_EXTERNAL;
1473 expr->value.function.name = sym->name;
1474 expr->value.function.esym = expr->symtree->n.sym;
1476 if (sym->as != NULL)
1477 expr->rank = sym->as->rank;
1479 /* Type of the expression is either the type of the symbol or the
1480 default type of the symbol. */
1482 set_type:
1483 gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
1485 if (sym->ts.type != BT_UNKNOWN)
1486 expr->ts = sym->ts;
1487 else
1489 ts = gfc_get_default_type (sym, sym->ns);
1491 if (ts->type == BT_UNKNOWN)
1493 gfc_error ("Function '%s' at %L has no IMPLICIT type",
1494 sym->name, &expr->where);
1495 return FAILURE;
1497 else
1498 expr->ts = *ts;
1501 return SUCCESS;
1505 /* Figure out if a function reference is pure or not. Also set the name
1506 of the function for a potential error message. Return nonzero if the
1507 function is PURE, zero if not. */
1509 static int
1510 pure_function (gfc_expr *e, const char **name)
1512 int pure;
1514 *name = NULL;
1516 if (e->symtree != NULL
1517 && e->symtree->n.sym != NULL
1518 && e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
1519 return 1;
1521 if (e->value.function.esym)
1523 pure = gfc_pure (e->value.function.esym);
1524 *name = e->value.function.esym->name;
1526 else if (e->value.function.isym)
1528 pure = e->value.function.isym->pure
1529 || e->value.function.isym->elemental;
1530 *name = e->value.function.isym->name;
1532 else
1534 /* Implicit functions are not pure. */
1535 pure = 0;
1536 *name = e->value.function.name;
1539 return pure;
1543 static try
1544 is_scalar_expr_ptr (gfc_expr *expr)
1546 try retval = SUCCESS;
1547 gfc_ref *ref;
1548 int start;
1549 int end;
1551 /* See if we have a gfc_ref, which means we have a substring, array
1552 reference, or a component. */
1553 if (expr->ref != NULL)
1555 ref = expr->ref;
1556 while (ref->next != NULL)
1557 ref = ref->next;
1559 switch (ref->type)
1561 case REF_SUBSTRING:
1562 if (ref->u.ss.length != NULL
1563 && ref->u.ss.length->length != NULL
1564 && ref->u.ss.start
1565 && ref->u.ss.start->expr_type == EXPR_CONSTANT
1566 && ref->u.ss.end
1567 && ref->u.ss.end->expr_type == EXPR_CONSTANT)
1569 start = (int) mpz_get_si (ref->u.ss.start->value.integer);
1570 end = (int) mpz_get_si (ref->u.ss.end->value.integer);
1571 if (end - start + 1 != 1)
1572 retval = FAILURE;
1574 else
1575 retval = FAILURE;
1576 break;
1577 case REF_ARRAY:
1578 if (ref->u.ar.type == AR_ELEMENT)
1579 retval = SUCCESS;
1580 else if (ref->u.ar.type == AR_FULL)
1582 /* The user can give a full array if the array is of size 1. */
1583 if (ref->u.ar.as != NULL
1584 && ref->u.ar.as->rank == 1
1585 && ref->u.ar.as->type == AS_EXPLICIT
1586 && ref->u.ar.as->lower[0] != NULL
1587 && ref->u.ar.as->lower[0]->expr_type == EXPR_CONSTANT
1588 && ref->u.ar.as->upper[0] != NULL
1589 && ref->u.ar.as->upper[0]->expr_type == EXPR_CONSTANT)
1591 /* If we have a character string, we need to check if
1592 its length is one. */
1593 if (expr->ts.type == BT_CHARACTER)
1595 if (expr->ts.cl == NULL
1596 || expr->ts.cl->length == NULL
1597 || mpz_cmp_si (expr->ts.cl->length->value.integer, 1)
1598 != 0)
1599 retval = FAILURE;
1601 else
1603 /* We have constant lower and upper bounds. If the
1604 difference between is 1, it can be considered a
1605 scalar. */
1606 start = (int) mpz_get_si
1607 (ref->u.ar.as->lower[0]->value.integer);
1608 end = (int) mpz_get_si
1609 (ref->u.ar.as->upper[0]->value.integer);
1610 if (end - start + 1 != 1)
1611 retval = FAILURE;
1614 else
1615 retval = FAILURE;
1617 else
1618 retval = FAILURE;
1619 break;
1620 default:
1621 retval = SUCCESS;
1622 break;
1625 else if (expr->ts.type == BT_CHARACTER && expr->rank == 0)
1627 /* Character string. Make sure it's of length 1. */
1628 if (expr->ts.cl == NULL
1629 || expr->ts.cl->length == NULL
1630 || mpz_cmp_si (expr->ts.cl->length->value.integer, 1) != 0)
1631 retval = FAILURE;
1633 else if (expr->rank != 0)
1634 retval = FAILURE;
1636 return retval;
1640 /* Match one of the iso_c_binding functions (c_associated or c_loc)
1641 and, in the case of c_associated, set the binding label based on
1642 the arguments. */
1644 static try
1645 gfc_iso_c_func_interface (gfc_symbol *sym, gfc_actual_arglist *args,
1646 gfc_symbol **new_sym)
1648 char name[GFC_MAX_SYMBOL_LEN + 1];
1649 char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
1650 int optional_arg = 0;
1651 try retval = SUCCESS;
1652 gfc_symbol *args_sym;
1654 args_sym = args->expr->symtree->n.sym;
1656 if (sym->intmod_sym_id == ISOCBINDING_ASSOCIATED)
1658 /* If the user gave two args then they are providing something for
1659 the optional arg (the second cptr). Therefore, set the name and
1660 binding label to the c_associated for two cptrs. Otherwise,
1661 set c_associated to expect one cptr. */
1662 if (args->next)
1664 /* two args. */
1665 sprintf (name, "%s_2", sym->name);
1666 sprintf (binding_label, "%s_2", sym->binding_label);
1667 optional_arg = 1;
1669 else
1671 /* one arg. */
1672 sprintf (name, "%s_1", sym->name);
1673 sprintf (binding_label, "%s_1", sym->binding_label);
1674 optional_arg = 0;
1677 /* Get a new symbol for the version of c_associated that
1678 will get called. */
1679 *new_sym = get_iso_c_sym (sym, name, binding_label, optional_arg);
1681 else if (sym->intmod_sym_id == ISOCBINDING_LOC
1682 || sym->intmod_sym_id == ISOCBINDING_FUNLOC)
1684 sprintf (name, "%s", sym->name);
1685 sprintf (binding_label, "%s", sym->binding_label);
1687 /* Error check the call. */
1688 if (args->next != NULL)
1690 gfc_error_now ("More actual than formal arguments in '%s' "
1691 "call at %L", name, &(args->expr->where));
1692 retval = FAILURE;
1694 else if (sym->intmod_sym_id == ISOCBINDING_LOC)
1696 /* Make sure we have either the target or pointer attribute. */
1697 if (!(args->expr->symtree->n.sym->attr.target)
1698 && !(args->expr->symtree->n.sym->attr.pointer))
1700 gfc_error_now ("Parameter '%s' to '%s' at %L must be either "
1701 "a TARGET or an associated pointer",
1702 args->expr->symtree->n.sym->name,
1703 sym->name, &(args->expr->where));
1704 retval = FAILURE;
1707 /* See if we have interoperable type and type param. */
1708 if (verify_c_interop (&(args->expr->symtree->n.sym->ts),
1709 args->expr->symtree->n.sym->name,
1710 &(args->expr->where)) == SUCCESS
1711 || gfc_check_any_c_kind (&(args_sym->ts)) == SUCCESS)
1713 if (args_sym->attr.target == 1)
1715 /* Case 1a, section 15.1.2.5, J3/04-007: variable that
1716 has the target attribute and is interoperable. */
1717 /* Case 1b, section 15.1.2.5, J3/04-007: allocated
1718 allocatable variable that has the TARGET attribute and
1719 is not an array of zero size. */
1720 if (args_sym->attr.allocatable == 1)
1722 if (args_sym->attr.dimension != 0
1723 && (args_sym->as && args_sym->as->rank == 0))
1725 gfc_error_now ("Allocatable variable '%s' used as a "
1726 "parameter to '%s' at %L must not be "
1727 "an array of zero size",
1728 args_sym->name, sym->name,
1729 &(args->expr->where));
1730 retval = FAILURE;
1733 else
1735 /* Make sure it's not a character string. Arrays of
1736 any type should be ok if the variable is of a C
1737 interoperable type. */
1738 if (args_sym->ts.type == BT_CHARACTER
1739 && is_scalar_expr_ptr (args->expr) != SUCCESS)
1741 gfc_error_now ("CHARACTER argument '%s' to '%s' at "
1742 "%L must have a length of 1",
1743 args_sym->name, sym->name,
1744 &(args->expr->where));
1745 retval = FAILURE;
1749 else if (args_sym->attr.pointer == 1
1750 && is_scalar_expr_ptr (args->expr) != SUCCESS)
1752 /* Case 1c, section 15.1.2.5, J3/04-007: an associated
1753 scalar pointer. */
1754 gfc_error_now ("Argument '%s' to '%s' at %L must be an "
1755 "associated scalar POINTER", args_sym->name,
1756 sym->name, &(args->expr->where));
1757 retval = FAILURE;
1760 else
1762 /* The parameter is not required to be C interoperable. If it
1763 is not C interoperable, it must be a nonpolymorphic scalar
1764 with no length type parameters. It still must have either
1765 the pointer or target attribute, and it can be
1766 allocatable (but must be allocated when c_loc is called). */
1767 if (args_sym->attr.dimension != 0
1768 && is_scalar_expr_ptr (args->expr) != SUCCESS)
1770 gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
1771 "scalar", args_sym->name, sym->name,
1772 &(args->expr->where));
1773 retval = FAILURE;
1775 else if (args_sym->ts.type == BT_CHARACTER
1776 && args_sym->ts.cl != NULL)
1778 gfc_error_now ("CHARACTER parameter '%s' to '%s' at %L "
1779 "cannot have a length type parameter",
1780 args_sym->name, sym->name,
1781 &(args->expr->where));
1782 retval = FAILURE;
1786 else if (sym->intmod_sym_id == ISOCBINDING_FUNLOC)
1788 if (args->expr->symtree->n.sym->attr.flavor != FL_PROCEDURE)
1790 /* TODO: Update this error message to allow for procedure
1791 pointers once they are implemented. */
1792 gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
1793 "procedure",
1794 args->expr->symtree->n.sym->name, sym->name,
1795 &(args->expr->where));
1796 retval = FAILURE;
1798 else if (args->expr->symtree->n.sym->attr.is_c_interop != 1)
1800 gfc_error_now ("Parameter '%s' to '%s' at %L must be C "
1801 "interoperable",
1802 args->expr->symtree->n.sym->name, sym->name,
1803 &(args->expr->where));
1804 retval = FAILURE;
1808 /* for c_loc/c_funloc, the new symbol is the same as the old one */
1809 *new_sym = sym;
1811 else
1813 gfc_internal_error ("gfc_iso_c_func_interface(): Unhandled "
1814 "iso_c_binding function: '%s'!\n", sym->name);
1817 return retval;
1821 /* Resolve a function call, which means resolving the arguments, then figuring
1822 out which entity the name refers to. */
1823 /* TODO: Check procedure arguments so that an INTENT(IN) isn't passed
1824 to INTENT(OUT) or INTENT(INOUT). */
1826 static try
1827 resolve_function (gfc_expr *expr)
1829 gfc_actual_arglist *arg;
1830 gfc_symbol *sym;
1831 const char *name;
1832 try t;
1833 int temp;
1834 procedure_type p = PROC_INTRINSIC;
1836 sym = NULL;
1837 if (expr->symtree)
1838 sym = expr->symtree->n.sym;
1840 if (sym && sym->attr.flavor == FL_VARIABLE)
1842 gfc_error ("'%s' at %L is not a function", sym->name, &expr->where);
1843 return FAILURE;
1846 /* If the procedure is not internal, a statement function or a module
1847 procedure,it must be external and should be checked for usage. */
1848 if (sym && !sym->attr.dummy && !sym->attr.contained
1849 && sym->attr.proc != PROC_ST_FUNCTION
1850 && !sym->attr.use_assoc
1851 && sym->name )
1852 resolve_global_procedure (sym, &expr->where, 0);
1854 /* Switch off assumed size checking and do this again for certain kinds
1855 of procedure, once the procedure itself is resolved. */
1856 need_full_assumed_size++;
1858 if (expr->symtree && expr->symtree->n.sym)
1859 p = expr->symtree->n.sym->attr.proc;
1861 if (resolve_actual_arglist (expr->value.function.actual, p) == FAILURE)
1862 return FAILURE;
1864 /* Need to setup the call to the correct c_associated, depending on
1865 the number of cptrs to user gives to compare. */
1866 if (sym && sym->attr.is_iso_c == 1)
1868 if (gfc_iso_c_func_interface (sym, expr->value.function.actual, &sym)
1869 == FAILURE)
1870 return FAILURE;
1872 /* Get the symtree for the new symbol (resolved func).
1873 the old one will be freed later, when it's no longer used. */
1874 gfc_find_sym_tree (sym->name, sym->ns, 1, &(expr->symtree));
1877 /* Resume assumed_size checking. */
1878 need_full_assumed_size--;
1880 if (sym && sym->ts.type == BT_CHARACTER
1881 && sym->ts.cl
1882 && sym->ts.cl->length == NULL
1883 && !sym->attr.dummy
1884 && expr->value.function.esym == NULL
1885 && !sym->attr.contained)
1887 /* Internal procedures are taken care of in resolve_contained_fntype. */
1888 gfc_error ("Function '%s' is declared CHARACTER(*) and cannot "
1889 "be used at %L since it is not a dummy argument",
1890 sym->name, &expr->where);
1891 return FAILURE;
1894 /* See if function is already resolved. */
1896 if (expr->value.function.name != NULL)
1898 if (expr->ts.type == BT_UNKNOWN)
1899 expr->ts = sym->ts;
1900 t = SUCCESS;
1902 else
1904 /* Apply the rules of section 14.1.2. */
1906 switch (procedure_kind (sym))
1908 case PTYPE_GENERIC:
1909 t = resolve_generic_f (expr);
1910 break;
1912 case PTYPE_SPECIFIC:
1913 t = resolve_specific_f (expr);
1914 break;
1916 case PTYPE_UNKNOWN:
1917 t = resolve_unknown_f (expr);
1918 break;
1920 default:
1921 gfc_internal_error ("resolve_function(): bad function type");
1925 /* If the expression is still a function (it might have simplified),
1926 then we check to see if we are calling an elemental function. */
1928 if (expr->expr_type != EXPR_FUNCTION)
1929 return t;
1931 temp = need_full_assumed_size;
1932 need_full_assumed_size = 0;
1934 if (resolve_elemental_actual (expr, NULL) == FAILURE)
1935 return FAILURE;
1937 if (omp_workshare_flag
1938 && expr->value.function.esym
1939 && ! gfc_elemental (expr->value.function.esym))
1941 gfc_error ("User defined non-ELEMENTAL function '%s' at %L not allowed "
1942 "in WORKSHARE construct", expr->value.function.esym->name,
1943 &expr->where);
1944 t = FAILURE;
1947 #define GENERIC_ID expr->value.function.isym->id
1948 else if (expr->value.function.actual != NULL
1949 && expr->value.function.isym != NULL
1950 && GENERIC_ID != GFC_ISYM_LBOUND
1951 && GENERIC_ID != GFC_ISYM_LEN
1952 && GENERIC_ID != GFC_ISYM_LOC
1953 && GENERIC_ID != GFC_ISYM_PRESENT)
1955 /* Array intrinsics must also have the last upper bound of an
1956 assumed size array argument. UBOUND and SIZE have to be
1957 excluded from the check if the second argument is anything
1958 than a constant. */
1959 int inquiry;
1960 inquiry = GENERIC_ID == GFC_ISYM_UBOUND
1961 || GENERIC_ID == GFC_ISYM_SIZE;
1963 for (arg = expr->value.function.actual; arg; arg = arg->next)
1965 if (inquiry && arg->next != NULL && arg->next->expr)
1967 if (arg->next->expr->expr_type != EXPR_CONSTANT)
1968 break;
1970 if ((int)mpz_get_si (arg->next->expr->value.integer)
1971 < arg->expr->rank)
1972 break;
1975 if (arg->expr != NULL
1976 && arg->expr->rank > 0
1977 && resolve_assumed_size_actual (arg->expr))
1978 return FAILURE;
1981 #undef GENERIC_ID
1983 need_full_assumed_size = temp;
1984 name = NULL;
1986 if (!pure_function (expr, &name) && name)
1988 if (forall_flag)
1990 gfc_error ("reference to non-PURE function '%s' at %L inside a "
1991 "FORALL %s", name, &expr->where,
1992 forall_flag == 2 ? "mask" : "block");
1993 t = FAILURE;
1995 else if (gfc_pure (NULL))
1997 gfc_error ("Function reference to '%s' at %L is to a non-PURE "
1998 "procedure within a PURE procedure", name, &expr->where);
1999 t = FAILURE;
2003 /* Functions without the RECURSIVE attribution are not allowed to
2004 * call themselves. */
2005 if (expr->value.function.esym && !expr->value.function.esym->attr.recursive)
2007 gfc_symbol *esym, *proc;
2008 esym = expr->value.function.esym;
2009 proc = gfc_current_ns->proc_name;
2010 if (esym == proc)
2012 gfc_error ("Function '%s' at %L cannot call itself, as it is not "
2013 "RECURSIVE", name, &expr->where);
2014 t = FAILURE;
2017 if (esym->attr.entry && esym->ns->entries && proc->ns->entries
2018 && esym->ns->entries->sym == proc->ns->entries->sym)
2020 gfc_error ("Call to ENTRY '%s' at %L is recursive, but function "
2021 "'%s' is not declared as RECURSIVE",
2022 esym->name, &expr->where, esym->ns->entries->sym->name);
2023 t = FAILURE;
2027 /* Character lengths of use associated functions may contains references to
2028 symbols not referenced from the current program unit otherwise. Make sure
2029 those symbols are marked as referenced. */
2031 if (expr->ts.type == BT_CHARACTER && expr->value.function.esym
2032 && expr->value.function.esym->attr.use_assoc)
2034 gfc_expr_set_symbols_referenced (expr->ts.cl->length);
2037 if (t == SUCCESS)
2038 find_noncopying_intrinsics (expr->value.function.esym,
2039 expr->value.function.actual);
2041 /* Make sure that the expression has a typespec that works. */
2042 if (expr->ts.type == BT_UNKNOWN)
2044 if (expr->symtree->n.sym->result
2045 && expr->symtree->n.sym->result->ts.type != BT_UNKNOWN)
2046 expr->ts = expr->symtree->n.sym->result->ts;
2049 return t;
2053 /************* Subroutine resolution *************/
2055 static void
2056 pure_subroutine (gfc_code *c, gfc_symbol *sym)
2058 if (gfc_pure (sym))
2059 return;
2061 if (forall_flag)
2062 gfc_error ("Subroutine call to '%s' in FORALL block at %L is not PURE",
2063 sym->name, &c->loc);
2064 else if (gfc_pure (NULL))
2065 gfc_error ("Subroutine call to '%s' at %L is not PURE", sym->name,
2066 &c->loc);
2070 static match
2071 resolve_generic_s0 (gfc_code *c, gfc_symbol *sym)
2073 gfc_symbol *s;
2075 if (sym->attr.generic)
2077 s = gfc_search_interface (sym->generic, 1, &c->ext.actual);
2078 if (s != NULL)
2080 c->resolved_sym = s;
2081 pure_subroutine (c, s);
2082 return MATCH_YES;
2085 /* TODO: Need to search for elemental references in generic interface. */
2088 if (sym->attr.intrinsic)
2089 return gfc_intrinsic_sub_interface (c, 0);
2091 return MATCH_NO;
2095 static try
2096 resolve_generic_s (gfc_code *c)
2098 gfc_symbol *sym;
2099 match m;
2101 sym = c->symtree->n.sym;
2103 for (;;)
2105 m = resolve_generic_s0 (c, sym);
2106 if (m == MATCH_YES)
2107 return SUCCESS;
2108 else if (m == MATCH_ERROR)
2109 return FAILURE;
2111 generic:
2112 if (sym->ns->parent == NULL)
2113 break;
2114 gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2116 if (sym == NULL)
2117 break;
2118 if (!generic_sym (sym))
2119 goto generic;
2122 /* Last ditch attempt. See if the reference is to an intrinsic
2123 that possesses a matching interface. 14.1.2.4 */
2124 sym = c->symtree->n.sym;
2126 if (!gfc_intrinsic_name (sym->name, 1))
2128 gfc_error ("There is no specific subroutine for the generic '%s' at %L",
2129 sym->name, &c->loc);
2130 return FAILURE;
2133 m = gfc_intrinsic_sub_interface (c, 0);
2134 if (m == MATCH_YES)
2135 return SUCCESS;
2136 if (m == MATCH_NO)
2137 gfc_error ("Generic subroutine '%s' at %L is not consistent with an "
2138 "intrinsic subroutine interface", sym->name, &c->loc);
2140 return FAILURE;
2144 /* Set the name and binding label of the subroutine symbol in the call
2145 expression represented by 'c' to include the type and kind of the
2146 second parameter. This function is for resolving the appropriate
2147 version of c_f_pointer() and c_f_procpointer(). For example, a
2148 call to c_f_pointer() for a default integer pointer could have a
2149 name of c_f_pointer_i4. If no second arg exists, which is an error
2150 for these two functions, it defaults to the generic symbol's name
2151 and binding label. */
2153 static void
2154 set_name_and_label (gfc_code *c, gfc_symbol *sym,
2155 char *name, char *binding_label)
2157 gfc_expr *arg = NULL;
2158 char type;
2159 int kind;
2161 /* The second arg of c_f_pointer and c_f_procpointer determines
2162 the type and kind for the procedure name. */
2163 arg = c->ext.actual->next->expr;
2165 if (arg != NULL)
2167 /* Set up the name to have the given symbol's name,
2168 plus the type and kind. */
2169 /* a derived type is marked with the type letter 'u' */
2170 if (arg->ts.type == BT_DERIVED)
2172 type = 'd';
2173 kind = 0; /* set the kind as 0 for now */
2175 else
2177 type = gfc_type_letter (arg->ts.type);
2178 kind = arg->ts.kind;
2180 sprintf (name, "%s_%c%d", sym->name, type, kind);
2181 /* Set up the binding label as the given symbol's label plus
2182 the type and kind. */
2183 sprintf (binding_label, "%s_%c%d", sym->binding_label, type, kind);
2185 else
2187 /* If the second arg is missing, set the name and label as
2188 was, cause it should at least be found, and the missing
2189 arg error will be caught by compare_parameters(). */
2190 sprintf (name, "%s", sym->name);
2191 sprintf (binding_label, "%s", sym->binding_label);
2194 return;
2198 /* Resolve a generic version of the iso_c_binding procedure given
2199 (sym) to the specific one based on the type and kind of the
2200 argument(s). Currently, this function resolves c_f_pointer() and
2201 c_f_procpointer based on the type and kind of the second argument
2202 (FPTR). Other iso_c_binding procedures aren't specially handled.
2203 Upon successfully exiting, c->resolved_sym will hold the resolved
2204 symbol. Returns MATCH_ERROR if an error occurred; MATCH_YES
2205 otherwise. */
2207 match
2208 gfc_iso_c_sub_interface (gfc_code *c, gfc_symbol *sym)
2210 gfc_symbol *new_sym;
2211 /* this is fine, since we know the names won't use the max */
2212 char name[GFC_MAX_SYMBOL_LEN + 1];
2213 char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
2214 /* default to success; will override if find error */
2215 match m = MATCH_YES;
2216 gfc_symbol *tmp_sym;
2218 if ((sym->intmod_sym_id == ISOCBINDING_F_POINTER) ||
2219 (sym->intmod_sym_id == ISOCBINDING_F_PROCPOINTER))
2221 set_name_and_label (c, sym, name, binding_label);
2223 if (sym->intmod_sym_id == ISOCBINDING_F_POINTER)
2225 if (c->ext.actual != NULL && c->ext.actual->next != NULL)
2227 /* Make sure we got a third arg. The type/rank of it will
2228 be checked later if it's there (gfc_procedure_use()). */
2229 if (c->ext.actual->next->expr->rank != 0 &&
2230 c->ext.actual->next->next == NULL)
2232 m = MATCH_ERROR;
2233 gfc_error ("Missing SHAPE parameter for call to %s "
2234 "at %L", sym->name, &(c->loc));
2236 /* Make sure the param is a POINTER. No need to make sure
2237 it does not have INTENT(IN) since it is a POINTER. */
2238 tmp_sym = c->ext.actual->next->expr->symtree->n.sym;
2239 if (tmp_sym != NULL && tmp_sym->attr.pointer != 1)
2241 gfc_error ("Argument '%s' to '%s' at %L "
2242 "must have the POINTER attribute",
2243 tmp_sym->name, sym->name, &(c->loc));
2244 m = MATCH_ERROR;
2249 if (m != MATCH_ERROR)
2251 /* the 1 means to add the optional arg to formal list */
2252 new_sym = get_iso_c_sym (sym, name, binding_label, 1);
2254 /* for error reporting, say it's declared where the original was */
2255 new_sym->declared_at = sym->declared_at;
2258 else if (sym->intmod_sym_id == ISOCBINDING_ASSOCIATED)
2260 /* TODO: Figure out if this is even reacable; this part of the
2261 conditional may not be necessary. */
2262 int num_args = 0;
2263 if (c->ext.actual->next == NULL)
2265 /* The user did not give two args, so resolve to the version
2266 of c_associated expecting one arg. */
2267 num_args = 1;
2268 /* get rid of the second arg */
2269 /* TODO!! Should free up the memory here! */
2270 sym->formal->next = NULL;
2272 else
2274 num_args = 2;
2277 new_sym = sym;
2278 sprintf (name, "%s_%d", sym->name, num_args);
2279 sprintf (binding_label, "%s_%d", sym->binding_label, num_args);
2280 sym->name = gfc_get_string (name);
2281 strcpy (sym->binding_label, binding_label);
2283 else
2285 /* no differences for c_loc or c_funloc */
2286 new_sym = sym;
2289 /* set the resolved symbol */
2290 if (m != MATCH_ERROR)
2292 gfc_procedure_use (new_sym, &c->ext.actual, &c->loc);
2293 c->resolved_sym = new_sym;
2295 else
2296 c->resolved_sym = sym;
2298 return m;
2302 /* Resolve a subroutine call known to be specific. */
2304 static match
2305 resolve_specific_s0 (gfc_code *c, gfc_symbol *sym)
2307 match m;
2309 if(sym->attr.is_iso_c)
2311 m = gfc_iso_c_sub_interface (c,sym);
2312 return m;
2315 if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
2317 if (sym->attr.dummy)
2319 sym->attr.proc = PROC_DUMMY;
2320 goto found;
2323 sym->attr.proc = PROC_EXTERNAL;
2324 goto found;
2327 if (sym->attr.proc == PROC_MODULE || sym->attr.proc == PROC_INTERNAL)
2328 goto found;
2330 if (sym->attr.intrinsic)
2332 m = gfc_intrinsic_sub_interface (c, 1);
2333 if (m == MATCH_YES)
2334 return MATCH_YES;
2335 if (m == MATCH_NO)
2336 gfc_error ("Subroutine '%s' at %L is INTRINSIC but is not compatible "
2337 "with an intrinsic", sym->name, &c->loc);
2339 return MATCH_ERROR;
2342 return MATCH_NO;
2344 found:
2345 gfc_procedure_use (sym, &c->ext.actual, &c->loc);
2347 c->resolved_sym = sym;
2348 pure_subroutine (c, sym);
2350 return MATCH_YES;
2354 static try
2355 resolve_specific_s (gfc_code *c)
2357 gfc_symbol *sym;
2358 match m;
2360 sym = c->symtree->n.sym;
2362 for (;;)
2364 m = resolve_specific_s0 (c, sym);
2365 if (m == MATCH_YES)
2366 return SUCCESS;
2367 if (m == MATCH_ERROR)
2368 return FAILURE;
2370 if (sym->ns->parent == NULL)
2371 break;
2373 gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2375 if (sym == NULL)
2376 break;
2379 sym = c->symtree->n.sym;
2380 gfc_error ("Unable to resolve the specific subroutine '%s' at %L",
2381 sym->name, &c->loc);
2383 return FAILURE;
2387 /* Resolve a subroutine call not known to be generic nor specific. */
2389 static try
2390 resolve_unknown_s (gfc_code *c)
2392 gfc_symbol *sym;
2394 sym = c->symtree->n.sym;
2396 if (sym->attr.dummy)
2398 sym->attr.proc = PROC_DUMMY;
2399 goto found;
2402 /* See if we have an intrinsic function reference. */
2404 if (gfc_intrinsic_name (sym->name, 1))
2406 if (gfc_intrinsic_sub_interface (c, 1) == MATCH_YES)
2407 return SUCCESS;
2408 return FAILURE;
2411 /* The reference is to an external name. */
2413 found:
2414 gfc_procedure_use (sym, &c->ext.actual, &c->loc);
2416 c->resolved_sym = sym;
2418 pure_subroutine (c, sym);
2420 return SUCCESS;
2424 /* Resolve a subroutine call. Although it was tempting to use the same code
2425 for functions, subroutines and functions are stored differently and this
2426 makes things awkward. */
2428 static try
2429 resolve_call (gfc_code *c)
2431 try t;
2432 procedure_type ptype = PROC_INTRINSIC;
2434 if (c->symtree && c->symtree->n.sym
2435 && c->symtree->n.sym->ts.type != BT_UNKNOWN)
2437 gfc_error ("'%s' at %L has a type, which is not consistent with "
2438 "the CALL at %L", c->symtree->n.sym->name,
2439 &c->symtree->n.sym->declared_at, &c->loc);
2440 return FAILURE;
2443 /* If the procedure is not internal or module, it must be external and
2444 should be checked for usage. */
2445 if (c->symtree && c->symtree->n.sym
2446 && !c->symtree->n.sym->attr.dummy
2447 && !c->symtree->n.sym->attr.contained
2448 && !c->symtree->n.sym->attr.use_assoc)
2449 resolve_global_procedure (c->symtree->n.sym, &c->loc, 1);
2451 /* Subroutines without the RECURSIVE attribution are not allowed to
2452 * call themselves. */
2453 if (c->symtree && c->symtree->n.sym && !c->symtree->n.sym->attr.recursive)
2455 gfc_symbol *csym, *proc;
2456 csym = c->symtree->n.sym;
2457 proc = gfc_current_ns->proc_name;
2458 if (csym == proc)
2460 gfc_error ("SUBROUTINE '%s' at %L cannot call itself, as it is not "
2461 "RECURSIVE", csym->name, &c->loc);
2462 t = FAILURE;
2465 if (csym->attr.entry && csym->ns->entries && proc->ns->entries
2466 && csym->ns->entries->sym == proc->ns->entries->sym)
2468 gfc_error ("Call to ENTRY '%s' at %L is recursive, but subroutine "
2469 "'%s' is not declared as RECURSIVE",
2470 csym->name, &c->loc, csym->ns->entries->sym->name);
2471 t = FAILURE;
2475 /* Switch off assumed size checking and do this again for certain kinds
2476 of procedure, once the procedure itself is resolved. */
2477 need_full_assumed_size++;
2479 if (c->symtree && c->symtree->n.sym)
2480 ptype = c->symtree->n.sym->attr.proc;
2482 if (resolve_actual_arglist (c->ext.actual, ptype) == FAILURE)
2483 return FAILURE;
2485 /* Resume assumed_size checking. */
2486 need_full_assumed_size--;
2488 t = SUCCESS;
2489 if (c->resolved_sym == NULL)
2490 switch (procedure_kind (c->symtree->n.sym))
2492 case PTYPE_GENERIC:
2493 t = resolve_generic_s (c);
2494 break;
2496 case PTYPE_SPECIFIC:
2497 t = resolve_specific_s (c);
2498 break;
2500 case PTYPE_UNKNOWN:
2501 t = resolve_unknown_s (c);
2502 break;
2504 default:
2505 gfc_internal_error ("resolve_subroutine(): bad function type");
2508 /* Some checks of elemental subroutine actual arguments. */
2509 if (resolve_elemental_actual (NULL, c) == FAILURE)
2510 return FAILURE;
2512 if (t == SUCCESS)
2513 find_noncopying_intrinsics (c->resolved_sym, c->ext.actual);
2514 return t;
2518 /* Compare the shapes of two arrays that have non-NULL shapes. If both
2519 op1->shape and op2->shape are non-NULL return SUCCESS if their shapes
2520 match. If both op1->shape and op2->shape are non-NULL return FAILURE
2521 if their shapes do not match. If either op1->shape or op2->shape is
2522 NULL, return SUCCESS. */
2524 static try
2525 compare_shapes (gfc_expr *op1, gfc_expr *op2)
2527 try t;
2528 int i;
2530 t = SUCCESS;
2532 if (op1->shape != NULL && op2->shape != NULL)
2534 for (i = 0; i < op1->rank; i++)
2536 if (mpz_cmp (op1->shape[i], op2->shape[i]) != 0)
2538 gfc_error ("Shapes for operands at %L and %L are not conformable",
2539 &op1->where, &op2->where);
2540 t = FAILURE;
2541 break;
2546 return t;
2550 /* Resolve an operator expression node. This can involve replacing the
2551 operation with a user defined function call. */
2553 static try
2554 resolve_operator (gfc_expr *e)
2556 gfc_expr *op1, *op2;
2557 char msg[200];
2558 bool dual_locus_error;
2559 try t;
2561 /* Resolve all subnodes-- give them types. */
2563 switch (e->value.op.operator)
2565 default:
2566 if (gfc_resolve_expr (e->value.op.op2) == FAILURE)
2567 return FAILURE;
2569 /* Fall through... */
2571 case INTRINSIC_NOT:
2572 case INTRINSIC_UPLUS:
2573 case INTRINSIC_UMINUS:
2574 case INTRINSIC_PARENTHESES:
2575 if (gfc_resolve_expr (e->value.op.op1) == FAILURE)
2576 return FAILURE;
2577 break;
2580 /* Typecheck the new node. */
2582 op1 = e->value.op.op1;
2583 op2 = e->value.op.op2;
2584 dual_locus_error = false;
2586 switch (e->value.op.operator)
2588 case INTRINSIC_UPLUS:
2589 case INTRINSIC_UMINUS:
2590 if (op1->ts.type == BT_INTEGER
2591 || op1->ts.type == BT_REAL
2592 || op1->ts.type == BT_COMPLEX)
2594 e->ts = op1->ts;
2595 break;
2598 sprintf (msg, _("Operand of unary numeric operator '%s' at %%L is %s"),
2599 gfc_op2string (e->value.op.operator), gfc_typename (&e->ts));
2600 goto bad_op;
2602 case INTRINSIC_PLUS:
2603 case INTRINSIC_MINUS:
2604 case INTRINSIC_TIMES:
2605 case INTRINSIC_DIVIDE:
2606 case INTRINSIC_POWER:
2607 if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
2609 gfc_type_convert_binary (e);
2610 break;
2613 sprintf (msg,
2614 _("Operands of binary numeric operator '%s' at %%L are %s/%s"),
2615 gfc_op2string (e->value.op.operator), gfc_typename (&op1->ts),
2616 gfc_typename (&op2->ts));
2617 goto bad_op;
2619 case INTRINSIC_CONCAT:
2620 if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER)
2622 e->ts.type = BT_CHARACTER;
2623 e->ts.kind = op1->ts.kind;
2624 break;
2627 sprintf (msg,
2628 _("Operands of string concatenation operator at %%L are %s/%s"),
2629 gfc_typename (&op1->ts), gfc_typename (&op2->ts));
2630 goto bad_op;
2632 case INTRINSIC_AND:
2633 case INTRINSIC_OR:
2634 case INTRINSIC_EQV:
2635 case INTRINSIC_NEQV:
2636 if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
2638 e->ts.type = BT_LOGICAL;
2639 e->ts.kind = gfc_kind_max (op1, op2);
2640 if (op1->ts.kind < e->ts.kind)
2641 gfc_convert_type (op1, &e->ts, 2);
2642 else if (op2->ts.kind < e->ts.kind)
2643 gfc_convert_type (op2, &e->ts, 2);
2644 break;
2647 sprintf (msg, _("Operands of logical operator '%s' at %%L are %s/%s"),
2648 gfc_op2string (e->value.op.operator), gfc_typename (&op1->ts),
2649 gfc_typename (&op2->ts));
2651 goto bad_op;
2653 case INTRINSIC_NOT:
2654 if (op1->ts.type == BT_LOGICAL)
2656 e->ts.type = BT_LOGICAL;
2657 e->ts.kind = op1->ts.kind;
2658 break;
2661 sprintf (msg, _("Operand of .NOT. operator at %%L is %s"),
2662 gfc_typename (&op1->ts));
2663 goto bad_op;
2665 case INTRINSIC_GT:
2666 case INTRINSIC_GE:
2667 case INTRINSIC_LT:
2668 case INTRINSIC_LE:
2669 if (op1->ts.type == BT_COMPLEX || op2->ts.type == BT_COMPLEX)
2671 strcpy (msg, _("COMPLEX quantities cannot be compared at %L"));
2672 goto bad_op;
2675 /* Fall through... */
2677 case INTRINSIC_EQ:
2678 case INTRINSIC_NE:
2679 if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER)
2681 e->ts.type = BT_LOGICAL;
2682 e->ts.kind = gfc_default_logical_kind;
2683 break;
2686 if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
2688 gfc_type_convert_binary (e);
2690 e->ts.type = BT_LOGICAL;
2691 e->ts.kind = gfc_default_logical_kind;
2692 break;
2695 if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
2696 sprintf (msg,
2697 _("Logicals at %%L must be compared with %s instead of %s"),
2698 e->value.op.operator == INTRINSIC_EQ ? ".EQV." : ".NEQV.",
2699 gfc_op2string (e->value.op.operator));
2700 else
2701 sprintf (msg,
2702 _("Operands of comparison operator '%s' at %%L are %s/%s"),
2703 gfc_op2string (e->value.op.operator), gfc_typename (&op1->ts),
2704 gfc_typename (&op2->ts));
2706 goto bad_op;
2708 case INTRINSIC_USER:
2709 if (e->value.op.uop->operator == NULL)
2710 sprintf (msg, _("Unknown operator '%s' at %%L"), e->value.op.uop->name);
2711 else if (op2 == NULL)
2712 sprintf (msg, _("Operand of user operator '%s' at %%L is %s"),
2713 e->value.op.uop->name, gfc_typename (&op1->ts));
2714 else
2715 sprintf (msg, _("Operands of user operator '%s' at %%L are %s/%s"),
2716 e->value.op.uop->name, gfc_typename (&op1->ts),
2717 gfc_typename (&op2->ts));
2719 goto bad_op;
2721 case INTRINSIC_PARENTHESES:
2722 break;
2724 default:
2725 gfc_internal_error ("resolve_operator(): Bad intrinsic");
2728 /* Deal with arrayness of an operand through an operator. */
2730 t = SUCCESS;
2732 switch (e->value.op.operator)
2734 case INTRINSIC_PLUS:
2735 case INTRINSIC_MINUS:
2736 case INTRINSIC_TIMES:
2737 case INTRINSIC_DIVIDE:
2738 case INTRINSIC_POWER:
2739 case INTRINSIC_CONCAT:
2740 case INTRINSIC_AND:
2741 case INTRINSIC_OR:
2742 case INTRINSIC_EQV:
2743 case INTRINSIC_NEQV:
2744 case INTRINSIC_EQ:
2745 case INTRINSIC_NE:
2746 case INTRINSIC_GT:
2747 case INTRINSIC_GE:
2748 case INTRINSIC_LT:
2749 case INTRINSIC_LE:
2751 if (op1->rank == 0 && op2->rank == 0)
2752 e->rank = 0;
2754 if (op1->rank == 0 && op2->rank != 0)
2756 e->rank = op2->rank;
2758 if (e->shape == NULL)
2759 e->shape = gfc_copy_shape (op2->shape, op2->rank);
2762 if (op1->rank != 0 && op2->rank == 0)
2764 e->rank = op1->rank;
2766 if (e->shape == NULL)
2767 e->shape = gfc_copy_shape (op1->shape, op1->rank);
2770 if (op1->rank != 0 && op2->rank != 0)
2772 if (op1->rank == op2->rank)
2774 e->rank = op1->rank;
2775 if (e->shape == NULL)
2777 t = compare_shapes(op1, op2);
2778 if (t == FAILURE)
2779 e->shape = NULL;
2780 else
2781 e->shape = gfc_copy_shape (op1->shape, op1->rank);
2784 else
2786 /* Allow higher level expressions to work. */
2787 e->rank = 0;
2789 /* Try user-defined operators, and otherwise throw an error. */
2790 dual_locus_error = true;
2791 sprintf (msg,
2792 _("Inconsistent ranks for operator at %%L and %%L"));
2793 goto bad_op;
2797 break;
2799 case INTRINSIC_NOT:
2800 case INTRINSIC_UPLUS:
2801 case INTRINSIC_UMINUS:
2802 case INTRINSIC_PARENTHESES:
2803 e->rank = op1->rank;
2805 if (e->shape == NULL)
2806 e->shape = gfc_copy_shape (op1->shape, op1->rank);
2808 /* Simply copy arrayness attribute */
2809 break;
2811 default:
2812 break;
2815 /* Attempt to simplify the expression. */
2816 if (t == SUCCESS)
2818 t = gfc_simplify_expr (e, 0);
2819 /* Some calls do not succeed in simplification and return FAILURE
2820 even though there is no error; eg. variable references to
2821 PARAMETER arrays. */
2822 if (!gfc_is_constant_expr (e))
2823 t = SUCCESS;
2825 return t;
2827 bad_op:
2829 if (gfc_extend_expr (e) == SUCCESS)
2830 return SUCCESS;
2832 if (dual_locus_error)
2833 gfc_error (msg, &op1->where, &op2->where);
2834 else
2835 gfc_error (msg, &e->where);
2837 return FAILURE;
2841 /************** Array resolution subroutines **************/
2843 typedef enum
2844 { CMP_LT, CMP_EQ, CMP_GT, CMP_UNKNOWN }
2845 comparison;
2847 /* Compare two integer expressions. */
2849 static comparison
2850 compare_bound (gfc_expr *a, gfc_expr *b)
2852 int i;
2854 if (a == NULL || a->expr_type != EXPR_CONSTANT
2855 || b == NULL || b->expr_type != EXPR_CONSTANT)
2856 return CMP_UNKNOWN;
2858 if (a->ts.type != BT_INTEGER || b->ts.type != BT_INTEGER)
2859 gfc_internal_error ("compare_bound(): Bad expression");
2861 i = mpz_cmp (a->value.integer, b->value.integer);
2863 if (i < 0)
2864 return CMP_LT;
2865 if (i > 0)
2866 return CMP_GT;
2867 return CMP_EQ;
2871 /* Compare an integer expression with an integer. */
2873 static comparison
2874 compare_bound_int (gfc_expr *a, int b)
2876 int i;
2878 if (a == NULL || a->expr_type != EXPR_CONSTANT)
2879 return CMP_UNKNOWN;
2881 if (a->ts.type != BT_INTEGER)
2882 gfc_internal_error ("compare_bound_int(): Bad expression");
2884 i = mpz_cmp_si (a->value.integer, b);
2886 if (i < 0)
2887 return CMP_LT;
2888 if (i > 0)
2889 return CMP_GT;
2890 return CMP_EQ;
2894 /* Compare an integer expression with a mpz_t. */
2896 static comparison
2897 compare_bound_mpz_t (gfc_expr *a, mpz_t b)
2899 int i;
2901 if (a == NULL || a->expr_type != EXPR_CONSTANT)
2902 return CMP_UNKNOWN;
2904 if (a->ts.type != BT_INTEGER)
2905 gfc_internal_error ("compare_bound_int(): Bad expression");
2907 i = mpz_cmp (a->value.integer, b);
2909 if (i < 0)
2910 return CMP_LT;
2911 if (i > 0)
2912 return CMP_GT;
2913 return CMP_EQ;
2917 /* Compute the last value of a sequence given by a triplet.
2918 Return 0 if it wasn't able to compute the last value, or if the
2919 sequence if empty, and 1 otherwise. */
2921 static int
2922 compute_last_value_for_triplet (gfc_expr *start, gfc_expr *end,
2923 gfc_expr *stride, mpz_t last)
2925 mpz_t rem;
2927 if (start == NULL || start->expr_type != EXPR_CONSTANT
2928 || end == NULL || end->expr_type != EXPR_CONSTANT
2929 || (stride != NULL && stride->expr_type != EXPR_CONSTANT))
2930 return 0;
2932 if (start->ts.type != BT_INTEGER || end->ts.type != BT_INTEGER
2933 || (stride != NULL && stride->ts.type != BT_INTEGER))
2934 return 0;
2936 if (stride == NULL || compare_bound_int(stride, 1) == CMP_EQ)
2938 if (compare_bound (start, end) == CMP_GT)
2939 return 0;
2940 mpz_set (last, end->value.integer);
2941 return 1;
2944 if (compare_bound_int (stride, 0) == CMP_GT)
2946 /* Stride is positive */
2947 if (mpz_cmp (start->value.integer, end->value.integer) > 0)
2948 return 0;
2950 else
2952 /* Stride is negative */
2953 if (mpz_cmp (start->value.integer, end->value.integer) < 0)
2954 return 0;
2957 mpz_init (rem);
2958 mpz_sub (rem, end->value.integer, start->value.integer);
2959 mpz_tdiv_r (rem, rem, stride->value.integer);
2960 mpz_sub (last, end->value.integer, rem);
2961 mpz_clear (rem);
2963 return 1;
2967 /* Compare a single dimension of an array reference to the array
2968 specification. */
2970 static try
2971 check_dimension (int i, gfc_array_ref *ar, gfc_array_spec *as)
2973 mpz_t last_value;
2975 /* Given start, end and stride values, calculate the minimum and
2976 maximum referenced indexes. */
2978 switch (ar->type)
2980 case AR_FULL:
2981 break;
2983 case AR_ELEMENT:
2984 if (compare_bound (ar->start[i], as->lower[i]) == CMP_LT)
2985 goto bound;
2986 if (compare_bound (ar->start[i], as->upper[i]) == CMP_GT)
2987 goto bound;
2989 break;
2991 case AR_SECTION:
2993 #define AR_START (ar->start[i] ? ar->start[i] : as->lower[i])
2994 #define AR_END (ar->end[i] ? ar->end[i] : as->upper[i])
2996 comparison comp_start_end = compare_bound (AR_START, AR_END);
2998 /* Check for zero stride, which is not allowed. */
2999 if (compare_bound_int (ar->stride[i], 0) == CMP_EQ)
3001 gfc_error ("Illegal stride of zero at %L", &ar->c_where[i]);
3002 return FAILURE;
3005 /* if start == len || (stride > 0 && start < len)
3006 || (stride < 0 && start > len),
3007 then the array section contains at least one element. In this
3008 case, there is an out-of-bounds access if
3009 (start < lower || start > upper). */
3010 if (compare_bound (AR_START, AR_END) == CMP_EQ
3011 || ((compare_bound_int (ar->stride[i], 0) == CMP_GT
3012 || ar->stride[i] == NULL) && comp_start_end == CMP_LT)
3013 || (compare_bound_int (ar->stride[i], 0) == CMP_LT
3014 && comp_start_end == CMP_GT))
3016 if (compare_bound (AR_START, as->lower[i]) == CMP_LT
3017 || compare_bound (AR_START, as->upper[i]) == CMP_GT)
3018 goto bound;
3021 /* If we can compute the highest index of the array section,
3022 then it also has to be between lower and upper. */
3023 mpz_init (last_value);
3024 if (compute_last_value_for_triplet (AR_START, AR_END, ar->stride[i],
3025 last_value))
3027 if (compare_bound_mpz_t (as->lower[i], last_value) == CMP_GT
3028 || compare_bound_mpz_t (as->upper[i], last_value) == CMP_LT)
3030 mpz_clear (last_value);
3031 goto bound;
3034 mpz_clear (last_value);
3036 #undef AR_START
3037 #undef AR_END
3039 break;
3041 default:
3042 gfc_internal_error ("check_dimension(): Bad array reference");
3045 return SUCCESS;
3047 bound:
3048 gfc_warning ("Array reference at %L is out of bounds", &ar->c_where[i]);
3049 return SUCCESS;
3053 /* Compare an array reference with an array specification. */
3055 static try
3056 compare_spec_to_ref (gfc_array_ref *ar)
3058 gfc_array_spec *as;
3059 int i;
3061 as = ar->as;
3062 i = as->rank - 1;
3063 /* TODO: Full array sections are only allowed as actual parameters. */
3064 if (as->type == AS_ASSUMED_SIZE
3065 && (/*ar->type == AR_FULL
3066 ||*/ (ar->type == AR_SECTION
3067 && ar->dimen_type[i] == DIMEN_RANGE && ar->end[i] == NULL)))
3069 gfc_error ("Rightmost upper bound of assumed size array section "
3070 "not specified at %L", &ar->where);
3071 return FAILURE;
3074 if (ar->type == AR_FULL)
3075 return SUCCESS;
3077 if (as->rank != ar->dimen)
3079 gfc_error ("Rank mismatch in array reference at %L (%d/%d)",
3080 &ar->where, ar->dimen, as->rank);
3081 return FAILURE;
3084 for (i = 0; i < as->rank; i++)
3085 if (check_dimension (i, ar, as) == FAILURE)
3086 return FAILURE;
3088 return SUCCESS;
3092 /* Resolve one part of an array index. */
3095 gfc_resolve_index (gfc_expr *index, int check_scalar)
3097 gfc_typespec ts;
3099 if (index == NULL)
3100 return SUCCESS;
3102 if (gfc_resolve_expr (index) == FAILURE)
3103 return FAILURE;
3105 if (check_scalar && index->rank != 0)
3107 gfc_error ("Array index at %L must be scalar", &index->where);
3108 return FAILURE;
3111 if (index->ts.type != BT_INTEGER && index->ts.type != BT_REAL)
3113 gfc_error ("Array index at %L must be of INTEGER type",
3114 &index->where);
3115 return FAILURE;
3118 if (index->ts.type == BT_REAL)
3119 if (gfc_notify_std (GFC_STD_LEGACY, "Extension: REAL array index at %L",
3120 &index->where) == FAILURE)
3121 return FAILURE;
3123 if (index->ts.kind != gfc_index_integer_kind
3124 || index->ts.type != BT_INTEGER)
3126 gfc_clear_ts (&ts);
3127 ts.type = BT_INTEGER;
3128 ts.kind = gfc_index_integer_kind;
3130 gfc_convert_type_warn (index, &ts, 2, 0);
3133 return SUCCESS;
3136 /* Resolve a dim argument to an intrinsic function. */
3139 gfc_resolve_dim_arg (gfc_expr *dim)
3141 if (dim == NULL)
3142 return SUCCESS;
3144 if (gfc_resolve_expr (dim) == FAILURE)
3145 return FAILURE;
3147 if (dim->rank != 0)
3149 gfc_error ("Argument dim at %L must be scalar", &dim->where);
3150 return FAILURE;
3153 if (dim->ts.type != BT_INTEGER)
3155 gfc_error ("Argument dim at %L must be of INTEGER type", &dim->where);
3156 return FAILURE;
3158 if (dim->ts.kind != gfc_index_integer_kind)
3160 gfc_typespec ts;
3162 ts.type = BT_INTEGER;
3163 ts.kind = gfc_index_integer_kind;
3165 gfc_convert_type_warn (dim, &ts, 2, 0);
3168 return SUCCESS;
3171 /* Given an expression that contains array references, update those array
3172 references to point to the right array specifications. While this is
3173 filled in during matching, this information is difficult to save and load
3174 in a module, so we take care of it here.
3176 The idea here is that the original array reference comes from the
3177 base symbol. We traverse the list of reference structures, setting
3178 the stored reference to references. Component references can
3179 provide an additional array specification. */
3181 static void
3182 find_array_spec (gfc_expr *e)
3184 gfc_array_spec *as;
3185 gfc_component *c;
3186 gfc_symbol *derived;
3187 gfc_ref *ref;
3189 as = e->symtree->n.sym->as;
3190 derived = NULL;
3192 for (ref = e->ref; ref; ref = ref->next)
3193 switch (ref->type)
3195 case REF_ARRAY:
3196 if (as == NULL)
3197 gfc_internal_error ("find_array_spec(): Missing spec");
3199 ref->u.ar.as = as;
3200 as = NULL;
3201 break;
3203 case REF_COMPONENT:
3204 if (derived == NULL)
3205 derived = e->symtree->n.sym->ts.derived;
3207 c = derived->components;
3209 for (; c; c = c->next)
3210 if (c == ref->u.c.component)
3212 /* Track the sequence of component references. */
3213 if (c->ts.type == BT_DERIVED)
3214 derived = c->ts.derived;
3215 break;
3218 if (c == NULL)
3219 gfc_internal_error ("find_array_spec(): Component not found");
3221 if (c->dimension)
3223 if (as != NULL)
3224 gfc_internal_error ("find_array_spec(): unused as(1)");
3225 as = c->as;
3228 break;
3230 case REF_SUBSTRING:
3231 break;
3234 if (as != NULL)
3235 gfc_internal_error ("find_array_spec(): unused as(2)");
3239 /* Resolve an array reference. */
3241 static try
3242 resolve_array_ref (gfc_array_ref *ar)
3244 int i, check_scalar;
3245 gfc_expr *e;
3247 for (i = 0; i < ar->dimen; i++)
3249 check_scalar = ar->dimen_type[i] == DIMEN_RANGE;
3251 if (gfc_resolve_index (ar->start[i], check_scalar) == FAILURE)
3252 return FAILURE;
3253 if (gfc_resolve_index (ar->end[i], check_scalar) == FAILURE)
3254 return FAILURE;
3255 if (gfc_resolve_index (ar->stride[i], check_scalar) == FAILURE)
3256 return FAILURE;
3258 e = ar->start[i];
3260 if (ar->dimen_type[i] == DIMEN_UNKNOWN)
3261 switch (e->rank)
3263 case 0:
3264 ar->dimen_type[i] = DIMEN_ELEMENT;
3265 break;
3267 case 1:
3268 ar->dimen_type[i] = DIMEN_VECTOR;
3269 if (e->expr_type == EXPR_VARIABLE
3270 && e->symtree->n.sym->ts.type == BT_DERIVED)
3271 ar->start[i] = gfc_get_parentheses (e);
3272 break;
3274 default:
3275 gfc_error ("Array index at %L is an array of rank %d",
3276 &ar->c_where[i], e->rank);
3277 return FAILURE;
3281 /* If the reference type is unknown, figure out what kind it is. */
3283 if (ar->type == AR_UNKNOWN)
3285 ar->type = AR_ELEMENT;
3286 for (i = 0; i < ar->dimen; i++)
3287 if (ar->dimen_type[i] == DIMEN_RANGE
3288 || ar->dimen_type[i] == DIMEN_VECTOR)
3290 ar->type = AR_SECTION;
3291 break;
3295 if (!ar->as->cray_pointee && compare_spec_to_ref (ar) == FAILURE)
3296 return FAILURE;
3298 return SUCCESS;
3302 static try
3303 resolve_substring (gfc_ref *ref)
3305 if (ref->u.ss.start != NULL)
3307 if (gfc_resolve_expr (ref->u.ss.start) == FAILURE)
3308 return FAILURE;
3310 if (ref->u.ss.start->ts.type != BT_INTEGER)
3312 gfc_error ("Substring start index at %L must be of type INTEGER",
3313 &ref->u.ss.start->where);
3314 return FAILURE;
3317 if (ref->u.ss.start->rank != 0)
3319 gfc_error ("Substring start index at %L must be scalar",
3320 &ref->u.ss.start->where);
3321 return FAILURE;
3324 if (compare_bound_int (ref->u.ss.start, 1) == CMP_LT
3325 && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
3326 || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
3328 gfc_error ("Substring start index at %L is less than one",
3329 &ref->u.ss.start->where);
3330 return FAILURE;
3334 if (ref->u.ss.end != NULL)
3336 if (gfc_resolve_expr (ref->u.ss.end) == FAILURE)
3337 return FAILURE;
3339 if (ref->u.ss.end->ts.type != BT_INTEGER)
3341 gfc_error ("Substring end index at %L must be of type INTEGER",
3342 &ref->u.ss.end->where);
3343 return FAILURE;
3346 if (ref->u.ss.end->rank != 0)
3348 gfc_error ("Substring end index at %L must be scalar",
3349 &ref->u.ss.end->where);
3350 return FAILURE;
3353 if (ref->u.ss.length != NULL
3354 && compare_bound (ref->u.ss.end, ref->u.ss.length->length) == CMP_GT
3355 && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
3356 || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
3358 gfc_error ("Substring end index at %L exceeds the string length",
3359 &ref->u.ss.start->where);
3360 return FAILURE;
3364 return SUCCESS;
3368 /* Resolve subtype references. */
3370 static try
3371 resolve_ref (gfc_expr *expr)
3373 int current_part_dimension, n_components, seen_part_dimension;
3374 gfc_ref *ref;
3376 for (ref = expr->ref; ref; ref = ref->next)
3377 if (ref->type == REF_ARRAY && ref->u.ar.as == NULL)
3379 find_array_spec (expr);
3380 break;
3383 for (ref = expr->ref; ref; ref = ref->next)
3384 switch (ref->type)
3386 case REF_ARRAY:
3387 if (resolve_array_ref (&ref->u.ar) == FAILURE)
3388 return FAILURE;
3389 break;
3391 case REF_COMPONENT:
3392 break;
3394 case REF_SUBSTRING:
3395 resolve_substring (ref);
3396 break;
3399 /* Check constraints on part references. */
3401 current_part_dimension = 0;
3402 seen_part_dimension = 0;
3403 n_components = 0;
3405 for (ref = expr->ref; ref; ref = ref->next)
3407 switch (ref->type)
3409 case REF_ARRAY:
3410 switch (ref->u.ar.type)
3412 case AR_FULL:
3413 case AR_SECTION:
3414 current_part_dimension = 1;
3415 break;
3417 case AR_ELEMENT:
3418 current_part_dimension = 0;
3419 break;
3421 case AR_UNKNOWN:
3422 gfc_internal_error ("resolve_ref(): Bad array reference");
3425 break;
3427 case REF_COMPONENT:
3428 if (current_part_dimension || seen_part_dimension)
3430 if (ref->u.c.component->pointer)
3432 gfc_error ("Component to the right of a part reference "
3433 "with nonzero rank must not have the POINTER "
3434 "attribute at %L", &expr->where);
3435 return FAILURE;
3437 else if (ref->u.c.component->allocatable)
3439 gfc_error ("Component to the right of a part reference "
3440 "with nonzero rank must not have the ALLOCATABLE "
3441 "attribute at %L", &expr->where);
3442 return FAILURE;
3446 n_components++;
3447 break;
3449 case REF_SUBSTRING:
3450 break;
3453 if (((ref->type == REF_COMPONENT && n_components > 1)
3454 || ref->next == NULL)
3455 && current_part_dimension
3456 && seen_part_dimension)
3458 gfc_error ("Two or more part references with nonzero rank must "
3459 "not be specified at %L", &expr->where);
3460 return FAILURE;
3463 if (ref->type == REF_COMPONENT)
3465 if (current_part_dimension)
3466 seen_part_dimension = 1;
3468 /* reset to make sure */
3469 current_part_dimension = 0;
3473 return SUCCESS;
3477 /* Given an expression, determine its shape. This is easier than it sounds.
3478 Leaves the shape array NULL if it is not possible to determine the shape. */
3480 static void
3481 expression_shape (gfc_expr *e)
3483 mpz_t array[GFC_MAX_DIMENSIONS];
3484 int i;
3486 if (e->rank == 0 || e->shape != NULL)
3487 return;
3489 for (i = 0; i < e->rank; i++)
3490 if (gfc_array_dimen_size (e, i, &array[i]) == FAILURE)
3491 goto fail;
3493 e->shape = gfc_get_shape (e->rank);
3495 memcpy (e->shape, array, e->rank * sizeof (mpz_t));
3497 return;
3499 fail:
3500 for (i--; i >= 0; i--)
3501 mpz_clear (array[i]);
3505 /* Given a variable expression node, compute the rank of the expression by
3506 examining the base symbol and any reference structures it may have. */
3508 static void
3509 expression_rank (gfc_expr *e)
3511 gfc_ref *ref;
3512 int i, rank;
3514 if (e->ref == NULL)
3516 if (e->expr_type == EXPR_ARRAY)
3517 goto done;
3518 /* Constructors can have a rank different from one via RESHAPE(). */
3520 if (e->symtree == NULL)
3522 e->rank = 0;
3523 goto done;
3526 e->rank = (e->symtree->n.sym->as == NULL)
3527 ? 0 : e->symtree->n.sym->as->rank;
3528 goto done;
3531 rank = 0;
3533 for (ref = e->ref; ref; ref = ref->next)
3535 if (ref->type != REF_ARRAY)
3536 continue;
3538 if (ref->u.ar.type == AR_FULL)
3540 rank = ref->u.ar.as->rank;
3541 break;
3544 if (ref->u.ar.type == AR_SECTION)
3546 /* Figure out the rank of the section. */
3547 if (rank != 0)
3548 gfc_internal_error ("expression_rank(): Two array specs");
3550 for (i = 0; i < ref->u.ar.dimen; i++)
3551 if (ref->u.ar.dimen_type[i] == DIMEN_RANGE
3552 || ref->u.ar.dimen_type[i] == DIMEN_VECTOR)
3553 rank++;
3555 break;
3559 e->rank = rank;
3561 done:
3562 expression_shape (e);
3566 /* Resolve a variable expression. */
3568 static try
3569 resolve_variable (gfc_expr *e)
3571 gfc_symbol *sym;
3572 try t;
3574 t = SUCCESS;
3576 if (e->symtree == NULL)
3577 return FAILURE;
3579 if (e->ref && resolve_ref (e) == FAILURE)
3580 return FAILURE;
3582 sym = e->symtree->n.sym;
3583 if (sym->attr.flavor == FL_PROCEDURE && !sym->attr.function)
3585 e->ts.type = BT_PROCEDURE;
3586 return SUCCESS;
3589 if (sym->ts.type != BT_UNKNOWN)
3590 gfc_variable_attr (e, &e->ts);
3591 else
3593 /* Must be a simple variable reference. */
3594 if (gfc_set_default_type (sym, 1, sym->ns) == FAILURE)
3595 return FAILURE;
3596 e->ts = sym->ts;
3599 if (check_assumed_size_reference (sym, e))
3600 return FAILURE;
3602 /* Deal with forward references to entries during resolve_code, to
3603 satisfy, at least partially, 12.5.2.5. */
3604 if (gfc_current_ns->entries
3605 && current_entry_id == sym->entry_id
3606 && cs_base
3607 && cs_base->current
3608 && cs_base->current->op != EXEC_ENTRY)
3610 gfc_entry_list *entry;
3611 gfc_formal_arglist *formal;
3612 int n;
3613 bool seen;
3615 /* If the symbol is a dummy... */
3616 if (sym->attr.dummy)
3618 entry = gfc_current_ns->entries;
3619 seen = false;
3621 /* ...test if the symbol is a parameter of previous entries. */
3622 for (; entry && entry->id <= current_entry_id; entry = entry->next)
3623 for (formal = entry->sym->formal; formal; formal = formal->next)
3625 if (formal->sym && sym->name == formal->sym->name)
3626 seen = true;
3629 /* If it has not been seen as a dummy, this is an error. */
3630 if (!seen)
3632 if (specification_expr)
3633 gfc_error ("Variable '%s',used in a specification expression, "
3634 "is referenced at %L before the ENTRY statement "
3635 "in which it is a parameter",
3636 sym->name, &cs_base->current->loc);
3637 else
3638 gfc_error ("Variable '%s' is used at %L before the ENTRY "
3639 "statement in which it is a parameter",
3640 sym->name, &cs_base->current->loc);
3641 t = FAILURE;
3645 /* Now do the same check on the specification expressions. */
3646 specification_expr = 1;
3647 if (sym->ts.type == BT_CHARACTER
3648 && gfc_resolve_expr (sym->ts.cl->length) == FAILURE)
3649 t = FAILURE;
3651 if (sym->as)
3652 for (n = 0; n < sym->as->rank; n++)
3654 specification_expr = 1;
3655 if (gfc_resolve_expr (sym->as->lower[n]) == FAILURE)
3656 t = FAILURE;
3657 specification_expr = 1;
3658 if (gfc_resolve_expr (sym->as->upper[n]) == FAILURE)
3659 t = FAILURE;
3661 specification_expr = 0;
3663 if (t == SUCCESS)
3664 /* Update the symbol's entry level. */
3665 sym->entry_id = current_entry_id + 1;
3668 return t;
3672 /* Checks to see that the correct symbol has been host associated.
3673 The only situation where this arises is that in which a twice
3674 contained function is parsed after the host association is made.
3675 Therefore, on detecting this, the line is rematched, having got
3676 rid of the existing references and actual_arg_list. */
3677 static bool
3678 check_host_association (gfc_expr *e)
3680 gfc_symbol *sym, *old_sym;
3681 locus temp_locus;
3682 gfc_expr *expr;
3683 int n;
3684 bool retval = e->expr_type == EXPR_FUNCTION;
3686 if (e->symtree == NULL || e->symtree->n.sym == NULL)
3687 return retval;
3689 old_sym = e->symtree->n.sym;
3691 if (old_sym->attr.use_assoc)
3692 return retval;
3694 if (gfc_current_ns->parent
3695 && gfc_current_ns->parent->parent
3696 && old_sym->ns != gfc_current_ns)
3698 gfc_find_symbol (old_sym->name, gfc_current_ns->parent, 1, &sym);
3699 if (sym && old_sym != sym && sym->attr.flavor == FL_PROCEDURE)
3701 temp_locus = gfc_current_locus;
3702 gfc_current_locus = e->where;
3704 gfc_buffer_error (1);
3706 gfc_free_ref_list (e->ref);
3707 e->ref = NULL;
3709 if (retval)
3711 gfc_free_actual_arglist (e->value.function.actual);
3712 e->value.function.actual = NULL;
3715 if (e->shape != NULL)
3717 for (n = 0; n < e->rank; n++)
3718 mpz_clear (e->shape[n]);
3720 gfc_free (e->shape);
3723 gfc_match_rvalue (&expr);
3724 gfc_clear_error ();
3725 gfc_buffer_error (0);
3727 gcc_assert (expr && sym == expr->symtree->n.sym);
3729 *e = *expr;
3730 gfc_free (expr);
3731 sym->refs++;
3733 gfc_current_locus = temp_locus;
3736 /* This might have changed! */
3737 return e->expr_type == EXPR_FUNCTION;
3741 /* Resolve an expression. That is, make sure that types of operands agree
3742 with their operators, intrinsic operators are converted to function calls
3743 for overloaded types and unresolved function references are resolved. */
3746 gfc_resolve_expr (gfc_expr *e)
3748 try t;
3750 if (e == NULL)
3751 return SUCCESS;
3753 switch (e->expr_type)
3755 case EXPR_OP:
3756 t = resolve_operator (e);
3757 break;
3759 case EXPR_FUNCTION:
3760 case EXPR_VARIABLE:
3762 if (check_host_association (e))
3763 t = resolve_function (e);
3764 else
3766 t = resolve_variable (e);
3767 if (t == SUCCESS)
3768 expression_rank (e);
3770 break;
3772 case EXPR_SUBSTRING:
3773 t = resolve_ref (e);
3774 break;
3776 case EXPR_CONSTANT:
3777 case EXPR_NULL:
3778 t = SUCCESS;
3779 break;
3781 case EXPR_ARRAY:
3782 t = FAILURE;
3783 if (resolve_ref (e) == FAILURE)
3784 break;
3786 t = gfc_resolve_array_constructor (e);
3787 /* Also try to expand a constructor. */
3788 if (t == SUCCESS)
3790 expression_rank (e);
3791 gfc_expand_constructor (e);
3794 /* This provides the opportunity for the length of constructors with
3795 character valued function elements to propogate the string length
3796 to the expression. */
3797 if (e->ts.type == BT_CHARACTER)
3798 gfc_resolve_character_array_constructor (e);
3800 break;
3802 case EXPR_STRUCTURE:
3803 t = resolve_ref (e);
3804 if (t == FAILURE)
3805 break;
3807 t = resolve_structure_cons (e);
3808 if (t == FAILURE)
3809 break;
3811 t = gfc_simplify_expr (e, 0);
3812 break;
3814 default:
3815 gfc_internal_error ("gfc_resolve_expr(): Bad expression type");
3818 return t;
3822 /* Resolve an expression from an iterator. They must be scalar and have
3823 INTEGER or (optionally) REAL type. */
3825 static try
3826 gfc_resolve_iterator_expr (gfc_expr *expr, bool real_ok,
3827 const char *name_msgid)
3829 if (gfc_resolve_expr (expr) == FAILURE)
3830 return FAILURE;
3832 if (expr->rank != 0)
3834 gfc_error ("%s at %L must be a scalar", _(name_msgid), &expr->where);
3835 return FAILURE;
3838 if (expr->ts.type != BT_INTEGER)
3840 if (expr->ts.type == BT_REAL)
3842 if (real_ok)
3843 return gfc_notify_std (GFC_STD_F95_DEL,
3844 "Deleted feature: %s at %L must be integer",
3845 _(name_msgid), &expr->where);
3846 else
3848 gfc_error ("%s at %L must be INTEGER", _(name_msgid),
3849 &expr->where);
3850 return FAILURE;
3853 else
3855 gfc_error ("%s at %L must be INTEGER", _(name_msgid), &expr->where);
3856 return FAILURE;
3859 return SUCCESS;
3863 /* Resolve the expressions in an iterator structure. If REAL_OK is
3864 false allow only INTEGER type iterators, otherwise allow REAL types. */
3867 gfc_resolve_iterator (gfc_iterator *iter, bool real_ok)
3869 if (gfc_resolve_iterator_expr (iter->var, real_ok, "Loop variable")
3870 == FAILURE)
3871 return FAILURE;
3873 if (gfc_pure (NULL) && gfc_impure_variable (iter->var->symtree->n.sym))
3875 gfc_error ("Cannot assign to loop variable in PURE procedure at %L",
3876 &iter->var->where);
3877 return FAILURE;
3880 if (gfc_resolve_iterator_expr (iter->start, real_ok,
3881 "Start expression in DO loop") == FAILURE)
3882 return FAILURE;
3884 if (gfc_resolve_iterator_expr (iter->end, real_ok,
3885 "End expression in DO loop") == FAILURE)
3886 return FAILURE;
3888 if (gfc_resolve_iterator_expr (iter->step, real_ok,
3889 "Step expression in DO loop") == FAILURE)
3890 return FAILURE;
3892 if (iter->step->expr_type == EXPR_CONSTANT)
3894 if ((iter->step->ts.type == BT_INTEGER
3895 && mpz_cmp_ui (iter->step->value.integer, 0) == 0)
3896 || (iter->step->ts.type == BT_REAL
3897 && mpfr_sgn (iter->step->value.real) == 0))
3899 gfc_error ("Step expression in DO loop at %L cannot be zero",
3900 &iter->step->where);
3901 return FAILURE;
3905 /* Convert start, end, and step to the same type as var. */
3906 if (iter->start->ts.kind != iter->var->ts.kind
3907 || iter->start->ts.type != iter->var->ts.type)
3908 gfc_convert_type (iter->start, &iter->var->ts, 2);
3910 if (iter->end->ts.kind != iter->var->ts.kind
3911 || iter->end->ts.type != iter->var->ts.type)
3912 gfc_convert_type (iter->end, &iter->var->ts, 2);
3914 if (iter->step->ts.kind != iter->var->ts.kind
3915 || iter->step->ts.type != iter->var->ts.type)
3916 gfc_convert_type (iter->step, &iter->var->ts, 2);
3918 return SUCCESS;
3922 /* Resolve a list of FORALL iterators. The FORALL index-name is constrained
3923 to be a scalar INTEGER variable. The subscripts and stride are scalar
3924 INTEGERs, and if stride is a constant it must be nonzero. */
3926 static void
3927 resolve_forall_iterators (gfc_forall_iterator *iter)
3929 while (iter)
3931 if (gfc_resolve_expr (iter->var) == SUCCESS
3932 && (iter->var->ts.type != BT_INTEGER || iter->var->rank != 0))
3933 gfc_error ("FORALL index-name at %L must be a scalar INTEGER",
3934 &iter->var->where);
3936 if (gfc_resolve_expr (iter->start) == SUCCESS
3937 && (iter->start->ts.type != BT_INTEGER || iter->start->rank != 0))
3938 gfc_error ("FORALL start expression at %L must be a scalar INTEGER",
3939 &iter->start->where);
3940 if (iter->var->ts.kind != iter->start->ts.kind)
3941 gfc_convert_type (iter->start, &iter->var->ts, 2);
3943 if (gfc_resolve_expr (iter->end) == SUCCESS
3944 && (iter->end->ts.type != BT_INTEGER || iter->end->rank != 0))
3945 gfc_error ("FORALL end expression at %L must be a scalar INTEGER",
3946 &iter->end->where);
3947 if (iter->var->ts.kind != iter->end->ts.kind)
3948 gfc_convert_type (iter->end, &iter->var->ts, 2);
3950 if (gfc_resolve_expr (iter->stride) == SUCCESS)
3952 if (iter->stride->ts.type != BT_INTEGER || iter->stride->rank != 0)
3953 gfc_error ("FORALL stride expression at %L must be a scalar %s",
3954 &iter->stride->where, "INTEGER");
3956 if (iter->stride->expr_type == EXPR_CONSTANT
3957 && mpz_cmp_ui(iter->stride->value.integer, 0) == 0)
3958 gfc_error ("FORALL stride expression at %L cannot be zero",
3959 &iter->stride->where);
3961 if (iter->var->ts.kind != iter->stride->ts.kind)
3962 gfc_convert_type (iter->stride, &iter->var->ts, 2);
3964 iter = iter->next;
3969 /* Given a pointer to a symbol that is a derived type, see if any components
3970 have the POINTER attribute. The search is recursive if necessary.
3971 Returns zero if no pointer components are found, nonzero otherwise. */
3973 static int
3974 derived_pointer (gfc_symbol *sym)
3976 gfc_component *c;
3978 for (c = sym->components; c; c = c->next)
3980 if (c->pointer)
3981 return 1;
3983 if (c->ts.type == BT_DERIVED && derived_pointer (c->ts.derived))
3984 return 1;
3987 return 0;
3991 /* Given a pointer to a symbol that is a derived type, see if it's
3992 inaccessible, i.e. if it's defined in another module and the components are
3993 PRIVATE. The search is recursive if necessary. Returns zero if no
3994 inaccessible components are found, nonzero otherwise. */
3996 static int
3997 derived_inaccessible (gfc_symbol *sym)
3999 gfc_component *c;
4001 if (sym->attr.use_assoc && sym->component_access == ACCESS_PRIVATE)
4002 return 1;
4004 for (c = sym->components; c; c = c->next)
4006 if (c->ts.type == BT_DERIVED && derived_inaccessible (c->ts.derived))
4007 return 1;
4010 return 0;
4014 /* Resolve the argument of a deallocate expression. The expression must be
4015 a pointer or a full array. */
4017 static try
4018 resolve_deallocate_expr (gfc_expr *e)
4020 symbol_attribute attr;
4021 int allocatable, pointer, check_intent_in;
4022 gfc_ref *ref;
4024 /* Check INTENT(IN), unless the object is a sub-component of a pointer. */
4025 check_intent_in = 1;
4027 if (gfc_resolve_expr (e) == FAILURE)
4028 return FAILURE;
4030 if (e->expr_type != EXPR_VARIABLE)
4031 goto bad;
4033 allocatable = e->symtree->n.sym->attr.allocatable;
4034 pointer = e->symtree->n.sym->attr.pointer;
4035 for (ref = e->ref; ref; ref = ref->next)
4037 if (pointer)
4038 check_intent_in = 0;
4040 switch (ref->type)
4042 case REF_ARRAY:
4043 if (ref->u.ar.type != AR_FULL)
4044 allocatable = 0;
4045 break;
4047 case REF_COMPONENT:
4048 allocatable = (ref->u.c.component->as != NULL
4049 && ref->u.c.component->as->type == AS_DEFERRED);
4050 pointer = ref->u.c.component->pointer;
4051 break;
4053 case REF_SUBSTRING:
4054 allocatable = 0;
4055 break;
4059 attr = gfc_expr_attr (e);
4061 if (allocatable == 0 && attr.pointer == 0)
4063 bad:
4064 gfc_error ("Expression in DEALLOCATE statement at %L must be "
4065 "ALLOCATABLE or a POINTER", &e->where);
4068 if (check_intent_in
4069 && e->symtree->n.sym->attr.intent == INTENT_IN)
4071 gfc_error ("Cannot deallocate INTENT(IN) variable '%s' at %L",
4072 e->symtree->n.sym->name, &e->where);
4073 return FAILURE;
4076 return SUCCESS;
4080 /* Returns true if the expression e contains a reference the symbol sym. */
4081 static bool
4082 find_sym_in_expr (gfc_symbol *sym, gfc_expr *e)
4084 gfc_actual_arglist *arg;
4085 gfc_ref *ref;
4086 int i;
4087 bool rv = false;
4089 if (e == NULL)
4090 return rv;
4092 switch (e->expr_type)
4094 case EXPR_FUNCTION:
4095 for (arg = e->value.function.actual; arg; arg = arg->next)
4096 rv = rv || find_sym_in_expr (sym, arg->expr);
4097 break;
4099 /* If the variable is not the same as the dependent, 'sym', and
4100 it is not marked as being declared and it is in the same
4101 namespace as 'sym', add it to the local declarations. */
4102 case EXPR_VARIABLE:
4103 if (sym == e->symtree->n.sym)
4104 return true;
4105 break;
4107 case EXPR_OP:
4108 rv = rv || find_sym_in_expr (sym, e->value.op.op1);
4109 rv = rv || find_sym_in_expr (sym, e->value.op.op2);
4110 break;
4112 default:
4113 break;
4116 if (e->ref)
4118 for (ref = e->ref; ref; ref = ref->next)
4120 switch (ref->type)
4122 case REF_ARRAY:
4123 for (i = 0; i < ref->u.ar.dimen; i++)
4125 rv = rv || find_sym_in_expr (sym, ref->u.ar.start[i]);
4126 rv = rv || find_sym_in_expr (sym, ref->u.ar.end[i]);
4127 rv = rv || find_sym_in_expr (sym, ref->u.ar.stride[i]);
4129 break;
4131 case REF_SUBSTRING:
4132 rv = rv || find_sym_in_expr (sym, ref->u.ss.start);
4133 rv = rv || find_sym_in_expr (sym, ref->u.ss.end);
4134 break;
4136 case REF_COMPONENT:
4137 if (ref->u.c.component->ts.type == BT_CHARACTER
4138 && ref->u.c.component->ts.cl->length->expr_type
4139 != EXPR_CONSTANT)
4140 rv = rv
4141 || find_sym_in_expr (sym,
4142 ref->u.c.component->ts.cl->length);
4144 if (ref->u.c.component->as)
4145 for (i = 0; i < ref->u.c.component->as->rank; i++)
4147 rv = rv
4148 || find_sym_in_expr (sym,
4149 ref->u.c.component->as->lower[i]);
4150 rv = rv
4151 || find_sym_in_expr (sym,
4152 ref->u.c.component->as->upper[i]);
4154 break;
4158 return rv;
4162 /* Given the expression node e for an allocatable/pointer of derived type to be
4163 allocated, get the expression node to be initialized afterwards (needed for
4164 derived types with default initializers, and derived types with allocatable
4165 components that need nullification.) */
4167 static gfc_expr *
4168 expr_to_initialize (gfc_expr *e)
4170 gfc_expr *result;
4171 gfc_ref *ref;
4172 int i;
4174 result = gfc_copy_expr (e);
4176 /* Change the last array reference from AR_ELEMENT to AR_FULL. */
4177 for (ref = result->ref; ref; ref = ref->next)
4178 if (ref->type == REF_ARRAY && ref->next == NULL)
4180 ref->u.ar.type = AR_FULL;
4182 for (i = 0; i < ref->u.ar.dimen; i++)
4183 ref->u.ar.start[i] = ref->u.ar.end[i] = ref->u.ar.stride[i] = NULL;
4185 result->rank = ref->u.ar.dimen;
4186 break;
4189 return result;
4193 /* Resolve the expression in an ALLOCATE statement, doing the additional
4194 checks to see whether the expression is OK or not. The expression must
4195 have a trailing array reference that gives the size of the array. */
4197 static try
4198 resolve_allocate_expr (gfc_expr *e, gfc_code *code)
4200 int i, pointer, allocatable, dimension, check_intent_in;
4201 symbol_attribute attr;
4202 gfc_ref *ref, *ref2;
4203 gfc_array_ref *ar;
4204 gfc_code *init_st;
4205 gfc_expr *init_e;
4206 gfc_symbol *sym;
4207 gfc_alloc *a;
4209 /* Check INTENT(IN), unless the object is a sub-component of a pointer. */
4210 check_intent_in = 1;
4212 if (gfc_resolve_expr (e) == FAILURE)
4213 return FAILURE;
4215 if (code->expr && code->expr->expr_type == EXPR_VARIABLE)
4216 sym = code->expr->symtree->n.sym;
4217 else
4218 sym = NULL;
4220 /* Make sure the expression is allocatable or a pointer. If it is
4221 pointer, the next-to-last reference must be a pointer. */
4223 ref2 = NULL;
4225 if (e->expr_type != EXPR_VARIABLE)
4227 allocatable = 0;
4228 attr = gfc_expr_attr (e);
4229 pointer = attr.pointer;
4230 dimension = attr.dimension;
4232 else
4234 allocatable = e->symtree->n.sym->attr.allocatable;
4235 pointer = e->symtree->n.sym->attr.pointer;
4236 dimension = e->symtree->n.sym->attr.dimension;
4238 if (sym == e->symtree->n.sym && sym->ts.type != BT_DERIVED)
4240 gfc_error ("The STAT variable '%s' in an ALLOCATE statement must "
4241 "not be allocated in the same statement at %L",
4242 sym->name, &e->where);
4243 return FAILURE;
4246 for (ref = e->ref; ref; ref2 = ref, ref = ref->next)
4248 if (pointer)
4249 check_intent_in = 0;
4251 switch (ref->type)
4253 case REF_ARRAY:
4254 if (ref->next != NULL)
4255 pointer = 0;
4256 break;
4258 case REF_COMPONENT:
4259 allocatable = (ref->u.c.component->as != NULL
4260 && ref->u.c.component->as->type == AS_DEFERRED);
4262 pointer = ref->u.c.component->pointer;
4263 dimension = ref->u.c.component->dimension;
4264 break;
4266 case REF_SUBSTRING:
4267 allocatable = 0;
4268 pointer = 0;
4269 break;
4274 if (allocatable == 0 && pointer == 0)
4276 gfc_error ("Expression in ALLOCATE statement at %L must be "
4277 "ALLOCATABLE or a POINTER", &e->where);
4278 return FAILURE;
4281 if (check_intent_in
4282 && e->symtree->n.sym->attr.intent == INTENT_IN)
4284 gfc_error ("Cannot allocate INTENT(IN) variable '%s' at %L",
4285 e->symtree->n.sym->name, &e->where);
4286 return FAILURE;
4289 /* Add default initializer for those derived types that need them. */
4290 if (e->ts.type == BT_DERIVED && (init_e = gfc_default_initializer (&e->ts)))
4292 init_st = gfc_get_code ();
4293 init_st->loc = code->loc;
4294 init_st->op = EXEC_INIT_ASSIGN;
4295 init_st->expr = expr_to_initialize (e);
4296 init_st->expr2 = init_e;
4297 init_st->next = code->next;
4298 code->next = init_st;
4301 if (pointer && dimension == 0)
4302 return SUCCESS;
4304 /* Make sure the next-to-last reference node is an array specification. */
4306 if (ref2 == NULL || ref2->type != REF_ARRAY || ref2->u.ar.type == AR_FULL)
4308 gfc_error ("Array specification required in ALLOCATE statement "
4309 "at %L", &e->where);
4310 return FAILURE;
4313 /* Make sure that the array section reference makes sense in the
4314 context of an ALLOCATE specification. */
4316 ar = &ref2->u.ar;
4318 for (i = 0; i < ar->dimen; i++)
4320 if (ref2->u.ar.type == AR_ELEMENT)
4321 goto check_symbols;
4323 switch (ar->dimen_type[i])
4325 case DIMEN_ELEMENT:
4326 break;
4328 case DIMEN_RANGE:
4329 if (ar->start[i] != NULL
4330 && ar->end[i] != NULL
4331 && ar->stride[i] == NULL)
4332 break;
4334 /* Fall Through... */
4336 case DIMEN_UNKNOWN:
4337 case DIMEN_VECTOR:
4338 gfc_error ("Bad array specification in ALLOCATE statement at %L",
4339 &e->where);
4340 return FAILURE;
4343 check_symbols:
4345 for (a = code->ext.alloc_list; a; a = a->next)
4347 sym = a->expr->symtree->n.sym;
4349 /* TODO - check derived type components. */
4350 if (sym->ts.type == BT_DERIVED)
4351 continue;
4353 if ((ar->start[i] != NULL && find_sym_in_expr (sym, ar->start[i]))
4354 || (ar->end[i] != NULL && find_sym_in_expr (sym, ar->end[i])))
4356 gfc_error ("'%s' must not appear an the array specification at "
4357 "%L in the same ALLOCATE statement where it is "
4358 "itself allocated", sym->name, &ar->where);
4359 return FAILURE;
4364 return SUCCESS;
4368 /************ SELECT CASE resolution subroutines ************/
4370 /* Callback function for our mergesort variant. Determines interval
4371 overlaps for CASEs. Return <0 if op1 < op2, 0 for overlap, >0 for
4372 op1 > op2. Assumes we're not dealing with the default case.
4373 We have op1 = (:L), (K:L) or (K:) and op2 = (:N), (M:N) or (M:).
4374 There are nine situations to check. */
4376 static int
4377 compare_cases (const gfc_case *op1, const gfc_case *op2)
4379 int retval;
4381 if (op1->low == NULL) /* op1 = (:L) */
4383 /* op2 = (:N), so overlap. */
4384 retval = 0;
4385 /* op2 = (M:) or (M:N), L < M */
4386 if (op2->low != NULL
4387 && gfc_compare_expr (op1->high, op2->low) < 0)
4388 retval = -1;
4390 else if (op1->high == NULL) /* op1 = (K:) */
4392 /* op2 = (M:), so overlap. */
4393 retval = 0;
4394 /* op2 = (:N) or (M:N), K > N */
4395 if (op2->high != NULL
4396 && gfc_compare_expr (op1->low, op2->high) > 0)
4397 retval = 1;
4399 else /* op1 = (K:L) */
4401 if (op2->low == NULL) /* op2 = (:N), K > N */
4402 retval = (gfc_compare_expr (op1->low, op2->high) > 0) ? 1 : 0;
4403 else if (op2->high == NULL) /* op2 = (M:), L < M */
4404 retval = (gfc_compare_expr (op1->high, op2->low) < 0) ? -1 : 0;
4405 else /* op2 = (M:N) */
4407 retval = 0;
4408 /* L < M */
4409 if (gfc_compare_expr (op1->high, op2->low) < 0)
4410 retval = -1;
4411 /* K > N */
4412 else if (gfc_compare_expr (op1->low, op2->high) > 0)
4413 retval = 1;
4417 return retval;
4421 /* Merge-sort a double linked case list, detecting overlap in the
4422 process. LIST is the head of the double linked case list before it
4423 is sorted. Returns the head of the sorted list if we don't see any
4424 overlap, or NULL otherwise. */
4426 static gfc_case *
4427 check_case_overlap (gfc_case *list)
4429 gfc_case *p, *q, *e, *tail;
4430 int insize, nmerges, psize, qsize, cmp, overlap_seen;
4432 /* If the passed list was empty, return immediately. */
4433 if (!list)
4434 return NULL;
4436 overlap_seen = 0;
4437 insize = 1;
4439 /* Loop unconditionally. The only exit from this loop is a return
4440 statement, when we've finished sorting the case list. */
4441 for (;;)
4443 p = list;
4444 list = NULL;
4445 tail = NULL;
4447 /* Count the number of merges we do in this pass. */
4448 nmerges = 0;
4450 /* Loop while there exists a merge to be done. */
4451 while (p)
4453 int i;
4455 /* Count this merge. */
4456 nmerges++;
4458 /* Cut the list in two pieces by stepping INSIZE places
4459 forward in the list, starting from P. */
4460 psize = 0;
4461 q = p;
4462 for (i = 0; i < insize; i++)
4464 psize++;
4465 q = q->right;
4466 if (!q)
4467 break;
4469 qsize = insize;
4471 /* Now we have two lists. Merge them! */
4472 while (psize > 0 || (qsize > 0 && q != NULL))
4474 /* See from which the next case to merge comes from. */
4475 if (psize == 0)
4477 /* P is empty so the next case must come from Q. */
4478 e = q;
4479 q = q->right;
4480 qsize--;
4482 else if (qsize == 0 || q == NULL)
4484 /* Q is empty. */
4485 e = p;
4486 p = p->right;
4487 psize--;
4489 else
4491 cmp = compare_cases (p, q);
4492 if (cmp < 0)
4494 /* The whole case range for P is less than the
4495 one for Q. */
4496 e = p;
4497 p = p->right;
4498 psize--;
4500 else if (cmp > 0)
4502 /* The whole case range for Q is greater than
4503 the case range for P. */
4504 e = q;
4505 q = q->right;
4506 qsize--;
4508 else
4510 /* The cases overlap, or they are the same
4511 element in the list. Either way, we must
4512 issue an error and get the next case from P. */
4513 /* FIXME: Sort P and Q by line number. */
4514 gfc_error ("CASE label at %L overlaps with CASE "
4515 "label at %L", &p->where, &q->where);
4516 overlap_seen = 1;
4517 e = p;
4518 p = p->right;
4519 psize--;
4523 /* Add the next element to the merged list. */
4524 if (tail)
4525 tail->right = e;
4526 else
4527 list = e;
4528 e->left = tail;
4529 tail = e;
4532 /* P has now stepped INSIZE places along, and so has Q. So
4533 they're the same. */
4534 p = q;
4536 tail->right = NULL;
4538 /* If we have done only one merge or none at all, we've
4539 finished sorting the cases. */
4540 if (nmerges <= 1)
4542 if (!overlap_seen)
4543 return list;
4544 else
4545 return NULL;
4548 /* Otherwise repeat, merging lists twice the size. */
4549 insize *= 2;
4554 /* Check to see if an expression is suitable for use in a CASE statement.
4555 Makes sure that all case expressions are scalar constants of the same
4556 type. Return FAILURE if anything is wrong. */
4558 static try
4559 validate_case_label_expr (gfc_expr *e, gfc_expr *case_expr)
4561 if (e == NULL) return SUCCESS;
4563 if (e->ts.type != case_expr->ts.type)
4565 gfc_error ("Expression in CASE statement at %L must be of type %s",
4566 &e->where, gfc_basic_typename (case_expr->ts.type));
4567 return FAILURE;
4570 /* C805 (R808) For a given case-construct, each case-value shall be of
4571 the same type as case-expr. For character type, length differences
4572 are allowed, but the kind type parameters shall be the same. */
4574 if (case_expr->ts.type == BT_CHARACTER && e->ts.kind != case_expr->ts.kind)
4576 gfc_error("Expression in CASE statement at %L must be kind %d",
4577 &e->where, case_expr->ts.kind);
4578 return FAILURE;
4581 /* Convert the case value kind to that of case expression kind, if needed.
4582 FIXME: Should a warning be issued? */
4583 if (e->ts.kind != case_expr->ts.kind)
4584 gfc_convert_type_warn (e, &case_expr->ts, 2, 0);
4586 if (e->rank != 0)
4588 gfc_error ("Expression in CASE statement at %L must be scalar",
4589 &e->where);
4590 return FAILURE;
4593 return SUCCESS;
4597 /* Given a completely parsed select statement, we:
4599 - Validate all expressions and code within the SELECT.
4600 - Make sure that the selection expression is not of the wrong type.
4601 - Make sure that no case ranges overlap.
4602 - Eliminate unreachable cases and unreachable code resulting from
4603 removing case labels.
4605 The standard does allow unreachable cases, e.g. CASE (5:3). But
4606 they are a hassle for code generation, and to prevent that, we just
4607 cut them out here. This is not necessary for overlapping cases
4608 because they are illegal and we never even try to generate code.
4610 We have the additional caveat that a SELECT construct could have
4611 been a computed GOTO in the source code. Fortunately we can fairly
4612 easily work around that here: The case_expr for a "real" SELECT CASE
4613 is in code->expr1, but for a computed GOTO it is in code->expr2. All
4614 we have to do is make sure that the case_expr is a scalar integer
4615 expression. */
4617 static void
4618 resolve_select (gfc_code *code)
4620 gfc_code *body;
4621 gfc_expr *case_expr;
4622 gfc_case *cp, *default_case, *tail, *head;
4623 int seen_unreachable;
4624 int seen_logical;
4625 int ncases;
4626 bt type;
4627 try t;
4629 if (code->expr == NULL)
4631 /* This was actually a computed GOTO statement. */
4632 case_expr = code->expr2;
4633 if (case_expr->ts.type != BT_INTEGER|| case_expr->rank != 0)
4634 gfc_error ("Selection expression in computed GOTO statement "
4635 "at %L must be a scalar integer expression",
4636 &case_expr->where);
4638 /* Further checking is not necessary because this SELECT was built
4639 by the compiler, so it should always be OK. Just move the
4640 case_expr from expr2 to expr so that we can handle computed
4641 GOTOs as normal SELECTs from here on. */
4642 code->expr = code->expr2;
4643 code->expr2 = NULL;
4644 return;
4647 case_expr = code->expr;
4649 type = case_expr->ts.type;
4650 if (type != BT_LOGICAL && type != BT_INTEGER && type != BT_CHARACTER)
4652 gfc_error ("Argument of SELECT statement at %L cannot be %s",
4653 &case_expr->where, gfc_typename (&case_expr->ts));
4655 /* Punt. Going on here just produce more garbage error messages. */
4656 return;
4659 if (case_expr->rank != 0)
4661 gfc_error ("Argument of SELECT statement at %L must be a scalar "
4662 "expression", &case_expr->where);
4664 /* Punt. */
4665 return;
4668 /* PR 19168 has a long discussion concerning a mismatch of the kinds
4669 of the SELECT CASE expression and its CASE values. Walk the lists
4670 of case values, and if we find a mismatch, promote case_expr to
4671 the appropriate kind. */
4673 if (type == BT_LOGICAL || type == BT_INTEGER)
4675 for (body = code->block; body; body = body->block)
4677 /* Walk the case label list. */
4678 for (cp = body->ext.case_list; cp; cp = cp->next)
4680 /* Intercept the DEFAULT case. It does not have a kind. */
4681 if (cp->low == NULL && cp->high == NULL)
4682 continue;
4684 /* Unreachable case ranges are discarded, so ignore. */
4685 if (cp->low != NULL && cp->high != NULL
4686 && cp->low != cp->high
4687 && gfc_compare_expr (cp->low, cp->high) > 0)
4688 continue;
4690 /* FIXME: Should a warning be issued? */
4691 if (cp->low != NULL
4692 && case_expr->ts.kind != gfc_kind_max(case_expr, cp->low))
4693 gfc_convert_type_warn (case_expr, &cp->low->ts, 2, 0);
4695 if (cp->high != NULL
4696 && case_expr->ts.kind != gfc_kind_max(case_expr, cp->high))
4697 gfc_convert_type_warn (case_expr, &cp->high->ts, 2, 0);
4702 /* Assume there is no DEFAULT case. */
4703 default_case = NULL;
4704 head = tail = NULL;
4705 ncases = 0;
4706 seen_logical = 0;
4708 for (body = code->block; body; body = body->block)
4710 /* Assume the CASE list is OK, and all CASE labels can be matched. */
4711 t = SUCCESS;
4712 seen_unreachable = 0;
4714 /* Walk the case label list, making sure that all case labels
4715 are legal. */
4716 for (cp = body->ext.case_list; cp; cp = cp->next)
4718 /* Count the number of cases in the whole construct. */
4719 ncases++;
4721 /* Intercept the DEFAULT case. */
4722 if (cp->low == NULL && cp->high == NULL)
4724 if (default_case != NULL)
4726 gfc_error ("The DEFAULT CASE at %L cannot be followed "
4727 "by a second DEFAULT CASE at %L",
4728 &default_case->where, &cp->where);
4729 t = FAILURE;
4730 break;
4732 else
4734 default_case = cp;
4735 continue;
4739 /* Deal with single value cases and case ranges. Errors are
4740 issued from the validation function. */
4741 if(validate_case_label_expr (cp->low, case_expr) != SUCCESS
4742 || validate_case_label_expr (cp->high, case_expr) != SUCCESS)
4744 t = FAILURE;
4745 break;
4748 if (type == BT_LOGICAL
4749 && ((cp->low == NULL || cp->high == NULL)
4750 || cp->low != cp->high))
4752 gfc_error ("Logical range in CASE statement at %L is not "
4753 "allowed", &cp->low->where);
4754 t = FAILURE;
4755 break;
4758 if (type == BT_LOGICAL && cp->low->expr_type == EXPR_CONSTANT)
4760 int value;
4761 value = cp->low->value.logical == 0 ? 2 : 1;
4762 if (value & seen_logical)
4764 gfc_error ("constant logical value in CASE statement "
4765 "is repeated at %L",
4766 &cp->low->where);
4767 t = FAILURE;
4768 break;
4770 seen_logical |= value;
4773 if (cp->low != NULL && cp->high != NULL
4774 && cp->low != cp->high
4775 && gfc_compare_expr (cp->low, cp->high) > 0)
4777 if (gfc_option.warn_surprising)
4778 gfc_warning ("Range specification at %L can never "
4779 "be matched", &cp->where);
4781 cp->unreachable = 1;
4782 seen_unreachable = 1;
4784 else
4786 /* If the case range can be matched, it can also overlap with
4787 other cases. To make sure it does not, we put it in a
4788 double linked list here. We sort that with a merge sort
4789 later on to detect any overlapping cases. */
4790 if (!head)
4792 head = tail = cp;
4793 head->right = head->left = NULL;
4795 else
4797 tail->right = cp;
4798 tail->right->left = tail;
4799 tail = tail->right;
4800 tail->right = NULL;
4805 /* It there was a failure in the previous case label, give up
4806 for this case label list. Continue with the next block. */
4807 if (t == FAILURE)
4808 continue;
4810 /* See if any case labels that are unreachable have been seen.
4811 If so, we eliminate them. This is a bit of a kludge because
4812 the case lists for a single case statement (label) is a
4813 single forward linked lists. */
4814 if (seen_unreachable)
4816 /* Advance until the first case in the list is reachable. */
4817 while (body->ext.case_list != NULL
4818 && body->ext.case_list->unreachable)
4820 gfc_case *n = body->ext.case_list;
4821 body->ext.case_list = body->ext.case_list->next;
4822 n->next = NULL;
4823 gfc_free_case_list (n);
4826 /* Strip all other unreachable cases. */
4827 if (body->ext.case_list)
4829 for (cp = body->ext.case_list; cp->next; cp = cp->next)
4831 if (cp->next->unreachable)
4833 gfc_case *n = cp->next;
4834 cp->next = cp->next->next;
4835 n->next = NULL;
4836 gfc_free_case_list (n);
4843 /* See if there were overlapping cases. If the check returns NULL,
4844 there was overlap. In that case we don't do anything. If head
4845 is non-NULL, we prepend the DEFAULT case. The sorted list can
4846 then used during code generation for SELECT CASE constructs with
4847 a case expression of a CHARACTER type. */
4848 if (head)
4850 head = check_case_overlap (head);
4852 /* Prepend the default_case if it is there. */
4853 if (head != NULL && default_case)
4855 default_case->left = NULL;
4856 default_case->right = head;
4857 head->left = default_case;
4861 /* Eliminate dead blocks that may be the result if we've seen
4862 unreachable case labels for a block. */
4863 for (body = code; body && body->block; body = body->block)
4865 if (body->block->ext.case_list == NULL)
4867 /* Cut the unreachable block from the code chain. */
4868 gfc_code *c = body->block;
4869 body->block = c->block;
4871 /* Kill the dead block, but not the blocks below it. */
4872 c->block = NULL;
4873 gfc_free_statements (c);
4877 /* More than two cases is legal but insane for logical selects.
4878 Issue a warning for it. */
4879 if (gfc_option.warn_surprising && type == BT_LOGICAL
4880 && ncases > 2)
4881 gfc_warning ("Logical SELECT CASE block at %L has more that two cases",
4882 &code->loc);
4886 /* Resolve a transfer statement. This is making sure that:
4887 -- a derived type being transferred has only non-pointer components
4888 -- a derived type being transferred doesn't have private components, unless
4889 it's being transferred from the module where the type was defined
4890 -- we're not trying to transfer a whole assumed size array. */
4892 static void
4893 resolve_transfer (gfc_code *code)
4895 gfc_typespec *ts;
4896 gfc_symbol *sym;
4897 gfc_ref *ref;
4898 gfc_expr *exp;
4900 exp = code->expr;
4902 if (exp->expr_type != EXPR_VARIABLE && exp->expr_type != EXPR_FUNCTION)
4903 return;
4905 sym = exp->symtree->n.sym;
4906 ts = &sym->ts;
4908 /* Go to actual component transferred. */
4909 for (ref = code->expr->ref; ref; ref = ref->next)
4910 if (ref->type == REF_COMPONENT)
4911 ts = &ref->u.c.component->ts;
4913 if (ts->type == BT_DERIVED)
4915 /* Check that transferred derived type doesn't contain POINTER
4916 components. */
4917 if (derived_pointer (ts->derived))
4919 gfc_error ("Data transfer element at %L cannot have "
4920 "POINTER components", &code->loc);
4921 return;
4924 if (ts->derived->attr.alloc_comp)
4926 gfc_error ("Data transfer element at %L cannot have "
4927 "ALLOCATABLE components", &code->loc);
4928 return;
4931 if (derived_inaccessible (ts->derived))
4933 gfc_error ("Data transfer element at %L cannot have "
4934 "PRIVATE components",&code->loc);
4935 return;
4939 if (sym->as != NULL && sym->as->type == AS_ASSUMED_SIZE
4940 && exp->ref->type == REF_ARRAY && exp->ref->u.ar.type == AR_FULL)
4942 gfc_error ("Data transfer element at %L cannot be a full reference to "
4943 "an assumed-size array", &code->loc);
4944 return;
4949 /*********** Toplevel code resolution subroutines ***********/
4951 /* Find the set of labels that are reachable from this block. We also
4952 record the last statement in each block so that we don't have to do
4953 a linear search to find the END DO statements of the blocks. */
4955 static void
4956 reachable_labels (gfc_code *block)
4958 gfc_code *c;
4960 if (!block)
4961 return;
4963 cs_base->reachable_labels = bitmap_obstack_alloc (&labels_obstack);
4965 /* Collect labels in this block. */
4966 for (c = block; c; c = c->next)
4968 if (c->here)
4969 bitmap_set_bit (cs_base->reachable_labels, c->here->value);
4971 if (!c->next && cs_base->prev)
4972 cs_base->prev->tail = c;
4975 /* Merge with labels from parent block. */
4976 if (cs_base->prev)
4978 gcc_assert (cs_base->prev->reachable_labels);
4979 bitmap_ior_into (cs_base->reachable_labels,
4980 cs_base->prev->reachable_labels);
4984 /* Given a branch to a label and a namespace, if the branch is conforming.
4985 The code node describes where the branch is located. */
4987 static void
4988 resolve_branch (gfc_st_label *label, gfc_code *code)
4990 code_stack *stack;
4992 if (label == NULL)
4993 return;
4995 /* Step one: is this a valid branching target? */
4997 if (label->defined == ST_LABEL_UNKNOWN)
4999 gfc_error ("Label %d referenced at %L is never defined", label->value,
5000 &label->where);
5001 return;
5004 if (label->defined != ST_LABEL_TARGET)
5006 gfc_error ("Statement at %L is not a valid branch target statement "
5007 "for the branch statement at %L", &label->where, &code->loc);
5008 return;
5011 /* Step two: make sure this branch is not a branch to itself ;-) */
5013 if (code->here == label)
5015 gfc_warning ("Branch at %L causes an infinite loop", &code->loc);
5016 return;
5019 /* Step three: See if the label is in the same block as the
5020 branching statement. The hard work has been done by setting up
5021 the bitmap reachable_labels. */
5023 if (!bitmap_bit_p (cs_base->reachable_labels, label->value))
5025 /* The label is not in an enclosing block, so illegal. This was
5026 allowed in Fortran 66, so we allow it as extension. No
5027 further checks are necessary in this case. */
5028 gfc_notify_std (GFC_STD_LEGACY, "Label at %L is not in the same block "
5029 "as the GOTO statement at %L", &label->where,
5030 &code->loc);
5031 return;
5034 /* Step four: Make sure that the branching target is legal if
5035 the statement is an END {SELECT,IF}. */
5037 for (stack = cs_base; stack; stack = stack->prev)
5038 if (stack->current->next && stack->current->next->here == label)
5039 break;
5041 if (stack && stack->current->next->op == EXEC_NOP)
5043 gfc_notify_std (GFC_STD_F95_DEL, "Deleted feature: GOTO at %L jumps to "
5044 "END of construct at %L", &code->loc,
5045 &stack->current->next->loc);
5046 return; /* We know this is not an END DO. */
5049 /* Step five: Make sure that we're not jumping to the end of a DO
5050 loop from within the loop. */
5052 for (stack = cs_base; stack; stack = stack->prev)
5053 if ((stack->current->op == EXEC_DO
5054 || stack->current->op == EXEC_DO_WHILE)
5055 && stack->tail->here == label && stack->tail->op == EXEC_NOP)
5057 gfc_notify_std (GFC_STD_F95_DEL, "Deleted feature: GOTO at %L jumps "
5058 "to END of construct at %L", &code->loc,
5059 &stack->tail->loc);
5060 return;
5066 /* Check whether EXPR1 has the same shape as EXPR2. */
5068 static try
5069 resolve_where_shape (gfc_expr *expr1, gfc_expr *expr2)
5071 mpz_t shape[GFC_MAX_DIMENSIONS];
5072 mpz_t shape2[GFC_MAX_DIMENSIONS];
5073 try result = FAILURE;
5074 int i;
5076 /* Compare the rank. */
5077 if (expr1->rank != expr2->rank)
5078 return result;
5080 /* Compare the size of each dimension. */
5081 for (i=0; i<expr1->rank; i++)
5083 if (gfc_array_dimen_size (expr1, i, &shape[i]) == FAILURE)
5084 goto ignore;
5086 if (gfc_array_dimen_size (expr2, i, &shape2[i]) == FAILURE)
5087 goto ignore;
5089 if (mpz_cmp (shape[i], shape2[i]))
5090 goto over;
5093 /* When either of the two expression is an assumed size array, we
5094 ignore the comparison of dimension sizes. */
5095 ignore:
5096 result = SUCCESS;
5098 over:
5099 for (i--; i >= 0; i--)
5101 mpz_clear (shape[i]);
5102 mpz_clear (shape2[i]);
5104 return result;
5108 /* Check whether a WHERE assignment target or a WHERE mask expression
5109 has the same shape as the outmost WHERE mask expression. */
5111 static void
5112 resolve_where (gfc_code *code, gfc_expr *mask)
5114 gfc_code *cblock;
5115 gfc_code *cnext;
5116 gfc_expr *e = NULL;
5118 cblock = code->block;
5120 /* Store the first WHERE mask-expr of the WHERE statement or construct.
5121 In case of nested WHERE, only the outmost one is stored. */
5122 if (mask == NULL) /* outmost WHERE */
5123 e = cblock->expr;
5124 else /* inner WHERE */
5125 e = mask;
5127 while (cblock)
5129 if (cblock->expr)
5131 /* Check if the mask-expr has a consistent shape with the
5132 outmost WHERE mask-expr. */
5133 if (resolve_where_shape (cblock->expr, e) == FAILURE)
5134 gfc_error ("WHERE mask at %L has inconsistent shape",
5135 &cblock->expr->where);
5138 /* the assignment statement of a WHERE statement, or the first
5139 statement in where-body-construct of a WHERE construct */
5140 cnext = cblock->next;
5141 while (cnext)
5143 switch (cnext->op)
5145 /* WHERE assignment statement */
5146 case EXEC_ASSIGN:
5148 /* Check shape consistent for WHERE assignment target. */
5149 if (e && resolve_where_shape (cnext->expr, e) == FAILURE)
5150 gfc_error ("WHERE assignment target at %L has "
5151 "inconsistent shape", &cnext->expr->where);
5152 break;
5155 case EXEC_ASSIGN_CALL:
5156 resolve_call (cnext);
5157 break;
5159 /* WHERE or WHERE construct is part of a where-body-construct */
5160 case EXEC_WHERE:
5161 resolve_where (cnext, e);
5162 break;
5164 default:
5165 gfc_error ("Unsupported statement inside WHERE at %L",
5166 &cnext->loc);
5168 /* the next statement within the same where-body-construct */
5169 cnext = cnext->next;
5171 /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
5172 cblock = cblock->block;
5177 /* Check whether the FORALL index appears in the expression or not. */
5179 static try
5180 gfc_find_forall_index (gfc_expr *expr, gfc_symbol *symbol)
5182 gfc_array_ref ar;
5183 gfc_ref *tmp;
5184 gfc_actual_arglist *args;
5185 int i;
5187 switch (expr->expr_type)
5189 case EXPR_VARIABLE:
5190 gcc_assert (expr->symtree->n.sym);
5192 /* A scalar assignment */
5193 if (!expr->ref)
5195 if (expr->symtree->n.sym == symbol)
5196 return SUCCESS;
5197 else
5198 return FAILURE;
5201 /* the expr is array ref, substring or struct component. */
5202 tmp = expr->ref;
5203 while (tmp != NULL)
5205 switch (tmp->type)
5207 case REF_ARRAY:
5208 /* Check if the symbol appears in the array subscript. */
5209 ar = tmp->u.ar;
5210 for (i = 0; i < GFC_MAX_DIMENSIONS; i++)
5212 if (ar.start[i])
5213 if (gfc_find_forall_index (ar.start[i], symbol) == SUCCESS)
5214 return SUCCESS;
5216 if (ar.end[i])
5217 if (gfc_find_forall_index (ar.end[i], symbol) == SUCCESS)
5218 return SUCCESS;
5220 if (ar.stride[i])
5221 if (gfc_find_forall_index (ar.stride[i], symbol) == SUCCESS)
5222 return SUCCESS;
5223 } /* end for */
5224 break;
5226 case REF_SUBSTRING:
5227 if (expr->symtree->n.sym == symbol)
5228 return SUCCESS;
5229 tmp = expr->ref;
5230 /* Check if the symbol appears in the substring section. */
5231 if (gfc_find_forall_index (tmp->u.ss.start, symbol) == SUCCESS)
5232 return SUCCESS;
5233 if (gfc_find_forall_index (tmp->u.ss.end, symbol) == SUCCESS)
5234 return SUCCESS;
5235 break;
5237 case REF_COMPONENT:
5238 break;
5240 default:
5241 gfc_error("expression reference type error at %L", &expr->where);
5243 tmp = tmp->next;
5245 break;
5247 /* If the expression is a function call, then check if the symbol
5248 appears in the actual arglist of the function. */
5249 case EXPR_FUNCTION:
5250 for (args = expr->value.function.actual; args; args = args->next)
5252 if (gfc_find_forall_index(args->expr,symbol) == SUCCESS)
5253 return SUCCESS;
5255 break;
5257 /* It seems not to happen. */
5258 case EXPR_SUBSTRING:
5259 if (expr->ref)
5261 tmp = expr->ref;
5262 gcc_assert (expr->ref->type == REF_SUBSTRING);
5263 if (gfc_find_forall_index (tmp->u.ss.start, symbol) == SUCCESS)
5264 return SUCCESS;
5265 if (gfc_find_forall_index (tmp->u.ss.end, symbol) == SUCCESS)
5266 return SUCCESS;
5268 break;
5270 /* It seems not to happen. */
5271 case EXPR_STRUCTURE:
5272 case EXPR_ARRAY:
5273 gfc_error ("Unsupported statement while finding forall index in "
5274 "expression");
5275 break;
5277 case EXPR_OP:
5278 /* Find the FORALL index in the first operand. */
5279 if (expr->value.op.op1)
5281 if (gfc_find_forall_index (expr->value.op.op1, symbol) == SUCCESS)
5282 return SUCCESS;
5285 /* Find the FORALL index in the second operand. */
5286 if (expr->value.op.op2)
5288 if (gfc_find_forall_index (expr->value.op.op2, symbol) == SUCCESS)
5289 return SUCCESS;
5291 break;
5293 default:
5294 break;
5297 return FAILURE;
5301 /* Resolve assignment in FORALL construct.
5302 NVAR is the number of FORALL index variables, and VAR_EXPR records the
5303 FORALL index variables. */
5305 static void
5306 gfc_resolve_assign_in_forall (gfc_code *code, int nvar, gfc_expr **var_expr)
5308 int n;
5310 for (n = 0; n < nvar; n++)
5312 gfc_symbol *forall_index;
5314 forall_index = var_expr[n]->symtree->n.sym;
5316 /* Check whether the assignment target is one of the FORALL index
5317 variable. */
5318 if ((code->expr->expr_type == EXPR_VARIABLE)
5319 && (code->expr->symtree->n.sym == forall_index))
5320 gfc_error ("Assignment to a FORALL index variable at %L",
5321 &code->expr->where);
5322 else
5324 /* If one of the FORALL index variables doesn't appear in the
5325 assignment target, then there will be a many-to-one
5326 assignment. */
5327 if (gfc_find_forall_index (code->expr, forall_index) == FAILURE)
5328 gfc_error ("The FORALL with index '%s' cause more than one "
5329 "assignment to this object at %L",
5330 var_expr[n]->symtree->name, &code->expr->where);
5336 /* Resolve WHERE statement in FORALL construct. */
5338 static void
5339 gfc_resolve_where_code_in_forall (gfc_code *code, int nvar,
5340 gfc_expr **var_expr)
5342 gfc_code *cblock;
5343 gfc_code *cnext;
5345 cblock = code->block;
5346 while (cblock)
5348 /* the assignment statement of a WHERE statement, or the first
5349 statement in where-body-construct of a WHERE construct */
5350 cnext = cblock->next;
5351 while (cnext)
5353 switch (cnext->op)
5355 /* WHERE assignment statement */
5356 case EXEC_ASSIGN:
5357 gfc_resolve_assign_in_forall (cnext, nvar, var_expr);
5358 break;
5360 /* WHERE operator assignment statement */
5361 case EXEC_ASSIGN_CALL:
5362 resolve_call (cnext);
5363 break;
5365 /* WHERE or WHERE construct is part of a where-body-construct */
5366 case EXEC_WHERE:
5367 gfc_resolve_where_code_in_forall (cnext, nvar, var_expr);
5368 break;
5370 default:
5371 gfc_error ("Unsupported statement inside WHERE at %L",
5372 &cnext->loc);
5374 /* the next statement within the same where-body-construct */
5375 cnext = cnext->next;
5377 /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
5378 cblock = cblock->block;
5383 /* Traverse the FORALL body to check whether the following errors exist:
5384 1. For assignment, check if a many-to-one assignment happens.
5385 2. For WHERE statement, check the WHERE body to see if there is any
5386 many-to-one assignment. */
5388 static void
5389 gfc_resolve_forall_body (gfc_code *code, int nvar, gfc_expr **var_expr)
5391 gfc_code *c;
5393 c = code->block->next;
5394 while (c)
5396 switch (c->op)
5398 case EXEC_ASSIGN:
5399 case EXEC_POINTER_ASSIGN:
5400 gfc_resolve_assign_in_forall (c, nvar, var_expr);
5401 break;
5403 case EXEC_ASSIGN_CALL:
5404 resolve_call (c);
5405 break;
5407 /* Because the gfc_resolve_blocks() will handle the nested FORALL,
5408 there is no need to handle it here. */
5409 case EXEC_FORALL:
5410 break;
5411 case EXEC_WHERE:
5412 gfc_resolve_where_code_in_forall(c, nvar, var_expr);
5413 break;
5414 default:
5415 break;
5417 /* The next statement in the FORALL body. */
5418 c = c->next;
5423 /* Given a FORALL construct, first resolve the FORALL iterator, then call
5424 gfc_resolve_forall_body to resolve the FORALL body. */
5426 static void
5427 gfc_resolve_forall (gfc_code *code, gfc_namespace *ns, int forall_save)
5429 static gfc_expr **var_expr;
5430 static int total_var = 0;
5431 static int nvar = 0;
5432 gfc_forall_iterator *fa;
5433 gfc_symbol *forall_index;
5434 gfc_code *next;
5435 int i;
5437 /* Start to resolve a FORALL construct */
5438 if (forall_save == 0)
5440 /* Count the total number of FORALL index in the nested FORALL
5441 construct in order to allocate the VAR_EXPR with proper size. */
5442 next = code;
5443 while ((next != NULL) && (next->op == EXEC_FORALL))
5445 for (fa = next->ext.forall_iterator; fa; fa = fa->next)
5446 total_var ++;
5447 next = next->block->next;
5450 /* Allocate VAR_EXPR with NUMBER_OF_FORALL_INDEX elements. */
5451 var_expr = (gfc_expr **) gfc_getmem (total_var * sizeof (gfc_expr *));
5454 /* The information about FORALL iterator, including FORALL index start, end
5455 and stride. The FORALL index can not appear in start, end or stride. */
5456 for (fa = code->ext.forall_iterator; fa; fa = fa->next)
5458 /* Check if any outer FORALL index name is the same as the current
5459 one. */
5460 for (i = 0; i < nvar; i++)
5462 if (fa->var->symtree->n.sym == var_expr[i]->symtree->n.sym)
5464 gfc_error ("An outer FORALL construct already has an index "
5465 "with this name %L", &fa->var->where);
5469 /* Record the current FORALL index. */
5470 var_expr[nvar] = gfc_copy_expr (fa->var);
5472 forall_index = fa->var->symtree->n.sym;
5474 /* Check if the FORALL index appears in start, end or stride. */
5475 if (gfc_find_forall_index (fa->start, forall_index) == SUCCESS)
5476 gfc_error ("A FORALL index must not appear in a limit or stride "
5477 "expression in the same FORALL at %L", &fa->start->where);
5478 if (gfc_find_forall_index (fa->end, forall_index) == SUCCESS)
5479 gfc_error ("A FORALL index must not appear in a limit or stride "
5480 "expression in the same FORALL at %L", &fa->end->where);
5481 if (gfc_find_forall_index (fa->stride, forall_index) == SUCCESS)
5482 gfc_error ("A FORALL index must not appear in a limit or stride "
5483 "expression in the same FORALL at %L", &fa->stride->where);
5484 nvar++;
5487 /* Resolve the FORALL body. */
5488 gfc_resolve_forall_body (code, nvar, var_expr);
5490 /* May call gfc_resolve_forall to resolve the inner FORALL loop. */
5491 gfc_resolve_blocks (code->block, ns);
5493 /* Free VAR_EXPR after the whole FORALL construct resolved. */
5494 for (i = 0; i < total_var; i++)
5495 gfc_free_expr (var_expr[i]);
5497 /* Reset the counters. */
5498 total_var = 0;
5499 nvar = 0;
5503 /* Resolve lists of blocks found in IF, SELECT CASE, WHERE, FORALL ,GOTO and
5504 DO code nodes. */
5506 static void resolve_code (gfc_code *, gfc_namespace *);
5508 void
5509 gfc_resolve_blocks (gfc_code *b, gfc_namespace *ns)
5511 try t;
5513 for (; b; b = b->block)
5515 t = gfc_resolve_expr (b->expr);
5516 if (gfc_resolve_expr (b->expr2) == FAILURE)
5517 t = FAILURE;
5519 switch (b->op)
5521 case EXEC_IF:
5522 if (t == SUCCESS && b->expr != NULL
5523 && (b->expr->ts.type != BT_LOGICAL || b->expr->rank != 0))
5524 gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
5525 &b->expr->where);
5526 break;
5528 case EXEC_WHERE:
5529 if (t == SUCCESS
5530 && b->expr != NULL
5531 && (b->expr->ts.type != BT_LOGICAL || b->expr->rank == 0))
5532 gfc_error ("WHERE/ELSEWHERE clause at %L requires a LOGICAL array",
5533 &b->expr->where);
5534 break;
5536 case EXEC_GOTO:
5537 resolve_branch (b->label, b);
5538 break;
5540 case EXEC_SELECT:
5541 case EXEC_FORALL:
5542 case EXEC_DO:
5543 case EXEC_DO_WHILE:
5544 case EXEC_READ:
5545 case EXEC_WRITE:
5546 case EXEC_IOLENGTH:
5547 break;
5549 case EXEC_OMP_ATOMIC:
5550 case EXEC_OMP_CRITICAL:
5551 case EXEC_OMP_DO:
5552 case EXEC_OMP_MASTER:
5553 case EXEC_OMP_ORDERED:
5554 case EXEC_OMP_PARALLEL:
5555 case EXEC_OMP_PARALLEL_DO:
5556 case EXEC_OMP_PARALLEL_SECTIONS:
5557 case EXEC_OMP_PARALLEL_WORKSHARE:
5558 case EXEC_OMP_SECTIONS:
5559 case EXEC_OMP_SINGLE:
5560 case EXEC_OMP_WORKSHARE:
5561 break;
5563 default:
5564 gfc_internal_error ("resolve_block(): Bad block type");
5567 resolve_code (b->next, ns);
5572 /* Given a block of code, recursively resolve everything pointed to by this
5573 code block. */
5575 static void
5576 resolve_code (gfc_code *code, gfc_namespace *ns)
5578 int omp_workshare_save;
5579 int forall_save;
5580 code_stack frame;
5581 gfc_alloc *a;
5582 try t;
5584 frame.prev = cs_base;
5585 frame.head = code;
5586 cs_base = &frame;
5588 reachable_labels (code);
5590 for (; code; code = code->next)
5592 frame.current = code;
5593 forall_save = forall_flag;
5595 if (code->op == EXEC_FORALL)
5597 forall_flag = 1;
5598 gfc_resolve_forall (code, ns, forall_save);
5599 forall_flag = 2;
5601 else if (code->block)
5603 omp_workshare_save = -1;
5604 switch (code->op)
5606 case EXEC_OMP_PARALLEL_WORKSHARE:
5607 omp_workshare_save = omp_workshare_flag;
5608 omp_workshare_flag = 1;
5609 gfc_resolve_omp_parallel_blocks (code, ns);
5610 break;
5611 case EXEC_OMP_PARALLEL:
5612 case EXEC_OMP_PARALLEL_DO:
5613 case EXEC_OMP_PARALLEL_SECTIONS:
5614 omp_workshare_save = omp_workshare_flag;
5615 omp_workshare_flag = 0;
5616 gfc_resolve_omp_parallel_blocks (code, ns);
5617 break;
5618 case EXEC_OMP_DO:
5619 gfc_resolve_omp_do_blocks (code, ns);
5620 break;
5621 case EXEC_OMP_WORKSHARE:
5622 omp_workshare_save = omp_workshare_flag;
5623 omp_workshare_flag = 1;
5624 /* FALLTHROUGH */
5625 default:
5626 gfc_resolve_blocks (code->block, ns);
5627 break;
5630 if (omp_workshare_save != -1)
5631 omp_workshare_flag = omp_workshare_save;
5634 t = gfc_resolve_expr (code->expr);
5635 forall_flag = forall_save;
5637 if (gfc_resolve_expr (code->expr2) == FAILURE)
5638 t = FAILURE;
5640 switch (code->op)
5642 case EXEC_NOP:
5643 case EXEC_CYCLE:
5644 case EXEC_PAUSE:
5645 case EXEC_STOP:
5646 case EXEC_EXIT:
5647 case EXEC_CONTINUE:
5648 case EXEC_DT_END:
5649 break;
5651 case EXEC_ENTRY:
5652 /* Keep track of which entry we are up to. */
5653 current_entry_id = code->ext.entry->id;
5654 break;
5656 case EXEC_WHERE:
5657 resolve_where (code, NULL);
5658 break;
5660 case EXEC_GOTO:
5661 if (code->expr != NULL)
5663 if (code->expr->ts.type != BT_INTEGER)
5664 gfc_error ("ASSIGNED GOTO statement at %L requires an "
5665 "INTEGER variable", &code->expr->where);
5666 else if (code->expr->symtree->n.sym->attr.assign != 1)
5667 gfc_error ("Variable '%s' has not been assigned a target "
5668 "label at %L", code->expr->symtree->n.sym->name,
5669 &code->expr->where);
5671 else
5672 resolve_branch (code->label, code);
5673 break;
5675 case EXEC_RETURN:
5676 if (code->expr != NULL
5677 && (code->expr->ts.type != BT_INTEGER || code->expr->rank))
5678 gfc_error ("Alternate RETURN statement at %L requires a SCALAR-"
5679 "INTEGER return specifier", &code->expr->where);
5680 break;
5682 case EXEC_INIT_ASSIGN:
5683 break;
5685 case EXEC_ASSIGN:
5686 if (t == FAILURE)
5687 break;
5689 if (gfc_extend_assign (code, ns) == SUCCESS)
5691 if (gfc_pure (NULL) && !gfc_pure (code->symtree->n.sym))
5693 gfc_error ("Subroutine '%s' called instead of assignment at "
5694 "%L must be PURE", code->symtree->n.sym->name,
5695 &code->loc);
5696 break;
5698 goto call;
5701 if (code->expr->ts.type == BT_CHARACTER
5702 && gfc_option.warn_character_truncation)
5704 int llen = 0, rlen = 0;
5706 if (code->expr->ts.cl != NULL
5707 && code->expr->ts.cl->length != NULL
5708 && code->expr->ts.cl->length->expr_type == EXPR_CONSTANT)
5709 llen = mpz_get_si (code->expr->ts.cl->length->value.integer);
5711 if (code->expr2->expr_type == EXPR_CONSTANT)
5712 rlen = code->expr2->value.character.length;
5714 else if (code->expr2->ts.cl != NULL
5715 && code->expr2->ts.cl->length != NULL
5716 && code->expr2->ts.cl->length->expr_type
5717 == EXPR_CONSTANT)
5718 rlen = mpz_get_si (code->expr2->ts.cl->length->value.integer);
5720 if (rlen && llen && rlen > llen)
5721 gfc_warning_now ("CHARACTER expression will be truncated "
5722 "in assignment (%d/%d) at %L",
5723 llen, rlen, &code->loc);
5726 if (gfc_pure (NULL))
5728 if (gfc_impure_variable (code->expr->symtree->n.sym))
5730 gfc_error ("Cannot assign to variable '%s' in PURE "
5731 "procedure at %L",
5732 code->expr->symtree->n.sym->name,
5733 &code->expr->where);
5734 break;
5737 if (code->expr->ts.type == BT_DERIVED
5738 && code->expr->expr_type == EXPR_VARIABLE
5739 && derived_pointer (code->expr->ts.derived)
5740 && gfc_impure_variable (code->expr2->symtree->n.sym))
5742 gfc_error ("The impure variable at %L is assigned to "
5743 "a derived type variable with a POINTER "
5744 "component in a PURE procedure (12.6)",
5745 &code->expr2->where);
5746 break;
5750 gfc_check_assign (code->expr, code->expr2, 1);
5751 break;
5753 case EXEC_LABEL_ASSIGN:
5754 if (code->label->defined == ST_LABEL_UNKNOWN)
5755 gfc_error ("Label %d referenced at %L is never defined",
5756 code->label->value, &code->label->where);
5757 if (t == SUCCESS
5758 && (code->expr->expr_type != EXPR_VARIABLE
5759 || code->expr->symtree->n.sym->ts.type != BT_INTEGER
5760 || code->expr->symtree->n.sym->ts.kind
5761 != gfc_default_integer_kind
5762 || code->expr->symtree->n.sym->as != NULL))
5763 gfc_error ("ASSIGN statement at %L requires a scalar "
5764 "default INTEGER variable", &code->expr->where);
5765 break;
5767 case EXEC_POINTER_ASSIGN:
5768 if (t == FAILURE)
5769 break;
5771 gfc_check_pointer_assign (code->expr, code->expr2);
5772 break;
5774 case EXEC_ARITHMETIC_IF:
5775 if (t == SUCCESS
5776 && code->expr->ts.type != BT_INTEGER
5777 && code->expr->ts.type != BT_REAL)
5778 gfc_error ("Arithmetic IF statement at %L requires a numeric "
5779 "expression", &code->expr->where);
5781 resolve_branch (code->label, code);
5782 resolve_branch (code->label2, code);
5783 resolve_branch (code->label3, code);
5784 break;
5786 case EXEC_IF:
5787 if (t == SUCCESS && code->expr != NULL
5788 && (code->expr->ts.type != BT_LOGICAL
5789 || code->expr->rank != 0))
5790 gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
5791 &code->expr->where);
5792 break;
5794 case EXEC_CALL:
5795 call:
5796 resolve_call (code);
5797 break;
5799 case EXEC_SELECT:
5800 /* Select is complicated. Also, a SELECT construct could be
5801 a transformed computed GOTO. */
5802 resolve_select (code);
5803 break;
5805 case EXEC_DO:
5806 if (code->ext.iterator != NULL)
5808 gfc_iterator *iter = code->ext.iterator;
5809 if (gfc_resolve_iterator (iter, true) != FAILURE)
5810 gfc_resolve_do_iterator (code, iter->var->symtree->n.sym);
5812 break;
5814 case EXEC_DO_WHILE:
5815 if (code->expr == NULL)
5816 gfc_internal_error ("resolve_code(): No expression on DO WHILE");
5817 if (t == SUCCESS
5818 && (code->expr->rank != 0
5819 || code->expr->ts.type != BT_LOGICAL))
5820 gfc_error ("Exit condition of DO WHILE loop at %L must be "
5821 "a scalar LOGICAL expression", &code->expr->where);
5822 break;
5824 case EXEC_ALLOCATE:
5825 if (t == SUCCESS && code->expr != NULL
5826 && code->expr->ts.type != BT_INTEGER)
5827 gfc_error ("STAT tag in ALLOCATE statement at %L must be "
5828 "of type INTEGER", &code->expr->where);
5830 for (a = code->ext.alloc_list; a; a = a->next)
5831 resolve_allocate_expr (a->expr, code);
5833 break;
5835 case EXEC_DEALLOCATE:
5836 if (t == SUCCESS && code->expr != NULL
5837 && code->expr->ts.type != BT_INTEGER)
5838 gfc_error
5839 ("STAT tag in DEALLOCATE statement at %L must be of type "
5840 "INTEGER", &code->expr->where);
5842 for (a = code->ext.alloc_list; a; a = a->next)
5843 resolve_deallocate_expr (a->expr);
5845 break;
5847 case EXEC_OPEN:
5848 if (gfc_resolve_open (code->ext.open) == FAILURE)
5849 break;
5851 resolve_branch (code->ext.open->err, code);
5852 break;
5854 case EXEC_CLOSE:
5855 if (gfc_resolve_close (code->ext.close) == FAILURE)
5856 break;
5858 resolve_branch (code->ext.close->err, code);
5859 break;
5861 case EXEC_BACKSPACE:
5862 case EXEC_ENDFILE:
5863 case EXEC_REWIND:
5864 case EXEC_FLUSH:
5865 if (gfc_resolve_filepos (code->ext.filepos) == FAILURE)
5866 break;
5868 resolve_branch (code->ext.filepos->err, code);
5869 break;
5871 case EXEC_INQUIRE:
5872 if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
5873 break;
5875 resolve_branch (code->ext.inquire->err, code);
5876 break;
5878 case EXEC_IOLENGTH:
5879 gcc_assert (code->ext.inquire != NULL);
5880 if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
5881 break;
5883 resolve_branch (code->ext.inquire->err, code);
5884 break;
5886 case EXEC_READ:
5887 case EXEC_WRITE:
5888 if (gfc_resolve_dt (code->ext.dt) == FAILURE)
5889 break;
5891 resolve_branch (code->ext.dt->err, code);
5892 resolve_branch (code->ext.dt->end, code);
5893 resolve_branch (code->ext.dt->eor, code);
5894 break;
5896 case EXEC_TRANSFER:
5897 resolve_transfer (code);
5898 break;
5900 case EXEC_FORALL:
5901 resolve_forall_iterators (code->ext.forall_iterator);
5903 if (code->expr != NULL && code->expr->ts.type != BT_LOGICAL)
5904 gfc_error ("FORALL mask clause at %L requires a LOGICAL "
5905 "expression", &code->expr->where);
5906 break;
5908 case EXEC_OMP_ATOMIC:
5909 case EXEC_OMP_BARRIER:
5910 case EXEC_OMP_CRITICAL:
5911 case EXEC_OMP_FLUSH:
5912 case EXEC_OMP_DO:
5913 case EXEC_OMP_MASTER:
5914 case EXEC_OMP_ORDERED:
5915 case EXEC_OMP_SECTIONS:
5916 case EXEC_OMP_SINGLE:
5917 case EXEC_OMP_WORKSHARE:
5918 gfc_resolve_omp_directive (code, ns);
5919 break;
5921 case EXEC_OMP_PARALLEL:
5922 case EXEC_OMP_PARALLEL_DO:
5923 case EXEC_OMP_PARALLEL_SECTIONS:
5924 case EXEC_OMP_PARALLEL_WORKSHARE:
5925 omp_workshare_save = omp_workshare_flag;
5926 omp_workshare_flag = 0;
5927 gfc_resolve_omp_directive (code, ns);
5928 omp_workshare_flag = omp_workshare_save;
5929 break;
5931 default:
5932 gfc_internal_error ("resolve_code(): Bad statement code");
5936 cs_base = frame.prev;
5940 /* Resolve initial values and make sure they are compatible with
5941 the variable. */
5943 static void
5944 resolve_values (gfc_symbol *sym)
5946 if (sym->value == NULL)
5947 return;
5949 if (gfc_resolve_expr (sym->value) == FAILURE)
5950 return;
5952 gfc_check_assign_symbol (sym, sym->value);
5956 /* Verify the binding labels for common blocks that are BIND(C). The label
5957 for a BIND(C) common block must be identical in all scoping units in which
5958 the common block is declared. Further, the binding label can not collide
5959 with any other global entity in the program. */
5961 static void
5962 resolve_bind_c_comms (gfc_symtree *comm_block_tree)
5964 if (comm_block_tree->n.common->is_bind_c == 1)
5966 gfc_gsymbol *binding_label_gsym;
5967 gfc_gsymbol *comm_name_gsym;
5969 /* See if a global symbol exists by the common block's name. It may
5970 be NULL if the common block is use-associated. */
5971 comm_name_gsym = gfc_find_gsymbol (gfc_gsym_root,
5972 comm_block_tree->n.common->name);
5973 if (comm_name_gsym != NULL && comm_name_gsym->type != GSYM_COMMON)
5974 gfc_error ("Binding label '%s' for common block '%s' at %L collides "
5975 "with the global entity '%s' at %L",
5976 comm_block_tree->n.common->binding_label,
5977 comm_block_tree->n.common->name,
5978 &(comm_block_tree->n.common->where),
5979 comm_name_gsym->name, &(comm_name_gsym->where));
5980 else if (comm_name_gsym != NULL
5981 && strcmp (comm_name_gsym->name,
5982 comm_block_tree->n.common->name) == 0)
5984 /* TODO: Need to make sure the fields of gfc_gsymbol are initialized
5985 as expected. */
5986 if (comm_name_gsym->binding_label == NULL)
5987 /* No binding label for common block stored yet; save this one. */
5988 comm_name_gsym->binding_label =
5989 comm_block_tree->n.common->binding_label;
5990 else
5991 if (strcmp (comm_name_gsym->binding_label,
5992 comm_block_tree->n.common->binding_label) != 0)
5994 /* Common block names match but binding labels do not. */
5995 gfc_error ("Binding label '%s' for common block '%s' at %L "
5996 "does not match the binding label '%s' for common "
5997 "block '%s' at %L",
5998 comm_block_tree->n.common->binding_label,
5999 comm_block_tree->n.common->name,
6000 &(comm_block_tree->n.common->where),
6001 comm_name_gsym->binding_label,
6002 comm_name_gsym->name,
6003 &(comm_name_gsym->where));
6004 return;
6008 /* There is no binding label (NAME="") so we have nothing further to
6009 check and nothing to add as a global symbol for the label. */
6010 if (comm_block_tree->n.common->binding_label[0] == '\0' )
6011 return;
6013 binding_label_gsym =
6014 gfc_find_gsymbol (gfc_gsym_root,
6015 comm_block_tree->n.common->binding_label);
6016 if (binding_label_gsym == NULL)
6018 /* Need to make a global symbol for the binding label to prevent
6019 it from colliding with another. */
6020 binding_label_gsym =
6021 gfc_get_gsymbol (comm_block_tree->n.common->binding_label);
6022 binding_label_gsym->sym_name = comm_block_tree->n.common->name;
6023 binding_label_gsym->type = GSYM_COMMON;
6025 else
6027 /* If comm_name_gsym is NULL, the name common block is use
6028 associated and the name could be colliding. */
6029 if (binding_label_gsym->type != GSYM_COMMON)
6030 gfc_error ("Binding label '%s' for common block '%s' at %L "
6031 "collides with the global entity '%s' at %L",
6032 comm_block_tree->n.common->binding_label,
6033 comm_block_tree->n.common->name,
6034 &(comm_block_tree->n.common->where),
6035 binding_label_gsym->name,
6036 &(binding_label_gsym->where));
6037 else if (comm_name_gsym != NULL
6038 && (strcmp (binding_label_gsym->name,
6039 comm_name_gsym->binding_label) != 0)
6040 && (strcmp (binding_label_gsym->sym_name,
6041 comm_name_gsym->name) != 0))
6042 gfc_error ("Binding label '%s' for common block '%s' at %L "
6043 "collides with global entity '%s' at %L",
6044 binding_label_gsym->name, binding_label_gsym->sym_name,
6045 &(comm_block_tree->n.common->where),
6046 comm_name_gsym->name, &(comm_name_gsym->where));
6050 return;
6054 /* Verify any BIND(C) derived types in the namespace so we can report errors
6055 for them once, rather than for each variable declared of that type. */
6057 static void
6058 resolve_bind_c_derived_types (gfc_symbol *derived_sym)
6060 if (derived_sym != NULL && derived_sym->attr.flavor == FL_DERIVED
6061 && derived_sym->attr.is_bind_c == 1)
6062 verify_bind_c_derived_type (derived_sym);
6064 return;
6068 /* Verify that any binding labels used in a given namespace do not collide
6069 with the names or binding labels of any global symbols. */
6071 static void
6072 gfc_verify_binding_labels (gfc_symbol *sym)
6074 int has_error = 0;
6076 if (sym != NULL && sym->attr.is_bind_c && sym->attr.is_iso_c == 0
6077 && sym->attr.flavor != FL_DERIVED && sym->binding_label[0] != '\0')
6079 gfc_gsymbol *bind_c_sym;
6081 bind_c_sym = gfc_find_gsymbol (gfc_gsym_root, sym->binding_label);
6082 if (bind_c_sym != NULL
6083 && strcmp (bind_c_sym->name, sym->binding_label) == 0)
6085 if (sym->attr.if_source == IFSRC_DECL
6086 && (bind_c_sym->type != GSYM_SUBROUTINE
6087 && bind_c_sym->type != GSYM_FUNCTION)
6088 && ((sym->attr.contained == 1
6089 && strcmp (bind_c_sym->sym_name, sym->name) != 0)
6090 || (sym->attr.use_assoc == 1
6091 && (strcmp (bind_c_sym->mod_name, sym->module) != 0))))
6093 /* Make sure global procedures don't collide with anything. */
6094 gfc_error ("Binding label '%s' at %L collides with the global "
6095 "entity '%s' at %L", sym->binding_label,
6096 &(sym->declared_at), bind_c_sym->name,
6097 &(bind_c_sym->where));
6098 has_error = 1;
6100 else if (sym->attr.contained == 0
6101 && (sym->attr.if_source == IFSRC_IFBODY
6102 && sym->attr.flavor == FL_PROCEDURE)
6103 && (bind_c_sym->sym_name != NULL
6104 && strcmp (bind_c_sym->sym_name, sym->name) != 0))
6106 /* Make sure procedures in interface bodies don't collide. */
6107 gfc_error ("Binding label '%s' in interface body at %L collides "
6108 "with the global entity '%s' at %L",
6109 sym->binding_label,
6110 &(sym->declared_at), bind_c_sym->name,
6111 &(bind_c_sym->where));
6112 has_error = 1;
6114 else if (sym->attr.contained == 0
6115 && (sym->attr.if_source == IFSRC_UNKNOWN))
6116 if ((sym->attr.use_assoc
6117 && (strcmp (bind_c_sym->mod_name, sym->module) != 0))
6118 || sym->attr.use_assoc == 0)
6120 gfc_error ("Binding label '%s' at %L collides with global "
6121 "entity '%s' at %L", sym->binding_label,
6122 &(sym->declared_at), bind_c_sym->name,
6123 &(bind_c_sym->where));
6124 has_error = 1;
6127 if (has_error != 0)
6128 /* Clear the binding label to prevent checking multiple times. */
6129 sym->binding_label[0] = '\0';
6131 else if (bind_c_sym == NULL)
6133 bind_c_sym = gfc_get_gsymbol (sym->binding_label);
6134 bind_c_sym->where = sym->declared_at;
6135 bind_c_sym->sym_name = sym->name;
6137 if (sym->attr.use_assoc == 1)
6138 bind_c_sym->mod_name = sym->module;
6139 else
6140 if (sym->ns->proc_name != NULL)
6141 bind_c_sym->mod_name = sym->ns->proc_name->name;
6143 if (sym->attr.contained == 0)
6145 if (sym->attr.subroutine)
6146 bind_c_sym->type = GSYM_SUBROUTINE;
6147 else if (sym->attr.function)
6148 bind_c_sym->type = GSYM_FUNCTION;
6152 return;
6156 /* Resolve an index expression. */
6158 static try
6159 resolve_index_expr (gfc_expr *e)
6161 if (gfc_resolve_expr (e) == FAILURE)
6162 return FAILURE;
6164 if (gfc_simplify_expr (e, 0) == FAILURE)
6165 return FAILURE;
6167 if (gfc_specification_expr (e) == FAILURE)
6168 return FAILURE;
6170 return SUCCESS;
6173 /* Resolve a charlen structure. */
6175 static try
6176 resolve_charlen (gfc_charlen *cl)
6178 int i;
6180 if (cl->resolved)
6181 return SUCCESS;
6183 cl->resolved = 1;
6185 specification_expr = 1;
6187 if (resolve_index_expr (cl->length) == FAILURE)
6189 specification_expr = 0;
6190 return FAILURE;
6193 /* "If the character length parameter value evaluates to a negative
6194 value, the length of character entities declared is zero." */
6195 if (cl->length && !gfc_extract_int (cl->length, &i) && i <= 0)
6197 gfc_warning_now ("CHARACTER variable has zero length at %L",
6198 &cl->length->where);
6199 gfc_replace_expr (cl->length, gfc_int_expr (0));
6202 return SUCCESS;
6206 /* Test for non-constant shape arrays. */
6208 static bool
6209 is_non_constant_shape_array (gfc_symbol *sym)
6211 gfc_expr *e;
6212 int i;
6213 bool not_constant;
6215 not_constant = false;
6216 if (sym->as != NULL)
6218 /* Unfortunately, !gfc_is_compile_time_shape hits a legal case that
6219 has not been simplified; parameter array references. Do the
6220 simplification now. */
6221 for (i = 0; i < sym->as->rank; i++)
6223 e = sym->as->lower[i];
6224 if (e && (resolve_index_expr (e) == FAILURE
6225 || !gfc_is_constant_expr (e)))
6226 not_constant = true;
6228 e = sym->as->upper[i];
6229 if (e && (resolve_index_expr (e) == FAILURE
6230 || !gfc_is_constant_expr (e)))
6231 not_constant = true;
6234 return not_constant;
6238 /* Assign the default initializer to a derived type variable or result. */
6240 static void
6241 apply_default_init (gfc_symbol *sym)
6243 gfc_expr *lval;
6244 gfc_expr *init = NULL;
6245 gfc_code *init_st;
6246 gfc_namespace *ns = sym->ns;
6248 if (sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
6249 return;
6251 if (sym->ts.type == BT_DERIVED && sym->ts.derived)
6252 init = gfc_default_initializer (&sym->ts);
6254 if (init == NULL)
6255 return;
6257 /* Search for the function namespace if this is a contained
6258 function without an explicit result. */
6259 if (sym->attr.function && sym == sym->result
6260 && sym->name != sym->ns->proc_name->name)
6262 ns = ns->contained;
6263 for (;ns; ns = ns->sibling)
6264 if (strcmp (ns->proc_name->name, sym->name) == 0)
6265 break;
6268 if (ns == NULL)
6270 gfc_free_expr (init);
6271 return;
6274 /* Build an l-value expression for the result. */
6275 lval = gfc_get_expr ();
6276 lval->expr_type = EXPR_VARIABLE;
6277 lval->where = sym->declared_at;
6278 lval->ts = sym->ts;
6279 lval->symtree = gfc_find_symtree (sym->ns->sym_root, sym->name);
6281 /* It will always be a full array. */
6282 lval->rank = sym->as ? sym->as->rank : 0;
6283 if (lval->rank)
6285 lval->ref = gfc_get_ref ();
6286 lval->ref->type = REF_ARRAY;
6287 lval->ref->u.ar.type = AR_FULL;
6288 lval->ref->u.ar.dimen = lval->rank;
6289 lval->ref->u.ar.where = sym->declared_at;
6290 lval->ref->u.ar.as = sym->as;
6293 /* Add the code at scope entry. */
6294 init_st = gfc_get_code ();
6295 init_st->next = ns->code;
6296 ns->code = init_st;
6298 /* Assign the default initializer to the l-value. */
6299 init_st->loc = sym->declared_at;
6300 init_st->op = EXEC_INIT_ASSIGN;
6301 init_st->expr = lval;
6302 init_st->expr2 = init;
6306 /* Resolution of common features of flavors variable and procedure. */
6308 static try
6309 resolve_fl_var_and_proc (gfc_symbol *sym, int mp_flag)
6311 /* Constraints on deferred shape variable. */
6312 if (sym->as == NULL || sym->as->type != AS_DEFERRED)
6314 if (sym->attr.allocatable)
6316 if (sym->attr.dimension)
6317 gfc_error ("Allocatable array '%s' at %L must have "
6318 "a deferred shape", sym->name, &sym->declared_at);
6319 else
6320 gfc_error ("Scalar object '%s' at %L may not be ALLOCATABLE",
6321 sym->name, &sym->declared_at);
6322 return FAILURE;
6325 if (sym->attr.pointer && sym->attr.dimension)
6327 gfc_error ("Array pointer '%s' at %L must have a deferred shape",
6328 sym->name, &sym->declared_at);
6329 return FAILURE;
6333 else
6335 if (!mp_flag && !sym->attr.allocatable
6336 && !sym->attr.pointer && !sym->attr.dummy)
6338 gfc_error ("Array '%s' at %L cannot have a deferred shape",
6339 sym->name, &sym->declared_at);
6340 return FAILURE;
6343 return SUCCESS;
6347 static gfc_component *
6348 has_default_initializer (gfc_symbol *der)
6350 gfc_component *c;
6351 for (c = der->components; c; c = c->next)
6352 if ((c->ts.type != BT_DERIVED && c->initializer)
6353 || (c->ts.type == BT_DERIVED
6354 && !c->pointer
6355 && has_default_initializer (c->ts.derived)))
6356 break;
6358 return c;
6362 /* Resolve symbols with flavor variable. */
6364 static try
6365 resolve_fl_variable (gfc_symbol *sym, int mp_flag)
6367 int flag;
6368 int i;
6369 gfc_expr *e;
6370 gfc_component *c;
6371 const char *auto_save_msg;
6373 auto_save_msg = "automatic object '%s' at %L cannot have the "
6374 "SAVE attribute";
6376 if (resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
6377 return FAILURE;
6379 /* Set this flag to check that variables are parameters of all entries.
6380 This check is effected by the call to gfc_resolve_expr through
6381 is_non_constant_shape_array. */
6382 specification_expr = 1;
6384 if (!sym->attr.use_assoc
6385 && !sym->attr.allocatable
6386 && !sym->attr.pointer
6387 && is_non_constant_shape_array (sym))
6389 /* The shape of a main program or module array needs to be
6390 constant. */
6391 if (sym->ns->proc_name
6392 && (sym->ns->proc_name->attr.flavor == FL_MODULE
6393 || sym->ns->proc_name->attr.is_main_program))
6395 gfc_error ("The module or main program array '%s' at %L must "
6396 "have constant shape", sym->name, &sym->declared_at);
6397 specification_expr = 0;
6398 return FAILURE;
6402 if (sym->ts.type == BT_CHARACTER)
6404 /* Make sure that character string variables with assumed length are
6405 dummy arguments. */
6406 e = sym->ts.cl->length;
6407 if (e == NULL && !sym->attr.dummy && !sym->attr.result)
6409 gfc_error ("Entity with assumed character length at %L must be a "
6410 "dummy argument or a PARAMETER", &sym->declared_at);
6411 return FAILURE;
6414 if (e && sym->attr.save && !gfc_is_constant_expr (e))
6416 gfc_error (auto_save_msg, sym->name, &sym->declared_at);
6417 return FAILURE;
6420 if (!gfc_is_constant_expr (e)
6421 && !(e->expr_type == EXPR_VARIABLE
6422 && e->symtree->n.sym->attr.flavor == FL_PARAMETER)
6423 && sym->ns->proc_name
6424 && (sym->ns->proc_name->attr.flavor == FL_MODULE
6425 || sym->ns->proc_name->attr.is_main_program)
6426 && !sym->attr.use_assoc)
6428 gfc_error ("'%s' at %L must have constant character length "
6429 "in this context", sym->name, &sym->declared_at);
6430 return FAILURE;
6434 /* Can the symbol have an initializer? */
6435 flag = 0;
6436 if (sym->attr.allocatable || sym->attr.external || sym->attr.dummy
6437 || sym->attr.intrinsic || sym->attr.result)
6438 flag = 1;
6439 else if (sym->attr.dimension && !sym->attr.pointer)
6441 /* Don't allow initialization of automatic arrays. */
6442 for (i = 0; i < sym->as->rank; i++)
6444 if (sym->as->lower[i] == NULL
6445 || sym->as->lower[i]->expr_type != EXPR_CONSTANT
6446 || sym->as->upper[i] == NULL
6447 || sym->as->upper[i]->expr_type != EXPR_CONSTANT)
6449 flag = 2;
6450 break;
6454 /* Also, they must not have the SAVE attribute. */
6455 if (flag && sym->attr.save)
6457 gfc_error (auto_save_msg, sym->name, &sym->declared_at);
6458 return FAILURE;
6462 /* Reject illegal initializers. */
6463 if (sym->value && flag)
6465 if (sym->attr.allocatable)
6466 gfc_error ("Allocatable '%s' at %L cannot have an initializer",
6467 sym->name, &sym->declared_at);
6468 else if (sym->attr.external)
6469 gfc_error ("External '%s' at %L cannot have an initializer",
6470 sym->name, &sym->declared_at);
6471 else if (sym->attr.dummy
6472 && !(sym->ts.type == BT_DERIVED && sym->attr.intent == INTENT_OUT))
6473 gfc_error ("Dummy '%s' at %L cannot have an initializer",
6474 sym->name, &sym->declared_at);
6475 else if (sym->attr.intrinsic)
6476 gfc_error ("Intrinsic '%s' at %L cannot have an initializer",
6477 sym->name, &sym->declared_at);
6478 else if (sym->attr.result)
6479 gfc_error ("Function result '%s' at %L cannot have an initializer",
6480 sym->name, &sym->declared_at);
6481 else if (flag == 2)
6482 gfc_error ("Automatic array '%s' at %L cannot have an initializer",
6483 sym->name, &sym->declared_at);
6484 else
6485 goto no_init_error;
6486 return FAILURE;
6489 no_init_error:
6490 /* Check to see if a derived type is blocked from being host associated
6491 by the presence of another class I symbol in the same namespace.
6492 14.6.1.3 of the standard and the discussion on comp.lang.fortran. */
6493 if (sym->ts.type == BT_DERIVED && sym->ns != sym->ts.derived->ns
6494 && sym->ns->proc_name->attr.if_source != IFSRC_IFBODY)
6496 gfc_symbol *s;
6497 gfc_find_symbol (sym->ts.derived->name, sym->ns, 0, &s);
6498 if (s && (s->attr.flavor != FL_DERIVED
6499 || !gfc_compare_derived_types (s, sym->ts.derived)))
6501 gfc_error ("The type %s cannot be host associated at %L because "
6502 "it is blocked by an incompatible object of the same "
6503 "name at %L", sym->ts.derived->name, &sym->declared_at,
6504 &s->declared_at);
6505 return FAILURE;
6509 /* Do not use gfc_default_initializer to test for a default initializer
6510 in the fortran because it generates a hidden default for allocatable
6511 components. */
6512 c = NULL;
6513 if (sym->ts.type == BT_DERIVED && !(sym->value || flag))
6514 c = has_default_initializer (sym->ts.derived);
6516 /* 4th constraint in section 11.3: "If an object of a type for which
6517 component-initialization is specified (R429) appears in the
6518 specification-part of a module and does not have the ALLOCATABLE
6519 or POINTER attribute, the object shall have the SAVE attribute." */
6520 if (c && sym->ns->proc_name
6521 && sym->ns->proc_name->attr.flavor == FL_MODULE
6522 && !sym->ns->save_all && !sym->attr.save
6523 && !sym->attr.pointer && !sym->attr.allocatable)
6525 gfc_error("Object '%s' at %L must have the SAVE attribute %s",
6526 sym->name, &sym->declared_at,
6527 "for default initialization of a component");
6528 return FAILURE;
6531 /* Assign default initializer. */
6532 if (sym->ts.type == BT_DERIVED
6533 && !sym->value
6534 && !sym->attr.pointer
6535 && !sym->attr.allocatable
6536 && (!flag || sym->attr.intent == INTENT_OUT))
6537 sym->value = gfc_default_initializer (&sym->ts);
6539 return SUCCESS;
6543 /* Resolve a procedure. */
6545 static try
6546 resolve_fl_procedure (gfc_symbol *sym, int mp_flag)
6548 gfc_formal_arglist *arg;
6550 if (sym->attr.ambiguous_interfaces && !sym->attr.referenced)
6551 gfc_warning ("Although not referenced, '%s' at %L has ambiguous "
6552 "interfaces", sym->name, &sym->declared_at);
6554 if (sym->attr.function
6555 && resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
6556 return FAILURE;
6558 if (sym->ts.type == BT_CHARACTER)
6560 gfc_charlen *cl = sym->ts.cl;
6562 if (cl && cl->length && gfc_is_constant_expr (cl->length)
6563 && resolve_charlen (cl) == FAILURE)
6564 return FAILURE;
6566 if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
6568 if (sym->attr.proc == PROC_ST_FUNCTION)
6570 gfc_error ("Character-valued statement function '%s' at %L must "
6571 "have constant length", sym->name, &sym->declared_at);
6572 return FAILURE;
6575 if (sym->attr.external && sym->formal == NULL
6576 && cl && cl->length && cl->length->expr_type != EXPR_CONSTANT)
6578 gfc_error ("Automatic character length function '%s' at %L must "
6579 "have an explicit interface", sym->name,
6580 &sym->declared_at);
6581 return FAILURE;
6586 /* Ensure that derived type for are not of a private type. Internal
6587 module procedures are excluded by 2.2.3.3 - ie. they are not
6588 externally accessible and can access all the objects accessible in
6589 the host. */
6590 if (!(sym->ns->parent
6591 && sym->ns->parent->proc_name->attr.flavor == FL_MODULE)
6592 && gfc_check_access(sym->attr.access, sym->ns->default_access))
6594 for (arg = sym->formal; arg; arg = arg->next)
6596 if (arg->sym
6597 && arg->sym->ts.type == BT_DERIVED
6598 && !arg->sym->ts.derived->attr.use_assoc
6599 && !gfc_check_access (arg->sym->ts.derived->attr.access,
6600 arg->sym->ts.derived->ns->default_access))
6602 gfc_error_now ("'%s' is of a PRIVATE type and cannot be "
6603 "a dummy argument of '%s', which is "
6604 "PUBLIC at %L", arg->sym->name, sym->name,
6605 &sym->declared_at);
6606 /* Stop this message from recurring. */
6607 arg->sym->ts.derived->attr.access = ACCESS_PUBLIC;
6608 return FAILURE;
6613 /* An external symbol may not have an initializer because it is taken to be
6614 a procedure. */
6615 if (sym->attr.external && sym->value)
6617 gfc_error ("External object '%s' at %L may not have an initializer",
6618 sym->name, &sym->declared_at);
6619 return FAILURE;
6622 /* An elemental function is required to return a scalar 12.7.1 */
6623 if (sym->attr.elemental && sym->attr.function && sym->as)
6625 gfc_error ("ELEMENTAL function '%s' at %L must have a scalar "
6626 "result", sym->name, &sym->declared_at);
6627 /* Reset so that the error only occurs once. */
6628 sym->attr.elemental = 0;
6629 return FAILURE;
6632 /* 5.1.1.5 of the Standard: A function name declared with an asterisk
6633 char-len-param shall not be array-valued, pointer-valued, recursive
6634 or pure. ....snip... A character value of * may only be used in the
6635 following ways: (i) Dummy arg of procedure - dummy associates with
6636 actual length; (ii) To declare a named constant; or (iii) External
6637 function - but length must be declared in calling scoping unit. */
6638 if (sym->attr.function
6639 && sym->ts.type == BT_CHARACTER
6640 && sym->ts.cl && sym->ts.cl->length == NULL)
6642 if ((sym->as && sym->as->rank) || (sym->attr.pointer)
6643 || (sym->attr.recursive) || (sym->attr.pure))
6645 if (sym->as && sym->as->rank)
6646 gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
6647 "array-valued", sym->name, &sym->declared_at);
6649 if (sym->attr.pointer)
6650 gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
6651 "pointer-valued", sym->name, &sym->declared_at);
6653 if (sym->attr.pure)
6654 gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
6655 "pure", sym->name, &sym->declared_at);
6657 if (sym->attr.recursive)
6658 gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
6659 "recursive", sym->name, &sym->declared_at);
6661 return FAILURE;
6664 /* Appendix B.2 of the standard. Contained functions give an
6665 error anyway. Fixed-form is likely to be F77/legacy. */
6666 if (!sym->attr.contained && gfc_current_form != FORM_FIXED)
6667 gfc_notify_std (GFC_STD_F95_OBS, "CHARACTER(*) function "
6668 "'%s' at %L is obsolescent in fortran 95",
6669 sym->name, &sym->declared_at);
6672 if (sym->attr.is_bind_c && sym->attr.is_c_interop != 1)
6674 gfc_formal_arglist *curr_arg;
6676 if (verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
6677 sym->common_block) == FAILURE)
6679 /* Clear these to prevent looking at them again if there was an
6680 error. */
6681 sym->attr.is_bind_c = 0;
6682 sym->attr.is_c_interop = 0;
6683 sym->ts.is_c_interop = 0;
6685 else
6687 /* So far, no errors have been found. */
6688 sym->attr.is_c_interop = 1;
6689 sym->ts.is_c_interop = 1;
6692 curr_arg = sym->formal;
6693 while (curr_arg != NULL)
6695 /* Skip implicitly typed dummy args here. */
6696 if (curr_arg->sym->attr.implicit_type == 0
6697 && verify_c_interop_param (curr_arg->sym) == FAILURE)
6699 /* If something is found to fail, mark the symbol for the
6700 procedure as not being BIND(C) to try and prevent multiple
6701 errors being reported. */
6702 sym->attr.is_c_interop = 0;
6703 sym->ts.is_c_interop = 0;
6704 sym->attr.is_bind_c = 0;
6706 curr_arg = curr_arg->next;
6710 return SUCCESS;
6714 /* Resolve the components of a derived type. */
6716 static try
6717 resolve_fl_derived (gfc_symbol *sym)
6719 gfc_component *c;
6720 gfc_dt_list * dt_list;
6721 int i;
6723 for (c = sym->components; c != NULL; c = c->next)
6725 if (c->ts.type == BT_CHARACTER)
6727 if (c->ts.cl->length == NULL
6728 || (resolve_charlen (c->ts.cl) == FAILURE)
6729 || !gfc_is_constant_expr (c->ts.cl->length))
6731 gfc_error ("Character length of component '%s' needs to "
6732 "be a constant specification expression at %L",
6733 c->name,
6734 c->ts.cl->length ? &c->ts.cl->length->where : &c->loc);
6735 return FAILURE;
6739 if (c->ts.type == BT_DERIVED
6740 && sym->component_access != ACCESS_PRIVATE
6741 && gfc_check_access (sym->attr.access, sym->ns->default_access)
6742 && !c->ts.derived->attr.use_assoc
6743 && !gfc_check_access (c->ts.derived->attr.access,
6744 c->ts.derived->ns->default_access))
6746 gfc_error ("The component '%s' is a PRIVATE type and cannot be "
6747 "a component of '%s', which is PUBLIC at %L",
6748 c->name, sym->name, &sym->declared_at);
6749 return FAILURE;
6752 if (sym->attr.sequence)
6754 if (c->ts.type == BT_DERIVED && c->ts.derived->attr.sequence == 0)
6756 gfc_error ("Component %s of SEQUENCE type declared at %L does "
6757 "not have the SEQUENCE attribute",
6758 c->ts.derived->name, &sym->declared_at);
6759 return FAILURE;
6763 if (c->ts.type == BT_DERIVED && c->pointer
6764 && c->ts.derived->components == NULL)
6766 gfc_error ("The pointer component '%s' of '%s' at %L is a type "
6767 "that has not been declared", c->name, sym->name,
6768 &c->loc);
6769 return FAILURE;
6772 if (c->pointer || c->allocatable || c->as == NULL)
6773 continue;
6775 for (i = 0; i < c->as->rank; i++)
6777 if (c->as->lower[i] == NULL
6778 || !gfc_is_constant_expr (c->as->lower[i])
6779 || (resolve_index_expr (c->as->lower[i]) == FAILURE)
6780 || c->as->upper[i] == NULL
6781 || (resolve_index_expr (c->as->upper[i]) == FAILURE)
6782 || !gfc_is_constant_expr (c->as->upper[i]))
6784 gfc_error ("Component '%s' of '%s' at %L must have "
6785 "constant array bounds",
6786 c->name, sym->name, &c->loc);
6787 return FAILURE;
6792 /* Add derived type to the derived type list. */
6793 for (dt_list = gfc_derived_types; dt_list; dt_list = dt_list->next)
6794 if (sym == dt_list->derived)
6795 break;
6797 if (dt_list == NULL)
6799 dt_list = gfc_get_dt_list ();
6800 dt_list->next = gfc_derived_types;
6801 dt_list->derived = sym;
6802 gfc_derived_types = dt_list;
6805 return SUCCESS;
6809 static try
6810 resolve_fl_namelist (gfc_symbol *sym)
6812 gfc_namelist *nl;
6813 gfc_symbol *nlsym;
6815 /* Reject PRIVATE objects in a PUBLIC namelist. */
6816 if (gfc_check_access(sym->attr.access, sym->ns->default_access))
6818 for (nl = sym->namelist; nl; nl = nl->next)
6820 if (!nl->sym->attr.use_assoc
6821 && !(sym->ns->parent == nl->sym->ns)
6822 && !gfc_check_access(nl->sym->attr.access,
6823 nl->sym->ns->default_access))
6825 gfc_error ("PRIVATE symbol '%s' cannot be member of "
6826 "PUBLIC namelist at %L", nl->sym->name,
6827 &sym->declared_at);
6828 return FAILURE;
6833 /* Reject namelist arrays that are not constant shape. */
6834 for (nl = sym->namelist; nl; nl = nl->next)
6836 if (is_non_constant_shape_array (nl->sym))
6838 gfc_error ("The array '%s' must have constant shape to be "
6839 "a NAMELIST object at %L", nl->sym->name,
6840 &sym->declared_at);
6841 return FAILURE;
6845 /* Namelist objects cannot have allocatable components. */
6846 for (nl = sym->namelist; nl; nl = nl->next)
6848 if (nl->sym->ts.type == BT_DERIVED
6849 && nl->sym->ts.derived->attr.alloc_comp)
6851 gfc_error ("NAMELIST object '%s' at %L cannot have ALLOCATABLE "
6852 "components", nl->sym->name, &sym->declared_at);
6853 return FAILURE;
6857 /* 14.1.2 A module or internal procedure represent local entities
6858 of the same type as a namelist member and so are not allowed. */
6859 for (nl = sym->namelist; nl; nl = nl->next)
6861 if (nl->sym->ts.kind != 0 && nl->sym->attr.flavor == FL_VARIABLE)
6862 continue;
6864 if (nl->sym->attr.function && nl->sym == nl->sym->result)
6865 if ((nl->sym == sym->ns->proc_name)
6867 (sym->ns->parent && nl->sym == sym->ns->parent->proc_name))
6868 continue;
6870 nlsym = NULL;
6871 if (nl->sym && nl->sym->name)
6872 gfc_find_symbol (nl->sym->name, sym->ns, 1, &nlsym);
6873 if (nlsym && nlsym->attr.flavor == FL_PROCEDURE)
6875 gfc_error ("PROCEDURE attribute conflicts with NAMELIST "
6876 "attribute in '%s' at %L", nlsym->name,
6877 &sym->declared_at);
6878 return FAILURE;
6882 return SUCCESS;
6886 static try
6887 resolve_fl_parameter (gfc_symbol *sym)
6889 /* A parameter array's shape needs to be constant. */
6890 if (sym->as != NULL && !gfc_is_compile_time_shape (sym->as))
6892 gfc_error ("Parameter array '%s' at %L cannot be automatic "
6893 "or assumed shape", sym->name, &sym->declared_at);
6894 return FAILURE;
6897 /* Make sure a parameter that has been implicitly typed still
6898 matches the implicit type, since PARAMETER statements can precede
6899 IMPLICIT statements. */
6900 if (sym->attr.implicit_type
6901 && !gfc_compare_types (&sym->ts, gfc_get_default_type (sym, sym->ns)))
6903 gfc_error ("Implicitly typed PARAMETER '%s' at %L doesn't match a "
6904 "later IMPLICIT type", sym->name, &sym->declared_at);
6905 return FAILURE;
6908 /* Make sure the types of derived parameters are consistent. This
6909 type checking is deferred until resolution because the type may
6910 refer to a derived type from the host. */
6911 if (sym->ts.type == BT_DERIVED
6912 && !gfc_compare_types (&sym->ts, &sym->value->ts))
6914 gfc_error ("Incompatible derived type in PARAMETER at %L",
6915 &sym->value->where);
6916 return FAILURE;
6918 return SUCCESS;
6922 /* Do anything necessary to resolve a symbol. Right now, we just
6923 assume that an otherwise unknown symbol is a variable. This sort
6924 of thing commonly happens for symbols in module. */
6926 static void
6927 resolve_symbol (gfc_symbol *sym)
6929 int check_constant, mp_flag;
6930 gfc_symtree *symtree;
6931 gfc_symtree *this_symtree;
6932 gfc_namespace *ns;
6933 gfc_component *c;
6935 if (sym->attr.flavor == FL_UNKNOWN)
6938 /* If we find that a flavorless symbol is an interface in one of the
6939 parent namespaces, find its symtree in this namespace, free the
6940 symbol and set the symtree to point to the interface symbol. */
6941 for (ns = gfc_current_ns->parent; ns; ns = ns->parent)
6943 symtree = gfc_find_symtree (ns->sym_root, sym->name);
6944 if (symtree && symtree->n.sym->generic)
6946 this_symtree = gfc_find_symtree (gfc_current_ns->sym_root,
6947 sym->name);
6948 sym->refs--;
6949 if (!sym->refs)
6950 gfc_free_symbol (sym);
6951 symtree->n.sym->refs++;
6952 this_symtree->n.sym = symtree->n.sym;
6953 return;
6957 /* Otherwise give it a flavor according to such attributes as
6958 it has. */
6959 if (sym->attr.external == 0 && sym->attr.intrinsic == 0)
6960 sym->attr.flavor = FL_VARIABLE;
6961 else
6963 sym->attr.flavor = FL_PROCEDURE;
6964 if (sym->attr.dimension)
6965 sym->attr.function = 1;
6969 if (sym->attr.flavor == FL_DERIVED && resolve_fl_derived (sym) == FAILURE)
6970 return;
6972 /* Symbols that are module procedures with results (functions) have
6973 the types and array specification copied for type checking in
6974 procedures that call them, as well as for saving to a module
6975 file. These symbols can't stand the scrutiny that their results
6976 can. */
6977 mp_flag = (sym->result != NULL && sym->result != sym);
6980 /* Make sure that the intrinsic is consistent with its internal
6981 representation. This needs to be done before assigning a default
6982 type to avoid spurious warnings. */
6983 if (sym->attr.flavor != FL_MODULE && sym->attr.intrinsic)
6985 if (gfc_intrinsic_name (sym->name, 0))
6987 if (sym->ts.type != BT_UNKNOWN && gfc_option.warn_surprising)
6988 gfc_warning ("Type specified for intrinsic function '%s' at %L is ignored",
6989 sym->name, &sym->declared_at);
6991 else if (gfc_intrinsic_name (sym->name, 1))
6993 if (sym->ts.type != BT_UNKNOWN)
6995 gfc_error ("Intrinsic subroutine '%s' at %L shall not have a type specifier",
6996 sym->name, &sym->declared_at);
6997 return;
7000 else
7002 gfc_error ("Intrinsic '%s' at %L does not exist", sym->name, &sym->declared_at);
7003 return;
7007 /* Assign default type to symbols that need one and don't have one. */
7008 if (sym->ts.type == BT_UNKNOWN)
7010 if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER)
7011 gfc_set_default_type (sym, 1, NULL);
7013 if (sym->attr.flavor == FL_PROCEDURE && sym->attr.function)
7015 /* The specific case of an external procedure should emit an error
7016 in the case that there is no implicit type. */
7017 if (!mp_flag)
7018 gfc_set_default_type (sym, sym->attr.external, NULL);
7019 else
7021 /* Result may be in another namespace. */
7022 resolve_symbol (sym->result);
7024 sym->ts = sym->result->ts;
7025 sym->as = gfc_copy_array_spec (sym->result->as);
7026 sym->attr.dimension = sym->result->attr.dimension;
7027 sym->attr.pointer = sym->result->attr.pointer;
7028 sym->attr.allocatable = sym->result->attr.allocatable;
7033 /* Assumed size arrays and assumed shape arrays must be dummy
7034 arguments. */
7036 if (sym->as != NULL
7037 && (sym->as->type == AS_ASSUMED_SIZE
7038 || sym->as->type == AS_ASSUMED_SHAPE)
7039 && sym->attr.dummy == 0)
7041 if (sym->as->type == AS_ASSUMED_SIZE)
7042 gfc_error ("Assumed size array at %L must be a dummy argument",
7043 &sym->declared_at);
7044 else
7045 gfc_error ("Assumed shape array at %L must be a dummy argument",
7046 &sym->declared_at);
7047 return;
7050 /* Make sure symbols with known intent or optional are really dummy
7051 variable. Because of ENTRY statement, this has to be deferred
7052 until resolution time. */
7054 if (!sym->attr.dummy
7055 && (sym->attr.optional || sym->attr.intent != INTENT_UNKNOWN))
7057 gfc_error ("Symbol at %L is not a DUMMY variable", &sym->declared_at);
7058 return;
7061 if (sym->attr.value && !sym->attr.dummy)
7063 gfc_error ("'%s' at %L cannot have the VALUE attribute because "
7064 "it is not a dummy argument", sym->name, &sym->declared_at);
7065 return;
7068 if (sym->attr.value && sym->ts.type == BT_CHARACTER)
7070 gfc_charlen *cl = sym->ts.cl;
7071 if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
7073 gfc_error ("Character dummy variable '%s' at %L with VALUE "
7074 "attribute must have constant length",
7075 sym->name, &sym->declared_at);
7076 return;
7079 if (sym->ts.is_c_interop
7080 && mpz_cmp_si (cl->length->value.integer, 1) != 0)
7082 gfc_error ("C interoperable character dummy variable '%s' at %L "
7083 "with VALUE attribute must have length one",
7084 sym->name, &sym->declared_at);
7085 return;
7089 /* If the symbol is marked as bind(c), verify it's type and kind. Do not
7090 do this for something that was implicitly typed because that is handled
7091 in gfc_set_default_type. Handle dummy arguments and procedure
7092 definitions separately. Also, anything that is use associated is not
7093 handled here but instead is handled in the module it is declared in.
7094 Finally, derived type definitions are allowed to be BIND(C) since that
7095 only implies that they're interoperable, and they are checked fully for
7096 interoperability when a variable is declared of that type. */
7097 if (sym->attr.is_bind_c && sym->attr.implicit_type == 0 &&
7098 sym->attr.use_assoc == 0 && sym->attr.dummy == 0 &&
7099 sym->attr.flavor != FL_PROCEDURE && sym->attr.flavor != FL_DERIVED)
7101 try t = SUCCESS;
7103 /* First, make sure the variable is declared at the
7104 module-level scope (J3/04-007, Section 15.3). */
7105 if (sym->ns->proc_name->attr.flavor != FL_MODULE &&
7106 sym->attr.in_common == 0)
7108 gfc_error ("Variable '%s' at %L cannot be BIND(C) because it "
7109 "is neither a COMMON block nor declared at the "
7110 "module level scope", sym->name, &(sym->declared_at));
7111 t = FAILURE;
7113 else if (sym->common_head != NULL)
7115 t = verify_com_block_vars_c_interop (sym->common_head);
7117 else
7119 /* If type() declaration, we need to verify that the components
7120 of the given type are all C interoperable, etc. */
7121 if (sym->ts.type == BT_DERIVED &&
7122 sym->ts.derived->attr.is_c_interop != 1)
7124 /* Make sure the user marked the derived type as BIND(C). If
7125 not, call the verify routine. This could print an error
7126 for the derived type more than once if multiple variables
7127 of that type are declared. */
7128 if (sym->ts.derived->attr.is_bind_c != 1)
7129 verify_bind_c_derived_type (sym->ts.derived);
7130 t = FAILURE;
7133 /* Verify the variable itself as C interoperable if it
7134 is BIND(C). It is not possible for this to succeed if
7135 the verify_bind_c_derived_type failed, so don't have to handle
7136 any error returned by verify_bind_c_derived_type. */
7137 t = verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
7138 sym->common_block);
7141 if (t == FAILURE)
7143 /* clear the is_bind_c flag to prevent reporting errors more than
7144 once if something failed. */
7145 sym->attr.is_bind_c = 0;
7146 return;
7150 /* If a derived type symbol has reached this point, without its
7151 type being declared, we have an error. Notice that most
7152 conditions that produce undefined derived types have already
7153 been dealt with. However, the likes of:
7154 implicit type(t) (t) ..... call foo (t) will get us here if
7155 the type is not declared in the scope of the implicit
7156 statement. Change the type to BT_UNKNOWN, both because it is so
7157 and to prevent an ICE. */
7158 if (sym->ts.type == BT_DERIVED && sym->ts.derived->components == NULL)
7160 gfc_error ("The derived type '%s' at %L is of type '%s', "
7161 "which has not been defined", sym->name,
7162 &sym->declared_at, sym->ts.derived->name);
7163 sym->ts.type = BT_UNKNOWN;
7164 return;
7167 /* An assumed-size array with INTENT(OUT) shall not be of a type for which
7168 default initialization is defined (5.1.2.4.4). */
7169 if (sym->ts.type == BT_DERIVED
7170 && sym->attr.dummy
7171 && sym->attr.intent == INTENT_OUT
7172 && sym->as
7173 && sym->as->type == AS_ASSUMED_SIZE)
7175 for (c = sym->ts.derived->components; c; c = c->next)
7177 if (c->initializer)
7179 gfc_error ("The INTENT(OUT) dummy argument '%s' at %L is "
7180 "ASSUMED SIZE and so cannot have a default initializer",
7181 sym->name, &sym->declared_at);
7182 return;
7187 switch (sym->attr.flavor)
7189 case FL_VARIABLE:
7190 if (resolve_fl_variable (sym, mp_flag) == FAILURE)
7191 return;
7192 break;
7194 case FL_PROCEDURE:
7195 if (resolve_fl_procedure (sym, mp_flag) == FAILURE)
7196 return;
7197 break;
7199 case FL_NAMELIST:
7200 if (resolve_fl_namelist (sym) == FAILURE)
7201 return;
7202 break;
7204 case FL_PARAMETER:
7205 if (resolve_fl_parameter (sym) == FAILURE)
7206 return;
7207 break;
7209 default:
7210 break;
7213 /* Resolve array specifier. Check as well some constraints
7214 on COMMON blocks. */
7216 check_constant = sym->attr.in_common && !sym->attr.pointer;
7218 /* Set the formal_arg_flag so that check_conflict will not throw
7219 an error for host associated variables in the specification
7220 expression for an array_valued function. */
7221 if (sym->attr.function && sym->as)
7222 formal_arg_flag = 1;
7224 gfc_resolve_array_spec (sym->as, check_constant);
7226 formal_arg_flag = 0;
7228 /* Resolve formal namespaces. */
7229 if (sym->formal_ns && sym->formal_ns != gfc_current_ns)
7230 gfc_resolve (sym->formal_ns);
7232 /* Check threadprivate restrictions. */
7233 if (sym->attr.threadprivate && !sym->attr.save
7234 && (!sym->attr.in_common
7235 && sym->module == NULL
7236 && (sym->ns->proc_name == NULL
7237 || sym->ns->proc_name->attr.flavor != FL_MODULE)))
7238 gfc_error ("Threadprivate at %L isn't SAVEd", &sym->declared_at);
7240 /* If we have come this far we can apply default-initializers, as
7241 described in 14.7.5, to those variables that have not already
7242 been assigned one. */
7243 if (sym->ts.type == BT_DERIVED
7244 && sym->attr.referenced
7245 && sym->ns == gfc_current_ns
7246 && !sym->value
7247 && !sym->attr.allocatable
7248 && !sym->attr.alloc_comp)
7250 symbol_attribute *a = &sym->attr;
7252 if ((!a->save && !a->dummy && !a->pointer
7253 && !a->in_common && !a->use_assoc
7254 && !(a->function && sym != sym->result))
7255 || (a->dummy && a->intent == INTENT_OUT))
7256 apply_default_init (sym);
7261 /************* Resolve DATA statements *************/
7263 static struct
7265 gfc_data_value *vnode;
7266 unsigned int left;
7268 values;
7271 /* Advance the values structure to point to the next value in the data list. */
7273 static try
7274 next_data_value (void)
7276 while (values.left == 0)
7278 if (values.vnode->next == NULL)
7279 return FAILURE;
7281 values.vnode = values.vnode->next;
7282 values.left = values.vnode->repeat;
7285 return SUCCESS;
7289 static try
7290 check_data_variable (gfc_data_variable *var, locus *where)
7292 gfc_expr *e;
7293 mpz_t size;
7294 mpz_t offset;
7295 try t;
7296 ar_type mark = AR_UNKNOWN;
7297 int i;
7298 mpz_t section_index[GFC_MAX_DIMENSIONS];
7299 gfc_ref *ref;
7300 gfc_array_ref *ar;
7302 if (gfc_resolve_expr (var->expr) == FAILURE)
7303 return FAILURE;
7305 ar = NULL;
7306 mpz_init_set_si (offset, 0);
7307 e = var->expr;
7309 if (e->expr_type != EXPR_VARIABLE)
7310 gfc_internal_error ("check_data_variable(): Bad expression");
7312 if (e->symtree->n.sym->ns->is_block_data
7313 && !e->symtree->n.sym->attr.in_common)
7315 gfc_error ("BLOCK DATA element '%s' at %L must be in COMMON",
7316 e->symtree->n.sym->name, &e->symtree->n.sym->declared_at);
7319 if (e->rank == 0)
7321 mpz_init_set_ui (size, 1);
7322 ref = NULL;
7324 else
7326 ref = e->ref;
7328 /* Find the array section reference. */
7329 for (ref = e->ref; ref; ref = ref->next)
7331 if (ref->type != REF_ARRAY)
7332 continue;
7333 if (ref->u.ar.type == AR_ELEMENT)
7334 continue;
7335 break;
7337 gcc_assert (ref);
7339 /* Set marks according to the reference pattern. */
7340 switch (ref->u.ar.type)
7342 case AR_FULL:
7343 mark = AR_FULL;
7344 break;
7346 case AR_SECTION:
7347 ar = &ref->u.ar;
7348 /* Get the start position of array section. */
7349 gfc_get_section_index (ar, section_index, &offset);
7350 mark = AR_SECTION;
7351 break;
7353 default:
7354 gcc_unreachable ();
7357 if (gfc_array_size (e, &size) == FAILURE)
7359 gfc_error ("Nonconstant array section at %L in DATA statement",
7360 &e->where);
7361 mpz_clear (offset);
7362 return FAILURE;
7366 t = SUCCESS;
7368 while (mpz_cmp_ui (size, 0) > 0)
7370 if (next_data_value () == FAILURE)
7372 gfc_error ("DATA statement at %L has more variables than values",
7373 where);
7374 t = FAILURE;
7375 break;
7378 t = gfc_check_assign (var->expr, values.vnode->expr, 0);
7379 if (t == FAILURE)
7380 break;
7382 /* If we have more than one element left in the repeat count,
7383 and we have more than one element left in the target variable,
7384 then create a range assignment. */
7385 /* ??? Only done for full arrays for now, since array sections
7386 seem tricky. */
7387 if (mark == AR_FULL && ref && ref->next == NULL
7388 && values.left > 1 && mpz_cmp_ui (size, 1) > 0)
7390 mpz_t range;
7392 if (mpz_cmp_ui (size, values.left) >= 0)
7394 mpz_init_set_ui (range, values.left);
7395 mpz_sub_ui (size, size, values.left);
7396 values.left = 0;
7398 else
7400 mpz_init_set (range, size);
7401 values.left -= mpz_get_ui (size);
7402 mpz_set_ui (size, 0);
7405 gfc_assign_data_value_range (var->expr, values.vnode->expr,
7406 offset, range);
7408 mpz_add (offset, offset, range);
7409 mpz_clear (range);
7412 /* Assign initial value to symbol. */
7413 else
7415 values.left -= 1;
7416 mpz_sub_ui (size, size, 1);
7418 gfc_assign_data_value (var->expr, values.vnode->expr, offset);
7420 if (mark == AR_FULL)
7421 mpz_add_ui (offset, offset, 1);
7423 /* Modify the array section indexes and recalculate the offset
7424 for next element. */
7425 else if (mark == AR_SECTION)
7426 gfc_advance_section (section_index, ar, &offset);
7430 if (mark == AR_SECTION)
7432 for (i = 0; i < ar->dimen; i++)
7433 mpz_clear (section_index[i]);
7436 mpz_clear (size);
7437 mpz_clear (offset);
7439 return t;
7443 static try traverse_data_var (gfc_data_variable *, locus *);
7445 /* Iterate over a list of elements in a DATA statement. */
7447 static try
7448 traverse_data_list (gfc_data_variable *var, locus *where)
7450 mpz_t trip;
7451 iterator_stack frame;
7452 gfc_expr *e, *start, *end, *step;
7453 try retval = SUCCESS;
7455 mpz_init (frame.value);
7457 start = gfc_copy_expr (var->iter.start);
7458 end = gfc_copy_expr (var->iter.end);
7459 step = gfc_copy_expr (var->iter.step);
7461 if (gfc_simplify_expr (start, 1) == FAILURE
7462 || start->expr_type != EXPR_CONSTANT)
7464 gfc_error ("iterator start at %L does not simplify", &start->where);
7465 retval = FAILURE;
7466 goto cleanup;
7468 if (gfc_simplify_expr (end, 1) == FAILURE
7469 || end->expr_type != EXPR_CONSTANT)
7471 gfc_error ("iterator end at %L does not simplify", &end->where);
7472 retval = FAILURE;
7473 goto cleanup;
7475 if (gfc_simplify_expr (step, 1) == FAILURE
7476 || step->expr_type != EXPR_CONSTANT)
7478 gfc_error ("iterator step at %L does not simplify", &step->where);
7479 retval = FAILURE;
7480 goto cleanup;
7483 mpz_init_set (trip, end->value.integer);
7484 mpz_sub (trip, trip, start->value.integer);
7485 mpz_add (trip, trip, step->value.integer);
7487 mpz_div (trip, trip, step->value.integer);
7489 mpz_set (frame.value, start->value.integer);
7491 frame.prev = iter_stack;
7492 frame.variable = var->iter.var->symtree;
7493 iter_stack = &frame;
7495 while (mpz_cmp_ui (trip, 0) > 0)
7497 if (traverse_data_var (var->list, where) == FAILURE)
7499 mpz_clear (trip);
7500 retval = FAILURE;
7501 goto cleanup;
7504 e = gfc_copy_expr (var->expr);
7505 if (gfc_simplify_expr (e, 1) == FAILURE)
7507 gfc_free_expr (e);
7508 mpz_clear (trip);
7509 retval = FAILURE;
7510 goto cleanup;
7513 mpz_add (frame.value, frame.value, step->value.integer);
7515 mpz_sub_ui (trip, trip, 1);
7518 mpz_clear (trip);
7519 cleanup:
7520 mpz_clear (frame.value);
7522 gfc_free_expr (start);
7523 gfc_free_expr (end);
7524 gfc_free_expr (step);
7526 iter_stack = frame.prev;
7527 return retval;
7531 /* Type resolve variables in the variable list of a DATA statement. */
7533 static try
7534 traverse_data_var (gfc_data_variable *var, locus *where)
7536 try t;
7538 for (; var; var = var->next)
7540 if (var->expr == NULL)
7541 t = traverse_data_list (var, where);
7542 else
7543 t = check_data_variable (var, where);
7545 if (t == FAILURE)
7546 return FAILURE;
7549 return SUCCESS;
7553 /* Resolve the expressions and iterators associated with a data statement.
7554 This is separate from the assignment checking because data lists should
7555 only be resolved once. */
7557 static try
7558 resolve_data_variables (gfc_data_variable *d)
7560 for (; d; d = d->next)
7562 if (d->list == NULL)
7564 if (gfc_resolve_expr (d->expr) == FAILURE)
7565 return FAILURE;
7567 else
7569 if (gfc_resolve_iterator (&d->iter, false) == FAILURE)
7570 return FAILURE;
7572 if (resolve_data_variables (d->list) == FAILURE)
7573 return FAILURE;
7577 return SUCCESS;
7581 /* Resolve a single DATA statement. We implement this by storing a pointer to
7582 the value list into static variables, and then recursively traversing the
7583 variables list, expanding iterators and such. */
7585 static void
7586 resolve_data (gfc_data * d)
7588 if (resolve_data_variables (d->var) == FAILURE)
7589 return;
7591 values.vnode = d->value;
7592 values.left = (d->value == NULL) ? 0 : d->value->repeat;
7594 if (traverse_data_var (d->var, &d->where) == FAILURE)
7595 return;
7597 /* At this point, we better not have any values left. */
7599 if (next_data_value () == SUCCESS)
7600 gfc_error ("DATA statement at %L has more values than variables",
7601 &d->where);
7605 /* 12.6 Constraint: In a pure subprogram any variable which is in common or
7606 accessed by host or use association, is a dummy argument to a pure function,
7607 is a dummy argument with INTENT (IN) to a pure subroutine, or an object that
7608 is storage associated with any such variable, shall not be used in the
7609 following contexts: (clients of this function). */
7611 /* Determines if a variable is not 'pure', ie not assignable within a pure
7612 procedure. Returns zero if assignment is OK, nonzero if there is a
7613 problem. */
7615 gfc_impure_variable (gfc_symbol *sym)
7617 gfc_symbol *proc;
7619 if (sym->attr.use_assoc || sym->attr.in_common)
7620 return 1;
7622 if (sym->ns != gfc_current_ns)
7623 return !sym->attr.function;
7625 proc = sym->ns->proc_name;
7626 if (sym->attr.dummy && gfc_pure (proc)
7627 && ((proc->attr.subroutine && sym->attr.intent == INTENT_IN)
7629 proc->attr.function))
7630 return 1;
7632 /* TODO: Sort out what can be storage associated, if anything, and include
7633 it here. In principle equivalences should be scanned but it does not
7634 seem to be possible to storage associate an impure variable this way. */
7635 return 0;
7639 /* Test whether a symbol is pure or not. For a NULL pointer, checks the
7640 symbol of the current procedure. */
7643 gfc_pure (gfc_symbol *sym)
7645 symbol_attribute attr;
7647 if (sym == NULL)
7648 sym = gfc_current_ns->proc_name;
7649 if (sym == NULL)
7650 return 0;
7652 attr = sym->attr;
7654 return attr.flavor == FL_PROCEDURE && (attr.pure || attr.elemental);
7658 /* Test whether the current procedure is elemental or not. */
7661 gfc_elemental (gfc_symbol *sym)
7663 symbol_attribute attr;
7665 if (sym == NULL)
7666 sym = gfc_current_ns->proc_name;
7667 if (sym == NULL)
7668 return 0;
7669 attr = sym->attr;
7671 return attr.flavor == FL_PROCEDURE && attr.elemental;
7675 /* Warn about unused labels. */
7677 static void
7678 warn_unused_fortran_label (gfc_st_label *label)
7680 if (label == NULL)
7681 return;
7683 warn_unused_fortran_label (label->left);
7685 if (label->defined == ST_LABEL_UNKNOWN)
7686 return;
7688 switch (label->referenced)
7690 case ST_LABEL_UNKNOWN:
7691 gfc_warning ("Label %d at %L defined but not used", label->value,
7692 &label->where);
7693 break;
7695 case ST_LABEL_BAD_TARGET:
7696 gfc_warning ("Label %d at %L defined but cannot be used",
7697 label->value, &label->where);
7698 break;
7700 default:
7701 break;
7704 warn_unused_fortran_label (label->right);
7708 /* Returns the sequence type of a symbol or sequence. */
7710 static seq_type
7711 sequence_type (gfc_typespec ts)
7713 seq_type result;
7714 gfc_component *c;
7716 switch (ts.type)
7718 case BT_DERIVED:
7720 if (ts.derived->components == NULL)
7721 return SEQ_NONDEFAULT;
7723 result = sequence_type (ts.derived->components->ts);
7724 for (c = ts.derived->components->next; c; c = c->next)
7725 if (sequence_type (c->ts) != result)
7726 return SEQ_MIXED;
7728 return result;
7730 case BT_CHARACTER:
7731 if (ts.kind != gfc_default_character_kind)
7732 return SEQ_NONDEFAULT;
7734 return SEQ_CHARACTER;
7736 case BT_INTEGER:
7737 if (ts.kind != gfc_default_integer_kind)
7738 return SEQ_NONDEFAULT;
7740 return SEQ_NUMERIC;
7742 case BT_REAL:
7743 if (!(ts.kind == gfc_default_real_kind
7744 || ts.kind == gfc_default_double_kind))
7745 return SEQ_NONDEFAULT;
7747 return SEQ_NUMERIC;
7749 case BT_COMPLEX:
7750 if (ts.kind != gfc_default_complex_kind)
7751 return SEQ_NONDEFAULT;
7753 return SEQ_NUMERIC;
7755 case BT_LOGICAL:
7756 if (ts.kind != gfc_default_logical_kind)
7757 return SEQ_NONDEFAULT;
7759 return SEQ_NUMERIC;
7761 default:
7762 return SEQ_NONDEFAULT;
7767 /* Resolve derived type EQUIVALENCE object. */
7769 static try
7770 resolve_equivalence_derived (gfc_symbol *derived, gfc_symbol *sym, gfc_expr *e)
7772 gfc_symbol *d;
7773 gfc_component *c = derived->components;
7775 if (!derived)
7776 return SUCCESS;
7778 /* Shall not be an object of nonsequence derived type. */
7779 if (!derived->attr.sequence)
7781 gfc_error ("Derived type variable '%s' at %L must have SEQUENCE "
7782 "attribute to be an EQUIVALENCE object", sym->name,
7783 &e->where);
7784 return FAILURE;
7787 /* Shall not have allocatable components. */
7788 if (derived->attr.alloc_comp)
7790 gfc_error ("Derived type variable '%s' at %L cannot have ALLOCATABLE "
7791 "components to be an EQUIVALENCE object",sym->name,
7792 &e->where);
7793 return FAILURE;
7796 for (; c ; c = c->next)
7798 d = c->ts.derived;
7799 if (d
7800 && (resolve_equivalence_derived (c->ts.derived, sym, e) == FAILURE))
7801 return FAILURE;
7803 /* Shall not be an object of sequence derived type containing a pointer
7804 in the structure. */
7805 if (c->pointer)
7807 gfc_error ("Derived type variable '%s' at %L with pointer "
7808 "component(s) cannot be an EQUIVALENCE object",
7809 sym->name, &e->where);
7810 return FAILURE;
7813 return SUCCESS;
7817 /* Resolve equivalence object.
7818 An EQUIVALENCE object shall not be a dummy argument, a pointer, a target,
7819 an allocatable array, an object of nonsequence derived type, an object of
7820 sequence derived type containing a pointer at any level of component
7821 selection, an automatic object, a function name, an entry name, a result
7822 name, a named constant, a structure component, or a subobject of any of
7823 the preceding objects. A substring shall not have length zero. A
7824 derived type shall not have components with default initialization nor
7825 shall two objects of an equivalence group be initialized.
7826 Either all or none of the objects shall have an protected attribute.
7827 The simple constraints are done in symbol.c(check_conflict) and the rest
7828 are implemented here. */
7830 static void
7831 resolve_equivalence (gfc_equiv *eq)
7833 gfc_symbol *sym;
7834 gfc_symbol *derived;
7835 gfc_symbol *first_sym;
7836 gfc_expr *e;
7837 gfc_ref *r;
7838 locus *last_where = NULL;
7839 seq_type eq_type, last_eq_type;
7840 gfc_typespec *last_ts;
7841 int object, cnt_protected;
7842 const char *value_name;
7843 const char *msg;
7845 value_name = NULL;
7846 last_ts = &eq->expr->symtree->n.sym->ts;
7848 first_sym = eq->expr->symtree->n.sym;
7850 cnt_protected = 0;
7852 for (object = 1; eq; eq = eq->eq, object++)
7854 e = eq->expr;
7856 e->ts = e->symtree->n.sym->ts;
7857 /* match_varspec might not know yet if it is seeing
7858 array reference or substring reference, as it doesn't
7859 know the types. */
7860 if (e->ref && e->ref->type == REF_ARRAY)
7862 gfc_ref *ref = e->ref;
7863 sym = e->symtree->n.sym;
7865 if (sym->attr.dimension)
7867 ref->u.ar.as = sym->as;
7868 ref = ref->next;
7871 /* For substrings, convert REF_ARRAY into REF_SUBSTRING. */
7872 if (e->ts.type == BT_CHARACTER
7873 && ref
7874 && ref->type == REF_ARRAY
7875 && ref->u.ar.dimen == 1
7876 && ref->u.ar.dimen_type[0] == DIMEN_RANGE
7877 && ref->u.ar.stride[0] == NULL)
7879 gfc_expr *start = ref->u.ar.start[0];
7880 gfc_expr *end = ref->u.ar.end[0];
7881 void *mem = NULL;
7883 /* Optimize away the (:) reference. */
7884 if (start == NULL && end == NULL)
7886 if (e->ref == ref)
7887 e->ref = ref->next;
7888 else
7889 e->ref->next = ref->next;
7890 mem = ref;
7892 else
7894 ref->type = REF_SUBSTRING;
7895 if (start == NULL)
7896 start = gfc_int_expr (1);
7897 ref->u.ss.start = start;
7898 if (end == NULL && e->ts.cl)
7899 end = gfc_copy_expr (e->ts.cl->length);
7900 ref->u.ss.end = end;
7901 ref->u.ss.length = e->ts.cl;
7902 e->ts.cl = NULL;
7904 ref = ref->next;
7905 gfc_free (mem);
7908 /* Any further ref is an error. */
7909 if (ref)
7911 gcc_assert (ref->type == REF_ARRAY);
7912 gfc_error ("Syntax error in EQUIVALENCE statement at %L",
7913 &ref->u.ar.where);
7914 continue;
7918 if (gfc_resolve_expr (e) == FAILURE)
7919 continue;
7921 sym = e->symtree->n.sym;
7923 if (sym->attr.protected)
7924 cnt_protected++;
7925 if (cnt_protected > 0 && cnt_protected != object)
7927 gfc_error ("Either all or none of the objects in the "
7928 "EQUIVALENCE set at %L shall have the "
7929 "PROTECTED attribute",
7930 &e->where);
7931 break;
7934 /* Shall not equivalence common block variables in a PURE procedure. */
7935 if (sym->ns->proc_name
7936 && sym->ns->proc_name->attr.pure
7937 && sym->attr.in_common)
7939 gfc_error ("Common block member '%s' at %L cannot be an EQUIVALENCE "
7940 "object in the pure procedure '%s'",
7941 sym->name, &e->where, sym->ns->proc_name->name);
7942 break;
7945 /* Shall not be a named constant. */
7946 if (e->expr_type == EXPR_CONSTANT)
7948 gfc_error ("Named constant '%s' at %L cannot be an EQUIVALENCE "
7949 "object", sym->name, &e->where);
7950 continue;
7953 derived = e->ts.derived;
7954 if (derived && resolve_equivalence_derived (derived, sym, e) == FAILURE)
7955 continue;
7957 /* Check that the types correspond correctly:
7958 Note 5.28:
7959 A numeric sequence structure may be equivalenced to another sequence
7960 structure, an object of default integer type, default real type, double
7961 precision real type, default logical type such that components of the
7962 structure ultimately only become associated to objects of the same
7963 kind. A character sequence structure may be equivalenced to an object
7964 of default character kind or another character sequence structure.
7965 Other objects may be equivalenced only to objects of the same type and
7966 kind parameters. */
7968 /* Identical types are unconditionally OK. */
7969 if (object == 1 || gfc_compare_types (last_ts, &sym->ts))
7970 goto identical_types;
7972 last_eq_type = sequence_type (*last_ts);
7973 eq_type = sequence_type (sym->ts);
7975 /* Since the pair of objects is not of the same type, mixed or
7976 non-default sequences can be rejected. */
7978 msg = "Sequence %s with mixed components in EQUIVALENCE "
7979 "statement at %L with different type objects";
7980 if ((object ==2
7981 && last_eq_type == SEQ_MIXED
7982 && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name, last_where)
7983 == FAILURE)
7984 || (eq_type == SEQ_MIXED
7985 && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
7986 &e->where) == FAILURE))
7987 continue;
7989 msg = "Non-default type object or sequence %s in EQUIVALENCE "
7990 "statement at %L with objects of different type";
7991 if ((object ==2
7992 && last_eq_type == SEQ_NONDEFAULT
7993 && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name,
7994 last_where) == FAILURE)
7995 || (eq_type == SEQ_NONDEFAULT
7996 && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
7997 &e->where) == FAILURE))
7998 continue;
8000 msg ="Non-CHARACTER object '%s' in default CHARACTER "
8001 "EQUIVALENCE statement at %L";
8002 if (last_eq_type == SEQ_CHARACTER
8003 && eq_type != SEQ_CHARACTER
8004 && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
8005 &e->where) == FAILURE)
8006 continue;
8008 msg ="Non-NUMERIC object '%s' in default NUMERIC "
8009 "EQUIVALENCE statement at %L";
8010 if (last_eq_type == SEQ_NUMERIC
8011 && eq_type != SEQ_NUMERIC
8012 && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
8013 &e->where) == FAILURE)
8014 continue;
8016 identical_types:
8017 last_ts =&sym->ts;
8018 last_where = &e->where;
8020 if (!e->ref)
8021 continue;
8023 /* Shall not be an automatic array. */
8024 if (e->ref->type == REF_ARRAY
8025 && gfc_resolve_array_spec (e->ref->u.ar.as, 1) == FAILURE)
8027 gfc_error ("Array '%s' at %L with non-constant bounds cannot be "
8028 "an EQUIVALENCE object", sym->name, &e->where);
8029 continue;
8032 r = e->ref;
8033 while (r)
8035 /* Shall not be a structure component. */
8036 if (r->type == REF_COMPONENT)
8038 gfc_error ("Structure component '%s' at %L cannot be an "
8039 "EQUIVALENCE object",
8040 r->u.c.component->name, &e->where);
8041 break;
8044 /* A substring shall not have length zero. */
8045 if (r->type == REF_SUBSTRING)
8047 if (compare_bound (r->u.ss.start, r->u.ss.end) == CMP_GT)
8049 gfc_error ("Substring at %L has length zero",
8050 &r->u.ss.start->where);
8051 break;
8054 r = r->next;
8060 /* Resolve function and ENTRY types, issue diagnostics if needed. */
8062 static void
8063 resolve_fntype (gfc_namespace *ns)
8065 gfc_entry_list *el;
8066 gfc_symbol *sym;
8068 if (ns->proc_name == NULL || !ns->proc_name->attr.function)
8069 return;
8071 /* If there are any entries, ns->proc_name is the entry master
8072 synthetic symbol and ns->entries->sym actual FUNCTION symbol. */
8073 if (ns->entries)
8074 sym = ns->entries->sym;
8075 else
8076 sym = ns->proc_name;
8077 if (sym->result == sym
8078 && sym->ts.type == BT_UNKNOWN
8079 && gfc_set_default_type (sym, 0, NULL) == FAILURE
8080 && !sym->attr.untyped)
8082 gfc_error ("Function '%s' at %L has no IMPLICIT type",
8083 sym->name, &sym->declared_at);
8084 sym->attr.untyped = 1;
8087 if (sym->ts.type == BT_DERIVED && !sym->ts.derived->attr.use_assoc
8088 && !gfc_check_access (sym->ts.derived->attr.access,
8089 sym->ts.derived->ns->default_access)
8090 && gfc_check_access (sym->attr.access, sym->ns->default_access))
8092 gfc_error ("PUBLIC function '%s' at %L cannot be of PRIVATE type '%s'",
8093 sym->name, &sym->declared_at, sym->ts.derived->name);
8096 if (ns->entries)
8097 for (el = ns->entries->next; el; el = el->next)
8099 if (el->sym->result == el->sym
8100 && el->sym->ts.type == BT_UNKNOWN
8101 && gfc_set_default_type (el->sym, 0, NULL) == FAILURE
8102 && !el->sym->attr.untyped)
8104 gfc_error ("ENTRY '%s' at %L has no IMPLICIT type",
8105 el->sym->name, &el->sym->declared_at);
8106 el->sym->attr.untyped = 1;
8111 /* 12.3.2.1.1 Defined operators. */
8113 static void
8114 gfc_resolve_uops (gfc_symtree *symtree)
8116 gfc_interface *itr;
8117 gfc_symbol *sym;
8118 gfc_formal_arglist *formal;
8120 if (symtree == NULL)
8121 return;
8123 gfc_resolve_uops (symtree->left);
8124 gfc_resolve_uops (symtree->right);
8126 for (itr = symtree->n.uop->operator; itr; itr = itr->next)
8128 sym = itr->sym;
8129 if (!sym->attr.function)
8130 gfc_error ("User operator procedure '%s' at %L must be a FUNCTION",
8131 sym->name, &sym->declared_at);
8133 if (sym->ts.type == BT_CHARACTER
8134 && !(sym->ts.cl && sym->ts.cl->length)
8135 && !(sym->result && sym->result->ts.cl
8136 && sym->result->ts.cl->length))
8137 gfc_error ("User operator procedure '%s' at %L cannot be assumed "
8138 "character length", sym->name, &sym->declared_at);
8140 formal = sym->formal;
8141 if (!formal || !formal->sym)
8143 gfc_error ("User operator procedure '%s' at %L must have at least "
8144 "one argument", sym->name, &sym->declared_at);
8145 continue;
8148 if (formal->sym->attr.intent != INTENT_IN)
8149 gfc_error ("First argument of operator interface at %L must be "
8150 "INTENT(IN)", &sym->declared_at);
8152 if (formal->sym->attr.optional)
8153 gfc_error ("First argument of operator interface at %L cannot be "
8154 "optional", &sym->declared_at);
8156 formal = formal->next;
8157 if (!formal || !formal->sym)
8158 continue;
8160 if (formal->sym->attr.intent != INTENT_IN)
8161 gfc_error ("Second argument of operator interface at %L must be "
8162 "INTENT(IN)", &sym->declared_at);
8164 if (formal->sym->attr.optional)
8165 gfc_error ("Second argument of operator interface at %L cannot be "
8166 "optional", &sym->declared_at);
8168 if (formal->next)
8169 gfc_error ("Operator interface at %L must have, at most, two "
8170 "arguments", &sym->declared_at);
8175 /* Examine all of the expressions associated with a program unit,
8176 assign types to all intermediate expressions, make sure that all
8177 assignments are to compatible types and figure out which names
8178 refer to which functions or subroutines. It doesn't check code
8179 block, which is handled by resolve_code. */
8181 static void
8182 resolve_types (gfc_namespace *ns)
8184 gfc_namespace *n;
8185 gfc_charlen *cl;
8186 gfc_data *d;
8187 gfc_equiv *eq;
8189 gfc_current_ns = ns;
8191 resolve_entries (ns);
8193 resolve_contained_functions (ns);
8195 gfc_traverse_ns (ns, resolve_bind_c_derived_types);
8197 for (cl = ns->cl_list; cl; cl = cl->next)
8198 resolve_charlen (cl);
8200 gfc_traverse_ns (ns, resolve_symbol);
8202 resolve_fntype (ns);
8204 for (n = ns->contained; n; n = n->sibling)
8206 if (gfc_pure (ns->proc_name) && !gfc_pure (n->proc_name))
8207 gfc_error ("Contained procedure '%s' at %L of a PURE procedure must "
8208 "also be PURE", n->proc_name->name,
8209 &n->proc_name->declared_at);
8211 resolve_types (n);
8214 forall_flag = 0;
8215 gfc_check_interfaces (ns);
8217 gfc_traverse_ns (ns, resolve_values);
8219 if (ns->save_all)
8220 gfc_save_all (ns);
8222 iter_stack = NULL;
8223 for (d = ns->data; d; d = d->next)
8224 resolve_data (d);
8226 iter_stack = NULL;
8227 gfc_traverse_ns (ns, gfc_formalize_init_value);
8229 gfc_traverse_ns (ns, gfc_verify_binding_labels);
8231 if (ns->common_root != NULL)
8232 gfc_traverse_symtree (ns->common_root, resolve_bind_c_comms);
8234 for (eq = ns->equiv; eq; eq = eq->next)
8235 resolve_equivalence (eq);
8237 /* Warn about unused labels. */
8238 if (warn_unused_label)
8239 warn_unused_fortran_label (ns->st_labels);
8241 gfc_resolve_uops (ns->uop_root);
8245 /* Call resolve_code recursively. */
8247 static void
8248 resolve_codes (gfc_namespace *ns)
8250 gfc_namespace *n;
8252 for (n = ns->contained; n; n = n->sibling)
8253 resolve_codes (n);
8255 gfc_current_ns = ns;
8256 cs_base = NULL;
8257 /* Set to an out of range value. */
8258 current_entry_id = -1;
8260 bitmap_obstack_initialize (&labels_obstack);
8261 resolve_code (ns->code, ns);
8262 bitmap_obstack_release (&labels_obstack);
8266 /* This function is called after a complete program unit has been compiled.
8267 Its purpose is to examine all of the expressions associated with a program
8268 unit, assign types to all intermediate expressions, make sure that all
8269 assignments are to compatible types and figure out which names refer to
8270 which functions or subroutines. */
8272 void
8273 gfc_resolve (gfc_namespace *ns)
8275 gfc_namespace *old_ns;
8277 old_ns = gfc_current_ns;
8279 resolve_types (ns);
8280 resolve_codes (ns);
8282 gfc_current_ns = old_ns;