trans-stmt.c: Fix a typo
[official-gcc.git] / gcc / fortran / resolve.c
blob2639cabae36b54247a7ccfa99cbe32606e7c9945
1 /* Perform type resolution on the various stuctures.
2 Copyright (C) 2001, 2002, 2003, 2004, 2005, 2006 Free Software Foundation,
3 Inc.
4 Contributed by Andy Vaught
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. */
24 #include "config.h"
25 #include "system.h"
26 #include "flags.h"
27 #include "gfortran.h"
28 #include "arith.h" /* For gfc_compare_expr(). */
29 #include "dependency.h"
31 /* Types used in equivalence statements. */
33 typedef enum seq_type
35 SEQ_NONDEFAULT, SEQ_NUMERIC, SEQ_CHARACTER, SEQ_MIXED
37 seq_type;
39 /* Stack to push the current if we descend into a block during
40 resolution. See resolve_branch() and resolve_code(). */
42 typedef struct code_stack
44 struct gfc_code *head, *current;
45 struct code_stack *prev;
47 code_stack;
49 static code_stack *cs_base = NULL;
52 /* Nonzero if we're inside a FORALL block. */
54 static int forall_flag;
56 /* Nonzero if we're inside a OpenMP WORKSHARE or PARALLEL WORKSHARE block. */
58 static int omp_workshare_flag;
60 /* Nonzero if we are processing a formal arglist. The corresponding function
61 resets the flag each time that it is read. */
62 static int formal_arg_flag = 0;
64 /* True if we are resolving a specification expression. */
65 static int specification_expr = 0;
67 /* The id of the last entry seen. */
68 static int current_entry_id;
70 int
71 gfc_is_formal_arg (void)
73 return formal_arg_flag;
76 /* Resolve types of formal argument lists. These have to be done early so that
77 the formal argument lists of module procedures can be copied to the
78 containing module before the individual procedures are resolved
79 individually. We also resolve argument lists of procedures in interface
80 blocks because they are self-contained scoping units.
82 Since a dummy argument cannot be a non-dummy procedure, the only
83 resort left for untyped names are the IMPLICIT types. */
85 static void
86 resolve_formal_arglist (gfc_symbol * proc)
88 gfc_formal_arglist *f;
89 gfc_symbol *sym;
90 int i;
92 /* TODO: Procedures whose return character length parameter is not constant
93 or assumed must also have explicit interfaces. */
94 if (proc->result != NULL)
95 sym = proc->result;
96 else
97 sym = proc;
99 if (gfc_elemental (proc)
100 || sym->attr.pointer || sym->attr.allocatable
101 || (sym->as && sym->as->rank > 0))
102 proc->attr.always_explicit = 1;
104 formal_arg_flag = 1;
106 for (f = proc->formal; f; f = f->next)
108 sym = f->sym;
110 if (sym == NULL)
112 /* Alternate return placeholder. */
113 if (gfc_elemental (proc))
114 gfc_error ("Alternate return specifier in elemental subroutine "
115 "'%s' at %L is not allowed", proc->name,
116 &proc->declared_at);
117 if (proc->attr.function)
118 gfc_error ("Alternate return specifier in function "
119 "'%s' at %L is not allowed", proc->name,
120 &proc->declared_at);
121 continue;
124 if (sym->attr.if_source != IFSRC_UNKNOWN)
125 resolve_formal_arglist (sym);
127 if (sym->attr.subroutine || sym->attr.external || sym->attr.intrinsic)
129 if (gfc_pure (proc) && !gfc_pure (sym))
131 gfc_error
132 ("Dummy procedure '%s' of PURE procedure at %L must also "
133 "be PURE", sym->name, &sym->declared_at);
134 continue;
137 if (gfc_elemental (proc))
139 gfc_error
140 ("Dummy procedure at %L not allowed in ELEMENTAL procedure",
141 &sym->declared_at);
142 continue;
145 continue;
148 if (sym->ts.type == BT_UNKNOWN)
150 if (!sym->attr.function || sym->result == sym)
151 gfc_set_default_type (sym, 1, sym->ns);
154 gfc_resolve_array_spec (sym->as, 0);
156 /* We can't tell if an array with dimension (:) is assumed or deferred
157 shape until we know if it has the pointer or allocatable attributes.
159 if (sym->as && sym->as->rank > 0 && sym->as->type == AS_DEFERRED
160 && !(sym->attr.pointer || sym->attr.allocatable))
162 sym->as->type = AS_ASSUMED_SHAPE;
163 for (i = 0; i < sym->as->rank; i++)
164 sym->as->lower[i] = gfc_int_expr (1);
167 if ((sym->as && sym->as->rank > 0 && sym->as->type == AS_ASSUMED_SHAPE)
168 || sym->attr.pointer || sym->attr.allocatable || sym->attr.target
169 || sym->attr.optional)
170 proc->attr.always_explicit = 1;
172 /* If the flavor is unknown at this point, it has to be a variable.
173 A procedure specification would have already set the type. */
175 if (sym->attr.flavor == FL_UNKNOWN)
176 gfc_add_flavor (&sym->attr, FL_VARIABLE, sym->name, &sym->declared_at);
178 if (gfc_pure (proc))
180 if (proc->attr.function && !sym->attr.pointer
181 && sym->attr.flavor != FL_PROCEDURE
182 && sym->attr.intent != INTENT_IN)
184 gfc_error ("Argument '%s' of pure function '%s' at %L must be "
185 "INTENT(IN)", sym->name, proc->name,
186 &sym->declared_at);
188 if (proc->attr.subroutine && !sym->attr.pointer
189 && sym->attr.intent == INTENT_UNKNOWN)
191 gfc_error
192 ("Argument '%s' of pure subroutine '%s' at %L must have "
193 "its INTENT specified", sym->name, proc->name,
194 &sym->declared_at);
198 if (gfc_elemental (proc))
200 if (sym->as != NULL)
202 gfc_error
203 ("Argument '%s' of elemental procedure at %L must be scalar",
204 sym->name, &sym->declared_at);
205 continue;
208 if (sym->attr.pointer)
210 gfc_error
211 ("Argument '%s' of elemental procedure at %L cannot have "
212 "the POINTER attribute", sym->name, &sym->declared_at);
213 continue;
217 /* Each dummy shall be specified to be scalar. */
218 if (proc->attr.proc == PROC_ST_FUNCTION)
220 if (sym->as != NULL)
222 gfc_error
223 ("Argument '%s' of statement function at %L must be scalar",
224 sym->name, &sym->declared_at);
225 continue;
228 if (sym->ts.type == BT_CHARACTER)
230 gfc_charlen *cl = sym->ts.cl;
231 if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
233 gfc_error
234 ("Character-valued argument '%s' of statement function at "
235 "%L must has constant length",
236 sym->name, &sym->declared_at);
237 continue;
242 formal_arg_flag = 0;
246 /* Work function called when searching for symbols that have argument lists
247 associated with them. */
249 static void
250 find_arglists (gfc_symbol * sym)
253 if (sym->attr.if_source == IFSRC_UNKNOWN || sym->ns != gfc_current_ns)
254 return;
256 resolve_formal_arglist (sym);
260 /* Given a namespace, resolve all formal argument lists within the namespace.
263 static void
264 resolve_formal_arglists (gfc_namespace * ns)
267 if (ns == NULL)
268 return;
270 gfc_traverse_ns (ns, find_arglists);
274 static void
275 resolve_contained_fntype (gfc_symbol * sym, gfc_namespace * ns)
277 try t;
279 /* If this namespace is not a function, ignore it. */
280 if (! sym
281 || !(sym->attr.function
282 || sym->attr.flavor == FL_VARIABLE))
283 return;
285 /* Try to find out of what the return type is. */
286 if (sym->result != NULL)
287 sym = sym->result;
289 if (sym->ts.type == BT_UNKNOWN)
291 t = gfc_set_default_type (sym, 0, ns);
293 if (t == FAILURE && !sym->attr.untyped)
295 gfc_error ("Contained function '%s' at %L has no IMPLICIT type",
296 sym->name, &sym->declared_at); /* FIXME */
297 sym->attr.untyped = 1;
301 /*Fortran 95 Draft Standard, page 51, Section 5.1.1.5, on the Character type,
302 lists the only ways a character length value of * can be used: dummy arguments
303 of procedures, named constants, and function results in external functions.
304 Internal function results are not on that list; ergo, not permitted. */
306 if (sym->ts.type == BT_CHARACTER)
308 gfc_charlen *cl = sym->ts.cl;
309 if (!cl || !cl->length)
310 gfc_error ("Character-valued internal function '%s' at %L must "
311 "not be assumed length", sym->name, &sym->declared_at);
316 /* Add NEW_ARGS to the formal argument list of PROC, taking care not to
317 introduce duplicates. */
319 static void
320 merge_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
322 gfc_formal_arglist *f, *new_arglist;
323 gfc_symbol *new_sym;
325 for (; new_args != NULL; new_args = new_args->next)
327 new_sym = new_args->sym;
328 /* See if this arg is already in the formal argument list. */
329 for (f = proc->formal; f; f = f->next)
331 if (new_sym == f->sym)
332 break;
335 if (f)
336 continue;
338 /* Add a new argument. Argument order is not important. */
339 new_arglist = gfc_get_formal_arglist ();
340 new_arglist->sym = new_sym;
341 new_arglist->next = proc->formal;
342 proc->formal = new_arglist;
347 /* Resolve alternate entry points. If a symbol has multiple entry points we
348 create a new master symbol for the main routine, and turn the existing
349 symbol into an entry point. */
351 static void
352 resolve_entries (gfc_namespace * ns)
354 gfc_namespace *old_ns;
355 gfc_code *c;
356 gfc_symbol *proc;
357 gfc_entry_list *el;
358 char name[GFC_MAX_SYMBOL_LEN + 1];
359 static int master_count = 0;
361 if (ns->proc_name == NULL)
362 return;
364 /* No need to do anything if this procedure doesn't have alternate entry
365 points. */
366 if (!ns->entries)
367 return;
369 /* We may already have resolved alternate entry points. */
370 if (ns->proc_name->attr.entry_master)
371 return;
373 /* If this isn't a procedure something has gone horribly wrong. */
374 gcc_assert (ns->proc_name->attr.flavor == FL_PROCEDURE);
376 /* Remember the current namespace. */
377 old_ns = gfc_current_ns;
379 gfc_current_ns = ns;
381 /* Add the main entry point to the list of entry points. */
382 el = gfc_get_entry_list ();
383 el->sym = ns->proc_name;
384 el->id = 0;
385 el->next = ns->entries;
386 ns->entries = el;
387 ns->proc_name->attr.entry = 1;
389 /* If it is a module function, it needs to be in the right namespace
390 so that gfc_get_fake_result_decl can gather up the results. The
391 need for this arose in get_proc_name, where these beasts were
392 left in their own namespace, to keep prior references linked to
393 the entry declaration.*/
394 if (ns->proc_name->attr.function
395 && ns->parent
396 && ns->parent->proc_name->attr.flavor == FL_MODULE)
397 el->sym->ns = ns;
399 /* Add an entry statement for it. */
400 c = gfc_get_code ();
401 c->op = EXEC_ENTRY;
402 c->ext.entry = el;
403 c->next = ns->code;
404 ns->code = c;
406 /* Create a new symbol for the master function. */
407 /* Give the internal function a unique name (within this file).
408 Also include the function name so the user has some hope of figuring
409 out what is going on. */
410 snprintf (name, GFC_MAX_SYMBOL_LEN, "master.%d.%s",
411 master_count++, ns->proc_name->name);
412 gfc_get_ha_symbol (name, &proc);
413 gcc_assert (proc != NULL);
415 gfc_add_procedure (&proc->attr, PROC_INTERNAL, proc->name, NULL);
416 if (ns->proc_name->attr.subroutine)
417 gfc_add_subroutine (&proc->attr, proc->name, NULL);
418 else
420 gfc_symbol *sym;
421 gfc_typespec *ts, *fts;
422 gfc_array_spec *as, *fas;
423 gfc_add_function (&proc->attr, proc->name, NULL);
424 proc->result = proc;
425 fas = ns->entries->sym->as;
426 fas = fas ? fas : ns->entries->sym->result->as;
427 fts = &ns->entries->sym->result->ts;
428 if (fts->type == BT_UNKNOWN)
429 fts = gfc_get_default_type (ns->entries->sym->result, NULL);
430 for (el = ns->entries->next; el; el = el->next)
432 ts = &el->sym->result->ts;
433 as = el->sym->as;
434 as = as ? as : el->sym->result->as;
435 if (ts->type == BT_UNKNOWN)
436 ts = gfc_get_default_type (el->sym->result, NULL);
438 if (! gfc_compare_types (ts, fts)
439 || (el->sym->result->attr.dimension
440 != ns->entries->sym->result->attr.dimension)
441 || (el->sym->result->attr.pointer
442 != ns->entries->sym->result->attr.pointer))
443 break;
445 else if (as && fas && gfc_compare_array_spec (as, fas) == 0)
446 gfc_error ("Procedure %s at %L has entries with mismatched "
447 "array specifications", ns->entries->sym->name,
448 &ns->entries->sym->declared_at);
451 if (el == NULL)
453 sym = ns->entries->sym->result;
454 /* All result types the same. */
455 proc->ts = *fts;
456 if (sym->attr.dimension)
457 gfc_set_array_spec (proc, gfc_copy_array_spec (sym->as), NULL);
458 if (sym->attr.pointer)
459 gfc_add_pointer (&proc->attr, NULL);
461 else
463 /* Otherwise the result will be passed through a union by
464 reference. */
465 proc->attr.mixed_entry_master = 1;
466 for (el = ns->entries; el; el = el->next)
468 sym = el->sym->result;
469 if (sym->attr.dimension)
471 if (el == ns->entries)
472 gfc_error
473 ("FUNCTION result %s can't be an array in FUNCTION %s at %L",
474 sym->name, ns->entries->sym->name, &sym->declared_at);
475 else
476 gfc_error
477 ("ENTRY result %s can't be an array in FUNCTION %s at %L",
478 sym->name, ns->entries->sym->name, &sym->declared_at);
480 else if (sym->attr.pointer)
482 if (el == ns->entries)
483 gfc_error
484 ("FUNCTION result %s can't be a POINTER in FUNCTION %s at %L",
485 sym->name, ns->entries->sym->name, &sym->declared_at);
486 else
487 gfc_error
488 ("ENTRY result %s can't be a POINTER in FUNCTION %s at %L",
489 sym->name, ns->entries->sym->name, &sym->declared_at);
491 else
493 ts = &sym->ts;
494 if (ts->type == BT_UNKNOWN)
495 ts = gfc_get_default_type (sym, NULL);
496 switch (ts->type)
498 case BT_INTEGER:
499 if (ts->kind == gfc_default_integer_kind)
500 sym = NULL;
501 break;
502 case BT_REAL:
503 if (ts->kind == gfc_default_real_kind
504 || ts->kind == gfc_default_double_kind)
505 sym = NULL;
506 break;
507 case BT_COMPLEX:
508 if (ts->kind == gfc_default_complex_kind)
509 sym = NULL;
510 break;
511 case BT_LOGICAL:
512 if (ts->kind == gfc_default_logical_kind)
513 sym = NULL;
514 break;
515 case BT_UNKNOWN:
516 /* We will issue error elsewhere. */
517 sym = NULL;
518 break;
519 default:
520 break;
522 if (sym)
524 if (el == ns->entries)
525 gfc_error
526 ("FUNCTION result %s can't be of type %s in FUNCTION %s at %L",
527 sym->name, gfc_typename (ts), ns->entries->sym->name,
528 &sym->declared_at);
529 else
530 gfc_error
531 ("ENTRY result %s can't be of type %s in FUNCTION %s at %L",
532 sym->name, gfc_typename (ts), ns->entries->sym->name,
533 &sym->declared_at);
539 proc->attr.access = ACCESS_PRIVATE;
540 proc->attr.entry_master = 1;
542 /* Merge all the entry point arguments. */
543 for (el = ns->entries; el; el = el->next)
544 merge_argument_lists (proc, el->sym->formal);
546 /* Use the master function for the function body. */
547 ns->proc_name = proc;
549 /* Finalize the new symbols. */
550 gfc_commit_symbols ();
552 /* Restore the original namespace. */
553 gfc_current_ns = old_ns;
557 /* Resolve contained function types. Because contained functions can call one
558 another, they have to be worked out before any of the contained procedures
559 can be resolved.
561 The good news is that if a function doesn't already have a type, the only
562 way it can get one is through an IMPLICIT type or a RESULT variable, because
563 by definition contained functions are contained namespace they're contained
564 in, not in a sibling or parent namespace. */
566 static void
567 resolve_contained_functions (gfc_namespace * ns)
569 gfc_namespace *child;
570 gfc_entry_list *el;
572 resolve_formal_arglists (ns);
574 for (child = ns->contained; child; child = child->sibling)
576 /* Resolve alternate entry points first. */
577 resolve_entries (child);
579 /* Then check function return types. */
580 resolve_contained_fntype (child->proc_name, child);
581 for (el = child->entries; el; el = el->next)
582 resolve_contained_fntype (el->sym, child);
587 /* Resolve all of the elements of a structure constructor and make sure that
588 the types are correct. */
590 static try
591 resolve_structure_cons (gfc_expr * expr)
593 gfc_constructor *cons;
594 gfc_component *comp;
595 try t;
596 symbol_attribute a;
598 t = SUCCESS;
599 cons = expr->value.constructor;
600 /* A constructor may have references if it is the result of substituting a
601 parameter variable. In this case we just pull out the component we
602 want. */
603 if (expr->ref)
604 comp = expr->ref->u.c.sym->components;
605 else
606 comp = expr->ts.derived->components;
608 for (; comp; comp = comp->next, cons = cons->next)
610 if (! cons->expr)
611 continue;
613 if (gfc_resolve_expr (cons->expr) == FAILURE)
615 t = FAILURE;
616 continue;
619 if (cons->expr->expr_type != EXPR_NULL
620 && comp->as && comp->as->rank != cons->expr->rank
621 && (comp->allocatable || cons->expr->rank))
623 gfc_error ("The rank of the element in the derived type "
624 "constructor at %L does not match that of the "
625 "component (%d/%d)", &cons->expr->where,
626 cons->expr->rank, comp->as ? comp->as->rank : 0);
627 t = FAILURE;
630 /* If we don't have the right type, try to convert it. */
632 if (!gfc_compare_types (&cons->expr->ts, &comp->ts))
634 t = FAILURE;
635 if (comp->pointer && cons->expr->ts.type != BT_UNKNOWN)
636 gfc_error ("The element in the derived type constructor at %L, "
637 "for pointer component '%s', is %s but should be %s",
638 &cons->expr->where, comp->name,
639 gfc_basic_typename (cons->expr->ts.type),
640 gfc_basic_typename (comp->ts.type));
641 else
642 t = gfc_convert_type (cons->expr, &comp->ts, 1);
645 if (!comp->pointer || cons->expr->expr_type == EXPR_NULL)
646 continue;
648 a = gfc_expr_attr (cons->expr);
650 if (!a.pointer && !a.target)
652 t = FAILURE;
653 gfc_error ("The element in the derived type constructor at %L, "
654 "for pointer component '%s' should be a POINTER or "
655 "a TARGET", &cons->expr->where, comp->name);
659 return t;
664 /****************** Expression name resolution ******************/
666 /* Returns 0 if a symbol was not declared with a type or
667 attribute declaration statement, nonzero otherwise. */
669 static int
670 was_declared (gfc_symbol * sym)
672 symbol_attribute a;
674 a = sym->attr;
676 if (!a.implicit_type && sym->ts.type != BT_UNKNOWN)
677 return 1;
679 if (a.allocatable || a.dimension || a.dummy || a.external || a.intrinsic
680 || a.optional || a.pointer || a.save || a.target
681 || a.access != ACCESS_UNKNOWN || a.intent != INTENT_UNKNOWN)
682 return 1;
684 return 0;
688 /* Determine if a symbol is generic or not. */
690 static int
691 generic_sym (gfc_symbol * sym)
693 gfc_symbol *s;
695 if (sym->attr.generic ||
696 (sym->attr.intrinsic && gfc_generic_intrinsic (sym->name)))
697 return 1;
699 if (was_declared (sym) || sym->ns->parent == NULL)
700 return 0;
702 gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
704 return (s == NULL) ? 0 : generic_sym (s);
708 /* Determine if a symbol is specific or not. */
710 static int
711 specific_sym (gfc_symbol * sym)
713 gfc_symbol *s;
715 if (sym->attr.if_source == IFSRC_IFBODY
716 || sym->attr.proc == PROC_MODULE
717 || sym->attr.proc == PROC_INTERNAL
718 || sym->attr.proc == PROC_ST_FUNCTION
719 || (sym->attr.intrinsic &&
720 gfc_specific_intrinsic (sym->name))
721 || sym->attr.external)
722 return 1;
724 if (was_declared (sym) || sym->ns->parent == NULL)
725 return 0;
727 gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
729 return (s == NULL) ? 0 : specific_sym (s);
733 /* Figure out if the procedure is specific, generic or unknown. */
735 typedef enum
736 { PTYPE_GENERIC = 1, PTYPE_SPECIFIC, PTYPE_UNKNOWN }
737 proc_type;
739 static proc_type
740 procedure_kind (gfc_symbol * sym)
743 if (generic_sym (sym))
744 return PTYPE_GENERIC;
746 if (specific_sym (sym))
747 return PTYPE_SPECIFIC;
749 return PTYPE_UNKNOWN;
752 /* Check references to assumed size arrays. The flag need_full_assumed_size
753 is nonzero when matching actual arguments. */
755 static int need_full_assumed_size = 0;
757 static bool
758 check_assumed_size_reference (gfc_symbol * sym, gfc_expr * e)
760 gfc_ref * ref;
761 int dim;
762 int last = 1;
764 if (need_full_assumed_size
765 || !(sym->as && sym->as->type == AS_ASSUMED_SIZE))
766 return false;
768 for (ref = e->ref; ref; ref = ref->next)
769 if (ref->type == REF_ARRAY)
770 for (dim = 0; dim < ref->u.ar.as->rank; dim++)
771 last = (ref->u.ar.end[dim] == NULL) && (ref->u.ar.type == DIMEN_ELEMENT);
773 if (last)
775 gfc_error ("The upper bound in the last dimension must "
776 "appear in the reference to the assumed size "
777 "array '%s' at %L.", sym->name, &e->where);
778 return true;
780 return false;
784 /* Look for bad assumed size array references in argument expressions
785 of elemental and array valued intrinsic procedures. Since this is
786 called from procedure resolution functions, it only recurses at
787 operators. */
789 static bool
790 resolve_assumed_size_actual (gfc_expr *e)
792 if (e == NULL)
793 return false;
795 switch (e->expr_type)
797 case EXPR_VARIABLE:
798 if (e->symtree
799 && check_assumed_size_reference (e->symtree->n.sym, e))
800 return true;
801 break;
803 case EXPR_OP:
804 if (resolve_assumed_size_actual (e->value.op.op1)
805 || resolve_assumed_size_actual (e->value.op.op2))
806 return true;
807 break;
809 default:
810 break;
812 return false;
816 /* Resolve an actual argument list. Most of the time, this is just
817 resolving the expressions in the list.
818 The exception is that we sometimes have to decide whether arguments
819 that look like procedure arguments are really simple variable
820 references. */
822 static try
823 resolve_actual_arglist (gfc_actual_arglist * arg)
825 gfc_symbol *sym;
826 gfc_symtree *parent_st;
827 gfc_expr *e;
829 for (; arg; arg = arg->next)
832 e = arg->expr;
833 if (e == NULL)
835 /* Check the label is a valid branching target. */
836 if (arg->label)
838 if (arg->label->defined == ST_LABEL_UNKNOWN)
840 gfc_error ("Label %d referenced at %L is never defined",
841 arg->label->value, &arg->label->where);
842 return FAILURE;
845 continue;
848 if (e->ts.type != BT_PROCEDURE)
850 if (gfc_resolve_expr (e) != SUCCESS)
851 return FAILURE;
852 continue;
855 /* See if the expression node should really be a variable
856 reference. */
858 sym = e->symtree->n.sym;
860 if (sym->attr.flavor == FL_PROCEDURE
861 || sym->attr.intrinsic
862 || sym->attr.external)
864 int actual_ok;
866 /* If a procedure is not already determined to be something else
867 check if it is intrinsic. */
868 if (!sym->attr.intrinsic
869 && !(sym->attr.external || sym->attr.use_assoc
870 || sym->attr.if_source == IFSRC_IFBODY)
871 && gfc_intrinsic_name (sym->name, sym->attr.subroutine))
872 sym->attr.intrinsic = 1;
874 if (sym->attr.proc == PROC_ST_FUNCTION)
876 gfc_error ("Statement function '%s' at %L is not allowed as an "
877 "actual argument", sym->name, &e->where);
880 actual_ok = gfc_intrinsic_actual_ok (sym->name, sym->attr.subroutine);
881 if (sym->attr.intrinsic && actual_ok == 0)
883 gfc_error ("Intrinsic '%s' at %L is not allowed as an "
884 "actual argument", sym->name, &e->where);
886 else if (sym->attr.intrinsic && actual_ok == 2)
887 /* We need a special case for CHAR, which is the only intrinsic
888 function allowed as actual argument in F2003 and not allowed
889 in F95. */
890 gfc_notify_std (GFC_STD_F2003, "Fortran 2003: CHAR intrinsic "
891 "allowed as actual argument at %L", &e->where);
893 if (sym->attr.contained && !sym->attr.use_assoc
894 && sym->ns->proc_name->attr.flavor != FL_MODULE)
896 gfc_error ("Internal procedure '%s' is not allowed as an "
897 "actual argument at %L", sym->name, &e->where);
900 if (sym->attr.elemental && !sym->attr.intrinsic)
902 gfc_error ("ELEMENTAL non-INTRINSIC procedure '%s' is not "
903 "allowed as an actual argument at %L", sym->name,
904 &e->where);
907 if (sym->attr.generic)
909 gfc_error ("GENERIC non-INTRINSIC procedure '%s' is not "
910 "allowed as an actual argument at %L", sym->name,
911 &e->where);
914 /* If the symbol is the function that names the current (or
915 parent) scope, then we really have a variable reference. */
917 if (sym->attr.function && sym->result == sym
918 && (sym->ns->proc_name == sym
919 || (sym->ns->parent != NULL
920 && sym->ns->parent->proc_name == sym)))
921 goto got_variable;
923 continue;
926 /* See if the name is a module procedure in a parent unit. */
928 if (was_declared (sym) || sym->ns->parent == NULL)
929 goto got_variable;
931 if (gfc_find_sym_tree (sym->name, sym->ns->parent, 1, &parent_st))
933 gfc_error ("Symbol '%s' at %L is ambiguous", sym->name, &e->where);
934 return FAILURE;
937 if (parent_st == NULL)
938 goto got_variable;
940 sym = parent_st->n.sym;
941 e->symtree = parent_st; /* Point to the right thing. */
943 if (sym->attr.flavor == FL_PROCEDURE
944 || sym->attr.intrinsic
945 || sym->attr.external)
947 continue;
950 got_variable:
951 e->expr_type = EXPR_VARIABLE;
952 e->ts = sym->ts;
953 if (sym->as != NULL)
955 e->rank = sym->as->rank;
956 e->ref = gfc_get_ref ();
957 e->ref->type = REF_ARRAY;
958 e->ref->u.ar.type = AR_FULL;
959 e->ref->u.ar.as = sym->as;
963 return SUCCESS;
967 /* Do the checks of the actual argument list that are specific to elemental
968 procedures. If called with c == NULL, we have a function, otherwise if
969 expr == NULL, we have a subroutine. */
970 static try
971 resolve_elemental_actual (gfc_expr *expr, gfc_code *c)
973 gfc_actual_arglist *arg0;
974 gfc_actual_arglist *arg;
975 gfc_symbol *esym = NULL;
976 gfc_intrinsic_sym *isym = NULL;
977 gfc_expr *e = NULL;
978 gfc_intrinsic_arg *iformal = NULL;
979 gfc_formal_arglist *eformal = NULL;
980 bool formal_optional = false;
981 bool set_by_optional = false;
982 int i;
983 int rank = 0;
985 /* Is this an elemental procedure? */
986 if (expr && expr->value.function.actual != NULL)
988 if (expr->value.function.esym != NULL
989 && expr->value.function.esym->attr.elemental)
991 arg0 = expr->value.function.actual;
992 esym = expr->value.function.esym;
994 else if (expr->value.function.isym != NULL
995 && expr->value.function.isym->elemental)
997 arg0 = expr->value.function.actual;
998 isym = expr->value.function.isym;
1000 else
1001 return SUCCESS;
1003 else if (c && c->ext.actual != NULL
1004 && c->symtree->n.sym->attr.elemental)
1006 arg0 = c->ext.actual;
1007 esym = c->symtree->n.sym;
1009 else
1010 return SUCCESS;
1012 /* The rank of an elemental is the rank of its array argument(s). */
1013 for (arg = arg0; arg; arg = arg->next)
1015 if (arg->expr != NULL && arg->expr->rank > 0)
1017 rank = arg->expr->rank;
1018 if (arg->expr->expr_type == EXPR_VARIABLE
1019 && arg->expr->symtree->n.sym->attr.optional)
1020 set_by_optional = true;
1022 /* Function specific; set the result rank and shape. */
1023 if (expr)
1025 expr->rank = rank;
1026 if (!expr->shape && arg->expr->shape)
1028 expr->shape = gfc_get_shape (rank);
1029 for (i = 0; i < rank; i++)
1030 mpz_init_set (expr->shape[i], arg->expr->shape[i]);
1033 break;
1037 /* If it is an array, it shall not be supplied as an actual argument
1038 to an elemental procedure unless an array of the same rank is supplied
1039 as an actual argument corresponding to a nonoptional dummy argument of
1040 that elemental procedure(12.4.1.5). */
1041 formal_optional = false;
1042 if (isym)
1043 iformal = isym->formal;
1044 else
1045 eformal = esym->formal;
1047 for (arg = arg0; arg; arg = arg->next)
1049 if (eformal)
1051 if (eformal->sym && eformal->sym->attr.optional)
1052 formal_optional = true;
1053 eformal = eformal->next;
1055 else if (isym && iformal)
1057 if (iformal->optional)
1058 formal_optional = true;
1059 iformal = iformal->next;
1061 else if (isym)
1062 formal_optional = true;
1064 if (pedantic && arg->expr != NULL
1065 && arg->expr->expr_type == EXPR_VARIABLE
1066 && arg->expr->symtree->n.sym->attr.optional
1067 && formal_optional
1068 && arg->expr->rank
1069 && (set_by_optional || arg->expr->rank != rank)
1070 && !(isym && isym->generic_id == GFC_ISYM_CONVERSION))
1072 gfc_warning ("'%s' at %L is an array and OPTIONAL; IF IT IS "
1073 "MISSING, it cannot be the actual argument of an "
1074 "ELEMENTAL procedure unless there is a non-optional"
1075 "argument with the same rank (12.4.1.5)",
1076 arg->expr->symtree->n.sym->name, &arg->expr->where);
1077 return FAILURE;
1081 for (arg = arg0; arg; arg = arg->next)
1083 if (arg->expr == NULL || arg->expr->rank == 0)
1084 continue;
1086 /* Being elemental, the last upper bound of an assumed size array
1087 argument must be present. */
1088 if (resolve_assumed_size_actual (arg->expr))
1089 return FAILURE;
1091 if (expr)
1092 continue;
1094 /* Elemental subroutine array actual arguments must conform. */
1095 if (e != NULL)
1097 if (gfc_check_conformance ("elemental subroutine", arg->expr, e)
1098 == FAILURE)
1099 return FAILURE;
1101 else
1102 e = arg->expr;
1105 return SUCCESS;
1109 /* Go through each actual argument in ACTUAL and see if it can be
1110 implemented as an inlined, non-copying intrinsic. FNSYM is the
1111 function being called, or NULL if not known. */
1113 static void
1114 find_noncopying_intrinsics (gfc_symbol * fnsym, gfc_actual_arglist * actual)
1116 gfc_actual_arglist *ap;
1117 gfc_expr *expr;
1119 for (ap = actual; ap; ap = ap->next)
1120 if (ap->expr
1121 && (expr = gfc_get_noncopying_intrinsic_argument (ap->expr))
1122 && !gfc_check_fncall_dependency (expr, INTENT_IN, fnsym, actual))
1123 ap->expr->inline_noncopying_intrinsic = 1;
1126 /* This function does the checking of references to global procedures
1127 as defined in sections 18.1 and 14.1, respectively, of the Fortran
1128 77 and 95 standards. It checks for a gsymbol for the name, making
1129 one if it does not already exist. If it already exists, then the
1130 reference being resolved must correspond to the type of gsymbol.
1131 Otherwise, the new symbol is equipped with the attributes of the
1132 reference. The corresponding code that is called in creating
1133 global entities is parse.c. */
1135 static void
1136 resolve_global_procedure (gfc_symbol *sym, locus *where, int sub)
1138 gfc_gsymbol * gsym;
1139 unsigned int type;
1141 type = sub ? GSYM_SUBROUTINE : GSYM_FUNCTION;
1143 gsym = gfc_get_gsymbol (sym->name);
1145 if ((gsym->type != GSYM_UNKNOWN && gsym->type != type))
1146 global_used (gsym, where);
1148 if (gsym->type == GSYM_UNKNOWN)
1150 gsym->type = type;
1151 gsym->where = *where;
1154 gsym->used = 1;
1157 /************* Function resolution *************/
1159 /* Resolve a function call known to be generic.
1160 Section 14.1.2.4.1. */
1162 static match
1163 resolve_generic_f0 (gfc_expr * expr, gfc_symbol * sym)
1165 gfc_symbol *s;
1167 if (sym->attr.generic)
1170 gfc_search_interface (sym->generic, 0, &expr->value.function.actual);
1171 if (s != NULL)
1173 expr->value.function.name = s->name;
1174 expr->value.function.esym = s;
1176 if (s->ts.type != BT_UNKNOWN)
1177 expr->ts = s->ts;
1178 else if (s->result != NULL && s->result->ts.type != BT_UNKNOWN)
1179 expr->ts = s->result->ts;
1181 if (s->as != NULL)
1182 expr->rank = s->as->rank;
1183 else if (s->result != NULL && s->result->as != NULL)
1184 expr->rank = s->result->as->rank;
1186 return MATCH_YES;
1189 /* TODO: Need to search for elemental references in generic interface */
1192 if (sym->attr.intrinsic)
1193 return gfc_intrinsic_func_interface (expr, 0);
1195 return MATCH_NO;
1199 static try
1200 resolve_generic_f (gfc_expr * expr)
1202 gfc_symbol *sym;
1203 match m;
1205 sym = expr->symtree->n.sym;
1207 for (;;)
1209 m = resolve_generic_f0 (expr, sym);
1210 if (m == MATCH_YES)
1211 return SUCCESS;
1212 else if (m == MATCH_ERROR)
1213 return FAILURE;
1215 generic:
1216 if (sym->ns->parent == NULL)
1217 break;
1218 gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
1220 if (sym == NULL)
1221 break;
1222 if (!generic_sym (sym))
1223 goto generic;
1226 /* Last ditch attempt. */
1228 if (!gfc_generic_intrinsic (expr->symtree->n.sym->name))
1230 gfc_error ("There is no specific function for the generic '%s' at %L",
1231 expr->symtree->n.sym->name, &expr->where);
1232 return FAILURE;
1235 m = gfc_intrinsic_func_interface (expr, 0);
1236 if (m == MATCH_YES)
1237 return SUCCESS;
1238 if (m == MATCH_NO)
1239 gfc_error
1240 ("Generic function '%s' at %L is not consistent with a specific "
1241 "intrinsic interface", expr->symtree->n.sym->name, &expr->where);
1243 return FAILURE;
1247 /* Resolve a function call known to be specific. */
1249 static match
1250 resolve_specific_f0 (gfc_symbol * sym, gfc_expr * expr)
1252 match m;
1254 if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
1256 if (sym->attr.dummy)
1258 sym->attr.proc = PROC_DUMMY;
1259 goto found;
1262 sym->attr.proc = PROC_EXTERNAL;
1263 goto found;
1266 if (sym->attr.proc == PROC_MODULE
1267 || sym->attr.proc == PROC_ST_FUNCTION
1268 || sym->attr.proc == PROC_INTERNAL)
1269 goto found;
1271 if (sym->attr.intrinsic)
1273 m = gfc_intrinsic_func_interface (expr, 1);
1274 if (m == MATCH_YES)
1275 return MATCH_YES;
1276 if (m == MATCH_NO)
1277 gfc_error
1278 ("Function '%s' at %L is INTRINSIC but is not compatible with "
1279 "an intrinsic", sym->name, &expr->where);
1281 return MATCH_ERROR;
1284 return MATCH_NO;
1286 found:
1287 gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
1289 expr->ts = sym->ts;
1290 expr->value.function.name = sym->name;
1291 expr->value.function.esym = sym;
1292 if (sym->as != NULL)
1293 expr->rank = sym->as->rank;
1295 return MATCH_YES;
1299 static try
1300 resolve_specific_f (gfc_expr * expr)
1302 gfc_symbol *sym;
1303 match m;
1305 sym = expr->symtree->n.sym;
1307 for (;;)
1309 m = resolve_specific_f0 (sym, expr);
1310 if (m == MATCH_YES)
1311 return SUCCESS;
1312 if (m == MATCH_ERROR)
1313 return FAILURE;
1315 if (sym->ns->parent == NULL)
1316 break;
1318 gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
1320 if (sym == NULL)
1321 break;
1324 gfc_error ("Unable to resolve the specific function '%s' at %L",
1325 expr->symtree->n.sym->name, &expr->where);
1327 return SUCCESS;
1331 /* Resolve a procedure call not known to be generic nor specific. */
1333 static try
1334 resolve_unknown_f (gfc_expr * expr)
1336 gfc_symbol *sym;
1337 gfc_typespec *ts;
1339 sym = expr->symtree->n.sym;
1341 if (sym->attr.dummy)
1343 sym->attr.proc = PROC_DUMMY;
1344 expr->value.function.name = sym->name;
1345 goto set_type;
1348 /* See if we have an intrinsic function reference. */
1350 if (gfc_intrinsic_name (sym->name, 0))
1352 if (gfc_intrinsic_func_interface (expr, 1) == MATCH_YES)
1353 return SUCCESS;
1354 return FAILURE;
1357 /* The reference is to an external name. */
1359 sym->attr.proc = PROC_EXTERNAL;
1360 expr->value.function.name = sym->name;
1361 expr->value.function.esym = expr->symtree->n.sym;
1363 if (sym->as != NULL)
1364 expr->rank = sym->as->rank;
1366 /* Type of the expression is either the type of the symbol or the
1367 default type of the symbol. */
1369 set_type:
1370 gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
1372 if (sym->ts.type != BT_UNKNOWN)
1373 expr->ts = sym->ts;
1374 else
1376 ts = gfc_get_default_type (sym, sym->ns);
1378 if (ts->type == BT_UNKNOWN)
1380 gfc_error ("Function '%s' at %L has no IMPLICIT type",
1381 sym->name, &expr->where);
1382 return FAILURE;
1384 else
1385 expr->ts = *ts;
1388 return SUCCESS;
1392 /* Figure out if a function reference is pure or not. Also set the name
1393 of the function for a potential error message. Return nonzero if the
1394 function is PURE, zero if not. */
1396 static int
1397 pure_function (gfc_expr * e, const char **name)
1399 int pure;
1401 if (e->value.function.esym)
1403 pure = gfc_pure (e->value.function.esym);
1404 *name = e->value.function.esym->name;
1406 else if (e->value.function.isym)
1408 pure = e->value.function.isym->pure
1409 || e->value.function.isym->elemental;
1410 *name = e->value.function.isym->name;
1412 else
1414 /* Implicit functions are not pure. */
1415 pure = 0;
1416 *name = e->value.function.name;
1419 return pure;
1423 /* Resolve a function call, which means resolving the arguments, then figuring
1424 out which entity the name refers to. */
1425 /* TODO: Check procedure arguments so that an INTENT(IN) isn't passed
1426 to INTENT(OUT) or INTENT(INOUT). */
1428 static try
1429 resolve_function (gfc_expr * expr)
1431 gfc_actual_arglist *arg;
1432 gfc_symbol * sym;
1433 const char *name;
1434 try t;
1435 int temp;
1437 sym = NULL;
1438 if (expr->symtree)
1439 sym = expr->symtree->n.sym;
1441 /* If the procedure is not internal, a statement function or a module
1442 procedure,it must be external and should be checked for usage. */
1443 if (sym && !sym->attr.dummy && !sym->attr.contained
1444 && sym->attr.proc != PROC_ST_FUNCTION
1445 && !sym->attr.use_assoc)
1446 resolve_global_procedure (sym, &expr->where, 0);
1448 /* Switch off assumed size checking and do this again for certain kinds
1449 of procedure, once the procedure itself is resolved. */
1450 need_full_assumed_size++;
1452 if (resolve_actual_arglist (expr->value.function.actual) == FAILURE)
1453 return FAILURE;
1455 /* Resume assumed_size checking. */
1456 need_full_assumed_size--;
1458 if (sym && sym->ts.type == BT_CHARACTER
1459 && sym->ts.cl
1460 && sym->ts.cl->length == NULL
1461 && !sym->attr.dummy
1462 && expr->value.function.esym == NULL
1463 && !sym->attr.contained)
1465 /* Internal procedures are taken care of in resolve_contained_fntype. */
1466 gfc_error ("Function '%s' is declared CHARACTER(*) and cannot "
1467 "be used at %L since it is not a dummy argument",
1468 sym->name, &expr->where);
1469 return FAILURE;
1472 /* See if function is already resolved. */
1474 if (expr->value.function.name != NULL)
1476 if (expr->ts.type == BT_UNKNOWN)
1477 expr->ts = sym->ts;
1478 t = SUCCESS;
1480 else
1482 /* Apply the rules of section 14.1.2. */
1484 switch (procedure_kind (sym))
1486 case PTYPE_GENERIC:
1487 t = resolve_generic_f (expr);
1488 break;
1490 case PTYPE_SPECIFIC:
1491 t = resolve_specific_f (expr);
1492 break;
1494 case PTYPE_UNKNOWN:
1495 t = resolve_unknown_f (expr);
1496 break;
1498 default:
1499 gfc_internal_error ("resolve_function(): bad function type");
1503 /* If the expression is still a function (it might have simplified),
1504 then we check to see if we are calling an elemental function. */
1506 if (expr->expr_type != EXPR_FUNCTION)
1507 return t;
1509 temp = need_full_assumed_size;
1510 need_full_assumed_size = 0;
1512 if (resolve_elemental_actual (expr, NULL) == FAILURE)
1513 return FAILURE;
1515 if (omp_workshare_flag
1516 && expr->value.function.esym
1517 && ! gfc_elemental (expr->value.function.esym))
1519 gfc_error ("User defined non-ELEMENTAL function '%s' at %L not allowed"
1520 " in WORKSHARE construct", expr->value.function.esym->name,
1521 &expr->where);
1522 t = FAILURE;
1525 else if (expr->value.function.actual != NULL
1526 && expr->value.function.isym != NULL
1527 && expr->value.function.isym->generic_id != GFC_ISYM_LBOUND
1528 && expr->value.function.isym->generic_id != GFC_ISYM_LOC
1529 && expr->value.function.isym->generic_id != GFC_ISYM_PRESENT)
1531 /* Array intrinsics must also have the last upper bound of an
1532 assumed size array argument. UBOUND and SIZE have to be
1533 excluded from the check if the second argument is anything
1534 than a constant. */
1535 int inquiry;
1536 inquiry = expr->value.function.isym->generic_id == GFC_ISYM_UBOUND
1537 || expr->value.function.isym->generic_id == GFC_ISYM_SIZE;
1539 for (arg = expr->value.function.actual; arg; arg = arg->next)
1541 if (inquiry && arg->next != NULL && arg->next->expr
1542 && arg->next->expr->expr_type != EXPR_CONSTANT)
1543 break;
1545 if (arg->expr != NULL
1546 && arg->expr->rank > 0
1547 && resolve_assumed_size_actual (arg->expr))
1548 return FAILURE;
1552 need_full_assumed_size = temp;
1554 if (!pure_function (expr, &name) && name)
1556 if (forall_flag)
1558 gfc_error
1559 ("reference to non-PURE function '%s' at %L inside a "
1560 "FORALL %s", name, &expr->where, forall_flag == 2 ?
1561 "mask" : "block");
1562 t = FAILURE;
1564 else if (gfc_pure (NULL))
1566 gfc_error ("Function reference to '%s' at %L is to a non-PURE "
1567 "procedure within a PURE procedure", name, &expr->where);
1568 t = FAILURE;
1572 /* Functions without the RECURSIVE attribution are not allowed to
1573 * call themselves. */
1574 if (expr->value.function.esym && !expr->value.function.esym->attr.recursive)
1576 gfc_symbol *esym, *proc;
1577 esym = expr->value.function.esym;
1578 proc = gfc_current_ns->proc_name;
1579 if (esym == proc)
1581 gfc_error ("Function '%s' at %L cannot call itself, as it is not "
1582 "RECURSIVE", name, &expr->where);
1583 t = FAILURE;
1586 if (esym->attr.entry && esym->ns->entries && proc->ns->entries
1587 && esym->ns->entries->sym == proc->ns->entries->sym)
1589 gfc_error ("Call to ENTRY '%s' at %L is recursive, but function "
1590 "'%s' is not declared as RECURSIVE",
1591 esym->name, &expr->where, esym->ns->entries->sym->name);
1592 t = FAILURE;
1596 /* Character lengths of use associated functions may contains references to
1597 symbols not referenced from the current program unit otherwise. Make sure
1598 those symbols are marked as referenced. */
1600 if (expr->ts.type == BT_CHARACTER && expr->value.function.esym
1601 && expr->value.function.esym->attr.use_assoc)
1603 gfc_expr_set_symbols_referenced (expr->ts.cl->length);
1606 if (t == SUCCESS)
1607 find_noncopying_intrinsics (expr->value.function.esym,
1608 expr->value.function.actual);
1609 return t;
1613 /************* Subroutine resolution *************/
1615 static void
1616 pure_subroutine (gfc_code * c, gfc_symbol * sym)
1619 if (gfc_pure (sym))
1620 return;
1622 if (forall_flag)
1623 gfc_error ("Subroutine call to '%s' in FORALL block at %L is not PURE",
1624 sym->name, &c->loc);
1625 else if (gfc_pure (NULL))
1626 gfc_error ("Subroutine call to '%s' at %L is not PURE", sym->name,
1627 &c->loc);
1631 static match
1632 resolve_generic_s0 (gfc_code * c, gfc_symbol * sym)
1634 gfc_symbol *s;
1636 if (sym->attr.generic)
1638 s = gfc_search_interface (sym->generic, 1, &c->ext.actual);
1639 if (s != NULL)
1641 c->resolved_sym = s;
1642 pure_subroutine (c, s);
1643 return MATCH_YES;
1646 /* TODO: Need to search for elemental references in generic interface. */
1649 if (sym->attr.intrinsic)
1650 return gfc_intrinsic_sub_interface (c, 0);
1652 return MATCH_NO;
1656 static try
1657 resolve_generic_s (gfc_code * c)
1659 gfc_symbol *sym;
1660 match m;
1662 sym = c->symtree->n.sym;
1664 for (;;)
1666 m = resolve_generic_s0 (c, sym);
1667 if (m == MATCH_YES)
1668 return SUCCESS;
1669 else if (m == MATCH_ERROR)
1670 return FAILURE;
1672 generic:
1673 if (sym->ns->parent == NULL)
1674 break;
1675 gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
1677 if (sym == NULL)
1678 break;
1679 if (!generic_sym (sym))
1680 goto generic;
1683 /* Last ditch attempt. */
1684 sym = c->symtree->n.sym;
1685 if (!gfc_generic_intrinsic (sym->name))
1687 gfc_error
1688 ("There is no specific subroutine for the generic '%s' at %L",
1689 sym->name, &c->loc);
1690 return FAILURE;
1693 m = gfc_intrinsic_sub_interface (c, 0);
1694 if (m == MATCH_YES)
1695 return SUCCESS;
1696 if (m == MATCH_NO)
1697 gfc_error ("Generic subroutine '%s' at %L is not consistent with an "
1698 "intrinsic subroutine interface", sym->name, &c->loc);
1700 return FAILURE;
1704 /* Resolve a subroutine call known to be specific. */
1706 static match
1707 resolve_specific_s0 (gfc_code * c, gfc_symbol * sym)
1709 match m;
1711 if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
1713 if (sym->attr.dummy)
1715 sym->attr.proc = PROC_DUMMY;
1716 goto found;
1719 sym->attr.proc = PROC_EXTERNAL;
1720 goto found;
1723 if (sym->attr.proc == PROC_MODULE || sym->attr.proc == PROC_INTERNAL)
1724 goto found;
1726 if (sym->attr.intrinsic)
1728 m = gfc_intrinsic_sub_interface (c, 1);
1729 if (m == MATCH_YES)
1730 return MATCH_YES;
1731 if (m == MATCH_NO)
1732 gfc_error ("Subroutine '%s' at %L is INTRINSIC but is not compatible "
1733 "with an intrinsic", sym->name, &c->loc);
1735 return MATCH_ERROR;
1738 return MATCH_NO;
1740 found:
1741 gfc_procedure_use (sym, &c->ext.actual, &c->loc);
1743 c->resolved_sym = sym;
1744 pure_subroutine (c, sym);
1746 return MATCH_YES;
1750 static try
1751 resolve_specific_s (gfc_code * c)
1753 gfc_symbol *sym;
1754 match m;
1756 sym = c->symtree->n.sym;
1758 for (;;)
1760 m = resolve_specific_s0 (c, sym);
1761 if (m == MATCH_YES)
1762 return SUCCESS;
1763 if (m == MATCH_ERROR)
1764 return FAILURE;
1766 if (sym->ns->parent == NULL)
1767 break;
1769 gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
1771 if (sym == NULL)
1772 break;
1775 sym = c->symtree->n.sym;
1776 gfc_error ("Unable to resolve the specific subroutine '%s' at %L",
1777 sym->name, &c->loc);
1779 return FAILURE;
1783 /* Resolve a subroutine call not known to be generic nor specific. */
1785 static try
1786 resolve_unknown_s (gfc_code * c)
1788 gfc_symbol *sym;
1790 sym = c->symtree->n.sym;
1792 if (sym->attr.dummy)
1794 sym->attr.proc = PROC_DUMMY;
1795 goto found;
1798 /* See if we have an intrinsic function reference. */
1800 if (gfc_intrinsic_name (sym->name, 1))
1802 if (gfc_intrinsic_sub_interface (c, 1) == MATCH_YES)
1803 return SUCCESS;
1804 return FAILURE;
1807 /* The reference is to an external name. */
1809 found:
1810 gfc_procedure_use (sym, &c->ext.actual, &c->loc);
1812 c->resolved_sym = sym;
1814 pure_subroutine (c, sym);
1816 return SUCCESS;
1820 /* Resolve a subroutine call. Although it was tempting to use the same code
1821 for functions, subroutines and functions are stored differently and this
1822 makes things awkward. */
1824 static try
1825 resolve_call (gfc_code * c)
1827 try t;
1829 if (c->symtree && c->symtree->n.sym
1830 && c->symtree->n.sym->ts.type != BT_UNKNOWN)
1832 gfc_error ("'%s' at %L has a type, which is not consistent with "
1833 "the CALL at %L", c->symtree->n.sym->name,
1834 &c->symtree->n.sym->declared_at, &c->loc);
1835 return FAILURE;
1838 /* If the procedure is not internal or module, it must be external and
1839 should be checked for usage. */
1840 if (c->symtree && c->symtree->n.sym
1841 && !c->symtree->n.sym->attr.dummy
1842 && !c->symtree->n.sym->attr.contained
1843 && !c->symtree->n.sym->attr.use_assoc)
1844 resolve_global_procedure (c->symtree->n.sym, &c->loc, 1);
1846 /* Subroutines without the RECURSIVE attribution are not allowed to
1847 * call themselves. */
1848 if (c->symtree && c->symtree->n.sym && !c->symtree->n.sym->attr.recursive)
1850 gfc_symbol *csym, *proc;
1851 csym = c->symtree->n.sym;
1852 proc = gfc_current_ns->proc_name;
1853 if (csym == proc)
1855 gfc_error ("SUBROUTINE '%s' at %L cannot call itself, as it is not "
1856 "RECURSIVE", csym->name, &c->loc);
1857 t = FAILURE;
1860 if (csym->attr.entry && csym->ns->entries && proc->ns->entries
1861 && csym->ns->entries->sym == proc->ns->entries->sym)
1863 gfc_error ("Call to ENTRY '%s' at %L is recursive, but subroutine "
1864 "'%s' is not declared as RECURSIVE",
1865 csym->name, &c->loc, csym->ns->entries->sym->name);
1866 t = FAILURE;
1870 /* Switch off assumed size checking and do this again for certain kinds
1871 of procedure, once the procedure itself is resolved. */
1872 need_full_assumed_size++;
1874 if (resolve_actual_arglist (c->ext.actual) == FAILURE)
1875 return FAILURE;
1877 /* Resume assumed_size checking. */
1878 need_full_assumed_size--;
1881 t = SUCCESS;
1882 if (c->resolved_sym == NULL)
1883 switch (procedure_kind (c->symtree->n.sym))
1885 case PTYPE_GENERIC:
1886 t = resolve_generic_s (c);
1887 break;
1889 case PTYPE_SPECIFIC:
1890 t = resolve_specific_s (c);
1891 break;
1893 case PTYPE_UNKNOWN:
1894 t = resolve_unknown_s (c);
1895 break;
1897 default:
1898 gfc_internal_error ("resolve_subroutine(): bad function type");
1901 /* Some checks of elemental subroutine actual arguments. */
1902 if (resolve_elemental_actual (NULL, c) == FAILURE)
1903 return FAILURE;
1905 if (t == SUCCESS)
1906 find_noncopying_intrinsics (c->resolved_sym, c->ext.actual);
1907 return t;
1910 /* Compare the shapes of two arrays that have non-NULL shapes. If both
1911 op1->shape and op2->shape are non-NULL return SUCCESS if their shapes
1912 match. If both op1->shape and op2->shape are non-NULL return FAILURE
1913 if their shapes do not match. If either op1->shape or op2->shape is
1914 NULL, return SUCCESS. */
1916 static try
1917 compare_shapes (gfc_expr * op1, gfc_expr * op2)
1919 try t;
1920 int i;
1922 t = SUCCESS;
1924 if (op1->shape != NULL && op2->shape != NULL)
1926 for (i = 0; i < op1->rank; i++)
1928 if (mpz_cmp (op1->shape[i], op2->shape[i]) != 0)
1930 gfc_error ("Shapes for operands at %L and %L are not conformable",
1931 &op1->where, &op2->where);
1932 t = FAILURE;
1933 break;
1938 return t;
1941 /* Resolve an operator expression node. This can involve replacing the
1942 operation with a user defined function call. */
1944 static try
1945 resolve_operator (gfc_expr * e)
1947 gfc_expr *op1, *op2;
1948 char msg[200];
1949 try t;
1951 /* Resolve all subnodes-- give them types. */
1953 switch (e->value.op.operator)
1955 default:
1956 if (gfc_resolve_expr (e->value.op.op2) == FAILURE)
1957 return FAILURE;
1959 /* Fall through... */
1961 case INTRINSIC_NOT:
1962 case INTRINSIC_UPLUS:
1963 case INTRINSIC_UMINUS:
1964 case INTRINSIC_PARENTHESES:
1965 if (gfc_resolve_expr (e->value.op.op1) == FAILURE)
1966 return FAILURE;
1967 break;
1970 /* Typecheck the new node. */
1972 op1 = e->value.op.op1;
1973 op2 = e->value.op.op2;
1975 switch (e->value.op.operator)
1977 case INTRINSIC_UPLUS:
1978 case INTRINSIC_UMINUS:
1979 if (op1->ts.type == BT_INTEGER
1980 || op1->ts.type == BT_REAL
1981 || op1->ts.type == BT_COMPLEX)
1983 e->ts = op1->ts;
1984 break;
1987 sprintf (msg, _("Operand of unary numeric operator '%s' at %%L is %s"),
1988 gfc_op2string (e->value.op.operator), gfc_typename (&e->ts));
1989 goto bad_op;
1991 case INTRINSIC_PLUS:
1992 case INTRINSIC_MINUS:
1993 case INTRINSIC_TIMES:
1994 case INTRINSIC_DIVIDE:
1995 case INTRINSIC_POWER:
1996 if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
1998 gfc_type_convert_binary (e);
1999 break;
2002 sprintf (msg,
2003 _("Operands of binary numeric operator '%s' at %%L are %s/%s"),
2004 gfc_op2string (e->value.op.operator), gfc_typename (&op1->ts),
2005 gfc_typename (&op2->ts));
2006 goto bad_op;
2008 case INTRINSIC_CONCAT:
2009 if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER)
2011 e->ts.type = BT_CHARACTER;
2012 e->ts.kind = op1->ts.kind;
2013 break;
2016 sprintf (msg,
2017 _("Operands of string concatenation operator at %%L are %s/%s"),
2018 gfc_typename (&op1->ts), gfc_typename (&op2->ts));
2019 goto bad_op;
2021 case INTRINSIC_AND:
2022 case INTRINSIC_OR:
2023 case INTRINSIC_EQV:
2024 case INTRINSIC_NEQV:
2025 if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
2027 e->ts.type = BT_LOGICAL;
2028 e->ts.kind = gfc_kind_max (op1, op2);
2029 if (op1->ts.kind < e->ts.kind)
2030 gfc_convert_type (op1, &e->ts, 2);
2031 else if (op2->ts.kind < e->ts.kind)
2032 gfc_convert_type (op2, &e->ts, 2);
2033 break;
2036 sprintf (msg, _("Operands of logical operator '%s' at %%L are %s/%s"),
2037 gfc_op2string (e->value.op.operator), gfc_typename (&op1->ts),
2038 gfc_typename (&op2->ts));
2040 goto bad_op;
2042 case INTRINSIC_NOT:
2043 if (op1->ts.type == BT_LOGICAL)
2045 e->ts.type = BT_LOGICAL;
2046 e->ts.kind = op1->ts.kind;
2047 break;
2050 sprintf (msg, _("Operand of .NOT. operator at %%L is %s"),
2051 gfc_typename (&op1->ts));
2052 goto bad_op;
2054 case INTRINSIC_GT:
2055 case INTRINSIC_GE:
2056 case INTRINSIC_LT:
2057 case INTRINSIC_LE:
2058 if (op1->ts.type == BT_COMPLEX || op2->ts.type == BT_COMPLEX)
2060 strcpy (msg, _("COMPLEX quantities cannot be compared at %L"));
2061 goto bad_op;
2064 /* Fall through... */
2066 case INTRINSIC_EQ:
2067 case INTRINSIC_NE:
2068 if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER)
2070 e->ts.type = BT_LOGICAL;
2071 e->ts.kind = gfc_default_logical_kind;
2072 break;
2075 if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
2077 gfc_type_convert_binary (e);
2079 e->ts.type = BT_LOGICAL;
2080 e->ts.kind = gfc_default_logical_kind;
2081 break;
2084 if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
2085 sprintf (msg,
2086 _("Logicals at %%L must be compared with %s instead of %s"),
2087 e->value.op.operator == INTRINSIC_EQ ? ".EQV." : ".NEQV.",
2088 gfc_op2string (e->value.op.operator));
2089 else
2090 sprintf (msg,
2091 _("Operands of comparison operator '%s' at %%L are %s/%s"),
2092 gfc_op2string (e->value.op.operator), gfc_typename (&op1->ts),
2093 gfc_typename (&op2->ts));
2095 goto bad_op;
2097 case INTRINSIC_USER:
2098 if (op2 == NULL)
2099 sprintf (msg, _("Operand of user operator '%s' at %%L is %s"),
2100 e->value.op.uop->name, gfc_typename (&op1->ts));
2101 else
2102 sprintf (msg, _("Operands of user operator '%s' at %%L are %s/%s"),
2103 e->value.op.uop->name, gfc_typename (&op1->ts),
2104 gfc_typename (&op2->ts));
2106 goto bad_op;
2108 case INTRINSIC_PARENTHESES:
2109 break;
2111 default:
2112 gfc_internal_error ("resolve_operator(): Bad intrinsic");
2115 /* Deal with arrayness of an operand through an operator. */
2117 t = SUCCESS;
2119 switch (e->value.op.operator)
2121 case INTRINSIC_PLUS:
2122 case INTRINSIC_MINUS:
2123 case INTRINSIC_TIMES:
2124 case INTRINSIC_DIVIDE:
2125 case INTRINSIC_POWER:
2126 case INTRINSIC_CONCAT:
2127 case INTRINSIC_AND:
2128 case INTRINSIC_OR:
2129 case INTRINSIC_EQV:
2130 case INTRINSIC_NEQV:
2131 case INTRINSIC_EQ:
2132 case INTRINSIC_NE:
2133 case INTRINSIC_GT:
2134 case INTRINSIC_GE:
2135 case INTRINSIC_LT:
2136 case INTRINSIC_LE:
2138 if (op1->rank == 0 && op2->rank == 0)
2139 e->rank = 0;
2141 if (op1->rank == 0 && op2->rank != 0)
2143 e->rank = op2->rank;
2145 if (e->shape == NULL)
2146 e->shape = gfc_copy_shape (op2->shape, op2->rank);
2149 if (op1->rank != 0 && op2->rank == 0)
2151 e->rank = op1->rank;
2153 if (e->shape == NULL)
2154 e->shape = gfc_copy_shape (op1->shape, op1->rank);
2157 if (op1->rank != 0 && op2->rank != 0)
2159 if (op1->rank == op2->rank)
2161 e->rank = op1->rank;
2162 if (e->shape == NULL)
2164 t = compare_shapes(op1, op2);
2165 if (t == FAILURE)
2166 e->shape = NULL;
2167 else
2168 e->shape = gfc_copy_shape (op1->shape, op1->rank);
2171 else
2173 gfc_error ("Inconsistent ranks for operator at %L and %L",
2174 &op1->where, &op2->where);
2175 t = FAILURE;
2177 /* Allow higher level expressions to work. */
2178 e->rank = 0;
2182 break;
2184 case INTRINSIC_NOT:
2185 case INTRINSIC_UPLUS:
2186 case INTRINSIC_UMINUS:
2187 case INTRINSIC_PARENTHESES:
2188 e->rank = op1->rank;
2190 if (e->shape == NULL)
2191 e->shape = gfc_copy_shape (op1->shape, op1->rank);
2193 /* Simply copy arrayness attribute */
2194 break;
2196 default:
2197 break;
2200 /* Attempt to simplify the expression. */
2201 if (t == SUCCESS)
2202 t = gfc_simplify_expr (e, 0);
2203 return t;
2205 bad_op:
2207 if (gfc_extend_expr (e) == SUCCESS)
2208 return SUCCESS;
2210 gfc_error (msg, &e->where);
2212 return FAILURE;
2216 /************** Array resolution subroutines **************/
2219 typedef enum
2220 { CMP_LT, CMP_EQ, CMP_GT, CMP_UNKNOWN }
2221 comparison;
2223 /* Compare two integer expressions. */
2225 static comparison
2226 compare_bound (gfc_expr * a, gfc_expr * b)
2228 int i;
2230 if (a == NULL || a->expr_type != EXPR_CONSTANT
2231 || b == NULL || b->expr_type != EXPR_CONSTANT)
2232 return CMP_UNKNOWN;
2234 if (a->ts.type != BT_INTEGER || b->ts.type != BT_INTEGER)
2235 gfc_internal_error ("compare_bound(): Bad expression");
2237 i = mpz_cmp (a->value.integer, b->value.integer);
2239 if (i < 0)
2240 return CMP_LT;
2241 if (i > 0)
2242 return CMP_GT;
2243 return CMP_EQ;
2247 /* Compare an integer expression with an integer. */
2249 static comparison
2250 compare_bound_int (gfc_expr * a, int b)
2252 int i;
2254 if (a == NULL || a->expr_type != EXPR_CONSTANT)
2255 return CMP_UNKNOWN;
2257 if (a->ts.type != BT_INTEGER)
2258 gfc_internal_error ("compare_bound_int(): Bad expression");
2260 i = mpz_cmp_si (a->value.integer, b);
2262 if (i < 0)
2263 return CMP_LT;
2264 if (i > 0)
2265 return CMP_GT;
2266 return CMP_EQ;
2270 /* Compare an integer expression with a mpz_t. */
2272 static comparison
2273 compare_bound_mpz_t (gfc_expr * a, mpz_t b)
2275 int i;
2277 if (a == NULL || a->expr_type != EXPR_CONSTANT)
2278 return CMP_UNKNOWN;
2280 if (a->ts.type != BT_INTEGER)
2281 gfc_internal_error ("compare_bound_int(): Bad expression");
2283 i = mpz_cmp (a->value.integer, b);
2285 if (i < 0)
2286 return CMP_LT;
2287 if (i > 0)
2288 return CMP_GT;
2289 return CMP_EQ;
2293 /* Compute the last value of a sequence given by a triplet.
2294 Return 0 if it wasn't able to compute the last value, or if the
2295 sequence if empty, and 1 otherwise. */
2297 static int
2298 compute_last_value_for_triplet (gfc_expr * start, gfc_expr * end,
2299 gfc_expr * stride, mpz_t last)
2301 mpz_t rem;
2303 if (start == NULL || start->expr_type != EXPR_CONSTANT
2304 || end == NULL || end->expr_type != EXPR_CONSTANT
2305 || (stride != NULL && stride->expr_type != EXPR_CONSTANT))
2306 return 0;
2308 if (start->ts.type != BT_INTEGER || end->ts.type != BT_INTEGER
2309 || (stride != NULL && stride->ts.type != BT_INTEGER))
2310 return 0;
2312 if (stride == NULL || compare_bound_int(stride, 1) == CMP_EQ)
2314 if (compare_bound (start, end) == CMP_GT)
2315 return 0;
2316 mpz_set (last, end->value.integer);
2317 return 1;
2320 if (compare_bound_int (stride, 0) == CMP_GT)
2322 /* Stride is positive */
2323 if (mpz_cmp (start->value.integer, end->value.integer) > 0)
2324 return 0;
2326 else
2328 /* Stride is negative */
2329 if (mpz_cmp (start->value.integer, end->value.integer) < 0)
2330 return 0;
2333 mpz_init (rem);
2334 mpz_sub (rem, end->value.integer, start->value.integer);
2335 mpz_tdiv_r (rem, rem, stride->value.integer);
2336 mpz_sub (last, end->value.integer, rem);
2337 mpz_clear (rem);
2339 return 1;
2343 /* Compare a single dimension of an array reference to the array
2344 specification. */
2346 static try
2347 check_dimension (int i, gfc_array_ref * ar, gfc_array_spec * as)
2349 mpz_t last_value;
2351 /* Given start, end and stride values, calculate the minimum and
2352 maximum referenced indexes. */
2354 switch (ar->type)
2356 case AR_FULL:
2357 break;
2359 case AR_ELEMENT:
2360 if (compare_bound (ar->start[i], as->lower[i]) == CMP_LT)
2361 goto bound;
2362 if (compare_bound (ar->start[i], as->upper[i]) == CMP_GT)
2363 goto bound;
2365 break;
2367 case AR_SECTION:
2368 if (compare_bound_int (ar->stride[i], 0) == CMP_EQ)
2370 gfc_error ("Illegal stride of zero at %L", &ar->c_where[i]);
2371 return FAILURE;
2374 #define AR_START (ar->start[i] ? ar->start[i] : as->lower[i])
2375 #define AR_END (ar->end[i] ? ar->end[i] : as->upper[i])
2377 if (compare_bound (AR_START, AR_END) == CMP_EQ
2378 && (compare_bound (AR_START, as->lower[i]) == CMP_LT
2379 || compare_bound (AR_START, as->upper[i]) == CMP_GT))
2380 goto bound;
2382 if (((compare_bound_int (ar->stride[i], 0) == CMP_GT
2383 || ar->stride[i] == NULL)
2384 && compare_bound (AR_START, AR_END) != CMP_GT)
2385 || (compare_bound_int (ar->stride[i], 0) == CMP_LT
2386 && compare_bound (AR_START, AR_END) != CMP_LT))
2388 if (compare_bound (AR_START, as->lower[i]) == CMP_LT)
2389 goto bound;
2390 if (compare_bound (AR_START, as->upper[i]) == CMP_GT)
2391 goto bound;
2394 mpz_init (last_value);
2395 if (compute_last_value_for_triplet (AR_START, AR_END, ar->stride[i],
2396 last_value))
2398 if (compare_bound_mpz_t (as->lower[i], last_value) == CMP_GT
2399 || compare_bound_mpz_t (as->upper[i], last_value) == CMP_LT)
2401 mpz_clear (last_value);
2402 goto bound;
2405 mpz_clear (last_value);
2407 #undef AR_START
2408 #undef AR_END
2410 break;
2412 default:
2413 gfc_internal_error ("check_dimension(): Bad array reference");
2416 return SUCCESS;
2418 bound:
2419 gfc_warning ("Array reference at %L is out of bounds", &ar->c_where[i]);
2420 return SUCCESS;
2424 /* Compare an array reference with an array specification. */
2426 static try
2427 compare_spec_to_ref (gfc_array_ref * ar)
2429 gfc_array_spec *as;
2430 int i;
2432 as = ar->as;
2433 i = as->rank - 1;
2434 /* TODO: Full array sections are only allowed as actual parameters. */
2435 if (as->type == AS_ASSUMED_SIZE
2436 && (/*ar->type == AR_FULL
2437 ||*/ (ar->type == AR_SECTION
2438 && ar->dimen_type[i] == DIMEN_RANGE && ar->end[i] == NULL)))
2440 gfc_error ("Rightmost upper bound of assumed size array section"
2441 " not specified at %L", &ar->where);
2442 return FAILURE;
2445 if (ar->type == AR_FULL)
2446 return SUCCESS;
2448 if (as->rank != ar->dimen)
2450 gfc_error ("Rank mismatch in array reference at %L (%d/%d)",
2451 &ar->where, ar->dimen, as->rank);
2452 return FAILURE;
2455 for (i = 0; i < as->rank; i++)
2456 if (check_dimension (i, ar, as) == FAILURE)
2457 return FAILURE;
2459 return SUCCESS;
2463 /* Resolve one part of an array index. */
2466 gfc_resolve_index (gfc_expr * index, int check_scalar)
2468 gfc_typespec ts;
2470 if (index == NULL)
2471 return SUCCESS;
2473 if (gfc_resolve_expr (index) == FAILURE)
2474 return FAILURE;
2476 if (check_scalar && index->rank != 0)
2478 gfc_error ("Array index at %L must be scalar", &index->where);
2479 return FAILURE;
2482 if (index->ts.type != BT_INTEGER && index->ts.type != BT_REAL)
2484 gfc_error ("Array index at %L must be of INTEGER type",
2485 &index->where);
2486 return FAILURE;
2489 if (index->ts.type == BT_REAL)
2490 if (gfc_notify_std (GFC_STD_LEGACY, "Extension: REAL array index at %L",
2491 &index->where) == FAILURE)
2492 return FAILURE;
2494 if (index->ts.kind != gfc_index_integer_kind
2495 || index->ts.type != BT_INTEGER)
2497 gfc_clear_ts (&ts);
2498 ts.type = BT_INTEGER;
2499 ts.kind = gfc_index_integer_kind;
2501 gfc_convert_type_warn (index, &ts, 2, 0);
2504 return SUCCESS;
2507 /* Resolve a dim argument to an intrinsic function. */
2510 gfc_resolve_dim_arg (gfc_expr *dim)
2512 if (dim == NULL)
2513 return SUCCESS;
2515 if (gfc_resolve_expr (dim) == FAILURE)
2516 return FAILURE;
2518 if (dim->rank != 0)
2520 gfc_error ("Argument dim at %L must be scalar", &dim->where);
2521 return FAILURE;
2524 if (dim->ts.type != BT_INTEGER)
2526 gfc_error ("Argument dim at %L must be of INTEGER type", &dim->where);
2527 return FAILURE;
2529 if (dim->ts.kind != gfc_index_integer_kind)
2531 gfc_typespec ts;
2533 ts.type = BT_INTEGER;
2534 ts.kind = gfc_index_integer_kind;
2536 gfc_convert_type_warn (dim, &ts, 2, 0);
2539 return SUCCESS;
2542 /* Given an expression that contains array references, update those array
2543 references to point to the right array specifications. While this is
2544 filled in during matching, this information is difficult to save and load
2545 in a module, so we take care of it here.
2547 The idea here is that the original array reference comes from the
2548 base symbol. We traverse the list of reference structures, setting
2549 the stored reference to references. Component references can
2550 provide an additional array specification. */
2552 static void
2553 find_array_spec (gfc_expr * e)
2555 gfc_array_spec *as;
2556 gfc_component *c;
2557 gfc_symbol *derived;
2558 gfc_ref *ref;
2560 as = e->symtree->n.sym->as;
2561 derived = NULL;
2563 for (ref = e->ref; ref; ref = ref->next)
2564 switch (ref->type)
2566 case REF_ARRAY:
2567 if (as == NULL)
2568 gfc_internal_error ("find_array_spec(): Missing spec");
2570 ref->u.ar.as = as;
2571 as = NULL;
2572 break;
2574 case REF_COMPONENT:
2575 if (derived == NULL)
2576 derived = e->symtree->n.sym->ts.derived;
2578 c = derived->components;
2580 for (; c; c = c->next)
2581 if (c == ref->u.c.component)
2583 /* Track the sequence of component references. */
2584 if (c->ts.type == BT_DERIVED)
2585 derived = c->ts.derived;
2586 break;
2589 if (c == NULL)
2590 gfc_internal_error ("find_array_spec(): Component not found");
2592 if (c->dimension)
2594 if (as != NULL)
2595 gfc_internal_error ("find_array_spec(): unused as(1)");
2596 as = c->as;
2599 break;
2601 case REF_SUBSTRING:
2602 break;
2605 if (as != NULL)
2606 gfc_internal_error ("find_array_spec(): unused as(2)");
2610 /* Resolve an array reference. */
2612 static try
2613 resolve_array_ref (gfc_array_ref * ar)
2615 int i, check_scalar;
2616 gfc_expr *e;
2618 for (i = 0; i < ar->dimen; i++)
2620 check_scalar = ar->dimen_type[i] == DIMEN_RANGE;
2622 if (gfc_resolve_index (ar->start[i], check_scalar) == FAILURE)
2623 return FAILURE;
2624 if (gfc_resolve_index (ar->end[i], check_scalar) == FAILURE)
2625 return FAILURE;
2626 if (gfc_resolve_index (ar->stride[i], check_scalar) == FAILURE)
2627 return FAILURE;
2629 e = ar->start[i];
2631 if (ar->dimen_type[i] == DIMEN_UNKNOWN)
2632 switch (e->rank)
2634 case 0:
2635 ar->dimen_type[i] = DIMEN_ELEMENT;
2636 break;
2638 case 1:
2639 ar->dimen_type[i] = DIMEN_VECTOR;
2640 if (e->expr_type == EXPR_VARIABLE
2641 && e->symtree->n.sym->ts.type == BT_DERIVED)
2642 ar->start[i] = gfc_get_parentheses (e);
2643 break;
2645 default:
2646 gfc_error ("Array index at %L is an array of rank %d",
2647 &ar->c_where[i], e->rank);
2648 return FAILURE;
2652 /* If the reference type is unknown, figure out what kind it is. */
2654 if (ar->type == AR_UNKNOWN)
2656 ar->type = AR_ELEMENT;
2657 for (i = 0; i < ar->dimen; i++)
2658 if (ar->dimen_type[i] == DIMEN_RANGE
2659 || ar->dimen_type[i] == DIMEN_VECTOR)
2661 ar->type = AR_SECTION;
2662 break;
2666 if (!ar->as->cray_pointee && compare_spec_to_ref (ar) == FAILURE)
2667 return FAILURE;
2669 return SUCCESS;
2673 static try
2674 resolve_substring (gfc_ref * ref)
2677 if (ref->u.ss.start != NULL)
2679 if (gfc_resolve_expr (ref->u.ss.start) == FAILURE)
2680 return FAILURE;
2682 if (ref->u.ss.start->ts.type != BT_INTEGER)
2684 gfc_error ("Substring start index at %L must be of type INTEGER",
2685 &ref->u.ss.start->where);
2686 return FAILURE;
2689 if (ref->u.ss.start->rank != 0)
2691 gfc_error ("Substring start index at %L must be scalar",
2692 &ref->u.ss.start->where);
2693 return FAILURE;
2696 if (compare_bound_int (ref->u.ss.start, 1) == CMP_LT
2697 && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
2698 || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
2700 gfc_error ("Substring start index at %L is less than one",
2701 &ref->u.ss.start->where);
2702 return FAILURE;
2706 if (ref->u.ss.end != NULL)
2708 if (gfc_resolve_expr (ref->u.ss.end) == FAILURE)
2709 return FAILURE;
2711 if (ref->u.ss.end->ts.type != BT_INTEGER)
2713 gfc_error ("Substring end index at %L must be of type INTEGER",
2714 &ref->u.ss.end->where);
2715 return FAILURE;
2718 if (ref->u.ss.end->rank != 0)
2720 gfc_error ("Substring end index at %L must be scalar",
2721 &ref->u.ss.end->where);
2722 return FAILURE;
2725 if (ref->u.ss.length != NULL
2726 && compare_bound (ref->u.ss.end, ref->u.ss.length->length) == CMP_GT
2727 && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
2728 || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
2730 gfc_error ("Substring end index at %L exceeds the string length",
2731 &ref->u.ss.start->where);
2732 return FAILURE;
2736 return SUCCESS;
2740 /* Resolve subtype references. */
2742 static try
2743 resolve_ref (gfc_expr * expr)
2745 int current_part_dimension, n_components, seen_part_dimension;
2746 gfc_ref *ref;
2748 for (ref = expr->ref; ref; ref = ref->next)
2749 if (ref->type == REF_ARRAY && ref->u.ar.as == NULL)
2751 find_array_spec (expr);
2752 break;
2755 for (ref = expr->ref; ref; ref = ref->next)
2756 switch (ref->type)
2758 case REF_ARRAY:
2759 if (resolve_array_ref (&ref->u.ar) == FAILURE)
2760 return FAILURE;
2761 break;
2763 case REF_COMPONENT:
2764 break;
2766 case REF_SUBSTRING:
2767 resolve_substring (ref);
2768 break;
2771 /* Check constraints on part references. */
2773 current_part_dimension = 0;
2774 seen_part_dimension = 0;
2775 n_components = 0;
2777 for (ref = expr->ref; ref; ref = ref->next)
2779 switch (ref->type)
2781 case REF_ARRAY:
2782 switch (ref->u.ar.type)
2784 case AR_FULL:
2785 case AR_SECTION:
2786 current_part_dimension = 1;
2787 break;
2789 case AR_ELEMENT:
2790 current_part_dimension = 0;
2791 break;
2793 case AR_UNKNOWN:
2794 gfc_internal_error ("resolve_ref(): Bad array reference");
2797 break;
2799 case REF_COMPONENT:
2800 if ((current_part_dimension || seen_part_dimension)
2801 && ref->u.c.component->pointer)
2803 gfc_error
2804 ("Component to the right of a part reference with nonzero "
2805 "rank must not have the POINTER attribute at %L",
2806 &expr->where);
2807 return FAILURE;
2810 n_components++;
2811 break;
2813 case REF_SUBSTRING:
2814 break;
2817 if (((ref->type == REF_COMPONENT && n_components > 1)
2818 || ref->next == NULL)
2819 && current_part_dimension
2820 && seen_part_dimension)
2823 gfc_error ("Two or more part references with nonzero rank must "
2824 "not be specified at %L", &expr->where);
2825 return FAILURE;
2828 if (ref->type == REF_COMPONENT)
2830 if (current_part_dimension)
2831 seen_part_dimension = 1;
2833 /* reset to make sure */
2834 current_part_dimension = 0;
2838 return SUCCESS;
2842 /* Given an expression, determine its shape. This is easier than it sounds.
2843 Leaves the shape array NULL if it is not possible to determine the shape. */
2845 static void
2846 expression_shape (gfc_expr * e)
2848 mpz_t array[GFC_MAX_DIMENSIONS];
2849 int i;
2851 if (e->rank == 0 || e->shape != NULL)
2852 return;
2854 for (i = 0; i < e->rank; i++)
2855 if (gfc_array_dimen_size (e, i, &array[i]) == FAILURE)
2856 goto fail;
2858 e->shape = gfc_get_shape (e->rank);
2860 memcpy (e->shape, array, e->rank * sizeof (mpz_t));
2862 return;
2864 fail:
2865 for (i--; i >= 0; i--)
2866 mpz_clear (array[i]);
2870 /* Given a variable expression node, compute the rank of the expression by
2871 examining the base symbol and any reference structures it may have. */
2873 static void
2874 expression_rank (gfc_expr * e)
2876 gfc_ref *ref;
2877 int i, rank;
2879 if (e->ref == NULL)
2881 if (e->expr_type == EXPR_ARRAY)
2882 goto done;
2883 /* Constructors can have a rank different from one via RESHAPE(). */
2885 if (e->symtree == NULL)
2887 e->rank = 0;
2888 goto done;
2891 e->rank = (e->symtree->n.sym->as == NULL)
2892 ? 0 : e->symtree->n.sym->as->rank;
2893 goto done;
2896 rank = 0;
2898 for (ref = e->ref; ref; ref = ref->next)
2900 if (ref->type != REF_ARRAY)
2901 continue;
2903 if (ref->u.ar.type == AR_FULL)
2905 rank = ref->u.ar.as->rank;
2906 break;
2909 if (ref->u.ar.type == AR_SECTION)
2911 /* Figure out the rank of the section. */
2912 if (rank != 0)
2913 gfc_internal_error ("expression_rank(): Two array specs");
2915 for (i = 0; i < ref->u.ar.dimen; i++)
2916 if (ref->u.ar.dimen_type[i] == DIMEN_RANGE
2917 || ref->u.ar.dimen_type[i] == DIMEN_VECTOR)
2918 rank++;
2920 break;
2924 e->rank = rank;
2926 done:
2927 expression_shape (e);
2931 /* Resolve a variable expression. */
2933 static try
2934 resolve_variable (gfc_expr * e)
2936 gfc_symbol *sym;
2937 try t;
2939 t = SUCCESS;
2941 if (e->symtree == NULL)
2942 return FAILURE;
2944 if (e->ref && resolve_ref (e) == FAILURE)
2945 return FAILURE;
2947 sym = e->symtree->n.sym;
2948 if (sym->attr.flavor == FL_PROCEDURE && !sym->attr.function)
2950 e->ts.type = BT_PROCEDURE;
2951 return SUCCESS;
2954 if (sym->ts.type != BT_UNKNOWN)
2955 gfc_variable_attr (e, &e->ts);
2956 else
2958 /* Must be a simple variable reference. */
2959 if (gfc_set_default_type (sym, 1, NULL) == FAILURE)
2960 return FAILURE;
2961 e->ts = sym->ts;
2964 if (check_assumed_size_reference (sym, e))
2965 return FAILURE;
2967 /* Deal with forward references to entries during resolve_code, to
2968 satisfy, at least partially, 12.5.2.5. */
2969 if (gfc_current_ns->entries
2970 && current_entry_id == sym->entry_id
2971 && cs_base
2972 && cs_base->current
2973 && cs_base->current->op != EXEC_ENTRY)
2975 gfc_entry_list *entry;
2976 gfc_formal_arglist *formal;
2977 int n;
2978 bool seen;
2980 /* If the symbol is a dummy... */
2981 if (sym->attr.dummy)
2983 entry = gfc_current_ns->entries;
2984 seen = false;
2986 /* ...test if the symbol is a parameter of previous entries. */
2987 for (; entry && entry->id <= current_entry_id; entry = entry->next)
2988 for (formal = entry->sym->formal; formal; formal = formal->next)
2990 if (formal->sym && sym->name == formal->sym->name)
2991 seen = true;
2994 /* If it has not been seen as a dummy, this is an error. */
2995 if (!seen)
2997 if (specification_expr)
2998 gfc_error ("Variable '%s',used in a specification expression, "
2999 "is referenced at %L before the ENTRY statement "
3000 "in which it is a parameter",
3001 sym->name, &cs_base->current->loc);
3002 else
3003 gfc_error ("Variable '%s' is used at %L before the ENTRY "
3004 "statement in which it is a parameter",
3005 sym->name, &cs_base->current->loc);
3006 t = FAILURE;
3010 /* Now do the same check on the specification expressions. */
3011 specification_expr = 1;
3012 if (sym->ts.type == BT_CHARACTER
3013 && gfc_resolve_expr (sym->ts.cl->length) == FAILURE)
3014 t = FAILURE;
3016 if (sym->as)
3017 for (n = 0; n < sym->as->rank; n++)
3019 specification_expr = 1;
3020 if (gfc_resolve_expr (sym->as->lower[n]) == FAILURE)
3021 t = FAILURE;
3022 specification_expr = 1;
3023 if (gfc_resolve_expr (sym->as->upper[n]) == FAILURE)
3024 t = FAILURE;
3026 specification_expr = 0;
3028 if (t == SUCCESS)
3029 /* Update the symbol's entry level. */
3030 sym->entry_id = current_entry_id + 1;
3033 return t;
3037 /* Resolve an expression. That is, make sure that types of operands agree
3038 with their operators, intrinsic operators are converted to function calls
3039 for overloaded types and unresolved function references are resolved. */
3042 gfc_resolve_expr (gfc_expr * e)
3044 try t;
3046 if (e == NULL)
3047 return SUCCESS;
3049 switch (e->expr_type)
3051 case EXPR_OP:
3052 t = resolve_operator (e);
3053 break;
3055 case EXPR_FUNCTION:
3056 t = resolve_function (e);
3057 break;
3059 case EXPR_VARIABLE:
3060 t = resolve_variable (e);
3061 if (t == SUCCESS)
3062 expression_rank (e);
3063 break;
3065 case EXPR_SUBSTRING:
3066 t = resolve_ref (e);
3067 break;
3069 case EXPR_CONSTANT:
3070 case EXPR_NULL:
3071 t = SUCCESS;
3072 break;
3074 case EXPR_ARRAY:
3075 t = FAILURE;
3076 if (resolve_ref (e) == FAILURE)
3077 break;
3079 t = gfc_resolve_array_constructor (e);
3080 /* Also try to expand a constructor. */
3081 if (t == SUCCESS)
3083 expression_rank (e);
3084 gfc_expand_constructor (e);
3087 /* This provides the opportunity for the length of constructors with character
3088 valued function elements to propogate the string length to the expression. */
3089 if (e->ts.type == BT_CHARACTER)
3090 gfc_resolve_character_array_constructor (e);
3092 break;
3094 case EXPR_STRUCTURE:
3095 t = resolve_ref (e);
3096 if (t == FAILURE)
3097 break;
3099 t = resolve_structure_cons (e);
3100 if (t == FAILURE)
3101 break;
3103 t = gfc_simplify_expr (e, 0);
3104 break;
3106 default:
3107 gfc_internal_error ("gfc_resolve_expr(): Bad expression type");
3110 return t;
3114 /* Resolve an expression from an iterator. They must be scalar and have
3115 INTEGER or (optionally) REAL type. */
3117 static try
3118 gfc_resolve_iterator_expr (gfc_expr * expr, bool real_ok,
3119 const char * name_msgid)
3121 if (gfc_resolve_expr (expr) == FAILURE)
3122 return FAILURE;
3124 if (expr->rank != 0)
3126 gfc_error ("%s at %L must be a scalar", _(name_msgid), &expr->where);
3127 return FAILURE;
3130 if (!(expr->ts.type == BT_INTEGER
3131 || (expr->ts.type == BT_REAL && real_ok)))
3133 if (real_ok)
3134 gfc_error ("%s at %L must be INTEGER or REAL", _(name_msgid),
3135 &expr->where);
3136 else
3137 gfc_error ("%s at %L must be INTEGER", _(name_msgid), &expr->where);
3138 return FAILURE;
3140 return SUCCESS;
3144 /* Resolve the expressions in an iterator structure. If REAL_OK is
3145 false allow only INTEGER type iterators, otherwise allow REAL types. */
3148 gfc_resolve_iterator (gfc_iterator * iter, bool real_ok)
3151 if (iter->var->ts.type == BT_REAL)
3152 gfc_notify_std (GFC_STD_F95_DEL,
3153 "Obsolete: REAL DO loop iterator at %L",
3154 &iter->var->where);
3156 if (gfc_resolve_iterator_expr (iter->var, real_ok, "Loop variable")
3157 == FAILURE)
3158 return FAILURE;
3160 if (gfc_pure (NULL) && gfc_impure_variable (iter->var->symtree->n.sym))
3162 gfc_error ("Cannot assign to loop variable in PURE procedure at %L",
3163 &iter->var->where);
3164 return FAILURE;
3167 if (gfc_resolve_iterator_expr (iter->start, real_ok,
3168 "Start expression in DO loop") == FAILURE)
3169 return FAILURE;
3171 if (gfc_resolve_iterator_expr (iter->end, real_ok,
3172 "End expression in DO loop") == FAILURE)
3173 return FAILURE;
3175 if (gfc_resolve_iterator_expr (iter->step, real_ok,
3176 "Step expression in DO loop") == FAILURE)
3177 return FAILURE;
3179 if (iter->step->expr_type == EXPR_CONSTANT)
3181 if ((iter->step->ts.type == BT_INTEGER
3182 && mpz_cmp_ui (iter->step->value.integer, 0) == 0)
3183 || (iter->step->ts.type == BT_REAL
3184 && mpfr_sgn (iter->step->value.real) == 0))
3186 gfc_error ("Step expression in DO loop at %L cannot be zero",
3187 &iter->step->where);
3188 return FAILURE;
3192 /* Convert start, end, and step to the same type as var. */
3193 if (iter->start->ts.kind != iter->var->ts.kind
3194 || iter->start->ts.type != iter->var->ts.type)
3195 gfc_convert_type (iter->start, &iter->var->ts, 2);
3197 if (iter->end->ts.kind != iter->var->ts.kind
3198 || iter->end->ts.type != iter->var->ts.type)
3199 gfc_convert_type (iter->end, &iter->var->ts, 2);
3201 if (iter->step->ts.kind != iter->var->ts.kind
3202 || iter->step->ts.type != iter->var->ts.type)
3203 gfc_convert_type (iter->step, &iter->var->ts, 2);
3205 return SUCCESS;
3209 /* Resolve a list of FORALL iterators. The FORALL index-name is constrained
3210 to be a scalar INTEGER variable. The subscripts and stride are scalar
3211 INTEGERs, and if stride is a constant it must be nonzero. */
3213 static void
3214 resolve_forall_iterators (gfc_forall_iterator * iter)
3217 while (iter)
3219 if (gfc_resolve_expr (iter->var) == SUCCESS
3220 && (iter->var->ts.type != BT_INTEGER || iter->var->rank != 0))
3221 gfc_error ("FORALL index-name at %L must be a scalar INTEGER",
3222 &iter->var->where);
3224 if (gfc_resolve_expr (iter->start) == SUCCESS
3225 && (iter->start->ts.type != BT_INTEGER || iter->start->rank != 0))
3226 gfc_error ("FORALL start expression at %L must be a scalar INTEGER",
3227 &iter->start->where);
3228 if (iter->var->ts.kind != iter->start->ts.kind)
3229 gfc_convert_type (iter->start, &iter->var->ts, 2);
3231 if (gfc_resolve_expr (iter->end) == SUCCESS
3232 && (iter->end->ts.type != BT_INTEGER || iter->end->rank != 0))
3233 gfc_error ("FORALL end expression at %L must be a scalar INTEGER",
3234 &iter->end->where);
3235 if (iter->var->ts.kind != iter->end->ts.kind)
3236 gfc_convert_type (iter->end, &iter->var->ts, 2);
3238 if (gfc_resolve_expr (iter->stride) == SUCCESS)
3240 if (iter->stride->ts.type != BT_INTEGER || iter->stride->rank != 0)
3241 gfc_error ("FORALL stride expression at %L must be a scalar %s",
3242 &iter->stride->where, "INTEGER");
3244 if (iter->stride->expr_type == EXPR_CONSTANT
3245 && mpz_cmp_ui(iter->stride->value.integer, 0) == 0)
3246 gfc_error ("FORALL stride expression at %L cannot be zero",
3247 &iter->stride->where);
3249 if (iter->var->ts.kind != iter->stride->ts.kind)
3250 gfc_convert_type (iter->stride, &iter->var->ts, 2);
3252 iter = iter->next;
3257 /* Given a pointer to a symbol that is a derived type, see if any components
3258 have the POINTER attribute. The search is recursive if necessary.
3259 Returns zero if no pointer components are found, nonzero otherwise. */
3261 static int
3262 derived_pointer (gfc_symbol * sym)
3264 gfc_component *c;
3266 for (c = sym->components; c; c = c->next)
3268 if (c->pointer)
3269 return 1;
3271 if (c->ts.type == BT_DERIVED && derived_pointer (c->ts.derived))
3272 return 1;
3275 return 0;
3279 /* Given a pointer to a symbol that is a derived type, see if it's
3280 inaccessible, i.e. if it's defined in another module and the components are
3281 PRIVATE. The search is recursive if necessary. Returns zero if no
3282 inaccessible components are found, nonzero otherwise. */
3284 static int
3285 derived_inaccessible (gfc_symbol *sym)
3287 gfc_component *c;
3289 if (sym->attr.use_assoc && sym->component_access == ACCESS_PRIVATE)
3290 return 1;
3292 for (c = sym->components; c; c = c->next)
3294 if (c->ts.type == BT_DERIVED && derived_inaccessible (c->ts.derived))
3295 return 1;
3298 return 0;
3302 /* Resolve the argument of a deallocate expression. The expression must be
3303 a pointer or a full array. */
3305 static try
3306 resolve_deallocate_expr (gfc_expr * e)
3308 symbol_attribute attr;
3309 int allocatable;
3310 gfc_ref *ref;
3312 if (gfc_resolve_expr (e) == FAILURE)
3313 return FAILURE;
3315 attr = gfc_expr_attr (e);
3316 if (attr.pointer)
3317 return SUCCESS;
3319 if (e->expr_type != EXPR_VARIABLE)
3320 goto bad;
3322 allocatable = e->symtree->n.sym->attr.allocatable;
3323 for (ref = e->ref; ref; ref = ref->next)
3324 switch (ref->type)
3326 case REF_ARRAY:
3327 if (ref->u.ar.type != AR_FULL)
3328 allocatable = 0;
3329 break;
3331 case REF_COMPONENT:
3332 allocatable = (ref->u.c.component->as != NULL
3333 && ref->u.c.component->as->type == AS_DEFERRED);
3334 break;
3336 case REF_SUBSTRING:
3337 allocatable = 0;
3338 break;
3341 if (allocatable == 0)
3343 bad:
3344 gfc_error ("Expression in DEALLOCATE statement at %L must be "
3345 "ALLOCATABLE or a POINTER", &e->where);
3348 if (e->symtree->n.sym->attr.intent == INTENT_IN)
3350 gfc_error ("Can't deallocate INTENT(IN) variable '%s' at %L",
3351 e->symtree->n.sym->name, &e->where);
3352 return FAILURE;
3355 return SUCCESS;
3358 /* Returns true if the expression e contains a reference the symbol sym. */
3359 static bool
3360 find_sym_in_expr (gfc_symbol *sym, gfc_expr *e)
3362 gfc_actual_arglist *arg;
3363 gfc_ref *ref;
3364 int i;
3365 bool rv = false;
3367 if (e == NULL)
3368 return rv;
3370 switch (e->expr_type)
3372 case EXPR_FUNCTION:
3373 for (arg = e->value.function.actual; arg; arg = arg->next)
3374 rv = rv || find_sym_in_expr (sym, arg->expr);
3375 break;
3377 /* If the variable is not the same as the dependent, 'sym', and
3378 it is not marked as being declared and it is in the same
3379 namespace as 'sym', add it to the local declarations. */
3380 case EXPR_VARIABLE:
3381 if (sym == e->symtree->n.sym)
3382 return true;
3383 break;
3385 case EXPR_OP:
3386 rv = rv || find_sym_in_expr (sym, e->value.op.op1);
3387 rv = rv || find_sym_in_expr (sym, e->value.op.op2);
3388 break;
3390 default:
3391 break;
3394 if (e->ref)
3396 for (ref = e->ref; ref; ref = ref->next)
3398 switch (ref->type)
3400 case REF_ARRAY:
3401 for (i = 0; i < ref->u.ar.dimen; i++)
3403 rv = rv || find_sym_in_expr (sym, ref->u.ar.start[i]);
3404 rv = rv || find_sym_in_expr (sym, ref->u.ar.end[i]);
3405 rv = rv || find_sym_in_expr (sym, ref->u.ar.stride[i]);
3407 break;
3409 case REF_SUBSTRING:
3410 rv = rv || find_sym_in_expr (sym, ref->u.ss.start);
3411 rv = rv || find_sym_in_expr (sym, ref->u.ss.end);
3412 break;
3414 case REF_COMPONENT:
3415 if (ref->u.c.component->ts.type == BT_CHARACTER
3416 && ref->u.c.component->ts.cl->length->expr_type
3417 != EXPR_CONSTANT)
3418 rv = rv || find_sym_in_expr (sym, ref->u.c.component->ts.cl->length);
3420 if (ref->u.c.component->as)
3421 for (i = 0; i < ref->u.c.component->as->rank; i++)
3423 rv = rv || find_sym_in_expr (sym, ref->u.c.component->as->lower[i]);
3424 rv = rv || find_sym_in_expr (sym, ref->u.c.component->as->upper[i]);
3426 break;
3430 return rv;
3434 /* Given the expression node e for an allocatable/pointer of derived type to be
3435 allocated, get the expression node to be initialized afterwards (needed for
3436 derived types with default initializers, and derived types with allocatable
3437 components that need nullification.) */
3439 static gfc_expr *
3440 expr_to_initialize (gfc_expr * e)
3442 gfc_expr *result;
3443 gfc_ref *ref;
3444 int i;
3446 result = gfc_copy_expr (e);
3448 /* Change the last array reference from AR_ELEMENT to AR_FULL. */
3449 for (ref = result->ref; ref; ref = ref->next)
3450 if (ref->type == REF_ARRAY && ref->next == NULL)
3452 ref->u.ar.type = AR_FULL;
3454 for (i = 0; i < ref->u.ar.dimen; i++)
3455 ref->u.ar.start[i] = ref->u.ar.end[i] = ref->u.ar.stride[i] = NULL;
3457 result->rank = ref->u.ar.dimen;
3458 break;
3461 return result;
3465 /* Resolve the expression in an ALLOCATE statement, doing the additional
3466 checks to see whether the expression is OK or not. The expression must
3467 have a trailing array reference that gives the size of the array. */
3469 static try
3470 resolve_allocate_expr (gfc_expr * e, gfc_code * code)
3472 int i, pointer, allocatable, dimension;
3473 symbol_attribute attr;
3474 gfc_ref *ref, *ref2;
3475 gfc_array_ref *ar;
3476 gfc_code *init_st;
3477 gfc_expr *init_e;
3478 gfc_symbol *sym;
3479 gfc_alloc *a;
3481 if (gfc_resolve_expr (e) == FAILURE)
3482 return FAILURE;
3484 if (code->expr && code->expr->expr_type == EXPR_VARIABLE)
3485 sym = code->expr->symtree->n.sym;
3486 else
3487 sym = NULL;
3489 /* Make sure the expression is allocatable or a pointer. If it is
3490 pointer, the next-to-last reference must be a pointer. */
3492 ref2 = NULL;
3494 if (e->expr_type != EXPR_VARIABLE)
3496 allocatable = 0;
3498 attr = gfc_expr_attr (e);
3499 pointer = attr.pointer;
3500 dimension = attr.dimension;
3503 else
3505 allocatable = e->symtree->n.sym->attr.allocatable;
3506 pointer = e->symtree->n.sym->attr.pointer;
3507 dimension = e->symtree->n.sym->attr.dimension;
3509 if (sym == e->symtree->n.sym && sym->ts.type != BT_DERIVED)
3511 gfc_error ("The STAT variable '%s' in an ALLOCATE statement must "
3512 "not be allocated in the same statement at %L",
3513 sym->name, &e->where);
3514 return FAILURE;
3517 for (ref = e->ref; ref; ref2 = ref, ref = ref->next)
3518 switch (ref->type)
3520 case REF_ARRAY:
3521 if (ref->next != NULL)
3522 pointer = 0;
3523 break;
3525 case REF_COMPONENT:
3526 allocatable = (ref->u.c.component->as != NULL
3527 && ref->u.c.component->as->type == AS_DEFERRED);
3529 pointer = ref->u.c.component->pointer;
3530 dimension = ref->u.c.component->dimension;
3531 break;
3533 case REF_SUBSTRING:
3534 allocatable = 0;
3535 pointer = 0;
3536 break;
3540 if (allocatable == 0 && pointer == 0)
3542 gfc_error ("Expression in ALLOCATE statement at %L must be "
3543 "ALLOCATABLE or a POINTER", &e->where);
3544 return FAILURE;
3547 if (e->symtree->n.sym->attr.intent == INTENT_IN)
3549 gfc_error ("Can't allocate INTENT(IN) variable '%s' at %L",
3550 e->symtree->n.sym->name, &e->where);
3551 return FAILURE;
3554 /* Add default initializer for those derived types that need them. */
3555 if (e->ts.type == BT_DERIVED && (init_e = gfc_default_initializer (&e->ts)))
3557 init_st = gfc_get_code ();
3558 init_st->loc = code->loc;
3559 init_st->op = EXEC_ASSIGN;
3560 init_st->expr = expr_to_initialize (e);
3561 init_st->expr2 = init_e;
3562 init_st->next = code->next;
3563 code->next = init_st;
3566 if (pointer && dimension == 0)
3567 return SUCCESS;
3569 /* Make sure the next-to-last reference node is an array specification. */
3571 if (ref2 == NULL || ref2->type != REF_ARRAY || ref2->u.ar.type == AR_FULL)
3573 gfc_error ("Array specification required in ALLOCATE statement "
3574 "at %L", &e->where);
3575 return FAILURE;
3578 /* Make sure that the array section reference makes sense in the
3579 context of an ALLOCATE specification. */
3581 ar = &ref2->u.ar;
3583 for (i = 0; i < ar->dimen; i++)
3585 if (ref2->u.ar.type == AR_ELEMENT)
3586 goto check_symbols;
3588 switch (ar->dimen_type[i])
3590 case DIMEN_ELEMENT:
3591 break;
3593 case DIMEN_RANGE:
3594 if (ar->start[i] != NULL
3595 && ar->end[i] != NULL
3596 && ar->stride[i] == NULL)
3597 break;
3599 /* Fall Through... */
3601 case DIMEN_UNKNOWN:
3602 case DIMEN_VECTOR:
3603 gfc_error ("Bad array specification in ALLOCATE statement at %L",
3604 &e->where);
3605 return FAILURE;
3608 check_symbols:
3610 for (a = code->ext.alloc_list; a; a = a->next)
3612 sym = a->expr->symtree->n.sym;
3614 /* TODO - check derived type components. */
3615 if (sym->ts.type == BT_DERIVED)
3616 continue;
3618 if ((ar->start[i] != NULL && find_sym_in_expr (sym, ar->start[i]))
3619 || (ar->end[i] != NULL && find_sym_in_expr (sym, ar->end[i])))
3621 gfc_error ("'%s' must not appear an the array specification at "
3622 "%L in the same ALLOCATE statement where it is "
3623 "itself allocated", sym->name, &ar->where);
3624 return FAILURE;
3629 return SUCCESS;
3633 /************ SELECT CASE resolution subroutines ************/
3635 /* Callback function for our mergesort variant. Determines interval
3636 overlaps for CASEs. Return <0 if op1 < op2, 0 for overlap, >0 for
3637 op1 > op2. Assumes we're not dealing with the default case.
3638 We have op1 = (:L), (K:L) or (K:) and op2 = (:N), (M:N) or (M:).
3639 There are nine situations to check. */
3641 static int
3642 compare_cases (const gfc_case * op1, const gfc_case * op2)
3644 int retval;
3646 if (op1->low == NULL) /* op1 = (:L) */
3648 /* op2 = (:N), so overlap. */
3649 retval = 0;
3650 /* op2 = (M:) or (M:N), L < M */
3651 if (op2->low != NULL
3652 && gfc_compare_expr (op1->high, op2->low) < 0)
3653 retval = -1;
3655 else if (op1->high == NULL) /* op1 = (K:) */
3657 /* op2 = (M:), so overlap. */
3658 retval = 0;
3659 /* op2 = (:N) or (M:N), K > N */
3660 if (op2->high != NULL
3661 && gfc_compare_expr (op1->low, op2->high) > 0)
3662 retval = 1;
3664 else /* op1 = (K:L) */
3666 if (op2->low == NULL) /* op2 = (:N), K > N */
3667 retval = (gfc_compare_expr (op1->low, op2->high) > 0) ? 1 : 0;
3668 else if (op2->high == NULL) /* op2 = (M:), L < M */
3669 retval = (gfc_compare_expr (op1->high, op2->low) < 0) ? -1 : 0;
3670 else /* op2 = (M:N) */
3672 retval = 0;
3673 /* L < M */
3674 if (gfc_compare_expr (op1->high, op2->low) < 0)
3675 retval = -1;
3676 /* K > N */
3677 else if (gfc_compare_expr (op1->low, op2->high) > 0)
3678 retval = 1;
3682 return retval;
3686 /* Merge-sort a double linked case list, detecting overlap in the
3687 process. LIST is the head of the double linked case list before it
3688 is sorted. Returns the head of the sorted list if we don't see any
3689 overlap, or NULL otherwise. */
3691 static gfc_case *
3692 check_case_overlap (gfc_case * list)
3694 gfc_case *p, *q, *e, *tail;
3695 int insize, nmerges, psize, qsize, cmp, overlap_seen;
3697 /* If the passed list was empty, return immediately. */
3698 if (!list)
3699 return NULL;
3701 overlap_seen = 0;
3702 insize = 1;
3704 /* Loop unconditionally. The only exit from this loop is a return
3705 statement, when we've finished sorting the case list. */
3706 for (;;)
3708 p = list;
3709 list = NULL;
3710 tail = NULL;
3712 /* Count the number of merges we do in this pass. */
3713 nmerges = 0;
3715 /* Loop while there exists a merge to be done. */
3716 while (p)
3718 int i;
3720 /* Count this merge. */
3721 nmerges++;
3723 /* Cut the list in two pieces by stepping INSIZE places
3724 forward in the list, starting from P. */
3725 psize = 0;
3726 q = p;
3727 for (i = 0; i < insize; i++)
3729 psize++;
3730 q = q->right;
3731 if (!q)
3732 break;
3734 qsize = insize;
3736 /* Now we have two lists. Merge them! */
3737 while (psize > 0 || (qsize > 0 && q != NULL))
3740 /* See from which the next case to merge comes from. */
3741 if (psize == 0)
3743 /* P is empty so the next case must come from Q. */
3744 e = q;
3745 q = q->right;
3746 qsize--;
3748 else if (qsize == 0 || q == NULL)
3750 /* Q is empty. */
3751 e = p;
3752 p = p->right;
3753 psize--;
3755 else
3757 cmp = compare_cases (p, q);
3758 if (cmp < 0)
3760 /* The whole case range for P is less than the
3761 one for Q. */
3762 e = p;
3763 p = p->right;
3764 psize--;
3766 else if (cmp > 0)
3768 /* The whole case range for Q is greater than
3769 the case range for P. */
3770 e = q;
3771 q = q->right;
3772 qsize--;
3774 else
3776 /* The cases overlap, or they are the same
3777 element in the list. Either way, we must
3778 issue an error and get the next case from P. */
3779 /* FIXME: Sort P and Q by line number. */
3780 gfc_error ("CASE label at %L overlaps with CASE "
3781 "label at %L", &p->where, &q->where);
3782 overlap_seen = 1;
3783 e = p;
3784 p = p->right;
3785 psize--;
3789 /* Add the next element to the merged list. */
3790 if (tail)
3791 tail->right = e;
3792 else
3793 list = e;
3794 e->left = tail;
3795 tail = e;
3798 /* P has now stepped INSIZE places along, and so has Q. So
3799 they're the same. */
3800 p = q;
3802 tail->right = NULL;
3804 /* If we have done only one merge or none at all, we've
3805 finished sorting the cases. */
3806 if (nmerges <= 1)
3808 if (!overlap_seen)
3809 return list;
3810 else
3811 return NULL;
3814 /* Otherwise repeat, merging lists twice the size. */
3815 insize *= 2;
3820 /* Check to see if an expression is suitable for use in a CASE statement.
3821 Makes sure that all case expressions are scalar constants of the same
3822 type. Return FAILURE if anything is wrong. */
3824 static try
3825 validate_case_label_expr (gfc_expr * e, gfc_expr * case_expr)
3827 if (e == NULL) return SUCCESS;
3829 if (e->ts.type != case_expr->ts.type)
3831 gfc_error ("Expression in CASE statement at %L must be of type %s",
3832 &e->where, gfc_basic_typename (case_expr->ts.type));
3833 return FAILURE;
3836 /* C805 (R808) For a given case-construct, each case-value shall be of
3837 the same type as case-expr. For character type, length differences
3838 are allowed, but the kind type parameters shall be the same. */
3840 if (case_expr->ts.type == BT_CHARACTER && e->ts.kind != case_expr->ts.kind)
3842 gfc_error("Expression in CASE statement at %L must be kind %d",
3843 &e->where, case_expr->ts.kind);
3844 return FAILURE;
3847 /* Convert the case value kind to that of case expression kind, if needed.
3848 FIXME: Should a warning be issued? */
3849 if (e->ts.kind != case_expr->ts.kind)
3850 gfc_convert_type_warn (e, &case_expr->ts, 2, 0);
3852 if (e->rank != 0)
3854 gfc_error ("Expression in CASE statement at %L must be scalar",
3855 &e->where);
3856 return FAILURE;
3859 return SUCCESS;
3863 /* Given a completely parsed select statement, we:
3865 - Validate all expressions and code within the SELECT.
3866 - Make sure that the selection expression is not of the wrong type.
3867 - Make sure that no case ranges overlap.
3868 - Eliminate unreachable cases and unreachable code resulting from
3869 removing case labels.
3871 The standard does allow unreachable cases, e.g. CASE (5:3). But
3872 they are a hassle for code generation, and to prevent that, we just
3873 cut them out here. This is not necessary for overlapping cases
3874 because they are illegal and we never even try to generate code.
3876 We have the additional caveat that a SELECT construct could have
3877 been a computed GOTO in the source code. Fortunately we can fairly
3878 easily work around that here: The case_expr for a "real" SELECT CASE
3879 is in code->expr1, but for a computed GOTO it is in code->expr2. All
3880 we have to do is make sure that the case_expr is a scalar integer
3881 expression. */
3883 static void
3884 resolve_select (gfc_code * code)
3886 gfc_code *body;
3887 gfc_expr *case_expr;
3888 gfc_case *cp, *default_case, *tail, *head;
3889 int seen_unreachable;
3890 int seen_logical;
3891 int ncases;
3892 bt type;
3893 try t;
3895 if (code->expr == NULL)
3897 /* This was actually a computed GOTO statement. */
3898 case_expr = code->expr2;
3899 if (case_expr->ts.type != BT_INTEGER
3900 || case_expr->rank != 0)
3901 gfc_error ("Selection expression in computed GOTO statement "
3902 "at %L must be a scalar integer expression",
3903 &case_expr->where);
3905 /* Further checking is not necessary because this SELECT was built
3906 by the compiler, so it should always be OK. Just move the
3907 case_expr from expr2 to expr so that we can handle computed
3908 GOTOs as normal SELECTs from here on. */
3909 code->expr = code->expr2;
3910 code->expr2 = NULL;
3911 return;
3914 case_expr = code->expr;
3916 type = case_expr->ts.type;
3917 if (type != BT_LOGICAL && type != BT_INTEGER && type != BT_CHARACTER)
3919 gfc_error ("Argument of SELECT statement at %L cannot be %s",
3920 &case_expr->where, gfc_typename (&case_expr->ts));
3922 /* Punt. Going on here just produce more garbage error messages. */
3923 return;
3926 if (case_expr->rank != 0)
3928 gfc_error ("Argument of SELECT statement at %L must be a scalar "
3929 "expression", &case_expr->where);
3931 /* Punt. */
3932 return;
3935 /* PR 19168 has a long discussion concerning a mismatch of the kinds
3936 of the SELECT CASE expression and its CASE values. Walk the lists
3937 of case values, and if we find a mismatch, promote case_expr to
3938 the appropriate kind. */
3940 if (type == BT_LOGICAL || type == BT_INTEGER)
3942 for (body = code->block; body; body = body->block)
3944 /* Walk the case label list. */
3945 for (cp = body->ext.case_list; cp; cp = cp->next)
3947 /* Intercept the DEFAULT case. It does not have a kind. */
3948 if (cp->low == NULL && cp->high == NULL)
3949 continue;
3951 /* Unreachable case ranges are discarded, so ignore. */
3952 if (cp->low != NULL && cp->high != NULL
3953 && cp->low != cp->high
3954 && gfc_compare_expr (cp->low, cp->high) > 0)
3955 continue;
3957 /* FIXME: Should a warning be issued? */
3958 if (cp->low != NULL
3959 && case_expr->ts.kind != gfc_kind_max(case_expr, cp->low))
3960 gfc_convert_type_warn (case_expr, &cp->low->ts, 2, 0);
3962 if (cp->high != NULL
3963 && case_expr->ts.kind != gfc_kind_max(case_expr, cp->high))
3964 gfc_convert_type_warn (case_expr, &cp->high->ts, 2, 0);
3969 /* Assume there is no DEFAULT case. */
3970 default_case = NULL;
3971 head = tail = NULL;
3972 ncases = 0;
3973 seen_logical = 0;
3975 for (body = code->block; body; body = body->block)
3977 /* Assume the CASE list is OK, and all CASE labels can be matched. */
3978 t = SUCCESS;
3979 seen_unreachable = 0;
3981 /* Walk the case label list, making sure that all case labels
3982 are legal. */
3983 for (cp = body->ext.case_list; cp; cp = cp->next)
3985 /* Count the number of cases in the whole construct. */
3986 ncases++;
3988 /* Intercept the DEFAULT case. */
3989 if (cp->low == NULL && cp->high == NULL)
3991 if (default_case != NULL)
3993 gfc_error ("The DEFAULT CASE at %L cannot be followed "
3994 "by a second DEFAULT CASE at %L",
3995 &default_case->where, &cp->where);
3996 t = FAILURE;
3997 break;
3999 else
4001 default_case = cp;
4002 continue;
4006 /* Deal with single value cases and case ranges. Errors are
4007 issued from the validation function. */
4008 if(validate_case_label_expr (cp->low, case_expr) != SUCCESS
4009 || validate_case_label_expr (cp->high, case_expr) != SUCCESS)
4011 t = FAILURE;
4012 break;
4015 if (type == BT_LOGICAL
4016 && ((cp->low == NULL || cp->high == NULL)
4017 || cp->low != cp->high))
4019 gfc_error
4020 ("Logical range in CASE statement at %L is not allowed",
4021 &cp->low->where);
4022 t = FAILURE;
4023 break;
4026 if (type == BT_LOGICAL && cp->low->expr_type == EXPR_CONSTANT)
4028 int value;
4029 value = cp->low->value.logical == 0 ? 2 : 1;
4030 if (value & seen_logical)
4032 gfc_error ("constant logical value in CASE statement "
4033 "is repeated at %L",
4034 &cp->low->where);
4035 t = FAILURE;
4036 break;
4038 seen_logical |= value;
4041 if (cp->low != NULL && cp->high != NULL
4042 && cp->low != cp->high
4043 && gfc_compare_expr (cp->low, cp->high) > 0)
4045 if (gfc_option.warn_surprising)
4046 gfc_warning ("Range specification at %L can never "
4047 "be matched", &cp->where);
4049 cp->unreachable = 1;
4050 seen_unreachable = 1;
4052 else
4054 /* If the case range can be matched, it can also overlap with
4055 other cases. To make sure it does not, we put it in a
4056 double linked list here. We sort that with a merge sort
4057 later on to detect any overlapping cases. */
4058 if (!head)
4060 head = tail = cp;
4061 head->right = head->left = NULL;
4063 else
4065 tail->right = cp;
4066 tail->right->left = tail;
4067 tail = tail->right;
4068 tail->right = NULL;
4073 /* It there was a failure in the previous case label, give up
4074 for this case label list. Continue with the next block. */
4075 if (t == FAILURE)
4076 continue;
4078 /* See if any case labels that are unreachable have been seen.
4079 If so, we eliminate them. This is a bit of a kludge because
4080 the case lists for a single case statement (label) is a
4081 single forward linked lists. */
4082 if (seen_unreachable)
4084 /* Advance until the first case in the list is reachable. */
4085 while (body->ext.case_list != NULL
4086 && body->ext.case_list->unreachable)
4088 gfc_case *n = body->ext.case_list;
4089 body->ext.case_list = body->ext.case_list->next;
4090 n->next = NULL;
4091 gfc_free_case_list (n);
4094 /* Strip all other unreachable cases. */
4095 if (body->ext.case_list)
4097 for (cp = body->ext.case_list; cp->next; cp = cp->next)
4099 if (cp->next->unreachable)
4101 gfc_case *n = cp->next;
4102 cp->next = cp->next->next;
4103 n->next = NULL;
4104 gfc_free_case_list (n);
4111 /* See if there were overlapping cases. If the check returns NULL,
4112 there was overlap. In that case we don't do anything. If head
4113 is non-NULL, we prepend the DEFAULT case. The sorted list can
4114 then used during code generation for SELECT CASE constructs with
4115 a case expression of a CHARACTER type. */
4116 if (head)
4118 head = check_case_overlap (head);
4120 /* Prepend the default_case if it is there. */
4121 if (head != NULL && default_case)
4123 default_case->left = NULL;
4124 default_case->right = head;
4125 head->left = default_case;
4129 /* Eliminate dead blocks that may be the result if we've seen
4130 unreachable case labels for a block. */
4131 for (body = code; body && body->block; body = body->block)
4133 if (body->block->ext.case_list == NULL)
4135 /* Cut the unreachable block from the code chain. */
4136 gfc_code *c = body->block;
4137 body->block = c->block;
4139 /* Kill the dead block, but not the blocks below it. */
4140 c->block = NULL;
4141 gfc_free_statements (c);
4145 /* More than two cases is legal but insane for logical selects.
4146 Issue a warning for it. */
4147 if (gfc_option.warn_surprising && type == BT_LOGICAL
4148 && ncases > 2)
4149 gfc_warning ("Logical SELECT CASE block at %L has more that two cases",
4150 &code->loc);
4154 /* Resolve a transfer statement. This is making sure that:
4155 -- a derived type being transferred has only non-pointer components
4156 -- a derived type being transferred doesn't have private components, unless
4157 it's being transferred from the module where the type was defined
4158 -- we're not trying to transfer a whole assumed size array. */
4160 static void
4161 resolve_transfer (gfc_code * code)
4163 gfc_typespec *ts;
4164 gfc_symbol *sym;
4165 gfc_ref *ref;
4166 gfc_expr *exp;
4168 exp = code->expr;
4170 if (exp->expr_type != EXPR_VARIABLE
4171 && exp->expr_type != EXPR_FUNCTION)
4172 return;
4174 sym = exp->symtree->n.sym;
4175 ts = &sym->ts;
4177 /* Go to actual component transferred. */
4178 for (ref = code->expr->ref; ref; ref = ref->next)
4179 if (ref->type == REF_COMPONENT)
4180 ts = &ref->u.c.component->ts;
4182 if (ts->type == BT_DERIVED)
4184 /* Check that transferred derived type doesn't contain POINTER
4185 components. */
4186 if (derived_pointer (ts->derived))
4188 gfc_error ("Data transfer element at %L cannot have "
4189 "POINTER components", &code->loc);
4190 return;
4193 if (ts->derived->attr.alloc_comp)
4195 gfc_error ("Data transfer element at %L cannot have "
4196 "ALLOCATABLE components", &code->loc);
4197 return;
4200 if (derived_inaccessible (ts->derived))
4202 gfc_error ("Data transfer element at %L cannot have "
4203 "PRIVATE components",&code->loc);
4204 return;
4208 if (sym->as != NULL && sym->as->type == AS_ASSUMED_SIZE
4209 && exp->ref->type == REF_ARRAY && exp->ref->u.ar.type == AR_FULL)
4211 gfc_error ("Data transfer element at %L cannot be a full reference to "
4212 "an assumed-size array", &code->loc);
4213 return;
4218 /*********** Toplevel code resolution subroutines ***********/
4220 /* Given a branch to a label and a namespace, if the branch is conforming.
4221 The code node described where the branch is located. */
4223 static void
4224 resolve_branch (gfc_st_label * label, gfc_code * code)
4226 gfc_code *block, *found;
4227 code_stack *stack;
4228 gfc_st_label *lp;
4230 if (label == NULL)
4231 return;
4232 lp = label;
4234 /* Step one: is this a valid branching target? */
4236 if (lp->defined == ST_LABEL_UNKNOWN)
4238 gfc_error ("Label %d referenced at %L is never defined", lp->value,
4239 &lp->where);
4240 return;
4243 if (lp->defined != ST_LABEL_TARGET)
4245 gfc_error ("Statement at %L is not a valid branch target statement "
4246 "for the branch statement at %L", &lp->where, &code->loc);
4247 return;
4250 /* Step two: make sure this branch is not a branch to itself ;-) */
4252 if (code->here == label)
4254 gfc_warning ("Branch at %L causes an infinite loop", &code->loc);
4255 return;
4258 /* Step three: Try to find the label in the parse tree. To do this,
4259 we traverse the tree block-by-block: first the block that
4260 contains this GOTO, then the block that it is nested in, etc. We
4261 can ignore other blocks because branching into another block is
4262 not allowed. */
4264 found = NULL;
4266 for (stack = cs_base; stack; stack = stack->prev)
4268 for (block = stack->head; block; block = block->next)
4270 if (block->here == label)
4272 found = block;
4273 break;
4277 if (found)
4278 break;
4281 if (found == NULL)
4283 /* The label is not in an enclosing block, so illegal. This was
4284 allowed in Fortran 66, so we allow it as extension. We also
4285 forego further checks if we run into this. */
4286 gfc_notify_std (GFC_STD_LEGACY,
4287 "Label at %L is not in the same block as the "
4288 "GOTO statement at %L", &lp->where, &code->loc);
4289 return;
4292 /* Step four: Make sure that the branching target is legal if
4293 the statement is an END {SELECT,DO,IF}. */
4295 if (found->op == EXEC_NOP)
4297 for (stack = cs_base; stack; stack = stack->prev)
4298 if (stack->current->next == found)
4299 break;
4301 if (stack == NULL)
4302 gfc_notify_std (GFC_STD_F95_DEL,
4303 "Obsolete: GOTO at %L jumps to END of construct at %L",
4304 &code->loc, &found->loc);
4309 /* Check whether EXPR1 has the same shape as EXPR2. */
4311 static try
4312 resolve_where_shape (gfc_expr *expr1, gfc_expr *expr2)
4314 mpz_t shape[GFC_MAX_DIMENSIONS];
4315 mpz_t shape2[GFC_MAX_DIMENSIONS];
4316 try result = FAILURE;
4317 int i;
4319 /* Compare the rank. */
4320 if (expr1->rank != expr2->rank)
4321 return result;
4323 /* Compare the size of each dimension. */
4324 for (i=0; i<expr1->rank; i++)
4326 if (gfc_array_dimen_size (expr1, i, &shape[i]) == FAILURE)
4327 goto ignore;
4329 if (gfc_array_dimen_size (expr2, i, &shape2[i]) == FAILURE)
4330 goto ignore;
4332 if (mpz_cmp (shape[i], shape2[i]))
4333 goto over;
4336 /* When either of the two expression is an assumed size array, we
4337 ignore the comparison of dimension sizes. */
4338 ignore:
4339 result = SUCCESS;
4341 over:
4342 for (i--; i>=0; i--)
4344 mpz_clear (shape[i]);
4345 mpz_clear (shape2[i]);
4347 return result;
4351 /* Check whether a WHERE assignment target or a WHERE mask expression
4352 has the same shape as the outmost WHERE mask expression. */
4354 static void
4355 resolve_where (gfc_code *code, gfc_expr *mask)
4357 gfc_code *cblock;
4358 gfc_code *cnext;
4359 gfc_expr *e = NULL;
4361 cblock = code->block;
4363 /* Store the first WHERE mask-expr of the WHERE statement or construct.
4364 In case of nested WHERE, only the outmost one is stored. */
4365 if (mask == NULL) /* outmost WHERE */
4366 e = cblock->expr;
4367 else /* inner WHERE */
4368 e = mask;
4370 while (cblock)
4372 if (cblock->expr)
4374 /* Check if the mask-expr has a consistent shape with the
4375 outmost WHERE mask-expr. */
4376 if (resolve_where_shape (cblock->expr, e) == FAILURE)
4377 gfc_error ("WHERE mask at %L has inconsistent shape",
4378 &cblock->expr->where);
4381 /* the assignment statement of a WHERE statement, or the first
4382 statement in where-body-construct of a WHERE construct */
4383 cnext = cblock->next;
4384 while (cnext)
4386 switch (cnext->op)
4388 /* WHERE assignment statement */
4389 case EXEC_ASSIGN:
4391 /* Check shape consistent for WHERE assignment target. */
4392 if (e && resolve_where_shape (cnext->expr, e) == FAILURE)
4393 gfc_error ("WHERE assignment target at %L has "
4394 "inconsistent shape", &cnext->expr->where);
4395 break;
4397 /* WHERE or WHERE construct is part of a where-body-construct */
4398 case EXEC_WHERE:
4399 resolve_where (cnext, e);
4400 break;
4402 default:
4403 gfc_error ("Unsupported statement inside WHERE at %L",
4404 &cnext->loc);
4406 /* the next statement within the same where-body-construct */
4407 cnext = cnext->next;
4409 /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
4410 cblock = cblock->block;
4415 /* Check whether the FORALL index appears in the expression or not. */
4417 static try
4418 gfc_find_forall_index (gfc_expr *expr, gfc_symbol *symbol)
4420 gfc_array_ref ar;
4421 gfc_ref *tmp;
4422 gfc_actual_arglist *args;
4423 int i;
4425 switch (expr->expr_type)
4427 case EXPR_VARIABLE:
4428 gcc_assert (expr->symtree->n.sym);
4430 /* A scalar assignment */
4431 if (!expr->ref)
4433 if (expr->symtree->n.sym == symbol)
4434 return SUCCESS;
4435 else
4436 return FAILURE;
4439 /* the expr is array ref, substring or struct component. */
4440 tmp = expr->ref;
4441 while (tmp != NULL)
4443 switch (tmp->type)
4445 case REF_ARRAY:
4446 /* Check if the symbol appears in the array subscript. */
4447 ar = tmp->u.ar;
4448 for (i = 0; i < GFC_MAX_DIMENSIONS; i++)
4450 if (ar.start[i])
4451 if (gfc_find_forall_index (ar.start[i], symbol) == SUCCESS)
4452 return SUCCESS;
4454 if (ar.end[i])
4455 if (gfc_find_forall_index (ar.end[i], symbol) == SUCCESS)
4456 return SUCCESS;
4458 if (ar.stride[i])
4459 if (gfc_find_forall_index (ar.stride[i], symbol) == SUCCESS)
4460 return SUCCESS;
4461 } /* end for */
4462 break;
4464 case REF_SUBSTRING:
4465 if (expr->symtree->n.sym == symbol)
4466 return SUCCESS;
4467 tmp = expr->ref;
4468 /* Check if the symbol appears in the substring section. */
4469 if (gfc_find_forall_index (tmp->u.ss.start, symbol) == SUCCESS)
4470 return SUCCESS;
4471 if (gfc_find_forall_index (tmp->u.ss.end, symbol) == SUCCESS)
4472 return SUCCESS;
4473 break;
4475 case REF_COMPONENT:
4476 break;
4478 default:
4479 gfc_error("expression reference type error at %L", &expr->where);
4481 tmp = tmp->next;
4483 break;
4485 /* If the expression is a function call, then check if the symbol
4486 appears in the actual arglist of the function. */
4487 case EXPR_FUNCTION:
4488 for (args = expr->value.function.actual; args; args = args->next)
4490 if (gfc_find_forall_index(args->expr,symbol) == SUCCESS)
4491 return SUCCESS;
4493 break;
4495 /* It seems not to happen. */
4496 case EXPR_SUBSTRING:
4497 if (expr->ref)
4499 tmp = expr->ref;
4500 gcc_assert (expr->ref->type == REF_SUBSTRING);
4501 if (gfc_find_forall_index (tmp->u.ss.start, symbol) == SUCCESS)
4502 return SUCCESS;
4503 if (gfc_find_forall_index (tmp->u.ss.end, symbol) == SUCCESS)
4504 return SUCCESS;
4506 break;
4508 /* It seems not to happen. */
4509 case EXPR_STRUCTURE:
4510 case EXPR_ARRAY:
4511 gfc_error ("Unsupported statement while finding forall index in "
4512 "expression");
4513 break;
4515 case EXPR_OP:
4516 /* Find the FORALL index in the first operand. */
4517 if (expr->value.op.op1)
4519 if (gfc_find_forall_index (expr->value.op.op1, symbol) == SUCCESS)
4520 return SUCCESS;
4523 /* Find the FORALL index in the second operand. */
4524 if (expr->value.op.op2)
4526 if (gfc_find_forall_index (expr->value.op.op2, symbol) == SUCCESS)
4527 return SUCCESS;
4529 break;
4531 default:
4532 break;
4535 return FAILURE;
4539 /* Resolve assignment in FORALL construct.
4540 NVAR is the number of FORALL index variables, and VAR_EXPR records the
4541 FORALL index variables. */
4543 static void
4544 gfc_resolve_assign_in_forall (gfc_code *code, int nvar, gfc_expr **var_expr)
4546 int n;
4548 for (n = 0; n < nvar; n++)
4550 gfc_symbol *forall_index;
4552 forall_index = var_expr[n]->symtree->n.sym;
4554 /* Check whether the assignment target is one of the FORALL index
4555 variable. */
4556 if ((code->expr->expr_type == EXPR_VARIABLE)
4557 && (code->expr->symtree->n.sym == forall_index))
4558 gfc_error ("Assignment to a FORALL index variable at %L",
4559 &code->expr->where);
4560 else
4562 /* If one of the FORALL index variables doesn't appear in the
4563 assignment target, then there will be a many-to-one
4564 assignment. */
4565 if (gfc_find_forall_index (code->expr, forall_index) == FAILURE)
4566 gfc_error ("The FORALL with index '%s' cause more than one "
4567 "assignment to this object at %L",
4568 var_expr[n]->symtree->name, &code->expr->where);
4574 /* Resolve WHERE statement in FORALL construct. */
4576 static void
4577 gfc_resolve_where_code_in_forall (gfc_code *code, int nvar, gfc_expr **var_expr){
4578 gfc_code *cblock;
4579 gfc_code *cnext;
4581 cblock = code->block;
4582 while (cblock)
4584 /* the assignment statement of a WHERE statement, or the first
4585 statement in where-body-construct of a WHERE construct */
4586 cnext = cblock->next;
4587 while (cnext)
4589 switch (cnext->op)
4591 /* WHERE assignment statement */
4592 case EXEC_ASSIGN:
4593 gfc_resolve_assign_in_forall (cnext, nvar, var_expr);
4594 break;
4596 /* WHERE or WHERE construct is part of a where-body-construct */
4597 case EXEC_WHERE:
4598 gfc_resolve_where_code_in_forall (cnext, nvar, var_expr);
4599 break;
4601 default:
4602 gfc_error ("Unsupported statement inside WHERE at %L",
4603 &cnext->loc);
4605 /* the next statement within the same where-body-construct */
4606 cnext = cnext->next;
4608 /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
4609 cblock = cblock->block;
4614 /* Traverse the FORALL body to check whether the following errors exist:
4615 1. For assignment, check if a many-to-one assignment happens.
4616 2. For WHERE statement, check the WHERE body to see if there is any
4617 many-to-one assignment. */
4619 static void
4620 gfc_resolve_forall_body (gfc_code *code, int nvar, gfc_expr **var_expr)
4622 gfc_code *c;
4624 c = code->block->next;
4625 while (c)
4627 switch (c->op)
4629 case EXEC_ASSIGN:
4630 case EXEC_POINTER_ASSIGN:
4631 gfc_resolve_assign_in_forall (c, nvar, var_expr);
4632 break;
4634 /* Because the gfc_resolve_blocks() will handle the nested FORALL,
4635 there is no need to handle it here. */
4636 case EXEC_FORALL:
4637 break;
4638 case EXEC_WHERE:
4639 gfc_resolve_where_code_in_forall(c, nvar, var_expr);
4640 break;
4641 default:
4642 break;
4644 /* The next statement in the FORALL body. */
4645 c = c->next;
4650 /* Given a FORALL construct, first resolve the FORALL iterator, then call
4651 gfc_resolve_forall_body to resolve the FORALL body. */
4653 static void
4654 gfc_resolve_forall (gfc_code *code, gfc_namespace *ns, int forall_save)
4656 static gfc_expr **var_expr;
4657 static int total_var = 0;
4658 static int nvar = 0;
4659 gfc_forall_iterator *fa;
4660 gfc_symbol *forall_index;
4661 gfc_code *next;
4662 int i;
4664 /* Start to resolve a FORALL construct */
4665 if (forall_save == 0)
4667 /* Count the total number of FORALL index in the nested FORALL
4668 construct in order to allocate the VAR_EXPR with proper size. */
4669 next = code;
4670 while ((next != NULL) && (next->op == EXEC_FORALL))
4672 for (fa = next->ext.forall_iterator; fa; fa = fa->next)
4673 total_var ++;
4674 next = next->block->next;
4677 /* Allocate VAR_EXPR with NUMBER_OF_FORALL_INDEX elements. */
4678 var_expr = (gfc_expr **) gfc_getmem (total_var * sizeof (gfc_expr *));
4681 /* The information about FORALL iterator, including FORALL index start, end
4682 and stride. The FORALL index can not appear in start, end or stride. */
4683 for (fa = code->ext.forall_iterator; fa; fa = fa->next)
4685 /* Check if any outer FORALL index name is the same as the current
4686 one. */
4687 for (i = 0; i < nvar; i++)
4689 if (fa->var->symtree->n.sym == var_expr[i]->symtree->n.sym)
4691 gfc_error ("An outer FORALL construct already has an index "
4692 "with this name %L", &fa->var->where);
4696 /* Record the current FORALL index. */
4697 var_expr[nvar] = gfc_copy_expr (fa->var);
4699 forall_index = fa->var->symtree->n.sym;
4701 /* Check if the FORALL index appears in start, end or stride. */
4702 if (gfc_find_forall_index (fa->start, forall_index) == SUCCESS)
4703 gfc_error ("A FORALL index must not appear in a limit or stride "
4704 "expression in the same FORALL at %L", &fa->start->where);
4705 if (gfc_find_forall_index (fa->end, forall_index) == SUCCESS)
4706 gfc_error ("A FORALL index must not appear in a limit or stride "
4707 "expression in the same FORALL at %L", &fa->end->where);
4708 if (gfc_find_forall_index (fa->stride, forall_index) == SUCCESS)
4709 gfc_error ("A FORALL index must not appear in a limit or stride "
4710 "expression in the same FORALL at %L", &fa->stride->where);
4711 nvar++;
4714 /* Resolve the FORALL body. */
4715 gfc_resolve_forall_body (code, nvar, var_expr);
4717 /* May call gfc_resolve_forall to resolve the inner FORALL loop. */
4718 gfc_resolve_blocks (code->block, ns);
4720 /* Free VAR_EXPR after the whole FORALL construct resolved. */
4721 for (i = 0; i < total_var; i++)
4722 gfc_free_expr (var_expr[i]);
4724 /* Reset the counters. */
4725 total_var = 0;
4726 nvar = 0;
4730 /* Resolve lists of blocks found in IF, SELECT CASE, WHERE, FORALL ,GOTO and
4731 DO code nodes. */
4733 static void resolve_code (gfc_code *, gfc_namespace *);
4735 void
4736 gfc_resolve_blocks (gfc_code * b, gfc_namespace * ns)
4738 try t;
4740 for (; b; b = b->block)
4742 t = gfc_resolve_expr (b->expr);
4743 if (gfc_resolve_expr (b->expr2) == FAILURE)
4744 t = FAILURE;
4746 switch (b->op)
4748 case EXEC_IF:
4749 if (t == SUCCESS && b->expr != NULL
4750 && (b->expr->ts.type != BT_LOGICAL || b->expr->rank != 0))
4751 gfc_error
4752 ("ELSE IF clause at %L requires a scalar LOGICAL expression",
4753 &b->expr->where);
4754 break;
4756 case EXEC_WHERE:
4757 if (t == SUCCESS
4758 && b->expr != NULL
4759 && (b->expr->ts.type != BT_LOGICAL
4760 || b->expr->rank == 0))
4761 gfc_error
4762 ("WHERE/ELSEWHERE clause at %L requires a LOGICAL array",
4763 &b->expr->where);
4764 break;
4766 case EXEC_GOTO:
4767 resolve_branch (b->label, b);
4768 break;
4770 case EXEC_SELECT:
4771 case EXEC_FORALL:
4772 case EXEC_DO:
4773 case EXEC_DO_WHILE:
4774 case EXEC_READ:
4775 case EXEC_WRITE:
4776 case EXEC_IOLENGTH:
4777 break;
4779 case EXEC_OMP_ATOMIC:
4780 case EXEC_OMP_CRITICAL:
4781 case EXEC_OMP_DO:
4782 case EXEC_OMP_MASTER:
4783 case EXEC_OMP_ORDERED:
4784 case EXEC_OMP_PARALLEL:
4785 case EXEC_OMP_PARALLEL_DO:
4786 case EXEC_OMP_PARALLEL_SECTIONS:
4787 case EXEC_OMP_PARALLEL_WORKSHARE:
4788 case EXEC_OMP_SECTIONS:
4789 case EXEC_OMP_SINGLE:
4790 case EXEC_OMP_WORKSHARE:
4791 break;
4793 default:
4794 gfc_internal_error ("resolve_block(): Bad block type");
4797 resolve_code (b->next, ns);
4802 /* Given a block of code, recursively resolve everything pointed to by this
4803 code block. */
4805 static void
4806 resolve_code (gfc_code * code, gfc_namespace * ns)
4808 int omp_workshare_save;
4809 int forall_save;
4810 code_stack frame;
4811 gfc_alloc *a;
4812 try t;
4814 frame.prev = cs_base;
4815 frame.head = code;
4816 cs_base = &frame;
4818 for (; code; code = code->next)
4820 frame.current = code;
4821 forall_save = forall_flag;
4823 if (code->op == EXEC_FORALL)
4825 forall_flag = 1;
4826 gfc_resolve_forall (code, ns, forall_save);
4827 forall_flag = 2;
4829 else if (code->block)
4831 omp_workshare_save = -1;
4832 switch (code->op)
4834 case EXEC_OMP_PARALLEL_WORKSHARE:
4835 omp_workshare_save = omp_workshare_flag;
4836 omp_workshare_flag = 1;
4837 gfc_resolve_omp_parallel_blocks (code, ns);
4838 break;
4839 case EXEC_OMP_PARALLEL:
4840 case EXEC_OMP_PARALLEL_DO:
4841 case EXEC_OMP_PARALLEL_SECTIONS:
4842 omp_workshare_save = omp_workshare_flag;
4843 omp_workshare_flag = 0;
4844 gfc_resolve_omp_parallel_blocks (code, ns);
4845 break;
4846 case EXEC_OMP_DO:
4847 gfc_resolve_omp_do_blocks (code, ns);
4848 break;
4849 case EXEC_OMP_WORKSHARE:
4850 omp_workshare_save = omp_workshare_flag;
4851 omp_workshare_flag = 1;
4852 /* FALLTHROUGH */
4853 default:
4854 gfc_resolve_blocks (code->block, ns);
4855 break;
4858 if (omp_workshare_save != -1)
4859 omp_workshare_flag = omp_workshare_save;
4862 t = gfc_resolve_expr (code->expr);
4863 forall_flag = forall_save;
4865 if (gfc_resolve_expr (code->expr2) == FAILURE)
4866 t = FAILURE;
4868 switch (code->op)
4870 case EXEC_NOP:
4871 case EXEC_CYCLE:
4872 case EXEC_PAUSE:
4873 case EXEC_STOP:
4874 case EXEC_EXIT:
4875 case EXEC_CONTINUE:
4876 case EXEC_DT_END:
4877 break;
4879 case EXEC_ENTRY:
4880 /* Keep track of which entry we are up to. */
4881 current_entry_id = code->ext.entry->id;
4882 break;
4884 case EXEC_WHERE:
4885 resolve_where (code, NULL);
4886 break;
4888 case EXEC_GOTO:
4889 if (code->expr != NULL)
4891 if (code->expr->ts.type != BT_INTEGER)
4892 gfc_error ("ASSIGNED GOTO statement at %L requires an INTEGER "
4893 "variable", &code->expr->where);
4894 else if (code->expr->symtree->n.sym->attr.assign != 1)
4895 gfc_error ("Variable '%s' has not been assigned a target label "
4896 "at %L", code->expr->symtree->n.sym->name,
4897 &code->expr->where);
4899 else
4900 resolve_branch (code->label, code);
4901 break;
4903 case EXEC_RETURN:
4904 if (code->expr != NULL
4905 && (code->expr->ts.type != BT_INTEGER || code->expr->rank))
4906 gfc_error ("Alternate RETURN statement at %L requires a SCALAR-"
4907 "INTEGER return specifier", &code->expr->where);
4908 break;
4910 case EXEC_ASSIGN:
4911 if (t == FAILURE)
4912 break;
4914 if (gfc_extend_assign (code, ns) == SUCCESS)
4916 if (gfc_pure (NULL) && !gfc_pure (code->symtree->n.sym))
4918 gfc_error ("Subroutine '%s' called instead of assignment at "
4919 "%L must be PURE", code->symtree->n.sym->name,
4920 &code->loc);
4921 break;
4923 goto call;
4926 if (gfc_pure (NULL))
4928 if (gfc_impure_variable (code->expr->symtree->n.sym))
4930 gfc_error
4931 ("Cannot assign to variable '%s' in PURE procedure at %L",
4932 code->expr->symtree->n.sym->name, &code->expr->where);
4933 break;
4936 if (code->expr2->ts.type == BT_DERIVED
4937 && derived_pointer (code->expr2->ts.derived))
4939 gfc_error
4940 ("Right side of assignment at %L is a derived type "
4941 "containing a POINTER in a PURE procedure",
4942 &code->expr2->where);
4943 break;
4947 gfc_check_assign (code->expr, code->expr2, 1);
4948 break;
4950 case EXEC_LABEL_ASSIGN:
4951 if (code->label->defined == ST_LABEL_UNKNOWN)
4952 gfc_error ("Label %d referenced at %L is never defined",
4953 code->label->value, &code->label->where);
4954 if (t == SUCCESS
4955 && (code->expr->expr_type != EXPR_VARIABLE
4956 || code->expr->symtree->n.sym->ts.type != BT_INTEGER
4957 || code->expr->symtree->n.sym->ts.kind
4958 != gfc_default_integer_kind
4959 || code->expr->symtree->n.sym->as != NULL))
4960 gfc_error ("ASSIGN statement at %L requires a scalar "
4961 "default INTEGER variable", &code->expr->where);
4962 break;
4964 case EXEC_POINTER_ASSIGN:
4965 if (t == FAILURE)
4966 break;
4968 gfc_check_pointer_assign (code->expr, code->expr2);
4969 break;
4971 case EXEC_ARITHMETIC_IF:
4972 if (t == SUCCESS
4973 && code->expr->ts.type != BT_INTEGER
4974 && code->expr->ts.type != BT_REAL)
4975 gfc_error ("Arithmetic IF statement at %L requires a numeric "
4976 "expression", &code->expr->where);
4978 resolve_branch (code->label, code);
4979 resolve_branch (code->label2, code);
4980 resolve_branch (code->label3, code);
4981 break;
4983 case EXEC_IF:
4984 if (t == SUCCESS && code->expr != NULL
4985 && (code->expr->ts.type != BT_LOGICAL
4986 || code->expr->rank != 0))
4987 gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
4988 &code->expr->where);
4989 break;
4991 case EXEC_CALL:
4992 call:
4993 resolve_call (code);
4994 break;
4996 case EXEC_SELECT:
4997 /* Select is complicated. Also, a SELECT construct could be
4998 a transformed computed GOTO. */
4999 resolve_select (code);
5000 break;
5002 case EXEC_DO:
5003 if (code->ext.iterator != NULL)
5005 gfc_iterator *iter = code->ext.iterator;
5006 if (gfc_resolve_iterator (iter, true) != FAILURE)
5007 gfc_resolve_do_iterator (code, iter->var->symtree->n.sym);
5009 break;
5011 case EXEC_DO_WHILE:
5012 if (code->expr == NULL)
5013 gfc_internal_error ("resolve_code(): No expression on DO WHILE");
5014 if (t == SUCCESS
5015 && (code->expr->rank != 0
5016 || code->expr->ts.type != BT_LOGICAL))
5017 gfc_error ("Exit condition of DO WHILE loop at %L must be "
5018 "a scalar LOGICAL expression", &code->expr->where);
5019 break;
5021 case EXEC_ALLOCATE:
5022 if (t == SUCCESS && code->expr != NULL
5023 && code->expr->ts.type != BT_INTEGER)
5024 gfc_error ("STAT tag in ALLOCATE statement at %L must be "
5025 "of type INTEGER", &code->expr->where);
5027 for (a = code->ext.alloc_list; a; a = a->next)
5028 resolve_allocate_expr (a->expr, code);
5030 break;
5032 case EXEC_DEALLOCATE:
5033 if (t == SUCCESS && code->expr != NULL
5034 && code->expr->ts.type != BT_INTEGER)
5035 gfc_error
5036 ("STAT tag in DEALLOCATE statement at %L must be of type "
5037 "INTEGER", &code->expr->where);
5039 for (a = code->ext.alloc_list; a; a = a->next)
5040 resolve_deallocate_expr (a->expr);
5042 break;
5044 case EXEC_OPEN:
5045 if (gfc_resolve_open (code->ext.open) == FAILURE)
5046 break;
5048 resolve_branch (code->ext.open->err, code);
5049 break;
5051 case EXEC_CLOSE:
5052 if (gfc_resolve_close (code->ext.close) == FAILURE)
5053 break;
5055 resolve_branch (code->ext.close->err, code);
5056 break;
5058 case EXEC_BACKSPACE:
5059 case EXEC_ENDFILE:
5060 case EXEC_REWIND:
5061 case EXEC_FLUSH:
5062 if (gfc_resolve_filepos (code->ext.filepos) == FAILURE)
5063 break;
5065 resolve_branch (code->ext.filepos->err, code);
5066 break;
5068 case EXEC_INQUIRE:
5069 if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
5070 break;
5072 resolve_branch (code->ext.inquire->err, code);
5073 break;
5075 case EXEC_IOLENGTH:
5076 gcc_assert (code->ext.inquire != NULL);
5077 if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
5078 break;
5080 resolve_branch (code->ext.inquire->err, code);
5081 break;
5083 case EXEC_READ:
5084 case EXEC_WRITE:
5085 if (gfc_resolve_dt (code->ext.dt) == FAILURE)
5086 break;
5088 resolve_branch (code->ext.dt->err, code);
5089 resolve_branch (code->ext.dt->end, code);
5090 resolve_branch (code->ext.dt->eor, code);
5091 break;
5093 case EXEC_TRANSFER:
5094 resolve_transfer (code);
5095 break;
5097 case EXEC_FORALL:
5098 resolve_forall_iterators (code->ext.forall_iterator);
5100 if (code->expr != NULL && code->expr->ts.type != BT_LOGICAL)
5101 gfc_error
5102 ("FORALL mask clause at %L requires a LOGICAL expression",
5103 &code->expr->where);
5104 break;
5106 case EXEC_OMP_ATOMIC:
5107 case EXEC_OMP_BARRIER:
5108 case EXEC_OMP_CRITICAL:
5109 case EXEC_OMP_FLUSH:
5110 case EXEC_OMP_DO:
5111 case EXEC_OMP_MASTER:
5112 case EXEC_OMP_ORDERED:
5113 case EXEC_OMP_SECTIONS:
5114 case EXEC_OMP_SINGLE:
5115 case EXEC_OMP_WORKSHARE:
5116 gfc_resolve_omp_directive (code, ns);
5117 break;
5119 case EXEC_OMP_PARALLEL:
5120 case EXEC_OMP_PARALLEL_DO:
5121 case EXEC_OMP_PARALLEL_SECTIONS:
5122 case EXEC_OMP_PARALLEL_WORKSHARE:
5123 omp_workshare_save = omp_workshare_flag;
5124 omp_workshare_flag = 0;
5125 gfc_resolve_omp_directive (code, ns);
5126 omp_workshare_flag = omp_workshare_save;
5127 break;
5129 default:
5130 gfc_internal_error ("resolve_code(): Bad statement code");
5134 cs_base = frame.prev;
5138 /* Resolve initial values and make sure they are compatible with
5139 the variable. */
5141 static void
5142 resolve_values (gfc_symbol * sym)
5145 if (sym->value == NULL)
5146 return;
5148 if (gfc_resolve_expr (sym->value) == FAILURE)
5149 return;
5151 gfc_check_assign_symbol (sym, sym->value);
5155 /* Resolve an index expression. */
5157 static try
5158 resolve_index_expr (gfc_expr * e)
5160 if (gfc_resolve_expr (e) == FAILURE)
5161 return FAILURE;
5163 if (gfc_simplify_expr (e, 0) == FAILURE)
5164 return FAILURE;
5166 if (gfc_specification_expr (e) == FAILURE)
5167 return FAILURE;
5169 return SUCCESS;
5172 /* Resolve a charlen structure. */
5174 static try
5175 resolve_charlen (gfc_charlen *cl)
5177 if (cl->resolved)
5178 return SUCCESS;
5180 cl->resolved = 1;
5182 specification_expr = 1;
5184 if (resolve_index_expr (cl->length) == FAILURE)
5186 specification_expr = 0;
5187 return FAILURE;
5190 return SUCCESS;
5194 /* Test for non-constant shape arrays. */
5196 static bool
5197 is_non_constant_shape_array (gfc_symbol *sym)
5199 gfc_expr *e;
5200 int i;
5201 bool not_constant;
5203 not_constant = false;
5204 if (sym->as != NULL)
5206 /* Unfortunately, !gfc_is_compile_time_shape hits a legal case that
5207 has not been simplified; parameter array references. Do the
5208 simplification now. */
5209 for (i = 0; i < sym->as->rank; i++)
5211 e = sym->as->lower[i];
5212 if (e && (resolve_index_expr (e) == FAILURE
5213 || !gfc_is_constant_expr (e)))
5214 not_constant = true;
5216 e = sym->as->upper[i];
5217 if (e && (resolve_index_expr (e) == FAILURE
5218 || !gfc_is_constant_expr (e)))
5219 not_constant = true;
5222 return not_constant;
5225 /* Resolution of common features of flavors variable and procedure. */
5227 static try
5228 resolve_fl_var_and_proc (gfc_symbol *sym, int mp_flag)
5230 /* Constraints on deferred shape variable. */
5231 if (sym->as == NULL || sym->as->type != AS_DEFERRED)
5233 if (sym->attr.allocatable)
5235 if (sym->attr.dimension)
5236 gfc_error ("Allocatable array '%s' at %L must have "
5237 "a deferred shape", sym->name, &sym->declared_at);
5238 else
5239 gfc_error ("Scalar object '%s' at %L may not be ALLOCATABLE",
5240 sym->name, &sym->declared_at);
5241 return FAILURE;
5244 if (sym->attr.pointer && sym->attr.dimension)
5246 gfc_error ("Array pointer '%s' at %L must have a deferred shape",
5247 sym->name, &sym->declared_at);
5248 return FAILURE;
5252 else
5254 if (!mp_flag && !sym->attr.allocatable
5255 && !sym->attr.pointer && !sym->attr.dummy)
5257 gfc_error ("Array '%s' at %L cannot have a deferred shape",
5258 sym->name, &sym->declared_at);
5259 return FAILURE;
5262 return SUCCESS;
5265 /* Resolve symbols with flavor variable. */
5267 static try
5268 resolve_fl_variable (gfc_symbol *sym, int mp_flag)
5270 int flag;
5271 int i;
5272 gfc_expr *e;
5273 gfc_expr *constructor_expr;
5274 const char * auto_save_msg;
5276 auto_save_msg = "automatic object '%s' at %L cannot have the "
5277 "SAVE attribute";
5279 if (resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
5280 return FAILURE;
5282 /* Set this flag to check that variables are parameters of all entries.
5283 This check is effected by the call to gfc_resolve_expr through
5284 is_non_constant_shape_array. */
5285 specification_expr = 1;
5287 if (!sym->attr.use_assoc
5288 && !sym->attr.allocatable
5289 && !sym->attr.pointer
5290 && is_non_constant_shape_array (sym))
5292 /* The shape of a main program or module array needs to be constant. */
5293 if (sym->ns->proc_name
5294 && (sym->ns->proc_name->attr.flavor == FL_MODULE
5295 || sym->ns->proc_name->attr.is_main_program))
5297 gfc_error ("The module or main program array '%s' at %L must "
5298 "have constant shape", sym->name, &sym->declared_at);
5299 specification_expr = 0;
5300 return FAILURE;
5304 if (sym->ts.type == BT_CHARACTER)
5306 /* Make sure that character string variables with assumed length are
5307 dummy arguments. */
5308 e = sym->ts.cl->length;
5309 if (e == NULL && !sym->attr.dummy && !sym->attr.result)
5311 gfc_error ("Entity with assumed character length at %L must be a "
5312 "dummy argument or a PARAMETER", &sym->declared_at);
5313 return FAILURE;
5316 if (e && sym->attr.save && !gfc_is_constant_expr (e))
5318 gfc_error (auto_save_msg, sym->name, &sym->declared_at);
5319 return FAILURE;
5322 if (!gfc_is_constant_expr (e)
5323 && !(e->expr_type == EXPR_VARIABLE
5324 && e->symtree->n.sym->attr.flavor == FL_PARAMETER)
5325 && sym->ns->proc_name
5326 && (sym->ns->proc_name->attr.flavor == FL_MODULE
5327 || sym->ns->proc_name->attr.is_main_program)
5328 && !sym->attr.use_assoc)
5330 gfc_error ("'%s' at %L must have constant character length "
5331 "in this context", sym->name, &sym->declared_at);
5332 return FAILURE;
5336 /* Can the symbol have an initializer? */
5337 flag = 0;
5338 if (sym->attr.allocatable || sym->attr.external || sym->attr.dummy
5339 || sym->attr.intrinsic || sym->attr.result)
5340 flag = 1;
5341 else if (sym->attr.dimension && !sym->attr.pointer)
5343 /* Don't allow initialization of automatic arrays. */
5344 for (i = 0; i < sym->as->rank; i++)
5346 if (sym->as->lower[i] == NULL
5347 || sym->as->lower[i]->expr_type != EXPR_CONSTANT
5348 || sym->as->upper[i] == NULL
5349 || sym->as->upper[i]->expr_type != EXPR_CONSTANT)
5351 flag = 1;
5352 break;
5356 /* Also, they must not have the SAVE attribute. */
5357 if (flag && sym->attr.save)
5359 gfc_error (auto_save_msg, sym->name, &sym->declared_at);
5360 return FAILURE;
5364 /* Reject illegal initializers. */
5365 if (sym->value && flag)
5367 if (sym->attr.allocatable)
5368 gfc_error ("Allocatable '%s' at %L cannot have an initializer",
5369 sym->name, &sym->declared_at);
5370 else if (sym->attr.external)
5371 gfc_error ("External '%s' at %L cannot have an initializer",
5372 sym->name, &sym->declared_at);
5373 else if (sym->attr.dummy)
5374 gfc_error ("Dummy '%s' at %L cannot have an initializer",
5375 sym->name, &sym->declared_at);
5376 else if (sym->attr.intrinsic)
5377 gfc_error ("Intrinsic '%s' at %L cannot have an initializer",
5378 sym->name, &sym->declared_at);
5379 else if (sym->attr.result)
5380 gfc_error ("Function result '%s' at %L cannot have an initializer",
5381 sym->name, &sym->declared_at);
5382 else
5383 gfc_error ("Automatic array '%s' at %L cannot have an initializer",
5384 sym->name, &sym->declared_at);
5385 return FAILURE;
5388 /* Check to see if a derived type is blocked from being host associated
5389 by the presence of another class I symbol in the same namespace.
5390 14.6.1.3 of the standard and the discussion on comp.lang.fortran. */
5391 if (sym->ts.type == BT_DERIVED && sym->ns != sym->ts.derived->ns)
5393 gfc_symbol *s;
5394 gfc_find_symbol (sym->ts.derived->name, sym->ns, 0, &s);
5395 if (s && (s->attr.flavor != FL_DERIVED
5396 || !gfc_compare_derived_types (s, sym->ts.derived)))
5398 gfc_error ("The type %s cannot be host associated at %L because "
5399 "it is blocked by an incompatible object of the same "
5400 "name at %L", sym->ts.derived->name, &sym->declared_at,
5401 &s->declared_at);
5402 return FAILURE;
5406 /* 4th constraint in section 11.3: "If an object of a type for which
5407 component-initialization is specified (R429) appears in the
5408 specification-part of a module and does not have the ALLOCATABLE
5409 or POINTER attribute, the object shall have the SAVE attribute." */
5411 constructor_expr = NULL;
5412 if (sym->ts.type == BT_DERIVED && !(sym->value || flag))
5413 constructor_expr = gfc_default_initializer (&sym->ts);
5415 if (sym->ns->proc_name
5416 && sym->ns->proc_name->attr.flavor == FL_MODULE
5417 && constructor_expr
5418 && !sym->ns->save_all && !sym->attr.save
5419 && !sym->attr.pointer && !sym->attr.allocatable)
5421 gfc_error("Object '%s' at %L must have the SAVE attribute %s",
5422 sym->name, &sym->declared_at,
5423 "for default initialization of a component");
5424 return FAILURE;
5427 /* Assign default initializer. */
5428 if (sym->ts.type == BT_DERIVED && !sym->value && !sym->attr.pointer
5429 && !sym->attr.allocatable && (!flag || sym->attr.intent == INTENT_OUT))
5430 sym->value = gfc_default_initializer (&sym->ts);
5432 return SUCCESS;
5436 /* Resolve a procedure. */
5438 static try
5439 resolve_fl_procedure (gfc_symbol *sym, int mp_flag)
5441 gfc_formal_arglist *arg;
5443 if (sym->attr.function
5444 && resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
5445 return FAILURE;
5447 if (sym->attr.proc == PROC_ST_FUNCTION)
5449 if (sym->ts.type == BT_CHARACTER)
5451 gfc_charlen *cl = sym->ts.cl;
5452 if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
5454 gfc_error ("Character-valued statement function '%s' at %L must "
5455 "have constant length", sym->name, &sym->declared_at);
5456 return FAILURE;
5461 /* Ensure that derived type for are not of a private type. Internal
5462 module procedures are excluded by 2.2.3.3 - ie. they are not
5463 externally accessible and can access all the objects accessible in
5464 the host. */
5465 if (!(sym->ns->parent
5466 && sym->ns->parent->proc_name->attr.flavor == FL_MODULE)
5467 && gfc_check_access(sym->attr.access, sym->ns->default_access))
5469 for (arg = sym->formal; arg; arg = arg->next)
5471 if (arg->sym
5472 && arg->sym->ts.type == BT_DERIVED
5473 && !arg->sym->ts.derived->attr.use_assoc
5474 && !gfc_check_access(arg->sym->ts.derived->attr.access,
5475 arg->sym->ts.derived->ns->default_access))
5477 gfc_error_now ("'%s' is of a PRIVATE type and cannot be "
5478 "a dummy argument of '%s', which is "
5479 "PUBLIC at %L", arg->sym->name, sym->name,
5480 &sym->declared_at);
5481 /* Stop this message from recurring. */
5482 arg->sym->ts.derived->attr.access = ACCESS_PUBLIC;
5483 return FAILURE;
5488 /* An external symbol may not have an initializer because it is taken to be
5489 a procedure. */
5490 if (sym->attr.external && sym->value)
5492 gfc_error ("External object '%s' at %L may not have an initializer",
5493 sym->name, &sym->declared_at);
5494 return FAILURE;
5497 /* An elemental function is required to return a scalar 12.7.1 */
5498 if (sym->attr.elemental && sym->attr.function && sym->as)
5500 gfc_error ("ELEMENTAL function '%s' at %L must have a scalar "
5501 "result", sym->name, &sym->declared_at);
5502 /* Reset so that the error only occurs once. */
5503 sym->attr.elemental = 0;
5504 return FAILURE;
5507 /* 5.1.1.5 of the Standard: A function name declared with an asterisk
5508 char-len-param shall not be array-valued, pointer-valued, recursive
5509 or pure. ....snip... A character value of * may only be used in the
5510 following ways: (i) Dummy arg of procedure - dummy associates with
5511 actual length; (ii) To declare a named constant; or (iii) External
5512 function - but length must be declared in calling scoping unit. */
5513 if (sym->attr.function
5514 && sym->ts.type == BT_CHARACTER
5515 && sym->ts.cl && sym->ts.cl->length == NULL)
5517 if ((sym->as && sym->as->rank) || (sym->attr.pointer)
5518 || (sym->attr.recursive) || (sym->attr.pure))
5520 if (sym->as && sym->as->rank)
5521 gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
5522 "array-valued", sym->name, &sym->declared_at);
5524 if (sym->attr.pointer)
5525 gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
5526 "pointer-valued", sym->name, &sym->declared_at);
5528 if (sym->attr.pure)
5529 gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
5530 "pure", sym->name, &sym->declared_at);
5532 if (sym->attr.recursive)
5533 gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
5534 "recursive", sym->name, &sym->declared_at);
5536 return FAILURE;
5539 /* Appendix B.2 of the standard. Contained functions give an
5540 error anyway. Fixed-form is likely to be F77/legacy. */
5541 if (!sym->attr.contained && gfc_current_form != FORM_FIXED)
5542 gfc_notify_std (GFC_STD_F95_OBS, "CHARACTER(*) function "
5543 "'%s' at %L is obsolescent in fortran 95",
5544 sym->name, &sym->declared_at);
5546 return SUCCESS;
5550 /* Resolve the components of a derived type. */
5552 static try
5553 resolve_fl_derived (gfc_symbol *sym)
5555 gfc_component *c;
5556 gfc_dt_list * dt_list;
5557 int i;
5559 for (c = sym->components; c != NULL; c = c->next)
5561 if (c->ts.type == BT_CHARACTER)
5563 if (c->ts.cl->length == NULL
5564 || (resolve_charlen (c->ts.cl) == FAILURE)
5565 || !gfc_is_constant_expr (c->ts.cl->length))
5567 gfc_error ("Character length of component '%s' needs to "
5568 "be a constant specification expression at %L.",
5569 c->name,
5570 c->ts.cl->length ? &c->ts.cl->length->where : &c->loc);
5571 return FAILURE;
5575 if (c->ts.type == BT_DERIVED
5576 && sym->component_access != ACCESS_PRIVATE
5577 && gfc_check_access(sym->attr.access, sym->ns->default_access)
5578 && !c->ts.derived->attr.use_assoc
5579 && !gfc_check_access(c->ts.derived->attr.access,
5580 c->ts.derived->ns->default_access))
5582 gfc_error ("The component '%s' is a PRIVATE type and cannot be "
5583 "a component of '%s', which is PUBLIC at %L",
5584 c->name, sym->name, &sym->declared_at);
5585 return FAILURE;
5588 if (sym->attr.sequence)
5590 if (c->ts.type == BT_DERIVED && c->ts.derived->attr.sequence == 0)
5592 gfc_error ("Component %s of SEQUENCE type declared at %L does "
5593 "not have the SEQUENCE attribute",
5594 c->ts.derived->name, &sym->declared_at);
5595 return FAILURE;
5599 if (c->ts.type == BT_DERIVED && c->pointer
5600 && c->ts.derived->components == NULL)
5602 gfc_error ("The pointer component '%s' of '%s' at %L is a type "
5603 "that has not been declared", c->name, sym->name,
5604 &c->loc);
5605 return FAILURE;
5608 if (c->pointer || c->allocatable || c->as == NULL)
5609 continue;
5611 for (i = 0; i < c->as->rank; i++)
5613 if (c->as->lower[i] == NULL
5614 || !gfc_is_constant_expr (c->as->lower[i])
5615 || (resolve_index_expr (c->as->lower[i]) == FAILURE)
5616 || c->as->upper[i] == NULL
5617 || (resolve_index_expr (c->as->upper[i]) == FAILURE)
5618 || !gfc_is_constant_expr (c->as->upper[i]))
5620 gfc_error ("Component '%s' of '%s' at %L must have "
5621 "constant array bounds.",
5622 c->name, sym->name, &c->loc);
5623 return FAILURE;
5628 /* Add derived type to the derived type list. */
5629 for (dt_list = sym->ns->derived_types; dt_list; dt_list = dt_list->next)
5630 if (sym == dt_list->derived)
5631 break;
5633 if (dt_list == NULL)
5635 dt_list = gfc_get_dt_list ();
5636 dt_list->next = sym->ns->derived_types;
5637 dt_list->derived = sym;
5638 sym->ns->derived_types = dt_list;
5641 return SUCCESS;
5645 static try
5646 resolve_fl_namelist (gfc_symbol *sym)
5648 gfc_namelist *nl;
5649 gfc_symbol *nlsym;
5651 /* Reject PRIVATE objects in a PUBLIC namelist. */
5652 if (gfc_check_access(sym->attr.access, sym->ns->default_access))
5654 for (nl = sym->namelist; nl; nl = nl->next)
5656 if (!nl->sym->attr.use_assoc
5657 && !(sym->ns->parent == nl->sym->ns)
5658 && !gfc_check_access(nl->sym->attr.access,
5659 nl->sym->ns->default_access))
5661 gfc_error ("PRIVATE symbol '%s' cannot be member of "
5662 "PUBLIC namelist at %L", nl->sym->name,
5663 &sym->declared_at);
5664 return FAILURE;
5669 /* Reject namelist arrays that are not constant shape. */
5670 for (nl = sym->namelist; nl; nl = nl->next)
5672 if (is_non_constant_shape_array (nl->sym))
5674 gfc_error ("The array '%s' must have constant shape to be "
5675 "a NAMELIST object at %L", nl->sym->name,
5676 &sym->declared_at);
5677 return FAILURE;
5681 /* Namelist objects cannot have allocatable components. */
5682 for (nl = sym->namelist; nl; nl = nl->next)
5684 if (nl->sym->ts.type == BT_DERIVED
5685 && nl->sym->ts.derived->attr.alloc_comp)
5687 gfc_error ("NAMELIST object '%s' at %L cannot have ALLOCATABLE "
5688 "components", nl->sym->name, &sym->declared_at);
5689 return FAILURE;
5693 /* 14.1.2 A module or internal procedure represent local entities
5694 of the same type as a namelist member and so are not allowed.
5695 Note that this is sometimes caught by check_conflict so the
5696 same message has been used. */
5697 for (nl = sym->namelist; nl; nl = nl->next)
5699 if (nl->sym->ts.kind != 0 && nl->sym->attr.flavor == FL_VARIABLE)
5700 continue;
5701 nlsym = NULL;
5702 if (sym->ns->parent && nl->sym && nl->sym->name)
5703 gfc_find_symbol (nl->sym->name, sym->ns->parent, 0, &nlsym);
5704 if (nlsym && nlsym->attr.flavor == FL_PROCEDURE)
5706 gfc_error ("PROCEDURE attribute conflicts with NAMELIST "
5707 "attribute in '%s' at %L", nlsym->name,
5708 &sym->declared_at);
5709 return FAILURE;
5713 return SUCCESS;
5717 static try
5718 resolve_fl_parameter (gfc_symbol *sym)
5720 /* A parameter array's shape needs to be constant. */
5721 if (sym->as != NULL && !gfc_is_compile_time_shape (sym->as))
5723 gfc_error ("Parameter array '%s' at %L cannot be automatic "
5724 "or assumed shape", sym->name, &sym->declared_at);
5725 return FAILURE;
5728 /* Make sure a parameter that has been implicitly typed still
5729 matches the implicit type, since PARAMETER statements can precede
5730 IMPLICIT statements. */
5731 if (sym->attr.implicit_type
5732 && !gfc_compare_types (&sym->ts,
5733 gfc_get_default_type (sym, sym->ns)))
5735 gfc_error ("Implicitly typed PARAMETER '%s' at %L doesn't match a "
5736 "later IMPLICIT type", sym->name, &sym->declared_at);
5737 return FAILURE;
5740 /* Make sure the types of derived parameters are consistent. This
5741 type checking is deferred until resolution because the type may
5742 refer to a derived type from the host. */
5743 if (sym->ts.type == BT_DERIVED
5744 && !gfc_compare_types (&sym->ts, &sym->value->ts))
5746 gfc_error ("Incompatible derived type in PARAMETER at %L",
5747 &sym->value->where);
5748 return FAILURE;
5750 return SUCCESS;
5754 /* Do anything necessary to resolve a symbol. Right now, we just
5755 assume that an otherwise unknown symbol is a variable. This sort
5756 of thing commonly happens for symbols in module. */
5758 static void
5759 resolve_symbol (gfc_symbol * sym)
5761 /* Zero if we are checking a formal namespace. */
5762 static int formal_ns_flag = 1;
5763 int formal_ns_save, check_constant, mp_flag;
5764 gfc_symtree *symtree;
5765 gfc_symtree *this_symtree;
5766 gfc_namespace *ns;
5767 gfc_component *c;
5769 if (sym->attr.flavor == FL_UNKNOWN)
5772 /* If we find that a flavorless symbol is an interface in one of the
5773 parent namespaces, find its symtree in this namespace, free the
5774 symbol and set the symtree to point to the interface symbol. */
5775 for (ns = gfc_current_ns->parent; ns; ns = ns->parent)
5777 symtree = gfc_find_symtree (ns->sym_root, sym->name);
5778 if (symtree && symtree->n.sym->generic)
5780 this_symtree = gfc_find_symtree (gfc_current_ns->sym_root,
5781 sym->name);
5782 sym->refs--;
5783 if (!sym->refs)
5784 gfc_free_symbol (sym);
5785 symtree->n.sym->refs++;
5786 this_symtree->n.sym = symtree->n.sym;
5787 return;
5791 /* Otherwise give it a flavor according to such attributes as
5792 it has. */
5793 if (sym->attr.external == 0 && sym->attr.intrinsic == 0)
5794 sym->attr.flavor = FL_VARIABLE;
5795 else
5797 sym->attr.flavor = FL_PROCEDURE;
5798 if (sym->attr.dimension)
5799 sym->attr.function = 1;
5803 if (sym->attr.flavor == FL_DERIVED && resolve_fl_derived (sym) == FAILURE)
5804 return;
5806 /* Symbols that are module procedures with results (functions) have
5807 the types and array specification copied for type checking in
5808 procedures that call them, as well as for saving to a module
5809 file. These symbols can't stand the scrutiny that their results
5810 can. */
5811 mp_flag = (sym->result != NULL && sym->result != sym);
5813 /* Assign default type to symbols that need one and don't have one. */
5814 if (sym->ts.type == BT_UNKNOWN)
5816 if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER)
5817 gfc_set_default_type (sym, 1, NULL);
5819 if (sym->attr.flavor == FL_PROCEDURE && sym->attr.function)
5821 /* The specific case of an external procedure should emit an error
5822 in the case that there is no implicit type. */
5823 if (!mp_flag)
5824 gfc_set_default_type (sym, sym->attr.external, NULL);
5825 else
5827 /* Result may be in another namespace. */
5828 resolve_symbol (sym->result);
5830 sym->ts = sym->result->ts;
5831 sym->as = gfc_copy_array_spec (sym->result->as);
5832 sym->attr.dimension = sym->result->attr.dimension;
5833 sym->attr.pointer = sym->result->attr.pointer;
5834 sym->attr.allocatable = sym->result->attr.allocatable;
5839 /* Assumed size arrays and assumed shape arrays must be dummy
5840 arguments. */
5842 if (sym->as != NULL
5843 && (sym->as->type == AS_ASSUMED_SIZE
5844 || sym->as->type == AS_ASSUMED_SHAPE)
5845 && sym->attr.dummy == 0)
5847 if (sym->as->type == AS_ASSUMED_SIZE)
5848 gfc_error ("Assumed size array at %L must be a dummy argument",
5849 &sym->declared_at);
5850 else
5851 gfc_error ("Assumed shape array at %L must be a dummy argument",
5852 &sym->declared_at);
5853 return;
5856 /* Make sure symbols with known intent or optional are really dummy
5857 variable. Because of ENTRY statement, this has to be deferred
5858 until resolution time. */
5860 if (!sym->attr.dummy
5861 && (sym->attr.optional
5862 || sym->attr.intent != INTENT_UNKNOWN))
5864 gfc_error ("Symbol at %L is not a DUMMY variable", &sym->declared_at);
5865 return;
5868 /* If a derived type symbol has reached this point, without its
5869 type being declared, we have an error. Notice that most
5870 conditions that produce undefined derived types have already
5871 been dealt with. However, the likes of:
5872 implicit type(t) (t) ..... call foo (t) will get us here if
5873 the type is not declared in the scope of the implicit
5874 statement. Change the type to BT_UNKNOWN, both because it is so
5875 and to prevent an ICE. */
5876 if (sym->ts.type == BT_DERIVED
5877 && sym->ts.derived->components == NULL)
5879 gfc_error ("The derived type '%s' at %L is of type '%s', "
5880 "which has not been defined.", sym->name,
5881 &sym->declared_at, sym->ts.derived->name);
5882 sym->ts.type = BT_UNKNOWN;
5883 return;
5886 /* An assumed-size array with INTENT(OUT) shall not be of a type for which
5887 default initialization is defined (5.1.2.4.4). */
5888 if (sym->ts.type == BT_DERIVED
5889 && sym->attr.dummy
5890 && sym->attr.intent == INTENT_OUT
5891 && sym->as
5892 && sym->as->type == AS_ASSUMED_SIZE)
5894 for (c = sym->ts.derived->components; c; c = c->next)
5896 if (c->initializer)
5898 gfc_error ("The INTENT(OUT) dummy argument '%s' at %L is "
5899 "ASSUMED SIZE and so cannot have a default initializer",
5900 sym->name, &sym->declared_at);
5901 return;
5906 switch (sym->attr.flavor)
5908 case FL_VARIABLE:
5909 if (resolve_fl_variable (sym, mp_flag) == FAILURE)
5910 return;
5911 break;
5913 case FL_PROCEDURE:
5914 if (resolve_fl_procedure (sym, mp_flag) == FAILURE)
5915 return;
5916 break;
5918 case FL_NAMELIST:
5919 if (resolve_fl_namelist (sym) == FAILURE)
5920 return;
5921 break;
5923 case FL_PARAMETER:
5924 if (resolve_fl_parameter (sym) == FAILURE)
5925 return;
5927 break;
5929 default:
5931 break;
5934 /* Make sure that intrinsic exist */
5935 if (sym->attr.intrinsic
5936 && ! gfc_intrinsic_name(sym->name, 0)
5937 && ! gfc_intrinsic_name(sym->name, 1))
5938 gfc_error("Intrinsic at %L does not exist", &sym->declared_at);
5940 /* Resolve array specifier. Check as well some constraints
5941 on COMMON blocks. */
5943 check_constant = sym->attr.in_common && !sym->attr.pointer;
5944 gfc_resolve_array_spec (sym->as, check_constant);
5946 /* Resolve formal namespaces. */
5948 if (formal_ns_flag && sym != NULL && sym->formal_ns != NULL)
5950 formal_ns_save = formal_ns_flag;
5951 formal_ns_flag = 0;
5952 gfc_resolve (sym->formal_ns);
5953 formal_ns_flag = formal_ns_save;
5956 /* Check threadprivate restrictions. */
5957 if (sym->attr.threadprivate && !sym->attr.save
5958 && (!sym->attr.in_common
5959 && sym->module == NULL
5960 && (sym->ns->proc_name == NULL
5961 || sym->ns->proc_name->attr.flavor != FL_MODULE)))
5962 gfc_error ("Threadprivate at %L isn't SAVEd", &sym->declared_at);
5967 /************* Resolve DATA statements *************/
5969 static struct
5971 gfc_data_value *vnode;
5972 unsigned int left;
5974 values;
5977 /* Advance the values structure to point to the next value in the data list. */
5979 static try
5980 next_data_value (void)
5982 while (values.left == 0)
5984 if (values.vnode->next == NULL)
5985 return FAILURE;
5987 values.vnode = values.vnode->next;
5988 values.left = values.vnode->repeat;
5991 return SUCCESS;
5995 static try
5996 check_data_variable (gfc_data_variable * var, locus * where)
5998 gfc_expr *e;
5999 mpz_t size;
6000 mpz_t offset;
6001 try t;
6002 ar_type mark = AR_UNKNOWN;
6003 int i;
6004 mpz_t section_index[GFC_MAX_DIMENSIONS];
6005 gfc_ref *ref;
6006 gfc_array_ref *ar;
6008 if (gfc_resolve_expr (var->expr) == FAILURE)
6009 return FAILURE;
6011 ar = NULL;
6012 mpz_init_set_si (offset, 0);
6013 e = var->expr;
6015 if (e->expr_type != EXPR_VARIABLE)
6016 gfc_internal_error ("check_data_variable(): Bad expression");
6018 if (e->symtree->n.sym->ns->is_block_data
6019 && !e->symtree->n.sym->attr.in_common)
6021 gfc_error ("BLOCK DATA element '%s' at %L must be in COMMON",
6022 e->symtree->n.sym->name, &e->symtree->n.sym->declared_at);
6025 if (e->rank == 0)
6027 mpz_init_set_ui (size, 1);
6028 ref = NULL;
6030 else
6032 ref = e->ref;
6034 /* Find the array section reference. */
6035 for (ref = e->ref; ref; ref = ref->next)
6037 if (ref->type != REF_ARRAY)
6038 continue;
6039 if (ref->u.ar.type == AR_ELEMENT)
6040 continue;
6041 break;
6043 gcc_assert (ref);
6045 /* Set marks according to the reference pattern. */
6046 switch (ref->u.ar.type)
6048 case AR_FULL:
6049 mark = AR_FULL;
6050 break;
6052 case AR_SECTION:
6053 ar = &ref->u.ar;
6054 /* Get the start position of array section. */
6055 gfc_get_section_index (ar, section_index, &offset);
6056 mark = AR_SECTION;
6057 break;
6059 default:
6060 gcc_unreachable ();
6063 if (gfc_array_size (e, &size) == FAILURE)
6065 gfc_error ("Nonconstant array section at %L in DATA statement",
6066 &e->where);
6067 mpz_clear (offset);
6068 return FAILURE;
6072 t = SUCCESS;
6074 while (mpz_cmp_ui (size, 0) > 0)
6076 if (next_data_value () == FAILURE)
6078 gfc_error ("DATA statement at %L has more variables than values",
6079 where);
6080 t = FAILURE;
6081 break;
6084 t = gfc_check_assign (var->expr, values.vnode->expr, 0);
6085 if (t == FAILURE)
6086 break;
6088 /* If we have more than one element left in the repeat count,
6089 and we have more than one element left in the target variable,
6090 then create a range assignment. */
6091 /* ??? Only done for full arrays for now, since array sections
6092 seem tricky. */
6093 if (mark == AR_FULL && ref && ref->next == NULL
6094 && values.left > 1 && mpz_cmp_ui (size, 1) > 0)
6096 mpz_t range;
6098 if (mpz_cmp_ui (size, values.left) >= 0)
6100 mpz_init_set_ui (range, values.left);
6101 mpz_sub_ui (size, size, values.left);
6102 values.left = 0;
6104 else
6106 mpz_init_set (range, size);
6107 values.left -= mpz_get_ui (size);
6108 mpz_set_ui (size, 0);
6111 gfc_assign_data_value_range (var->expr, values.vnode->expr,
6112 offset, range);
6114 mpz_add (offset, offset, range);
6115 mpz_clear (range);
6118 /* Assign initial value to symbol. */
6119 else
6121 values.left -= 1;
6122 mpz_sub_ui (size, size, 1);
6124 gfc_assign_data_value (var->expr, values.vnode->expr, offset);
6126 if (mark == AR_FULL)
6127 mpz_add_ui (offset, offset, 1);
6129 /* Modify the array section indexes and recalculate the offset
6130 for next element. */
6131 else if (mark == AR_SECTION)
6132 gfc_advance_section (section_index, ar, &offset);
6136 if (mark == AR_SECTION)
6138 for (i = 0; i < ar->dimen; i++)
6139 mpz_clear (section_index[i]);
6142 mpz_clear (size);
6143 mpz_clear (offset);
6145 return t;
6149 static try traverse_data_var (gfc_data_variable *, locus *);
6151 /* Iterate over a list of elements in a DATA statement. */
6153 static try
6154 traverse_data_list (gfc_data_variable * var, locus * where)
6156 mpz_t trip;
6157 iterator_stack frame;
6158 gfc_expr *e;
6160 mpz_init (frame.value);
6162 mpz_init_set (trip, var->iter.end->value.integer);
6163 mpz_sub (trip, trip, var->iter.start->value.integer);
6164 mpz_add (trip, trip, var->iter.step->value.integer);
6166 mpz_div (trip, trip, var->iter.step->value.integer);
6168 mpz_set (frame.value, var->iter.start->value.integer);
6170 frame.prev = iter_stack;
6171 frame.variable = var->iter.var->symtree;
6172 iter_stack = &frame;
6174 while (mpz_cmp_ui (trip, 0) > 0)
6176 if (traverse_data_var (var->list, where) == FAILURE)
6178 mpz_clear (trip);
6179 return FAILURE;
6182 e = gfc_copy_expr (var->expr);
6183 if (gfc_simplify_expr (e, 1) == FAILURE)
6185 gfc_free_expr (e);
6186 return FAILURE;
6189 mpz_add (frame.value, frame.value, var->iter.step->value.integer);
6191 mpz_sub_ui (trip, trip, 1);
6194 mpz_clear (trip);
6195 mpz_clear (frame.value);
6197 iter_stack = frame.prev;
6198 return SUCCESS;
6202 /* Type resolve variables in the variable list of a DATA statement. */
6204 static try
6205 traverse_data_var (gfc_data_variable * var, locus * where)
6207 try t;
6209 for (; var; var = var->next)
6211 if (var->expr == NULL)
6212 t = traverse_data_list (var, where);
6213 else
6214 t = check_data_variable (var, where);
6216 if (t == FAILURE)
6217 return FAILURE;
6220 return SUCCESS;
6224 /* Resolve the expressions and iterators associated with a data statement.
6225 This is separate from the assignment checking because data lists should
6226 only be resolved once. */
6228 static try
6229 resolve_data_variables (gfc_data_variable * d)
6231 for (; d; d = d->next)
6233 if (d->list == NULL)
6235 if (gfc_resolve_expr (d->expr) == FAILURE)
6236 return FAILURE;
6238 else
6240 if (gfc_resolve_iterator (&d->iter, false) == FAILURE)
6241 return FAILURE;
6243 if (d->iter.start->expr_type != EXPR_CONSTANT
6244 || d->iter.end->expr_type != EXPR_CONSTANT
6245 || d->iter.step->expr_type != EXPR_CONSTANT)
6246 gfc_internal_error ("resolve_data_variables(): Bad iterator");
6248 if (resolve_data_variables (d->list) == FAILURE)
6249 return FAILURE;
6253 return SUCCESS;
6257 /* Resolve a single DATA statement. We implement this by storing a pointer to
6258 the value list into static variables, and then recursively traversing the
6259 variables list, expanding iterators and such. */
6261 static void
6262 resolve_data (gfc_data * d)
6264 if (resolve_data_variables (d->var) == FAILURE)
6265 return;
6267 values.vnode = d->value;
6268 values.left = (d->value == NULL) ? 0 : d->value->repeat;
6270 if (traverse_data_var (d->var, &d->where) == FAILURE)
6271 return;
6273 /* At this point, we better not have any values left. */
6275 if (next_data_value () == SUCCESS)
6276 gfc_error ("DATA statement at %L has more values than variables",
6277 &d->where);
6281 /* Determines if a variable is not 'pure', ie not assignable within a pure
6282 procedure. Returns zero if assignment is OK, nonzero if there is a problem.
6286 gfc_impure_variable (gfc_symbol * sym)
6288 if (sym->attr.use_assoc || sym->attr.in_common)
6289 return 1;
6291 if (sym->ns != gfc_current_ns)
6292 return !sym->attr.function;
6294 /* TODO: Check storage association through EQUIVALENCE statements */
6296 return 0;
6300 /* Test whether a symbol is pure or not. For a NULL pointer, checks the
6301 symbol of the current procedure. */
6304 gfc_pure (gfc_symbol * sym)
6306 symbol_attribute attr;
6308 if (sym == NULL)
6309 sym = gfc_current_ns->proc_name;
6310 if (sym == NULL)
6311 return 0;
6313 attr = sym->attr;
6315 return attr.flavor == FL_PROCEDURE && (attr.pure || attr.elemental);
6319 /* Test whether the current procedure is elemental or not. */
6322 gfc_elemental (gfc_symbol * sym)
6324 symbol_attribute attr;
6326 if (sym == NULL)
6327 sym = gfc_current_ns->proc_name;
6328 if (sym == NULL)
6329 return 0;
6330 attr = sym->attr;
6332 return attr.flavor == FL_PROCEDURE && attr.elemental;
6336 /* Warn about unused labels. */
6338 static void
6339 warn_unused_fortran_label (gfc_st_label * label)
6341 if (label == NULL)
6342 return;
6344 warn_unused_fortran_label (label->left);
6346 if (label->defined == ST_LABEL_UNKNOWN)
6347 return;
6349 switch (label->referenced)
6351 case ST_LABEL_UNKNOWN:
6352 gfc_warning ("Label %d at %L defined but not used", label->value,
6353 &label->where);
6354 break;
6356 case ST_LABEL_BAD_TARGET:
6357 gfc_warning ("Label %d at %L defined but cannot be used",
6358 label->value, &label->where);
6359 break;
6361 default:
6362 break;
6365 warn_unused_fortran_label (label->right);
6369 /* Returns the sequence type of a symbol or sequence. */
6371 static seq_type
6372 sequence_type (gfc_typespec ts)
6374 seq_type result;
6375 gfc_component *c;
6377 switch (ts.type)
6379 case BT_DERIVED:
6381 if (ts.derived->components == NULL)
6382 return SEQ_NONDEFAULT;
6384 result = sequence_type (ts.derived->components->ts);
6385 for (c = ts.derived->components->next; c; c = c->next)
6386 if (sequence_type (c->ts) != result)
6387 return SEQ_MIXED;
6389 return result;
6391 case BT_CHARACTER:
6392 if (ts.kind != gfc_default_character_kind)
6393 return SEQ_NONDEFAULT;
6395 return SEQ_CHARACTER;
6397 case BT_INTEGER:
6398 if (ts.kind != gfc_default_integer_kind)
6399 return SEQ_NONDEFAULT;
6401 return SEQ_NUMERIC;
6403 case BT_REAL:
6404 if (!(ts.kind == gfc_default_real_kind
6405 || ts.kind == gfc_default_double_kind))
6406 return SEQ_NONDEFAULT;
6408 return SEQ_NUMERIC;
6410 case BT_COMPLEX:
6411 if (ts.kind != gfc_default_complex_kind)
6412 return SEQ_NONDEFAULT;
6414 return SEQ_NUMERIC;
6416 case BT_LOGICAL:
6417 if (ts.kind != gfc_default_logical_kind)
6418 return SEQ_NONDEFAULT;
6420 return SEQ_NUMERIC;
6422 default:
6423 return SEQ_NONDEFAULT;
6428 /* Resolve derived type EQUIVALENCE object. */
6430 static try
6431 resolve_equivalence_derived (gfc_symbol *derived, gfc_symbol *sym, gfc_expr *e)
6433 gfc_symbol *d;
6434 gfc_component *c = derived->components;
6436 if (!derived)
6437 return SUCCESS;
6439 /* Shall not be an object of nonsequence derived type. */
6440 if (!derived->attr.sequence)
6442 gfc_error ("Derived type variable '%s' at %L must have SEQUENCE "
6443 "attribute to be an EQUIVALENCE object", sym->name, &e->where);
6444 return FAILURE;
6447 /* Shall not have allocatable components. */
6448 if (derived->attr.alloc_comp)
6450 gfc_error ("Derived type variable '%s' at %L cannot have ALLOCATABLE "
6451 "components to be an EQUIVALENCE object",sym->name, &e->where);
6452 return FAILURE;
6455 for (; c ; c = c->next)
6457 d = c->ts.derived;
6458 if (d && (resolve_equivalence_derived (c->ts.derived, sym, e) == FAILURE))
6459 return FAILURE;
6461 /* Shall not be an object of sequence derived type containing a pointer
6462 in the structure. */
6463 if (c->pointer)
6465 gfc_error ("Derived type variable '%s' at %L with pointer component(s) "
6466 "cannot be an EQUIVALENCE object", sym->name, &e->where);
6467 return FAILURE;
6470 if (c->initializer)
6472 gfc_error ("Derived type variable '%s' at %L with default initializer "
6473 "cannot be an EQUIVALENCE object", sym->name, &e->where);
6474 return FAILURE;
6477 return SUCCESS;
6481 /* Resolve equivalence object.
6482 An EQUIVALENCE object shall not be a dummy argument, a pointer, a target,
6483 an allocatable array, an object of nonsequence derived type, an object of
6484 sequence derived type containing a pointer at any level of component
6485 selection, an automatic object, a function name, an entry name, a result
6486 name, a named constant, a structure component, or a subobject of any of
6487 the preceding objects. A substring shall not have length zero. A
6488 derived type shall not have components with default initialization nor
6489 shall two objects of an equivalence group be initialized.
6490 The simple constraints are done in symbol.c(check_conflict) and the rest
6491 are implemented here. */
6493 static void
6494 resolve_equivalence (gfc_equiv *eq)
6496 gfc_symbol *sym;
6497 gfc_symbol *derived;
6498 gfc_symbol *first_sym;
6499 gfc_expr *e;
6500 gfc_ref *r;
6501 locus *last_where = NULL;
6502 seq_type eq_type, last_eq_type;
6503 gfc_typespec *last_ts;
6504 int object;
6505 const char *value_name;
6506 const char *msg;
6508 value_name = NULL;
6509 last_ts = &eq->expr->symtree->n.sym->ts;
6511 first_sym = eq->expr->symtree->n.sym;
6513 for (object = 1; eq; eq = eq->eq, object++)
6515 e = eq->expr;
6517 e->ts = e->symtree->n.sym->ts;
6518 /* match_varspec might not know yet if it is seeing
6519 array reference or substring reference, as it doesn't
6520 know the types. */
6521 if (e->ref && e->ref->type == REF_ARRAY)
6523 gfc_ref *ref = e->ref;
6524 sym = e->symtree->n.sym;
6526 if (sym->attr.dimension)
6528 ref->u.ar.as = sym->as;
6529 ref = ref->next;
6532 /* For substrings, convert REF_ARRAY into REF_SUBSTRING. */
6533 if (e->ts.type == BT_CHARACTER
6534 && ref
6535 && ref->type == REF_ARRAY
6536 && ref->u.ar.dimen == 1
6537 && ref->u.ar.dimen_type[0] == DIMEN_RANGE
6538 && ref->u.ar.stride[0] == NULL)
6540 gfc_expr *start = ref->u.ar.start[0];
6541 gfc_expr *end = ref->u.ar.end[0];
6542 void *mem = NULL;
6544 /* Optimize away the (:) reference. */
6545 if (start == NULL && end == NULL)
6547 if (e->ref == ref)
6548 e->ref = ref->next;
6549 else
6550 e->ref->next = ref->next;
6551 mem = ref;
6553 else
6555 ref->type = REF_SUBSTRING;
6556 if (start == NULL)
6557 start = gfc_int_expr (1);
6558 ref->u.ss.start = start;
6559 if (end == NULL && e->ts.cl)
6560 end = gfc_copy_expr (e->ts.cl->length);
6561 ref->u.ss.end = end;
6562 ref->u.ss.length = e->ts.cl;
6563 e->ts.cl = NULL;
6565 ref = ref->next;
6566 gfc_free (mem);
6569 /* Any further ref is an error. */
6570 if (ref)
6572 gcc_assert (ref->type == REF_ARRAY);
6573 gfc_error ("Syntax error in EQUIVALENCE statement at %L",
6574 &ref->u.ar.where);
6575 continue;
6579 if (gfc_resolve_expr (e) == FAILURE)
6580 continue;
6582 sym = e->symtree->n.sym;
6584 /* An equivalence statement cannot have more than one initialized
6585 object. */
6586 if (sym->value)
6588 if (value_name != NULL)
6590 gfc_error ("Initialized objects '%s' and '%s' cannot both "
6591 "be in the EQUIVALENCE statement at %L",
6592 value_name, sym->name, &e->where);
6593 continue;
6595 else
6596 value_name = sym->name;
6599 /* Shall not equivalence common block variables in a PURE procedure. */
6600 if (sym->ns->proc_name
6601 && sym->ns->proc_name->attr.pure
6602 && sym->attr.in_common)
6604 gfc_error ("Common block member '%s' at %L cannot be an EQUIVALENCE "
6605 "object in the pure procedure '%s'",
6606 sym->name, &e->where, sym->ns->proc_name->name);
6607 break;
6610 /* Shall not be a named constant. */
6611 if (e->expr_type == EXPR_CONSTANT)
6613 gfc_error ("Named constant '%s' at %L cannot be an EQUIVALENCE "
6614 "object", sym->name, &e->where);
6615 continue;
6618 derived = e->ts.derived;
6619 if (derived && resolve_equivalence_derived (derived, sym, e) == FAILURE)
6620 continue;
6622 /* Check that the types correspond correctly:
6623 Note 5.28:
6624 A numeric sequence structure may be equivalenced to another sequence
6625 structure, an object of default integer type, default real type, double
6626 precision real type, default logical type such that components of the
6627 structure ultimately only become associated to objects of the same
6628 kind. A character sequence structure may be equivalenced to an object
6629 of default character kind or another character sequence structure.
6630 Other objects may be equivalenced only to objects of the same type and
6631 kind parameters. */
6633 /* Identical types are unconditionally OK. */
6634 if (object == 1 || gfc_compare_types (last_ts, &sym->ts))
6635 goto identical_types;
6637 last_eq_type = sequence_type (*last_ts);
6638 eq_type = sequence_type (sym->ts);
6640 /* Since the pair of objects is not of the same type, mixed or
6641 non-default sequences can be rejected. */
6643 msg = "Sequence %s with mixed components in EQUIVALENCE "
6644 "statement at %L with different type objects";
6645 if ((object ==2
6646 && last_eq_type == SEQ_MIXED
6647 && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name,
6648 last_where) == FAILURE)
6649 || (eq_type == SEQ_MIXED
6650 && gfc_notify_std (GFC_STD_GNU, msg,sym->name,
6651 &e->where) == FAILURE))
6652 continue;
6654 msg = "Non-default type object or sequence %s in EQUIVALENCE "
6655 "statement at %L with objects of different type";
6656 if ((object ==2
6657 && last_eq_type == SEQ_NONDEFAULT
6658 && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name,
6659 last_where) == FAILURE)
6660 || (eq_type == SEQ_NONDEFAULT
6661 && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
6662 &e->where) == FAILURE))
6663 continue;
6665 msg ="Non-CHARACTER object '%s' in default CHARACTER "
6666 "EQUIVALENCE statement at %L";
6667 if (last_eq_type == SEQ_CHARACTER
6668 && eq_type != SEQ_CHARACTER
6669 && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
6670 &e->where) == FAILURE)
6671 continue;
6673 msg ="Non-NUMERIC object '%s' in default NUMERIC "
6674 "EQUIVALENCE statement at %L";
6675 if (last_eq_type == SEQ_NUMERIC
6676 && eq_type != SEQ_NUMERIC
6677 && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
6678 &e->where) == FAILURE)
6679 continue;
6681 identical_types:
6682 last_ts =&sym->ts;
6683 last_where = &e->where;
6685 if (!e->ref)
6686 continue;
6688 /* Shall not be an automatic array. */
6689 if (e->ref->type == REF_ARRAY
6690 && gfc_resolve_array_spec (e->ref->u.ar.as, 1) == FAILURE)
6692 gfc_error ("Array '%s' at %L with non-constant bounds cannot be "
6693 "an EQUIVALENCE object", sym->name, &e->where);
6694 continue;
6697 r = e->ref;
6698 while (r)
6700 /* Shall not be a structure component. */
6701 if (r->type == REF_COMPONENT)
6703 gfc_error ("Structure component '%s' at %L cannot be an "
6704 "EQUIVALENCE object",
6705 r->u.c.component->name, &e->where);
6706 break;
6709 /* A substring shall not have length zero. */
6710 if (r->type == REF_SUBSTRING)
6712 if (compare_bound (r->u.ss.start, r->u.ss.end) == CMP_GT)
6714 gfc_error ("Substring at %L has length zero",
6715 &r->u.ss.start->where);
6716 break;
6719 r = r->next;
6725 /* Resolve function and ENTRY types, issue diagnostics if needed. */
6727 static void
6728 resolve_fntype (gfc_namespace * ns)
6730 gfc_entry_list *el;
6731 gfc_symbol *sym;
6733 if (ns->proc_name == NULL || !ns->proc_name->attr.function)
6734 return;
6736 /* If there are any entries, ns->proc_name is the entry master
6737 synthetic symbol and ns->entries->sym actual FUNCTION symbol. */
6738 if (ns->entries)
6739 sym = ns->entries->sym;
6740 else
6741 sym = ns->proc_name;
6742 if (sym->result == sym
6743 && sym->ts.type == BT_UNKNOWN
6744 && gfc_set_default_type (sym, 0, NULL) == FAILURE
6745 && !sym->attr.untyped)
6747 gfc_error ("Function '%s' at %L has no IMPLICIT type",
6748 sym->name, &sym->declared_at);
6749 sym->attr.untyped = 1;
6752 if (sym->ts.type == BT_DERIVED && !sym->ts.derived->attr.use_assoc
6753 && !gfc_check_access (sym->ts.derived->attr.access,
6754 sym->ts.derived->ns->default_access)
6755 && gfc_check_access (sym->attr.access, sym->ns->default_access))
6757 gfc_error ("PUBLIC function '%s' at %L cannot be of PRIVATE type '%s'",
6758 sym->name, &sym->declared_at, sym->ts.derived->name);
6761 /* Make sure that the type of a module derived type function is in the
6762 module namespace, by copying it from the namespace's derived type
6763 list, if necessary. */
6764 if (sym->ts.type == BT_DERIVED
6765 && sym->ns->proc_name->attr.flavor == FL_MODULE
6766 && sym->ts.derived->ns
6767 && sym->ns != sym->ts.derived->ns)
6769 gfc_dt_list *dt = sym->ns->derived_types;
6771 for (; dt; dt = dt->next)
6772 if (gfc_compare_derived_types (sym->ts.derived, dt->derived))
6773 sym->ts.derived = dt->derived;
6776 if (ns->entries)
6777 for (el = ns->entries->next; el; el = el->next)
6779 if (el->sym->result == el->sym
6780 && el->sym->ts.type == BT_UNKNOWN
6781 && gfc_set_default_type (el->sym, 0, NULL) == FAILURE
6782 && !el->sym->attr.untyped)
6784 gfc_error ("ENTRY '%s' at %L has no IMPLICIT type",
6785 el->sym->name, &el->sym->declared_at);
6786 el->sym->attr.untyped = 1;
6791 /* 12.3.2.1.1 Defined operators. */
6793 static void
6794 gfc_resolve_uops(gfc_symtree *symtree)
6796 gfc_interface *itr;
6797 gfc_symbol *sym;
6798 gfc_formal_arglist *formal;
6800 if (symtree == NULL)
6801 return;
6803 gfc_resolve_uops (symtree->left);
6804 gfc_resolve_uops (symtree->right);
6806 for (itr = symtree->n.uop->operator; itr; itr = itr->next)
6808 sym = itr->sym;
6809 if (!sym->attr.function)
6810 gfc_error("User operator procedure '%s' at %L must be a FUNCTION",
6811 sym->name, &sym->declared_at);
6813 if (sym->ts.type == BT_CHARACTER
6814 && !(sym->ts.cl && sym->ts.cl->length)
6815 && !(sym->result && sym->result->ts.cl && sym->result->ts.cl->length))
6816 gfc_error("User operator procedure '%s' at %L cannot be assumed character "
6817 "length", sym->name, &sym->declared_at);
6819 formal = sym->formal;
6820 if (!formal || !formal->sym)
6822 gfc_error("User operator procedure '%s' at %L must have at least "
6823 "one argument", sym->name, &sym->declared_at);
6824 continue;
6827 if (formal->sym->attr.intent != INTENT_IN)
6828 gfc_error ("First argument of operator interface at %L must be "
6829 "INTENT(IN)", &sym->declared_at);
6831 if (formal->sym->attr.optional)
6832 gfc_error ("First argument of operator interface at %L cannot be "
6833 "optional", &sym->declared_at);
6835 formal = formal->next;
6836 if (!formal || !formal->sym)
6837 continue;
6839 if (formal->sym->attr.intent != INTENT_IN)
6840 gfc_error ("Second argument of operator interface at %L must be "
6841 "INTENT(IN)", &sym->declared_at);
6843 if (formal->sym->attr.optional)
6844 gfc_error ("Second argument of operator interface at %L cannot be "
6845 "optional", &sym->declared_at);
6847 if (formal->next)
6848 gfc_error ("Operator interface at %L must have, at most, two "
6849 "arguments", &sym->declared_at);
6854 /* Examine all of the expressions associated with a program unit,
6855 assign types to all intermediate expressions, make sure that all
6856 assignments are to compatible types and figure out which names
6857 refer to which functions or subroutines. It doesn't check code
6858 block, which is handled by resolve_code. */
6860 static void
6861 resolve_types (gfc_namespace * ns)
6863 gfc_namespace *n;
6864 gfc_charlen *cl;
6865 gfc_data *d;
6866 gfc_equiv *eq;
6868 gfc_current_ns = ns;
6870 resolve_entries (ns);
6872 resolve_contained_functions (ns);
6874 gfc_traverse_ns (ns, resolve_symbol);
6876 resolve_fntype (ns);
6878 for (n = ns->contained; n; n = n->sibling)
6880 if (gfc_pure (ns->proc_name) && !gfc_pure (n->proc_name))
6881 gfc_error ("Contained procedure '%s' at %L of a PURE procedure must "
6882 "also be PURE", n->proc_name->name,
6883 &n->proc_name->declared_at);
6885 resolve_types (n);
6888 forall_flag = 0;
6889 gfc_check_interfaces (ns);
6891 for (cl = ns->cl_list; cl; cl = cl->next)
6892 resolve_charlen (cl);
6894 gfc_traverse_ns (ns, resolve_values);
6896 if (ns->save_all)
6897 gfc_save_all (ns);
6899 iter_stack = NULL;
6900 for (d = ns->data; d; d = d->next)
6901 resolve_data (d);
6903 iter_stack = NULL;
6904 gfc_traverse_ns (ns, gfc_formalize_init_value);
6906 for (eq = ns->equiv; eq; eq = eq->next)
6907 resolve_equivalence (eq);
6909 /* Warn about unused labels. */
6910 if (warn_unused_label)
6911 warn_unused_fortran_label (ns->st_labels);
6913 gfc_resolve_uops (ns->uop_root);
6917 /* Call resolve_code recursively. */
6919 static void
6920 resolve_codes (gfc_namespace * ns)
6922 gfc_namespace *n;
6924 for (n = ns->contained; n; n = n->sibling)
6925 resolve_codes (n);
6927 gfc_current_ns = ns;
6928 cs_base = NULL;
6929 /* Set to an out of range value. */
6930 current_entry_id = -1;
6931 resolve_code (ns->code, ns);
6935 /* This function is called after a complete program unit has been compiled.
6936 Its purpose is to examine all of the expressions associated with a program
6937 unit, assign types to all intermediate expressions, make sure that all
6938 assignments are to compatible types and figure out which names refer to
6939 which functions or subroutines. */
6941 void
6942 gfc_resolve (gfc_namespace * ns)
6944 gfc_namespace *old_ns;
6946 old_ns = gfc_current_ns;
6948 resolve_types (ns);
6949 resolve_codes (ns);
6951 gfc_current_ns = old_ns;