1 /* Perform type resolution on the various structures.
2 Copyright (C) 2001, 2002, 2003, 2004, 2005, 2006, 2007, 2008, 2009, 2010
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
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
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/>. */
28 #include "arith.h" /* For gfc_compare_expr(). */
29 #include "dependency.h"
31 #include "target-memory.h" /* for gfc_simplify_transfer */
32 #include "constructor.h"
34 /* Types used in equivalence statements. */
38 SEQ_NONDEFAULT, SEQ_NUMERIC, SEQ_CHARACTER, SEQ_MIXED
42 /* Stack to keep track of the nesting of blocks as we move through the
43 code. See resolve_branch() and resolve_code(). */
45 typedef struct code_stack
47 struct gfc_code *head, *current;
48 struct code_stack *prev;
50 /* This bitmap keeps track of the targets valid for a branch from
51 inside this block except for END {IF|SELECT}s of enclosing
53 bitmap reachable_labels;
57 static code_stack *cs_base = NULL;
60 /* Nonzero if we're inside a FORALL block. */
62 static int forall_flag;
64 /* Nonzero if we're inside a OpenMP WORKSHARE or PARALLEL WORKSHARE block. */
66 static int omp_workshare_flag;
68 /* Nonzero if we are processing a formal arglist. The corresponding function
69 resets the flag each time that it is read. */
70 static int formal_arg_flag = 0;
72 /* True if we are resolving a specification expression. */
73 static int specification_expr = 0;
75 /* The id of the last entry seen. */
76 static int current_entry_id;
78 /* We use bitmaps to determine if a branch target is valid. */
79 static bitmap_obstack labels_obstack;
81 /* True when simplifying a EXPR_VARIABLE argument to an inquiry function. */
82 static bool inquiry_argument = false;
85 gfc_is_formal_arg (void)
87 return formal_arg_flag;
90 /* Is the symbol host associated? */
92 is_sym_host_assoc (gfc_symbol *sym, gfc_namespace *ns)
94 for (ns = ns->parent; ns; ns = ns->parent)
103 /* Ensure a typespec used is valid; for instance, TYPE(t) is invalid if t is
104 an ABSTRACT derived-type. If where is not NULL, an error message with that
105 locus is printed, optionally using name. */
108 resolve_typespec_used (gfc_typespec* ts, locus* where, const char* name)
110 if (ts->type == BT_DERIVED && ts->u.derived->attr.abstract)
115 gfc_error ("'%s' at %L is of the ABSTRACT type '%s'",
116 name, where, ts->u.derived->name);
118 gfc_error ("ABSTRACT type '%s' used at %L",
119 ts->u.derived->name, where);
129 /* Resolve types of formal argument lists. These have to be done early so that
130 the formal argument lists of module procedures can be copied to the
131 containing module before the individual procedures are resolved
132 individually. We also resolve argument lists of procedures in interface
133 blocks because they are self-contained scoping units.
135 Since a dummy argument cannot be a non-dummy procedure, the only
136 resort left for untyped names are the IMPLICIT types. */
139 resolve_formal_arglist (gfc_symbol *proc)
141 gfc_formal_arglist *f;
145 if (proc->result != NULL)
150 if (gfc_elemental (proc)
151 || sym->attr.pointer || sym->attr.allocatable
152 || (sym->as && sym->as->rank > 0))
154 proc->attr.always_explicit = 1;
155 sym->attr.always_explicit = 1;
160 for (f = proc->formal; f; f = f->next)
166 /* Alternate return placeholder. */
167 if (gfc_elemental (proc))
168 gfc_error ("Alternate return specifier in elemental subroutine "
169 "'%s' at %L is not allowed", proc->name,
171 if (proc->attr.function)
172 gfc_error ("Alternate return specifier in function "
173 "'%s' at %L is not allowed", proc->name,
178 if (sym->attr.if_source != IFSRC_UNKNOWN)
179 resolve_formal_arglist (sym);
181 if (sym->attr.subroutine || sym->attr.external || sym->attr.intrinsic)
183 if (gfc_pure (proc) && !gfc_pure (sym))
185 gfc_error ("Dummy procedure '%s' of PURE procedure at %L must "
186 "also be PURE", sym->name, &sym->declared_at);
190 if (gfc_elemental (proc))
192 gfc_error ("Dummy procedure at %L not allowed in ELEMENTAL "
193 "procedure", &sym->declared_at);
197 if (sym->attr.function
198 && sym->ts.type == BT_UNKNOWN
199 && sym->attr.intrinsic)
201 gfc_intrinsic_sym *isym;
202 isym = gfc_find_function (sym->name);
203 if (isym == NULL || !isym->specific)
205 gfc_error ("Unable to find a specific INTRINSIC procedure "
206 "for the reference '%s' at %L", sym->name,
215 if (sym->ts.type == BT_UNKNOWN)
217 if (!sym->attr.function || sym->result == sym)
218 gfc_set_default_type (sym, 1, sym->ns);
221 gfc_resolve_array_spec (sym->as, 0);
223 /* We can't tell if an array with dimension (:) is assumed or deferred
224 shape until we know if it has the pointer or allocatable attributes.
226 if (sym->as && sym->as->rank > 0 && sym->as->type == AS_DEFERRED
227 && !(sym->attr.pointer || sym->attr.allocatable))
229 sym->as->type = AS_ASSUMED_SHAPE;
230 for (i = 0; i < sym->as->rank; i++)
231 sym->as->lower[i] = gfc_get_int_expr (gfc_default_integer_kind,
235 if ((sym->as && sym->as->rank > 0 && sym->as->type == AS_ASSUMED_SHAPE)
236 || sym->attr.pointer || sym->attr.allocatable || sym->attr.target
237 || sym->attr.optional)
239 proc->attr.always_explicit = 1;
241 proc->result->attr.always_explicit = 1;
244 /* If the flavor is unknown at this point, it has to be a variable.
245 A procedure specification would have already set the type. */
247 if (sym->attr.flavor == FL_UNKNOWN)
248 gfc_add_flavor (&sym->attr, FL_VARIABLE, sym->name, &sym->declared_at);
250 if (gfc_pure (proc) && !sym->attr.pointer
251 && sym->attr.flavor != FL_PROCEDURE)
253 if (proc->attr.function && sym->attr.intent != INTENT_IN)
254 gfc_error ("Argument '%s' of pure function '%s' at %L must be "
255 "INTENT(IN)", sym->name, proc->name,
258 if (proc->attr.subroutine && sym->attr.intent == INTENT_UNKNOWN)
259 gfc_error ("Argument '%s' of pure subroutine '%s' at %L must "
260 "have its INTENT specified", sym->name, proc->name,
264 if (gfc_elemental (proc))
267 if (sym->attr.codimension)
269 gfc_error ("Coarray dummy argument '%s' at %L to elemental "
270 "procedure", sym->name, &sym->declared_at);
276 gfc_error ("Argument '%s' of elemental procedure at %L must "
277 "be scalar", sym->name, &sym->declared_at);
281 if (sym->attr.pointer)
283 gfc_error ("Argument '%s' of elemental procedure at %L cannot "
284 "have the POINTER attribute", sym->name,
289 if (sym->attr.flavor == FL_PROCEDURE)
291 gfc_error ("Dummy procedure '%s' not allowed in elemental "
292 "procedure '%s' at %L", sym->name, proc->name,
298 /* Each dummy shall be specified to be scalar. */
299 if (proc->attr.proc == PROC_ST_FUNCTION)
303 gfc_error ("Argument '%s' of statement function at %L must "
304 "be scalar", sym->name, &sym->declared_at);
308 if (sym->ts.type == BT_CHARACTER)
310 gfc_charlen *cl = sym->ts.u.cl;
311 if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
313 gfc_error ("Character-valued argument '%s' of statement "
314 "function at %L must have constant length",
315 sym->name, &sym->declared_at);
325 /* Work function called when searching for symbols that have argument lists
326 associated with them. */
329 find_arglists (gfc_symbol *sym)
331 if (sym->attr.if_source == IFSRC_UNKNOWN || sym->ns != gfc_current_ns)
334 resolve_formal_arglist (sym);
338 /* Given a namespace, resolve all formal argument lists within the namespace.
342 resolve_formal_arglists (gfc_namespace *ns)
347 gfc_traverse_ns (ns, find_arglists);
352 resolve_contained_fntype (gfc_symbol *sym, gfc_namespace *ns)
356 /* If this namespace is not a function or an entry master function,
358 if (! sym || !(sym->attr.function || sym->attr.flavor == FL_VARIABLE)
359 || sym->attr.entry_master)
362 /* Try to find out of what the return type is. */
363 if (sym->result->ts.type == BT_UNKNOWN && sym->result->ts.interface == NULL)
365 t = gfc_set_default_type (sym->result, 0, ns);
367 if (t == FAILURE && !sym->result->attr.untyped)
369 if (sym->result == sym)
370 gfc_error ("Contained function '%s' at %L has no IMPLICIT type",
371 sym->name, &sym->declared_at);
372 else if (!sym->result->attr.proc_pointer)
373 gfc_error ("Result '%s' of contained function '%s' at %L has "
374 "no IMPLICIT type", sym->result->name, sym->name,
375 &sym->result->declared_at);
376 sym->result->attr.untyped = 1;
380 /* Fortran 95 Draft Standard, page 51, Section 5.1.1.5, on the Character
381 type, lists the only ways a character length value of * can be used:
382 dummy arguments of procedures, named constants, and function results
383 in external functions. Internal function results and results of module
384 procedures are not on this list, ergo, not permitted. */
386 if (sym->result->ts.type == BT_CHARACTER)
388 gfc_charlen *cl = sym->result->ts.u.cl;
389 if (!cl || !cl->length)
391 /* See if this is a module-procedure and adapt error message
394 gcc_assert (ns->parent && ns->parent->proc_name);
395 module_proc = (ns->parent->proc_name->attr.flavor == FL_MODULE);
397 gfc_error ("Character-valued %s '%s' at %L must not be"
399 module_proc ? _("module procedure")
400 : _("internal function"),
401 sym->name, &sym->declared_at);
407 /* Add NEW_ARGS to the formal argument list of PROC, taking care not to
408 introduce duplicates. */
411 merge_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
413 gfc_formal_arglist *f, *new_arglist;
416 for (; new_args != NULL; new_args = new_args->next)
418 new_sym = new_args->sym;
419 /* See if this arg is already in the formal argument list. */
420 for (f = proc->formal; f; f = f->next)
422 if (new_sym == f->sym)
429 /* Add a new argument. Argument order is not important. */
430 new_arglist = gfc_get_formal_arglist ();
431 new_arglist->sym = new_sym;
432 new_arglist->next = proc->formal;
433 proc->formal = new_arglist;
438 /* Flag the arguments that are not present in all entries. */
441 check_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
443 gfc_formal_arglist *f, *head;
446 for (f = proc->formal; f; f = f->next)
451 for (new_args = head; new_args; new_args = new_args->next)
453 if (new_args->sym == f->sym)
460 f->sym->attr.not_always_present = 1;
465 /* Resolve alternate entry points. If a symbol has multiple entry points we
466 create a new master symbol for the main routine, and turn the existing
467 symbol into an entry point. */
470 resolve_entries (gfc_namespace *ns)
472 gfc_namespace *old_ns;
476 char name[GFC_MAX_SYMBOL_LEN + 1];
477 static int master_count = 0;
479 if (ns->proc_name == NULL)
482 /* No need to do anything if this procedure doesn't have alternate entry
487 /* We may already have resolved alternate entry points. */
488 if (ns->proc_name->attr.entry_master)
491 /* If this isn't a procedure something has gone horribly wrong. */
492 gcc_assert (ns->proc_name->attr.flavor == FL_PROCEDURE);
494 /* Remember the current namespace. */
495 old_ns = gfc_current_ns;
499 /* Add the main entry point to the list of entry points. */
500 el = gfc_get_entry_list ();
501 el->sym = ns->proc_name;
503 el->next = ns->entries;
505 ns->proc_name->attr.entry = 1;
507 /* If it is a module function, it needs to be in the right namespace
508 so that gfc_get_fake_result_decl can gather up the results. The
509 need for this arose in get_proc_name, where these beasts were
510 left in their own namespace, to keep prior references linked to
511 the entry declaration.*/
512 if (ns->proc_name->attr.function
513 && ns->parent && ns->parent->proc_name->attr.flavor == FL_MODULE)
516 /* Do the same for entries where the master is not a module
517 procedure. These are retained in the module namespace because
518 of the module procedure declaration. */
519 for (el = el->next; el; el = el->next)
520 if (el->sym->ns->proc_name->attr.flavor == FL_MODULE
521 && el->sym->attr.mod_proc)
525 /* Add an entry statement for it. */
532 /* Create a new symbol for the master function. */
533 /* Give the internal function a unique name (within this file).
534 Also include the function name so the user has some hope of figuring
535 out what is going on. */
536 snprintf (name, GFC_MAX_SYMBOL_LEN, "master.%d.%s",
537 master_count++, ns->proc_name->name);
538 gfc_get_ha_symbol (name, &proc);
539 gcc_assert (proc != NULL);
541 gfc_add_procedure (&proc->attr, PROC_INTERNAL, proc->name, NULL);
542 if (ns->proc_name->attr.subroutine)
543 gfc_add_subroutine (&proc->attr, proc->name, NULL);
547 gfc_typespec *ts, *fts;
548 gfc_array_spec *as, *fas;
549 gfc_add_function (&proc->attr, proc->name, NULL);
551 fas = ns->entries->sym->as;
552 fas = fas ? fas : ns->entries->sym->result->as;
553 fts = &ns->entries->sym->result->ts;
554 if (fts->type == BT_UNKNOWN)
555 fts = gfc_get_default_type (ns->entries->sym->result->name, NULL);
556 for (el = ns->entries->next; el; el = el->next)
558 ts = &el->sym->result->ts;
560 as = as ? as : el->sym->result->as;
561 if (ts->type == BT_UNKNOWN)
562 ts = gfc_get_default_type (el->sym->result->name, NULL);
564 if (! gfc_compare_types (ts, fts)
565 || (el->sym->result->attr.dimension
566 != ns->entries->sym->result->attr.dimension)
567 || (el->sym->result->attr.pointer
568 != ns->entries->sym->result->attr.pointer))
570 else if (as && fas && ns->entries->sym->result != el->sym->result
571 && gfc_compare_array_spec (as, fas) == 0)
572 gfc_error ("Function %s at %L has entries with mismatched "
573 "array specifications", ns->entries->sym->name,
574 &ns->entries->sym->declared_at);
575 /* The characteristics need to match and thus both need to have
576 the same string length, i.e. both len=*, or both len=4.
577 Having both len=<variable> is also possible, but difficult to
578 check at compile time. */
579 else if (ts->type == BT_CHARACTER && ts->u.cl && fts->u.cl
580 && (((ts->u.cl->length && !fts->u.cl->length)
581 ||(!ts->u.cl->length && fts->u.cl->length))
583 && ts->u.cl->length->expr_type
584 != fts->u.cl->length->expr_type)
586 && ts->u.cl->length->expr_type == EXPR_CONSTANT
587 && mpz_cmp (ts->u.cl->length->value.integer,
588 fts->u.cl->length->value.integer) != 0)))
589 gfc_notify_std (GFC_STD_GNU, "Extension: Function %s at %L with "
590 "entries returning variables of different "
591 "string lengths", ns->entries->sym->name,
592 &ns->entries->sym->declared_at);
597 sym = ns->entries->sym->result;
598 /* All result types the same. */
600 if (sym->attr.dimension)
601 gfc_set_array_spec (proc, gfc_copy_array_spec (sym->as), NULL);
602 if (sym->attr.pointer)
603 gfc_add_pointer (&proc->attr, NULL);
607 /* Otherwise the result will be passed through a union by
609 proc->attr.mixed_entry_master = 1;
610 for (el = ns->entries; el; el = el->next)
612 sym = el->sym->result;
613 if (sym->attr.dimension)
615 if (el == ns->entries)
616 gfc_error ("FUNCTION result %s can't be an array in "
617 "FUNCTION %s at %L", sym->name,
618 ns->entries->sym->name, &sym->declared_at);
620 gfc_error ("ENTRY result %s can't be an array in "
621 "FUNCTION %s at %L", sym->name,
622 ns->entries->sym->name, &sym->declared_at);
624 else if (sym->attr.pointer)
626 if (el == ns->entries)
627 gfc_error ("FUNCTION result %s can't be a POINTER in "
628 "FUNCTION %s at %L", sym->name,
629 ns->entries->sym->name, &sym->declared_at);
631 gfc_error ("ENTRY result %s can't be a POINTER in "
632 "FUNCTION %s at %L", sym->name,
633 ns->entries->sym->name, &sym->declared_at);
638 if (ts->type == BT_UNKNOWN)
639 ts = gfc_get_default_type (sym->name, NULL);
643 if (ts->kind == gfc_default_integer_kind)
647 if (ts->kind == gfc_default_real_kind
648 || ts->kind == gfc_default_double_kind)
652 if (ts->kind == gfc_default_complex_kind)
656 if (ts->kind == gfc_default_logical_kind)
660 /* We will issue error elsewhere. */
668 if (el == ns->entries)
669 gfc_error ("FUNCTION result %s can't be of type %s "
670 "in FUNCTION %s at %L", sym->name,
671 gfc_typename (ts), ns->entries->sym->name,
674 gfc_error ("ENTRY result %s can't be of type %s "
675 "in FUNCTION %s at %L", sym->name,
676 gfc_typename (ts), ns->entries->sym->name,
683 proc->attr.access = ACCESS_PRIVATE;
684 proc->attr.entry_master = 1;
686 /* Merge all the entry point arguments. */
687 for (el = ns->entries; el; el = el->next)
688 merge_argument_lists (proc, el->sym->formal);
690 /* Check the master formal arguments for any that are not
691 present in all entry points. */
692 for (el = ns->entries; el; el = el->next)
693 check_argument_lists (proc, el->sym->formal);
695 /* Use the master function for the function body. */
696 ns->proc_name = proc;
698 /* Finalize the new symbols. */
699 gfc_commit_symbols ();
701 /* Restore the original namespace. */
702 gfc_current_ns = old_ns;
706 /* Resolve common variables. */
708 resolve_common_vars (gfc_symbol *sym, bool named_common)
710 gfc_symbol *csym = sym;
712 for (; csym; csym = csym->common_next)
714 if (csym->value || csym->attr.data)
716 if (!csym->ns->is_block_data)
717 gfc_notify_std (GFC_STD_GNU, "Variable '%s' at %L is in COMMON "
718 "but only in BLOCK DATA initialization is "
719 "allowed", csym->name, &csym->declared_at);
720 else if (!named_common)
721 gfc_notify_std (GFC_STD_GNU, "Initialized variable '%s' at %L is "
722 "in a blank COMMON but initialization is only "
723 "allowed in named common blocks", csym->name,
727 if (csym->ts.type != BT_DERIVED)
730 if (!(csym->ts.u.derived->attr.sequence
731 || csym->ts.u.derived->attr.is_bind_c))
732 gfc_error_now ("Derived type variable '%s' in COMMON at %L "
733 "has neither the SEQUENCE nor the BIND(C) "
734 "attribute", csym->name, &csym->declared_at);
735 if (csym->ts.u.derived->attr.alloc_comp)
736 gfc_error_now ("Derived type variable '%s' in COMMON at %L "
737 "has an ultimate component that is "
738 "allocatable", csym->name, &csym->declared_at);
739 if (gfc_has_default_initializer (csym->ts.u.derived))
740 gfc_error_now ("Derived type variable '%s' in COMMON at %L "
741 "may not have default initializer", csym->name,
744 if (csym->attr.flavor == FL_UNKNOWN && !csym->attr.proc_pointer)
745 gfc_add_flavor (&csym->attr, FL_VARIABLE, csym->name, &csym->declared_at);
749 /* Resolve common blocks. */
751 resolve_common_blocks (gfc_symtree *common_root)
755 if (common_root == NULL)
758 if (common_root->left)
759 resolve_common_blocks (common_root->left);
760 if (common_root->right)
761 resolve_common_blocks (common_root->right);
763 resolve_common_vars (common_root->n.common->head, true);
765 gfc_find_symbol (common_root->name, gfc_current_ns, 0, &sym);
769 if (sym->attr.flavor == FL_PARAMETER)
770 gfc_error ("COMMON block '%s' at %L is used as PARAMETER at %L",
771 sym->name, &common_root->n.common->where, &sym->declared_at);
773 if (sym->attr.intrinsic)
774 gfc_error ("COMMON block '%s' at %L is also an intrinsic procedure",
775 sym->name, &common_root->n.common->where);
776 else if (sym->attr.result
777 || gfc_is_function_return_value (sym, gfc_current_ns))
778 gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
779 "that is also a function result", sym->name,
780 &common_root->n.common->where);
781 else if (sym->attr.flavor == FL_PROCEDURE && sym->attr.proc != PROC_INTERNAL
782 && sym->attr.proc != PROC_ST_FUNCTION)
783 gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
784 "that is also a global procedure", sym->name,
785 &common_root->n.common->where);
789 /* Resolve contained function types. Because contained functions can call one
790 another, they have to be worked out before any of the contained procedures
793 The good news is that if a function doesn't already have a type, the only
794 way it can get one is through an IMPLICIT type or a RESULT variable, because
795 by definition contained functions are contained namespace they're contained
796 in, not in a sibling or parent namespace. */
799 resolve_contained_functions (gfc_namespace *ns)
801 gfc_namespace *child;
804 resolve_formal_arglists (ns);
806 for (child = ns->contained; child; child = child->sibling)
808 /* Resolve alternate entry points first. */
809 resolve_entries (child);
811 /* Then check function return types. */
812 resolve_contained_fntype (child->proc_name, child);
813 for (el = child->entries; el; el = el->next)
814 resolve_contained_fntype (el->sym, child);
819 /* Resolve all of the elements of a structure constructor and make sure that
820 the types are correct. */
823 resolve_structure_cons (gfc_expr *expr)
825 gfc_constructor *cons;
831 cons = gfc_constructor_first (expr->value.constructor);
832 /* A constructor may have references if it is the result of substituting a
833 parameter variable. In this case we just pull out the component we
836 comp = expr->ref->u.c.sym->components;
838 comp = expr->ts.u.derived->components;
840 /* See if the user is trying to invoke a structure constructor for one of
841 the iso_c_binding derived types. */
842 if (expr->ts.type == BT_DERIVED && expr->ts.u.derived
843 && expr->ts.u.derived->ts.is_iso_c && cons
844 && (cons->expr == NULL || cons->expr->expr_type != EXPR_NULL))
846 gfc_error ("Components of structure constructor '%s' at %L are PRIVATE",
847 expr->ts.u.derived->name, &(expr->where));
851 /* Return if structure constructor is c_null_(fun)prt. */
852 if (expr->ts.type == BT_DERIVED && expr->ts.u.derived
853 && expr->ts.u.derived->ts.is_iso_c && cons
854 && cons->expr && cons->expr->expr_type == EXPR_NULL)
857 for (; comp && cons; comp = comp->next, cons = gfc_constructor_next (cons))
864 if (gfc_resolve_expr (cons->expr) == FAILURE)
870 rank = comp->as ? comp->as->rank : 0;
871 if (cons->expr->expr_type != EXPR_NULL && rank != cons->expr->rank
872 && (comp->attr.allocatable || cons->expr->rank))
874 gfc_error ("The rank of the element in the derived type "
875 "constructor at %L does not match that of the "
876 "component (%d/%d)", &cons->expr->where,
877 cons->expr->rank, rank);
881 /* If we don't have the right type, try to convert it. */
883 if (!gfc_compare_types (&cons->expr->ts, &comp->ts))
886 if (strcmp (comp->name, "$extends") == 0)
888 /* Can afford to be brutal with the $extends initializer.
889 The derived type can get lost because it is PRIVATE
890 but it is not usage constrained by the standard. */
891 cons->expr->ts = comp->ts;
894 else if (comp->attr.pointer && cons->expr->ts.type != BT_UNKNOWN)
895 gfc_error ("The element in the derived type constructor at %L, "
896 "for pointer component '%s', is %s but should be %s",
897 &cons->expr->where, comp->name,
898 gfc_basic_typename (cons->expr->ts.type),
899 gfc_basic_typename (comp->ts.type));
901 t = gfc_convert_type (cons->expr, &comp->ts, 1);
904 if (cons->expr->expr_type == EXPR_NULL
905 && !(comp->attr.pointer || comp->attr.allocatable
906 || comp->attr.proc_pointer
907 || (comp->ts.type == BT_CLASS
908 && (CLASS_DATA (comp)->attr.pointer
909 || CLASS_DATA (comp)->attr.allocatable))))
912 gfc_error ("The NULL in the derived type constructor at %L is "
913 "being applied to component '%s', which is neither "
914 "a POINTER nor ALLOCATABLE", &cons->expr->where,
918 if (!comp->attr.pointer || cons->expr->expr_type == EXPR_NULL)
921 a = gfc_expr_attr (cons->expr);
923 if (!a.pointer && !a.target)
926 gfc_error ("The element in the derived type constructor at %L, "
927 "for pointer component '%s' should be a POINTER or "
928 "a TARGET", &cons->expr->where, comp->name);
931 /* F2003, C1272 (3). */
932 if (gfc_pure (NULL) && cons->expr->expr_type == EXPR_VARIABLE
933 && (gfc_impure_variable (cons->expr->symtree->n.sym)
934 || gfc_is_coindexed (cons->expr)))
937 gfc_error ("Invalid expression in the derived type constructor for "
938 "pointer component '%s' at %L in PURE procedure",
939 comp->name, &cons->expr->where);
947 /****************** Expression name resolution ******************/
949 /* Returns 0 if a symbol was not declared with a type or
950 attribute declaration statement, nonzero otherwise. */
953 was_declared (gfc_symbol *sym)
959 if (!a.implicit_type && sym->ts.type != BT_UNKNOWN)
962 if (a.allocatable || a.dimension || a.dummy || a.external || a.intrinsic
963 || a.optional || a.pointer || a.save || a.target || a.volatile_
964 || a.value || a.access != ACCESS_UNKNOWN || a.intent != INTENT_UNKNOWN
965 || a.asynchronous || a.codimension)
972 /* Determine if a symbol is generic or not. */
975 generic_sym (gfc_symbol *sym)
979 if (sym->attr.generic ||
980 (sym->attr.intrinsic && gfc_generic_intrinsic (sym->name)))
983 if (was_declared (sym) || sym->ns->parent == NULL)
986 gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
993 return generic_sym (s);
1000 /* Determine if a symbol is specific or not. */
1003 specific_sym (gfc_symbol *sym)
1007 if (sym->attr.if_source == IFSRC_IFBODY
1008 || sym->attr.proc == PROC_MODULE
1009 || sym->attr.proc == PROC_INTERNAL
1010 || sym->attr.proc == PROC_ST_FUNCTION
1011 || (sym->attr.intrinsic && gfc_specific_intrinsic (sym->name))
1012 || sym->attr.external)
1015 if (was_declared (sym) || sym->ns->parent == NULL)
1018 gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
1020 return (s == NULL) ? 0 : specific_sym (s);
1024 /* Figure out if the procedure is specific, generic or unknown. */
1027 { PTYPE_GENERIC = 1, PTYPE_SPECIFIC, PTYPE_UNKNOWN }
1031 procedure_kind (gfc_symbol *sym)
1033 if (generic_sym (sym))
1034 return PTYPE_GENERIC;
1036 if (specific_sym (sym))
1037 return PTYPE_SPECIFIC;
1039 return PTYPE_UNKNOWN;
1042 /* Check references to assumed size arrays. The flag need_full_assumed_size
1043 is nonzero when matching actual arguments. */
1045 static int need_full_assumed_size = 0;
1048 check_assumed_size_reference (gfc_symbol *sym, gfc_expr *e)
1050 if (need_full_assumed_size || !(sym->as && sym->as->type == AS_ASSUMED_SIZE))
1053 /* FIXME: The comparison "e->ref->u.ar.type == AR_FULL" is wrong.
1054 What should it be? */
1055 if ((e->ref->u.ar.end[e->ref->u.ar.as->rank - 1] == NULL)
1056 && (e->ref->u.ar.as->type == AS_ASSUMED_SIZE)
1057 && (e->ref->u.ar.type == AR_FULL))
1059 gfc_error ("The upper bound in the last dimension must "
1060 "appear in the reference to the assumed size "
1061 "array '%s' at %L", sym->name, &e->where);
1068 /* Look for bad assumed size array references in argument expressions
1069 of elemental and array valued intrinsic procedures. Since this is
1070 called from procedure resolution functions, it only recurses at
1074 resolve_assumed_size_actual (gfc_expr *e)
1079 switch (e->expr_type)
1082 if (e->symtree && check_assumed_size_reference (e->symtree->n.sym, e))
1087 if (resolve_assumed_size_actual (e->value.op.op1)
1088 || resolve_assumed_size_actual (e->value.op.op2))
1099 /* Check a generic procedure, passed as an actual argument, to see if
1100 there is a matching specific name. If none, it is an error, and if
1101 more than one, the reference is ambiguous. */
1103 count_specific_procs (gfc_expr *e)
1110 sym = e->symtree->n.sym;
1112 for (p = sym->generic; p; p = p->next)
1113 if (strcmp (sym->name, p->sym->name) == 0)
1115 e->symtree = gfc_find_symtree (p->sym->ns->sym_root,
1121 gfc_error ("'%s' at %L is ambiguous", e->symtree->n.sym->name,
1125 gfc_error ("GENERIC procedure '%s' is not allowed as an actual "
1126 "argument at %L", sym->name, &e->where);
1132 /* See if a call to sym could possibly be a not allowed RECURSION because of
1133 a missing RECURIVE declaration. This means that either sym is the current
1134 context itself, or sym is the parent of a contained procedure calling its
1135 non-RECURSIVE containing procedure.
1136 This also works if sym is an ENTRY. */
1139 is_illegal_recursion (gfc_symbol* sym, gfc_namespace* context)
1141 gfc_symbol* proc_sym;
1142 gfc_symbol* context_proc;
1143 gfc_namespace* real_context;
1145 if (sym->attr.flavor == FL_PROGRAM)
1148 gcc_assert (sym->attr.flavor == FL_PROCEDURE);
1150 /* If we've got an ENTRY, find real procedure. */
1151 if (sym->attr.entry && sym->ns->entries)
1152 proc_sym = sym->ns->entries->sym;
1156 /* If sym is RECURSIVE, all is well of course. */
1157 if (proc_sym->attr.recursive || gfc_option.flag_recursive)
1160 /* Find the context procedure's "real" symbol if it has entries.
1161 We look for a procedure symbol, so recurse on the parents if we don't
1162 find one (like in case of a BLOCK construct). */
1163 for (real_context = context; ; real_context = real_context->parent)
1165 /* We should find something, eventually! */
1166 gcc_assert (real_context);
1168 context_proc = (real_context->entries ? real_context->entries->sym
1169 : real_context->proc_name);
1171 /* In some special cases, there may not be a proc_name, like for this
1173 real(bad_kind()) function foo () ...
1174 when checking the call to bad_kind ().
1175 In these cases, we simply return here and assume that the
1180 if (context_proc->attr.flavor != FL_LABEL)
1184 /* A call from sym's body to itself is recursion, of course. */
1185 if (context_proc == proc_sym)
1188 /* The same is true if context is a contained procedure and sym the
1190 if (context_proc->attr.contained)
1192 gfc_symbol* parent_proc;
1194 gcc_assert (context->parent);
1195 parent_proc = (context->parent->entries ? context->parent->entries->sym
1196 : context->parent->proc_name);
1198 if (parent_proc == proc_sym)
1206 /* Resolve an intrinsic procedure: Set its function/subroutine attribute,
1207 its typespec and formal argument list. */
1210 resolve_intrinsic (gfc_symbol *sym, locus *loc)
1212 gfc_intrinsic_sym* isym;
1218 /* We already know this one is an intrinsic, so we don't call
1219 gfc_is_intrinsic for full checking but rather use gfc_find_function and
1220 gfc_find_subroutine directly to check whether it is a function or
1223 if ((isym = gfc_find_function (sym->name)))
1225 if (sym->ts.type != BT_UNKNOWN && gfc_option.warn_surprising
1226 && !sym->attr.implicit_type)
1227 gfc_warning ("Type specified for intrinsic function '%s' at %L is"
1228 " ignored", sym->name, &sym->declared_at);
1230 if (!sym->attr.function &&
1231 gfc_add_function (&sym->attr, sym->name, loc) == FAILURE)
1236 else if ((isym = gfc_find_subroutine (sym->name)))
1238 if (sym->ts.type != BT_UNKNOWN && !sym->attr.implicit_type)
1240 gfc_error ("Intrinsic subroutine '%s' at %L shall not have a type"
1241 " specifier", sym->name, &sym->declared_at);
1245 if (!sym->attr.subroutine &&
1246 gfc_add_subroutine (&sym->attr, sym->name, loc) == FAILURE)
1251 gfc_error ("'%s' declared INTRINSIC at %L does not exist", sym->name,
1256 gfc_copy_formal_args_intr (sym, isym);
1258 /* Check it is actually available in the standard settings. */
1259 if (gfc_check_intrinsic_standard (isym, &symstd, false, sym->declared_at)
1262 gfc_error ("The intrinsic '%s' declared INTRINSIC at %L is not"
1263 " available in the current standard settings but %s. Use"
1264 " an appropriate -std=* option or enable -fall-intrinsics"
1265 " in order to use it.",
1266 sym->name, &sym->declared_at, symstd);
1274 /* Resolve a procedure expression, like passing it to a called procedure or as
1275 RHS for a procedure pointer assignment. */
1278 resolve_procedure_expression (gfc_expr* expr)
1282 if (expr->expr_type != EXPR_VARIABLE)
1284 gcc_assert (expr->symtree);
1286 sym = expr->symtree->n.sym;
1288 if (sym->attr.intrinsic)
1289 resolve_intrinsic (sym, &expr->where);
1291 if (sym->attr.flavor != FL_PROCEDURE
1292 || (sym->attr.function && sym->result == sym))
1295 /* A non-RECURSIVE procedure that is used as procedure expression within its
1296 own body is in danger of being called recursively. */
1297 if (is_illegal_recursion (sym, gfc_current_ns))
1298 gfc_warning ("Non-RECURSIVE procedure '%s' at %L is possibly calling"
1299 " itself recursively. Declare it RECURSIVE or use"
1300 " -frecursive", sym->name, &expr->where);
1306 /* Resolve an actual argument list. Most of the time, this is just
1307 resolving the expressions in the list.
1308 The exception is that we sometimes have to decide whether arguments
1309 that look like procedure arguments are really simple variable
1313 resolve_actual_arglist (gfc_actual_arglist *arg, procedure_type ptype,
1314 bool no_formal_args)
1317 gfc_symtree *parent_st;
1319 int save_need_full_assumed_size;
1320 gfc_component *comp;
1322 for (; arg; arg = arg->next)
1327 /* Check the label is a valid branching target. */
1330 if (arg->label->defined == ST_LABEL_UNKNOWN)
1332 gfc_error ("Label %d referenced at %L is never defined",
1333 arg->label->value, &arg->label->where);
1340 if (gfc_is_proc_ptr_comp (e, &comp))
1343 if (e->expr_type == EXPR_PPC)
1345 if (comp->as != NULL)
1346 e->rank = comp->as->rank;
1347 e->expr_type = EXPR_FUNCTION;
1349 if (gfc_resolve_expr (e) == FAILURE)
1354 if (e->expr_type == EXPR_VARIABLE
1355 && e->symtree->n.sym->attr.generic
1357 && count_specific_procs (e) != 1)
1360 if (e->ts.type != BT_PROCEDURE)
1362 save_need_full_assumed_size = need_full_assumed_size;
1363 if (e->expr_type != EXPR_VARIABLE)
1364 need_full_assumed_size = 0;
1365 if (gfc_resolve_expr (e) != SUCCESS)
1367 need_full_assumed_size = save_need_full_assumed_size;
1371 /* See if the expression node should really be a variable reference. */
1373 sym = e->symtree->n.sym;
1375 if (sym->attr.flavor == FL_PROCEDURE
1376 || sym->attr.intrinsic
1377 || sym->attr.external)
1381 /* If a procedure is not already determined to be something else
1382 check if it is intrinsic. */
1383 if (!sym->attr.intrinsic
1384 && !(sym->attr.external || sym->attr.use_assoc
1385 || sym->attr.if_source == IFSRC_IFBODY)
1386 && gfc_is_intrinsic (sym, sym->attr.subroutine, e->where))
1387 sym->attr.intrinsic = 1;
1389 if (sym->attr.proc == PROC_ST_FUNCTION)
1391 gfc_error ("Statement function '%s' at %L is not allowed as an "
1392 "actual argument", sym->name, &e->where);
1395 actual_ok = gfc_intrinsic_actual_ok (sym->name,
1396 sym->attr.subroutine);
1397 if (sym->attr.intrinsic && actual_ok == 0)
1399 gfc_error ("Intrinsic '%s' at %L is not allowed as an "
1400 "actual argument", sym->name, &e->where);
1403 if (sym->attr.contained && !sym->attr.use_assoc
1404 && sym->ns->proc_name->attr.flavor != FL_MODULE)
1406 gfc_error ("Internal procedure '%s' is not allowed as an "
1407 "actual argument at %L", sym->name, &e->where);
1410 if (sym->attr.elemental && !sym->attr.intrinsic)
1412 gfc_error ("ELEMENTAL non-INTRINSIC procedure '%s' is not "
1413 "allowed as an actual argument at %L", sym->name,
1417 /* Check if a generic interface has a specific procedure
1418 with the same name before emitting an error. */
1419 if (sym->attr.generic && count_specific_procs (e) != 1)
1422 /* Just in case a specific was found for the expression. */
1423 sym = e->symtree->n.sym;
1425 /* If the symbol is the function that names the current (or
1426 parent) scope, then we really have a variable reference. */
1428 if (gfc_is_function_return_value (sym, sym->ns))
1431 /* If all else fails, see if we have a specific intrinsic. */
1432 if (sym->ts.type == BT_UNKNOWN && sym->attr.intrinsic)
1434 gfc_intrinsic_sym *isym;
1436 isym = gfc_find_function (sym->name);
1437 if (isym == NULL || !isym->specific)
1439 gfc_error ("Unable to find a specific INTRINSIC procedure "
1440 "for the reference '%s' at %L", sym->name,
1445 sym->attr.intrinsic = 1;
1446 sym->attr.function = 1;
1449 if (gfc_resolve_expr (e) == FAILURE)
1454 /* See if the name is a module procedure in a parent unit. */
1456 if (was_declared (sym) || sym->ns->parent == NULL)
1459 if (gfc_find_sym_tree (sym->name, sym->ns->parent, 1, &parent_st))
1461 gfc_error ("Symbol '%s' at %L is ambiguous", sym->name, &e->where);
1465 if (parent_st == NULL)
1468 sym = parent_st->n.sym;
1469 e->symtree = parent_st; /* Point to the right thing. */
1471 if (sym->attr.flavor == FL_PROCEDURE
1472 || sym->attr.intrinsic
1473 || sym->attr.external)
1475 if (gfc_resolve_expr (e) == FAILURE)
1481 e->expr_type = EXPR_VARIABLE;
1483 if (sym->as != NULL)
1485 e->rank = sym->as->rank;
1486 e->ref = gfc_get_ref ();
1487 e->ref->type = REF_ARRAY;
1488 e->ref->u.ar.type = AR_FULL;
1489 e->ref->u.ar.as = sym->as;
1492 /* Expressions are assigned a default ts.type of BT_PROCEDURE in
1493 primary.c (match_actual_arg). If above code determines that it
1494 is a variable instead, it needs to be resolved as it was not
1495 done at the beginning of this function. */
1496 save_need_full_assumed_size = need_full_assumed_size;
1497 if (e->expr_type != EXPR_VARIABLE)
1498 need_full_assumed_size = 0;
1499 if (gfc_resolve_expr (e) != SUCCESS)
1501 need_full_assumed_size = save_need_full_assumed_size;
1504 /* Check argument list functions %VAL, %LOC and %REF. There is
1505 nothing to do for %REF. */
1506 if (arg->name && arg->name[0] == '%')
1508 if (strncmp ("%VAL", arg->name, 4) == 0)
1510 if (e->ts.type == BT_CHARACTER || e->ts.type == BT_DERIVED)
1512 gfc_error ("By-value argument at %L is not of numeric "
1519 gfc_error ("By-value argument at %L cannot be an array or "
1520 "an array section", &e->where);
1524 /* Intrinsics are still PROC_UNKNOWN here. However,
1525 since same file external procedures are not resolvable
1526 in gfortran, it is a good deal easier to leave them to
1528 if (ptype != PROC_UNKNOWN
1529 && ptype != PROC_DUMMY
1530 && ptype != PROC_EXTERNAL
1531 && ptype != PROC_MODULE)
1533 gfc_error ("By-value argument at %L is not allowed "
1534 "in this context", &e->where);
1539 /* Statement functions have already been excluded above. */
1540 else if (strncmp ("%LOC", arg->name, 4) == 0
1541 && e->ts.type == BT_PROCEDURE)
1543 if (e->symtree->n.sym->attr.proc == PROC_INTERNAL)
1545 gfc_error ("Passing internal procedure at %L by location "
1546 "not allowed", &e->where);
1552 /* Fortran 2008, C1237. */
1553 if (e->expr_type == EXPR_VARIABLE && gfc_is_coindexed (e)
1554 && gfc_has_ultimate_pointer (e))
1556 gfc_error ("Coindexed actual argument at %L with ultimate pointer "
1557 "component", &e->where);
1566 /* Do the checks of the actual argument list that are specific to elemental
1567 procedures. If called with c == NULL, we have a function, otherwise if
1568 expr == NULL, we have a subroutine. */
1571 resolve_elemental_actual (gfc_expr *expr, gfc_code *c)
1573 gfc_actual_arglist *arg0;
1574 gfc_actual_arglist *arg;
1575 gfc_symbol *esym = NULL;
1576 gfc_intrinsic_sym *isym = NULL;
1578 gfc_intrinsic_arg *iformal = NULL;
1579 gfc_formal_arglist *eformal = NULL;
1580 bool formal_optional = false;
1581 bool set_by_optional = false;
1585 /* Is this an elemental procedure? */
1586 if (expr && expr->value.function.actual != NULL)
1588 if (expr->value.function.esym != NULL
1589 && expr->value.function.esym->attr.elemental)
1591 arg0 = expr->value.function.actual;
1592 esym = expr->value.function.esym;
1594 else if (expr->value.function.isym != NULL
1595 && expr->value.function.isym->elemental)
1597 arg0 = expr->value.function.actual;
1598 isym = expr->value.function.isym;
1603 else if (c && c->ext.actual != NULL)
1605 arg0 = c->ext.actual;
1607 if (c->resolved_sym)
1608 esym = c->resolved_sym;
1610 esym = c->symtree->n.sym;
1613 if (!esym->attr.elemental)
1619 /* The rank of an elemental is the rank of its array argument(s). */
1620 for (arg = arg0; arg; arg = arg->next)
1622 if (arg->expr != NULL && arg->expr->rank > 0)
1624 rank = arg->expr->rank;
1625 if (arg->expr->expr_type == EXPR_VARIABLE
1626 && arg->expr->symtree->n.sym->attr.optional)
1627 set_by_optional = true;
1629 /* Function specific; set the result rank and shape. */
1633 if (!expr->shape && arg->expr->shape)
1635 expr->shape = gfc_get_shape (rank);
1636 for (i = 0; i < rank; i++)
1637 mpz_init_set (expr->shape[i], arg->expr->shape[i]);
1644 /* If it is an array, it shall not be supplied as an actual argument
1645 to an elemental procedure unless an array of the same rank is supplied
1646 as an actual argument corresponding to a nonoptional dummy argument of
1647 that elemental procedure(12.4.1.5). */
1648 formal_optional = false;
1650 iformal = isym->formal;
1652 eformal = esym->formal;
1654 for (arg = arg0; arg; arg = arg->next)
1658 if (eformal->sym && eformal->sym->attr.optional)
1659 formal_optional = true;
1660 eformal = eformal->next;
1662 else if (isym && iformal)
1664 if (iformal->optional)
1665 formal_optional = true;
1666 iformal = iformal->next;
1669 formal_optional = true;
1671 if (pedantic && arg->expr != NULL
1672 && arg->expr->expr_type == EXPR_VARIABLE
1673 && arg->expr->symtree->n.sym->attr.optional
1676 && (set_by_optional || arg->expr->rank != rank)
1677 && !(isym && isym->id == GFC_ISYM_CONVERSION))
1679 gfc_warning ("'%s' at %L is an array and OPTIONAL; IF IT IS "
1680 "MISSING, it cannot be the actual argument of an "
1681 "ELEMENTAL procedure unless there is a non-optional "
1682 "argument with the same rank (12.4.1.5)",
1683 arg->expr->symtree->n.sym->name, &arg->expr->where);
1688 for (arg = arg0; arg; arg = arg->next)
1690 if (arg->expr == NULL || arg->expr->rank == 0)
1693 /* Being elemental, the last upper bound of an assumed size array
1694 argument must be present. */
1695 if (resolve_assumed_size_actual (arg->expr))
1698 /* Elemental procedure's array actual arguments must conform. */
1701 if (gfc_check_conformance (arg->expr, e,
1702 "elemental procedure") == FAILURE)
1709 /* INTENT(OUT) is only allowed for subroutines; if any actual argument
1710 is an array, the intent inout/out variable needs to be also an array. */
1711 if (rank > 0 && esym && expr == NULL)
1712 for (eformal = esym->formal, arg = arg0; arg && eformal;
1713 arg = arg->next, eformal = eformal->next)
1714 if ((eformal->sym->attr.intent == INTENT_OUT
1715 || eformal->sym->attr.intent == INTENT_INOUT)
1716 && arg->expr && arg->expr->rank == 0)
1718 gfc_error ("Actual argument at %L for INTENT(%s) dummy '%s' of "
1719 "ELEMENTAL subroutine '%s' is a scalar, but another "
1720 "actual argument is an array", &arg->expr->where,
1721 (eformal->sym->attr.intent == INTENT_OUT) ? "OUT"
1722 : "INOUT", eformal->sym->name, esym->name);
1729 /* Go through each actual argument in ACTUAL and see if it can be
1730 implemented as an inlined, non-copying intrinsic. FNSYM is the
1731 function being called, or NULL if not known. */
1734 find_noncopying_intrinsics (gfc_symbol *fnsym, gfc_actual_arglist *actual)
1736 gfc_actual_arglist *ap;
1739 for (ap = actual; ap; ap = ap->next)
1741 && (expr = gfc_get_noncopying_intrinsic_argument (ap->expr))
1742 && !gfc_check_fncall_dependency (expr, INTENT_IN, fnsym, actual,
1744 ap->expr->inline_noncopying_intrinsic = 1;
1748 /* This function does the checking of references to global procedures
1749 as defined in sections 18.1 and 14.1, respectively, of the Fortran
1750 77 and 95 standards. It checks for a gsymbol for the name, making
1751 one if it does not already exist. If it already exists, then the
1752 reference being resolved must correspond to the type of gsymbol.
1753 Otherwise, the new symbol is equipped with the attributes of the
1754 reference. The corresponding code that is called in creating
1755 global entities is parse.c.
1757 In addition, for all but -std=legacy, the gsymbols are used to
1758 check the interfaces of external procedures from the same file.
1759 The namespace of the gsymbol is resolved and then, once this is
1760 done the interface is checked. */
1764 not_in_recursive (gfc_symbol *sym, gfc_namespace *gsym_ns)
1766 if (!gsym_ns->proc_name->attr.recursive)
1769 if (sym->ns == gsym_ns)
1772 if (sym->ns->parent && sym->ns->parent == gsym_ns)
1779 not_entry_self_reference (gfc_symbol *sym, gfc_namespace *gsym_ns)
1781 if (gsym_ns->entries)
1783 gfc_entry_list *entry = gsym_ns->entries;
1785 for (; entry; entry = entry->next)
1787 if (strcmp (sym->name, entry->sym->name) == 0)
1789 if (strcmp (gsym_ns->proc_name->name,
1790 sym->ns->proc_name->name) == 0)
1794 && strcmp (gsym_ns->proc_name->name,
1795 sym->ns->parent->proc_name->name) == 0)
1804 resolve_global_procedure (gfc_symbol *sym, locus *where,
1805 gfc_actual_arglist **actual, int sub)
1809 enum gfc_symbol_type type;
1811 type = sub ? GSYM_SUBROUTINE : GSYM_FUNCTION;
1813 gsym = gfc_get_gsymbol (sym->name);
1815 if ((gsym->type != GSYM_UNKNOWN && gsym->type != type))
1816 gfc_global_used (gsym, where);
1818 if (gfc_option.flag_whole_file
1819 && sym->attr.if_source == IFSRC_UNKNOWN
1820 && gsym->type != GSYM_UNKNOWN
1822 && gsym->ns->resolved != -1
1823 && gsym->ns->proc_name
1824 && not_in_recursive (sym, gsym->ns)
1825 && not_entry_self_reference (sym, gsym->ns))
1827 /* Resolve the gsymbol namespace if needed. */
1828 if (!gsym->ns->resolved)
1830 gfc_dt_list *old_dt_list;
1832 /* Stash away derived types so that the backend_decls do not
1834 old_dt_list = gfc_derived_types;
1835 gfc_derived_types = NULL;
1837 gfc_resolve (gsym->ns);
1839 /* Store the new derived types with the global namespace. */
1840 if (gfc_derived_types)
1841 gsym->ns->derived_types = gfc_derived_types;
1843 /* Restore the derived types of this namespace. */
1844 gfc_derived_types = old_dt_list;
1847 /* Make sure that translation for the gsymbol occurs before
1848 the procedure currently being resolved. */
1849 ns = gfc_global_ns_list;
1850 for (; ns && ns != gsym->ns; ns = ns->sibling)
1852 if (ns->sibling == gsym->ns)
1854 ns->sibling = gsym->ns->sibling;
1855 gsym->ns->sibling = gfc_global_ns_list;
1856 gfc_global_ns_list = gsym->ns;
1861 if (gsym->ns->proc_name->attr.function
1862 && gsym->ns->proc_name->as
1863 && gsym->ns->proc_name->as->rank
1864 && (!sym->as || sym->as->rank != gsym->ns->proc_name->as->rank))
1865 gfc_error ("The reference to function '%s' at %L either needs an "
1866 "explicit INTERFACE or the rank is incorrect", sym->name,
1869 /* Non-assumed length character functions. */
1870 if (sym->attr.function && sym->ts.type == BT_CHARACTER
1871 && gsym->ns->proc_name->ts.u.cl->length != NULL)
1873 gfc_charlen *cl = sym->ts.u.cl;
1875 if (!sym->attr.entry_master && sym->attr.if_source == IFSRC_UNKNOWN
1876 && cl && cl->length && cl->length->expr_type != EXPR_CONSTANT)
1878 gfc_error ("Nonconstant character-length function '%s' at %L "
1879 "must have an explicit interface", sym->name,
1884 /* Differences in constant character lengths. */
1885 if (sym->attr.function && sym->ts.type == BT_CHARACTER)
1887 long int l1 = 0, l2 = 0;
1888 gfc_charlen *cl1 = sym->ts.u.cl;
1889 gfc_charlen *cl2 = gsym->ns->proc_name->ts.u.cl;
1892 && cl1->length != NULL
1893 && cl1->length->expr_type == EXPR_CONSTANT)
1894 l1 = mpz_get_si (cl1->length->value.integer);
1897 && cl2->length != NULL
1898 && cl2->length->expr_type == EXPR_CONSTANT)
1899 l2 = mpz_get_si (cl2->length->value.integer);
1901 if (l1 && l2 && l1 != l2)
1902 gfc_error ("Character length mismatch in return type of "
1903 "function '%s' at %L (%ld/%ld)", sym->name,
1904 &sym->declared_at, l1, l2);
1907 /* Type mismatch of function return type and expected type. */
1908 if (sym->attr.function
1909 && !gfc_compare_types (&sym->ts, &gsym->ns->proc_name->ts))
1910 gfc_error ("Return type mismatch of function '%s' at %L (%s/%s)",
1911 sym->name, &sym->declared_at, gfc_typename (&sym->ts),
1912 gfc_typename (&gsym->ns->proc_name->ts));
1914 /* Assumed shape arrays as dummy arguments. */
1915 if (gsym->ns->proc_name->formal)
1917 gfc_formal_arglist *arg = gsym->ns->proc_name->formal;
1918 for ( ; arg; arg = arg->next)
1919 if (arg->sym && arg->sym->as
1920 && arg->sym->as->type == AS_ASSUMED_SHAPE)
1922 gfc_error ("Procedure '%s' at %L with assumed-shape dummy "
1923 "'%s' argument must have an explicit interface",
1924 sym->name, &sym->declared_at, arg->sym->name);
1927 else if (arg->sym && arg->sym->attr.optional)
1929 gfc_error ("Procedure '%s' at %L with optional dummy argument "
1930 "'%s' must have an explicit interface",
1931 sym->name, &sym->declared_at, arg->sym->name);
1936 if (gfc_option.flag_whole_file == 1
1937 || ((gfc_option.warn_std & GFC_STD_LEGACY)
1938 && !(gfc_option.warn_std & GFC_STD_GNU)))
1939 gfc_errors_to_warnings (1);
1941 gfc_procedure_use (gsym->ns->proc_name, actual, where);
1943 gfc_errors_to_warnings (0);
1946 if (gsym->type == GSYM_UNKNOWN)
1949 gsym->where = *where;
1956 /************* Function resolution *************/
1958 /* Resolve a function call known to be generic.
1959 Section 14.1.2.4.1. */
1962 resolve_generic_f0 (gfc_expr *expr, gfc_symbol *sym)
1966 if (sym->attr.generic)
1968 s = gfc_search_interface (sym->generic, 0, &expr->value.function.actual);
1971 expr->value.function.name = s->name;
1972 expr->value.function.esym = s;
1974 if (s->ts.type != BT_UNKNOWN)
1976 else if (s->result != NULL && s->result->ts.type != BT_UNKNOWN)
1977 expr->ts = s->result->ts;
1980 expr->rank = s->as->rank;
1981 else if (s->result != NULL && s->result->as != NULL)
1982 expr->rank = s->result->as->rank;
1984 gfc_set_sym_referenced (expr->value.function.esym);
1989 /* TODO: Need to search for elemental references in generic
1993 if (sym->attr.intrinsic)
1994 return gfc_intrinsic_func_interface (expr, 0);
2001 resolve_generic_f (gfc_expr *expr)
2006 sym = expr->symtree->n.sym;
2010 m = resolve_generic_f0 (expr, sym);
2013 else if (m == MATCH_ERROR)
2017 if (sym->ns->parent == NULL)
2019 gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2023 if (!generic_sym (sym))
2027 /* Last ditch attempt. See if the reference is to an intrinsic
2028 that possesses a matching interface. 14.1.2.4 */
2029 if (sym && !gfc_is_intrinsic (sym, 0, expr->where))
2031 gfc_error ("There is no specific function for the generic '%s' at %L",
2032 expr->symtree->n.sym->name, &expr->where);
2036 m = gfc_intrinsic_func_interface (expr, 0);
2040 gfc_error ("Generic function '%s' at %L is not consistent with a "
2041 "specific intrinsic interface", expr->symtree->n.sym->name,
2048 /* Resolve a function call known to be specific. */
2051 resolve_specific_f0 (gfc_symbol *sym, gfc_expr *expr)
2055 if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
2057 if (sym->attr.dummy)
2059 sym->attr.proc = PROC_DUMMY;
2063 sym->attr.proc = PROC_EXTERNAL;
2067 if (sym->attr.proc == PROC_MODULE
2068 || sym->attr.proc == PROC_ST_FUNCTION
2069 || sym->attr.proc == PROC_INTERNAL)
2072 if (sym->attr.intrinsic)
2074 m = gfc_intrinsic_func_interface (expr, 1);
2078 gfc_error ("Function '%s' at %L is INTRINSIC but is not compatible "
2079 "with an intrinsic", sym->name, &expr->where);
2087 gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2090 expr->ts = sym->result->ts;
2093 expr->value.function.name = sym->name;
2094 expr->value.function.esym = sym;
2095 if (sym->as != NULL)
2096 expr->rank = sym->as->rank;
2103 resolve_specific_f (gfc_expr *expr)
2108 sym = expr->symtree->n.sym;
2112 m = resolve_specific_f0 (sym, expr);
2115 if (m == MATCH_ERROR)
2118 if (sym->ns->parent == NULL)
2121 gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2127 gfc_error ("Unable to resolve the specific function '%s' at %L",
2128 expr->symtree->n.sym->name, &expr->where);
2134 /* Resolve a procedure call not known to be generic nor specific. */
2137 resolve_unknown_f (gfc_expr *expr)
2142 sym = expr->symtree->n.sym;
2144 if (sym->attr.dummy)
2146 sym->attr.proc = PROC_DUMMY;
2147 expr->value.function.name = sym->name;
2151 /* See if we have an intrinsic function reference. */
2153 if (gfc_is_intrinsic (sym, 0, expr->where))
2155 if (gfc_intrinsic_func_interface (expr, 1) == MATCH_YES)
2160 /* The reference is to an external name. */
2162 sym->attr.proc = PROC_EXTERNAL;
2163 expr->value.function.name = sym->name;
2164 expr->value.function.esym = expr->symtree->n.sym;
2166 if (sym->as != NULL)
2167 expr->rank = sym->as->rank;
2169 /* Type of the expression is either the type of the symbol or the
2170 default type of the symbol. */
2173 gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2175 if (sym->ts.type != BT_UNKNOWN)
2179 ts = gfc_get_default_type (sym->name, sym->ns);
2181 if (ts->type == BT_UNKNOWN)
2183 gfc_error ("Function '%s' at %L has no IMPLICIT type",
2184 sym->name, &expr->where);
2195 /* Return true, if the symbol is an external procedure. */
2197 is_external_proc (gfc_symbol *sym)
2199 if (!sym->attr.dummy && !sym->attr.contained
2200 && !(sym->attr.intrinsic
2201 || gfc_is_intrinsic (sym, sym->attr.subroutine, sym->declared_at))
2202 && sym->attr.proc != PROC_ST_FUNCTION
2203 && !sym->attr.use_assoc
2211 /* Figure out if a function reference is pure or not. Also set the name
2212 of the function for a potential error message. Return nonzero if the
2213 function is PURE, zero if not. */
2215 pure_stmt_function (gfc_expr *, gfc_symbol *);
2218 pure_function (gfc_expr *e, const char **name)
2224 if (e->symtree != NULL
2225 && e->symtree->n.sym != NULL
2226 && e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2227 return pure_stmt_function (e, e->symtree->n.sym);
2229 if (e->value.function.esym)
2231 pure = gfc_pure (e->value.function.esym);
2232 *name = e->value.function.esym->name;
2234 else if (e->value.function.isym)
2236 pure = e->value.function.isym->pure
2237 || e->value.function.isym->elemental;
2238 *name = e->value.function.isym->name;
2242 /* Implicit functions are not pure. */
2244 *name = e->value.function.name;
2252 impure_stmt_fcn (gfc_expr *e, gfc_symbol *sym,
2253 int *f ATTRIBUTE_UNUSED)
2257 /* Don't bother recursing into other statement functions
2258 since they will be checked individually for purity. */
2259 if (e->expr_type != EXPR_FUNCTION
2261 || e->symtree->n.sym == sym
2262 || e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2265 return pure_function (e, &name) ? false : true;
2270 pure_stmt_function (gfc_expr *e, gfc_symbol *sym)
2272 return gfc_traverse_expr (e, sym, impure_stmt_fcn, 0) ? 0 : 1;
2277 is_scalar_expr_ptr (gfc_expr *expr)
2279 gfc_try retval = SUCCESS;
2284 /* See if we have a gfc_ref, which means we have a substring, array
2285 reference, or a component. */
2286 if (expr->ref != NULL)
2289 while (ref->next != NULL)
2295 if (ref->u.ss.length != NULL
2296 && ref->u.ss.length->length != NULL
2298 && ref->u.ss.start->expr_type == EXPR_CONSTANT
2300 && ref->u.ss.end->expr_type == EXPR_CONSTANT)
2302 start = (int) mpz_get_si (ref->u.ss.start->value.integer);
2303 end = (int) mpz_get_si (ref->u.ss.end->value.integer);
2304 if (end - start + 1 != 1)
2311 if (ref->u.ar.type == AR_ELEMENT)
2313 else if (ref->u.ar.type == AR_FULL)
2315 /* The user can give a full array if the array is of size 1. */
2316 if (ref->u.ar.as != NULL
2317 && ref->u.ar.as->rank == 1
2318 && ref->u.ar.as->type == AS_EXPLICIT
2319 && ref->u.ar.as->lower[0] != NULL
2320 && ref->u.ar.as->lower[0]->expr_type == EXPR_CONSTANT
2321 && ref->u.ar.as->upper[0] != NULL
2322 && ref->u.ar.as->upper[0]->expr_type == EXPR_CONSTANT)
2324 /* If we have a character string, we need to check if
2325 its length is one. */
2326 if (expr->ts.type == BT_CHARACTER)
2328 if (expr->ts.u.cl == NULL
2329 || expr->ts.u.cl->length == NULL
2330 || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1)
2336 /* We have constant lower and upper bounds. If the
2337 difference between is 1, it can be considered a
2339 start = (int) mpz_get_si
2340 (ref->u.ar.as->lower[0]->value.integer);
2341 end = (int) mpz_get_si
2342 (ref->u.ar.as->upper[0]->value.integer);
2343 if (end - start + 1 != 1)
2358 else if (expr->ts.type == BT_CHARACTER && expr->rank == 0)
2360 /* Character string. Make sure it's of length 1. */
2361 if (expr->ts.u.cl == NULL
2362 || expr->ts.u.cl->length == NULL
2363 || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1) != 0)
2366 else if (expr->rank != 0)
2373 /* Match one of the iso_c_binding functions (c_associated or c_loc)
2374 and, in the case of c_associated, set the binding label based on
2378 gfc_iso_c_func_interface (gfc_symbol *sym, gfc_actual_arglist *args,
2379 gfc_symbol **new_sym)
2381 char name[GFC_MAX_SYMBOL_LEN + 1];
2382 char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
2383 int optional_arg = 0, is_pointer = 0;
2384 gfc_try retval = SUCCESS;
2385 gfc_symbol *args_sym;
2386 gfc_typespec *arg_ts;
2388 if (args->expr->expr_type == EXPR_CONSTANT
2389 || args->expr->expr_type == EXPR_OP
2390 || args->expr->expr_type == EXPR_NULL)
2392 gfc_error ("Argument to '%s' at %L is not a variable",
2393 sym->name, &(args->expr->where));
2397 args_sym = args->expr->symtree->n.sym;
2399 /* The typespec for the actual arg should be that stored in the expr
2400 and not necessarily that of the expr symbol (args_sym), because
2401 the actual expression could be a part-ref of the expr symbol. */
2402 arg_ts = &(args->expr->ts);
2404 is_pointer = gfc_is_data_pointer (args->expr);
2406 if (sym->intmod_sym_id == ISOCBINDING_ASSOCIATED)
2408 /* If the user gave two args then they are providing something for
2409 the optional arg (the second cptr). Therefore, set the name and
2410 binding label to the c_associated for two cptrs. Otherwise,
2411 set c_associated to expect one cptr. */
2415 sprintf (name, "%s_2", sym->name);
2416 sprintf (binding_label, "%s_2", sym->binding_label);
2422 sprintf (name, "%s_1", sym->name);
2423 sprintf (binding_label, "%s_1", sym->binding_label);
2427 /* Get a new symbol for the version of c_associated that
2429 *new_sym = get_iso_c_sym (sym, name, binding_label, optional_arg);
2431 else if (sym->intmod_sym_id == ISOCBINDING_LOC
2432 || sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2434 sprintf (name, "%s", sym->name);
2435 sprintf (binding_label, "%s", sym->binding_label);
2437 /* Error check the call. */
2438 if (args->next != NULL)
2440 gfc_error_now ("More actual than formal arguments in '%s' "
2441 "call at %L", name, &(args->expr->where));
2444 else if (sym->intmod_sym_id == ISOCBINDING_LOC)
2446 /* Make sure we have either the target or pointer attribute. */
2447 if (!args_sym->attr.target && !is_pointer)
2449 gfc_error_now ("Parameter '%s' to '%s' at %L must be either "
2450 "a TARGET or an associated pointer",
2452 sym->name, &(args->expr->where));
2456 /* See if we have interoperable type and type param. */
2457 if (verify_c_interop (arg_ts) == SUCCESS
2458 || gfc_check_any_c_kind (arg_ts) == SUCCESS)
2460 if (args_sym->attr.target == 1)
2462 /* Case 1a, section 15.1.2.5, J3/04-007: variable that
2463 has the target attribute and is interoperable. */
2464 /* Case 1b, section 15.1.2.5, J3/04-007: allocated
2465 allocatable variable that has the TARGET attribute and
2466 is not an array of zero size. */
2467 if (args_sym->attr.allocatable == 1)
2469 if (args_sym->attr.dimension != 0
2470 && (args_sym->as && args_sym->as->rank == 0))
2472 gfc_error_now ("Allocatable variable '%s' used as a "
2473 "parameter to '%s' at %L must not be "
2474 "an array of zero size",
2475 args_sym->name, sym->name,
2476 &(args->expr->where));
2482 /* A non-allocatable target variable with C
2483 interoperable type and type parameters must be
2485 if (args_sym && args_sym->attr.dimension)
2487 if (args_sym->as->type == AS_ASSUMED_SHAPE)
2489 gfc_error ("Assumed-shape array '%s' at %L "
2490 "cannot be an argument to the "
2491 "procedure '%s' because "
2492 "it is not C interoperable",
2494 &(args->expr->where), sym->name);
2497 else if (args_sym->as->type == AS_DEFERRED)
2499 gfc_error ("Deferred-shape array '%s' at %L "
2500 "cannot be an argument to the "
2501 "procedure '%s' because "
2502 "it is not C interoperable",
2504 &(args->expr->where), sym->name);
2509 /* Make sure it's not a character string. Arrays of
2510 any type should be ok if the variable is of a C
2511 interoperable type. */
2512 if (arg_ts->type == BT_CHARACTER)
2513 if (arg_ts->u.cl != NULL
2514 && (arg_ts->u.cl->length == NULL
2515 || arg_ts->u.cl->length->expr_type
2518 (arg_ts->u.cl->length->value.integer, 1)
2520 && is_scalar_expr_ptr (args->expr) != SUCCESS)
2522 gfc_error_now ("CHARACTER argument '%s' to '%s' "
2523 "at %L must have a length of 1",
2524 args_sym->name, sym->name,
2525 &(args->expr->where));
2531 && is_scalar_expr_ptr (args->expr) != SUCCESS)
2533 /* Case 1c, section 15.1.2.5, J3/04-007: an associated
2535 gfc_error_now ("Argument '%s' to '%s' at %L must be an "
2536 "associated scalar POINTER", args_sym->name,
2537 sym->name, &(args->expr->where));
2543 /* The parameter is not required to be C interoperable. If it
2544 is not C interoperable, it must be a nonpolymorphic scalar
2545 with no length type parameters. It still must have either
2546 the pointer or target attribute, and it can be
2547 allocatable (but must be allocated when c_loc is called). */
2548 if (args->expr->rank != 0
2549 && is_scalar_expr_ptr (args->expr) != SUCCESS)
2551 gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2552 "scalar", args_sym->name, sym->name,
2553 &(args->expr->where));
2556 else if (arg_ts->type == BT_CHARACTER
2557 && is_scalar_expr_ptr (args->expr) != SUCCESS)
2559 gfc_error_now ("CHARACTER argument '%s' to '%s' at "
2560 "%L must have a length of 1",
2561 args_sym->name, sym->name,
2562 &(args->expr->where));
2567 else if (sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2569 if (args_sym->attr.flavor != FL_PROCEDURE)
2571 /* TODO: Update this error message to allow for procedure
2572 pointers once they are implemented. */
2573 gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2575 args_sym->name, sym->name,
2576 &(args->expr->where));
2579 else if (args_sym->attr.is_bind_c != 1)
2581 gfc_error_now ("Parameter '%s' to '%s' at %L must be "
2583 args_sym->name, sym->name,
2584 &(args->expr->where));
2589 /* for c_loc/c_funloc, the new symbol is the same as the old one */
2594 gfc_internal_error ("gfc_iso_c_func_interface(): Unhandled "
2595 "iso_c_binding function: '%s'!\n", sym->name);
2602 /* Resolve a function call, which means resolving the arguments, then figuring
2603 out which entity the name refers to. */
2604 /* TODO: Check procedure arguments so that an INTENT(IN) isn't passed
2605 to INTENT(OUT) or INTENT(INOUT). */
2608 resolve_function (gfc_expr *expr)
2610 gfc_actual_arglist *arg;
2615 procedure_type p = PROC_INTRINSIC;
2616 bool no_formal_args;
2620 sym = expr->symtree->n.sym;
2622 /* If this is a procedure pointer component, it has already been resolved. */
2623 if (gfc_is_proc_ptr_comp (expr, NULL))
2626 if (sym && sym->attr.intrinsic
2627 && resolve_intrinsic (sym, &expr->where) == FAILURE)
2630 if (sym && (sym->attr.flavor == FL_VARIABLE || sym->attr.subroutine))
2632 gfc_error ("'%s' at %L is not a function", sym->name, &expr->where);
2636 /* If this ia a deferred TBP with an abstract interface (which may
2637 of course be referenced), expr->value.function.esym will be set. */
2638 if (sym && sym->attr.abstract && !expr->value.function.esym)
2640 gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
2641 sym->name, &expr->where);
2645 /* Switch off assumed size checking and do this again for certain kinds
2646 of procedure, once the procedure itself is resolved. */
2647 need_full_assumed_size++;
2649 if (expr->symtree && expr->symtree->n.sym)
2650 p = expr->symtree->n.sym->attr.proc;
2652 if (expr->value.function.isym && expr->value.function.isym->inquiry)
2653 inquiry_argument = true;
2654 no_formal_args = sym && is_external_proc (sym) && sym->formal == NULL;
2656 if (resolve_actual_arglist (expr->value.function.actual,
2657 p, no_formal_args) == FAILURE)
2659 inquiry_argument = false;
2663 inquiry_argument = false;
2665 /* Need to setup the call to the correct c_associated, depending on
2666 the number of cptrs to user gives to compare. */
2667 if (sym && sym->attr.is_iso_c == 1)
2669 if (gfc_iso_c_func_interface (sym, expr->value.function.actual, &sym)
2673 /* Get the symtree for the new symbol (resolved func).
2674 the old one will be freed later, when it's no longer used. */
2675 gfc_find_sym_tree (sym->name, sym->ns, 1, &(expr->symtree));
2678 /* Resume assumed_size checking. */
2679 need_full_assumed_size--;
2681 /* If the procedure is external, check for usage. */
2682 if (sym && is_external_proc (sym))
2683 resolve_global_procedure (sym, &expr->where,
2684 &expr->value.function.actual, 0);
2686 if (sym && sym->ts.type == BT_CHARACTER
2688 && sym->ts.u.cl->length == NULL
2690 && expr->value.function.esym == NULL
2691 && !sym->attr.contained)
2693 /* Internal procedures are taken care of in resolve_contained_fntype. */
2694 gfc_error ("Function '%s' is declared CHARACTER(*) and cannot "
2695 "be used at %L since it is not a dummy argument",
2696 sym->name, &expr->where);
2700 /* See if function is already resolved. */
2702 if (expr->value.function.name != NULL)
2704 if (expr->ts.type == BT_UNKNOWN)
2710 /* Apply the rules of section 14.1.2. */
2712 switch (procedure_kind (sym))
2715 t = resolve_generic_f (expr);
2718 case PTYPE_SPECIFIC:
2719 t = resolve_specific_f (expr);
2723 t = resolve_unknown_f (expr);
2727 gfc_internal_error ("resolve_function(): bad function type");
2731 /* If the expression is still a function (it might have simplified),
2732 then we check to see if we are calling an elemental function. */
2734 if (expr->expr_type != EXPR_FUNCTION)
2737 temp = need_full_assumed_size;
2738 need_full_assumed_size = 0;
2740 if (resolve_elemental_actual (expr, NULL) == FAILURE)
2743 if (omp_workshare_flag
2744 && expr->value.function.esym
2745 && ! gfc_elemental (expr->value.function.esym))
2747 gfc_error ("User defined non-ELEMENTAL function '%s' at %L not allowed "
2748 "in WORKSHARE construct", expr->value.function.esym->name,
2753 #define GENERIC_ID expr->value.function.isym->id
2754 else if (expr->value.function.actual != NULL
2755 && expr->value.function.isym != NULL
2756 && GENERIC_ID != GFC_ISYM_LBOUND
2757 && GENERIC_ID != GFC_ISYM_LEN
2758 && GENERIC_ID != GFC_ISYM_LOC
2759 && GENERIC_ID != GFC_ISYM_PRESENT)
2761 /* Array intrinsics must also have the last upper bound of an
2762 assumed size array argument. UBOUND and SIZE have to be
2763 excluded from the check if the second argument is anything
2766 for (arg = expr->value.function.actual; arg; arg = arg->next)
2768 if ((GENERIC_ID == GFC_ISYM_UBOUND || GENERIC_ID == GFC_ISYM_SIZE)
2769 && arg->next != NULL && arg->next->expr)
2771 if (arg->next->expr->expr_type != EXPR_CONSTANT)
2774 if (arg->next->name && strncmp(arg->next->name, "kind", 4) == 0)
2777 if ((int)mpz_get_si (arg->next->expr->value.integer)
2782 if (arg->expr != NULL
2783 && arg->expr->rank > 0
2784 && resolve_assumed_size_actual (arg->expr))
2790 need_full_assumed_size = temp;
2793 if (!pure_function (expr, &name) && name)
2797 gfc_error ("reference to non-PURE function '%s' at %L inside a "
2798 "FORALL %s", name, &expr->where,
2799 forall_flag == 2 ? "mask" : "block");
2802 else if (gfc_pure (NULL))
2804 gfc_error ("Function reference to '%s' at %L is to a non-PURE "
2805 "procedure within a PURE procedure", name, &expr->where);
2810 /* Functions without the RECURSIVE attribution are not allowed to
2811 * call themselves. */
2812 if (expr->value.function.esym && !expr->value.function.esym->attr.recursive)
2815 esym = expr->value.function.esym;
2817 if (is_illegal_recursion (esym, gfc_current_ns))
2819 if (esym->attr.entry && esym->ns->entries)
2820 gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
2821 " function '%s' is not RECURSIVE",
2822 esym->name, &expr->where, esym->ns->entries->sym->name);
2824 gfc_error ("Function '%s' at %L cannot be called recursively, as it"
2825 " is not RECURSIVE", esym->name, &expr->where);
2831 /* Character lengths of use associated functions may contains references to
2832 symbols not referenced from the current program unit otherwise. Make sure
2833 those symbols are marked as referenced. */
2835 if (expr->ts.type == BT_CHARACTER && expr->value.function.esym
2836 && expr->value.function.esym->attr.use_assoc)
2838 gfc_expr_set_symbols_referenced (expr->ts.u.cl->length);
2842 && !((expr->value.function.esym
2843 && expr->value.function.esym->attr.elemental)
2845 (expr->value.function.isym
2846 && expr->value.function.isym->elemental)))
2847 find_noncopying_intrinsics (expr->value.function.esym,
2848 expr->value.function.actual);
2850 /* Make sure that the expression has a typespec that works. */
2851 if (expr->ts.type == BT_UNKNOWN)
2853 if (expr->symtree->n.sym->result
2854 && expr->symtree->n.sym->result->ts.type != BT_UNKNOWN
2855 && !expr->symtree->n.sym->result->attr.proc_pointer)
2856 expr->ts = expr->symtree->n.sym->result->ts;
2863 /************* Subroutine resolution *************/
2866 pure_subroutine (gfc_code *c, gfc_symbol *sym)
2872 gfc_error ("Subroutine call to '%s' in FORALL block at %L is not PURE",
2873 sym->name, &c->loc);
2874 else if (gfc_pure (NULL))
2875 gfc_error ("Subroutine call to '%s' at %L is not PURE", sym->name,
2881 resolve_generic_s0 (gfc_code *c, gfc_symbol *sym)
2885 if (sym->attr.generic)
2887 s = gfc_search_interface (sym->generic, 1, &c->ext.actual);
2890 c->resolved_sym = s;
2891 pure_subroutine (c, s);
2895 /* TODO: Need to search for elemental references in generic interface. */
2898 if (sym->attr.intrinsic)
2899 return gfc_intrinsic_sub_interface (c, 0);
2906 resolve_generic_s (gfc_code *c)
2911 sym = c->symtree->n.sym;
2915 m = resolve_generic_s0 (c, sym);
2918 else if (m == MATCH_ERROR)
2922 if (sym->ns->parent == NULL)
2924 gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2928 if (!generic_sym (sym))
2932 /* Last ditch attempt. See if the reference is to an intrinsic
2933 that possesses a matching interface. 14.1.2.4 */
2934 sym = c->symtree->n.sym;
2936 if (!gfc_is_intrinsic (sym, 1, c->loc))
2938 gfc_error ("There is no specific subroutine for the generic '%s' at %L",
2939 sym->name, &c->loc);
2943 m = gfc_intrinsic_sub_interface (c, 0);
2947 gfc_error ("Generic subroutine '%s' at %L is not consistent with an "
2948 "intrinsic subroutine interface", sym->name, &c->loc);
2954 /* Set the name and binding label of the subroutine symbol in the call
2955 expression represented by 'c' to include the type and kind of the
2956 second parameter. This function is for resolving the appropriate
2957 version of c_f_pointer() and c_f_procpointer(). For example, a
2958 call to c_f_pointer() for a default integer pointer could have a
2959 name of c_f_pointer_i4. If no second arg exists, which is an error
2960 for these two functions, it defaults to the generic symbol's name
2961 and binding label. */
2964 set_name_and_label (gfc_code *c, gfc_symbol *sym,
2965 char *name, char *binding_label)
2967 gfc_expr *arg = NULL;
2971 /* The second arg of c_f_pointer and c_f_procpointer determines
2972 the type and kind for the procedure name. */
2973 arg = c->ext.actual->next->expr;
2977 /* Set up the name to have the given symbol's name,
2978 plus the type and kind. */
2979 /* a derived type is marked with the type letter 'u' */
2980 if (arg->ts.type == BT_DERIVED)
2983 kind = 0; /* set the kind as 0 for now */
2987 type = gfc_type_letter (arg->ts.type);
2988 kind = arg->ts.kind;
2991 if (arg->ts.type == BT_CHARACTER)
2992 /* Kind info for character strings not needed. */
2995 sprintf (name, "%s_%c%d", sym->name, type, kind);
2996 /* Set up the binding label as the given symbol's label plus
2997 the type and kind. */
2998 sprintf (binding_label, "%s_%c%d", sym->binding_label, type, kind);
3002 /* If the second arg is missing, set the name and label as
3003 was, cause it should at least be found, and the missing
3004 arg error will be caught by compare_parameters(). */
3005 sprintf (name, "%s", sym->name);
3006 sprintf (binding_label, "%s", sym->binding_label);
3013 /* Resolve a generic version of the iso_c_binding procedure given
3014 (sym) to the specific one based on the type and kind of the
3015 argument(s). Currently, this function resolves c_f_pointer() and
3016 c_f_procpointer based on the type and kind of the second argument
3017 (FPTR). Other iso_c_binding procedures aren't specially handled.
3018 Upon successfully exiting, c->resolved_sym will hold the resolved
3019 symbol. Returns MATCH_ERROR if an error occurred; MATCH_YES
3023 gfc_iso_c_sub_interface (gfc_code *c, gfc_symbol *sym)
3025 gfc_symbol *new_sym;
3026 /* this is fine, since we know the names won't use the max */
3027 char name[GFC_MAX_SYMBOL_LEN + 1];
3028 char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
3029 /* default to success; will override if find error */
3030 match m = MATCH_YES;
3032 /* Make sure the actual arguments are in the necessary order (based on the
3033 formal args) before resolving. */
3034 gfc_procedure_use (sym, &c->ext.actual, &(c->loc));
3036 if ((sym->intmod_sym_id == ISOCBINDING_F_POINTER) ||
3037 (sym->intmod_sym_id == ISOCBINDING_F_PROCPOINTER))
3039 set_name_and_label (c, sym, name, binding_label);
3041 if (sym->intmod_sym_id == ISOCBINDING_F_POINTER)
3043 if (c->ext.actual != NULL && c->ext.actual->next != NULL)
3045 /* Make sure we got a third arg if the second arg has non-zero
3046 rank. We must also check that the type and rank are
3047 correct since we short-circuit this check in
3048 gfc_procedure_use() (called above to sort actual args). */
3049 if (c->ext.actual->next->expr->rank != 0)
3051 if(c->ext.actual->next->next == NULL
3052 || c->ext.actual->next->next->expr == NULL)
3055 gfc_error ("Missing SHAPE parameter for call to %s "
3056 "at %L", sym->name, &(c->loc));
3058 else if (c->ext.actual->next->next->expr->ts.type
3060 || c->ext.actual->next->next->expr->rank != 1)
3063 gfc_error ("SHAPE parameter for call to %s at %L must "
3064 "be a rank 1 INTEGER array", sym->name,
3071 if (m != MATCH_ERROR)
3073 /* the 1 means to add the optional arg to formal list */
3074 new_sym = get_iso_c_sym (sym, name, binding_label, 1);
3076 /* for error reporting, say it's declared where the original was */
3077 new_sym->declared_at = sym->declared_at;
3082 /* no differences for c_loc or c_funloc */
3086 /* set the resolved symbol */
3087 if (m != MATCH_ERROR)
3088 c->resolved_sym = new_sym;
3090 c->resolved_sym = sym;
3096 /* Resolve a subroutine call known to be specific. */
3099 resolve_specific_s0 (gfc_code *c, gfc_symbol *sym)
3103 if(sym->attr.is_iso_c)
3105 m = gfc_iso_c_sub_interface (c,sym);
3109 if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
3111 if (sym->attr.dummy)
3113 sym->attr.proc = PROC_DUMMY;
3117 sym->attr.proc = PROC_EXTERNAL;
3121 if (sym->attr.proc == PROC_MODULE || sym->attr.proc == PROC_INTERNAL)
3124 if (sym->attr.intrinsic)
3126 m = gfc_intrinsic_sub_interface (c, 1);
3130 gfc_error ("Subroutine '%s' at %L is INTRINSIC but is not compatible "
3131 "with an intrinsic", sym->name, &c->loc);
3139 gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3141 c->resolved_sym = sym;
3142 pure_subroutine (c, sym);
3149 resolve_specific_s (gfc_code *c)
3154 sym = c->symtree->n.sym;
3158 m = resolve_specific_s0 (c, sym);
3161 if (m == MATCH_ERROR)
3164 if (sym->ns->parent == NULL)
3167 gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
3173 sym = c->symtree->n.sym;
3174 gfc_error ("Unable to resolve the specific subroutine '%s' at %L",
3175 sym->name, &c->loc);
3181 /* Resolve a subroutine call not known to be generic nor specific. */
3184 resolve_unknown_s (gfc_code *c)
3188 sym = c->symtree->n.sym;
3190 if (sym->attr.dummy)
3192 sym->attr.proc = PROC_DUMMY;
3196 /* See if we have an intrinsic function reference. */
3198 if (gfc_is_intrinsic (sym, 1, c->loc))
3200 if (gfc_intrinsic_sub_interface (c, 1) == MATCH_YES)
3205 /* The reference is to an external name. */
3208 gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3210 c->resolved_sym = sym;
3212 pure_subroutine (c, sym);
3218 /* Resolve a subroutine call. Although it was tempting to use the same code
3219 for functions, subroutines and functions are stored differently and this
3220 makes things awkward. */
3223 resolve_call (gfc_code *c)
3226 procedure_type ptype = PROC_INTRINSIC;
3227 gfc_symbol *csym, *sym;
3228 bool no_formal_args;
3230 csym = c->symtree ? c->symtree->n.sym : NULL;
3232 if (csym && csym->ts.type != BT_UNKNOWN)
3234 gfc_error ("'%s' at %L has a type, which is not consistent with "
3235 "the CALL at %L", csym->name, &csym->declared_at, &c->loc);
3239 if (csym && gfc_current_ns->parent && csym->ns != gfc_current_ns)
3242 gfc_find_sym_tree (csym->name, gfc_current_ns, 1, &st);
3243 sym = st ? st->n.sym : NULL;
3244 if (sym && csym != sym
3245 && sym->ns == gfc_current_ns
3246 && sym->attr.flavor == FL_PROCEDURE
3247 && sym->attr.contained)
3250 if (csym->attr.generic)
3251 c->symtree->n.sym = sym;
3254 csym = c->symtree->n.sym;
3258 /* If this ia a deferred TBP with an abstract interface
3259 (which may of course be referenced), c->expr1 will be set. */
3260 if (csym && csym->attr.abstract && !c->expr1)
3262 gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
3263 csym->name, &c->loc);
3267 /* Subroutines without the RECURSIVE attribution are not allowed to
3268 * call themselves. */
3269 if (csym && is_illegal_recursion (csym, gfc_current_ns))
3271 if (csym->attr.entry && csym->ns->entries)
3272 gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
3273 " subroutine '%s' is not RECURSIVE",
3274 csym->name, &c->loc, csym->ns->entries->sym->name);
3276 gfc_error ("SUBROUTINE '%s' at %L cannot be called recursively, as it"
3277 " is not RECURSIVE", csym->name, &c->loc);
3282 /* Switch off assumed size checking and do this again for certain kinds
3283 of procedure, once the procedure itself is resolved. */
3284 need_full_assumed_size++;
3287 ptype = csym->attr.proc;
3289 no_formal_args = csym && is_external_proc (csym) && csym->formal == NULL;
3290 if (resolve_actual_arglist (c->ext.actual, ptype,
3291 no_formal_args) == FAILURE)
3294 /* Resume assumed_size checking. */
3295 need_full_assumed_size--;
3297 /* If external, check for usage. */
3298 if (csym && is_external_proc (csym))
3299 resolve_global_procedure (csym, &c->loc, &c->ext.actual, 1);
3302 if (c->resolved_sym == NULL)
3304 c->resolved_isym = NULL;
3305 switch (procedure_kind (csym))
3308 t = resolve_generic_s (c);
3311 case PTYPE_SPECIFIC:
3312 t = resolve_specific_s (c);
3316 t = resolve_unknown_s (c);
3320 gfc_internal_error ("resolve_subroutine(): bad function type");
3324 /* Some checks of elemental subroutine actual arguments. */
3325 if (resolve_elemental_actual (NULL, c) == FAILURE)
3328 if (t == SUCCESS && !(c->resolved_sym && c->resolved_sym->attr.elemental))
3329 find_noncopying_intrinsics (c->resolved_sym, c->ext.actual);
3334 /* Compare the shapes of two arrays that have non-NULL shapes. If both
3335 op1->shape and op2->shape are non-NULL return SUCCESS if their shapes
3336 match. If both op1->shape and op2->shape are non-NULL return FAILURE
3337 if their shapes do not match. If either op1->shape or op2->shape is
3338 NULL, return SUCCESS. */
3341 compare_shapes (gfc_expr *op1, gfc_expr *op2)
3348 if (op1->shape != NULL && op2->shape != NULL)
3350 for (i = 0; i < op1->rank; i++)
3352 if (mpz_cmp (op1->shape[i], op2->shape[i]) != 0)
3354 gfc_error ("Shapes for operands at %L and %L are not conformable",
3355 &op1->where, &op2->where);
3366 /* Resolve an operator expression node. This can involve replacing the
3367 operation with a user defined function call. */
3370 resolve_operator (gfc_expr *e)
3372 gfc_expr *op1, *op2;
3374 bool dual_locus_error;
3377 /* Resolve all subnodes-- give them types. */
3379 switch (e->value.op.op)
3382 if (gfc_resolve_expr (e->value.op.op2) == FAILURE)
3385 /* Fall through... */
3388 case INTRINSIC_UPLUS:
3389 case INTRINSIC_UMINUS:
3390 case INTRINSIC_PARENTHESES:
3391 if (gfc_resolve_expr (e->value.op.op1) == FAILURE)
3396 /* Typecheck the new node. */
3398 op1 = e->value.op.op1;
3399 op2 = e->value.op.op2;
3400 dual_locus_error = false;
3402 if ((op1 && op1->expr_type == EXPR_NULL)
3403 || (op2 && op2->expr_type == EXPR_NULL))
3405 sprintf (msg, _("Invalid context for NULL() pointer at %%L"));
3409 switch (e->value.op.op)
3411 case INTRINSIC_UPLUS:
3412 case INTRINSIC_UMINUS:
3413 if (op1->ts.type == BT_INTEGER
3414 || op1->ts.type == BT_REAL
3415 || op1->ts.type == BT_COMPLEX)
3421 sprintf (msg, _("Operand of unary numeric operator '%s' at %%L is %s"),
3422 gfc_op2string (e->value.op.op), gfc_typename (&e->ts));
3425 case INTRINSIC_PLUS:
3426 case INTRINSIC_MINUS:
3427 case INTRINSIC_TIMES:
3428 case INTRINSIC_DIVIDE:
3429 case INTRINSIC_POWER:
3430 if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3432 gfc_type_convert_binary (e, 1);
3437 _("Operands of binary numeric operator '%s' at %%L are %s/%s"),
3438 gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3439 gfc_typename (&op2->ts));
3442 case INTRINSIC_CONCAT:
3443 if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3444 && op1->ts.kind == op2->ts.kind)
3446 e->ts.type = BT_CHARACTER;
3447 e->ts.kind = op1->ts.kind;
3452 _("Operands of string concatenation operator at %%L are %s/%s"),
3453 gfc_typename (&op1->ts), gfc_typename (&op2->ts));
3459 case INTRINSIC_NEQV:
3460 if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3462 e->ts.type = BT_LOGICAL;
3463 e->ts.kind = gfc_kind_max (op1, op2);
3464 if (op1->ts.kind < e->ts.kind)
3465 gfc_convert_type (op1, &e->ts, 2);
3466 else if (op2->ts.kind < e->ts.kind)
3467 gfc_convert_type (op2, &e->ts, 2);
3471 sprintf (msg, _("Operands of logical operator '%s' at %%L are %s/%s"),
3472 gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3473 gfc_typename (&op2->ts));
3478 if (op1->ts.type == BT_LOGICAL)
3480 e->ts.type = BT_LOGICAL;
3481 e->ts.kind = op1->ts.kind;
3485 sprintf (msg, _("Operand of .not. operator at %%L is %s"),
3486 gfc_typename (&op1->ts));
3490 case INTRINSIC_GT_OS:
3492 case INTRINSIC_GE_OS:
3494 case INTRINSIC_LT_OS:
3496 case INTRINSIC_LE_OS:
3497 if (op1->ts.type == BT_COMPLEX || op2->ts.type == BT_COMPLEX)
3499 strcpy (msg, _("COMPLEX quantities cannot be compared at %L"));
3503 /* Fall through... */
3506 case INTRINSIC_EQ_OS:
3508 case INTRINSIC_NE_OS:
3509 if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3510 && op1->ts.kind == op2->ts.kind)
3512 e->ts.type = BT_LOGICAL;
3513 e->ts.kind = gfc_default_logical_kind;
3517 if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3519 gfc_type_convert_binary (e, 1);
3521 e->ts.type = BT_LOGICAL;
3522 e->ts.kind = gfc_default_logical_kind;
3526 if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3528 _("Logicals at %%L must be compared with %s instead of %s"),
3529 (e->value.op.op == INTRINSIC_EQ
3530 || e->value.op.op == INTRINSIC_EQ_OS)
3531 ? ".eqv." : ".neqv.", gfc_op2string (e->value.op.op));
3534 _("Operands of comparison operator '%s' at %%L are %s/%s"),
3535 gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3536 gfc_typename (&op2->ts));
3540 case INTRINSIC_USER:
3541 if (e->value.op.uop->op == NULL)
3542 sprintf (msg, _("Unknown operator '%s' at %%L"), e->value.op.uop->name);
3543 else if (op2 == NULL)
3544 sprintf (msg, _("Operand of user operator '%s' at %%L is %s"),
3545 e->value.op.uop->name, gfc_typename (&op1->ts));
3547 sprintf (msg, _("Operands of user operator '%s' at %%L are %s/%s"),
3548 e->value.op.uop->name, gfc_typename (&op1->ts),
3549 gfc_typename (&op2->ts));
3553 case INTRINSIC_PARENTHESES:
3555 if (e->ts.type == BT_CHARACTER)
3556 e->ts.u.cl = op1->ts.u.cl;
3560 gfc_internal_error ("resolve_operator(): Bad intrinsic");
3563 /* Deal with arrayness of an operand through an operator. */
3567 switch (e->value.op.op)
3569 case INTRINSIC_PLUS:
3570 case INTRINSIC_MINUS:
3571 case INTRINSIC_TIMES:
3572 case INTRINSIC_DIVIDE:
3573 case INTRINSIC_POWER:
3574 case INTRINSIC_CONCAT:
3578 case INTRINSIC_NEQV:
3580 case INTRINSIC_EQ_OS:
3582 case INTRINSIC_NE_OS:
3584 case INTRINSIC_GT_OS:
3586 case INTRINSIC_GE_OS:
3588 case INTRINSIC_LT_OS:
3590 case INTRINSIC_LE_OS:
3592 if (op1->rank == 0 && op2->rank == 0)
3595 if (op1->rank == 0 && op2->rank != 0)
3597 e->rank = op2->rank;
3599 if (e->shape == NULL)
3600 e->shape = gfc_copy_shape (op2->shape, op2->rank);
3603 if (op1->rank != 0 && op2->rank == 0)
3605 e->rank = op1->rank;
3607 if (e->shape == NULL)
3608 e->shape = gfc_copy_shape (op1->shape, op1->rank);
3611 if (op1->rank != 0 && op2->rank != 0)
3613 if (op1->rank == op2->rank)
3615 e->rank = op1->rank;
3616 if (e->shape == NULL)
3618 t = compare_shapes(op1, op2);
3622 e->shape = gfc_copy_shape (op1->shape, op1->rank);
3627 /* Allow higher level expressions to work. */
3630 /* Try user-defined operators, and otherwise throw an error. */
3631 dual_locus_error = true;
3633 _("Inconsistent ranks for operator at %%L and %%L"));
3640 case INTRINSIC_PARENTHESES:
3642 case INTRINSIC_UPLUS:
3643 case INTRINSIC_UMINUS:
3644 /* Simply copy arrayness attribute */
3645 e->rank = op1->rank;
3647 if (e->shape == NULL)
3648 e->shape = gfc_copy_shape (op1->shape, op1->rank);
3656 /* Attempt to simplify the expression. */
3659 t = gfc_simplify_expr (e, 0);
3660 /* Some calls do not succeed in simplification and return FAILURE
3661 even though there is no error; e.g. variable references to
3662 PARAMETER arrays. */
3663 if (!gfc_is_constant_expr (e))
3672 if (gfc_extend_expr (e, &real_error) == SUCCESS)
3679 if (dual_locus_error)
3680 gfc_error (msg, &op1->where, &op2->where);
3682 gfc_error (msg, &e->where);
3688 /************** Array resolution subroutines **************/
3691 { CMP_LT, CMP_EQ, CMP_GT, CMP_UNKNOWN }
3694 /* Compare two integer expressions. */
3697 compare_bound (gfc_expr *a, gfc_expr *b)
3701 if (a == NULL || a->expr_type != EXPR_CONSTANT
3702 || b == NULL || b->expr_type != EXPR_CONSTANT)
3705 /* If either of the types isn't INTEGER, we must have
3706 raised an error earlier. */
3708 if (a->ts.type != BT_INTEGER || b->ts.type != BT_INTEGER)
3711 i = mpz_cmp (a->value.integer, b->value.integer);
3721 /* Compare an integer expression with an integer. */
3724 compare_bound_int (gfc_expr *a, int b)
3728 if (a == NULL || a->expr_type != EXPR_CONSTANT)
3731 if (a->ts.type != BT_INTEGER)
3732 gfc_internal_error ("compare_bound_int(): Bad expression");
3734 i = mpz_cmp_si (a->value.integer, b);
3744 /* Compare an integer expression with a mpz_t. */
3747 compare_bound_mpz_t (gfc_expr *a, mpz_t b)
3751 if (a == NULL || a->expr_type != EXPR_CONSTANT)
3754 if (a->ts.type != BT_INTEGER)
3755 gfc_internal_error ("compare_bound_int(): Bad expression");
3757 i = mpz_cmp (a->value.integer, b);
3767 /* Compute the last value of a sequence given by a triplet.
3768 Return 0 if it wasn't able to compute the last value, or if the
3769 sequence if empty, and 1 otherwise. */
3772 compute_last_value_for_triplet (gfc_expr *start, gfc_expr *end,
3773 gfc_expr *stride, mpz_t last)
3777 if (start == NULL || start->expr_type != EXPR_CONSTANT
3778 || end == NULL || end->expr_type != EXPR_CONSTANT
3779 || (stride != NULL && stride->expr_type != EXPR_CONSTANT))
3782 if (start->ts.type != BT_INTEGER || end->ts.type != BT_INTEGER
3783 || (stride != NULL && stride->ts.type != BT_INTEGER))
3786 if (stride == NULL || compare_bound_int(stride, 1) == CMP_EQ)
3788 if (compare_bound (start, end) == CMP_GT)
3790 mpz_set (last, end->value.integer);
3794 if (compare_bound_int (stride, 0) == CMP_GT)
3796 /* Stride is positive */
3797 if (mpz_cmp (start->value.integer, end->value.integer) > 0)
3802 /* Stride is negative */
3803 if (mpz_cmp (start->value.integer, end->value.integer) < 0)
3808 mpz_sub (rem, end->value.integer, start->value.integer);
3809 mpz_tdiv_r (rem, rem, stride->value.integer);
3810 mpz_sub (last, end->value.integer, rem);
3817 /* Compare a single dimension of an array reference to the array
3821 check_dimension (int i, gfc_array_ref *ar, gfc_array_spec *as)
3825 if (ar->dimen_type[i] == DIMEN_STAR)
3827 gcc_assert (ar->stride[i] == NULL);
3828 /* This implies [*] as [*:] and [*:3] are not possible. */
3829 if (ar->start[i] == NULL)
3831 gcc_assert (ar->end[i] == NULL);
3836 /* Given start, end and stride values, calculate the minimum and
3837 maximum referenced indexes. */
3839 switch (ar->dimen_type[i])
3846 if (compare_bound (ar->start[i], as->lower[i]) == CMP_LT)
3849 gfc_warning ("Array reference at %L is out of bounds "
3850 "(%ld < %ld) in dimension %d", &ar->c_where[i],
3851 mpz_get_si (ar->start[i]->value.integer),
3852 mpz_get_si (as->lower[i]->value.integer), i+1);
3854 gfc_warning ("Array reference at %L is out of bounds "
3855 "(%ld < %ld) in codimension %d", &ar->c_where[i],
3856 mpz_get_si (ar->start[i]->value.integer),
3857 mpz_get_si (as->lower[i]->value.integer),
3861 if (compare_bound (ar->start[i], as->upper[i]) == CMP_GT)
3864 gfc_warning ("Array reference at %L is out of bounds "
3865 "(%ld > %ld) in dimension %d", &ar->c_where[i],
3866 mpz_get_si (ar->start[i]->value.integer),
3867 mpz_get_si (as->upper[i]->value.integer), i+1);
3869 gfc_warning ("Array reference at %L is out of bounds "
3870 "(%ld > %ld) in codimension %d", &ar->c_where[i],
3871 mpz_get_si (ar->start[i]->value.integer),
3872 mpz_get_si (as->upper[i]->value.integer),
3881 #define AR_START (ar->start[i] ? ar->start[i] : as->lower[i])
3882 #define AR_END (ar->end[i] ? ar->end[i] : as->upper[i])
3884 comparison comp_start_end = compare_bound (AR_START, AR_END);
3886 /* Check for zero stride, which is not allowed. */
3887 if (compare_bound_int (ar->stride[i], 0) == CMP_EQ)
3889 gfc_error ("Illegal stride of zero at %L", &ar->c_where[i]);
3893 /* if start == len || (stride > 0 && start < len)
3894 || (stride < 0 && start > len),
3895 then the array section contains at least one element. In this
3896 case, there is an out-of-bounds access if
3897 (start < lower || start > upper). */
3898 if (compare_bound (AR_START, AR_END) == CMP_EQ
3899 || ((compare_bound_int (ar->stride[i], 0) == CMP_GT
3900 || ar->stride[i] == NULL) && comp_start_end == CMP_LT)
3901 || (compare_bound_int (ar->stride[i], 0) == CMP_LT
3902 && comp_start_end == CMP_GT))
3904 if (compare_bound (AR_START, as->lower[i]) == CMP_LT)
3906 gfc_warning ("Lower array reference at %L is out of bounds "
3907 "(%ld < %ld) in dimension %d", &ar->c_where[i],
3908 mpz_get_si (AR_START->value.integer),
3909 mpz_get_si (as->lower[i]->value.integer), i+1);
3912 if (compare_bound (AR_START, as->upper[i]) == CMP_GT)
3914 gfc_warning ("Lower array reference at %L is out of bounds "
3915 "(%ld > %ld) in dimension %d", &ar->c_where[i],
3916 mpz_get_si (AR_START->value.integer),
3917 mpz_get_si (as->upper[i]->value.integer), i+1);
3922 /* If we can compute the highest index of the array section,
3923 then it also has to be between lower and upper. */
3924 mpz_init (last_value);
3925 if (compute_last_value_for_triplet (AR_START, AR_END, ar->stride[i],
3928 if (compare_bound_mpz_t (as->lower[i], last_value) == CMP_GT)
3930 gfc_warning ("Upper array reference at %L is out of bounds "
3931 "(%ld < %ld) in dimension %d", &ar->c_where[i],
3932 mpz_get_si (last_value),
3933 mpz_get_si (as->lower[i]->value.integer), i+1);
3934 mpz_clear (last_value);
3937 if (compare_bound_mpz_t (as->upper[i], last_value) == CMP_LT)
3939 gfc_warning ("Upper array reference at %L is out of bounds "
3940 "(%ld > %ld) in dimension %d", &ar->c_where[i],
3941 mpz_get_si (last_value),
3942 mpz_get_si (as->upper[i]->value.integer), i+1);
3943 mpz_clear (last_value);
3947 mpz_clear (last_value);
3955 gfc_internal_error ("check_dimension(): Bad array reference");
3962 /* Compare an array reference with an array specification. */
3965 compare_spec_to_ref (gfc_array_ref *ar)