* configure.ac: Don't check AC_LIBTOOL_DLOPEN if using newlib.
[official-gcc/alias-decl.git] / gcc / fortran / resolve.c
blob6338b068ecce3845f3e959dd118b574658999733
1 /* Perform type resolution on the various stuctures.
2 Copyright (C) 2001, 2002, 2003, 2004, 2005, 2006, 2007, 2008
3 Free Software Foundation, Inc.
4 Contributed by Andy Vaught
6 This file is part of GCC.
8 GCC is free software; you can redistribute it and/or modify it under
9 the terms of the GNU General Public License as published by the Free
10 Software Foundation; either version 3, 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 COPYING3. If not see
20 <http://www.gnu.org/licenses/>. */
22 #include "config.h"
23 #include "system.h"
24 #include "flags.h"
25 #include "gfortran.h"
26 #include "obstack.h"
27 #include "bitmap.h"
28 #include "arith.h" /* For gfc_compare_expr(). */
29 #include "dependency.h"
30 #include "data.h"
31 #include "target-memory.h" /* for gfc_simplify_transfer */
33 /* Types used in equivalence statements. */
35 typedef enum seq_type
37 SEQ_NONDEFAULT, SEQ_NUMERIC, SEQ_CHARACTER, SEQ_MIXED
39 seq_type;
41 /* Stack to keep track of the nesting of blocks as we move through the
42 code. See resolve_branch() and resolve_code(). */
44 typedef struct code_stack
46 struct gfc_code *head, *current, *tail;
47 struct code_stack *prev;
49 /* This bitmap keeps track of the targets valid for a branch from
50 inside this block. */
51 bitmap reachable_labels;
53 code_stack;
55 static code_stack *cs_base = NULL;
58 /* Nonzero if we're inside a FORALL block. */
60 static int forall_flag;
62 /* Nonzero if we're inside a OpenMP WORKSHARE or PARALLEL WORKSHARE block. */
64 static int omp_workshare_flag;
66 /* Nonzero if we are processing a formal arglist. The corresponding function
67 resets the flag each time that it is read. */
68 static int formal_arg_flag = 0;
70 /* True if we are resolving a specification expression. */
71 static int specification_expr = 0;
73 /* The id of the last entry seen. */
74 static int current_entry_id;
76 /* We use bitmaps to determine if a branch target is valid. */
77 static bitmap_obstack labels_obstack;
79 int
80 gfc_is_formal_arg (void)
82 return formal_arg_flag;
85 /* Resolve types of formal argument lists. These have to be done early so that
86 the formal argument lists of module procedures can be copied to the
87 containing module before the individual procedures are resolved
88 individually. We also resolve argument lists of procedures in interface
89 blocks because they are self-contained scoping units.
91 Since a dummy argument cannot be a non-dummy procedure, the only
92 resort left for untyped names are the IMPLICIT types. */
94 static void
95 resolve_formal_arglist (gfc_symbol *proc)
97 gfc_formal_arglist *f;
98 gfc_symbol *sym;
99 int i;
101 if (proc->result != NULL)
102 sym = proc->result;
103 else
104 sym = proc;
106 if (gfc_elemental (proc)
107 || sym->attr.pointer || sym->attr.allocatable
108 || (sym->as && sym->as->rank > 0))
110 proc->attr.always_explicit = 1;
111 sym->attr.always_explicit = 1;
114 formal_arg_flag = 1;
116 for (f = proc->formal; f; f = f->next)
118 sym = f->sym;
120 if (sym == NULL)
122 /* Alternate return placeholder. */
123 if (gfc_elemental (proc))
124 gfc_error ("Alternate return specifier in elemental subroutine "
125 "'%s' at %L is not allowed", proc->name,
126 &proc->declared_at);
127 if (proc->attr.function)
128 gfc_error ("Alternate return specifier in function "
129 "'%s' at %L is not allowed", proc->name,
130 &proc->declared_at);
131 continue;
134 if (sym->attr.if_source != IFSRC_UNKNOWN)
135 resolve_formal_arglist (sym);
137 if (sym->attr.subroutine || sym->attr.external || sym->attr.intrinsic)
139 if (gfc_pure (proc) && !gfc_pure (sym))
141 gfc_error ("Dummy procedure '%s' of PURE procedure at %L must "
142 "also be PURE", sym->name, &sym->declared_at);
143 continue;
146 if (gfc_elemental (proc))
148 gfc_error ("Dummy procedure at %L not allowed in ELEMENTAL "
149 "procedure", &sym->declared_at);
150 continue;
153 if (sym->attr.function
154 && sym->ts.type == BT_UNKNOWN
155 && sym->attr.intrinsic)
157 gfc_intrinsic_sym *isym;
158 isym = gfc_find_function (sym->name);
159 if (isym == NULL || !isym->specific)
161 gfc_error ("Unable to find a specific INTRINSIC procedure "
162 "for the reference '%s' at %L", sym->name,
163 &sym->declared_at);
165 sym->ts = isym->ts;
168 continue;
171 if (sym->ts.type == BT_UNKNOWN)
173 if (!sym->attr.function || sym->result == sym)
174 gfc_set_default_type (sym, 1, sym->ns);
177 gfc_resolve_array_spec (sym->as, 0);
179 /* We can't tell if an array with dimension (:) is assumed or deferred
180 shape until we know if it has the pointer or allocatable attributes.
182 if (sym->as && sym->as->rank > 0 && sym->as->type == AS_DEFERRED
183 && !(sym->attr.pointer || sym->attr.allocatable))
185 sym->as->type = AS_ASSUMED_SHAPE;
186 for (i = 0; i < sym->as->rank; i++)
187 sym->as->lower[i] = gfc_int_expr (1);
190 if ((sym->as && sym->as->rank > 0 && sym->as->type == AS_ASSUMED_SHAPE)
191 || sym->attr.pointer || sym->attr.allocatable || sym->attr.target
192 || sym->attr.optional)
194 proc->attr.always_explicit = 1;
195 if (proc->result)
196 proc->result->attr.always_explicit = 1;
199 /* If the flavor is unknown at this point, it has to be a variable.
200 A procedure specification would have already set the type. */
202 if (sym->attr.flavor == FL_UNKNOWN)
203 gfc_add_flavor (&sym->attr, FL_VARIABLE, sym->name, &sym->declared_at);
205 if (gfc_pure (proc) && !sym->attr.pointer
206 && sym->attr.flavor != FL_PROCEDURE)
208 if (proc->attr.function && sym->attr.intent != INTENT_IN)
209 gfc_error ("Argument '%s' of pure function '%s' at %L must be "
210 "INTENT(IN)", sym->name, proc->name,
211 &sym->declared_at);
213 if (proc->attr.subroutine && sym->attr.intent == INTENT_UNKNOWN)
214 gfc_error ("Argument '%s' of pure subroutine '%s' at %L must "
215 "have its INTENT specified", sym->name, proc->name,
216 &sym->declared_at);
219 if (gfc_elemental (proc))
221 if (sym->as != NULL)
223 gfc_error ("Argument '%s' of elemental procedure at %L must "
224 "be scalar", sym->name, &sym->declared_at);
225 continue;
228 if (sym->attr.pointer)
230 gfc_error ("Argument '%s' of elemental procedure at %L cannot "
231 "have the POINTER attribute", sym->name,
232 &sym->declared_at);
233 continue;
236 if (sym->attr.flavor == FL_PROCEDURE)
238 gfc_error ("Dummy procedure '%s' not allowed in elemental "
239 "procedure '%s' at %L", sym->name, proc->name,
240 &sym->declared_at);
241 continue;
245 /* Each dummy shall be specified to be scalar. */
246 if (proc->attr.proc == PROC_ST_FUNCTION)
248 if (sym->as != NULL)
250 gfc_error ("Argument '%s' of statement function at %L must "
251 "be scalar", sym->name, &sym->declared_at);
252 continue;
255 if (sym->ts.type == BT_CHARACTER)
257 gfc_charlen *cl = sym->ts.cl;
258 if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
260 gfc_error ("Character-valued argument '%s' of statement "
261 "function at %L must have constant length",
262 sym->name, &sym->declared_at);
263 continue;
268 formal_arg_flag = 0;
272 /* Work function called when searching for symbols that have argument lists
273 associated with them. */
275 static void
276 find_arglists (gfc_symbol *sym)
278 if (sym->attr.if_source == IFSRC_UNKNOWN || sym->ns != gfc_current_ns)
279 return;
281 resolve_formal_arglist (sym);
285 /* Given a namespace, resolve all formal argument lists within the namespace.
288 static void
289 resolve_formal_arglists (gfc_namespace *ns)
291 if (ns == NULL)
292 return;
294 gfc_traverse_ns (ns, find_arglists);
298 static void
299 resolve_contained_fntype (gfc_symbol *sym, gfc_namespace *ns)
301 try t;
303 /* If this namespace is not a function or an entry master function,
304 ignore it. */
305 if (! sym || !(sym->attr.function || sym->attr.flavor == FL_VARIABLE)
306 || sym->attr.entry_master)
307 return;
309 /* Try to find out of what the return type is. */
310 if (sym->result->ts.type == BT_UNKNOWN)
312 t = gfc_set_default_type (sym->result, 0, ns);
314 if (t == FAILURE && !sym->result->attr.untyped)
316 if (sym->result == sym)
317 gfc_error ("Contained function '%s' at %L has no IMPLICIT type",
318 sym->name, &sym->declared_at);
319 else
320 gfc_error ("Result '%s' of contained function '%s' at %L has "
321 "no IMPLICIT type", sym->result->name, sym->name,
322 &sym->result->declared_at);
323 sym->result->attr.untyped = 1;
327 /* Fortran 95 Draft Standard, page 51, Section 5.1.1.5, on the Character
328 type, lists the only ways a character length value of * can be used:
329 dummy arguments of procedures, named constants, and function results
330 in external functions. Internal function results are not on that list;
331 ergo, not permitted. */
333 if (sym->result->ts.type == BT_CHARACTER)
335 gfc_charlen *cl = sym->result->ts.cl;
336 if (!cl || !cl->length)
337 gfc_error ("Character-valued internal function '%s' at %L must "
338 "not be assumed length", sym->name, &sym->declared_at);
343 /* Add NEW_ARGS to the formal argument list of PROC, taking care not to
344 introduce duplicates. */
346 static void
347 merge_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
349 gfc_formal_arglist *f, *new_arglist;
350 gfc_symbol *new_sym;
352 for (; new_args != NULL; new_args = new_args->next)
354 new_sym = new_args->sym;
355 /* See if this arg is already in the formal argument list. */
356 for (f = proc->formal; f; f = f->next)
358 if (new_sym == f->sym)
359 break;
362 if (f)
363 continue;
365 /* Add a new argument. Argument order is not important. */
366 new_arglist = gfc_get_formal_arglist ();
367 new_arglist->sym = new_sym;
368 new_arglist->next = proc->formal;
369 proc->formal = new_arglist;
374 /* Flag the arguments that are not present in all entries. */
376 static void
377 check_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
379 gfc_formal_arglist *f, *head;
380 head = new_args;
382 for (f = proc->formal; f; f = f->next)
384 if (f->sym == NULL)
385 continue;
387 for (new_args = head; new_args; new_args = new_args->next)
389 if (new_args->sym == f->sym)
390 break;
393 if (new_args)
394 continue;
396 f->sym->attr.not_always_present = 1;
401 /* Resolve alternate entry points. If a symbol has multiple entry points we
402 create a new master symbol for the main routine, and turn the existing
403 symbol into an entry point. */
405 static void
406 resolve_entries (gfc_namespace *ns)
408 gfc_namespace *old_ns;
409 gfc_code *c;
410 gfc_symbol *proc;
411 gfc_entry_list *el;
412 char name[GFC_MAX_SYMBOL_LEN + 1];
413 static int master_count = 0;
415 if (ns->proc_name == NULL)
416 return;
418 /* No need to do anything if this procedure doesn't have alternate entry
419 points. */
420 if (!ns->entries)
421 return;
423 /* We may already have resolved alternate entry points. */
424 if (ns->proc_name->attr.entry_master)
425 return;
427 /* If this isn't a procedure something has gone horribly wrong. */
428 gcc_assert (ns->proc_name->attr.flavor == FL_PROCEDURE);
430 /* Remember the current namespace. */
431 old_ns = gfc_current_ns;
433 gfc_current_ns = ns;
435 /* Add the main entry point to the list of entry points. */
436 el = gfc_get_entry_list ();
437 el->sym = ns->proc_name;
438 el->id = 0;
439 el->next = ns->entries;
440 ns->entries = el;
441 ns->proc_name->attr.entry = 1;
443 /* If it is a module function, it needs to be in the right namespace
444 so that gfc_get_fake_result_decl can gather up the results. The
445 need for this arose in get_proc_name, where these beasts were
446 left in their own namespace, to keep prior references linked to
447 the entry declaration.*/
448 if (ns->proc_name->attr.function
449 && ns->parent && ns->parent->proc_name->attr.flavor == FL_MODULE)
450 el->sym->ns = ns;
452 /* Do the same for entries where the master is not a module
453 procedure. These are retained in the module namespace because
454 of the module procedure declaration. */
455 for (el = el->next; el; el = el->next)
456 if (el->sym->ns->proc_name->attr.flavor == FL_MODULE
457 && el->sym->attr.mod_proc)
458 el->sym->ns = ns;
459 el = ns->entries;
461 /* Add an entry statement for it. */
462 c = gfc_get_code ();
463 c->op = EXEC_ENTRY;
464 c->ext.entry = el;
465 c->next = ns->code;
466 ns->code = c;
468 /* Create a new symbol for the master function. */
469 /* Give the internal function a unique name (within this file).
470 Also include the function name so the user has some hope of figuring
471 out what is going on. */
472 snprintf (name, GFC_MAX_SYMBOL_LEN, "master.%d.%s",
473 master_count++, ns->proc_name->name);
474 gfc_get_ha_symbol (name, &proc);
475 gcc_assert (proc != NULL);
477 gfc_add_procedure (&proc->attr, PROC_INTERNAL, proc->name, NULL);
478 if (ns->proc_name->attr.subroutine)
479 gfc_add_subroutine (&proc->attr, proc->name, NULL);
480 else
482 gfc_symbol *sym;
483 gfc_typespec *ts, *fts;
484 gfc_array_spec *as, *fas;
485 gfc_add_function (&proc->attr, proc->name, NULL);
486 proc->result = proc;
487 fas = ns->entries->sym->as;
488 fas = fas ? fas : ns->entries->sym->result->as;
489 fts = &ns->entries->sym->result->ts;
490 if (fts->type == BT_UNKNOWN)
491 fts = gfc_get_default_type (ns->entries->sym->result, NULL);
492 for (el = ns->entries->next; el; el = el->next)
494 ts = &el->sym->result->ts;
495 as = el->sym->as;
496 as = as ? as : el->sym->result->as;
497 if (ts->type == BT_UNKNOWN)
498 ts = gfc_get_default_type (el->sym->result, NULL);
500 if (! gfc_compare_types (ts, fts)
501 || (el->sym->result->attr.dimension
502 != ns->entries->sym->result->attr.dimension)
503 || (el->sym->result->attr.pointer
504 != ns->entries->sym->result->attr.pointer))
505 break;
506 else if (as && fas && ns->entries->sym->result != el->sym->result
507 && gfc_compare_array_spec (as, fas) == 0)
508 gfc_error ("Function %s at %L has entries with mismatched "
509 "array specifications", ns->entries->sym->name,
510 &ns->entries->sym->declared_at);
511 /* The characteristics need to match and thus both need to have
512 the same string length, i.e. both len=*, or both len=4.
513 Having both len=<variable> is also possible, but difficult to
514 check at compile time. */
515 else if (ts->type == BT_CHARACTER && ts->cl && fts->cl
516 && (((ts->cl->length && !fts->cl->length)
517 ||(!ts->cl->length && fts->cl->length))
518 || (ts->cl->length
519 && ts->cl->length->expr_type
520 != fts->cl->length->expr_type)
521 || (ts->cl->length
522 && ts->cl->length->expr_type == EXPR_CONSTANT
523 && mpz_cmp (ts->cl->length->value.integer,
524 fts->cl->length->value.integer) != 0)))
525 gfc_notify_std (GFC_STD_GNU, "Extension: Function %s at %L with "
526 "entries returning variables of different "
527 "string lengths", ns->entries->sym->name,
528 &ns->entries->sym->declared_at);
531 if (el == NULL)
533 sym = ns->entries->sym->result;
534 /* All result types the same. */
535 proc->ts = *fts;
536 if (sym->attr.dimension)
537 gfc_set_array_spec (proc, gfc_copy_array_spec (sym->as), NULL);
538 if (sym->attr.pointer)
539 gfc_add_pointer (&proc->attr, NULL);
541 else
543 /* Otherwise the result will be passed through a union by
544 reference. */
545 proc->attr.mixed_entry_master = 1;
546 for (el = ns->entries; el; el = el->next)
548 sym = el->sym->result;
549 if (sym->attr.dimension)
551 if (el == ns->entries)
552 gfc_error ("FUNCTION result %s can't be an array in "
553 "FUNCTION %s at %L", sym->name,
554 ns->entries->sym->name, &sym->declared_at);
555 else
556 gfc_error ("ENTRY result %s can't be an array in "
557 "FUNCTION %s at %L", sym->name,
558 ns->entries->sym->name, &sym->declared_at);
560 else if (sym->attr.pointer)
562 if (el == ns->entries)
563 gfc_error ("FUNCTION result %s can't be a POINTER in "
564 "FUNCTION %s at %L", sym->name,
565 ns->entries->sym->name, &sym->declared_at);
566 else
567 gfc_error ("ENTRY result %s can't be a POINTER in "
568 "FUNCTION %s at %L", sym->name,
569 ns->entries->sym->name, &sym->declared_at);
571 else
573 ts = &sym->ts;
574 if (ts->type == BT_UNKNOWN)
575 ts = gfc_get_default_type (sym, NULL);
576 switch (ts->type)
578 case BT_INTEGER:
579 if (ts->kind == gfc_default_integer_kind)
580 sym = NULL;
581 break;
582 case BT_REAL:
583 if (ts->kind == gfc_default_real_kind
584 || ts->kind == gfc_default_double_kind)
585 sym = NULL;
586 break;
587 case BT_COMPLEX:
588 if (ts->kind == gfc_default_complex_kind)
589 sym = NULL;
590 break;
591 case BT_LOGICAL:
592 if (ts->kind == gfc_default_logical_kind)
593 sym = NULL;
594 break;
595 case BT_UNKNOWN:
596 /* We will issue error elsewhere. */
597 sym = NULL;
598 break;
599 default:
600 break;
602 if (sym)
604 if (el == ns->entries)
605 gfc_error ("FUNCTION result %s can't be of type %s "
606 "in FUNCTION %s at %L", sym->name,
607 gfc_typename (ts), ns->entries->sym->name,
608 &sym->declared_at);
609 else
610 gfc_error ("ENTRY result %s can't be of type %s "
611 "in FUNCTION %s at %L", sym->name,
612 gfc_typename (ts), ns->entries->sym->name,
613 &sym->declared_at);
619 proc->attr.access = ACCESS_PRIVATE;
620 proc->attr.entry_master = 1;
622 /* Merge all the entry point arguments. */
623 for (el = ns->entries; el; el = el->next)
624 merge_argument_lists (proc, el->sym->formal);
626 /* Check the master formal arguments for any that are not
627 present in all entry points. */
628 for (el = ns->entries; el; el = el->next)
629 check_argument_lists (proc, el->sym->formal);
631 /* Use the master function for the function body. */
632 ns->proc_name = proc;
634 /* Finalize the new symbols. */
635 gfc_commit_symbols ();
637 /* Restore the original namespace. */
638 gfc_current_ns = old_ns;
642 static bool
643 has_default_initializer (gfc_symbol *der)
645 gfc_component *c;
647 gcc_assert (der->attr.flavor == FL_DERIVED);
648 for (c = der->components; c; c = c->next)
649 if ((c->ts.type != BT_DERIVED && c->initializer)
650 || (c->ts.type == BT_DERIVED
651 && (!c->pointer && has_default_initializer (c->ts.derived))))
652 break;
654 return c != NULL;
657 /* Resolve common variables. */
658 static void
659 resolve_common_vars (gfc_symbol *sym, bool named_common)
661 gfc_symbol *csym = sym;
663 for (; csym; csym = csym->common_next)
665 if (csym->value || csym->attr.data)
667 if (!csym->ns->is_block_data)
668 gfc_notify_std (GFC_STD_GNU, "Variable '%s' at %L is in COMMON "
669 "but only in BLOCK DATA initialization is "
670 "allowed", csym->name, &csym->declared_at);
671 else if (!named_common)
672 gfc_notify_std (GFC_STD_GNU, "Initialized variable '%s' at %L is "
673 "in a blank COMMON but initialization is only "
674 "allowed in named common blocks", csym->name,
675 &csym->declared_at);
678 if (csym->ts.type != BT_DERIVED)
679 continue;
681 if (!(csym->ts.derived->attr.sequence
682 || csym->ts.derived->attr.is_bind_c))
683 gfc_error_now ("Derived type variable '%s' in COMMON at %L "
684 "has neither the SEQUENCE nor the BIND(C) "
685 "attribute", csym->name, &csym->declared_at);
686 if (csym->ts.derived->attr.alloc_comp)
687 gfc_error_now ("Derived type variable '%s' in COMMON at %L "
688 "has an ultimate component that is "
689 "allocatable", csym->name, &csym->declared_at);
690 if (has_default_initializer (csym->ts.derived))
691 gfc_error_now ("Derived type variable '%s' in COMMON at %L "
692 "may not have default initializer", csym->name,
693 &csym->declared_at);
697 /* Resolve common blocks. */
698 static void
699 resolve_common_blocks (gfc_symtree *common_root)
701 gfc_symbol *sym;
703 if (common_root == NULL)
704 return;
706 if (common_root->left)
707 resolve_common_blocks (common_root->left);
708 if (common_root->right)
709 resolve_common_blocks (common_root->right);
711 resolve_common_vars (common_root->n.common->head, true);
713 gfc_find_symbol (common_root->name, gfc_current_ns, 0, &sym);
714 if (sym == NULL)
715 return;
717 if (sym->attr.flavor == FL_PARAMETER)
718 gfc_error ("COMMON block '%s' at %L is used as PARAMETER at %L",
719 sym->name, &common_root->n.common->where, &sym->declared_at);
721 if (sym->attr.intrinsic)
722 gfc_error ("COMMON block '%s' at %L is also an intrinsic procedure",
723 sym->name, &common_root->n.common->where);
724 else if (sym->attr.result
725 ||(sym->attr.function && gfc_current_ns->proc_name == sym))
726 gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
727 "that is also a function result", sym->name,
728 &common_root->n.common->where);
729 else if (sym->attr.flavor == FL_PROCEDURE && sym->attr.proc != PROC_INTERNAL
730 && sym->attr.proc != PROC_ST_FUNCTION)
731 gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
732 "that is also a global procedure", sym->name,
733 &common_root->n.common->where);
737 /* Resolve contained function types. Because contained functions can call one
738 another, they have to be worked out before any of the contained procedures
739 can be resolved.
741 The good news is that if a function doesn't already have a type, the only
742 way it can get one is through an IMPLICIT type or a RESULT variable, because
743 by definition contained functions are contained namespace they're contained
744 in, not in a sibling or parent namespace. */
746 static void
747 resolve_contained_functions (gfc_namespace *ns)
749 gfc_namespace *child;
750 gfc_entry_list *el;
752 resolve_formal_arglists (ns);
754 for (child = ns->contained; child; child = child->sibling)
756 /* Resolve alternate entry points first. */
757 resolve_entries (child);
759 /* Then check function return types. */
760 resolve_contained_fntype (child->proc_name, child);
761 for (el = child->entries; el; el = el->next)
762 resolve_contained_fntype (el->sym, child);
767 /* Resolve all of the elements of a structure constructor and make sure that
768 the types are correct. */
770 static try
771 resolve_structure_cons (gfc_expr *expr)
773 gfc_constructor *cons;
774 gfc_component *comp;
775 try t;
776 symbol_attribute a;
778 t = SUCCESS;
779 cons = expr->value.constructor;
780 /* A constructor may have references if it is the result of substituting a
781 parameter variable. In this case we just pull out the component we
782 want. */
783 if (expr->ref)
784 comp = expr->ref->u.c.sym->components;
785 else
786 comp = expr->ts.derived->components;
788 /* See if the user is trying to invoke a structure constructor for one of
789 the iso_c_binding derived types. */
790 if (expr->ts.derived && expr->ts.derived->ts.is_iso_c && cons
791 && cons->expr != NULL)
793 gfc_error ("Components of structure constructor '%s' at %L are PRIVATE",
794 expr->ts.derived->name, &(expr->where));
795 return FAILURE;
798 for (; comp; comp = comp->next, cons = cons->next)
800 int rank;
802 if (!cons->expr)
803 continue;
805 if (gfc_resolve_expr (cons->expr) == FAILURE)
807 t = FAILURE;
808 continue;
811 rank = comp->as ? comp->as->rank : 0;
812 if (cons->expr->expr_type != EXPR_NULL && rank != cons->expr->rank
813 && (comp->allocatable || cons->expr->rank))
815 gfc_error ("The rank of the element in the derived type "
816 "constructor at %L does not match that of the "
817 "component (%d/%d)", &cons->expr->where,
818 cons->expr->rank, rank);
819 t = FAILURE;
822 /* If we don't have the right type, try to convert it. */
824 if (!gfc_compare_types (&cons->expr->ts, &comp->ts))
826 t = FAILURE;
827 if (comp->pointer && cons->expr->ts.type != BT_UNKNOWN)
828 gfc_error ("The element in the derived type constructor at %L, "
829 "for pointer component '%s', is %s but should be %s",
830 &cons->expr->where, comp->name,
831 gfc_basic_typename (cons->expr->ts.type),
832 gfc_basic_typename (comp->ts.type));
833 else
834 t = gfc_convert_type (cons->expr, &comp->ts, 1);
837 if (cons->expr->expr_type == EXPR_NULL
838 && !(comp->pointer || comp->allocatable))
840 t = FAILURE;
841 gfc_error ("The NULL in the derived type constructor at %L is "
842 "being applied to component '%s', which is neither "
843 "a POINTER nor ALLOCATABLE", &cons->expr->where,
844 comp->name);
847 if (!comp->pointer || cons->expr->expr_type == EXPR_NULL)
848 continue;
850 a = gfc_expr_attr (cons->expr);
852 if (!a.pointer && !a.target)
854 t = FAILURE;
855 gfc_error ("The element in the derived type constructor at %L, "
856 "for pointer component '%s' should be a POINTER or "
857 "a TARGET", &cons->expr->where, comp->name);
861 return t;
865 /****************** Expression name resolution ******************/
867 /* Returns 0 if a symbol was not declared with a type or
868 attribute declaration statement, nonzero otherwise. */
870 static int
871 was_declared (gfc_symbol *sym)
873 symbol_attribute a;
875 a = sym->attr;
877 if (!a.implicit_type && sym->ts.type != BT_UNKNOWN)
878 return 1;
880 if (a.allocatable || a.dimension || a.dummy || a.external || a.intrinsic
881 || a.optional || a.pointer || a.save || a.target || a.volatile_
882 || a.value || a.access != ACCESS_UNKNOWN || a.intent != INTENT_UNKNOWN)
883 return 1;
885 return 0;
889 /* Determine if a symbol is generic or not. */
891 static int
892 generic_sym (gfc_symbol *sym)
894 gfc_symbol *s;
896 if (sym->attr.generic ||
897 (sym->attr.intrinsic && gfc_generic_intrinsic (sym->name)))
898 return 1;
900 if (was_declared (sym) || sym->ns->parent == NULL)
901 return 0;
903 gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
905 if (s != NULL)
907 if (s == sym)
908 return 0;
909 else
910 return generic_sym (s);
913 return 0;
917 /* Determine if a symbol is specific or not. */
919 static int
920 specific_sym (gfc_symbol *sym)
922 gfc_symbol *s;
924 if (sym->attr.if_source == IFSRC_IFBODY
925 || sym->attr.proc == PROC_MODULE
926 || sym->attr.proc == PROC_INTERNAL
927 || sym->attr.proc == PROC_ST_FUNCTION
928 || (sym->attr.intrinsic && gfc_specific_intrinsic (sym->name))
929 || sym->attr.external)
930 return 1;
932 if (was_declared (sym) || sym->ns->parent == NULL)
933 return 0;
935 gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
937 return (s == NULL) ? 0 : specific_sym (s);
941 /* Figure out if the procedure is specific, generic or unknown. */
943 typedef enum
944 { PTYPE_GENERIC = 1, PTYPE_SPECIFIC, PTYPE_UNKNOWN }
945 proc_type;
947 static proc_type
948 procedure_kind (gfc_symbol *sym)
950 if (generic_sym (sym))
951 return PTYPE_GENERIC;
953 if (specific_sym (sym))
954 return PTYPE_SPECIFIC;
956 return PTYPE_UNKNOWN;
959 /* Check references to assumed size arrays. The flag need_full_assumed_size
960 is nonzero when matching actual arguments. */
962 static int need_full_assumed_size = 0;
964 static bool
965 check_assumed_size_reference (gfc_symbol *sym, gfc_expr *e)
967 if (need_full_assumed_size || !(sym->as && sym->as->type == AS_ASSUMED_SIZE))
968 return false;
970 if ((e->ref->u.ar.end[e->ref->u.ar.as->rank - 1] == NULL)
971 && (e->ref->u.ar.as->type == AS_ASSUMED_SIZE)
972 && (e->ref->u.ar.type == DIMEN_ELEMENT))
974 gfc_error ("The upper bound in the last dimension must "
975 "appear in the reference to the assumed size "
976 "array '%s' at %L", sym->name, &e->where);
977 return true;
979 return false;
983 /* Look for bad assumed size array references in argument expressions
984 of elemental and array valued intrinsic procedures. Since this is
985 called from procedure resolution functions, it only recurses at
986 operators. */
988 static bool
989 resolve_assumed_size_actual (gfc_expr *e)
991 if (e == NULL)
992 return false;
994 switch (e->expr_type)
996 case EXPR_VARIABLE:
997 if (e->symtree && check_assumed_size_reference (e->symtree->n.sym, e))
998 return true;
999 break;
1001 case EXPR_OP:
1002 if (resolve_assumed_size_actual (e->value.op.op1)
1003 || resolve_assumed_size_actual (e->value.op.op2))
1004 return true;
1005 break;
1007 default:
1008 break;
1010 return false;
1014 /* Resolve an actual argument list. Most of the time, this is just
1015 resolving the expressions in the list.
1016 The exception is that we sometimes have to decide whether arguments
1017 that look like procedure arguments are really simple variable
1018 references. */
1020 static try
1021 resolve_actual_arglist (gfc_actual_arglist *arg, procedure_type ptype)
1023 gfc_symbol *sym;
1024 gfc_symtree *parent_st;
1025 gfc_expr *e;
1026 int save_need_full_assumed_size;
1028 for (; arg; arg = arg->next)
1030 e = arg->expr;
1031 if (e == NULL)
1033 /* Check the label is a valid branching target. */
1034 if (arg->label)
1036 if (arg->label->defined == ST_LABEL_UNKNOWN)
1038 gfc_error ("Label %d referenced at %L is never defined",
1039 arg->label->value, &arg->label->where);
1040 return FAILURE;
1043 continue;
1046 if (e->expr_type == FL_VARIABLE && e->symtree->ambiguous)
1048 gfc_error ("'%s' at %L is ambiguous", e->symtree->n.sym->name,
1049 &e->where);
1050 return FAILURE;
1053 if (e->ts.type != BT_PROCEDURE)
1055 save_need_full_assumed_size = need_full_assumed_size;
1056 if (e->expr_type != FL_VARIABLE)
1057 need_full_assumed_size = 0;
1058 if (gfc_resolve_expr (e) != SUCCESS)
1059 return FAILURE;
1060 need_full_assumed_size = save_need_full_assumed_size;
1061 goto argument_list;
1064 /* See if the expression node should really be a variable reference. */
1066 sym = e->symtree->n.sym;
1068 if (sym->attr.flavor == FL_PROCEDURE
1069 || sym->attr.intrinsic
1070 || sym->attr.external)
1072 int actual_ok;
1074 /* If a procedure is not already determined to be something else
1075 check if it is intrinsic. */
1076 if (!sym->attr.intrinsic
1077 && !(sym->attr.external || sym->attr.use_assoc
1078 || sym->attr.if_source == IFSRC_IFBODY)
1079 && gfc_intrinsic_name (sym->name, sym->attr.subroutine))
1080 sym->attr.intrinsic = 1;
1082 if (sym->attr.proc == PROC_ST_FUNCTION)
1084 gfc_error ("Statement function '%s' at %L is not allowed as an "
1085 "actual argument", sym->name, &e->where);
1088 actual_ok = gfc_intrinsic_actual_ok (sym->name,
1089 sym->attr.subroutine);
1090 if (sym->attr.intrinsic && actual_ok == 0)
1092 gfc_error ("Intrinsic '%s' at %L is not allowed as an "
1093 "actual argument", sym->name, &e->where);
1096 if (sym->attr.contained && !sym->attr.use_assoc
1097 && sym->ns->proc_name->attr.flavor != FL_MODULE)
1099 gfc_error ("Internal procedure '%s' is not allowed as an "
1100 "actual argument at %L", sym->name, &e->where);
1103 if (sym->attr.elemental && !sym->attr.intrinsic)
1105 gfc_error ("ELEMENTAL non-INTRINSIC procedure '%s' is not "
1106 "allowed as an actual argument at %L", sym->name,
1107 &e->where);
1110 /* Check if a generic interface has a specific procedure
1111 with the same name before emitting an error. */
1112 if (sym->attr.generic)
1114 gfc_interface *p;
1115 for (p = sym->generic; p; p = p->next)
1116 if (strcmp (sym->name, p->sym->name) == 0)
1118 e->symtree = gfc_find_symtree
1119 (p->sym->ns->sym_root, sym->name);
1120 sym = p->sym;
1121 break;
1124 if (p == NULL || e->symtree == NULL)
1125 gfc_error ("GENERIC procedure '%s' is not "
1126 "allowed as an actual argument at %L", sym->name,
1127 &e->where);
1130 /* If the symbol is the function that names the current (or
1131 parent) scope, then we really have a variable reference. */
1133 if (sym->attr.function && sym->result == sym
1134 && (sym->ns->proc_name == sym
1135 || (sym->ns->parent != NULL
1136 && sym->ns->parent->proc_name == sym)))
1137 goto got_variable;
1139 /* If all else fails, see if we have a specific intrinsic. */
1140 if (sym->ts.type == BT_UNKNOWN && sym->attr.intrinsic)
1142 gfc_intrinsic_sym *isym;
1144 isym = gfc_find_function (sym->name);
1145 if (isym == NULL || !isym->specific)
1147 gfc_error ("Unable to find a specific INTRINSIC procedure "
1148 "for the reference '%s' at %L", sym->name,
1149 &e->where);
1150 return FAILURE;
1152 sym->ts = isym->ts;
1153 sym->attr.intrinsic = 1;
1154 sym->attr.function = 1;
1156 goto argument_list;
1159 /* See if the name is a module procedure in a parent unit. */
1161 if (was_declared (sym) || sym->ns->parent == NULL)
1162 goto got_variable;
1164 if (gfc_find_sym_tree (sym->name, sym->ns->parent, 1, &parent_st))
1166 gfc_error ("Symbol '%s' at %L is ambiguous", sym->name, &e->where);
1167 return FAILURE;
1170 if (parent_st == NULL)
1171 goto got_variable;
1173 sym = parent_st->n.sym;
1174 e->symtree = parent_st; /* Point to the right thing. */
1176 if (sym->attr.flavor == FL_PROCEDURE
1177 || sym->attr.intrinsic
1178 || sym->attr.external)
1180 goto argument_list;
1183 got_variable:
1184 e->expr_type = EXPR_VARIABLE;
1185 e->ts = sym->ts;
1186 if (sym->as != NULL)
1188 e->rank = sym->as->rank;
1189 e->ref = gfc_get_ref ();
1190 e->ref->type = REF_ARRAY;
1191 e->ref->u.ar.type = AR_FULL;
1192 e->ref->u.ar.as = sym->as;
1195 /* Expressions are assigned a default ts.type of BT_PROCEDURE in
1196 primary.c (match_actual_arg). If above code determines that it
1197 is a variable instead, it needs to be resolved as it was not
1198 done at the beginning of this function. */
1199 save_need_full_assumed_size = need_full_assumed_size;
1200 if (e->expr_type != FL_VARIABLE)
1201 need_full_assumed_size = 0;
1202 if (gfc_resolve_expr (e) != SUCCESS)
1203 return FAILURE;
1204 need_full_assumed_size = save_need_full_assumed_size;
1206 argument_list:
1207 /* Check argument list functions %VAL, %LOC and %REF. There is
1208 nothing to do for %REF. */
1209 if (arg->name && arg->name[0] == '%')
1211 if (strncmp ("%VAL", arg->name, 4) == 0)
1213 if (e->ts.type == BT_CHARACTER || e->ts.type == BT_DERIVED)
1215 gfc_error ("By-value argument at %L is not of numeric "
1216 "type", &e->where);
1217 return FAILURE;
1220 if (e->rank)
1222 gfc_error ("By-value argument at %L cannot be an array or "
1223 "an array section", &e->where);
1224 return FAILURE;
1227 /* Intrinsics are still PROC_UNKNOWN here. However,
1228 since same file external procedures are not resolvable
1229 in gfortran, it is a good deal easier to leave them to
1230 intrinsic.c. */
1231 if (ptype != PROC_UNKNOWN
1232 && ptype != PROC_DUMMY
1233 && ptype != PROC_EXTERNAL
1234 && ptype != PROC_MODULE)
1236 gfc_error ("By-value argument at %L is not allowed "
1237 "in this context", &e->where);
1238 return FAILURE;
1242 /* Statement functions have already been excluded above. */
1243 else if (strncmp ("%LOC", arg->name, 4) == 0
1244 && e->ts.type == BT_PROCEDURE)
1246 if (e->symtree->n.sym->attr.proc == PROC_INTERNAL)
1248 gfc_error ("Passing internal procedure at %L by location "
1249 "not allowed", &e->where);
1250 return FAILURE;
1256 return SUCCESS;
1260 /* Do the checks of the actual argument list that are specific to elemental
1261 procedures. If called with c == NULL, we have a function, otherwise if
1262 expr == NULL, we have a subroutine. */
1264 static try
1265 resolve_elemental_actual (gfc_expr *expr, gfc_code *c)
1267 gfc_actual_arglist *arg0;
1268 gfc_actual_arglist *arg;
1269 gfc_symbol *esym = NULL;
1270 gfc_intrinsic_sym *isym = NULL;
1271 gfc_expr *e = NULL;
1272 gfc_intrinsic_arg *iformal = NULL;
1273 gfc_formal_arglist *eformal = NULL;
1274 bool formal_optional = false;
1275 bool set_by_optional = false;
1276 int i;
1277 int rank = 0;
1279 /* Is this an elemental procedure? */
1280 if (expr && expr->value.function.actual != NULL)
1282 if (expr->value.function.esym != NULL
1283 && expr->value.function.esym->attr.elemental)
1285 arg0 = expr->value.function.actual;
1286 esym = expr->value.function.esym;
1288 else if (expr->value.function.isym != NULL
1289 && expr->value.function.isym->elemental)
1291 arg0 = expr->value.function.actual;
1292 isym = expr->value.function.isym;
1294 else
1295 return SUCCESS;
1297 else if (c && c->ext.actual != NULL && c->symtree->n.sym->attr.elemental)
1299 arg0 = c->ext.actual;
1300 esym = c->symtree->n.sym;
1302 else
1303 return SUCCESS;
1305 /* The rank of an elemental is the rank of its array argument(s). */
1306 for (arg = arg0; arg; arg = arg->next)
1308 if (arg->expr != NULL && arg->expr->rank > 0)
1310 rank = arg->expr->rank;
1311 if (arg->expr->expr_type == EXPR_VARIABLE
1312 && arg->expr->symtree->n.sym->attr.optional)
1313 set_by_optional = true;
1315 /* Function specific; set the result rank and shape. */
1316 if (expr)
1318 expr->rank = rank;
1319 if (!expr->shape && arg->expr->shape)
1321 expr->shape = gfc_get_shape (rank);
1322 for (i = 0; i < rank; i++)
1323 mpz_init_set (expr->shape[i], arg->expr->shape[i]);
1326 break;
1330 /* If it is an array, it shall not be supplied as an actual argument
1331 to an elemental procedure unless an array of the same rank is supplied
1332 as an actual argument corresponding to a nonoptional dummy argument of
1333 that elemental procedure(12.4.1.5). */
1334 formal_optional = false;
1335 if (isym)
1336 iformal = isym->formal;
1337 else
1338 eformal = esym->formal;
1340 for (arg = arg0; arg; arg = arg->next)
1342 if (eformal)
1344 if (eformal->sym && eformal->sym->attr.optional)
1345 formal_optional = true;
1346 eformal = eformal->next;
1348 else if (isym && iformal)
1350 if (iformal->optional)
1351 formal_optional = true;
1352 iformal = iformal->next;
1354 else if (isym)
1355 formal_optional = true;
1357 if (pedantic && arg->expr != NULL
1358 && arg->expr->expr_type == EXPR_VARIABLE
1359 && arg->expr->symtree->n.sym->attr.optional
1360 && formal_optional
1361 && arg->expr->rank
1362 && (set_by_optional || arg->expr->rank != rank)
1363 && !(isym && isym->id == GFC_ISYM_CONVERSION))
1365 gfc_warning ("'%s' at %L is an array and OPTIONAL; IF IT IS "
1366 "MISSING, it cannot be the actual argument of an "
1367 "ELEMENTAL procedure unless there is a non-optional "
1368 "argument with the same rank (12.4.1.5)",
1369 arg->expr->symtree->n.sym->name, &arg->expr->where);
1370 return FAILURE;
1374 for (arg = arg0; arg; arg = arg->next)
1376 if (arg->expr == NULL || arg->expr->rank == 0)
1377 continue;
1379 /* Being elemental, the last upper bound of an assumed size array
1380 argument must be present. */
1381 if (resolve_assumed_size_actual (arg->expr))
1382 return FAILURE;
1384 /* Elemental procedure's array actual arguments must conform. */
1385 if (e != NULL)
1387 if (gfc_check_conformance ("elemental procedure", arg->expr, e)
1388 == FAILURE)
1389 return FAILURE;
1391 else
1392 e = arg->expr;
1395 /* INTENT(OUT) is only allowed for subroutines; if any actual argument
1396 is an array, the intent inout/out variable needs to be also an array. */
1397 if (rank > 0 && esym && expr == NULL)
1398 for (eformal = esym->formal, arg = arg0; arg && eformal;
1399 arg = arg->next, eformal = eformal->next)
1400 if ((eformal->sym->attr.intent == INTENT_OUT
1401 || eformal->sym->attr.intent == INTENT_INOUT)
1402 && arg->expr && arg->expr->rank == 0)
1404 gfc_error ("Actual argument at %L for INTENT(%s) dummy '%s' of "
1405 "ELEMENTAL subroutine '%s' is a scalar, but another "
1406 "actual argument is an array", &arg->expr->where,
1407 (eformal->sym->attr.intent == INTENT_OUT) ? "OUT"
1408 : "INOUT", eformal->sym->name, esym->name);
1409 return FAILURE;
1411 return SUCCESS;
1415 /* Go through each actual argument in ACTUAL and see if it can be
1416 implemented as an inlined, non-copying intrinsic. FNSYM is the
1417 function being called, or NULL if not known. */
1419 static void
1420 find_noncopying_intrinsics (gfc_symbol *fnsym, gfc_actual_arglist *actual)
1422 gfc_actual_arglist *ap;
1423 gfc_expr *expr;
1425 for (ap = actual; ap; ap = ap->next)
1426 if (ap->expr
1427 && (expr = gfc_get_noncopying_intrinsic_argument (ap->expr))
1428 && !gfc_check_fncall_dependency (expr, INTENT_IN, fnsym, actual))
1429 ap->expr->inline_noncopying_intrinsic = 1;
1433 /* This function does the checking of references to global procedures
1434 as defined in sections 18.1 and 14.1, respectively, of the Fortran
1435 77 and 95 standards. It checks for a gsymbol for the name, making
1436 one if it does not already exist. If it already exists, then the
1437 reference being resolved must correspond to the type of gsymbol.
1438 Otherwise, the new symbol is equipped with the attributes of the
1439 reference. The corresponding code that is called in creating
1440 global entities is parse.c. */
1442 static void
1443 resolve_global_procedure (gfc_symbol *sym, locus *where, int sub)
1445 gfc_gsymbol * gsym;
1446 unsigned int type;
1448 type = sub ? GSYM_SUBROUTINE : GSYM_FUNCTION;
1450 gsym = gfc_get_gsymbol (sym->name);
1452 if ((gsym->type != GSYM_UNKNOWN && gsym->type != type))
1453 gfc_global_used (gsym, where);
1455 if (gsym->type == GSYM_UNKNOWN)
1457 gsym->type = type;
1458 gsym->where = *where;
1461 gsym->used = 1;
1465 /************* Function resolution *************/
1467 /* Resolve a function call known to be generic.
1468 Section 14.1.2.4.1. */
1470 static match
1471 resolve_generic_f0 (gfc_expr *expr, gfc_symbol *sym)
1473 gfc_symbol *s;
1475 if (sym->attr.generic)
1477 s = gfc_search_interface (sym->generic, 0, &expr->value.function.actual);
1478 if (s != NULL)
1480 expr->value.function.name = s->name;
1481 expr->value.function.esym = s;
1483 if (s->ts.type != BT_UNKNOWN)
1484 expr->ts = s->ts;
1485 else if (s->result != NULL && s->result->ts.type != BT_UNKNOWN)
1486 expr->ts = s->result->ts;
1488 if (s->as != NULL)
1489 expr->rank = s->as->rank;
1490 else if (s->result != NULL && s->result->as != NULL)
1491 expr->rank = s->result->as->rank;
1493 gfc_set_sym_referenced (expr->value.function.esym);
1495 return MATCH_YES;
1498 /* TODO: Need to search for elemental references in generic
1499 interface. */
1502 if (sym->attr.intrinsic)
1503 return gfc_intrinsic_func_interface (expr, 0);
1505 return MATCH_NO;
1509 static try
1510 resolve_generic_f (gfc_expr *expr)
1512 gfc_symbol *sym;
1513 match m;
1515 sym = expr->symtree->n.sym;
1517 for (;;)
1519 m = resolve_generic_f0 (expr, sym);
1520 if (m == MATCH_YES)
1521 return SUCCESS;
1522 else if (m == MATCH_ERROR)
1523 return FAILURE;
1525 generic:
1526 if (sym->ns->parent == NULL)
1527 break;
1528 gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
1530 if (sym == NULL)
1531 break;
1532 if (!generic_sym (sym))
1533 goto generic;
1536 /* Last ditch attempt. See if the reference is to an intrinsic
1537 that possesses a matching interface. 14.1.2.4 */
1538 if (sym && !gfc_intrinsic_name (sym->name, 0))
1540 gfc_error ("There is no specific function for the generic '%s' at %L",
1541 expr->symtree->n.sym->name, &expr->where);
1542 return FAILURE;
1545 m = gfc_intrinsic_func_interface (expr, 0);
1546 if (m == MATCH_YES)
1547 return SUCCESS;
1548 if (m == MATCH_NO)
1549 gfc_error ("Generic function '%s' at %L is not consistent with a "
1550 "specific intrinsic interface", expr->symtree->n.sym->name,
1551 &expr->where);
1553 return FAILURE;
1557 /* Resolve a function call known to be specific. */
1559 static match
1560 resolve_specific_f0 (gfc_symbol *sym, gfc_expr *expr)
1562 match m;
1564 /* See if we have an intrinsic interface. */
1566 if (sym->ts.interface != NULL && sym->ts.interface->attr.intrinsic)
1568 gfc_intrinsic_sym *isym;
1569 isym = gfc_find_function (sym->ts.interface->name);
1571 /* Existance of isym should be checked already. */
1572 gcc_assert (isym);
1574 sym->ts = isym->ts;
1575 sym->attr.function = 1;
1576 sym->attr.proc = PROC_EXTERNAL;
1577 goto found;
1580 if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
1582 if (sym->attr.dummy)
1584 sym->attr.proc = PROC_DUMMY;
1585 goto found;
1588 sym->attr.proc = PROC_EXTERNAL;
1589 goto found;
1592 if (sym->attr.proc == PROC_MODULE
1593 || sym->attr.proc == PROC_ST_FUNCTION
1594 || sym->attr.proc == PROC_INTERNAL)
1595 goto found;
1597 if (sym->attr.intrinsic)
1599 m = gfc_intrinsic_func_interface (expr, 1);
1600 if (m == MATCH_YES)
1601 return MATCH_YES;
1602 if (m == MATCH_NO)
1603 gfc_error ("Function '%s' at %L is INTRINSIC but is not compatible "
1604 "with an intrinsic", sym->name, &expr->where);
1606 return MATCH_ERROR;
1609 return MATCH_NO;
1611 found:
1612 gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
1614 expr->ts = sym->ts;
1615 expr->value.function.name = sym->name;
1616 expr->value.function.esym = sym;
1617 if (sym->as != NULL)
1618 expr->rank = sym->as->rank;
1620 return MATCH_YES;
1624 static try
1625 resolve_specific_f (gfc_expr *expr)
1627 gfc_symbol *sym;
1628 match m;
1630 sym = expr->symtree->n.sym;
1632 for (;;)
1634 m = resolve_specific_f0 (sym, expr);
1635 if (m == MATCH_YES)
1636 return SUCCESS;
1637 if (m == MATCH_ERROR)
1638 return FAILURE;
1640 if (sym->ns->parent == NULL)
1641 break;
1643 gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
1645 if (sym == NULL)
1646 break;
1649 gfc_error ("Unable to resolve the specific function '%s' at %L",
1650 expr->symtree->n.sym->name, &expr->where);
1652 return SUCCESS;
1656 /* Resolve a procedure call not known to be generic nor specific. */
1658 static try
1659 resolve_unknown_f (gfc_expr *expr)
1661 gfc_symbol *sym;
1662 gfc_typespec *ts;
1664 sym = expr->symtree->n.sym;
1666 if (sym->attr.dummy)
1668 sym->attr.proc = PROC_DUMMY;
1669 expr->value.function.name = sym->name;
1670 goto set_type;
1673 /* See if we have an intrinsic function reference. */
1675 if (gfc_intrinsic_name (sym->name, 0))
1677 if (gfc_intrinsic_func_interface (expr, 1) == MATCH_YES)
1678 return SUCCESS;
1679 return FAILURE;
1682 /* The reference is to an external name. */
1684 sym->attr.proc = PROC_EXTERNAL;
1685 expr->value.function.name = sym->name;
1686 expr->value.function.esym = expr->symtree->n.sym;
1688 if (sym->as != NULL)
1689 expr->rank = sym->as->rank;
1691 /* Type of the expression is either the type of the symbol or the
1692 default type of the symbol. */
1694 set_type:
1695 gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
1697 if (sym->ts.type != BT_UNKNOWN)
1698 expr->ts = sym->ts;
1699 else
1701 ts = gfc_get_default_type (sym, sym->ns);
1703 if (ts->type == BT_UNKNOWN)
1705 gfc_error ("Function '%s' at %L has no IMPLICIT type",
1706 sym->name, &expr->where);
1707 return FAILURE;
1709 else
1710 expr->ts = *ts;
1713 return SUCCESS;
1717 /* Return true, if the symbol is an external procedure. */
1718 static bool
1719 is_external_proc (gfc_symbol *sym)
1721 if (!sym->attr.dummy && !sym->attr.contained
1722 && !(sym->attr.intrinsic
1723 || gfc_intrinsic_name (sym->name, sym->attr.subroutine))
1724 && sym->attr.proc != PROC_ST_FUNCTION
1725 && !sym->attr.use_assoc
1726 && sym->name)
1727 return true;
1728 else
1729 return false;
1733 /* Figure out if a function reference is pure or not. Also set the name
1734 of the function for a potential error message. Return nonzero if the
1735 function is PURE, zero if not. */
1736 static int
1737 pure_stmt_function (gfc_expr *, gfc_symbol *);
1739 static int
1740 pure_function (gfc_expr *e, const char **name)
1742 int pure;
1744 *name = NULL;
1746 if (e->symtree != NULL
1747 && e->symtree->n.sym != NULL
1748 && e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
1749 return pure_stmt_function (e, e->symtree->n.sym);
1751 if (e->value.function.esym)
1753 pure = gfc_pure (e->value.function.esym);
1754 *name = e->value.function.esym->name;
1756 else if (e->value.function.isym)
1758 pure = e->value.function.isym->pure
1759 || e->value.function.isym->elemental;
1760 *name = e->value.function.isym->name;
1762 else
1764 /* Implicit functions are not pure. */
1765 pure = 0;
1766 *name = e->value.function.name;
1769 return pure;
1773 static bool
1774 impure_stmt_fcn (gfc_expr *e, gfc_symbol *sym,
1775 int *f ATTRIBUTE_UNUSED)
1777 const char *name;
1779 /* Don't bother recursing into other statement functions
1780 since they will be checked individually for purity. */
1781 if (e->expr_type != EXPR_FUNCTION
1782 || !e->symtree
1783 || e->symtree->n.sym == sym
1784 || e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
1785 return false;
1787 return pure_function (e, &name) ? false : true;
1791 static int
1792 pure_stmt_function (gfc_expr *e, gfc_symbol *sym)
1794 return gfc_traverse_expr (e, sym, impure_stmt_fcn, 0) ? 0 : 1;
1798 static try
1799 is_scalar_expr_ptr (gfc_expr *expr)
1801 try retval = SUCCESS;
1802 gfc_ref *ref;
1803 int start;
1804 int end;
1806 /* See if we have a gfc_ref, which means we have a substring, array
1807 reference, or a component. */
1808 if (expr->ref != NULL)
1810 ref = expr->ref;
1811 while (ref->next != NULL)
1812 ref = ref->next;
1814 switch (ref->type)
1816 case REF_SUBSTRING:
1817 if (ref->u.ss.length != NULL
1818 && ref->u.ss.length->length != NULL
1819 && ref->u.ss.start
1820 && ref->u.ss.start->expr_type == EXPR_CONSTANT
1821 && ref->u.ss.end
1822 && ref->u.ss.end->expr_type == EXPR_CONSTANT)
1824 start = (int) mpz_get_si (ref->u.ss.start->value.integer);
1825 end = (int) mpz_get_si (ref->u.ss.end->value.integer);
1826 if (end - start + 1 != 1)
1827 retval = FAILURE;
1829 else
1830 retval = FAILURE;
1831 break;
1832 case REF_ARRAY:
1833 if (ref->u.ar.type == AR_ELEMENT)
1834 retval = SUCCESS;
1835 else if (ref->u.ar.type == AR_FULL)
1837 /* The user can give a full array if the array is of size 1. */
1838 if (ref->u.ar.as != NULL
1839 && ref->u.ar.as->rank == 1
1840 && ref->u.ar.as->type == AS_EXPLICIT
1841 && ref->u.ar.as->lower[0] != NULL
1842 && ref->u.ar.as->lower[0]->expr_type == EXPR_CONSTANT
1843 && ref->u.ar.as->upper[0] != NULL
1844 && ref->u.ar.as->upper[0]->expr_type == EXPR_CONSTANT)
1846 /* If we have a character string, we need to check if
1847 its length is one. */
1848 if (expr->ts.type == BT_CHARACTER)
1850 if (expr->ts.cl == NULL
1851 || expr->ts.cl->length == NULL
1852 || mpz_cmp_si (expr->ts.cl->length->value.integer, 1)
1853 != 0)
1854 retval = FAILURE;
1856 else
1858 /* We have constant lower and upper bounds. If the
1859 difference between is 1, it can be considered a
1860 scalar. */
1861 start = (int) mpz_get_si
1862 (ref->u.ar.as->lower[0]->value.integer);
1863 end = (int) mpz_get_si
1864 (ref->u.ar.as->upper[0]->value.integer);
1865 if (end - start + 1 != 1)
1866 retval = FAILURE;
1869 else
1870 retval = FAILURE;
1872 else
1873 retval = FAILURE;
1874 break;
1875 default:
1876 retval = SUCCESS;
1877 break;
1880 else if (expr->ts.type == BT_CHARACTER && expr->rank == 0)
1882 /* Character string. Make sure it's of length 1. */
1883 if (expr->ts.cl == NULL
1884 || expr->ts.cl->length == NULL
1885 || mpz_cmp_si (expr->ts.cl->length->value.integer, 1) != 0)
1886 retval = FAILURE;
1888 else if (expr->rank != 0)
1889 retval = FAILURE;
1891 return retval;
1895 /* Match one of the iso_c_binding functions (c_associated or c_loc)
1896 and, in the case of c_associated, set the binding label based on
1897 the arguments. */
1899 static try
1900 gfc_iso_c_func_interface (gfc_symbol *sym, gfc_actual_arglist *args,
1901 gfc_symbol **new_sym)
1903 char name[GFC_MAX_SYMBOL_LEN + 1];
1904 char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
1905 int optional_arg = 0;
1906 try retval = SUCCESS;
1907 gfc_symbol *args_sym;
1908 gfc_typespec *arg_ts;
1909 gfc_ref *parent_ref;
1910 gfc_ref *curr_ref;
1912 if (args->expr->expr_type == EXPR_CONSTANT
1913 || args->expr->expr_type == EXPR_OP
1914 || args->expr->expr_type == EXPR_NULL)
1916 gfc_error ("Argument to '%s' at %L is not a variable",
1917 sym->name, &(args->expr->where));
1918 return FAILURE;
1921 args_sym = args->expr->symtree->n.sym;
1923 /* The typespec for the actual arg should be that stored in the expr
1924 and not necessarily that of the expr symbol (args_sym), because
1925 the actual expression could be a part-ref of the expr symbol. */
1926 arg_ts = &(args->expr->ts);
1928 /* Get the parent reference (if any) for the expression. This happens for
1929 cases such as a%b%c. */
1930 parent_ref = args->expr->ref;
1931 curr_ref = NULL;
1932 if (parent_ref != NULL)
1934 curr_ref = parent_ref->next;
1935 while (curr_ref != NULL && curr_ref->next != NULL)
1937 parent_ref = curr_ref;
1938 curr_ref = curr_ref->next;
1942 /* If curr_ref is non-NULL, we had a part-ref expression. If the curr_ref
1943 is for a REF_COMPONENT, then we need to use it as the parent_ref for
1944 the name, etc. Otherwise, the current parent_ref should be correct. */
1945 if (curr_ref != NULL && curr_ref->type == REF_COMPONENT)
1946 parent_ref = curr_ref;
1948 if (parent_ref == args->expr->ref)
1949 parent_ref = NULL;
1950 else if (parent_ref != NULL && parent_ref->type != REF_COMPONENT)
1951 gfc_internal_error ("Unexpected expression reference type in "
1952 "gfc_iso_c_func_interface");
1954 if (sym->intmod_sym_id == ISOCBINDING_ASSOCIATED)
1956 /* If the user gave two args then they are providing something for
1957 the optional arg (the second cptr). Therefore, set the name and
1958 binding label to the c_associated for two cptrs. Otherwise,
1959 set c_associated to expect one cptr. */
1960 if (args->next)
1962 /* two args. */
1963 sprintf (name, "%s_2", sym->name);
1964 sprintf (binding_label, "%s_2", sym->binding_label);
1965 optional_arg = 1;
1967 else
1969 /* one arg. */
1970 sprintf (name, "%s_1", sym->name);
1971 sprintf (binding_label, "%s_1", sym->binding_label);
1972 optional_arg = 0;
1975 /* Get a new symbol for the version of c_associated that
1976 will get called. */
1977 *new_sym = get_iso_c_sym (sym, name, binding_label, optional_arg);
1979 else if (sym->intmod_sym_id == ISOCBINDING_LOC
1980 || sym->intmod_sym_id == ISOCBINDING_FUNLOC)
1982 sprintf (name, "%s", sym->name);
1983 sprintf (binding_label, "%s", sym->binding_label);
1985 /* Error check the call. */
1986 if (args->next != NULL)
1988 gfc_error_now ("More actual than formal arguments in '%s' "
1989 "call at %L", name, &(args->expr->where));
1990 retval = FAILURE;
1992 else if (sym->intmod_sym_id == ISOCBINDING_LOC)
1994 /* Make sure we have either the target or pointer attribute. */
1995 if (!(args_sym->attr.target)
1996 && !(args_sym->attr.pointer)
1997 && (parent_ref == NULL ||
1998 !parent_ref->u.c.component->pointer))
2000 gfc_error_now ("Parameter '%s' to '%s' at %L must be either "
2001 "a TARGET or an associated pointer",
2002 args_sym->name,
2003 sym->name, &(args->expr->where));
2004 retval = FAILURE;
2007 /* See if we have interoperable type and type param. */
2008 if (verify_c_interop (arg_ts,
2009 (parent_ref ? parent_ref->u.c.component->name
2010 : args_sym->name),
2011 &(args->expr->where)) == SUCCESS
2012 || gfc_check_any_c_kind (arg_ts) == SUCCESS)
2014 if (args_sym->attr.target == 1)
2016 /* Case 1a, section 15.1.2.5, J3/04-007: variable that
2017 has the target attribute and is interoperable. */
2018 /* Case 1b, section 15.1.2.5, J3/04-007: allocated
2019 allocatable variable that has the TARGET attribute and
2020 is not an array of zero size. */
2021 if (args_sym->attr.allocatable == 1)
2023 if (args_sym->attr.dimension != 0
2024 && (args_sym->as && args_sym->as->rank == 0))
2026 gfc_error_now ("Allocatable variable '%s' used as a "
2027 "parameter to '%s' at %L must not be "
2028 "an array of zero size",
2029 args_sym->name, sym->name,
2030 &(args->expr->where));
2031 retval = FAILURE;
2034 else
2036 /* A non-allocatable target variable with C
2037 interoperable type and type parameters must be
2038 interoperable. */
2039 if (args_sym && args_sym->attr.dimension)
2041 if (args_sym->as->type == AS_ASSUMED_SHAPE)
2043 gfc_error ("Assumed-shape array '%s' at %L "
2044 "cannot be an argument to the "
2045 "procedure '%s' because "
2046 "it is not C interoperable",
2047 args_sym->name,
2048 &(args->expr->where), sym->name);
2049 retval = FAILURE;
2051 else if (args_sym->as->type == AS_DEFERRED)
2053 gfc_error ("Deferred-shape array '%s' at %L "
2054 "cannot be an argument to the "
2055 "procedure '%s' because "
2056 "it is not C interoperable",
2057 args_sym->name,
2058 &(args->expr->where), sym->name);
2059 retval = FAILURE;
2063 /* Make sure it's not a character string. Arrays of
2064 any type should be ok if the variable is of a C
2065 interoperable type. */
2066 if (arg_ts->type == BT_CHARACTER)
2067 if (arg_ts->cl != NULL
2068 && (arg_ts->cl->length == NULL
2069 || arg_ts->cl->length->expr_type
2070 != EXPR_CONSTANT
2071 || mpz_cmp_si
2072 (arg_ts->cl->length->value.integer, 1)
2073 != 0)
2074 && is_scalar_expr_ptr (args->expr) != SUCCESS)
2076 gfc_error_now ("CHARACTER argument '%s' to '%s' "
2077 "at %L must have a length of 1",
2078 args_sym->name, sym->name,
2079 &(args->expr->where));
2080 retval = FAILURE;
2084 else if ((args_sym->attr.pointer == 1 ||
2085 (parent_ref != NULL
2086 && parent_ref->u.c.component->pointer))
2087 && is_scalar_expr_ptr (args->expr) != SUCCESS)
2089 /* Case 1c, section 15.1.2.5, J3/04-007: an associated
2090 scalar pointer. */
2091 gfc_error_now ("Argument '%s' to '%s' at %L must be an "
2092 "associated scalar POINTER", args_sym->name,
2093 sym->name, &(args->expr->where));
2094 retval = FAILURE;
2097 else
2099 /* The parameter is not required to be C interoperable. If it
2100 is not C interoperable, it must be a nonpolymorphic scalar
2101 with no length type parameters. It still must have either
2102 the pointer or target attribute, and it can be
2103 allocatable (but must be allocated when c_loc is called). */
2104 if (args->expr->rank != 0
2105 && is_scalar_expr_ptr (args->expr) != SUCCESS)
2107 gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2108 "scalar", args_sym->name, sym->name,
2109 &(args->expr->where));
2110 retval = FAILURE;
2112 else if (arg_ts->type == BT_CHARACTER
2113 && is_scalar_expr_ptr (args->expr) != SUCCESS)
2115 gfc_error_now ("CHARACTER argument '%s' to '%s' at "
2116 "%L must have a length of 1",
2117 args_sym->name, sym->name,
2118 &(args->expr->where));
2119 retval = FAILURE;
2123 else if (sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2125 if (args_sym->attr.flavor != FL_PROCEDURE)
2127 /* TODO: Update this error message to allow for procedure
2128 pointers once they are implemented. */
2129 gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2130 "procedure",
2131 args_sym->name, sym->name,
2132 &(args->expr->where));
2133 retval = FAILURE;
2135 else if (args_sym->attr.is_bind_c != 1)
2137 gfc_error_now ("Parameter '%s' to '%s' at %L must be "
2138 "BIND(C)",
2139 args_sym->name, sym->name,
2140 &(args->expr->where));
2141 retval = FAILURE;
2145 /* for c_loc/c_funloc, the new symbol is the same as the old one */
2146 *new_sym = sym;
2148 else
2150 gfc_internal_error ("gfc_iso_c_func_interface(): Unhandled "
2151 "iso_c_binding function: '%s'!\n", sym->name);
2154 return retval;
2158 /* Resolve a function call, which means resolving the arguments, then figuring
2159 out which entity the name refers to. */
2160 /* TODO: Check procedure arguments so that an INTENT(IN) isn't passed
2161 to INTENT(OUT) or INTENT(INOUT). */
2163 static try
2164 resolve_function (gfc_expr *expr)
2166 gfc_actual_arglist *arg;
2167 gfc_symbol *sym;
2168 const char *name;
2169 try t;
2170 int temp;
2171 procedure_type p = PROC_INTRINSIC;
2173 sym = NULL;
2174 if (expr->symtree)
2175 sym = expr->symtree->n.sym;
2177 if (sym && sym->attr.flavor == FL_VARIABLE)
2179 gfc_error ("'%s' at %L is not a function", sym->name, &expr->where);
2180 return FAILURE;
2183 if (sym && sym->attr.abstract)
2185 gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
2186 sym->name, &expr->where);
2187 return FAILURE;
2190 /* If the procedure is external, check for usage. */
2191 if (sym && is_external_proc (sym))
2192 resolve_global_procedure (sym, &expr->where, 0);
2194 /* Switch off assumed size checking and do this again for certain kinds
2195 of procedure, once the procedure itself is resolved. */
2196 need_full_assumed_size++;
2198 if (expr->symtree && expr->symtree->n.sym)
2199 p = expr->symtree->n.sym->attr.proc;
2201 if (resolve_actual_arglist (expr->value.function.actual, p) == FAILURE)
2202 return FAILURE;
2204 /* Need to setup the call to the correct c_associated, depending on
2205 the number of cptrs to user gives to compare. */
2206 if (sym && sym->attr.is_iso_c == 1)
2208 if (gfc_iso_c_func_interface (sym, expr->value.function.actual, &sym)
2209 == FAILURE)
2210 return FAILURE;
2212 /* Get the symtree for the new symbol (resolved func).
2213 the old one will be freed later, when it's no longer used. */
2214 gfc_find_sym_tree (sym->name, sym->ns, 1, &(expr->symtree));
2217 /* Resume assumed_size checking. */
2218 need_full_assumed_size--;
2220 if (sym && sym->ts.type == BT_CHARACTER
2221 && sym->ts.cl
2222 && sym->ts.cl->length == NULL
2223 && !sym->attr.dummy
2224 && expr->value.function.esym == NULL
2225 && !sym->attr.contained)
2227 /* Internal procedures are taken care of in resolve_contained_fntype. */
2228 gfc_error ("Function '%s' is declared CHARACTER(*) and cannot "
2229 "be used at %L since it is not a dummy argument",
2230 sym->name, &expr->where);
2231 return FAILURE;
2234 /* See if function is already resolved. */
2236 if (expr->value.function.name != NULL)
2238 if (expr->ts.type == BT_UNKNOWN)
2239 expr->ts = sym->ts;
2240 t = SUCCESS;
2242 else
2244 /* Apply the rules of section 14.1.2. */
2246 switch (procedure_kind (sym))
2248 case PTYPE_GENERIC:
2249 t = resolve_generic_f (expr);
2250 break;
2252 case PTYPE_SPECIFIC:
2253 t = resolve_specific_f (expr);
2254 break;
2256 case PTYPE_UNKNOWN:
2257 t = resolve_unknown_f (expr);
2258 break;
2260 default:
2261 gfc_internal_error ("resolve_function(): bad function type");
2265 /* If the expression is still a function (it might have simplified),
2266 then we check to see if we are calling an elemental function. */
2268 if (expr->expr_type != EXPR_FUNCTION)
2269 return t;
2271 temp = need_full_assumed_size;
2272 need_full_assumed_size = 0;
2274 if (resolve_elemental_actual (expr, NULL) == FAILURE)
2275 return FAILURE;
2277 if (omp_workshare_flag
2278 && expr->value.function.esym
2279 && ! gfc_elemental (expr->value.function.esym))
2281 gfc_error ("User defined non-ELEMENTAL function '%s' at %L not allowed "
2282 "in WORKSHARE construct", expr->value.function.esym->name,
2283 &expr->where);
2284 t = FAILURE;
2287 #define GENERIC_ID expr->value.function.isym->id
2288 else if (expr->value.function.actual != NULL
2289 && expr->value.function.isym != NULL
2290 && GENERIC_ID != GFC_ISYM_LBOUND
2291 && GENERIC_ID != GFC_ISYM_LEN
2292 && GENERIC_ID != GFC_ISYM_LOC
2293 && GENERIC_ID != GFC_ISYM_PRESENT)
2295 /* Array intrinsics must also have the last upper bound of an
2296 assumed size array argument. UBOUND and SIZE have to be
2297 excluded from the check if the second argument is anything
2298 than a constant. */
2299 int inquiry;
2300 inquiry = GENERIC_ID == GFC_ISYM_UBOUND
2301 || GENERIC_ID == GFC_ISYM_SIZE;
2303 for (arg = expr->value.function.actual; arg; arg = arg->next)
2305 if (inquiry && arg->next != NULL && arg->next->expr)
2307 if (arg->next->expr->expr_type != EXPR_CONSTANT)
2308 break;
2310 if ((int)mpz_get_si (arg->next->expr->value.integer)
2311 < arg->expr->rank)
2312 break;
2315 if (arg->expr != NULL
2316 && arg->expr->rank > 0
2317 && resolve_assumed_size_actual (arg->expr))
2318 return FAILURE;
2321 #undef GENERIC_ID
2323 need_full_assumed_size = temp;
2324 name = NULL;
2326 if (!pure_function (expr, &name) && name)
2328 if (forall_flag)
2330 gfc_error ("reference to non-PURE function '%s' at %L inside a "
2331 "FORALL %s", name, &expr->where,
2332 forall_flag == 2 ? "mask" : "block");
2333 t = FAILURE;
2335 else if (gfc_pure (NULL))
2337 gfc_error ("Function reference to '%s' at %L is to a non-PURE "
2338 "procedure within a PURE procedure", name, &expr->where);
2339 t = FAILURE;
2343 /* Functions without the RECURSIVE attribution are not allowed to
2344 * call themselves. */
2345 if (expr->value.function.esym && !expr->value.function.esym->attr.recursive)
2347 gfc_symbol *esym, *proc;
2348 esym = expr->value.function.esym;
2349 proc = gfc_current_ns->proc_name;
2350 if (esym == proc)
2352 gfc_error ("Function '%s' at %L cannot call itself, as it is not "
2353 "RECURSIVE", name, &expr->where);
2354 t = FAILURE;
2357 if (esym->attr.entry && esym->ns->entries && proc->ns->entries
2358 && esym->ns->entries->sym == proc->ns->entries->sym)
2360 gfc_error ("Call to ENTRY '%s' at %L is recursive, but function "
2361 "'%s' is not declared as RECURSIVE",
2362 esym->name, &expr->where, esym->ns->entries->sym->name);
2363 t = FAILURE;
2367 /* Character lengths of use associated functions may contains references to
2368 symbols not referenced from the current program unit otherwise. Make sure
2369 those symbols are marked as referenced. */
2371 if (expr->ts.type == BT_CHARACTER && expr->value.function.esym
2372 && expr->value.function.esym->attr.use_assoc)
2374 gfc_expr_set_symbols_referenced (expr->ts.cl->length);
2377 if (t == SUCCESS
2378 && !((expr->value.function.esym
2379 && expr->value.function.esym->attr.elemental)
2381 (expr->value.function.isym
2382 && expr->value.function.isym->elemental)))
2383 find_noncopying_intrinsics (expr->value.function.esym,
2384 expr->value.function.actual);
2386 /* Make sure that the expression has a typespec that works. */
2387 if (expr->ts.type == BT_UNKNOWN)
2389 if (expr->symtree->n.sym->result
2390 && expr->symtree->n.sym->result->ts.type != BT_UNKNOWN)
2391 expr->ts = expr->symtree->n.sym->result->ts;
2394 return t;
2398 /************* Subroutine resolution *************/
2400 static void
2401 pure_subroutine (gfc_code *c, gfc_symbol *sym)
2403 if (gfc_pure (sym))
2404 return;
2406 if (forall_flag)
2407 gfc_error ("Subroutine call to '%s' in FORALL block at %L is not PURE",
2408 sym->name, &c->loc);
2409 else if (gfc_pure (NULL))
2410 gfc_error ("Subroutine call to '%s' at %L is not PURE", sym->name,
2411 &c->loc);
2415 static match
2416 resolve_generic_s0 (gfc_code *c, gfc_symbol *sym)
2418 gfc_symbol *s;
2420 if (sym->attr.generic)
2422 s = gfc_search_interface (sym->generic, 1, &c->ext.actual);
2423 if (s != NULL)
2425 c->resolved_sym = s;
2426 pure_subroutine (c, s);
2427 return MATCH_YES;
2430 /* TODO: Need to search for elemental references in generic interface. */
2433 if (sym->attr.intrinsic)
2434 return gfc_intrinsic_sub_interface (c, 0);
2436 return MATCH_NO;
2440 static try
2441 resolve_generic_s (gfc_code *c)
2443 gfc_symbol *sym;
2444 match m;
2446 sym = c->symtree->n.sym;
2448 for (;;)
2450 m = resolve_generic_s0 (c, sym);
2451 if (m == MATCH_YES)
2452 return SUCCESS;
2453 else if (m == MATCH_ERROR)
2454 return FAILURE;
2456 generic:
2457 if (sym->ns->parent == NULL)
2458 break;
2459 gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2461 if (sym == NULL)
2462 break;
2463 if (!generic_sym (sym))
2464 goto generic;
2467 /* Last ditch attempt. See if the reference is to an intrinsic
2468 that possesses a matching interface. 14.1.2.4 */
2469 sym = c->symtree->n.sym;
2471 if (!gfc_intrinsic_name (sym->name, 1))
2473 gfc_error ("There is no specific subroutine for the generic '%s' at %L",
2474 sym->name, &c->loc);
2475 return FAILURE;
2478 m = gfc_intrinsic_sub_interface (c, 0);
2479 if (m == MATCH_YES)
2480 return SUCCESS;
2481 if (m == MATCH_NO)
2482 gfc_error ("Generic subroutine '%s' at %L is not consistent with an "
2483 "intrinsic subroutine interface", sym->name, &c->loc);
2485 return FAILURE;
2489 /* Set the name and binding label of the subroutine symbol in the call
2490 expression represented by 'c' to include the type and kind of the
2491 second parameter. This function is for resolving the appropriate
2492 version of c_f_pointer() and c_f_procpointer(). For example, a
2493 call to c_f_pointer() for a default integer pointer could have a
2494 name of c_f_pointer_i4. If no second arg exists, which is an error
2495 for these two functions, it defaults to the generic symbol's name
2496 and binding label. */
2498 static void
2499 set_name_and_label (gfc_code *c, gfc_symbol *sym,
2500 char *name, char *binding_label)
2502 gfc_expr *arg = NULL;
2503 char type;
2504 int kind;
2506 /* The second arg of c_f_pointer and c_f_procpointer determines
2507 the type and kind for the procedure name. */
2508 arg = c->ext.actual->next->expr;
2510 if (arg != NULL)
2512 /* Set up the name to have the given symbol's name,
2513 plus the type and kind. */
2514 /* a derived type is marked with the type letter 'u' */
2515 if (arg->ts.type == BT_DERIVED)
2517 type = 'd';
2518 kind = 0; /* set the kind as 0 for now */
2520 else
2522 type = gfc_type_letter (arg->ts.type);
2523 kind = arg->ts.kind;
2526 if (arg->ts.type == BT_CHARACTER)
2527 /* Kind info for character strings not needed. */
2528 kind = 0;
2530 sprintf (name, "%s_%c%d", sym->name, type, kind);
2531 /* Set up the binding label as the given symbol's label plus
2532 the type and kind. */
2533 sprintf (binding_label, "%s_%c%d", sym->binding_label, type, kind);
2535 else
2537 /* If the second arg is missing, set the name and label as
2538 was, cause it should at least be found, and the missing
2539 arg error will be caught by compare_parameters(). */
2540 sprintf (name, "%s", sym->name);
2541 sprintf (binding_label, "%s", sym->binding_label);
2544 return;
2548 /* Resolve a generic version of the iso_c_binding procedure given
2549 (sym) to the specific one based on the type and kind of the
2550 argument(s). Currently, this function resolves c_f_pointer() and
2551 c_f_procpointer based on the type and kind of the second argument
2552 (FPTR). Other iso_c_binding procedures aren't specially handled.
2553 Upon successfully exiting, c->resolved_sym will hold the resolved
2554 symbol. Returns MATCH_ERROR if an error occurred; MATCH_YES
2555 otherwise. */
2557 match
2558 gfc_iso_c_sub_interface (gfc_code *c, gfc_symbol *sym)
2560 gfc_symbol *new_sym;
2561 /* this is fine, since we know the names won't use the max */
2562 char name[GFC_MAX_SYMBOL_LEN + 1];
2563 char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
2564 /* default to success; will override if find error */
2565 match m = MATCH_YES;
2567 /* Make sure the actual arguments are in the necessary order (based on the
2568 formal args) before resolving. */
2569 gfc_procedure_use (sym, &c->ext.actual, &(c->loc));
2571 if ((sym->intmod_sym_id == ISOCBINDING_F_POINTER) ||
2572 (sym->intmod_sym_id == ISOCBINDING_F_PROCPOINTER))
2574 set_name_and_label (c, sym, name, binding_label);
2576 if (sym->intmod_sym_id == ISOCBINDING_F_POINTER)
2578 if (c->ext.actual != NULL && c->ext.actual->next != NULL)
2580 /* Make sure we got a third arg if the second arg has non-zero
2581 rank. We must also check that the type and rank are
2582 correct since we short-circuit this check in
2583 gfc_procedure_use() (called above to sort actual args). */
2584 if (c->ext.actual->next->expr->rank != 0)
2586 if(c->ext.actual->next->next == NULL
2587 || c->ext.actual->next->next->expr == NULL)
2589 m = MATCH_ERROR;
2590 gfc_error ("Missing SHAPE parameter for call to %s "
2591 "at %L", sym->name, &(c->loc));
2593 else if (c->ext.actual->next->next->expr->ts.type
2594 != BT_INTEGER
2595 || c->ext.actual->next->next->expr->rank != 1)
2597 m = MATCH_ERROR;
2598 gfc_error ("SHAPE parameter for call to %s at %L must "
2599 "be a rank 1 INTEGER array", sym->name,
2600 &(c->loc));
2606 if (m != MATCH_ERROR)
2608 /* the 1 means to add the optional arg to formal list */
2609 new_sym = get_iso_c_sym (sym, name, binding_label, 1);
2611 /* for error reporting, say it's declared where the original was */
2612 new_sym->declared_at = sym->declared_at;
2615 else
2617 /* no differences for c_loc or c_funloc */
2618 new_sym = sym;
2621 /* set the resolved symbol */
2622 if (m != MATCH_ERROR)
2623 c->resolved_sym = new_sym;
2624 else
2625 c->resolved_sym = sym;
2627 return m;
2631 /* Resolve a subroutine call known to be specific. */
2633 static match
2634 resolve_specific_s0 (gfc_code *c, gfc_symbol *sym)
2636 match m;
2638 /* See if we have an intrinsic interface. */
2639 if (sym->ts.interface != NULL && !sym->ts.interface->attr.abstract
2640 && !sym->ts.interface->attr.subroutine)
2642 gfc_intrinsic_sym *isym;
2644 isym = gfc_find_function (sym->ts.interface->name);
2646 /* Existance of isym should be checked already. */
2647 gcc_assert (isym);
2649 sym->ts = isym->ts;
2650 sym->attr.function = 1;
2651 goto found;
2654 if(sym->attr.is_iso_c)
2656 m = gfc_iso_c_sub_interface (c,sym);
2657 return m;
2660 if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
2662 if (sym->attr.dummy)
2664 sym->attr.proc = PROC_DUMMY;
2665 goto found;
2668 sym->attr.proc = PROC_EXTERNAL;
2669 goto found;
2672 if (sym->attr.proc == PROC_MODULE || sym->attr.proc == PROC_INTERNAL)
2673 goto found;
2675 if (sym->attr.intrinsic)
2677 m = gfc_intrinsic_sub_interface (c, 1);
2678 if (m == MATCH_YES)
2679 return MATCH_YES;
2680 if (m == MATCH_NO)
2681 gfc_error ("Subroutine '%s' at %L is INTRINSIC but is not compatible "
2682 "with an intrinsic", sym->name, &c->loc);
2684 return MATCH_ERROR;
2687 return MATCH_NO;
2689 found:
2690 gfc_procedure_use (sym, &c->ext.actual, &c->loc);
2692 c->resolved_sym = sym;
2693 pure_subroutine (c, sym);
2695 return MATCH_YES;
2699 static try
2700 resolve_specific_s (gfc_code *c)
2702 gfc_symbol *sym;
2703 match m;
2705 sym = c->symtree->n.sym;
2707 for (;;)
2709 m = resolve_specific_s0 (c, sym);
2710 if (m == MATCH_YES)
2711 return SUCCESS;
2712 if (m == MATCH_ERROR)
2713 return FAILURE;
2715 if (sym->ns->parent == NULL)
2716 break;
2718 gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2720 if (sym == NULL)
2721 break;
2724 sym = c->symtree->n.sym;
2725 gfc_error ("Unable to resolve the specific subroutine '%s' at %L",
2726 sym->name, &c->loc);
2728 return FAILURE;
2732 /* Resolve a subroutine call not known to be generic nor specific. */
2734 static try
2735 resolve_unknown_s (gfc_code *c)
2737 gfc_symbol *sym;
2739 sym = c->symtree->n.sym;
2741 if (sym->attr.dummy)
2743 sym->attr.proc = PROC_DUMMY;
2744 goto found;
2747 /* See if we have an intrinsic function reference. */
2749 if (gfc_intrinsic_name (sym->name, 1))
2751 if (gfc_intrinsic_sub_interface (c, 1) == MATCH_YES)
2752 return SUCCESS;
2753 return FAILURE;
2756 /* The reference is to an external name. */
2758 found:
2759 gfc_procedure_use (sym, &c->ext.actual, &c->loc);
2761 c->resolved_sym = sym;
2763 pure_subroutine (c, sym);
2765 return SUCCESS;
2769 /* Resolve a subroutine call. Although it was tempting to use the same code
2770 for functions, subroutines and functions are stored differently and this
2771 makes things awkward. */
2773 static try
2774 resolve_call (gfc_code *c)
2776 try t;
2777 procedure_type ptype = PROC_INTRINSIC;
2779 if (c->symtree && c->symtree->n.sym
2780 && c->symtree->n.sym->ts.type != BT_UNKNOWN)
2782 gfc_error ("'%s' at %L has a type, which is not consistent with "
2783 "the CALL at %L", c->symtree->n.sym->name,
2784 &c->symtree->n.sym->declared_at, &c->loc);
2785 return FAILURE;
2788 /* If external, check for usage. */
2789 if (c->symtree && is_external_proc (c->symtree->n.sym))
2790 resolve_global_procedure (c->symtree->n.sym, &c->loc, 1);
2792 /* Subroutines without the RECURSIVE attribution are not allowed to
2793 * call themselves. */
2794 if (c->symtree && c->symtree->n.sym && !c->symtree->n.sym->attr.recursive)
2796 gfc_symbol *csym, *proc;
2797 csym = c->symtree->n.sym;
2798 proc = gfc_current_ns->proc_name;
2799 if (csym == proc)
2801 gfc_error ("SUBROUTINE '%s' at %L cannot call itself, as it is not "
2802 "RECURSIVE", csym->name, &c->loc);
2803 t = FAILURE;
2806 if (csym->attr.entry && csym->ns->entries && proc->ns->entries
2807 && csym->ns->entries->sym == proc->ns->entries->sym)
2809 gfc_error ("Call to ENTRY '%s' at %L is recursive, but subroutine "
2810 "'%s' is not declared as RECURSIVE",
2811 csym->name, &c->loc, csym->ns->entries->sym->name);
2812 t = FAILURE;
2816 /* Switch off assumed size checking and do this again for certain kinds
2817 of procedure, once the procedure itself is resolved. */
2818 need_full_assumed_size++;
2820 if (c->symtree && c->symtree->n.sym)
2821 ptype = c->symtree->n.sym->attr.proc;
2823 if (resolve_actual_arglist (c->ext.actual, ptype) == FAILURE)
2824 return FAILURE;
2826 /* Resume assumed_size checking. */
2827 need_full_assumed_size--;
2829 t = SUCCESS;
2830 if (c->resolved_sym == NULL)
2831 switch (procedure_kind (c->symtree->n.sym))
2833 case PTYPE_GENERIC:
2834 t = resolve_generic_s (c);
2835 break;
2837 case PTYPE_SPECIFIC:
2838 t = resolve_specific_s (c);
2839 break;
2841 case PTYPE_UNKNOWN:
2842 t = resolve_unknown_s (c);
2843 break;
2845 default:
2846 gfc_internal_error ("resolve_subroutine(): bad function type");
2849 /* Some checks of elemental subroutine actual arguments. */
2850 if (resolve_elemental_actual (NULL, c) == FAILURE)
2851 return FAILURE;
2853 if (t == SUCCESS && !(c->resolved_sym && c->resolved_sym->attr.elemental))
2854 find_noncopying_intrinsics (c->resolved_sym, c->ext.actual);
2855 return t;
2859 /* Compare the shapes of two arrays that have non-NULL shapes. If both
2860 op1->shape and op2->shape are non-NULL return SUCCESS if their shapes
2861 match. If both op1->shape and op2->shape are non-NULL return FAILURE
2862 if their shapes do not match. If either op1->shape or op2->shape is
2863 NULL, return SUCCESS. */
2865 static try
2866 compare_shapes (gfc_expr *op1, gfc_expr *op2)
2868 try t;
2869 int i;
2871 t = SUCCESS;
2873 if (op1->shape != NULL && op2->shape != NULL)
2875 for (i = 0; i < op1->rank; i++)
2877 if (mpz_cmp (op1->shape[i], op2->shape[i]) != 0)
2879 gfc_error ("Shapes for operands at %L and %L are not conformable",
2880 &op1->where, &op2->where);
2881 t = FAILURE;
2882 break;
2887 return t;
2891 /* Resolve an operator expression node. This can involve replacing the
2892 operation with a user defined function call. */
2894 static try
2895 resolve_operator (gfc_expr *e)
2897 gfc_expr *op1, *op2;
2898 char msg[200];
2899 bool dual_locus_error;
2900 try t;
2902 /* Resolve all subnodes-- give them types. */
2904 switch (e->value.op.operator)
2906 default:
2907 if (gfc_resolve_expr (e->value.op.op2) == FAILURE)
2908 return FAILURE;
2910 /* Fall through... */
2912 case INTRINSIC_NOT:
2913 case INTRINSIC_UPLUS:
2914 case INTRINSIC_UMINUS:
2915 case INTRINSIC_PARENTHESES:
2916 if (gfc_resolve_expr (e->value.op.op1) == FAILURE)
2917 return FAILURE;
2918 break;
2921 /* Typecheck the new node. */
2923 op1 = e->value.op.op1;
2924 op2 = e->value.op.op2;
2925 dual_locus_error = false;
2927 if ((op1 && op1->expr_type == EXPR_NULL)
2928 || (op2 && op2->expr_type == EXPR_NULL))
2930 sprintf (msg, _("Invalid context for NULL() pointer at %%L"));
2931 goto bad_op;
2934 switch (e->value.op.operator)
2936 case INTRINSIC_UPLUS:
2937 case INTRINSIC_UMINUS:
2938 if (op1->ts.type == BT_INTEGER
2939 || op1->ts.type == BT_REAL
2940 || op1->ts.type == BT_COMPLEX)
2942 e->ts = op1->ts;
2943 break;
2946 sprintf (msg, _("Operand of unary numeric operator '%s' at %%L is %s"),
2947 gfc_op2string (e->value.op.operator), gfc_typename (&e->ts));
2948 goto bad_op;
2950 case INTRINSIC_PLUS:
2951 case INTRINSIC_MINUS:
2952 case INTRINSIC_TIMES:
2953 case INTRINSIC_DIVIDE:
2954 case INTRINSIC_POWER:
2955 if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
2957 gfc_type_convert_binary (e);
2958 break;
2961 sprintf (msg,
2962 _("Operands of binary numeric operator '%s' at %%L are %s/%s"),
2963 gfc_op2string (e->value.op.operator), gfc_typename (&op1->ts),
2964 gfc_typename (&op2->ts));
2965 goto bad_op;
2967 case INTRINSIC_CONCAT:
2968 if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER)
2970 e->ts.type = BT_CHARACTER;
2971 e->ts.kind = op1->ts.kind;
2972 break;
2975 sprintf (msg,
2976 _("Operands of string concatenation operator at %%L are %s/%s"),
2977 gfc_typename (&op1->ts), gfc_typename (&op2->ts));
2978 goto bad_op;
2980 case INTRINSIC_AND:
2981 case INTRINSIC_OR:
2982 case INTRINSIC_EQV:
2983 case INTRINSIC_NEQV:
2984 if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
2986 e->ts.type = BT_LOGICAL;
2987 e->ts.kind = gfc_kind_max (op1, op2);
2988 if (op1->ts.kind < e->ts.kind)
2989 gfc_convert_type (op1, &e->ts, 2);
2990 else if (op2->ts.kind < e->ts.kind)
2991 gfc_convert_type (op2, &e->ts, 2);
2992 break;
2995 sprintf (msg, _("Operands of logical operator '%s' at %%L are %s/%s"),
2996 gfc_op2string (e->value.op.operator), gfc_typename (&op1->ts),
2997 gfc_typename (&op2->ts));
2999 goto bad_op;
3001 case INTRINSIC_NOT:
3002 if (op1->ts.type == BT_LOGICAL)
3004 e->ts.type = BT_LOGICAL;
3005 e->ts.kind = op1->ts.kind;
3006 break;
3009 sprintf (msg, _("Operand of .not. operator at %%L is %s"),
3010 gfc_typename (&op1->ts));
3011 goto bad_op;
3013 case INTRINSIC_GT:
3014 case INTRINSIC_GT_OS:
3015 case INTRINSIC_GE:
3016 case INTRINSIC_GE_OS:
3017 case INTRINSIC_LT:
3018 case INTRINSIC_LT_OS:
3019 case INTRINSIC_LE:
3020 case INTRINSIC_LE_OS:
3021 if (op1->ts.type == BT_COMPLEX || op2->ts.type == BT_COMPLEX)
3023 strcpy (msg, _("COMPLEX quantities cannot be compared at %L"));
3024 goto bad_op;
3027 /* Fall through... */
3029 case INTRINSIC_EQ:
3030 case INTRINSIC_EQ_OS:
3031 case INTRINSIC_NE:
3032 case INTRINSIC_NE_OS:
3033 if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER)
3035 e->ts.type = BT_LOGICAL;
3036 e->ts.kind = gfc_default_logical_kind;
3037 break;
3040 if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3042 gfc_type_convert_binary (e);
3044 e->ts.type = BT_LOGICAL;
3045 e->ts.kind = gfc_default_logical_kind;
3046 break;
3049 if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3050 sprintf (msg,
3051 _("Logicals at %%L must be compared with %s instead of %s"),
3052 (e->value.op.operator == INTRINSIC_EQ
3053 || e->value.op.operator == INTRINSIC_EQ_OS)
3054 ? ".eqv." : ".neqv.", gfc_op2string (e->value.op.operator));
3055 else
3056 sprintf (msg,
3057 _("Operands of comparison operator '%s' at %%L are %s/%s"),
3058 gfc_op2string (e->value.op.operator), gfc_typename (&op1->ts),
3059 gfc_typename (&op2->ts));
3061 goto bad_op;
3063 case INTRINSIC_USER:
3064 if (e->value.op.uop->operator == NULL)
3065 sprintf (msg, _("Unknown operator '%s' at %%L"), e->value.op.uop->name);
3066 else if (op2 == NULL)
3067 sprintf (msg, _("Operand of user operator '%s' at %%L is %s"),
3068 e->value.op.uop->name, gfc_typename (&op1->ts));
3069 else
3070 sprintf (msg, _("Operands of user operator '%s' at %%L are %s/%s"),
3071 e->value.op.uop->name, gfc_typename (&op1->ts),
3072 gfc_typename (&op2->ts));
3074 goto bad_op;
3076 case INTRINSIC_PARENTHESES:
3077 e->ts = op1->ts;
3078 if (e->ts.type == BT_CHARACTER)
3079 e->ts.cl = op1->ts.cl;
3080 break;
3082 default:
3083 gfc_internal_error ("resolve_operator(): Bad intrinsic");
3086 /* Deal with arrayness of an operand through an operator. */
3088 t = SUCCESS;
3090 switch (e->value.op.operator)
3092 case INTRINSIC_PLUS:
3093 case INTRINSIC_MINUS:
3094 case INTRINSIC_TIMES:
3095 case INTRINSIC_DIVIDE:
3096 case INTRINSIC_POWER:
3097 case INTRINSIC_CONCAT:
3098 case INTRINSIC_AND:
3099 case INTRINSIC_OR:
3100 case INTRINSIC_EQV:
3101 case INTRINSIC_NEQV:
3102 case INTRINSIC_EQ:
3103 case INTRINSIC_EQ_OS:
3104 case INTRINSIC_NE:
3105 case INTRINSIC_NE_OS:
3106 case INTRINSIC_GT:
3107 case INTRINSIC_GT_OS:
3108 case INTRINSIC_GE:
3109 case INTRINSIC_GE_OS:
3110 case INTRINSIC_LT:
3111 case INTRINSIC_LT_OS:
3112 case INTRINSIC_LE:
3113 case INTRINSIC_LE_OS:
3115 if (op1->rank == 0 && op2->rank == 0)
3116 e->rank = 0;
3118 if (op1->rank == 0 && op2->rank != 0)
3120 e->rank = op2->rank;
3122 if (e->shape == NULL)
3123 e->shape = gfc_copy_shape (op2->shape, op2->rank);
3126 if (op1->rank != 0 && op2->rank == 0)
3128 e->rank = op1->rank;
3130 if (e->shape == NULL)
3131 e->shape = gfc_copy_shape (op1->shape, op1->rank);
3134 if (op1->rank != 0 && op2->rank != 0)
3136 if (op1->rank == op2->rank)
3138 e->rank = op1->rank;
3139 if (e->shape == NULL)
3141 t = compare_shapes(op1, op2);
3142 if (t == FAILURE)
3143 e->shape = NULL;
3144 else
3145 e->shape = gfc_copy_shape (op1->shape, op1->rank);
3148 else
3150 /* Allow higher level expressions to work. */
3151 e->rank = 0;
3153 /* Try user-defined operators, and otherwise throw an error. */
3154 dual_locus_error = true;
3155 sprintf (msg,
3156 _("Inconsistent ranks for operator at %%L and %%L"));
3157 goto bad_op;
3161 break;
3163 case INTRINSIC_PARENTHESES:
3164 case INTRINSIC_NOT:
3165 case INTRINSIC_UPLUS:
3166 case INTRINSIC_UMINUS:
3167 /* Simply copy arrayness attribute */
3168 e->rank = op1->rank;
3170 if (e->shape == NULL)
3171 e->shape = gfc_copy_shape (op1->shape, op1->rank);
3173 break;
3175 default:
3176 break;
3179 /* Attempt to simplify the expression. */
3180 if (t == SUCCESS)
3182 t = gfc_simplify_expr (e, 0);
3183 /* Some calls do not succeed in simplification and return FAILURE
3184 even though there is no error; eg. variable references to
3185 PARAMETER arrays. */
3186 if (!gfc_is_constant_expr (e))
3187 t = SUCCESS;
3189 return t;
3191 bad_op:
3193 if (gfc_extend_expr (e) == SUCCESS)
3194 return SUCCESS;
3196 if (dual_locus_error)
3197 gfc_error (msg, &op1->where, &op2->where);
3198 else
3199 gfc_error (msg, &e->where);
3201 return FAILURE;
3205 /************** Array resolution subroutines **************/
3207 typedef enum
3208 { CMP_LT, CMP_EQ, CMP_GT, CMP_UNKNOWN }
3209 comparison;
3211 /* Compare two integer expressions. */
3213 static comparison
3214 compare_bound (gfc_expr *a, gfc_expr *b)
3216 int i;
3218 if (a == NULL || a->expr_type != EXPR_CONSTANT
3219 || b == NULL || b->expr_type != EXPR_CONSTANT)
3220 return CMP_UNKNOWN;
3222 /* If either of the types isn't INTEGER, we must have
3223 raised an error earlier. */
3225 if (a->ts.type != BT_INTEGER || b->ts.type != BT_INTEGER)
3226 return CMP_UNKNOWN;
3228 i = mpz_cmp (a->value.integer, b->value.integer);
3230 if (i < 0)
3231 return CMP_LT;
3232 if (i > 0)
3233 return CMP_GT;
3234 return CMP_EQ;
3238 /* Compare an integer expression with an integer. */
3240 static comparison
3241 compare_bound_int (gfc_expr *a, int b)
3243 int i;
3245 if (a == NULL || a->expr_type != EXPR_CONSTANT)
3246 return CMP_UNKNOWN;
3248 if (a->ts.type != BT_INTEGER)
3249 gfc_internal_error ("compare_bound_int(): Bad expression");
3251 i = mpz_cmp_si (a->value.integer, b);
3253 if (i < 0)
3254 return CMP_LT;
3255 if (i > 0)
3256 return CMP_GT;
3257 return CMP_EQ;
3261 /* Compare an integer expression with a mpz_t. */
3263 static comparison
3264 compare_bound_mpz_t (gfc_expr *a, mpz_t b)
3266 int i;
3268 if (a == NULL || a->expr_type != EXPR_CONSTANT)
3269 return CMP_UNKNOWN;
3271 if (a->ts.type != BT_INTEGER)
3272 gfc_internal_error ("compare_bound_int(): Bad expression");
3274 i = mpz_cmp (a->value.integer, b);
3276 if (i < 0)
3277 return CMP_LT;
3278 if (i > 0)
3279 return CMP_GT;
3280 return CMP_EQ;
3284 /* Compute the last value of a sequence given by a triplet.
3285 Return 0 if it wasn't able to compute the last value, or if the
3286 sequence if empty, and 1 otherwise. */
3288 static int
3289 compute_last_value_for_triplet (gfc_expr *start, gfc_expr *end,
3290 gfc_expr *stride, mpz_t last)
3292 mpz_t rem;
3294 if (start == NULL || start->expr_type != EXPR_CONSTANT
3295 || end == NULL || end->expr_type != EXPR_CONSTANT
3296 || (stride != NULL && stride->expr_type != EXPR_CONSTANT))
3297 return 0;
3299 if (start->ts.type != BT_INTEGER || end->ts.type != BT_INTEGER
3300 || (stride != NULL && stride->ts.type != BT_INTEGER))
3301 return 0;
3303 if (stride == NULL || compare_bound_int(stride, 1) == CMP_EQ)
3305 if (compare_bound (start, end) == CMP_GT)
3306 return 0;
3307 mpz_set (last, end->value.integer);
3308 return 1;
3311 if (compare_bound_int (stride, 0) == CMP_GT)
3313 /* Stride is positive */
3314 if (mpz_cmp (start->value.integer, end->value.integer) > 0)
3315 return 0;
3317 else
3319 /* Stride is negative */
3320 if (mpz_cmp (start->value.integer, end->value.integer) < 0)
3321 return 0;
3324 mpz_init (rem);
3325 mpz_sub (rem, end->value.integer, start->value.integer);
3326 mpz_tdiv_r (rem, rem, stride->value.integer);
3327 mpz_sub (last, end->value.integer, rem);
3328 mpz_clear (rem);
3330 return 1;
3334 /* Compare a single dimension of an array reference to the array
3335 specification. */
3337 static try
3338 check_dimension (int i, gfc_array_ref *ar, gfc_array_spec *as)
3340 mpz_t last_value;
3342 /* Given start, end and stride values, calculate the minimum and
3343 maximum referenced indexes. */
3345 switch (ar->dimen_type[i])
3347 case DIMEN_VECTOR:
3348 break;
3350 case DIMEN_ELEMENT:
3351 if (compare_bound (ar->start[i], as->lower[i]) == CMP_LT)
3353 gfc_warning ("Array reference at %L is out of bounds "
3354 "(%ld < %ld) in dimension %d", &ar->c_where[i],
3355 mpz_get_si (ar->start[i]->value.integer),
3356 mpz_get_si (as->lower[i]->value.integer), i+1);
3357 return SUCCESS;
3359 if (compare_bound (ar->start[i], as->upper[i]) == CMP_GT)
3361 gfc_warning ("Array reference at %L is out of bounds "
3362 "(%ld > %ld) in dimension %d", &ar->c_where[i],
3363 mpz_get_si (ar->start[i]->value.integer),
3364 mpz_get_si (as->upper[i]->value.integer), i+1);
3365 return SUCCESS;
3368 break;
3370 case DIMEN_RANGE:
3372 #define AR_START (ar->start[i] ? ar->start[i] : as->lower[i])
3373 #define AR_END (ar->end[i] ? ar->end[i] : as->upper[i])
3375 comparison comp_start_end = compare_bound (AR_START, AR_END);
3377 /* Check for zero stride, which is not allowed. */
3378 if (compare_bound_int (ar->stride[i], 0) == CMP_EQ)
3380 gfc_error ("Illegal stride of zero at %L", &ar->c_where[i]);
3381 return FAILURE;
3384 /* if start == len || (stride > 0 && start < len)
3385 || (stride < 0 && start > len),
3386 then the array section contains at least one element. In this
3387 case, there is an out-of-bounds access if
3388 (start < lower || start > upper). */
3389 if (compare_bound (AR_START, AR_END) == CMP_EQ
3390 || ((compare_bound_int (ar->stride[i], 0) == CMP_GT
3391 || ar->stride[i] == NULL) && comp_start_end == CMP_LT)
3392 || (compare_bound_int (ar->stride[i], 0) == CMP_LT
3393 && comp_start_end == CMP_GT))
3395 if (compare_bound (AR_START, as->lower[i]) == CMP_LT)
3397 gfc_warning ("Lower array reference at %L is out of bounds "
3398 "(%ld < %ld) in dimension %d", &ar->c_where[i],
3399 mpz_get_si (AR_START->value.integer),
3400 mpz_get_si (as->lower[i]->value.integer), i+1);
3401 return SUCCESS;
3403 if (compare_bound (AR_START, as->upper[i]) == CMP_GT)
3405 gfc_warning ("Lower array reference at %L is out of bounds "
3406 "(%ld > %ld) in dimension %d", &ar->c_where[i],
3407 mpz_get_si (AR_START->value.integer),
3408 mpz_get_si (as->upper[i]->value.integer), i+1);
3409 return SUCCESS;
3413 /* If we can compute the highest index of the array section,
3414 then it also has to be between lower and upper. */
3415 mpz_init (last_value);
3416 if (compute_last_value_for_triplet (AR_START, AR_END, ar->stride[i],
3417 last_value))
3419 if (compare_bound_mpz_t (as->lower[i], last_value) == CMP_GT)
3421 gfc_warning ("Upper array reference at %L is out of bounds "
3422 "(%ld < %ld) in dimension %d", &ar->c_where[i],
3423 mpz_get_si (last_value),
3424 mpz_get_si (as->lower[i]->value.integer), i+1);
3425 mpz_clear (last_value);
3426 return SUCCESS;
3428 if (compare_bound_mpz_t (as->upper[i], last_value) == CMP_LT)
3430 gfc_warning ("Upper array reference at %L is out of bounds "
3431 "(%ld > %ld) in dimension %d", &ar->c_where[i],
3432 mpz_get_si (last_value),
3433 mpz_get_si (as->upper[i]->value.integer), i+1);
3434 mpz_clear (last_value);
3435 return SUCCESS;
3438 mpz_clear (last_value);
3440 #undef AR_START
3441 #undef AR_END
3443 break;
3445 default:
3446 gfc_internal_error ("check_dimension(): Bad array reference");
3449 return SUCCESS;
3453 /* Compare an array reference with an array specification. */
3455 static try
3456 compare_spec_to_ref (gfc_array_ref *ar)
3458 gfc_array_spec *as;
3459 int i;
3461 as = ar->as;
3462 i = as->rank - 1;
3463 /* TODO: Full array sections are only allowed as actual parameters. */
3464 if (as->type == AS_ASSUMED_SIZE
3465 && (/*ar->type == AR_FULL
3466 ||*/ (ar->type == AR_SECTION
3467 && ar->dimen_type[i] == DIMEN_RANGE && ar->end[i] == NULL)))
3469 gfc_error ("Rightmost upper bound of assumed size array section "
3470 "not specified at %L", &ar->where);
3471 return FAILURE;
3474 if (ar->type == AR_FULL)
3475 return SUCCESS;
3477 if (as->rank != ar->dimen)
3479 gfc_error ("Rank mismatch in array reference at %L (%d/%d)",
3480 &ar->where, ar->dimen, as->rank);
3481 return FAILURE;
3484 for (i = 0; i < as->rank; i++)
3485 if (check_dimension (i, ar, as) == FAILURE)
3486 return FAILURE;
3488 return SUCCESS;
3492 /* Resolve one part of an array index. */
3495 gfc_resolve_index (gfc_expr *index, int check_scalar)
3497 gfc_typespec ts;
3499 if (index == NULL)
3500 return SUCCESS;
3502 if (gfc_resolve_expr (index) == FAILURE)
3503 return FAILURE;
3505 if (check_scalar && index->rank != 0)
3507 gfc_error ("Array index at %L must be scalar", &index->where);
3508 return FAILURE;
3511 if (index->ts.type != BT_INTEGER && index->ts.type != BT_REAL)
3513 gfc_error ("Array index at %L must be of INTEGER type",
3514 &index->where);
3515 return FAILURE;
3518 if (index->ts.type == BT_REAL)
3519 if (gfc_notify_std (GFC_STD_LEGACY, "Extension: REAL array index at %L",
3520 &index->where) == FAILURE)
3521 return FAILURE;
3523 if (index->ts.kind != gfc_index_integer_kind
3524 || index->ts.type != BT_INTEGER)
3526 gfc_clear_ts (&ts);
3527 ts.type = BT_INTEGER;
3528 ts.kind = gfc_index_integer_kind;
3530 gfc_convert_type_warn (index, &ts, 2, 0);
3533 return SUCCESS;
3536 /* Resolve a dim argument to an intrinsic function. */
3539 gfc_resolve_dim_arg (gfc_expr *dim)
3541 if (dim == NULL)
3542 return SUCCESS;
3544 if (gfc_resolve_expr (dim) == FAILURE)
3545 return FAILURE;
3547 if (dim->rank != 0)
3549 gfc_error ("Argument dim at %L must be scalar", &dim->where);
3550 return FAILURE;
3554 if (dim->ts.type != BT_INTEGER)
3556 gfc_error ("Argument dim at %L must be of INTEGER type", &dim->where);
3557 return FAILURE;
3560 if (dim->ts.kind != gfc_index_integer_kind)
3562 gfc_typespec ts;
3564 ts.type = BT_INTEGER;
3565 ts.kind = gfc_index_integer_kind;
3567 gfc_convert_type_warn (dim, &ts, 2, 0);
3570 return SUCCESS;
3573 /* Given an expression that contains array references, update those array
3574 references to point to the right array specifications. While this is
3575 filled in during matching, this information is difficult to save and load
3576 in a module, so we take care of it here.
3578 The idea here is that the original array reference comes from the
3579 base symbol. We traverse the list of reference structures, setting
3580 the stored reference to references. Component references can
3581 provide an additional array specification. */
3583 static void
3584 find_array_spec (gfc_expr *e)
3586 gfc_array_spec *as;
3587 gfc_component *c;
3588 gfc_symbol *derived;
3589 gfc_ref *ref;
3591 as = e->symtree->n.sym->as;
3592 derived = NULL;
3594 for (ref = e->ref; ref; ref = ref->next)
3595 switch (ref->type)
3597 case REF_ARRAY:
3598 if (as == NULL)
3599 gfc_internal_error ("find_array_spec(): Missing spec");
3601 ref->u.ar.as = as;
3602 as = NULL;
3603 break;
3605 case REF_COMPONENT:
3606 if (derived == NULL)
3607 derived = e->symtree->n.sym->ts.derived;
3609 c = derived->components;
3611 for (; c; c = c->next)
3612 if (c == ref->u.c.component)
3614 /* Track the sequence of component references. */
3615 if (c->ts.type == BT_DERIVED)
3616 derived = c->ts.derived;
3617 break;
3620 if (c == NULL)
3621 gfc_internal_error ("find_array_spec(): Component not found");
3623 if (c->dimension)
3625 if (as != NULL)
3626 gfc_internal_error ("find_array_spec(): unused as(1)");
3627 as = c->as;
3630 break;
3632 case REF_SUBSTRING:
3633 break;
3636 if (as != NULL)
3637 gfc_internal_error ("find_array_spec(): unused as(2)");
3641 /* Resolve an array reference. */
3643 static try
3644 resolve_array_ref (gfc_array_ref *ar)
3646 int i, check_scalar;
3647 gfc_expr *e;
3649 for (i = 0; i < ar->dimen; i++)
3651 check_scalar = ar->dimen_type[i] == DIMEN_RANGE;
3653 if (gfc_resolve_index (ar->start[i], check_scalar) == FAILURE)
3654 return FAILURE;
3655 if (gfc_resolve_index (ar->end[i], check_scalar) == FAILURE)
3656 return FAILURE;
3657 if (gfc_resolve_index (ar->stride[i], check_scalar) == FAILURE)
3658 return FAILURE;
3660 e = ar->start[i];
3662 if (ar->dimen_type[i] == DIMEN_UNKNOWN)
3663 switch (e->rank)
3665 case 0:
3666 ar->dimen_type[i] = DIMEN_ELEMENT;
3667 break;
3669 case 1:
3670 ar->dimen_type[i] = DIMEN_VECTOR;
3671 if (e->expr_type == EXPR_VARIABLE
3672 && e->symtree->n.sym->ts.type == BT_DERIVED)
3673 ar->start[i] = gfc_get_parentheses (e);
3674 break;
3676 default:
3677 gfc_error ("Array index at %L is an array of rank %d",
3678 &ar->c_where[i], e->rank);
3679 return FAILURE;
3683 /* If the reference type is unknown, figure out what kind it is. */
3685 if (ar->type == AR_UNKNOWN)
3687 ar->type = AR_ELEMENT;
3688 for (i = 0; i < ar->dimen; i++)
3689 if (ar->dimen_type[i] == DIMEN_RANGE
3690 || ar->dimen_type[i] == DIMEN_VECTOR)
3692 ar->type = AR_SECTION;
3693 break;
3697 if (!ar->as->cray_pointee && compare_spec_to_ref (ar) == FAILURE)
3698 return FAILURE;
3700 return SUCCESS;
3704 static try
3705 resolve_substring (gfc_ref *ref)
3707 if (ref->u.ss.start != NULL)
3709 if (gfc_resolve_expr (ref->u.ss.start) == FAILURE)
3710 return FAILURE;
3712 if (ref->u.ss.start->ts.type != BT_INTEGER)
3714 gfc_error ("Substring start index at %L must be of type INTEGER",
3715 &ref->u.ss.start->where);
3716 return FAILURE;
3719 if (ref->u.ss.start->rank != 0)
3721 gfc_error ("Substring start index at %L must be scalar",
3722 &ref->u.ss.start->where);
3723 return FAILURE;
3726 if (compare_bound_int (ref->u.ss.start, 1) == CMP_LT
3727 && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
3728 || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
3730 gfc_error ("Substring start index at %L is less than one",
3731 &ref->u.ss.start->where);
3732 return FAILURE;
3736 if (ref->u.ss.end != NULL)
3738 if (gfc_resolve_expr (ref->u.ss.end) == FAILURE)
3739 return FAILURE;
3741 if (ref->u.ss.end->ts.type != BT_INTEGER)
3743 gfc_error ("Substring end index at %L must be of type INTEGER",
3744 &ref->u.ss.end->where);
3745 return FAILURE;
3748 if (ref->u.ss.end->rank != 0)
3750 gfc_error ("Substring end index at %L must be scalar",
3751 &ref->u.ss.end->where);
3752 return FAILURE;
3755 if (ref->u.ss.length != NULL
3756 && compare_bound (ref->u.ss.end, ref->u.ss.length->length) == CMP_GT
3757 && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
3758 || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
3760 gfc_error ("Substring end index at %L exceeds the string length",
3761 &ref->u.ss.start->where);
3762 return FAILURE;
3766 return SUCCESS;
3770 /* This function supplies missing substring charlens. */
3772 void
3773 gfc_resolve_substring_charlen (gfc_expr *e)
3775 gfc_ref *char_ref;
3776 gfc_expr *start, *end;
3778 for (char_ref = e->ref; char_ref; char_ref = char_ref->next)
3779 if (char_ref->type == REF_SUBSTRING)
3780 break;
3782 if (!char_ref)
3783 return;
3785 gcc_assert (char_ref->next == NULL);
3787 if (e->ts.cl)
3789 if (e->ts.cl->length)
3790 gfc_free_expr (e->ts.cl->length);
3791 else if (e->expr_type == EXPR_VARIABLE
3792 && e->symtree->n.sym->attr.dummy)
3793 return;
3796 e->ts.type = BT_CHARACTER;
3797 e->ts.kind = gfc_default_character_kind;
3799 if (!e->ts.cl)
3801 e->ts.cl = gfc_get_charlen ();
3802 e->ts.cl->next = gfc_current_ns->cl_list;
3803 gfc_current_ns->cl_list = e->ts.cl;
3806 if (char_ref->u.ss.start)
3807 start = gfc_copy_expr (char_ref->u.ss.start);
3808 else
3809 start = gfc_int_expr (1);
3811 if (char_ref->u.ss.end)
3812 end = gfc_copy_expr (char_ref->u.ss.end);
3813 else if (e->expr_type == EXPR_VARIABLE)
3814 end = gfc_copy_expr (e->symtree->n.sym->ts.cl->length);
3815 else
3816 end = NULL;
3818 if (!start || !end)
3819 return;
3821 /* Length = (end - start +1). */
3822 e->ts.cl->length = gfc_subtract (end, start);
3823 e->ts.cl->length = gfc_add (e->ts.cl->length, gfc_int_expr (1));
3825 e->ts.cl->length->ts.type = BT_INTEGER;
3826 e->ts.cl->length->ts.kind = gfc_charlen_int_kind;;
3828 /* Make sure that the length is simplified. */
3829 gfc_simplify_expr (e->ts.cl->length, 1);
3830 gfc_resolve_expr (e->ts.cl->length);
3834 /* Resolve subtype references. */
3836 static try
3837 resolve_ref (gfc_expr *expr)
3839 int current_part_dimension, n_components, seen_part_dimension;
3840 gfc_ref *ref;
3842 for (ref = expr->ref; ref; ref = ref->next)
3843 if (ref->type == REF_ARRAY && ref->u.ar.as == NULL)
3845 find_array_spec (expr);
3846 break;
3849 for (ref = expr->ref; ref; ref = ref->next)
3850 switch (ref->type)
3852 case REF_ARRAY:
3853 if (resolve_array_ref (&ref->u.ar) == FAILURE)
3854 return FAILURE;
3855 break;
3857 case REF_COMPONENT:
3858 break;
3860 case REF_SUBSTRING:
3861 resolve_substring (ref);
3862 break;
3865 /* Check constraints on part references. */
3867 current_part_dimension = 0;
3868 seen_part_dimension = 0;
3869 n_components = 0;
3871 for (ref = expr->ref; ref; ref = ref->next)
3873 switch (ref->type)
3875 case REF_ARRAY:
3876 switch (ref->u.ar.type)
3878 case AR_FULL:
3879 case AR_SECTION:
3880 current_part_dimension = 1;
3881 break;
3883 case AR_ELEMENT:
3884 current_part_dimension = 0;
3885 break;
3887 case AR_UNKNOWN:
3888 gfc_internal_error ("resolve_ref(): Bad array reference");
3891 break;
3893 case REF_COMPONENT:
3894 if (current_part_dimension || seen_part_dimension)
3896 if (ref->u.c.component->pointer)
3898 gfc_error ("Component to the right of a part reference "
3899 "with nonzero rank must not have the POINTER "
3900 "attribute at %L", &expr->where);
3901 return FAILURE;
3903 else if (ref->u.c.component->allocatable)
3905 gfc_error ("Component to the right of a part reference "
3906 "with nonzero rank must not have the ALLOCATABLE "
3907 "attribute at %L", &expr->where);
3908 return FAILURE;
3912 n_components++;
3913 break;
3915 case REF_SUBSTRING:
3916 break;
3919 if (((ref->type == REF_COMPONENT && n_components > 1)
3920 || ref->next == NULL)
3921 && current_part_dimension
3922 && seen_part_dimension)
3924 gfc_error ("Two or more part references with nonzero rank must "
3925 "not be specified at %L", &expr->where);
3926 return FAILURE;
3929 if (ref->type == REF_COMPONENT)
3931 if (current_part_dimension)
3932 seen_part_dimension = 1;
3934 /* reset to make sure */
3935 current_part_dimension = 0;
3939 return SUCCESS;
3943 /* Given an expression, determine its shape. This is easier than it sounds.
3944 Leaves the shape array NULL if it is not possible to determine the shape. */
3946 static void
3947 expression_shape (gfc_expr *e)
3949 mpz_t array[GFC_MAX_DIMENSIONS];
3950 int i;
3952 if (e->rank == 0 || e->shape != NULL)
3953 return;
3955 for (i = 0; i < e->rank; i++)
3956 if (gfc_array_dimen_size (e, i, &array[i]) == FAILURE)
3957 goto fail;
3959 e->shape = gfc_get_shape (e->rank);
3961 memcpy (e->shape, array, e->rank * sizeof (mpz_t));
3963 return;
3965 fail:
3966 for (i--; i >= 0; i--)
3967 mpz_clear (array[i]);
3971 /* Given a variable expression node, compute the rank of the expression by
3972 examining the base symbol and any reference structures it may have. */
3974 static void
3975 expression_rank (gfc_expr *e)
3977 gfc_ref *ref;
3978 int i, rank;
3980 if (e->ref == NULL)
3982 if (e->expr_type == EXPR_ARRAY)
3983 goto done;
3984 /* Constructors can have a rank different from one via RESHAPE(). */
3986 if (e->symtree == NULL)
3988 e->rank = 0;
3989 goto done;
3992 e->rank = (e->symtree->n.sym->as == NULL)
3993 ? 0 : e->symtree->n.sym->as->rank;
3994 goto done;
3997 rank = 0;
3999 for (ref = e->ref; ref; ref = ref->next)
4001 if (ref->type != REF_ARRAY)
4002 continue;
4004 if (ref->u.ar.type == AR_FULL)
4006 rank = ref->u.ar.as->rank;
4007 break;
4010 if (ref->u.ar.type == AR_SECTION)
4012 /* Figure out the rank of the section. */
4013 if (rank != 0)
4014 gfc_internal_error ("expression_rank(): Two array specs");
4016 for (i = 0; i < ref->u.ar.dimen; i++)
4017 if (ref->u.ar.dimen_type[i] == DIMEN_RANGE
4018 || ref->u.ar.dimen_type[i] == DIMEN_VECTOR)
4019 rank++;
4021 break;
4025 e->rank = rank;
4027 done:
4028 expression_shape (e);
4032 /* Resolve a variable expression. */
4034 static try
4035 resolve_variable (gfc_expr *e)
4037 gfc_symbol *sym;
4038 try t;
4040 t = SUCCESS;
4042 if (e->symtree == NULL)
4043 return FAILURE;
4045 if (e->ref && resolve_ref (e) == FAILURE)
4046 return FAILURE;
4048 sym = e->symtree->n.sym;
4049 if (sym->attr.flavor == FL_PROCEDURE && !sym->attr.function)
4051 e->ts.type = BT_PROCEDURE;
4052 return SUCCESS;
4055 if (sym->ts.type != BT_UNKNOWN)
4056 gfc_variable_attr (e, &e->ts);
4057 else
4059 /* Must be a simple variable reference. */
4060 if (gfc_set_default_type (sym, 1, sym->ns) == FAILURE)
4061 return FAILURE;
4062 e->ts = sym->ts;
4065 if (check_assumed_size_reference (sym, e))
4066 return FAILURE;
4068 /* Deal with forward references to entries during resolve_code, to
4069 satisfy, at least partially, 12.5.2.5. */
4070 if (gfc_current_ns->entries
4071 && current_entry_id == sym->entry_id
4072 && cs_base
4073 && cs_base->current
4074 && cs_base->current->op != EXEC_ENTRY)
4076 gfc_entry_list *entry;
4077 gfc_formal_arglist *formal;
4078 int n;
4079 bool seen;
4081 /* If the symbol is a dummy... */
4082 if (sym->attr.dummy && sym->ns == gfc_current_ns)
4084 entry = gfc_current_ns->entries;
4085 seen = false;
4087 /* ...test if the symbol is a parameter of previous entries. */
4088 for (; entry && entry->id <= current_entry_id; entry = entry->next)
4089 for (formal = entry->sym->formal; formal; formal = formal->next)
4091 if (formal->sym && sym->name == formal->sym->name)
4092 seen = true;
4095 /* If it has not been seen as a dummy, this is an error. */
4096 if (!seen)
4098 if (specification_expr)
4099 gfc_error ("Variable '%s', used in a specification expression"
4100 ", is referenced at %L before the ENTRY statement "
4101 "in which it is a parameter",
4102 sym->name, &cs_base->current->loc);
4103 else
4104 gfc_error ("Variable '%s' is used at %L before the ENTRY "
4105 "statement in which it is a parameter",
4106 sym->name, &cs_base->current->loc);
4107 t = FAILURE;
4111 /* Now do the same check on the specification expressions. */
4112 specification_expr = 1;
4113 if (sym->ts.type == BT_CHARACTER
4114 && gfc_resolve_expr (sym->ts.cl->length) == FAILURE)
4115 t = FAILURE;
4117 if (sym->as)
4118 for (n = 0; n < sym->as->rank; n++)
4120 specification_expr = 1;
4121 if (gfc_resolve_expr (sym->as->lower[n]) == FAILURE)
4122 t = FAILURE;
4123 specification_expr = 1;
4124 if (gfc_resolve_expr (sym->as->upper[n]) == FAILURE)
4125 t = FAILURE;
4127 specification_expr = 0;
4129 if (t == SUCCESS)
4130 /* Update the symbol's entry level. */
4131 sym->entry_id = current_entry_id + 1;
4134 return t;
4138 /* Checks to see that the correct symbol has been host associated.
4139 The only situation where this arises is that in which a twice
4140 contained function is parsed after the host association is made.
4141 Therefore, on detecting this, the line is rematched, having got
4142 rid of the existing references and actual_arg_list. */
4143 static bool
4144 check_host_association (gfc_expr *e)
4146 gfc_symbol *sym, *old_sym;
4147 locus temp_locus;
4148 gfc_expr *expr;
4149 int n;
4150 bool retval = e->expr_type == EXPR_FUNCTION;
4152 if (e->symtree == NULL || e->symtree->n.sym == NULL)
4153 return retval;
4155 old_sym = e->symtree->n.sym;
4157 if (old_sym->attr.use_assoc)
4158 return retval;
4160 if (gfc_current_ns->parent
4161 && old_sym->ns != gfc_current_ns)
4163 gfc_find_symbol (old_sym->name, gfc_current_ns, 1, &sym);
4164 if (sym && old_sym != sym
4165 && sym->attr.flavor == FL_PROCEDURE
4166 && sym->attr.contained)
4168 temp_locus = gfc_current_locus;
4169 gfc_current_locus = e->where;
4171 gfc_buffer_error (1);
4173 gfc_free_ref_list (e->ref);
4174 e->ref = NULL;
4176 if (retval)
4178 gfc_free_actual_arglist (e->value.function.actual);
4179 e->value.function.actual = NULL;
4182 if (e->shape != NULL)
4184 for (n = 0; n < e->rank; n++)
4185 mpz_clear (e->shape[n]);
4187 gfc_free (e->shape);
4190 gfc_match_rvalue (&expr);
4191 gfc_clear_error ();
4192 gfc_buffer_error (0);
4194 gcc_assert (expr && sym == expr->symtree->n.sym);
4196 *e = *expr;
4197 gfc_free (expr);
4198 sym->refs++;
4200 gfc_current_locus = temp_locus;
4203 /* This might have changed! */
4204 return e->expr_type == EXPR_FUNCTION;
4208 static void
4209 gfc_resolve_character_operator (gfc_expr *e)
4211 gfc_expr *op1 = e->value.op.op1;
4212 gfc_expr *op2 = e->value.op.op2;
4213 gfc_expr *e1 = NULL;
4214 gfc_expr *e2 = NULL;
4216 gcc_assert (e->value.op.operator == INTRINSIC_CONCAT);
4218 if (op1->ts.cl && op1->ts.cl->length)
4219 e1 = gfc_copy_expr (op1->ts.cl->length);
4220 else if (op1->expr_type == EXPR_CONSTANT)
4221 e1 = gfc_int_expr (op1->value.character.length);
4223 if (op2->ts.cl && op2->ts.cl->length)
4224 e2 = gfc_copy_expr (op2->ts.cl->length);
4225 else if (op2->expr_type == EXPR_CONSTANT)
4226 e2 = gfc_int_expr (op2->value.character.length);
4228 e->ts.cl = gfc_get_charlen ();
4229 e->ts.cl->next = gfc_current_ns->cl_list;
4230 gfc_current_ns->cl_list = e->ts.cl;
4232 if (!e1 || !e2)
4233 return;
4235 e->ts.cl->length = gfc_add (e1, e2);
4236 e->ts.cl->length->ts.type = BT_INTEGER;
4237 e->ts.cl->length->ts.kind = gfc_charlen_int_kind;;
4238 gfc_simplify_expr (e->ts.cl->length, 0);
4239 gfc_resolve_expr (e->ts.cl->length);
4241 return;
4245 /* Ensure that an character expression has a charlen and, if possible, a
4246 length expression. */
4248 static void
4249 fixup_charlen (gfc_expr *e)
4251 /* The cases fall through so that changes in expression type and the need
4252 for multiple fixes are picked up. In all circumstances, a charlen should
4253 be available for the middle end to hang a backend_decl on. */
4254 switch (e->expr_type)
4256 case EXPR_OP:
4257 gfc_resolve_character_operator (e);
4259 case EXPR_ARRAY:
4260 if (e->expr_type == EXPR_ARRAY)
4261 gfc_resolve_character_array_constructor (e);
4263 case EXPR_SUBSTRING:
4264 if (!e->ts.cl && e->ref)
4265 gfc_resolve_substring_charlen (e);
4267 default:
4268 if (!e->ts.cl)
4270 e->ts.cl = gfc_get_charlen ();
4271 e->ts.cl->next = gfc_current_ns->cl_list;
4272 gfc_current_ns->cl_list = e->ts.cl;
4275 break;
4280 /* Resolve an expression. That is, make sure that types of operands agree
4281 with their operators, intrinsic operators are converted to function calls
4282 for overloaded types and unresolved function references are resolved. */
4285 gfc_resolve_expr (gfc_expr *e)
4287 try t;
4289 if (e == NULL)
4290 return SUCCESS;
4292 switch (e->expr_type)
4294 case EXPR_OP:
4295 t = resolve_operator (e);
4296 break;
4298 case EXPR_FUNCTION:
4299 case EXPR_VARIABLE:
4301 if (check_host_association (e))
4302 t = resolve_function (e);
4303 else
4305 t = resolve_variable (e);
4306 if (t == SUCCESS)
4307 expression_rank (e);
4310 if (e->ts.type == BT_CHARACTER && e->ts.cl == NULL && e->ref
4311 && e->ref->type != REF_SUBSTRING)
4312 gfc_resolve_substring_charlen (e);
4314 break;
4316 case EXPR_SUBSTRING:
4317 t = resolve_ref (e);
4318 break;
4320 case EXPR_CONSTANT:
4321 case EXPR_NULL:
4322 t = SUCCESS;
4323 break;
4325 case EXPR_ARRAY:
4326 t = FAILURE;
4327 if (resolve_ref (e) == FAILURE)
4328 break;
4330 t = gfc_resolve_array_constructor (e);
4331 /* Also try to expand a constructor. */
4332 if (t == SUCCESS)
4334 expression_rank (e);
4335 gfc_expand_constructor (e);
4338 /* This provides the opportunity for the length of constructors with
4339 character valued function elements to propagate the string length
4340 to the expression. */
4341 if (e->ts.type == BT_CHARACTER)
4342 gfc_resolve_character_array_constructor (e);
4344 break;
4346 case EXPR_STRUCTURE:
4347 t = resolve_ref (e);
4348 if (t == FAILURE)
4349 break;
4351 t = resolve_structure_cons (e);
4352 if (t == FAILURE)
4353 break;
4355 t = gfc_simplify_expr (e, 0);
4356 break;
4358 default:
4359 gfc_internal_error ("gfc_resolve_expr(): Bad expression type");
4362 if (e->ts.type == BT_CHARACTER && t == SUCCESS && !e->ts.cl)
4363 fixup_charlen (e);
4365 return t;
4369 /* Resolve an expression from an iterator. They must be scalar and have
4370 INTEGER or (optionally) REAL type. */
4372 static try
4373 gfc_resolve_iterator_expr (gfc_expr *expr, bool real_ok,
4374 const char *name_msgid)
4376 if (gfc_resolve_expr (expr) == FAILURE)
4377 return FAILURE;
4379 if (expr->rank != 0)
4381 gfc_error ("%s at %L must be a scalar", _(name_msgid), &expr->where);
4382 return FAILURE;
4385 if (expr->ts.type != BT_INTEGER)
4387 if (expr->ts.type == BT_REAL)
4389 if (real_ok)
4390 return gfc_notify_std (GFC_STD_F95_DEL,
4391 "Deleted feature: %s at %L must be integer",
4392 _(name_msgid), &expr->where);
4393 else
4395 gfc_error ("%s at %L must be INTEGER", _(name_msgid),
4396 &expr->where);
4397 return FAILURE;
4400 else
4402 gfc_error ("%s at %L must be INTEGER", _(name_msgid), &expr->where);
4403 return FAILURE;
4406 return SUCCESS;
4410 /* Resolve the expressions in an iterator structure. If REAL_OK is
4411 false allow only INTEGER type iterators, otherwise allow REAL types. */
4414 gfc_resolve_iterator (gfc_iterator *iter, bool real_ok)
4416 if (gfc_resolve_iterator_expr (iter->var, real_ok, "Loop variable")
4417 == FAILURE)
4418 return FAILURE;
4420 if (gfc_pure (NULL) && gfc_impure_variable (iter->var->symtree->n.sym))
4422 gfc_error ("Cannot assign to loop variable in PURE procedure at %L",
4423 &iter->var->where);
4424 return FAILURE;
4427 if (gfc_resolve_iterator_expr (iter->start, real_ok,
4428 "Start expression in DO loop") == FAILURE)
4429 return FAILURE;
4431 if (gfc_resolve_iterator_expr (iter->end, real_ok,
4432 "End expression in DO loop") == FAILURE)
4433 return FAILURE;
4435 if (gfc_resolve_iterator_expr (iter->step, real_ok,
4436 "Step expression in DO loop") == FAILURE)
4437 return FAILURE;
4439 if (iter->step->expr_type == EXPR_CONSTANT)
4441 if ((iter->step->ts.type == BT_INTEGER
4442 && mpz_cmp_ui (iter->step->value.integer, 0) == 0)
4443 || (iter->step->ts.type == BT_REAL
4444 && mpfr_sgn (iter->step->value.real) == 0))
4446 gfc_error ("Step expression in DO loop at %L cannot be zero",
4447 &iter->step->where);
4448 return FAILURE;
4452 /* Convert start, end, and step to the same type as var. */
4453 if (iter->start->ts.kind != iter->var->ts.kind
4454 || iter->start->ts.type != iter->var->ts.type)
4455 gfc_convert_type (iter->start, &iter->var->ts, 2);
4457 if (iter->end->ts.kind != iter->var->ts.kind
4458 || iter->end->ts.type != iter->var->ts.type)
4459 gfc_convert_type (iter->end, &iter->var->ts, 2);
4461 if (iter->step->ts.kind != iter->var->ts.kind
4462 || iter->step->ts.type != iter->var->ts.type)
4463 gfc_convert_type (iter->step, &iter->var->ts, 2);
4465 return SUCCESS;
4469 /* Traversal function for find_forall_index. f == 2 signals that
4470 that variable itself is not to be checked - only the references. */
4472 static bool
4473 forall_index (gfc_expr *expr, gfc_symbol *sym, int *f)
4475 if (expr->expr_type != EXPR_VARIABLE)
4476 return false;
4478 /* A scalar assignment */
4479 if (!expr->ref || *f == 1)
4481 if (expr->symtree->n.sym == sym)
4482 return true;
4483 else
4484 return false;
4487 if (*f == 2)
4488 *f = 1;
4489 return false;
4493 /* Check whether the FORALL index appears in the expression or not.
4494 Returns SUCCESS if SYM is found in EXPR. */
4497 find_forall_index (gfc_expr *expr, gfc_symbol *sym, int f)
4499 if (gfc_traverse_expr (expr, sym, forall_index, f))
4500 return SUCCESS;
4501 else
4502 return FAILURE;
4506 /* Resolve a list of FORALL iterators. The FORALL index-name is constrained
4507 to be a scalar INTEGER variable. The subscripts and stride are scalar
4508 INTEGERs, and if stride is a constant it must be nonzero.
4509 Furthermore "A subscript or stride in a forall-triplet-spec shall
4510 not contain a reference to any index-name in the
4511 forall-triplet-spec-list in which it appears." (7.5.4.1) */
4513 static void
4514 resolve_forall_iterators (gfc_forall_iterator *it)
4516 gfc_forall_iterator *iter, *iter2;
4518 for (iter = it; iter; iter = iter->next)
4520 if (gfc_resolve_expr (iter->var) == SUCCESS
4521 && (iter->var->ts.type != BT_INTEGER || iter->var->rank != 0))
4522 gfc_error ("FORALL index-name at %L must be a scalar INTEGER",
4523 &iter->var->where);
4525 if (gfc_resolve_expr (iter->start) == SUCCESS
4526 && (iter->start->ts.type != BT_INTEGER || iter->start->rank != 0))
4527 gfc_error ("FORALL start expression at %L must be a scalar INTEGER",
4528 &iter->start->where);
4529 if (iter->var->ts.kind != iter->start->ts.kind)
4530 gfc_convert_type (iter->start, &iter->var->ts, 2);
4532 if (gfc_resolve_expr (iter->end) == SUCCESS
4533 && (iter->end->ts.type != BT_INTEGER || iter->end->rank != 0))
4534 gfc_error ("FORALL end expression at %L must be a scalar INTEGER",
4535 &iter->end->where);
4536 if (iter->var->ts.kind != iter->end->ts.kind)
4537 gfc_convert_type (iter->end, &iter->var->ts, 2);
4539 if (gfc_resolve_expr (iter->stride) == SUCCESS)
4541 if (iter->stride->ts.type != BT_INTEGER || iter->stride->rank != 0)
4542 gfc_error ("FORALL stride expression at %L must be a scalar %s",
4543 &iter->stride->where, "INTEGER");
4545 if (iter->stride->expr_type == EXPR_CONSTANT
4546 && mpz_cmp_ui(iter->stride->value.integer, 0) == 0)
4547 gfc_error ("FORALL stride expression at %L cannot be zero",
4548 &iter->stride->where);
4550 if (iter->var->ts.kind != iter->stride->ts.kind)
4551 gfc_convert_type (iter->stride, &iter->var->ts, 2);
4554 for (iter = it; iter; iter = iter->next)
4555 for (iter2 = iter; iter2; iter2 = iter2->next)
4557 if (find_forall_index (iter2->start,
4558 iter->var->symtree->n.sym, 0) == SUCCESS
4559 || find_forall_index (iter2->end,
4560 iter->var->symtree->n.sym, 0) == SUCCESS
4561 || find_forall_index (iter2->stride,
4562 iter->var->symtree->n.sym, 0) == SUCCESS)
4563 gfc_error ("FORALL index '%s' may not appear in triplet "
4564 "specification at %L", iter->var->symtree->name,
4565 &iter2->start->where);
4570 /* Given a pointer to a symbol that is a derived type, see if it's
4571 inaccessible, i.e. if it's defined in another module and the components are
4572 PRIVATE. The search is recursive if necessary. Returns zero if no
4573 inaccessible components are found, nonzero otherwise. */
4575 static int
4576 derived_inaccessible (gfc_symbol *sym)
4578 gfc_component *c;
4580 if (sym->attr.use_assoc && sym->attr.private_comp)
4581 return 1;
4583 for (c = sym->components; c; c = c->next)
4585 if (c->ts.type == BT_DERIVED && derived_inaccessible (c->ts.derived))
4586 return 1;
4589 return 0;
4593 /* Resolve the argument of a deallocate expression. The expression must be
4594 a pointer or a full array. */
4596 static try
4597 resolve_deallocate_expr (gfc_expr *e)
4599 symbol_attribute attr;
4600 int allocatable, pointer, check_intent_in;
4601 gfc_ref *ref;
4603 /* Check INTENT(IN), unless the object is a sub-component of a pointer. */
4604 check_intent_in = 1;
4606 if (gfc_resolve_expr (e) == FAILURE)
4607 return FAILURE;
4609 if (e->expr_type != EXPR_VARIABLE)
4610 goto bad;
4612 allocatable = e->symtree->n.sym->attr.allocatable;
4613 pointer = e->symtree->n.sym->attr.pointer;
4614 for (ref = e->ref; ref; ref = ref->next)
4616 if (pointer)
4617 check_intent_in = 0;
4619 switch (ref->type)
4621 case REF_ARRAY:
4622 if (ref->u.ar.type != AR_FULL)
4623 allocatable = 0;
4624 break;
4626 case REF_COMPONENT:
4627 allocatable = (ref->u.c.component->as != NULL
4628 && ref->u.c.component->as->type == AS_DEFERRED);
4629 pointer = ref->u.c.component->pointer;
4630 break;
4632 case REF_SUBSTRING:
4633 allocatable = 0;
4634 break;
4638 attr = gfc_expr_attr (e);
4640 if (allocatable == 0 && attr.pointer == 0)
4642 bad:
4643 gfc_error ("Expression in DEALLOCATE statement at %L must be "
4644 "ALLOCATABLE or a POINTER", &e->where);
4647 if (check_intent_in
4648 && e->symtree->n.sym->attr.intent == INTENT_IN)
4650 gfc_error ("Cannot deallocate INTENT(IN) variable '%s' at %L",
4651 e->symtree->n.sym->name, &e->where);
4652 return FAILURE;
4655 return SUCCESS;
4659 /* Returns true if the expression e contains a reference to the symbol sym. */
4660 static bool
4661 sym_in_expr (gfc_expr *e, gfc_symbol *sym, int *f ATTRIBUTE_UNUSED)
4663 if (e->expr_type == EXPR_VARIABLE && e->symtree->n.sym == sym)
4664 return true;
4666 return false;
4669 static bool
4670 find_sym_in_expr (gfc_symbol *sym, gfc_expr *e)
4672 return gfc_traverse_expr (e, sym, sym_in_expr, 0);
4676 /* Given the expression node e for an allocatable/pointer of derived type to be
4677 allocated, get the expression node to be initialized afterwards (needed for
4678 derived types with default initializers, and derived types with allocatable
4679 components that need nullification.) */
4681 static gfc_expr *
4682 expr_to_initialize (gfc_expr *e)
4684 gfc_expr *result;
4685 gfc_ref *ref;
4686 int i;
4688 result = gfc_copy_expr (e);
4690 /* Change the last array reference from AR_ELEMENT to AR_FULL. */
4691 for (ref = result->ref; ref; ref = ref->next)
4692 if (ref->type == REF_ARRAY && ref->next == NULL)
4694 ref->u.ar.type = AR_FULL;
4696 for (i = 0; i < ref->u.ar.dimen; i++)
4697 ref->u.ar.start[i] = ref->u.ar.end[i] = ref->u.ar.stride[i] = NULL;
4699 result->rank = ref->u.ar.dimen;
4700 break;
4703 return result;
4707 /* Resolve the expression in an ALLOCATE statement, doing the additional
4708 checks to see whether the expression is OK or not. The expression must
4709 have a trailing array reference that gives the size of the array. */
4711 static try
4712 resolve_allocate_expr (gfc_expr *e, gfc_code *code)
4714 int i, pointer, allocatable, dimension, check_intent_in;
4715 symbol_attribute attr;
4716 gfc_ref *ref, *ref2;
4717 gfc_array_ref *ar;
4718 gfc_code *init_st;
4719 gfc_expr *init_e;
4720 gfc_symbol *sym;
4721 gfc_alloc *a;
4723 /* Check INTENT(IN), unless the object is a sub-component of a pointer. */
4724 check_intent_in = 1;
4726 if (gfc_resolve_expr (e) == FAILURE)
4727 return FAILURE;
4729 if (code->expr && code->expr->expr_type == EXPR_VARIABLE)
4730 sym = code->expr->symtree->n.sym;
4731 else
4732 sym = NULL;
4734 /* Make sure the expression is allocatable or a pointer. If it is
4735 pointer, the next-to-last reference must be a pointer. */
4737 ref2 = NULL;
4739 if (e->expr_type != EXPR_VARIABLE)
4741 allocatable = 0;
4742 attr = gfc_expr_attr (e);
4743 pointer = attr.pointer;
4744 dimension = attr.dimension;
4746 else
4748 allocatable = e->symtree->n.sym->attr.allocatable;
4749 pointer = e->symtree->n.sym->attr.pointer;
4750 dimension = e->symtree->n.sym->attr.dimension;
4752 if (sym == e->symtree->n.sym && sym->ts.type != BT_DERIVED)
4754 gfc_error ("The STAT variable '%s' in an ALLOCATE statement must "
4755 "not be allocated in the same statement at %L",
4756 sym->name, &e->where);
4757 return FAILURE;
4760 for (ref = e->ref; ref; ref2 = ref, ref = ref->next)
4762 if (pointer)
4763 check_intent_in = 0;
4765 switch (ref->type)
4767 case REF_ARRAY:
4768 if (ref->next != NULL)
4769 pointer = 0;
4770 break;
4772 case REF_COMPONENT:
4773 allocatable = (ref->u.c.component->as != NULL
4774 && ref->u.c.component->as->type == AS_DEFERRED);
4776 pointer = ref->u.c.component->pointer;
4777 dimension = ref->u.c.component->dimension;
4778 break;
4780 case REF_SUBSTRING:
4781 allocatable = 0;
4782 pointer = 0;
4783 break;
4788 if (allocatable == 0 && pointer == 0)
4790 gfc_error ("Expression in ALLOCATE statement at %L must be "
4791 "ALLOCATABLE or a POINTER", &e->where);
4792 return FAILURE;
4795 if (check_intent_in
4796 && e->symtree->n.sym->attr.intent == INTENT_IN)
4798 gfc_error ("Cannot allocate INTENT(IN) variable '%s' at %L",
4799 e->symtree->n.sym->name, &e->where);
4800 return FAILURE;
4803 /* Add default initializer for those derived types that need them. */
4804 if (e->ts.type == BT_DERIVED && (init_e = gfc_default_initializer (&e->ts)))
4806 init_st = gfc_get_code ();
4807 init_st->loc = code->loc;
4808 init_st->op = EXEC_INIT_ASSIGN;
4809 init_st->expr = expr_to_initialize (e);
4810 init_st->expr2 = init_e;
4811 init_st->next = code->next;
4812 code->next = init_st;
4815 if (pointer && dimension == 0)
4816 return SUCCESS;
4818 /* Make sure the next-to-last reference node is an array specification. */
4820 if (ref2 == NULL || ref2->type != REF_ARRAY || ref2->u.ar.type == AR_FULL)
4822 gfc_error ("Array specification required in ALLOCATE statement "
4823 "at %L", &e->where);
4824 return FAILURE;
4827 /* Make sure that the array section reference makes sense in the
4828 context of an ALLOCATE specification. */
4830 ar = &ref2->u.ar;
4832 for (i = 0; i < ar->dimen; i++)
4834 if (ref2->u.ar.type == AR_ELEMENT)
4835 goto check_symbols;
4837 switch (ar->dimen_type[i])
4839 case DIMEN_ELEMENT:
4840 break;
4842 case DIMEN_RANGE:
4843 if (ar->start[i] != NULL
4844 && ar->end[i] != NULL
4845 && ar->stride[i] == NULL)
4846 break;
4848 /* Fall Through... */
4850 case DIMEN_UNKNOWN:
4851 case DIMEN_VECTOR:
4852 gfc_error ("Bad array specification in ALLOCATE statement at %L",
4853 &e->where);
4854 return FAILURE;
4857 check_symbols:
4859 for (a = code->ext.alloc_list; a; a = a->next)
4861 sym = a->expr->symtree->n.sym;
4863 /* TODO - check derived type components. */
4864 if (sym->ts.type == BT_DERIVED)
4865 continue;
4867 if ((ar->start[i] != NULL && find_sym_in_expr (sym, ar->start[i]))
4868 || (ar->end[i] != NULL && find_sym_in_expr (sym, ar->end[i])))
4870 gfc_error ("'%s' must not appear an the array specification at "
4871 "%L in the same ALLOCATE statement where it is "
4872 "itself allocated", sym->name, &ar->where);
4873 return FAILURE;
4878 return SUCCESS;
4881 static void
4882 resolve_allocate_deallocate (gfc_code *code, const char *fcn)
4884 gfc_symbol *s = NULL;
4885 gfc_alloc *a;
4887 if (code->expr)
4888 s = code->expr->symtree->n.sym;
4890 if (s)
4892 if (s->attr.intent == INTENT_IN)
4893 gfc_error ("STAT variable '%s' of %s statement at %C cannot "
4894 "be INTENT(IN)", s->name, fcn);
4896 if (gfc_pure (NULL) && gfc_impure_variable (s))
4897 gfc_error ("Illegal STAT variable in %s statement at %C "
4898 "for a PURE procedure", fcn);
4901 if (s && code->expr->ts.type != BT_INTEGER)
4902 gfc_error ("STAT tag in %s statement at %L must be "
4903 "of type INTEGER", fcn, &code->expr->where);
4905 if (strcmp (fcn, "ALLOCATE") == 0)
4907 for (a = code->ext.alloc_list; a; a = a->next)
4908 resolve_allocate_expr (a->expr, code);
4910 else
4912 for (a = code->ext.alloc_list; a; a = a->next)
4913 resolve_deallocate_expr (a->expr);
4917 /************ SELECT CASE resolution subroutines ************/
4919 /* Callback function for our mergesort variant. Determines interval
4920 overlaps for CASEs. Return <0 if op1 < op2, 0 for overlap, >0 for
4921 op1 > op2. Assumes we're not dealing with the default case.
4922 We have op1 = (:L), (K:L) or (K:) and op2 = (:N), (M:N) or (M:).
4923 There are nine situations to check. */
4925 static int
4926 compare_cases (const gfc_case *op1, const gfc_case *op2)
4928 int retval;
4930 if (op1->low == NULL) /* op1 = (:L) */
4932 /* op2 = (:N), so overlap. */
4933 retval = 0;
4934 /* op2 = (M:) or (M:N), L < M */
4935 if (op2->low != NULL
4936 && gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
4937 retval = -1;
4939 else if (op1->high == NULL) /* op1 = (K:) */
4941 /* op2 = (M:), so overlap. */
4942 retval = 0;
4943 /* op2 = (:N) or (M:N), K > N */
4944 if (op2->high != NULL
4945 && gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
4946 retval = 1;
4948 else /* op1 = (K:L) */
4950 if (op2->low == NULL) /* op2 = (:N), K > N */
4951 retval = (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
4952 ? 1 : 0;
4953 else if (op2->high == NULL) /* op2 = (M:), L < M */
4954 retval = (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
4955 ? -1 : 0;
4956 else /* op2 = (M:N) */
4958 retval = 0;
4959 /* L < M */
4960 if (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
4961 retval = -1;
4962 /* K > N */
4963 else if (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
4964 retval = 1;
4968 return retval;
4972 /* Merge-sort a double linked case list, detecting overlap in the
4973 process. LIST is the head of the double linked case list before it
4974 is sorted. Returns the head of the sorted list if we don't see any
4975 overlap, or NULL otherwise. */
4977 static gfc_case *
4978 check_case_overlap (gfc_case *list)
4980 gfc_case *p, *q, *e, *tail;
4981 int insize, nmerges, psize, qsize, cmp, overlap_seen;
4983 /* If the passed list was empty, return immediately. */
4984 if (!list)
4985 return NULL;
4987 overlap_seen = 0;
4988 insize = 1;
4990 /* Loop unconditionally. The only exit from this loop is a return
4991 statement, when we've finished sorting the case list. */
4992 for (;;)
4994 p = list;
4995 list = NULL;
4996 tail = NULL;
4998 /* Count the number of merges we do in this pass. */
4999 nmerges = 0;
5001 /* Loop while there exists a merge to be done. */
5002 while (p)
5004 int i;
5006 /* Count this merge. */
5007 nmerges++;
5009 /* Cut the list in two pieces by stepping INSIZE places
5010 forward in the list, starting from P. */
5011 psize = 0;
5012 q = p;
5013 for (i = 0; i < insize; i++)
5015 psize++;
5016 q = q->right;
5017 if (!q)
5018 break;
5020 qsize = insize;
5022 /* Now we have two lists. Merge them! */
5023 while (psize > 0 || (qsize > 0 && q != NULL))
5025 /* See from which the next case to merge comes from. */
5026 if (psize == 0)
5028 /* P is empty so the next case must come from Q. */
5029 e = q;
5030 q = q->right;
5031 qsize--;
5033 else if (qsize == 0 || q == NULL)
5035 /* Q is empty. */
5036 e = p;
5037 p = p->right;
5038 psize--;
5040 else
5042 cmp = compare_cases (p, q);
5043 if (cmp < 0)
5045 /* The whole case range for P is less than the
5046 one for Q. */
5047 e = p;
5048 p = p->right;
5049 psize--;
5051 else if (cmp > 0)
5053 /* The whole case range for Q is greater than
5054 the case range for P. */
5055 e = q;
5056 q = q->right;
5057 qsize--;
5059 else
5061 /* The cases overlap, or they are the same
5062 element in the list. Either way, we must
5063 issue an error and get the next case from P. */
5064 /* FIXME: Sort P and Q by line number. */
5065 gfc_error ("CASE label at %L overlaps with CASE "
5066 "label at %L", &p->where, &q->where);
5067 overlap_seen = 1;
5068 e = p;
5069 p = p->right;
5070 psize--;
5074 /* Add the next element to the merged list. */
5075 if (tail)
5076 tail->right = e;
5077 else
5078 list = e;
5079 e->left = tail;
5080 tail = e;
5083 /* P has now stepped INSIZE places along, and so has Q. So
5084 they're the same. */
5085 p = q;
5087 tail->right = NULL;
5089 /* If we have done only one merge or none at all, we've
5090 finished sorting the cases. */
5091 if (nmerges <= 1)
5093 if (!overlap_seen)
5094 return list;
5095 else
5096 return NULL;
5099 /* Otherwise repeat, merging lists twice the size. */
5100 insize *= 2;
5105 /* Check to see if an expression is suitable for use in a CASE statement.
5106 Makes sure that all case expressions are scalar constants of the same
5107 type. Return FAILURE if anything is wrong. */
5109 static try
5110 validate_case_label_expr (gfc_expr *e, gfc_expr *case_expr)
5112 if (e == NULL) return SUCCESS;
5114 if (e->ts.type != case_expr->ts.type)
5116 gfc_error ("Expression in CASE statement at %L must be of type %s",
5117 &e->where, gfc_basic_typename (case_expr->ts.type));
5118 return FAILURE;
5121 /* C805 (R808) For a given case-construct, each case-value shall be of
5122 the same type as case-expr. For character type, length differences
5123 are allowed, but the kind type parameters shall be the same. */
5125 if (case_expr->ts.type == BT_CHARACTER && e->ts.kind != case_expr->ts.kind)
5127 gfc_error("Expression in CASE statement at %L must be kind %d",
5128 &e->where, case_expr->ts.kind);
5129 return FAILURE;
5132 /* Convert the case value kind to that of case expression kind, if needed.
5133 FIXME: Should a warning be issued? */
5134 if (e->ts.kind != case_expr->ts.kind)
5135 gfc_convert_type_warn (e, &case_expr->ts, 2, 0);
5137 if (e->rank != 0)
5139 gfc_error ("Expression in CASE statement at %L must be scalar",
5140 &e->where);
5141 return FAILURE;
5144 return SUCCESS;
5148 /* Given a completely parsed select statement, we:
5150 - Validate all expressions and code within the SELECT.
5151 - Make sure that the selection expression is not of the wrong type.
5152 - Make sure that no case ranges overlap.
5153 - Eliminate unreachable cases and unreachable code resulting from
5154 removing case labels.
5156 The standard does allow unreachable cases, e.g. CASE (5:3). But
5157 they are a hassle for code generation, and to prevent that, we just
5158 cut them out here. This is not necessary for overlapping cases
5159 because they are illegal and we never even try to generate code.
5161 We have the additional caveat that a SELECT construct could have
5162 been a computed GOTO in the source code. Fortunately we can fairly
5163 easily work around that here: The case_expr for a "real" SELECT CASE
5164 is in code->expr1, but for a computed GOTO it is in code->expr2. All
5165 we have to do is make sure that the case_expr is a scalar integer
5166 expression. */
5168 static void
5169 resolve_select (gfc_code *code)
5171 gfc_code *body;
5172 gfc_expr *case_expr;
5173 gfc_case *cp, *default_case, *tail, *head;
5174 int seen_unreachable;
5175 int seen_logical;
5176 int ncases;
5177 bt type;
5178 try t;
5180 if (code->expr == NULL)
5182 /* This was actually a computed GOTO statement. */
5183 case_expr = code->expr2;
5184 if (case_expr->ts.type != BT_INTEGER|| case_expr->rank != 0)
5185 gfc_error ("Selection expression in computed GOTO statement "
5186 "at %L must be a scalar integer expression",
5187 &case_expr->where);
5189 /* Further checking is not necessary because this SELECT was built
5190 by the compiler, so it should always be OK. Just move the
5191 case_expr from expr2 to expr so that we can handle computed
5192 GOTOs as normal SELECTs from here on. */
5193 code->expr = code->expr2;
5194 code->expr2 = NULL;
5195 return;
5198 case_expr = code->expr;
5200 type = case_expr->ts.type;
5201 if (type != BT_LOGICAL && type != BT_INTEGER && type != BT_CHARACTER)
5203 gfc_error ("Argument of SELECT statement at %L cannot be %s",
5204 &case_expr->where, gfc_typename (&case_expr->ts));
5206 /* Punt. Going on here just produce more garbage error messages. */
5207 return;
5210 if (case_expr->rank != 0)
5212 gfc_error ("Argument of SELECT statement at %L must be a scalar "
5213 "expression", &case_expr->where);
5215 /* Punt. */
5216 return;
5219 /* PR 19168 has a long discussion concerning a mismatch of the kinds
5220 of the SELECT CASE expression and its CASE values. Walk the lists
5221 of case values, and if we find a mismatch, promote case_expr to
5222 the appropriate kind. */
5224 if (type == BT_LOGICAL || type == BT_INTEGER)
5226 for (body = code->block; body; body = body->block)
5228 /* Walk the case label list. */
5229 for (cp = body->ext.case_list; cp; cp = cp->next)
5231 /* Intercept the DEFAULT case. It does not have a kind. */
5232 if (cp->low == NULL && cp->high == NULL)
5233 continue;
5235 /* Unreachable case ranges are discarded, so ignore. */
5236 if (cp->low != NULL && cp->high != NULL
5237 && cp->low != cp->high
5238 && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
5239 continue;
5241 /* FIXME: Should a warning be issued? */
5242 if (cp->low != NULL
5243 && case_expr->ts.kind != gfc_kind_max(case_expr, cp->low))
5244 gfc_convert_type_warn (case_expr, &cp->low->ts, 2, 0);
5246 if (cp->high != NULL
5247 && case_expr->ts.kind != gfc_kind_max(case_expr, cp->high))
5248 gfc_convert_type_warn (case_expr, &cp->high->ts, 2, 0);
5253 /* Assume there is no DEFAULT case. */
5254 default_case = NULL;
5255 head = tail = NULL;
5256 ncases = 0;
5257 seen_logical = 0;
5259 for (body = code->block; body; body = body->block)
5261 /* Assume the CASE list is OK, and all CASE labels can be matched. */
5262 t = SUCCESS;
5263 seen_unreachable = 0;
5265 /* Walk the case label list, making sure that all case labels
5266 are legal. */
5267 for (cp = body->ext.case_list; cp; cp = cp->next)
5269 /* Count the number of cases in the whole construct. */
5270 ncases++;
5272 /* Intercept the DEFAULT case. */
5273 if (cp->low == NULL && cp->high == NULL)
5275 if (default_case != NULL)
5277 gfc_error ("The DEFAULT CASE at %L cannot be followed "
5278 "by a second DEFAULT CASE at %L",
5279 &default_case->where, &cp->where);
5280 t = FAILURE;
5281 break;
5283 else
5285 default_case = cp;
5286 continue;
5290 /* Deal with single value cases and case ranges. Errors are
5291 issued from the validation function. */
5292 if(validate_case_label_expr (cp->low, case_expr) != SUCCESS
5293 || validate_case_label_expr (cp->high, case_expr) != SUCCESS)
5295 t = FAILURE;
5296 break;
5299 if (type == BT_LOGICAL
5300 && ((cp->low == NULL || cp->high == NULL)
5301 || cp->low != cp->high))
5303 gfc_error ("Logical range in CASE statement at %L is not "
5304 "allowed", &cp->low->where);
5305 t = FAILURE;
5306 break;
5309 if (type == BT_LOGICAL && cp->low->expr_type == EXPR_CONSTANT)
5311 int value;
5312 value = cp->low->value.logical == 0 ? 2 : 1;
5313 if (value & seen_logical)
5315 gfc_error ("constant logical value in CASE statement "
5316 "is repeated at %L",
5317 &cp->low->where);
5318 t = FAILURE;
5319 break;
5321 seen_logical |= value;
5324 if (cp->low != NULL && cp->high != NULL
5325 && cp->low != cp->high
5326 && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
5328 if (gfc_option.warn_surprising)
5329 gfc_warning ("Range specification at %L can never "
5330 "be matched", &cp->where);
5332 cp->unreachable = 1;
5333 seen_unreachable = 1;
5335 else
5337 /* If the case range can be matched, it can also overlap with
5338 other cases. To make sure it does not, we put it in a
5339 double linked list here. We sort that with a merge sort
5340 later on to detect any overlapping cases. */
5341 if (!head)
5343 head = tail = cp;
5344 head->right = head->left = NULL;
5346 else
5348 tail->right = cp;
5349 tail->right->left = tail;
5350 tail = tail->right;
5351 tail->right = NULL;
5356 /* It there was a failure in the previous case label, give up
5357 for this case label list. Continue with the next block. */
5358 if (t == FAILURE)
5359 continue;
5361 /* See if any case labels that are unreachable have been seen.
5362 If so, we eliminate them. This is a bit of a kludge because
5363 the case lists for a single case statement (label) is a
5364 single forward linked lists. */
5365 if (seen_unreachable)
5367 /* Advance until the first case in the list is reachable. */
5368 while (body->ext.case_list != NULL
5369 && body->ext.case_list->unreachable)
5371 gfc_case *n = body->ext.case_list;
5372 body->ext.case_list = body->ext.case_list->next;
5373 n->next = NULL;
5374 gfc_free_case_list (n);
5377 /* Strip all other unreachable cases. */
5378 if (body->ext.case_list)
5380 for (cp = body->ext.case_list; cp->next; cp = cp->next)
5382 if (cp->next->unreachable)
5384 gfc_case *n = cp->next;
5385 cp->next = cp->next->next;
5386 n->next = NULL;
5387 gfc_free_case_list (n);
5394 /* See if there were overlapping cases. If the check returns NULL,
5395 there was overlap. In that case we don't do anything. If head
5396 is non-NULL, we prepend the DEFAULT case. The sorted list can
5397 then used during code generation for SELECT CASE constructs with
5398 a case expression of a CHARACTER type. */
5399 if (head)
5401 head = check_case_overlap (head);
5403 /* Prepend the default_case if it is there. */
5404 if (head != NULL && default_case)
5406 default_case->left = NULL;
5407 default_case->right = head;
5408 head->left = default_case;
5412 /* Eliminate dead blocks that may be the result if we've seen
5413 unreachable case labels for a block. */
5414 for (body = code; body && body->block; body = body->block)
5416 if (body->block->ext.case_list == NULL)
5418 /* Cut the unreachable block from the code chain. */
5419 gfc_code *c = body->block;
5420 body->block = c->block;
5422 /* Kill the dead block, but not the blocks below it. */
5423 c->block = NULL;
5424 gfc_free_statements (c);
5428 /* More than two cases is legal but insane for logical selects.
5429 Issue a warning for it. */
5430 if (gfc_option.warn_surprising && type == BT_LOGICAL
5431 && ncases > 2)
5432 gfc_warning ("Logical SELECT CASE block at %L has more that two cases",
5433 &code->loc);
5437 /* Resolve a transfer statement. This is making sure that:
5438 -- a derived type being transferred has only non-pointer components
5439 -- a derived type being transferred doesn't have private components, unless
5440 it's being transferred from the module where the type was defined
5441 -- we're not trying to transfer a whole assumed size array. */
5443 static void
5444 resolve_transfer (gfc_code *code)
5446 gfc_typespec *ts;
5447 gfc_symbol *sym;
5448 gfc_ref *ref;
5449 gfc_expr *exp;
5451 exp = code->expr;
5453 if (exp->expr_type != EXPR_VARIABLE && exp->expr_type != EXPR_FUNCTION)
5454 return;
5456 sym = exp->symtree->n.sym;
5457 ts = &sym->ts;
5459 /* Go to actual component transferred. */
5460 for (ref = code->expr->ref; ref; ref = ref->next)
5461 if (ref->type == REF_COMPONENT)
5462 ts = &ref->u.c.component->ts;
5464 if (ts->type == BT_DERIVED)
5466 /* Check that transferred derived type doesn't contain POINTER
5467 components. */
5468 if (ts->derived->attr.pointer_comp)
5470 gfc_error ("Data transfer element at %L cannot have "
5471 "POINTER components", &code->loc);
5472 return;
5475 if (ts->derived->attr.alloc_comp)
5477 gfc_error ("Data transfer element at %L cannot have "
5478 "ALLOCATABLE components", &code->loc);
5479 return;
5482 if (derived_inaccessible (ts->derived))
5484 gfc_error ("Data transfer element at %L cannot have "
5485 "PRIVATE components",&code->loc);
5486 return;
5490 if (sym->as != NULL && sym->as->type == AS_ASSUMED_SIZE
5491 && exp->ref->type == REF_ARRAY && exp->ref->u.ar.type == AR_FULL)
5493 gfc_error ("Data transfer element at %L cannot be a full reference to "
5494 "an assumed-size array", &code->loc);
5495 return;
5500 /*********** Toplevel code resolution subroutines ***********/
5502 /* Find the set of labels that are reachable from this block. We also
5503 record the last statement in each block so that we don't have to do
5504 a linear search to find the END DO statements of the blocks. */
5506 static void
5507 reachable_labels (gfc_code *block)
5509 gfc_code *c;
5511 if (!block)
5512 return;
5514 cs_base->reachable_labels = bitmap_obstack_alloc (&labels_obstack);
5516 /* Collect labels in this block. */
5517 for (c = block; c; c = c->next)
5519 if (c->here)
5520 bitmap_set_bit (cs_base->reachable_labels, c->here->value);
5522 if (!c->next && cs_base->prev)
5523 cs_base->prev->tail = c;
5526 /* Merge with labels from parent block. */
5527 if (cs_base->prev)
5529 gcc_assert (cs_base->prev->reachable_labels);
5530 bitmap_ior_into (cs_base->reachable_labels,
5531 cs_base->prev->reachable_labels);
5535 /* Given a branch to a label and a namespace, if the branch is conforming.
5536 The code node describes where the branch is located. */
5538 static void
5539 resolve_branch (gfc_st_label *label, gfc_code *code)
5541 code_stack *stack;
5543 if (label == NULL)
5544 return;
5546 /* Step one: is this a valid branching target? */
5548 if (label->defined == ST_LABEL_UNKNOWN)
5550 gfc_error ("Label %d referenced at %L is never defined", label->value,
5551 &label->where);
5552 return;
5555 if (label->defined != ST_LABEL_TARGET)
5557 gfc_error ("Statement at %L is not a valid branch target statement "
5558 "for the branch statement at %L", &label->where, &code->loc);
5559 return;
5562 /* Step two: make sure this branch is not a branch to itself ;-) */
5564 if (code->here == label)
5566 gfc_warning ("Branch at %L may result in an infinite loop", &code->loc);
5567 return;
5570 /* Step three: See if the label is in the same block as the
5571 branching statement. The hard work has been done by setting up
5572 the bitmap reachable_labels. */
5574 if (!bitmap_bit_p (cs_base->reachable_labels, label->value))
5576 /* The label is not in an enclosing block, so illegal. This was
5577 allowed in Fortran 66, so we allow it as extension. No
5578 further checks are necessary in this case. */
5579 gfc_notify_std (GFC_STD_LEGACY, "Label at %L is not in the same block "
5580 "as the GOTO statement at %L", &label->where,
5581 &code->loc);
5582 return;
5585 /* Step four: Make sure that the branching target is legal if
5586 the statement is an END {SELECT,IF}. */
5588 for (stack = cs_base; stack; stack = stack->prev)
5589 if (stack->current->next && stack->current->next->here == label)
5590 break;
5592 if (stack && stack->current->next->op == EXEC_NOP)
5594 gfc_notify_std (GFC_STD_F95_DEL, "Deleted feature: GOTO at %L jumps to "
5595 "END of construct at %L", &code->loc,
5596 &stack->current->next->loc);
5597 return; /* We know this is not an END DO. */
5600 /* Step five: Make sure that we're not jumping to the end of a DO
5601 loop from within the loop. */
5603 for (stack = cs_base; stack; stack = stack->prev)
5604 if ((stack->current->op == EXEC_DO
5605 || stack->current->op == EXEC_DO_WHILE)
5606 && stack->tail->here == label && stack->tail->op == EXEC_NOP)
5608 gfc_notify_std (GFC_STD_F95_DEL, "Deleted feature: GOTO at %L jumps "
5609 "to END of construct at %L", &code->loc,
5610 &stack->tail->loc);
5611 return;
5617 /* Check whether EXPR1 has the same shape as EXPR2. */
5619 static try
5620 resolve_where_shape (gfc_expr *expr1, gfc_expr *expr2)
5622 mpz_t shape[GFC_MAX_DIMENSIONS];
5623 mpz_t shape2[GFC_MAX_DIMENSIONS];
5624 try result = FAILURE;
5625 int i;
5627 /* Compare the rank. */
5628 if (expr1->rank != expr2->rank)
5629 return result;
5631 /* Compare the size of each dimension. */
5632 for (i=0; i<expr1->rank; i++)
5634 if (gfc_array_dimen_size (expr1, i, &shape[i]) == FAILURE)
5635 goto ignore;
5637 if (gfc_array_dimen_size (expr2, i, &shape2[i]) == FAILURE)
5638 goto ignore;
5640 if (mpz_cmp (shape[i], shape2[i]))
5641 goto over;
5644 /* When either of the two expression is an assumed size array, we
5645 ignore the comparison of dimension sizes. */
5646 ignore:
5647 result = SUCCESS;
5649 over:
5650 for (i--; i >= 0; i--)
5652 mpz_clear (shape[i]);
5653 mpz_clear (shape2[i]);
5655 return result;
5659 /* Check whether a WHERE assignment target or a WHERE mask expression
5660 has the same shape as the outmost WHERE mask expression. */
5662 static void
5663 resolve_where (gfc_code *code, gfc_expr *mask)
5665 gfc_code *cblock;
5666 gfc_code *cnext;
5667 gfc_expr *e = NULL;
5669 cblock = code->block;
5671 /* Store the first WHERE mask-expr of the WHERE statement or construct.
5672 In case of nested WHERE, only the outmost one is stored. */
5673 if (mask == NULL) /* outmost WHERE */
5674 e = cblock->expr;
5675 else /* inner WHERE */
5676 e = mask;
5678 while (cblock)
5680 if (cblock->expr)
5682 /* Check if the mask-expr has a consistent shape with the
5683 outmost WHERE mask-expr. */
5684 if (resolve_where_shape (cblock->expr, e) == FAILURE)
5685 gfc_error ("WHERE mask at %L has inconsistent shape",
5686 &cblock->expr->where);
5689 /* the assignment statement of a WHERE statement, or the first
5690 statement in where-body-construct of a WHERE construct */
5691 cnext = cblock->next;
5692 while (cnext)
5694 switch (cnext->op)
5696 /* WHERE assignment statement */
5697 case EXEC_ASSIGN:
5699 /* Check shape consistent for WHERE assignment target. */
5700 if (e && resolve_where_shape (cnext->expr, e) == FAILURE)
5701 gfc_error ("WHERE assignment target at %L has "
5702 "inconsistent shape", &cnext->expr->where);
5703 break;
5706 case EXEC_ASSIGN_CALL:
5707 resolve_call (cnext);
5708 if (!cnext->resolved_sym->attr.elemental)
5709 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
5710 &cnext->ext.actual->expr->where);
5711 break;
5713 /* WHERE or WHERE construct is part of a where-body-construct */
5714 case EXEC_WHERE:
5715 resolve_where (cnext, e);
5716 break;
5718 default:
5719 gfc_error ("Unsupported statement inside WHERE at %L",
5720 &cnext->loc);
5722 /* the next statement within the same where-body-construct */
5723 cnext = cnext->next;
5725 /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
5726 cblock = cblock->block;
5731 /* Resolve assignment in FORALL construct.
5732 NVAR is the number of FORALL index variables, and VAR_EXPR records the
5733 FORALL index variables. */
5735 static void
5736 gfc_resolve_assign_in_forall (gfc_code *code, int nvar, gfc_expr **var_expr)
5738 int n;
5740 for (n = 0; n < nvar; n++)
5742 gfc_symbol *forall_index;
5744 forall_index = var_expr[n]->symtree->n.sym;
5746 /* Check whether the assignment target is one of the FORALL index
5747 variable. */
5748 if ((code->expr->expr_type == EXPR_VARIABLE)
5749 && (code->expr->symtree->n.sym == forall_index))
5750 gfc_error ("Assignment to a FORALL index variable at %L",
5751 &code->expr->where);
5752 else
5754 /* If one of the FORALL index variables doesn't appear in the
5755 assignment target, then there will be a many-to-one
5756 assignment. */
5757 if (find_forall_index (code->expr, forall_index, 0) == FAILURE)
5758 gfc_error ("The FORALL with index '%s' cause more than one "
5759 "assignment to this object at %L",
5760 var_expr[n]->symtree->name, &code->expr->where);
5766 /* Resolve WHERE statement in FORALL construct. */
5768 static void
5769 gfc_resolve_where_code_in_forall (gfc_code *code, int nvar,
5770 gfc_expr **var_expr)
5772 gfc_code *cblock;
5773 gfc_code *cnext;
5775 cblock = code->block;
5776 while (cblock)
5778 /* the assignment statement of a WHERE statement, or the first
5779 statement in where-body-construct of a WHERE construct */
5780 cnext = cblock->next;
5781 while (cnext)
5783 switch (cnext->op)
5785 /* WHERE assignment statement */
5786 case EXEC_ASSIGN:
5787 gfc_resolve_assign_in_forall (cnext, nvar, var_expr);
5788 break;
5790 /* WHERE operator assignment statement */
5791 case EXEC_ASSIGN_CALL:
5792 resolve_call (cnext);
5793 if (!cnext->resolved_sym->attr.elemental)
5794 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
5795 &cnext->ext.actual->expr->where);
5796 break;
5798 /* WHERE or WHERE construct is part of a where-body-construct */
5799 case EXEC_WHERE:
5800 gfc_resolve_where_code_in_forall (cnext, nvar, var_expr);
5801 break;
5803 default:
5804 gfc_error ("Unsupported statement inside WHERE at %L",
5805 &cnext->loc);
5807 /* the next statement within the same where-body-construct */
5808 cnext = cnext->next;
5810 /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
5811 cblock = cblock->block;
5816 /* Traverse the FORALL body to check whether the following errors exist:
5817 1. For assignment, check if a many-to-one assignment happens.
5818 2. For WHERE statement, check the WHERE body to see if there is any
5819 many-to-one assignment. */
5821 static void
5822 gfc_resolve_forall_body (gfc_code *code, int nvar, gfc_expr **var_expr)
5824 gfc_code *c;
5826 c = code->block->next;
5827 while (c)
5829 switch (c->op)
5831 case EXEC_ASSIGN:
5832 case EXEC_POINTER_ASSIGN:
5833 gfc_resolve_assign_in_forall (c, nvar, var_expr);
5834 break;
5836 case EXEC_ASSIGN_CALL:
5837 resolve_call (c);
5838 break;
5840 /* Because the gfc_resolve_blocks() will handle the nested FORALL,
5841 there is no need to handle it here. */
5842 case EXEC_FORALL:
5843 break;
5844 case EXEC_WHERE:
5845 gfc_resolve_where_code_in_forall(c, nvar, var_expr);
5846 break;
5847 default:
5848 break;
5850 /* The next statement in the FORALL body. */
5851 c = c->next;
5856 /* Given a FORALL construct, first resolve the FORALL iterator, then call
5857 gfc_resolve_forall_body to resolve the FORALL body. */
5859 static void
5860 gfc_resolve_forall (gfc_code *code, gfc_namespace *ns, int forall_save)
5862 static gfc_expr **var_expr;
5863 static int total_var = 0;
5864 static int nvar = 0;
5865 gfc_forall_iterator *fa;
5866 gfc_code *next;
5867 int i;
5869 /* Start to resolve a FORALL construct */
5870 if (forall_save == 0)
5872 /* Count the total number of FORALL index in the nested FORALL
5873 construct in order to allocate the VAR_EXPR with proper size. */
5874 next = code;
5875 while ((next != NULL) && (next->op == EXEC_FORALL))
5877 for (fa = next->ext.forall_iterator; fa; fa = fa->next)
5878 total_var ++;
5879 next = next->block->next;
5882 /* Allocate VAR_EXPR with NUMBER_OF_FORALL_INDEX elements. */
5883 var_expr = (gfc_expr **) gfc_getmem (total_var * sizeof (gfc_expr *));
5886 /* The information about FORALL iterator, including FORALL index start, end
5887 and stride. The FORALL index can not appear in start, end or stride. */
5888 for (fa = code->ext.forall_iterator; fa; fa = fa->next)
5890 /* Check if any outer FORALL index name is the same as the current
5891 one. */
5892 for (i = 0; i < nvar; i++)
5894 if (fa->var->symtree->n.sym == var_expr[i]->symtree->n.sym)
5896 gfc_error ("An outer FORALL construct already has an index "
5897 "with this name %L", &fa->var->where);
5901 /* Record the current FORALL index. */
5902 var_expr[nvar] = gfc_copy_expr (fa->var);
5904 nvar++;
5907 /* Resolve the FORALL body. */
5908 gfc_resolve_forall_body (code, nvar, var_expr);
5910 /* May call gfc_resolve_forall to resolve the inner FORALL loop. */
5911 gfc_resolve_blocks (code->block, ns);
5913 /* Free VAR_EXPR after the whole FORALL construct resolved. */
5914 for (i = 0; i < total_var; i++)
5915 gfc_free_expr (var_expr[i]);
5917 /* Reset the counters. */
5918 total_var = 0;
5919 nvar = 0;
5923 /* Resolve lists of blocks found in IF, SELECT CASE, WHERE, FORALL ,GOTO and
5924 DO code nodes. */
5926 static void resolve_code (gfc_code *, gfc_namespace *);
5928 void
5929 gfc_resolve_blocks (gfc_code *b, gfc_namespace *ns)
5931 try t;
5933 for (; b; b = b->block)
5935 t = gfc_resolve_expr (b->expr);
5936 if (gfc_resolve_expr (b->expr2) == FAILURE)
5937 t = FAILURE;
5939 switch (b->op)
5941 case EXEC_IF:
5942 if (t == SUCCESS && b->expr != NULL
5943 && (b->expr->ts.type != BT_LOGICAL || b->expr->rank != 0))
5944 gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
5945 &b->expr->where);
5946 break;
5948 case EXEC_WHERE:
5949 if (t == SUCCESS
5950 && b->expr != NULL
5951 && (b->expr->ts.type != BT_LOGICAL || b->expr->rank == 0))
5952 gfc_error ("WHERE/ELSEWHERE clause at %L requires a LOGICAL array",
5953 &b->expr->where);
5954 break;
5956 case EXEC_GOTO:
5957 resolve_branch (b->label, b);
5958 break;
5960 case EXEC_SELECT:
5961 case EXEC_FORALL:
5962 case EXEC_DO:
5963 case EXEC_DO_WHILE:
5964 case EXEC_READ:
5965 case EXEC_WRITE:
5966 case EXEC_IOLENGTH:
5967 case EXEC_WAIT:
5968 break;
5970 case EXEC_OMP_ATOMIC:
5971 case EXEC_OMP_CRITICAL:
5972 case EXEC_OMP_DO:
5973 case EXEC_OMP_MASTER:
5974 case EXEC_OMP_ORDERED:
5975 case EXEC_OMP_PARALLEL:
5976 case EXEC_OMP_PARALLEL_DO:
5977 case EXEC_OMP_PARALLEL_SECTIONS:
5978 case EXEC_OMP_PARALLEL_WORKSHARE:
5979 case EXEC_OMP_SECTIONS:
5980 case EXEC_OMP_SINGLE:
5981 case EXEC_OMP_WORKSHARE:
5982 break;
5984 default:
5985 gfc_internal_error ("resolve_block(): Bad block type");
5988 resolve_code (b->next, ns);
5993 /* Does everything to resolve an ordinary assignment. Returns true
5994 if this is an interface asignment. */
5995 static bool
5996 resolve_ordinary_assign (gfc_code *code, gfc_namespace *ns)
5998 bool rval = false;
5999 gfc_expr *lhs;
6000 gfc_expr *rhs;
6001 int llen = 0;
6002 int rlen = 0;
6003 int n;
6004 gfc_ref *ref;
6006 if (gfc_extend_assign (code, ns) == SUCCESS)
6008 lhs = code->ext.actual->expr;
6009 rhs = code->ext.actual->next->expr;
6010 if (gfc_pure (NULL) && !gfc_pure (code->symtree->n.sym))
6012 gfc_error ("Subroutine '%s' called instead of assignment at "
6013 "%L must be PURE", code->symtree->n.sym->name,
6014 &code->loc);
6015 return rval;
6018 /* Make a temporary rhs when there is a default initializer
6019 and rhs is the same symbol as the lhs. */
6020 if (rhs->expr_type == EXPR_VARIABLE
6021 && rhs->symtree->n.sym->ts.type == BT_DERIVED
6022 && has_default_initializer (rhs->symtree->n.sym->ts.derived)
6023 && (lhs->symtree->n.sym == rhs->symtree->n.sym))
6024 code->ext.actual->next->expr = gfc_get_parentheses (rhs);
6026 return true;
6029 lhs = code->expr;
6030 rhs = code->expr2;
6032 if (rhs->is_boz
6033 && gfc_notify_std (GFC_STD_GNU, "Extension: BOZ literal at %L outside "
6034 "a DATA statement and outside INT/REAL/DBLE/CMPLX",
6035 &code->loc) == FAILURE)
6036 return false;
6038 /* Handle the case of a BOZ literal on the RHS. */
6039 if (rhs->is_boz && lhs->ts.type != BT_INTEGER)
6041 int rc;
6042 if (gfc_option.warn_surprising)
6043 gfc_warning ("BOZ literal at %L is bitwise transferred "
6044 "non-integer symbol '%s'", &code->loc,
6045 lhs->symtree->n.sym->name);
6047 if (!gfc_convert_boz (rhs, &lhs->ts))
6048 return false;
6049 if ((rc = gfc_range_check (rhs)) != ARITH_OK)
6051 if (rc == ARITH_UNDERFLOW)
6052 gfc_error ("Arithmetic underflow of bit-wise transferred BOZ at %L"
6053 ". This check can be disabled with the option "
6054 "-fno-range-check", &rhs->where);
6055 else if (rc == ARITH_OVERFLOW)
6056 gfc_error ("Arithmetic overflow of bit-wise transferred BOZ at %L"
6057 ". This check can be disabled with the option "
6058 "-fno-range-check", &rhs->where);
6059 else if (rc == ARITH_NAN)
6060 gfc_error ("Arithmetic NaN of bit-wise transferred BOZ at %L"
6061 ". This check can be disabled with the option "
6062 "-fno-range-check", &rhs->where);
6063 return false;
6068 if (lhs->ts.type == BT_CHARACTER
6069 && gfc_option.warn_character_truncation)
6071 if (lhs->ts.cl != NULL
6072 && lhs->ts.cl->length != NULL
6073 && lhs->ts.cl->length->expr_type == EXPR_CONSTANT)
6074 llen = mpz_get_si (lhs->ts.cl->length->value.integer);
6076 if (rhs->expr_type == EXPR_CONSTANT)
6077 rlen = rhs->value.character.length;
6079 else if (rhs->ts.cl != NULL
6080 && rhs->ts.cl->length != NULL
6081 && rhs->ts.cl->length->expr_type == EXPR_CONSTANT)
6082 rlen = mpz_get_si (rhs->ts.cl->length->value.integer);
6084 if (rlen && llen && rlen > llen)
6085 gfc_warning_now ("CHARACTER expression will be truncated "
6086 "in assignment (%d/%d) at %L",
6087 llen, rlen, &code->loc);
6090 /* Ensure that a vector index expression for the lvalue is evaluated
6091 to a temporary if the lvalue symbol is referenced in it. */
6092 if (lhs->rank)
6094 for (ref = lhs->ref; ref; ref= ref->next)
6095 if (ref->type == REF_ARRAY)
6097 for (n = 0; n < ref->u.ar.dimen; n++)
6098 if (ref->u.ar.dimen_type[n] == DIMEN_VECTOR
6099 && find_sym_in_expr (lhs->symtree->n.sym,
6100 ref->u.ar.start[n]))
6101 ref->u.ar.start[n]
6102 = gfc_get_parentheses (ref->u.ar.start[n]);
6106 if (gfc_pure (NULL))
6108 if (gfc_impure_variable (lhs->symtree->n.sym))
6110 gfc_error ("Cannot assign to variable '%s' in PURE "
6111 "procedure at %L",
6112 lhs->symtree->n.sym->name,
6113 &lhs->where);
6114 return rval;
6117 if (lhs->ts.type == BT_DERIVED
6118 && lhs->expr_type == EXPR_VARIABLE
6119 && lhs->ts.derived->attr.pointer_comp
6120 && gfc_impure_variable (rhs->symtree->n.sym))
6122 gfc_error ("The impure variable at %L is assigned to "
6123 "a derived type variable with a POINTER "
6124 "component in a PURE procedure (12.6)",
6125 &rhs->where);
6126 return rval;
6130 gfc_check_assign (lhs, rhs, 1);
6131 return false;
6134 /* Given a block of code, recursively resolve everything pointed to by this
6135 code block. */
6137 static void
6138 resolve_code (gfc_code *code, gfc_namespace *ns)
6140 int omp_workshare_save;
6141 int forall_save;
6142 code_stack frame;
6143 try t;
6145 frame.prev = cs_base;
6146 frame.head = code;
6147 cs_base = &frame;
6149 reachable_labels (code);
6151 for (; code; code = code->next)
6153 frame.current = code;
6154 forall_save = forall_flag;
6156 if (code->op == EXEC_FORALL)
6158 forall_flag = 1;
6159 gfc_resolve_forall (code, ns, forall_save);
6160 forall_flag = 2;
6162 else if (code->block)
6164 omp_workshare_save = -1;
6165 switch (code->op)
6167 case EXEC_OMP_PARALLEL_WORKSHARE:
6168 omp_workshare_save = omp_workshare_flag;
6169 omp_workshare_flag = 1;
6170 gfc_resolve_omp_parallel_blocks (code, ns);
6171 break;
6172 case EXEC_OMP_PARALLEL:
6173 case EXEC_OMP_PARALLEL_DO:
6174 case EXEC_OMP_PARALLEL_SECTIONS:
6175 omp_workshare_save = omp_workshare_flag;
6176 omp_workshare_flag = 0;
6177 gfc_resolve_omp_parallel_blocks (code, ns);
6178 break;
6179 case EXEC_OMP_DO:
6180 gfc_resolve_omp_do_blocks (code, ns);
6181 break;
6182 case EXEC_OMP_WORKSHARE:
6183 omp_workshare_save = omp_workshare_flag;
6184 omp_workshare_flag = 1;
6185 /* FALLTHROUGH */
6186 default:
6187 gfc_resolve_blocks (code->block, ns);
6188 break;
6191 if (omp_workshare_save != -1)
6192 omp_workshare_flag = omp_workshare_save;
6195 t = gfc_resolve_expr (code->expr);
6196 forall_flag = forall_save;
6198 if (gfc_resolve_expr (code->expr2) == FAILURE)
6199 t = FAILURE;
6201 switch (code->op)
6203 case EXEC_NOP:
6204 case EXEC_CYCLE:
6205 case EXEC_PAUSE:
6206 case EXEC_STOP:
6207 case EXEC_EXIT:
6208 case EXEC_CONTINUE:
6209 case EXEC_DT_END:
6210 break;
6212 case EXEC_ENTRY:
6213 /* Keep track of which entry we are up to. */
6214 current_entry_id = code->ext.entry->id;
6215 break;
6217 case EXEC_WHERE:
6218 resolve_where (code, NULL);
6219 break;
6221 case EXEC_GOTO:
6222 if (code->expr != NULL)
6224 if (code->expr->ts.type != BT_INTEGER)
6225 gfc_error ("ASSIGNED GOTO statement at %L requires an "
6226 "INTEGER variable", &code->expr->where);
6227 else if (code->expr->symtree->n.sym->attr.assign != 1)
6228 gfc_error ("Variable '%s' has not been assigned a target "
6229 "label at %L", code->expr->symtree->n.sym->name,
6230 &code->expr->where);
6232 else
6233 resolve_branch (code->label, code);
6234 break;
6236 case EXEC_RETURN:
6237 if (code->expr != NULL
6238 && (code->expr->ts.type != BT_INTEGER || code->expr->rank))
6239 gfc_error ("Alternate RETURN statement at %L requires a SCALAR-"
6240 "INTEGER return specifier", &code->expr->where);
6241 break;
6243 case EXEC_INIT_ASSIGN:
6244 break;
6246 case EXEC_ASSIGN:
6247 if (t == FAILURE)
6248 break;
6250 if (resolve_ordinary_assign (code, ns))
6251 goto call;
6253 break;
6255 case EXEC_LABEL_ASSIGN:
6256 if (code->label->defined == ST_LABEL_UNKNOWN)
6257 gfc_error ("Label %d referenced at %L is never defined",
6258 code->label->value, &code->label->where);
6259 if (t == SUCCESS
6260 && (code->expr->expr_type != EXPR_VARIABLE
6261 || code->expr->symtree->n.sym->ts.type != BT_INTEGER
6262 || code->expr->symtree->n.sym->ts.kind
6263 != gfc_default_integer_kind
6264 || code->expr->symtree->n.sym->as != NULL))
6265 gfc_error ("ASSIGN statement at %L requires a scalar "
6266 "default INTEGER variable", &code->expr->where);
6267 break;
6269 case EXEC_POINTER_ASSIGN:
6270 if (t == FAILURE)
6271 break;
6273 gfc_check_pointer_assign (code->expr, code->expr2);
6274 break;
6276 case EXEC_ARITHMETIC_IF:
6277 if (t == SUCCESS
6278 && code->expr->ts.type != BT_INTEGER
6279 && code->expr->ts.type != BT_REAL)
6280 gfc_error ("Arithmetic IF statement at %L requires a numeric "
6281 "expression", &code->expr->where);
6283 resolve_branch (code->label, code);
6284 resolve_branch (code->label2, code);
6285 resolve_branch (code->label3, code);
6286 break;
6288 case EXEC_IF:
6289 if (t == SUCCESS && code->expr != NULL
6290 && (code->expr->ts.type != BT_LOGICAL
6291 || code->expr->rank != 0))
6292 gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
6293 &code->expr->where);
6294 break;
6296 case EXEC_CALL:
6297 call:
6298 resolve_call (code);
6299 break;
6301 case EXEC_SELECT:
6302 /* Select is complicated. Also, a SELECT construct could be
6303 a transformed computed GOTO. */
6304 resolve_select (code);
6305 break;
6307 case EXEC_DO:
6308 if (code->ext.iterator != NULL)
6310 gfc_iterator *iter = code->ext.iterator;
6311 if (gfc_resolve_iterator (iter, true) != FAILURE)
6312 gfc_resolve_do_iterator (code, iter->var->symtree->n.sym);
6314 break;
6316 case EXEC_DO_WHILE:
6317 if (code->expr == NULL)
6318 gfc_internal_error ("resolve_code(): No expression on DO WHILE");
6319 if (t == SUCCESS
6320 && (code->expr->rank != 0
6321 || code->expr->ts.type != BT_LOGICAL))
6322 gfc_error ("Exit condition of DO WHILE loop at %L must be "
6323 "a scalar LOGICAL expression", &code->expr->where);
6324 break;
6326 case EXEC_ALLOCATE:
6327 if (t == SUCCESS)
6328 resolve_allocate_deallocate (code, "ALLOCATE");
6330 break;
6332 case EXEC_DEALLOCATE:
6333 if (t == SUCCESS)
6334 resolve_allocate_deallocate (code, "DEALLOCATE");
6336 break;
6338 case EXEC_OPEN:
6339 if (gfc_resolve_open (code->ext.open) == FAILURE)
6340 break;
6342 resolve_branch (code->ext.open->err, code);
6343 break;
6345 case EXEC_CLOSE:
6346 if (gfc_resolve_close (code->ext.close) == FAILURE)
6347 break;
6349 resolve_branch (code->ext.close->err, code);
6350 break;
6352 case EXEC_BACKSPACE:
6353 case EXEC_ENDFILE:
6354 case EXEC_REWIND:
6355 case EXEC_FLUSH:
6356 if (gfc_resolve_filepos (code->ext.filepos) == FAILURE)
6357 break;
6359 resolve_branch (code->ext.filepos->err, code);
6360 break;
6362 case EXEC_INQUIRE:
6363 if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
6364 break;
6366 resolve_branch (code->ext.inquire->err, code);
6367 break;
6369 case EXEC_IOLENGTH:
6370 gcc_assert (code->ext.inquire != NULL);
6371 if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
6372 break;
6374 resolve_branch (code->ext.inquire->err, code);
6375 break;
6377 case EXEC_WAIT:
6378 if (gfc_resolve_wait (code->ext.wait) == FAILURE)
6379 break;
6381 resolve_branch (code->ext.wait->err, code);
6382 resolve_branch (code->ext.wait->end, code);
6383 resolve_branch (code->ext.wait->eor, code);
6384 break;
6386 case EXEC_READ:
6387 case EXEC_WRITE:
6388 if (gfc_resolve_dt (code->ext.dt) == FAILURE)
6389 break;
6391 resolve_branch (code->ext.dt->err, code);
6392 resolve_branch (code->ext.dt->end, code);
6393 resolve_branch (code->ext.dt->eor, code);
6394 break;
6396 case EXEC_TRANSFER:
6397 resolve_transfer (code);
6398 break;
6400 case EXEC_FORALL:
6401 resolve_forall_iterators (code->ext.forall_iterator);
6403 if (code->expr != NULL && code->expr->ts.type != BT_LOGICAL)
6404 gfc_error ("FORALL mask clause at %L requires a LOGICAL "
6405 "expression", &code->expr->where);
6406 break;
6408 case EXEC_OMP_ATOMIC:
6409 case EXEC_OMP_BARRIER:
6410 case EXEC_OMP_CRITICAL:
6411 case EXEC_OMP_FLUSH:
6412 case EXEC_OMP_DO:
6413 case EXEC_OMP_MASTER:
6414 case EXEC_OMP_ORDERED:
6415 case EXEC_OMP_SECTIONS:
6416 case EXEC_OMP_SINGLE:
6417 case EXEC_OMP_WORKSHARE:
6418 gfc_resolve_omp_directive (code, ns);
6419 break;
6421 case EXEC_OMP_PARALLEL:
6422 case EXEC_OMP_PARALLEL_DO:
6423 case EXEC_OMP_PARALLEL_SECTIONS:
6424 case EXEC_OMP_PARALLEL_WORKSHARE:
6425 omp_workshare_save = omp_workshare_flag;
6426 omp_workshare_flag = 0;
6427 gfc_resolve_omp_directive (code, ns);
6428 omp_workshare_flag = omp_workshare_save;
6429 break;
6431 default:
6432 gfc_internal_error ("resolve_code(): Bad statement code");
6436 cs_base = frame.prev;
6440 /* Resolve initial values and make sure they are compatible with
6441 the variable. */
6443 static void
6444 resolve_values (gfc_symbol *sym)
6446 if (sym->value == NULL)
6447 return;
6449 if (gfc_resolve_expr (sym->value) == FAILURE)
6450 return;
6452 gfc_check_assign_symbol (sym, sym->value);
6456 /* Verify the binding labels for common blocks that are BIND(C). The label
6457 for a BIND(C) common block must be identical in all scoping units in which
6458 the common block is declared. Further, the binding label can not collide
6459 with any other global entity in the program. */
6461 static void
6462 resolve_bind_c_comms (gfc_symtree *comm_block_tree)
6464 if (comm_block_tree->n.common->is_bind_c == 1)
6466 gfc_gsymbol *binding_label_gsym;
6467 gfc_gsymbol *comm_name_gsym;
6469 /* See if a global symbol exists by the common block's name. It may
6470 be NULL if the common block is use-associated. */
6471 comm_name_gsym = gfc_find_gsymbol (gfc_gsym_root,
6472 comm_block_tree->n.common->name);
6473 if (comm_name_gsym != NULL && comm_name_gsym->type != GSYM_COMMON)
6474 gfc_error ("Binding label '%s' for common block '%s' at %L collides "
6475 "with the global entity '%s' at %L",
6476 comm_block_tree->n.common->binding_label,
6477 comm_block_tree->n.common->name,
6478 &(comm_block_tree->n.common->where),
6479 comm_name_gsym->name, &(comm_name_gsym->where));
6480 else if (comm_name_gsym != NULL
6481 && strcmp (comm_name_gsym->name,
6482 comm_block_tree->n.common->name) == 0)
6484 /* TODO: Need to make sure the fields of gfc_gsymbol are initialized
6485 as expected. */
6486 if (comm_name_gsym->binding_label == NULL)
6487 /* No binding label for common block stored yet; save this one. */
6488 comm_name_gsym->binding_label =
6489 comm_block_tree->n.common->binding_label;
6490 else
6491 if (strcmp (comm_name_gsym->binding_label,
6492 comm_block_tree->n.common->binding_label) != 0)
6494 /* Common block names match but binding labels do not. */
6495 gfc_error ("Binding label '%s' for common block '%s' at %L "
6496 "does not match the binding label '%s' for common "
6497 "block '%s' at %L",
6498 comm_block_tree->n.common->binding_label,
6499 comm_block_tree->n.common->name,
6500 &(comm_block_tree->n.common->where),
6501 comm_name_gsym->binding_label,
6502 comm_name_gsym->name,
6503 &(comm_name_gsym->where));
6504 return;
6508 /* There is no binding label (NAME="") so we have nothing further to
6509 check and nothing to add as a global symbol for the label. */
6510 if (comm_block_tree->n.common->binding_label[0] == '\0' )
6511 return;
6513 binding_label_gsym =
6514 gfc_find_gsymbol (gfc_gsym_root,
6515 comm_block_tree->n.common->binding_label);
6516 if (binding_label_gsym == NULL)
6518 /* Need to make a global symbol for the binding label to prevent
6519 it from colliding with another. */
6520 binding_label_gsym =
6521 gfc_get_gsymbol (comm_block_tree->n.common->binding_label);
6522 binding_label_gsym->sym_name = comm_block_tree->n.common->name;
6523 binding_label_gsym->type = GSYM_COMMON;
6525 else
6527 /* If comm_name_gsym is NULL, the name common block is use
6528 associated and the name could be colliding. */
6529 if (binding_label_gsym->type != GSYM_COMMON)
6530 gfc_error ("Binding label '%s' for common block '%s' at %L "
6531 "collides with the global entity '%s' at %L",
6532 comm_block_tree->n.common->binding_label,
6533 comm_block_tree->n.common->name,
6534 &(comm_block_tree->n.common->where),
6535 binding_label_gsym->name,
6536 &(binding_label_gsym->where));
6537 else if (comm_name_gsym != NULL
6538 && (strcmp (binding_label_gsym->name,
6539 comm_name_gsym->binding_label) != 0)
6540 && (strcmp (binding_label_gsym->sym_name,
6541 comm_name_gsym->name) != 0))
6542 gfc_error ("Binding label '%s' for common block '%s' at %L "
6543 "collides with global entity '%s' at %L",
6544 binding_label_gsym->name, binding_label_gsym->sym_name,
6545 &(comm_block_tree->n.common->where),
6546 comm_name_gsym->name, &(comm_name_gsym->where));
6550 return;
6554 /* Verify any BIND(C) derived types in the namespace so we can report errors
6555 for them once, rather than for each variable declared of that type. */
6557 static void
6558 resolve_bind_c_derived_types (gfc_symbol *derived_sym)
6560 if (derived_sym != NULL && derived_sym->attr.flavor == FL_DERIVED
6561 && derived_sym->attr.is_bind_c == 1)
6562 verify_bind_c_derived_type (derived_sym);
6564 return;
6568 /* Verify that any binding labels used in a given namespace do not collide
6569 with the names or binding labels of any global symbols. */
6571 static void
6572 gfc_verify_binding_labels (gfc_symbol *sym)
6574 int has_error = 0;
6576 if (sym != NULL && sym->attr.is_bind_c && sym->attr.is_iso_c == 0
6577 && sym->attr.flavor != FL_DERIVED && sym->binding_label[0] != '\0')
6579 gfc_gsymbol *bind_c_sym;
6581 bind_c_sym = gfc_find_gsymbol (gfc_gsym_root, sym->binding_label);
6582 if (bind_c_sym != NULL
6583 && strcmp (bind_c_sym->name, sym->binding_label) == 0)
6585 if (sym->attr.if_source == IFSRC_DECL
6586 && (bind_c_sym->type != GSYM_SUBROUTINE
6587 && bind_c_sym->type != GSYM_FUNCTION)
6588 && ((sym->attr.contained == 1
6589 && strcmp (bind_c_sym->sym_name, sym->name) != 0)
6590 || (sym->attr.use_assoc == 1
6591 && (strcmp (bind_c_sym->mod_name, sym->module) != 0))))
6593 /* Make sure global procedures don't collide with anything. */
6594 gfc_error ("Binding label '%s' at %L collides with the global "
6595 "entity '%s' at %L", sym->binding_label,
6596 &(sym->declared_at), bind_c_sym->name,
6597 &(bind_c_sym->where));
6598 has_error = 1;
6600 else if (sym->attr.contained == 0
6601 && (sym->attr.if_source == IFSRC_IFBODY
6602 && sym->attr.flavor == FL_PROCEDURE)
6603 && (bind_c_sym->sym_name != NULL
6604 && strcmp (bind_c_sym->sym_name, sym->name) != 0))
6606 /* Make sure procedures in interface bodies don't collide. */
6607 gfc_error ("Binding label '%s' in interface body at %L collides "
6608 "with the global entity '%s' at %L",
6609 sym->binding_label,
6610 &(sym->declared_at), bind_c_sym->name,
6611 &(bind_c_sym->where));
6612 has_error = 1;
6614 else if (sym->attr.contained == 0
6615 && (sym->attr.if_source == IFSRC_UNKNOWN))
6616 if ((sym->attr.use_assoc
6617 && (strcmp (bind_c_sym->mod_name, sym->module) != 0))
6618 || sym->attr.use_assoc == 0)
6620 gfc_error ("Binding label '%s' at %L collides with global "
6621 "entity '%s' at %L", sym->binding_label,
6622 &(sym->declared_at), bind_c_sym->name,
6623 &(bind_c_sym->where));
6624 has_error = 1;
6627 if (has_error != 0)
6628 /* Clear the binding label to prevent checking multiple times. */
6629 sym->binding_label[0] = '\0';
6631 else if (bind_c_sym == NULL)
6633 bind_c_sym = gfc_get_gsymbol (sym->binding_label);
6634 bind_c_sym->where = sym->declared_at;
6635 bind_c_sym->sym_name = sym->name;
6637 if (sym->attr.use_assoc == 1)
6638 bind_c_sym->mod_name = sym->module;
6639 else
6640 if (sym->ns->proc_name != NULL)
6641 bind_c_sym->mod_name = sym->ns->proc_name->name;
6643 if (sym->attr.contained == 0)
6645 if (sym->attr.subroutine)
6646 bind_c_sym->type = GSYM_SUBROUTINE;
6647 else if (sym->attr.function)
6648 bind_c_sym->type = GSYM_FUNCTION;
6652 return;
6656 /* Resolve an index expression. */
6658 static try
6659 resolve_index_expr (gfc_expr *e)
6661 if (gfc_resolve_expr (e) == FAILURE)
6662 return FAILURE;
6664 if (gfc_simplify_expr (e, 0) == FAILURE)
6665 return FAILURE;
6667 if (gfc_specification_expr (e) == FAILURE)
6668 return FAILURE;
6670 return SUCCESS;
6673 /* Resolve a charlen structure. */
6675 static try
6676 resolve_charlen (gfc_charlen *cl)
6678 int i;
6680 if (cl->resolved)
6681 return SUCCESS;
6683 cl->resolved = 1;
6685 specification_expr = 1;
6687 if (resolve_index_expr (cl->length) == FAILURE)
6689 specification_expr = 0;
6690 return FAILURE;
6693 /* "If the character length parameter value evaluates to a negative
6694 value, the length of character entities declared is zero." */
6695 if (cl->length && !gfc_extract_int (cl->length, &i) && i < 0)
6697 gfc_warning_now ("CHARACTER variable has zero length at %L",
6698 &cl->length->where);
6699 gfc_replace_expr (cl->length, gfc_int_expr (0));
6702 return SUCCESS;
6706 /* Test for non-constant shape arrays. */
6708 static bool
6709 is_non_constant_shape_array (gfc_symbol *sym)
6711 gfc_expr *e;
6712 int i;
6713 bool not_constant;
6715 not_constant = false;
6716 if (sym->as != NULL)
6718 /* Unfortunately, !gfc_is_compile_time_shape hits a legal case that
6719 has not been simplified; parameter array references. Do the
6720 simplification now. */
6721 for (i = 0; i < sym->as->rank; i++)
6723 e = sym->as->lower[i];
6724 if (e && (resolve_index_expr (e) == FAILURE
6725 || !gfc_is_constant_expr (e)))
6726 not_constant = true;
6728 e = sym->as->upper[i];
6729 if (e && (resolve_index_expr (e) == FAILURE
6730 || !gfc_is_constant_expr (e)))
6731 not_constant = true;
6734 return not_constant;
6737 /* Given a symbol and an initialization expression, add code to initialize
6738 the symbol to the function entry. */
6739 static void
6740 build_init_assign (gfc_symbol *sym, gfc_expr *init)
6742 gfc_expr *lval;
6743 gfc_code *init_st;
6744 gfc_namespace *ns = sym->ns;
6746 /* Search for the function namespace if this is a contained
6747 function without an explicit result. */
6748 if (sym->attr.function && sym == sym->result
6749 && sym->name != sym->ns->proc_name->name)
6751 ns = ns->contained;
6752 for (;ns; ns = ns->sibling)
6753 if (strcmp (ns->proc_name->name, sym->name) == 0)
6754 break;
6757 if (ns == NULL)
6759 gfc_free_expr (init);
6760 return;
6763 /* Build an l-value expression for the result. */
6764 lval = gfc_lval_expr_from_sym (sym);
6766 /* Add the code at scope entry. */
6767 init_st = gfc_get_code ();
6768 init_st->next = ns->code;
6769 ns->code = init_st;
6771 /* Assign the default initializer to the l-value. */
6772 init_st->loc = sym->declared_at;
6773 init_st->op = EXEC_INIT_ASSIGN;
6774 init_st->expr = lval;
6775 init_st->expr2 = init;
6778 /* Assign the default initializer to a derived type variable or result. */
6780 static void
6781 apply_default_init (gfc_symbol *sym)
6783 gfc_expr *init = NULL;
6785 if (sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
6786 return;
6788 if (sym->ts.type == BT_DERIVED && sym->ts.derived)
6789 init = gfc_default_initializer (&sym->ts);
6791 if (init == NULL)
6792 return;
6794 build_init_assign (sym, init);
6797 /* Build an initializer for a local integer, real, complex, logical, or
6798 character variable, based on the command line flags finit-local-zero,
6799 finit-integer=, finit-real=, finit-logical=, and finit-runtime. Returns
6800 null if the symbol should not have a default initialization. */
6801 static gfc_expr *
6802 build_default_init_expr (gfc_symbol *sym)
6804 int char_len;
6805 gfc_expr *init_expr;
6806 int i;
6808 /* These symbols should never have a default initialization. */
6809 if ((sym->attr.dimension && !gfc_is_compile_time_shape (sym->as))
6810 || sym->attr.external
6811 || sym->attr.dummy
6812 || sym->attr.pointer
6813 || sym->attr.in_equivalence
6814 || sym->attr.in_common
6815 || sym->attr.data
6816 || sym->module
6817 || sym->attr.cray_pointee
6818 || sym->attr.cray_pointer)
6819 return NULL;
6821 /* Now we'll try to build an initializer expression. */
6822 init_expr = gfc_get_expr ();
6823 init_expr->expr_type = EXPR_CONSTANT;
6824 init_expr->ts.type = sym->ts.type;
6825 init_expr->ts.kind = sym->ts.kind;
6826 init_expr->where = sym->declared_at;
6828 /* We will only initialize integers, reals, complex, logicals, and
6829 characters, and only if the corresponding command-line flags
6830 were set. Otherwise, we free init_expr and return null. */
6831 switch (sym->ts.type)
6833 case BT_INTEGER:
6834 if (gfc_option.flag_init_integer != GFC_INIT_INTEGER_OFF)
6835 mpz_init_set_si (init_expr->value.integer,
6836 gfc_option.flag_init_integer_value);
6837 else
6839 gfc_free_expr (init_expr);
6840 init_expr = NULL;
6842 break;
6844 case BT_REAL:
6845 mpfr_init (init_expr->value.real);
6846 switch (gfc_option.flag_init_real)
6848 case GFC_INIT_REAL_NAN:
6849 mpfr_set_nan (init_expr->value.real);
6850 break;
6852 case GFC_INIT_REAL_INF:
6853 mpfr_set_inf (init_expr->value.real, 1);
6854 break;
6856 case GFC_INIT_REAL_NEG_INF:
6857 mpfr_set_inf (init_expr->value.real, -1);
6858 break;
6860 case GFC_INIT_REAL_ZERO:
6861 mpfr_set_ui (init_expr->value.real, 0.0, GFC_RND_MODE);
6862 break;
6864 default:
6865 gfc_free_expr (init_expr);
6866 init_expr = NULL;
6867 break;
6869 break;
6871 case BT_COMPLEX:
6872 mpfr_init (init_expr->value.complex.r);
6873 mpfr_init (init_expr->value.complex.i);
6874 switch (gfc_option.flag_init_real)
6876 case GFC_INIT_REAL_NAN:
6877 mpfr_set_nan (init_expr->value.complex.r);
6878 mpfr_set_nan (init_expr->value.complex.i);
6879 break;
6881 case GFC_INIT_REAL_INF:
6882 mpfr_set_inf (init_expr->value.complex.r, 1);
6883 mpfr_set_inf (init_expr->value.complex.i, 1);
6884 break;
6886 case GFC_INIT_REAL_NEG_INF:
6887 mpfr_set_inf (init_expr->value.complex.r, -1);
6888 mpfr_set_inf (init_expr->value.complex.i, -1);
6889 break;
6891 case GFC_INIT_REAL_ZERO:
6892 mpfr_set_ui (init_expr->value.complex.r, 0.0, GFC_RND_MODE);
6893 mpfr_set_ui (init_expr->value.complex.i, 0.0, GFC_RND_MODE);
6894 break;
6896 default:
6897 gfc_free_expr (init_expr);
6898 init_expr = NULL;
6899 break;
6901 break;
6903 case BT_LOGICAL:
6904 if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_FALSE)
6905 init_expr->value.logical = 0;
6906 else if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_TRUE)
6907 init_expr->value.logical = 1;
6908 else
6910 gfc_free_expr (init_expr);
6911 init_expr = NULL;
6913 break;
6915 case BT_CHARACTER:
6916 /* For characters, the length must be constant in order to
6917 create a default initializer. */
6918 if (gfc_option.flag_init_character == GFC_INIT_CHARACTER_ON
6919 && sym->ts.cl->length
6920 && sym->ts.cl->length->expr_type == EXPR_CONSTANT)
6922 char_len = mpz_get_si (sym->ts.cl->length->value.integer);
6923 init_expr->value.character.length = char_len;
6924 init_expr->value.character.string = gfc_get_wide_string (char_len+1);
6925 for (i = 0; i < char_len; i++)
6926 init_expr->value.character.string[i]
6927 = (unsigned char) gfc_option.flag_init_character_value;
6929 else
6931 gfc_free_expr (init_expr);
6932 init_expr = NULL;
6934 break;
6936 default:
6937 gfc_free_expr (init_expr);
6938 init_expr = NULL;
6940 return init_expr;
6943 /* Add an initialization expression to a local variable. */
6944 static void
6945 apply_default_init_local (gfc_symbol *sym)
6947 gfc_expr *init = NULL;
6949 /* The symbol should be a variable or a function return value. */
6950 if ((sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
6951 || (sym->attr.function && sym->result != sym))
6952 return;
6954 /* Try to build the initializer expression. If we can't initialize
6955 this symbol, then init will be NULL. */
6956 init = build_default_init_expr (sym);
6957 if (init == NULL)
6958 return;
6960 /* For saved variables, we don't want to add an initializer at
6961 function entry, so we just add a static initializer. */
6962 if (sym->attr.save || sym->ns->save_all)
6964 /* Don't clobber an existing initializer! */
6965 gcc_assert (sym->value == NULL);
6966 sym->value = init;
6967 return;
6970 build_init_assign (sym, init);
6973 /* Resolution of common features of flavors variable and procedure. */
6975 static try
6976 resolve_fl_var_and_proc (gfc_symbol *sym, int mp_flag)
6978 /* Constraints on deferred shape variable. */
6979 if (sym->as == NULL || sym->as->type != AS_DEFERRED)
6981 if (sym->attr.allocatable)
6983 if (sym->attr.dimension)
6984 gfc_error ("Allocatable array '%s' at %L must have "
6985 "a deferred shape", sym->name, &sym->declared_at);
6986 else
6987 gfc_error ("Scalar object '%s' at %L may not be ALLOCATABLE",
6988 sym->name, &sym->declared_at);
6989 return FAILURE;
6992 if (sym->attr.pointer && sym->attr.dimension)
6994 gfc_error ("Array pointer '%s' at %L must have a deferred shape",
6995 sym->name, &sym->declared_at);
6996 return FAILURE;
7000 else
7002 if (!mp_flag && !sym->attr.allocatable
7003 && !sym->attr.pointer && !sym->attr.dummy)
7005 gfc_error ("Array '%s' at %L cannot have a deferred shape",
7006 sym->name, &sym->declared_at);
7007 return FAILURE;
7010 return SUCCESS;
7014 /* Additional checks for symbols with flavor variable and derived
7015 type. To be called from resolve_fl_variable. */
7017 static try
7018 resolve_fl_variable_derived (gfc_symbol *sym, int no_init_flag)
7020 gcc_assert (sym->ts.type == BT_DERIVED);
7022 /* Check to see if a derived type is blocked from being host
7023 associated by the presence of another class I symbol in the same
7024 namespace. 14.6.1.3 of the standard and the discussion on
7025 comp.lang.fortran. */
7026 if (sym->ns != sym->ts.derived->ns
7027 && sym->ns->proc_name->attr.if_source != IFSRC_IFBODY)
7029 gfc_symbol *s;
7030 gfc_find_symbol (sym->ts.derived->name, sym->ns, 0, &s);
7031 if (s && (s->attr.flavor != FL_DERIVED
7032 || !gfc_compare_derived_types (s, sym->ts.derived)))
7034 gfc_error ("The type '%s' cannot be host associated at %L "
7035 "because it is blocked by an incompatible object "
7036 "of the same name declared at %L",
7037 sym->ts.derived->name, &sym->declared_at,
7038 &s->declared_at);
7039 return FAILURE;
7043 /* 4th constraint in section 11.3: "If an object of a type for which
7044 component-initialization is specified (R429) appears in the
7045 specification-part of a module and does not have the ALLOCATABLE
7046 or POINTER attribute, the object shall have the SAVE attribute."
7048 The check for initializers is performed with
7049 has_default_initializer because gfc_default_initializer generates
7050 a hidden default for allocatable components. */
7051 if (!(sym->value || no_init_flag) && sym->ns->proc_name
7052 && sym->ns->proc_name->attr.flavor == FL_MODULE
7053 && !sym->ns->save_all && !sym->attr.save
7054 && !sym->attr.pointer && !sym->attr.allocatable
7055 && has_default_initializer (sym->ts.derived))
7057 gfc_error("Object '%s' at %L must have the SAVE attribute for "
7058 "default initialization of a component",
7059 sym->name, &sym->declared_at);
7060 return FAILURE;
7063 /* Assign default initializer. */
7064 if (!(sym->value || sym->attr.pointer || sym->attr.allocatable)
7065 && (!no_init_flag || sym->attr.intent == INTENT_OUT))
7067 sym->value = gfc_default_initializer (&sym->ts);
7070 return SUCCESS;
7074 /* Resolve symbols with flavor variable. */
7076 static try
7077 resolve_fl_variable (gfc_symbol *sym, int mp_flag)
7079 int no_init_flag, automatic_flag;
7080 gfc_expr *e;
7081 const char *auto_save_msg;
7083 auto_save_msg = "Automatic object '%s' at %L cannot have the "
7084 "SAVE attribute";
7086 if (resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
7087 return FAILURE;
7089 /* Set this flag to check that variables are parameters of all entries.
7090 This check is effected by the call to gfc_resolve_expr through
7091 is_non_constant_shape_array. */
7092 specification_expr = 1;
7094 if (sym->ns->proc_name
7095 && (sym->ns->proc_name->attr.flavor == FL_MODULE
7096 || sym->ns->proc_name->attr.is_main_program)
7097 && !sym->attr.use_assoc
7098 && !sym->attr.allocatable
7099 && !sym->attr.pointer
7100 && is_non_constant_shape_array (sym))
7102 /* The shape of a main program or module array needs to be
7103 constant. */
7104 gfc_error ("The module or main program array '%s' at %L must "
7105 "have constant shape", sym->name, &sym->declared_at);
7106 specification_expr = 0;
7107 return FAILURE;
7110 if (sym->ts.type == BT_CHARACTER)
7112 /* Make sure that character string variables with assumed length are
7113 dummy arguments. */
7114 e = sym->ts.cl->length;
7115 if (e == NULL && !sym->attr.dummy && !sym->attr.result)
7117 gfc_error ("Entity with assumed character length at %L must be a "
7118 "dummy argument or a PARAMETER", &sym->declared_at);
7119 return FAILURE;
7122 if (e && sym->attr.save && !gfc_is_constant_expr (e))
7124 gfc_error (auto_save_msg, sym->name, &sym->declared_at);
7125 return FAILURE;
7128 if (!gfc_is_constant_expr (e)
7129 && !(e->expr_type == EXPR_VARIABLE
7130 && e->symtree->n.sym->attr.flavor == FL_PARAMETER)
7131 && sym->ns->proc_name
7132 && (sym->ns->proc_name->attr.flavor == FL_MODULE
7133 || sym->ns->proc_name->attr.is_main_program)
7134 && !sym->attr.use_assoc)
7136 gfc_error ("'%s' at %L must have constant character length "
7137 "in this context", sym->name, &sym->declared_at);
7138 return FAILURE;
7142 if (sym->value == NULL && sym->attr.referenced)
7143 apply_default_init_local (sym); /* Try to apply a default initialization. */
7145 /* Determine if the symbol may not have an initializer. */
7146 no_init_flag = automatic_flag = 0;
7147 if (sym->attr.allocatable || sym->attr.external || sym->attr.dummy
7148 || sym->attr.intrinsic || sym->attr.result)
7149 no_init_flag = 1;
7150 else if (sym->attr.dimension && !sym->attr.pointer
7151 && is_non_constant_shape_array (sym))
7153 no_init_flag = automatic_flag = 1;
7155 /* Also, they must not have the SAVE attribute.
7156 SAVE_IMPLICIT is checked below. */
7157 if (sym->attr.save == SAVE_EXPLICIT)
7159 gfc_error (auto_save_msg, sym->name, &sym->declared_at);
7160 return FAILURE;
7164 /* Reject illegal initializers. */
7165 if (!sym->mark && sym->value)
7167 if (sym->attr.allocatable)
7168 gfc_error ("Allocatable '%s' at %L cannot have an initializer",
7169 sym->name, &sym->declared_at);
7170 else if (sym->attr.external)
7171 gfc_error ("External '%s' at %L cannot have an initializer",
7172 sym->name, &sym->declared_at);
7173 else if (sym->attr.dummy
7174 && !(sym->ts.type == BT_DERIVED && sym->attr.intent == INTENT_OUT))
7175 gfc_error ("Dummy '%s' at %L cannot have an initializer",
7176 sym->name, &sym->declared_at);
7177 else if (sym->attr.intrinsic)
7178 gfc_error ("Intrinsic '%s' at %L cannot have an initializer",
7179 sym->name, &sym->declared_at);
7180 else if (sym->attr.result)
7181 gfc_error ("Function result '%s' at %L cannot have an initializer",
7182 sym->name, &sym->declared_at);
7183 else if (automatic_flag)
7184 gfc_error ("Automatic array '%s' at %L cannot have an initializer",
7185 sym->name, &sym->declared_at);
7186 else
7187 goto no_init_error;
7188 return FAILURE;
7191 no_init_error:
7192 if (sym->ts.type == BT_DERIVED)
7193 return resolve_fl_variable_derived (sym, no_init_flag);
7195 return SUCCESS;
7199 /* Resolve a procedure. */
7201 static try
7202 resolve_fl_procedure (gfc_symbol *sym, int mp_flag)
7204 gfc_formal_arglist *arg;
7206 if (sym->attr.ambiguous_interfaces && !sym->attr.referenced)
7207 gfc_warning ("Although not referenced, '%s' at %L has ambiguous "
7208 "interfaces", sym->name, &sym->declared_at);
7210 if (sym->attr.function
7211 && resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
7212 return FAILURE;
7214 if (sym->ts.type == BT_CHARACTER)
7216 gfc_charlen *cl = sym->ts.cl;
7218 if (cl && cl->length && gfc_is_constant_expr (cl->length)
7219 && resolve_charlen (cl) == FAILURE)
7220 return FAILURE;
7222 if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
7224 if (sym->attr.proc == PROC_ST_FUNCTION)
7226 gfc_error ("Character-valued statement function '%s' at %L must "
7227 "have constant length", sym->name, &sym->declared_at);
7228 return FAILURE;
7231 if (sym->attr.external && sym->formal == NULL
7232 && cl && cl->length && cl->length->expr_type != EXPR_CONSTANT)
7234 gfc_error ("Automatic character length function '%s' at %L must "
7235 "have an explicit interface", sym->name,
7236 &sym->declared_at);
7237 return FAILURE;
7242 /* Ensure that derived type for are not of a private type. Internal
7243 module procedures are excluded by 2.2.3.3 - ie. they are not
7244 externally accessible and can access all the objects accessible in
7245 the host. */
7246 if (!(sym->ns->parent
7247 && sym->ns->parent->proc_name->attr.flavor == FL_MODULE)
7248 && gfc_check_access(sym->attr.access, sym->ns->default_access))
7250 gfc_interface *iface;
7252 for (arg = sym->formal; arg; arg = arg->next)
7254 if (arg->sym
7255 && arg->sym->ts.type == BT_DERIVED
7256 && !arg->sym->ts.derived->attr.use_assoc
7257 && !gfc_check_access (arg->sym->ts.derived->attr.access,
7258 arg->sym->ts.derived->ns->default_access)
7259 && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: '%s' is of a "
7260 "PRIVATE type and cannot be a dummy argument"
7261 " of '%s', which is PUBLIC at %L",
7262 arg->sym->name, sym->name, &sym->declared_at)
7263 == FAILURE)
7265 /* Stop this message from recurring. */
7266 arg->sym->ts.derived->attr.access = ACCESS_PUBLIC;
7267 return FAILURE;
7271 /* PUBLIC interfaces may expose PRIVATE procedures that take types
7272 PRIVATE to the containing module. */
7273 for (iface = sym->generic; iface; iface = iface->next)
7275 for (arg = iface->sym->formal; arg; arg = arg->next)
7277 if (arg->sym
7278 && arg->sym->ts.type == BT_DERIVED
7279 && !arg->sym->ts.derived->attr.use_assoc
7280 && !gfc_check_access (arg->sym->ts.derived->attr.access,
7281 arg->sym->ts.derived->ns->default_access)
7282 && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
7283 "'%s' in PUBLIC interface '%s' at %L "
7284 "takes dummy arguments of '%s' which is "
7285 "PRIVATE", iface->sym->name, sym->name,
7286 &iface->sym->declared_at,
7287 gfc_typename (&arg->sym->ts)) == FAILURE)
7289 /* Stop this message from recurring. */
7290 arg->sym->ts.derived->attr.access = ACCESS_PUBLIC;
7291 return FAILURE;
7296 /* PUBLIC interfaces may expose PRIVATE procedures that take types
7297 PRIVATE to the containing module. */
7298 for (iface = sym->generic; iface; iface = iface->next)
7300 for (arg = iface->sym->formal; arg; arg = arg->next)
7302 if (arg->sym
7303 && arg->sym->ts.type == BT_DERIVED
7304 && !arg->sym->ts.derived->attr.use_assoc
7305 && !gfc_check_access (arg->sym->ts.derived->attr.access,
7306 arg->sym->ts.derived->ns->default_access)
7307 && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
7308 "'%s' in PUBLIC interface '%s' at %L "
7309 "takes dummy arguments of '%s' which is "
7310 "PRIVATE", iface->sym->name, sym->name,
7311 &iface->sym->declared_at,
7312 gfc_typename (&arg->sym->ts)) == FAILURE)
7314 /* Stop this message from recurring. */
7315 arg->sym->ts.derived->attr.access = ACCESS_PUBLIC;
7316 return FAILURE;
7322 if (sym->attr.function && sym->value && sym->attr.proc != PROC_ST_FUNCTION)
7324 gfc_error ("Function '%s' at %L cannot have an initializer",
7325 sym->name, &sym->declared_at);
7326 return FAILURE;
7329 /* An external symbol may not have an initializer because it is taken to be
7330 a procedure. */
7331 if (sym->attr.external && sym->value)
7333 gfc_error ("External object '%s' at %L may not have an initializer",
7334 sym->name, &sym->declared_at);
7335 return FAILURE;
7338 /* An elemental function is required to return a scalar 12.7.1 */
7339 if (sym->attr.elemental && sym->attr.function && sym->as)
7341 gfc_error ("ELEMENTAL function '%s' at %L must have a scalar "
7342 "result", sym->name, &sym->declared_at);
7343 /* Reset so that the error only occurs once. */
7344 sym->attr.elemental = 0;
7345 return FAILURE;
7348 /* 5.1.1.5 of the Standard: A function name declared with an asterisk
7349 char-len-param shall not be array-valued, pointer-valued, recursive
7350 or pure. ....snip... A character value of * may only be used in the
7351 following ways: (i) Dummy arg of procedure - dummy associates with
7352 actual length; (ii) To declare a named constant; or (iii) External
7353 function - but length must be declared in calling scoping unit. */
7354 if (sym->attr.function
7355 && sym->ts.type == BT_CHARACTER
7356 && sym->ts.cl && sym->ts.cl->length == NULL)
7358 if ((sym->as && sym->as->rank) || (sym->attr.pointer)
7359 || (sym->attr.recursive) || (sym->attr.pure))
7361 if (sym->as && sym->as->rank)
7362 gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
7363 "array-valued", sym->name, &sym->declared_at);
7365 if (sym->attr.pointer)
7366 gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
7367 "pointer-valued", sym->name, &sym->declared_at);
7369 if (sym->attr.pure)
7370 gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
7371 "pure", sym->name, &sym->declared_at);
7373 if (sym->attr.recursive)
7374 gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
7375 "recursive", sym->name, &sym->declared_at);
7377 return FAILURE;
7380 /* Appendix B.2 of the standard. Contained functions give an
7381 error anyway. Fixed-form is likely to be F77/legacy. */
7382 if (!sym->attr.contained && gfc_current_form != FORM_FIXED)
7383 gfc_notify_std (GFC_STD_F95_OBS, "CHARACTER(*) function "
7384 "'%s' at %L is obsolescent in fortran 95",
7385 sym->name, &sym->declared_at);
7388 if (sym->attr.is_bind_c && sym->attr.is_c_interop != 1)
7390 gfc_formal_arglist *curr_arg;
7391 int has_non_interop_arg = 0;
7393 if (verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
7394 sym->common_block) == FAILURE)
7396 /* Clear these to prevent looking at them again if there was an
7397 error. */
7398 sym->attr.is_bind_c = 0;
7399 sym->attr.is_c_interop = 0;
7400 sym->ts.is_c_interop = 0;
7402 else
7404 /* So far, no errors have been found. */
7405 sym->attr.is_c_interop = 1;
7406 sym->ts.is_c_interop = 1;
7409 curr_arg = sym->formal;
7410 while (curr_arg != NULL)
7412 /* Skip implicitly typed dummy args here. */
7413 if (curr_arg->sym->attr.implicit_type == 0)
7414 if (verify_c_interop_param (curr_arg->sym) == FAILURE)
7415 /* If something is found to fail, record the fact so we
7416 can mark the symbol for the procedure as not being
7417 BIND(C) to try and prevent multiple errors being
7418 reported. */
7419 has_non_interop_arg = 1;
7421 curr_arg = curr_arg->next;
7424 /* See if any of the arguments were not interoperable and if so, clear
7425 the procedure symbol to prevent duplicate error messages. */
7426 if (has_non_interop_arg != 0)
7428 sym->attr.is_c_interop = 0;
7429 sym->ts.is_c_interop = 0;
7430 sym->attr.is_bind_c = 0;
7434 return SUCCESS;
7438 /* Resolve the components of a derived type. */
7440 static try
7441 resolve_fl_derived (gfc_symbol *sym)
7443 gfc_component *c;
7444 gfc_dt_list * dt_list;
7445 int i;
7447 for (c = sym->components; c != NULL; c = c->next)
7449 if (c->ts.type == BT_CHARACTER)
7451 if (c->ts.cl->length == NULL
7452 || (resolve_charlen (c->ts.cl) == FAILURE)
7453 || !gfc_is_constant_expr (c->ts.cl->length))
7455 gfc_error ("Character length of component '%s' needs to "
7456 "be a constant specification expression at %L",
7457 c->name,
7458 c->ts.cl->length ? &c->ts.cl->length->where : &c->loc);
7459 return FAILURE;
7463 if (c->ts.type == BT_DERIVED
7464 && sym->component_access != ACCESS_PRIVATE
7465 && gfc_check_access (sym->attr.access, sym->ns->default_access)
7466 && !c->ts.derived->attr.use_assoc
7467 && !gfc_check_access (c->ts.derived->attr.access,
7468 c->ts.derived->ns->default_access))
7470 gfc_error ("The component '%s' is a PRIVATE type and cannot be "
7471 "a component of '%s', which is PUBLIC at %L",
7472 c->name, sym->name, &sym->declared_at);
7473 return FAILURE;
7476 if (sym->attr.sequence)
7478 if (c->ts.type == BT_DERIVED && c->ts.derived->attr.sequence == 0)
7480 gfc_error ("Component %s of SEQUENCE type declared at %L does "
7481 "not have the SEQUENCE attribute",
7482 c->ts.derived->name, &sym->declared_at);
7483 return FAILURE;
7487 if (c->ts.type == BT_DERIVED && c->pointer
7488 && c->ts.derived->components == NULL)
7490 gfc_error ("The pointer component '%s' of '%s' at %L is a type "
7491 "that has not been declared", c->name, sym->name,
7492 &c->loc);
7493 return FAILURE;
7496 if (c->pointer || c->allocatable || c->as == NULL)
7497 continue;
7499 for (i = 0; i < c->as->rank; i++)
7501 if (c->as->lower[i] == NULL
7502 || !gfc_is_constant_expr (c->as->lower[i])
7503 || (resolve_index_expr (c->as->lower[i]) == FAILURE)
7504 || c->as->upper[i] == NULL
7505 || (resolve_index_expr (c->as->upper[i]) == FAILURE)
7506 || !gfc_is_constant_expr (c->as->upper[i]))
7508 gfc_error ("Component '%s' of '%s' at %L must have "
7509 "constant array bounds",
7510 c->name, sym->name, &c->loc);
7511 return FAILURE;
7516 /* Add derived type to the derived type list. */
7517 for (dt_list = gfc_derived_types; dt_list; dt_list = dt_list->next)
7518 if (sym == dt_list->derived)
7519 break;
7521 if (dt_list == NULL)
7523 dt_list = gfc_get_dt_list ();
7524 dt_list->next = gfc_derived_types;
7525 dt_list->derived = sym;
7526 gfc_derived_types = dt_list;
7529 return SUCCESS;
7533 static try
7534 resolve_fl_namelist (gfc_symbol *sym)
7536 gfc_namelist *nl;
7537 gfc_symbol *nlsym;
7539 /* Reject PRIVATE objects in a PUBLIC namelist. */
7540 if (gfc_check_access(sym->attr.access, sym->ns->default_access))
7542 for (nl = sym->namelist; nl; nl = nl->next)
7544 if (!nl->sym->attr.use_assoc
7545 && !(sym->ns->parent == nl->sym->ns)
7546 && !(sym->ns->parent
7547 && sym->ns->parent->parent == nl->sym->ns)
7548 && !gfc_check_access(nl->sym->attr.access,
7549 nl->sym->ns->default_access))
7551 gfc_error ("NAMELIST object '%s' was declared PRIVATE and "
7552 "cannot be member of PUBLIC namelist '%s' at %L",
7553 nl->sym->name, sym->name, &sym->declared_at);
7554 return FAILURE;
7557 /* Types with private components that came here by USE-association. */
7558 if (nl->sym->ts.type == BT_DERIVED
7559 && derived_inaccessible (nl->sym->ts.derived))
7561 gfc_error ("NAMELIST object '%s' has use-associated PRIVATE "
7562 "components and cannot be member of namelist '%s' at %L",
7563 nl->sym->name, sym->name, &sym->declared_at);
7564 return FAILURE;
7567 /* Types with private components that are defined in the same module. */
7568 if (nl->sym->ts.type == BT_DERIVED
7569 && !(sym->ns->parent == nl->sym->ts.derived->ns)
7570 && !gfc_check_access (nl->sym->ts.derived->attr.private_comp
7571 ? ACCESS_PRIVATE : ACCESS_UNKNOWN,
7572 nl->sym->ns->default_access))
7574 gfc_error ("NAMELIST object '%s' has PRIVATE components and "
7575 "cannot be a member of PUBLIC namelist '%s' at %L",
7576 nl->sym->name, sym->name, &sym->declared_at);
7577 return FAILURE;
7582 for (nl = sym->namelist; nl; nl = nl->next)
7584 /* Reject namelist arrays of assumed shape. */
7585 if (nl->sym->as && nl->sym->as->type == AS_ASSUMED_SHAPE
7586 && gfc_notify_std (GFC_STD_F2003, "NAMELIST array object '%s' "
7587 "must not have assumed shape in namelist "
7588 "'%s' at %L", nl->sym->name, sym->name,
7589 &sym->declared_at) == FAILURE)
7590 return FAILURE;
7592 /* Reject namelist arrays that are not constant shape. */
7593 if (is_non_constant_shape_array (nl->sym))
7595 gfc_error ("NAMELIST array object '%s' must have constant "
7596 "shape in namelist '%s' at %L", nl->sym->name,
7597 sym->name, &sym->declared_at);
7598 return FAILURE;
7601 /* Namelist objects cannot have allocatable or pointer components. */
7602 if (nl->sym->ts.type != BT_DERIVED)
7603 continue;
7605 if (nl->sym->ts.derived->attr.alloc_comp)
7607 gfc_error ("NAMELIST object '%s' in namelist '%s' at %L cannot "
7608 "have ALLOCATABLE components",
7609 nl->sym->name, sym->name, &sym->declared_at);
7610 return FAILURE;
7613 if (nl->sym->ts.derived->attr.pointer_comp)
7615 gfc_error ("NAMELIST object '%s' in namelist '%s' at %L cannot "
7616 "have POINTER components",
7617 nl->sym->name, sym->name, &sym->declared_at);
7618 return FAILURE;
7623 /* 14.1.2 A module or internal procedure represent local entities
7624 of the same type as a namelist member and so are not allowed. */
7625 for (nl = sym->namelist; nl; nl = nl->next)
7627 if (nl->sym->ts.kind != 0 && nl->sym->attr.flavor == FL_VARIABLE)
7628 continue;
7630 if (nl->sym->attr.function && nl->sym == nl->sym->result)
7631 if ((nl->sym == sym->ns->proc_name)
7633 (sym->ns->parent && nl->sym == sym->ns->parent->proc_name))
7634 continue;
7636 nlsym = NULL;
7637 if (nl->sym && nl->sym->name)
7638 gfc_find_symbol (nl->sym->name, sym->ns, 1, &nlsym);
7639 if (nlsym && nlsym->attr.flavor == FL_PROCEDURE)
7641 gfc_error ("PROCEDURE attribute conflicts with NAMELIST "
7642 "attribute in '%s' at %L", nlsym->name,
7643 &sym->declared_at);
7644 return FAILURE;
7648 return SUCCESS;
7652 static try
7653 resolve_fl_parameter (gfc_symbol *sym)
7655 /* A parameter array's shape needs to be constant. */
7656 if (sym->as != NULL
7657 && (sym->as->type == AS_DEFERRED
7658 || is_non_constant_shape_array (sym)))
7660 gfc_error ("Parameter array '%s' at %L cannot be automatic "
7661 "or of deferred shape", sym->name, &sym->declared_at);
7662 return FAILURE;
7665 /* Make sure a parameter that has been implicitly typed still
7666 matches the implicit type, since PARAMETER statements can precede
7667 IMPLICIT statements. */
7668 if (sym->attr.implicit_type
7669 && !gfc_compare_types (&sym->ts, gfc_get_default_type (sym, sym->ns)))
7671 gfc_error ("Implicitly typed PARAMETER '%s' at %L doesn't match a "
7672 "later IMPLICIT type", sym->name, &sym->declared_at);
7673 return FAILURE;
7676 /* Make sure the types of derived parameters are consistent. This
7677 type checking is deferred until resolution because the type may
7678 refer to a derived type from the host. */
7679 if (sym->ts.type == BT_DERIVED
7680 && !gfc_compare_types (&sym->ts, &sym->value->ts))
7682 gfc_error ("Incompatible derived type in PARAMETER at %L",
7683 &sym->value->where);
7684 return FAILURE;
7686 return SUCCESS;
7690 /* Do anything necessary to resolve a symbol. Right now, we just
7691 assume that an otherwise unknown symbol is a variable. This sort
7692 of thing commonly happens for symbols in module. */
7694 static void
7695 resolve_symbol (gfc_symbol *sym)
7697 int check_constant, mp_flag;
7698 gfc_symtree *symtree;
7699 gfc_symtree *this_symtree;
7700 gfc_namespace *ns;
7701 gfc_component *c;
7703 if (sym->attr.flavor == FL_UNKNOWN)
7706 /* If we find that a flavorless symbol is an interface in one of the
7707 parent namespaces, find its symtree in this namespace, free the
7708 symbol and set the symtree to point to the interface symbol. */
7709 for (ns = gfc_current_ns->parent; ns; ns = ns->parent)
7711 symtree = gfc_find_symtree (ns->sym_root, sym->name);
7712 if (symtree && symtree->n.sym->generic)
7714 this_symtree = gfc_find_symtree (gfc_current_ns->sym_root,
7715 sym->name);
7716 sym->refs--;
7717 if (!sym->refs)
7718 gfc_free_symbol (sym);
7719 symtree->n.sym->refs++;
7720 this_symtree->n.sym = symtree->n.sym;
7721 return;
7725 /* Otherwise give it a flavor according to such attributes as
7726 it has. */
7727 if (sym->attr.external == 0 && sym->attr.intrinsic == 0)
7728 sym->attr.flavor = FL_VARIABLE;
7729 else
7731 sym->attr.flavor = FL_PROCEDURE;
7732 if (sym->attr.dimension)
7733 sym->attr.function = 1;
7737 if (sym->attr.procedure && sym->ts.interface
7738 && sym->attr.if_source != IFSRC_DECL)
7740 if (sym->ts.interface->attr.procedure)
7741 gfc_error ("Interface '%s', used by procedure '%s' at %L, is declared "
7742 "in a later PROCEDURE statement", sym->ts.interface->name,
7743 sym->name,&sym->declared_at);
7745 /* Get the attributes from the interface (now resolved). */
7746 if (sym->ts.interface->attr.if_source || sym->ts.interface->attr.intrinsic)
7748 sym->ts.type = sym->ts.interface->ts.type;
7749 sym->ts.kind = sym->ts.interface->ts.kind;
7750 sym->attr.function = sym->ts.interface->attr.function;
7751 sym->attr.subroutine = sym->ts.interface->attr.subroutine;
7752 copy_formal_args (sym, sym->ts.interface);
7754 else if (sym->ts.interface->name[0] != '\0')
7756 gfc_error ("Interface '%s' of procedure '%s' at %L must be explicit",
7757 sym->ts.interface->name, sym->name, &sym->declared_at);
7758 return;
7762 if (sym->attr.flavor == FL_DERIVED && resolve_fl_derived (sym) == FAILURE)
7763 return;
7765 /* Symbols that are module procedures with results (functions) have
7766 the types and array specification copied for type checking in
7767 procedures that call them, as well as for saving to a module
7768 file. These symbols can't stand the scrutiny that their results
7769 can. */
7770 mp_flag = (sym->result != NULL && sym->result != sym);
7773 /* Make sure that the intrinsic is consistent with its internal
7774 representation. This needs to be done before assigning a default
7775 type to avoid spurious warnings. */
7776 if (sym->attr.flavor != FL_MODULE && sym->attr.intrinsic)
7778 if (gfc_intrinsic_name (sym->name, 0))
7780 if (sym->ts.type != BT_UNKNOWN && gfc_option.warn_surprising)
7781 gfc_warning ("Type specified for intrinsic function '%s' at %L is ignored",
7782 sym->name, &sym->declared_at);
7784 else if (gfc_intrinsic_name (sym->name, 1))
7786 if (sym->ts.type != BT_UNKNOWN)
7788 gfc_error ("Intrinsic subroutine '%s' at %L shall not have a type specifier",
7789 sym->name, &sym->declared_at);
7790 return;
7793 else
7795 gfc_error ("Intrinsic '%s' at %L does not exist", sym->name, &sym->declared_at);
7796 return;
7800 /* Assign default type to symbols that need one and don't have one. */
7801 if (sym->ts.type == BT_UNKNOWN)
7803 if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER)
7804 gfc_set_default_type (sym, 1, NULL);
7806 if (sym->attr.flavor == FL_PROCEDURE && sym->attr.function)
7808 /* The specific case of an external procedure should emit an error
7809 in the case that there is no implicit type. */
7810 if (!mp_flag)
7811 gfc_set_default_type (sym, sym->attr.external, NULL);
7812 else
7814 /* Result may be in another namespace. */
7815 resolve_symbol (sym->result);
7817 sym->ts = sym->result->ts;
7818 sym->as = gfc_copy_array_spec (sym->result->as);
7819 sym->attr.dimension = sym->result->attr.dimension;
7820 sym->attr.pointer = sym->result->attr.pointer;
7821 sym->attr.allocatable = sym->result->attr.allocatable;
7826 /* Assumed size arrays and assumed shape arrays must be dummy
7827 arguments. */
7829 if (sym->as != NULL
7830 && (sym->as->type == AS_ASSUMED_SIZE
7831 || sym->as->type == AS_ASSUMED_SHAPE)
7832 && sym->attr.dummy == 0)
7834 if (sym->as->type == AS_ASSUMED_SIZE)
7835 gfc_error ("Assumed size array at %L must be a dummy argument",
7836 &sym->declared_at);
7837 else
7838 gfc_error ("Assumed shape array at %L must be a dummy argument",
7839 &sym->declared_at);
7840 return;
7843 /* Make sure symbols with known intent or optional are really dummy
7844 variable. Because of ENTRY statement, this has to be deferred
7845 until resolution time. */
7847 if (!sym->attr.dummy
7848 && (sym->attr.optional || sym->attr.intent != INTENT_UNKNOWN))
7850 gfc_error ("Symbol at %L is not a DUMMY variable", &sym->declared_at);
7851 return;
7854 if (sym->attr.value && !sym->attr.dummy)
7856 gfc_error ("'%s' at %L cannot have the VALUE attribute because "
7857 "it is not a dummy argument", sym->name, &sym->declared_at);
7858 return;
7861 if (sym->attr.value && sym->ts.type == BT_CHARACTER)
7863 gfc_charlen *cl = sym->ts.cl;
7864 if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
7866 gfc_error ("Character dummy variable '%s' at %L with VALUE "
7867 "attribute must have constant length",
7868 sym->name, &sym->declared_at);
7869 return;
7872 if (sym->ts.is_c_interop
7873 && mpz_cmp_si (cl->length->value.integer, 1) != 0)
7875 gfc_error ("C interoperable character dummy variable '%s' at %L "
7876 "with VALUE attribute must have length one",
7877 sym->name, &sym->declared_at);
7878 return;
7882 /* If the symbol is marked as bind(c), verify it's type and kind. Do not
7883 do this for something that was implicitly typed because that is handled
7884 in gfc_set_default_type. Handle dummy arguments and procedure
7885 definitions separately. Also, anything that is use associated is not
7886 handled here but instead is handled in the module it is declared in.
7887 Finally, derived type definitions are allowed to be BIND(C) since that
7888 only implies that they're interoperable, and they are checked fully for
7889 interoperability when a variable is declared of that type. */
7890 if (sym->attr.is_bind_c && sym->attr.implicit_type == 0 &&
7891 sym->attr.use_assoc == 0 && sym->attr.dummy == 0 &&
7892 sym->attr.flavor != FL_PROCEDURE && sym->attr.flavor != FL_DERIVED)
7894 try t = SUCCESS;
7896 /* First, make sure the variable is declared at the
7897 module-level scope (J3/04-007, Section 15.3). */
7898 if (sym->ns->proc_name->attr.flavor != FL_MODULE &&
7899 sym->attr.in_common == 0)
7901 gfc_error ("Variable '%s' at %L cannot be BIND(C) because it "
7902 "is neither a COMMON block nor declared at the "
7903 "module level scope", sym->name, &(sym->declared_at));
7904 t = FAILURE;
7906 else if (sym->common_head != NULL)
7908 t = verify_com_block_vars_c_interop (sym->common_head);
7910 else
7912 /* If type() declaration, we need to verify that the components
7913 of the given type are all C interoperable, etc. */
7914 if (sym->ts.type == BT_DERIVED &&
7915 sym->ts.derived->attr.is_c_interop != 1)
7917 /* Make sure the user marked the derived type as BIND(C). If
7918 not, call the verify routine. This could print an error
7919 for the derived type more than once if multiple variables
7920 of that type are declared. */
7921 if (sym->ts.derived->attr.is_bind_c != 1)
7922 verify_bind_c_derived_type (sym->ts.derived);
7923 t = FAILURE;
7926 /* Verify the variable itself as C interoperable if it
7927 is BIND(C). It is not possible for this to succeed if
7928 the verify_bind_c_derived_type failed, so don't have to handle
7929 any error returned by verify_bind_c_derived_type. */
7930 t = verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
7931 sym->common_block);
7934 if (t == FAILURE)
7936 /* clear the is_bind_c flag to prevent reporting errors more than
7937 once if something failed. */
7938 sym->attr.is_bind_c = 0;
7939 return;
7943 /* If a derived type symbol has reached this point, without its
7944 type being declared, we have an error. Notice that most
7945 conditions that produce undefined derived types have already
7946 been dealt with. However, the likes of:
7947 implicit type(t) (t) ..... call foo (t) will get us here if
7948 the type is not declared in the scope of the implicit
7949 statement. Change the type to BT_UNKNOWN, both because it is so
7950 and to prevent an ICE. */
7951 if (sym->ts.type == BT_DERIVED && sym->ts.derived->components == NULL
7952 && !sym->ts.derived->attr.zero_comp)
7954 gfc_error ("The derived type '%s' at %L is of type '%s', "
7955 "which has not been defined", sym->name,
7956 &sym->declared_at, sym->ts.derived->name);
7957 sym->ts.type = BT_UNKNOWN;
7958 return;
7961 /* Make sure that the derived type has been resolved and that the
7962 derived type is visible in the symbol's namespace, if it is a
7963 module function and is not PRIVATE. */
7964 if (sym->ts.type == BT_DERIVED
7965 && sym->ts.derived->attr.use_assoc
7966 && sym->ns->proc_name->attr.flavor == FL_MODULE)
7968 gfc_symbol *ds;
7970 if (resolve_fl_derived (sym->ts.derived) == FAILURE)
7971 return;
7973 gfc_find_symbol (sym->ts.derived->name, sym->ns, 1, &ds);
7974 if (!ds && sym->attr.function
7975 && gfc_check_access (sym->attr.access, sym->ns->default_access))
7977 symtree = gfc_new_symtree (&sym->ns->sym_root,
7978 sym->ts.derived->name);
7979 symtree->n.sym = sym->ts.derived;
7980 sym->ts.derived->refs++;
7984 /* Unless the derived-type declaration is use associated, Fortran 95
7985 does not allow public entries of private derived types.
7986 See 4.4.1 (F95) and 4.5.1.1 (F2003); and related interpretation
7987 161 in 95-006r3. */
7988 if (sym->ts.type == BT_DERIVED
7989 && sym->ns->proc_name && sym->ns->proc_name->attr.flavor == FL_MODULE
7990 && !sym->ts.derived->attr.use_assoc
7991 && gfc_check_access (sym->attr.access, sym->ns->default_access)
7992 && !gfc_check_access (sym->ts.derived->attr.access,
7993 sym->ts.derived->ns->default_access)
7994 && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC %s '%s' at %L "
7995 "of PRIVATE derived type '%s'",
7996 (sym->attr.flavor == FL_PARAMETER) ? "parameter"
7997 : "variable", sym->name, &sym->declared_at,
7998 sym->ts.derived->name) == FAILURE)
7999 return;
8001 /* An assumed-size array with INTENT(OUT) shall not be of a type for which
8002 default initialization is defined (5.1.2.4.4). */
8003 if (sym->ts.type == BT_DERIVED
8004 && sym->attr.dummy
8005 && sym->attr.intent == INTENT_OUT
8006 && sym->as
8007 && sym->as->type == AS_ASSUMED_SIZE)
8009 for (c = sym->ts.derived->components; c; c = c->next)
8011 if (c->initializer)
8013 gfc_error ("The INTENT(OUT) dummy argument '%s' at %L is "
8014 "ASSUMED SIZE and so cannot have a default initializer",
8015 sym->name, &sym->declared_at);
8016 return;
8021 switch (sym->attr.flavor)
8023 case FL_VARIABLE:
8024 if (resolve_fl_variable (sym, mp_flag) == FAILURE)
8025 return;
8026 break;
8028 case FL_PROCEDURE:
8029 if (resolve_fl_procedure (sym, mp_flag) == FAILURE)
8030 return;
8031 break;
8033 case FL_NAMELIST:
8034 if (resolve_fl_namelist (sym) == FAILURE)
8035 return;
8036 break;
8038 case FL_PARAMETER:
8039 if (resolve_fl_parameter (sym) == FAILURE)
8040 return;
8041 break;
8043 default:
8044 break;
8047 /* Resolve array specifier. Check as well some constraints
8048 on COMMON blocks. */
8050 check_constant = sym->attr.in_common && !sym->attr.pointer;
8052 /* Set the formal_arg_flag so that check_conflict will not throw
8053 an error for host associated variables in the specification
8054 expression for an array_valued function. */
8055 if (sym->attr.function && sym->as)
8056 formal_arg_flag = 1;
8058 gfc_resolve_array_spec (sym->as, check_constant);
8060 formal_arg_flag = 0;
8062 /* Resolve formal namespaces. */
8063 if (sym->formal_ns && sym->formal_ns != gfc_current_ns)
8064 gfc_resolve (sym->formal_ns);
8066 /* Check threadprivate restrictions. */
8067 if (sym->attr.threadprivate && !sym->attr.save && !sym->ns->save_all
8068 && (!sym->attr.in_common
8069 && sym->module == NULL
8070 && (sym->ns->proc_name == NULL
8071 || sym->ns->proc_name->attr.flavor != FL_MODULE)))
8072 gfc_error ("Threadprivate at %L isn't SAVEd", &sym->declared_at);
8074 /* If we have come this far we can apply default-initializers, as
8075 described in 14.7.5, to those variables that have not already
8076 been assigned one. */
8077 if (sym->ts.type == BT_DERIVED
8078 && sym->attr.referenced
8079 && sym->ns == gfc_current_ns
8080 && !sym->value
8081 && !sym->attr.allocatable
8082 && !sym->attr.alloc_comp)
8084 symbol_attribute *a = &sym->attr;
8086 if ((!a->save && !a->dummy && !a->pointer
8087 && !a->in_common && !a->use_assoc
8088 && !(a->function && sym != sym->result))
8089 || (a->dummy && a->intent == INTENT_OUT))
8090 apply_default_init (sym);
8095 /************* Resolve DATA statements *************/
8097 static struct
8099 gfc_data_value *vnode;
8100 mpz_t left;
8102 values;
8105 /* Advance the values structure to point to the next value in the data list. */
8107 static try
8108 next_data_value (void)
8111 while (mpz_cmp_ui (values.left, 0) == 0)
8113 if (values.vnode->next == NULL)
8114 return FAILURE;
8116 values.vnode = values.vnode->next;
8117 mpz_set (values.left, values.vnode->repeat);
8120 return SUCCESS;
8124 static try
8125 check_data_variable (gfc_data_variable *var, locus *where)
8127 gfc_expr *e;
8128 mpz_t size;
8129 mpz_t offset;
8130 try t;
8131 ar_type mark = AR_UNKNOWN;
8132 int i;
8133 mpz_t section_index[GFC_MAX_DIMENSIONS];
8134 gfc_ref *ref;
8135 gfc_array_ref *ar;
8137 if (gfc_resolve_expr (var->expr) == FAILURE)
8138 return FAILURE;
8140 ar = NULL;
8141 mpz_init_set_si (offset, 0);
8142 e = var->expr;
8144 if (e->expr_type != EXPR_VARIABLE)
8145 gfc_internal_error ("check_data_variable(): Bad expression");
8147 if (e->symtree->n.sym->ns->is_block_data
8148 && !e->symtree->n.sym->attr.in_common)
8150 gfc_error ("BLOCK DATA element '%s' at %L must be in COMMON",
8151 e->symtree->n.sym->name, &e->symtree->n.sym->declared_at);
8154 if (e->ref == NULL && e->symtree->n.sym->as)
8156 gfc_error ("DATA array '%s' at %L must be specified in a previous"
8157 " declaration", e->symtree->n.sym->name, where);
8158 return FAILURE;
8161 if (e->rank == 0)
8163 mpz_init_set_ui (size, 1);
8164 ref = NULL;
8166 else
8168 ref = e->ref;
8170 /* Find the array section reference. */
8171 for (ref = e->ref; ref; ref = ref->next)
8173 if (ref->type != REF_ARRAY)
8174 continue;
8175 if (ref->u.ar.type == AR_ELEMENT)
8176 continue;
8177 break;
8179 gcc_assert (ref);
8181 /* Set marks according to the reference pattern. */
8182 switch (ref->u.ar.type)
8184 case AR_FULL:
8185 mark = AR_FULL;
8186 break;
8188 case AR_SECTION:
8189 ar = &ref->u.ar;
8190 /* Get the start position of array section. */
8191 gfc_get_section_index (ar, section_index, &offset);
8192 mark = AR_SECTION;
8193 break;
8195 default:
8196 gcc_unreachable ();
8199 if (gfc_array_size (e, &size) == FAILURE)
8201 gfc_error ("Nonconstant array section at %L in DATA statement",
8202 &e->where);
8203 mpz_clear (offset);
8204 return FAILURE;
8208 t = SUCCESS;
8210 while (mpz_cmp_ui (size, 0) > 0)
8212 if (next_data_value () == FAILURE)
8214 gfc_error ("DATA statement at %L has more variables than values",
8215 where);
8216 t = FAILURE;
8217 break;
8220 t = gfc_check_assign (var->expr, values.vnode->expr, 0);
8221 if (t == FAILURE)
8222 break;
8224 /* If we have more than one element left in the repeat count,
8225 and we have more than one element left in the target variable,
8226 then create a range assignment. */
8227 /* FIXME: Only done for full arrays for now, since array sections
8228 seem tricky. */
8229 if (mark == AR_FULL && ref && ref->next == NULL
8230 && mpz_cmp_ui (values.left, 1) > 0 && mpz_cmp_ui (size, 1) > 0)
8232 mpz_t range;
8234 if (mpz_cmp (size, values.left) >= 0)
8236 mpz_init_set (range, values.left);
8237 mpz_sub (size, size, values.left);
8238 mpz_set_ui (values.left, 0);
8240 else
8242 mpz_init_set (range, size);
8243 mpz_sub (values.left, values.left, size);
8244 mpz_set_ui (size, 0);
8247 gfc_assign_data_value_range (var->expr, values.vnode->expr,
8248 offset, range);
8250 mpz_add (offset, offset, range);
8251 mpz_clear (range);
8254 /* Assign initial value to symbol. */
8255 else
8257 mpz_sub_ui (values.left, values.left, 1);
8258 mpz_sub_ui (size, size, 1);
8260 t = gfc_assign_data_value (var->expr, values.vnode->expr, offset);
8261 if (t == FAILURE)
8262 break;
8264 if (mark == AR_FULL)
8265 mpz_add_ui (offset, offset, 1);
8267 /* Modify the array section indexes and recalculate the offset
8268 for next element. */
8269 else if (mark == AR_SECTION)
8270 gfc_advance_section (section_index, ar, &offset);
8274 if (mark == AR_SECTION)
8276 for (i = 0; i < ar->dimen; i++)
8277 mpz_clear (section_index[i]);
8280 mpz_clear (size);
8281 mpz_clear (offset);
8283 return t;
8287 static try traverse_data_var (gfc_data_variable *, locus *);
8289 /* Iterate over a list of elements in a DATA statement. */
8291 static try
8292 traverse_data_list (gfc_data_variable *var, locus *where)
8294 mpz_t trip;
8295 iterator_stack frame;
8296 gfc_expr *e, *start, *end, *step;
8297 try retval = SUCCESS;
8299 mpz_init (frame.value);
8301 start = gfc_copy_expr (var->iter.start);
8302 end = gfc_copy_expr (var->iter.end);
8303 step = gfc_copy_expr (var->iter.step);
8305 if (gfc_simplify_expr (start, 1) == FAILURE
8306 || start->expr_type != EXPR_CONSTANT)
8308 gfc_error ("iterator start at %L does not simplify", &start->where);
8309 retval = FAILURE;
8310 goto cleanup;
8312 if (gfc_simplify_expr (end, 1) == FAILURE
8313 || end->expr_type != EXPR_CONSTANT)
8315 gfc_error ("iterator end at %L does not simplify", &end->where);
8316 retval = FAILURE;
8317 goto cleanup;
8319 if (gfc_simplify_expr (step, 1) == FAILURE
8320 || step->expr_type != EXPR_CONSTANT)
8322 gfc_error ("iterator step at %L does not simplify", &step->where);
8323 retval = FAILURE;
8324 goto cleanup;
8327 mpz_init_set (trip, end->value.integer);
8328 mpz_sub (trip, trip, start->value.integer);
8329 mpz_add (trip, trip, step->value.integer);
8331 mpz_div (trip, trip, step->value.integer);
8333 mpz_set (frame.value, start->value.integer);
8335 frame.prev = iter_stack;
8336 frame.variable = var->iter.var->symtree;
8337 iter_stack = &frame;
8339 while (mpz_cmp_ui (trip, 0) > 0)
8341 if (traverse_data_var (var->list, where) == FAILURE)
8343 mpz_clear (trip);
8344 retval = FAILURE;
8345 goto cleanup;
8348 e = gfc_copy_expr (var->expr);
8349 if (gfc_simplify_expr (e, 1) == FAILURE)
8351 gfc_free_expr (e);
8352 mpz_clear (trip);
8353 retval = FAILURE;
8354 goto cleanup;
8357 mpz_add (frame.value, frame.value, step->value.integer);
8359 mpz_sub_ui (trip, trip, 1);
8362 mpz_clear (trip);
8363 cleanup:
8364 mpz_clear (frame.value);
8366 gfc_free_expr (start);
8367 gfc_free_expr (end);
8368 gfc_free_expr (step);
8370 iter_stack = frame.prev;
8371 return retval;
8375 /* Type resolve variables in the variable list of a DATA statement. */
8377 static try
8378 traverse_data_var (gfc_data_variable *var, locus *where)
8380 try t;
8382 for (; var; var = var->next)
8384 if (var->expr == NULL)
8385 t = traverse_data_list (var, where);
8386 else
8387 t = check_data_variable (var, where);
8389 if (t == FAILURE)
8390 return FAILURE;
8393 return SUCCESS;
8397 /* Resolve the expressions and iterators associated with a data statement.
8398 This is separate from the assignment checking because data lists should
8399 only be resolved once. */
8401 static try
8402 resolve_data_variables (gfc_data_variable *d)
8404 for (; d; d = d->next)
8406 if (d->list == NULL)
8408 if (gfc_resolve_expr (d->expr) == FAILURE)
8409 return FAILURE;
8411 else
8413 if (gfc_resolve_iterator (&d->iter, false) == FAILURE)
8414 return FAILURE;
8416 if (resolve_data_variables (d->list) == FAILURE)
8417 return FAILURE;
8421 return SUCCESS;
8425 /* Resolve a single DATA statement. We implement this by storing a pointer to
8426 the value list into static variables, and then recursively traversing the
8427 variables list, expanding iterators and such. */
8429 static void
8430 resolve_data (gfc_data *d)
8433 if (resolve_data_variables (d->var) == FAILURE)
8434 return;
8436 values.vnode = d->value;
8437 if (d->value == NULL)
8438 mpz_set_ui (values.left, 0);
8439 else
8440 mpz_set (values.left, d->value->repeat);
8442 if (traverse_data_var (d->var, &d->where) == FAILURE)
8443 return;
8445 /* At this point, we better not have any values left. */
8447 if (next_data_value () == SUCCESS)
8448 gfc_error ("DATA statement at %L has more values than variables",
8449 &d->where);
8453 /* 12.6 Constraint: In a pure subprogram any variable which is in common or
8454 accessed by host or use association, is a dummy argument to a pure function,
8455 is a dummy argument with INTENT (IN) to a pure subroutine, or an object that
8456 is storage associated with any such variable, shall not be used in the
8457 following contexts: (clients of this function). */
8459 /* Determines if a variable is not 'pure', ie not assignable within a pure
8460 procedure. Returns zero if assignment is OK, nonzero if there is a
8461 problem. */
8463 gfc_impure_variable (gfc_symbol *sym)
8465 gfc_symbol *proc;
8467 if (sym->attr.use_assoc || sym->attr.in_common)
8468 return 1;
8470 if (sym->ns != gfc_current_ns)
8471 return !sym->attr.function;
8473 proc = sym->ns->proc_name;
8474 if (sym->attr.dummy && gfc_pure (proc)
8475 && ((proc->attr.subroutine && sym->attr.intent == INTENT_IN)
8477 proc->attr.function))
8478 return 1;
8480 /* TODO: Sort out what can be storage associated, if anything, and include
8481 it here. In principle equivalences should be scanned but it does not
8482 seem to be possible to storage associate an impure variable this way. */
8483 return 0;
8487 /* Test whether a symbol is pure or not. For a NULL pointer, checks the
8488 symbol of the current procedure. */
8491 gfc_pure (gfc_symbol *sym)
8493 symbol_attribute attr;
8495 if (sym == NULL)
8496 sym = gfc_current_ns->proc_name;
8497 if (sym == NULL)
8498 return 0;
8500 attr = sym->attr;
8502 return attr.flavor == FL_PROCEDURE && (attr.pure || attr.elemental);
8506 /* Test whether the current procedure is elemental or not. */
8509 gfc_elemental (gfc_symbol *sym)
8511 symbol_attribute attr;
8513 if (sym == NULL)
8514 sym = gfc_current_ns->proc_name;
8515 if (sym == NULL)
8516 return 0;
8517 attr = sym->attr;
8519 return attr.flavor == FL_PROCEDURE && attr.elemental;
8523 /* Warn about unused labels. */
8525 static void
8526 warn_unused_fortran_label (gfc_st_label *label)
8528 if (label == NULL)
8529 return;
8531 warn_unused_fortran_label (label->left);
8533 if (label->defined == ST_LABEL_UNKNOWN)
8534 return;
8536 switch (label->referenced)
8538 case ST_LABEL_UNKNOWN:
8539 gfc_warning ("Label %d at %L defined but not used", label->value,
8540 &label->where);
8541 break;
8543 case ST_LABEL_BAD_TARGET:
8544 gfc_warning ("Label %d at %L defined but cannot be used",
8545 label->value, &label->where);
8546 break;
8548 default:
8549 break;
8552 warn_unused_fortran_label (label->right);
8556 /* Returns the sequence type of a symbol or sequence. */
8558 static seq_type
8559 sequence_type (gfc_typespec ts)
8561 seq_type result;
8562 gfc_component *c;
8564 switch (ts.type)
8566 case BT_DERIVED:
8568 if (ts.derived->components == NULL)
8569 return SEQ_NONDEFAULT;
8571 result = sequence_type (ts.derived->components->ts);
8572 for (c = ts.derived->components->next; c; c = c->next)
8573 if (sequence_type (c->ts) != result)
8574 return SEQ_MIXED;
8576 return result;
8578 case BT_CHARACTER:
8579 if (ts.kind != gfc_default_character_kind)
8580 return SEQ_NONDEFAULT;
8582 return SEQ_CHARACTER;
8584 case BT_INTEGER:
8585 if (ts.kind != gfc_default_integer_kind)
8586 return SEQ_NONDEFAULT;
8588 return SEQ_NUMERIC;
8590 case BT_REAL:
8591 if (!(ts.kind == gfc_default_real_kind
8592 || ts.kind == gfc_default_double_kind))
8593 return SEQ_NONDEFAULT;
8595 return SEQ_NUMERIC;
8597 case BT_COMPLEX:
8598 if (ts.kind != gfc_default_complex_kind)
8599 return SEQ_NONDEFAULT;
8601 return SEQ_NUMERIC;
8603 case BT_LOGICAL:
8604 if (ts.kind != gfc_default_logical_kind)
8605 return SEQ_NONDEFAULT;
8607 return SEQ_NUMERIC;
8609 default:
8610 return SEQ_NONDEFAULT;
8615 /* Resolve derived type EQUIVALENCE object. */
8617 static try
8618 resolve_equivalence_derived (gfc_symbol *derived, gfc_symbol *sym, gfc_expr *e)
8620 gfc_symbol *d;
8621 gfc_component *c = derived->components;
8623 if (!derived)
8624 return SUCCESS;
8626 /* Shall not be an object of nonsequence derived type. */
8627 if (!derived->attr.sequence)
8629 gfc_error ("Derived type variable '%s' at %L must have SEQUENCE "
8630 "attribute to be an EQUIVALENCE object", sym->name,
8631 &e->where);
8632 return FAILURE;
8635 /* Shall not have allocatable components. */
8636 if (derived->attr.alloc_comp)
8638 gfc_error ("Derived type variable '%s' at %L cannot have ALLOCATABLE "
8639 "components to be an EQUIVALENCE object",sym->name,
8640 &e->where);
8641 return FAILURE;
8644 if (sym->attr.in_common && has_default_initializer (sym->ts.derived))
8646 gfc_error ("Derived type variable '%s' at %L with default "
8647 "initialization cannot be in EQUIVALENCE with a variable "
8648 "in COMMON", sym->name, &e->where);
8649 return FAILURE;
8652 for (; c ; c = c->next)
8654 d = c->ts.derived;
8655 if (d
8656 && (resolve_equivalence_derived (c->ts.derived, sym, e) == FAILURE))
8657 return FAILURE;
8659 /* Shall not be an object of sequence derived type containing a pointer
8660 in the structure. */
8661 if (c->pointer)
8663 gfc_error ("Derived type variable '%s' at %L with pointer "
8664 "component(s) cannot be an EQUIVALENCE object",
8665 sym->name, &e->where);
8666 return FAILURE;
8669 return SUCCESS;
8673 /* Resolve equivalence object.
8674 An EQUIVALENCE object shall not be a dummy argument, a pointer, a target,
8675 an allocatable array, an object of nonsequence derived type, an object of
8676 sequence derived type containing a pointer at any level of component
8677 selection, an automatic object, a function name, an entry name, a result
8678 name, a named constant, a structure component, or a subobject of any of
8679 the preceding objects. A substring shall not have length zero. A
8680 derived type shall not have components with default initialization nor
8681 shall two objects of an equivalence group be initialized.
8682 Either all or none of the objects shall have an protected attribute.
8683 The simple constraints are done in symbol.c(check_conflict) and the rest
8684 are implemented here. */
8686 static void
8687 resolve_equivalence (gfc_equiv *eq)
8689 gfc_symbol *sym;
8690 gfc_symbol *derived;
8691 gfc_symbol *first_sym;
8692 gfc_expr *e;
8693 gfc_ref *r;
8694 locus *last_where = NULL;
8695 seq_type eq_type, last_eq_type;
8696 gfc_typespec *last_ts;
8697 int object, cnt_protected;
8698 const char *value_name;
8699 const char *msg;
8701 value_name = NULL;
8702 last_ts = &eq->expr->symtree->n.sym->ts;
8704 first_sym = eq->expr->symtree->n.sym;
8706 cnt_protected = 0;
8708 for (object = 1; eq; eq = eq->eq, object++)
8710 e = eq->expr;
8712 e->ts = e->symtree->n.sym->ts;
8713 /* match_varspec might not know yet if it is seeing
8714 array reference or substring reference, as it doesn't
8715 know the types. */
8716 if (e->ref && e->ref->type == REF_ARRAY)
8718 gfc_ref *ref = e->ref;
8719 sym = e->symtree->n.sym;
8721 if (sym->attr.dimension)
8723 ref->u.ar.as = sym->as;
8724 ref = ref->next;
8727 /* For substrings, convert REF_ARRAY into REF_SUBSTRING. */
8728 if (e->ts.type == BT_CHARACTER
8729 && ref
8730 && ref->type == REF_ARRAY
8731 && ref->u.ar.dimen == 1
8732 && ref->u.ar.dimen_type[0] == DIMEN_RANGE
8733 && ref->u.ar.stride[0] == NULL)
8735 gfc_expr *start = ref->u.ar.start[0];
8736 gfc_expr *end = ref->u.ar.end[0];
8737 void *mem = NULL;
8739 /* Optimize away the (:) reference. */
8740 if (start == NULL && end == NULL)
8742 if (e->ref == ref)
8743 e->ref = ref->next;
8744 else
8745 e->ref->next = ref->next;
8746 mem = ref;
8748 else
8750 ref->type = REF_SUBSTRING;
8751 if (start == NULL)
8752 start = gfc_int_expr (1);
8753 ref->u.ss.start = start;
8754 if (end == NULL && e->ts.cl)
8755 end = gfc_copy_expr (e->ts.cl->length);
8756 ref->u.ss.end = end;
8757 ref->u.ss.length = e->ts.cl;
8758 e->ts.cl = NULL;
8760 ref = ref->next;
8761 gfc_free (mem);
8764 /* Any further ref is an error. */
8765 if (ref)
8767 gcc_assert (ref->type == REF_ARRAY);
8768 gfc_error ("Syntax error in EQUIVALENCE statement at %L",
8769 &ref->u.ar.where);
8770 continue;
8774 if (gfc_resolve_expr (e) == FAILURE)
8775 continue;
8777 sym = e->symtree->n.sym;
8779 if (sym->attr.protected)
8780 cnt_protected++;
8781 if (cnt_protected > 0 && cnt_protected != object)
8783 gfc_error ("Either all or none of the objects in the "
8784 "EQUIVALENCE set at %L shall have the "
8785 "PROTECTED attribute",
8786 &e->where);
8787 break;
8790 /* Shall not equivalence common block variables in a PURE procedure. */
8791 if (sym->ns->proc_name
8792 && sym->ns->proc_name->attr.pure
8793 && sym->attr.in_common)
8795 gfc_error ("Common block member '%s' at %L cannot be an EQUIVALENCE "
8796 "object in the pure procedure '%s'",
8797 sym->name, &e->where, sym->ns->proc_name->name);
8798 break;
8801 /* Shall not be a named constant. */
8802 if (e->expr_type == EXPR_CONSTANT)
8804 gfc_error ("Named constant '%s' at %L cannot be an EQUIVALENCE "
8805 "object", sym->name, &e->where);
8806 continue;
8809 derived = e->ts.derived;
8810 if (derived && resolve_equivalence_derived (derived, sym, e) == FAILURE)
8811 continue;
8813 /* Check that the types correspond correctly:
8814 Note 5.28:
8815 A numeric sequence structure may be equivalenced to another sequence
8816 structure, an object of default integer type, default real type, double
8817 precision real type, default logical type such that components of the
8818 structure ultimately only become associated to objects of the same
8819 kind. A character sequence structure may be equivalenced to an object
8820 of default character kind or another character sequence structure.
8821 Other objects may be equivalenced only to objects of the same type and
8822 kind parameters. */
8824 /* Identical types are unconditionally OK. */
8825 if (object == 1 || gfc_compare_types (last_ts, &sym->ts))
8826 goto identical_types;
8828 last_eq_type = sequence_type (*last_ts);
8829 eq_type = sequence_type (sym->ts);
8831 /* Since the pair of objects is not of the same type, mixed or
8832 non-default sequences can be rejected. */
8834 msg = "Sequence %s with mixed components in EQUIVALENCE "
8835 "statement at %L with different type objects";
8836 if ((object ==2
8837 && last_eq_type == SEQ_MIXED
8838 && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name, last_where)
8839 == FAILURE)
8840 || (eq_type == SEQ_MIXED
8841 && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
8842 &e->where) == FAILURE))
8843 continue;
8845 msg = "Non-default type object or sequence %s in EQUIVALENCE "
8846 "statement at %L with objects of different type";
8847 if ((object ==2
8848 && last_eq_type == SEQ_NONDEFAULT
8849 && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name,
8850 last_where) == FAILURE)
8851 || (eq_type == SEQ_NONDEFAULT
8852 && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
8853 &e->where) == FAILURE))
8854 continue;
8856 msg ="Non-CHARACTER object '%s' in default CHARACTER "
8857 "EQUIVALENCE statement at %L";
8858 if (last_eq_type == SEQ_CHARACTER
8859 && eq_type != SEQ_CHARACTER
8860 && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
8861 &e->where) == FAILURE)
8862 continue;
8864 msg ="Non-NUMERIC object '%s' in default NUMERIC "
8865 "EQUIVALENCE statement at %L";
8866 if (last_eq_type == SEQ_NUMERIC
8867 && eq_type != SEQ_NUMERIC
8868 && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
8869 &e->where) == FAILURE)
8870 continue;
8872 identical_types:
8873 last_ts =&sym->ts;
8874 last_where = &e->where;
8876 if (!e->ref)
8877 continue;
8879 /* Shall not be an automatic array. */
8880 if (e->ref->type == REF_ARRAY
8881 && gfc_resolve_array_spec (e->ref->u.ar.as, 1) == FAILURE)
8883 gfc_error ("Array '%s' at %L with non-constant bounds cannot be "
8884 "an EQUIVALENCE object", sym->name, &e->where);
8885 continue;
8888 r = e->ref;
8889 while (r)
8891 /* Shall not be a structure component. */
8892 if (r->type == REF_COMPONENT)
8894 gfc_error ("Structure component '%s' at %L cannot be an "
8895 "EQUIVALENCE object",
8896 r->u.c.component->name, &e->where);
8897 break;
8900 /* A substring shall not have length zero. */
8901 if (r->type == REF_SUBSTRING)
8903 if (compare_bound (r->u.ss.start, r->u.ss.end) == CMP_GT)
8905 gfc_error ("Substring at %L has length zero",
8906 &r->u.ss.start->where);
8907 break;
8910 r = r->next;
8916 /* Resolve function and ENTRY types, issue diagnostics if needed. */
8918 static void
8919 resolve_fntype (gfc_namespace *ns)
8921 gfc_entry_list *el;
8922 gfc_symbol *sym;
8924 if (ns->proc_name == NULL || !ns->proc_name->attr.function)
8925 return;
8927 /* If there are any entries, ns->proc_name is the entry master
8928 synthetic symbol and ns->entries->sym actual FUNCTION symbol. */
8929 if (ns->entries)
8930 sym = ns->entries->sym;
8931 else
8932 sym = ns->proc_name;
8933 if (sym->result == sym
8934 && sym->ts.type == BT_UNKNOWN
8935 && gfc_set_default_type (sym, 0, NULL) == FAILURE
8936 && !sym->attr.untyped)
8938 gfc_error ("Function '%s' at %L has no IMPLICIT type",
8939 sym->name, &sym->declared_at);
8940 sym->attr.untyped = 1;
8943 if (sym->ts.type == BT_DERIVED && !sym->ts.derived->attr.use_assoc
8944 && !gfc_check_access (sym->ts.derived->attr.access,
8945 sym->ts.derived->ns->default_access)
8946 && gfc_check_access (sym->attr.access, sym->ns->default_access))
8948 gfc_error ("PUBLIC function '%s' at %L cannot be of PRIVATE type '%s'",
8949 sym->name, &sym->declared_at, sym->ts.derived->name);
8952 if (ns->entries)
8953 for (el = ns->entries->next; el; el = el->next)
8955 if (el->sym->result == el->sym
8956 && el->sym->ts.type == BT_UNKNOWN
8957 && gfc_set_default_type (el->sym, 0, NULL) == FAILURE
8958 && !el->sym->attr.untyped)
8960 gfc_error ("ENTRY '%s' at %L has no IMPLICIT type",
8961 el->sym->name, &el->sym->declared_at);
8962 el->sym->attr.untyped = 1;
8967 /* 12.3.2.1.1 Defined operators. */
8969 static void
8970 gfc_resolve_uops (gfc_symtree *symtree)
8972 gfc_interface *itr;
8973 gfc_symbol *sym;
8974 gfc_formal_arglist *formal;
8976 if (symtree == NULL)
8977 return;
8979 gfc_resolve_uops (symtree->left);
8980 gfc_resolve_uops (symtree->right);
8982 for (itr = symtree->n.uop->operator; itr; itr = itr->next)
8984 sym = itr->sym;
8985 if (!sym->attr.function)
8986 gfc_error ("User operator procedure '%s' at %L must be a FUNCTION",
8987 sym->name, &sym->declared_at);
8989 if (sym->ts.type == BT_CHARACTER
8990 && !(sym->ts.cl && sym->ts.cl->length)
8991 && !(sym->result && sym->result->ts.cl
8992 && sym->result->ts.cl->length))
8993 gfc_error ("User operator procedure '%s' at %L cannot be assumed "
8994 "character length", sym->name, &sym->declared_at);
8996 formal = sym->formal;
8997 if (!formal || !formal->sym)
8999 gfc_error ("User operator procedure '%s' at %L must have at least "
9000 "one argument", sym->name, &sym->declared_at);
9001 continue;
9004 if (formal->sym->attr.intent != INTENT_IN)
9005 gfc_error ("First argument of operator interface at %L must be "
9006 "INTENT(IN)", &sym->declared_at);
9008 if (formal->sym->attr.optional)
9009 gfc_error ("First argument of operator interface at %L cannot be "
9010 "optional", &sym->declared_at);
9012 formal = formal->next;
9013 if (!formal || !formal->sym)
9014 continue;
9016 if (formal->sym->attr.intent != INTENT_IN)
9017 gfc_error ("Second argument of operator interface at %L must be "
9018 "INTENT(IN)", &sym->declared_at);
9020 if (formal->sym->attr.optional)
9021 gfc_error ("Second argument of operator interface at %L cannot be "
9022 "optional", &sym->declared_at);
9024 if (formal->next)
9025 gfc_error ("Operator interface at %L must have, at most, two "
9026 "arguments", &sym->declared_at);
9031 /* Examine all of the expressions associated with a program unit,
9032 assign types to all intermediate expressions, make sure that all
9033 assignments are to compatible types and figure out which names
9034 refer to which functions or subroutines. It doesn't check code
9035 block, which is handled by resolve_code. */
9037 static void
9038 resolve_types (gfc_namespace *ns)
9040 gfc_namespace *n;
9041 gfc_charlen *cl;
9042 gfc_data *d;
9043 gfc_equiv *eq;
9045 gfc_current_ns = ns;
9047 resolve_entries (ns);
9049 resolve_common_vars (ns->blank_common.head, false);
9050 resolve_common_blocks (ns->common_root);
9052 resolve_contained_functions (ns);
9054 gfc_traverse_ns (ns, resolve_bind_c_derived_types);
9056 for (cl = ns->cl_list; cl; cl = cl->next)
9057 resolve_charlen (cl);
9059 gfc_traverse_ns (ns, resolve_symbol);
9061 resolve_fntype (ns);
9063 for (n = ns->contained; n; n = n->sibling)
9065 if (gfc_pure (ns->proc_name) && !gfc_pure (n->proc_name))
9066 gfc_error ("Contained procedure '%s' at %L of a PURE procedure must "
9067 "also be PURE", n->proc_name->name,
9068 &n->proc_name->declared_at);
9070 resolve_types (n);
9073 forall_flag = 0;
9074 gfc_check_interfaces (ns);
9076 gfc_traverse_ns (ns, resolve_values);
9078 if (ns->save_all)
9079 gfc_save_all (ns);
9081 iter_stack = NULL;
9082 for (d = ns->data; d; d = d->next)
9083 resolve_data (d);
9085 iter_stack = NULL;
9086 gfc_traverse_ns (ns, gfc_formalize_init_value);
9088 gfc_traverse_ns (ns, gfc_verify_binding_labels);
9090 if (ns->common_root != NULL)
9091 gfc_traverse_symtree (ns->common_root, resolve_bind_c_comms);
9093 for (eq = ns->equiv; eq; eq = eq->next)
9094 resolve_equivalence (eq);
9096 /* Warn about unused labels. */
9097 if (warn_unused_label)
9098 warn_unused_fortran_label (ns->st_labels);
9100 gfc_resolve_uops (ns->uop_root);
9104 /* Call resolve_code recursively. */
9106 static void
9107 resolve_codes (gfc_namespace *ns)
9109 gfc_namespace *n;
9111 for (n = ns->contained; n; n = n->sibling)
9112 resolve_codes (n);
9114 gfc_current_ns = ns;
9115 cs_base = NULL;
9116 /* Set to an out of range value. */
9117 current_entry_id = -1;
9119 bitmap_obstack_initialize (&labels_obstack);
9120 resolve_code (ns->code, ns);
9121 bitmap_obstack_release (&labels_obstack);
9125 /* This function is called after a complete program unit has been compiled.
9126 Its purpose is to examine all of the expressions associated with a program
9127 unit, assign types to all intermediate expressions, make sure that all
9128 assignments are to compatible types and figure out which names refer to
9129 which functions or subroutines. */
9131 void
9132 gfc_resolve (gfc_namespace *ns)
9134 gfc_namespace *old_ns;
9136 old_ns = gfc_current_ns;
9138 resolve_types (ns);
9139 resolve_codes (ns);
9141 gfc_current_ns = old_ns;