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;
707 has_default_initializer (gfc_symbol *der)
711 gcc_assert (der->attr.flavor == FL_DERIVED);
712 for (c = der->components; c; c = c->next)
713 if ((c->ts.type != BT_DERIVED && c->initializer)
714 || (c->ts.type == BT_DERIVED
715 && (!c->attr.pointer && has_default_initializer (c->ts.u.derived))))
721 /* Resolve common variables. */
723 resolve_common_vars (gfc_symbol *sym, bool named_common)
725 gfc_symbol *csym = sym;
727 for (; csym; csym = csym->common_next)
729 if (csym->value || csym->attr.data)
731 if (!csym->ns->is_block_data)
732 gfc_notify_std (GFC_STD_GNU, "Variable '%s' at %L is in COMMON "
733 "but only in BLOCK DATA initialization is "
734 "allowed", csym->name, &csym->declared_at);
735 else if (!named_common)
736 gfc_notify_std (GFC_STD_GNU, "Initialized variable '%s' at %L is "
737 "in a blank COMMON but initialization is only "
738 "allowed in named common blocks", csym->name,
742 if (csym->ts.type != BT_DERIVED)
745 if (!(csym->ts.u.derived->attr.sequence
746 || csym->ts.u.derived->attr.is_bind_c))
747 gfc_error_now ("Derived type variable '%s' in COMMON at %L "
748 "has neither the SEQUENCE nor the BIND(C) "
749 "attribute", csym->name, &csym->declared_at);
750 if (csym->ts.u.derived->attr.alloc_comp)
751 gfc_error_now ("Derived type variable '%s' in COMMON at %L "
752 "has an ultimate component that is "
753 "allocatable", csym->name, &csym->declared_at);
754 if (has_default_initializer (csym->ts.u.derived))
755 gfc_error_now ("Derived type variable '%s' in COMMON at %L "
756 "may not have default initializer", csym->name,
759 if (csym->attr.flavor == FL_UNKNOWN && !csym->attr.proc_pointer)
760 gfc_add_flavor (&csym->attr, FL_VARIABLE, csym->name, &csym->declared_at);
764 /* Resolve common blocks. */
766 resolve_common_blocks (gfc_symtree *common_root)
770 if (common_root == NULL)
773 if (common_root->left)
774 resolve_common_blocks (common_root->left);
775 if (common_root->right)
776 resolve_common_blocks (common_root->right);
778 resolve_common_vars (common_root->n.common->head, true);
780 gfc_find_symbol (common_root->name, gfc_current_ns, 0, &sym);
784 if (sym->attr.flavor == FL_PARAMETER)
785 gfc_error ("COMMON block '%s' at %L is used as PARAMETER at %L",
786 sym->name, &common_root->n.common->where, &sym->declared_at);
788 if (sym->attr.intrinsic)
789 gfc_error ("COMMON block '%s' at %L is also an intrinsic procedure",
790 sym->name, &common_root->n.common->where);
791 else if (sym->attr.result
792 || gfc_is_function_return_value (sym, gfc_current_ns))
793 gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
794 "that is also a function result", sym->name,
795 &common_root->n.common->where);
796 else if (sym->attr.flavor == FL_PROCEDURE && sym->attr.proc != PROC_INTERNAL
797 && sym->attr.proc != PROC_ST_FUNCTION)
798 gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
799 "that is also a global procedure", sym->name,
800 &common_root->n.common->where);
804 /* Resolve contained function types. Because contained functions can call one
805 another, they have to be worked out before any of the contained procedures
808 The good news is that if a function doesn't already have a type, the only
809 way it can get one is through an IMPLICIT type or a RESULT variable, because
810 by definition contained functions are contained namespace they're contained
811 in, not in a sibling or parent namespace. */
814 resolve_contained_functions (gfc_namespace *ns)
816 gfc_namespace *child;
819 resolve_formal_arglists (ns);
821 for (child = ns->contained; child; child = child->sibling)
823 /* Resolve alternate entry points first. */
824 resolve_entries (child);
826 /* Then check function return types. */
827 resolve_contained_fntype (child->proc_name, child);
828 for (el = child->entries; el; el = el->next)
829 resolve_contained_fntype (el->sym, child);
834 /* Resolve all of the elements of a structure constructor and make sure that
835 the types are correct. */
838 resolve_structure_cons (gfc_expr *expr)
840 gfc_constructor *cons;
846 cons = gfc_constructor_first (expr->value.constructor);
847 /* A constructor may have references if it is the result of substituting a
848 parameter variable. In this case we just pull out the component we
851 comp = expr->ref->u.c.sym->components;
853 comp = expr->ts.u.derived->components;
855 /* See if the user is trying to invoke a structure constructor for one of
856 the iso_c_binding derived types. */
857 if (expr->ts.type == BT_DERIVED && expr->ts.u.derived
858 && expr->ts.u.derived->ts.is_iso_c && cons
859 && (cons->expr == NULL || cons->expr->expr_type != EXPR_NULL))
861 gfc_error ("Components of structure constructor '%s' at %L are PRIVATE",
862 expr->ts.u.derived->name, &(expr->where));
866 /* Return if structure constructor is c_null_(fun)prt. */
867 if (expr->ts.type == BT_DERIVED && expr->ts.u.derived
868 && expr->ts.u.derived->ts.is_iso_c && cons
869 && cons->expr && cons->expr->expr_type == EXPR_NULL)
872 for (; comp && cons; comp = comp->next, cons = gfc_constructor_next (cons))
879 if (gfc_resolve_expr (cons->expr) == FAILURE)
885 rank = comp->as ? comp->as->rank : 0;
886 if (cons->expr->expr_type != EXPR_NULL && rank != cons->expr->rank
887 && (comp->attr.allocatable || cons->expr->rank))
889 gfc_error ("The rank of the element in the derived type "
890 "constructor at %L does not match that of the "
891 "component (%d/%d)", &cons->expr->where,
892 cons->expr->rank, rank);
896 /* If we don't have the right type, try to convert it. */
898 if (!gfc_compare_types (&cons->expr->ts, &comp->ts))
901 if (strcmp (comp->name, "$extends") == 0)
903 /* Can afford to be brutal with the $extends initializer.
904 The derived type can get lost because it is PRIVATE
905 but it is not usage constrained by the standard. */
906 cons->expr->ts = comp->ts;
909 else if (comp->attr.pointer && cons->expr->ts.type != BT_UNKNOWN)
910 gfc_error ("The element in the derived type constructor at %L, "
911 "for pointer component '%s', is %s but should be %s",
912 &cons->expr->where, comp->name,
913 gfc_basic_typename (cons->expr->ts.type),
914 gfc_basic_typename (comp->ts.type));
916 t = gfc_convert_type (cons->expr, &comp->ts, 1);
919 if (cons->expr->expr_type == EXPR_NULL
920 && !(comp->attr.pointer || comp->attr.allocatable
921 || comp->attr.proc_pointer
922 || (comp->ts.type == BT_CLASS
923 && (comp->ts.u.derived->components->attr.pointer
924 || comp->ts.u.derived->components->attr.allocatable))))
927 gfc_error ("The NULL in the derived type constructor at %L is "
928 "being applied to component '%s', which is neither "
929 "a POINTER nor ALLOCATABLE", &cons->expr->where,
933 if (!comp->attr.pointer || cons->expr->expr_type == EXPR_NULL)
936 a = gfc_expr_attr (cons->expr);
938 if (!a.pointer && !a.target)
941 gfc_error ("The element in the derived type constructor at %L, "
942 "for pointer component '%s' should be a POINTER or "
943 "a TARGET", &cons->expr->where, comp->name);
946 /* F2003, C1272 (3). */
947 if (gfc_pure (NULL) && cons->expr->expr_type == EXPR_VARIABLE
948 && (gfc_impure_variable (cons->expr->symtree->n.sym)
949 || gfc_is_coindexed (cons->expr)))
952 gfc_error ("Invalid expression in the derived type constructor for "
953 "pointer component '%s' at %L in PURE procedure",
954 comp->name, &cons->expr->where);
962 /****************** Expression name resolution ******************/
964 /* Returns 0 if a symbol was not declared with a type or
965 attribute declaration statement, nonzero otherwise. */
968 was_declared (gfc_symbol *sym)
974 if (!a.implicit_type && sym->ts.type != BT_UNKNOWN)
977 if (a.allocatable || a.dimension || a.dummy || a.external || a.intrinsic
978 || a.optional || a.pointer || a.save || a.target || a.volatile_
979 || a.value || a.access != ACCESS_UNKNOWN || a.intent != INTENT_UNKNOWN
980 || a.asynchronous || a.codimension)
987 /* Determine if a symbol is generic or not. */
990 generic_sym (gfc_symbol *sym)
994 if (sym->attr.generic ||
995 (sym->attr.intrinsic && gfc_generic_intrinsic (sym->name)))
998 if (was_declared (sym) || sym->ns->parent == NULL)
1001 gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
1008 return generic_sym (s);
1015 /* Determine if a symbol is specific or not. */
1018 specific_sym (gfc_symbol *sym)
1022 if (sym->attr.if_source == IFSRC_IFBODY
1023 || sym->attr.proc == PROC_MODULE
1024 || sym->attr.proc == PROC_INTERNAL
1025 || sym->attr.proc == PROC_ST_FUNCTION
1026 || (sym->attr.intrinsic && gfc_specific_intrinsic (sym->name))
1027 || sym->attr.external)
1030 if (was_declared (sym) || sym->ns->parent == NULL)
1033 gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
1035 return (s == NULL) ? 0 : specific_sym (s);
1039 /* Figure out if the procedure is specific, generic or unknown. */
1042 { PTYPE_GENERIC = 1, PTYPE_SPECIFIC, PTYPE_UNKNOWN }
1046 procedure_kind (gfc_symbol *sym)
1048 if (generic_sym (sym))
1049 return PTYPE_GENERIC;
1051 if (specific_sym (sym))
1052 return PTYPE_SPECIFIC;
1054 return PTYPE_UNKNOWN;
1057 /* Check references to assumed size arrays. The flag need_full_assumed_size
1058 is nonzero when matching actual arguments. */
1060 static int need_full_assumed_size = 0;
1063 check_assumed_size_reference (gfc_symbol *sym, gfc_expr *e)
1065 if (need_full_assumed_size || !(sym->as && sym->as->type == AS_ASSUMED_SIZE))
1068 /* FIXME: The comparison "e->ref->u.ar.type == AR_FULL" is wrong.
1069 What should it be? */
1070 if ((e->ref->u.ar.end[e->ref->u.ar.as->rank - 1] == NULL)
1071 && (e->ref->u.ar.as->type == AS_ASSUMED_SIZE)
1072 && (e->ref->u.ar.type == AR_FULL))
1074 gfc_error ("The upper bound in the last dimension must "
1075 "appear in the reference to the assumed size "
1076 "array '%s' at %L", sym->name, &e->where);
1083 /* Look for bad assumed size array references in argument expressions
1084 of elemental and array valued intrinsic procedures. Since this is
1085 called from procedure resolution functions, it only recurses at
1089 resolve_assumed_size_actual (gfc_expr *e)
1094 switch (e->expr_type)
1097 if (e->symtree && check_assumed_size_reference (e->symtree->n.sym, e))
1102 if (resolve_assumed_size_actual (e->value.op.op1)
1103 || resolve_assumed_size_actual (e->value.op.op2))
1114 /* Check a generic procedure, passed as an actual argument, to see if
1115 there is a matching specific name. If none, it is an error, and if
1116 more than one, the reference is ambiguous. */
1118 count_specific_procs (gfc_expr *e)
1125 sym = e->symtree->n.sym;
1127 for (p = sym->generic; p; p = p->next)
1128 if (strcmp (sym->name, p->sym->name) == 0)
1130 e->symtree = gfc_find_symtree (p->sym->ns->sym_root,
1136 gfc_error ("'%s' at %L is ambiguous", e->symtree->n.sym->name,
1140 gfc_error ("GENERIC procedure '%s' is not allowed as an actual "
1141 "argument at %L", sym->name, &e->where);
1147 /* See if a call to sym could possibly be a not allowed RECURSION because of
1148 a missing RECURIVE declaration. This means that either sym is the current
1149 context itself, or sym is the parent of a contained procedure calling its
1150 non-RECURSIVE containing procedure.
1151 This also works if sym is an ENTRY. */
1154 is_illegal_recursion (gfc_symbol* sym, gfc_namespace* context)
1156 gfc_symbol* proc_sym;
1157 gfc_symbol* context_proc;
1158 gfc_namespace* real_context;
1160 if (sym->attr.flavor == FL_PROGRAM)
1163 gcc_assert (sym->attr.flavor == FL_PROCEDURE);
1165 /* If we've got an ENTRY, find real procedure. */
1166 if (sym->attr.entry && sym->ns->entries)
1167 proc_sym = sym->ns->entries->sym;
1171 /* If sym is RECURSIVE, all is well of course. */
1172 if (proc_sym->attr.recursive || gfc_option.flag_recursive)
1175 /* Find the context procedure's "real" symbol if it has entries.
1176 We look for a procedure symbol, so recurse on the parents if we don't
1177 find one (like in case of a BLOCK construct). */
1178 for (real_context = context; ; real_context = real_context->parent)
1180 /* We should find something, eventually! */
1181 gcc_assert (real_context);
1183 context_proc = (real_context->entries ? real_context->entries->sym
1184 : real_context->proc_name);
1186 /* In some special cases, there may not be a proc_name, like for this
1188 real(bad_kind()) function foo () ...
1189 when checking the call to bad_kind ().
1190 In these cases, we simply return here and assume that the
1195 if (context_proc->attr.flavor != FL_LABEL)
1199 /* A call from sym's body to itself is recursion, of course. */
1200 if (context_proc == proc_sym)
1203 /* The same is true if context is a contained procedure and sym the
1205 if (context_proc->attr.contained)
1207 gfc_symbol* parent_proc;
1209 gcc_assert (context->parent);
1210 parent_proc = (context->parent->entries ? context->parent->entries->sym
1211 : context->parent->proc_name);
1213 if (parent_proc == proc_sym)
1221 /* Resolve an intrinsic procedure: Set its function/subroutine attribute,
1222 its typespec and formal argument list. */
1225 resolve_intrinsic (gfc_symbol *sym, locus *loc)
1227 gfc_intrinsic_sym* isym;
1233 /* We already know this one is an intrinsic, so we don't call
1234 gfc_is_intrinsic for full checking but rather use gfc_find_function and
1235 gfc_find_subroutine directly to check whether it is a function or
1238 if ((isym = gfc_find_function (sym->name)))
1240 if (sym->ts.type != BT_UNKNOWN && gfc_option.warn_surprising
1241 && !sym->attr.implicit_type)
1242 gfc_warning ("Type specified for intrinsic function '%s' at %L is"
1243 " ignored", sym->name, &sym->declared_at);
1245 if (!sym->attr.function &&
1246 gfc_add_function (&sym->attr, sym->name, loc) == FAILURE)
1251 else if ((isym = gfc_find_subroutine (sym->name)))
1253 if (sym->ts.type != BT_UNKNOWN && !sym->attr.implicit_type)
1255 gfc_error ("Intrinsic subroutine '%s' at %L shall not have a type"
1256 " specifier", sym->name, &sym->declared_at);
1260 if (!sym->attr.subroutine &&
1261 gfc_add_subroutine (&sym->attr, sym->name, loc) == FAILURE)
1266 gfc_error ("'%s' declared INTRINSIC at %L does not exist", sym->name,
1271 gfc_copy_formal_args_intr (sym, isym);
1273 /* Check it is actually available in the standard settings. */
1274 if (gfc_check_intrinsic_standard (isym, &symstd, false, sym->declared_at)
1277 gfc_error ("The intrinsic '%s' declared INTRINSIC at %L is not"
1278 " available in the current standard settings but %s. Use"
1279 " an appropriate -std=* option or enable -fall-intrinsics"
1280 " in order to use it.",
1281 sym->name, &sym->declared_at, symstd);
1289 /* Resolve a procedure expression, like passing it to a called procedure or as
1290 RHS for a procedure pointer assignment. */
1293 resolve_procedure_expression (gfc_expr* expr)
1297 if (expr->expr_type != EXPR_VARIABLE)
1299 gcc_assert (expr->symtree);
1301 sym = expr->symtree->n.sym;
1303 if (sym->attr.intrinsic)
1304 resolve_intrinsic (sym, &expr->where);
1306 if (sym->attr.flavor != FL_PROCEDURE
1307 || (sym->attr.function && sym->result == sym))
1310 /* A non-RECURSIVE procedure that is used as procedure expression within its
1311 own body is in danger of being called recursively. */
1312 if (is_illegal_recursion (sym, gfc_current_ns))
1313 gfc_warning ("Non-RECURSIVE procedure '%s' at %L is possibly calling"
1314 " itself recursively. Declare it RECURSIVE or use"
1315 " -frecursive", sym->name, &expr->where);
1321 /* Resolve an actual argument list. Most of the time, this is just
1322 resolving the expressions in the list.
1323 The exception is that we sometimes have to decide whether arguments
1324 that look like procedure arguments are really simple variable
1328 resolve_actual_arglist (gfc_actual_arglist *arg, procedure_type ptype,
1329 bool no_formal_args)
1332 gfc_symtree *parent_st;
1334 int save_need_full_assumed_size;
1335 gfc_component *comp;
1337 for (; arg; arg = arg->next)
1342 /* Check the label is a valid branching target. */
1345 if (arg->label->defined == ST_LABEL_UNKNOWN)
1347 gfc_error ("Label %d referenced at %L is never defined",
1348 arg->label->value, &arg->label->where);
1355 if (gfc_is_proc_ptr_comp (e, &comp))
1358 if (e->expr_type == EXPR_PPC)
1360 if (comp->as != NULL)
1361 e->rank = comp->as->rank;
1362 e->expr_type = EXPR_FUNCTION;
1364 if (gfc_resolve_expr (e) == FAILURE)
1369 if (e->expr_type == EXPR_VARIABLE
1370 && e->symtree->n.sym->attr.generic
1372 && count_specific_procs (e) != 1)
1375 if (e->ts.type != BT_PROCEDURE)
1377 save_need_full_assumed_size = need_full_assumed_size;
1378 if (e->expr_type != EXPR_VARIABLE)
1379 need_full_assumed_size = 0;
1380 if (gfc_resolve_expr (e) != SUCCESS)
1382 need_full_assumed_size = save_need_full_assumed_size;
1386 /* See if the expression node should really be a variable reference. */
1388 sym = e->symtree->n.sym;
1390 if (sym->attr.flavor == FL_PROCEDURE
1391 || sym->attr.intrinsic
1392 || sym->attr.external)
1396 /* If a procedure is not already determined to be something else
1397 check if it is intrinsic. */
1398 if (!sym->attr.intrinsic
1399 && !(sym->attr.external || sym->attr.use_assoc
1400 || sym->attr.if_source == IFSRC_IFBODY)
1401 && gfc_is_intrinsic (sym, sym->attr.subroutine, e->where))
1402 sym->attr.intrinsic = 1;
1404 if (sym->attr.proc == PROC_ST_FUNCTION)
1406 gfc_error ("Statement function '%s' at %L is not allowed as an "
1407 "actual argument", sym->name, &e->where);
1410 actual_ok = gfc_intrinsic_actual_ok (sym->name,
1411 sym->attr.subroutine);
1412 if (sym->attr.intrinsic && actual_ok == 0)
1414 gfc_error ("Intrinsic '%s' at %L is not allowed as an "
1415 "actual argument", sym->name, &e->where);
1418 if (sym->attr.contained && !sym->attr.use_assoc
1419 && sym->ns->proc_name->attr.flavor != FL_MODULE)
1421 gfc_error ("Internal procedure '%s' is not allowed as an "
1422 "actual argument at %L", sym->name, &e->where);
1425 if (sym->attr.elemental && !sym->attr.intrinsic)
1427 gfc_error ("ELEMENTAL non-INTRINSIC procedure '%s' is not "
1428 "allowed as an actual argument at %L", sym->name,
1432 /* Check if a generic interface has a specific procedure
1433 with the same name before emitting an error. */
1434 if (sym->attr.generic && count_specific_procs (e) != 1)
1437 /* Just in case a specific was found for the expression. */
1438 sym = e->symtree->n.sym;
1440 /* If the symbol is the function that names the current (or
1441 parent) scope, then we really have a variable reference. */
1443 if (gfc_is_function_return_value (sym, sym->ns))
1446 /* If all else fails, see if we have a specific intrinsic. */
1447 if (sym->ts.type == BT_UNKNOWN && sym->attr.intrinsic)
1449 gfc_intrinsic_sym *isym;
1451 isym = gfc_find_function (sym->name);
1452 if (isym == NULL || !isym->specific)
1454 gfc_error ("Unable to find a specific INTRINSIC procedure "
1455 "for the reference '%s' at %L", sym->name,
1460 sym->attr.intrinsic = 1;
1461 sym->attr.function = 1;
1464 if (gfc_resolve_expr (e) == FAILURE)
1469 /* See if the name is a module procedure in a parent unit. */
1471 if (was_declared (sym) || sym->ns->parent == NULL)
1474 if (gfc_find_sym_tree (sym->name, sym->ns->parent, 1, &parent_st))
1476 gfc_error ("Symbol '%s' at %L is ambiguous", sym->name, &e->where);
1480 if (parent_st == NULL)
1483 sym = parent_st->n.sym;
1484 e->symtree = parent_st; /* Point to the right thing. */
1486 if (sym->attr.flavor == FL_PROCEDURE
1487 || sym->attr.intrinsic
1488 || sym->attr.external)
1490 if (gfc_resolve_expr (e) == FAILURE)
1496 e->expr_type = EXPR_VARIABLE;
1498 if (sym->as != NULL)
1500 e->rank = sym->as->rank;
1501 e->ref = gfc_get_ref ();
1502 e->ref->type = REF_ARRAY;
1503 e->ref->u.ar.type = AR_FULL;
1504 e->ref->u.ar.as = sym->as;
1507 /* Expressions are assigned a default ts.type of BT_PROCEDURE in
1508 primary.c (match_actual_arg). If above code determines that it
1509 is a variable instead, it needs to be resolved as it was not
1510 done at the beginning of this function. */
1511 save_need_full_assumed_size = need_full_assumed_size;
1512 if (e->expr_type != EXPR_VARIABLE)
1513 need_full_assumed_size = 0;
1514 if (gfc_resolve_expr (e) != SUCCESS)
1516 need_full_assumed_size = save_need_full_assumed_size;
1519 /* Check argument list functions %VAL, %LOC and %REF. There is
1520 nothing to do for %REF. */
1521 if (arg->name && arg->name[0] == '%')
1523 if (strncmp ("%VAL", arg->name, 4) == 0)
1525 if (e->ts.type == BT_CHARACTER || e->ts.type == BT_DERIVED)
1527 gfc_error ("By-value argument at %L is not of numeric "
1534 gfc_error ("By-value argument at %L cannot be an array or "
1535 "an array section", &e->where);
1539 /* Intrinsics are still PROC_UNKNOWN here. However,
1540 since same file external procedures are not resolvable
1541 in gfortran, it is a good deal easier to leave them to
1543 if (ptype != PROC_UNKNOWN
1544 && ptype != PROC_DUMMY
1545 && ptype != PROC_EXTERNAL
1546 && ptype != PROC_MODULE)
1548 gfc_error ("By-value argument at %L is not allowed "
1549 "in this context", &e->where);
1554 /* Statement functions have already been excluded above. */
1555 else if (strncmp ("%LOC", arg->name, 4) == 0
1556 && e->ts.type == BT_PROCEDURE)
1558 if (e->symtree->n.sym->attr.proc == PROC_INTERNAL)
1560 gfc_error ("Passing internal procedure at %L by location "
1561 "not allowed", &e->where);
1567 /* Fortran 2008, C1237. */
1568 if (e->expr_type == EXPR_VARIABLE && gfc_is_coindexed (e)
1569 && gfc_has_ultimate_pointer (e))
1571 gfc_error ("Coindexed actual argument at %L with ultimate pointer "
1572 "component", &e->where);
1581 /* Do the checks of the actual argument list that are specific to elemental
1582 procedures. If called with c == NULL, we have a function, otherwise if
1583 expr == NULL, we have a subroutine. */
1586 resolve_elemental_actual (gfc_expr *expr, gfc_code *c)
1588 gfc_actual_arglist *arg0;
1589 gfc_actual_arglist *arg;
1590 gfc_symbol *esym = NULL;
1591 gfc_intrinsic_sym *isym = NULL;
1593 gfc_intrinsic_arg *iformal = NULL;
1594 gfc_formal_arglist *eformal = NULL;
1595 bool formal_optional = false;
1596 bool set_by_optional = false;
1600 /* Is this an elemental procedure? */
1601 if (expr && expr->value.function.actual != NULL)
1603 if (expr->value.function.esym != NULL
1604 && expr->value.function.esym->attr.elemental)
1606 arg0 = expr->value.function.actual;
1607 esym = expr->value.function.esym;
1609 else if (expr->value.function.isym != NULL
1610 && expr->value.function.isym->elemental)
1612 arg0 = expr->value.function.actual;
1613 isym = expr->value.function.isym;
1618 else if (c && c->ext.actual != NULL)
1620 arg0 = c->ext.actual;
1622 if (c->resolved_sym)
1623 esym = c->resolved_sym;
1625 esym = c->symtree->n.sym;
1628 if (!esym->attr.elemental)
1634 /* The rank of an elemental is the rank of its array argument(s). */
1635 for (arg = arg0; arg; arg = arg->next)
1637 if (arg->expr != NULL && arg->expr->rank > 0)
1639 rank = arg->expr->rank;
1640 if (arg->expr->expr_type == EXPR_VARIABLE
1641 && arg->expr->symtree->n.sym->attr.optional)
1642 set_by_optional = true;
1644 /* Function specific; set the result rank and shape. */
1648 if (!expr->shape && arg->expr->shape)
1650 expr->shape = gfc_get_shape (rank);
1651 for (i = 0; i < rank; i++)
1652 mpz_init_set (expr->shape[i], arg->expr->shape[i]);
1659 /* If it is an array, it shall not be supplied as an actual argument
1660 to an elemental procedure unless an array of the same rank is supplied
1661 as an actual argument corresponding to a nonoptional dummy argument of
1662 that elemental procedure(12.4.1.5). */
1663 formal_optional = false;
1665 iformal = isym->formal;
1667 eformal = esym->formal;
1669 for (arg = arg0; arg; arg = arg->next)
1673 if (eformal->sym && eformal->sym->attr.optional)
1674 formal_optional = true;
1675 eformal = eformal->next;
1677 else if (isym && iformal)
1679 if (iformal->optional)
1680 formal_optional = true;
1681 iformal = iformal->next;
1684 formal_optional = true;
1686 if (pedantic && arg->expr != NULL
1687 && arg->expr->expr_type == EXPR_VARIABLE
1688 && arg->expr->symtree->n.sym->attr.optional
1691 && (set_by_optional || arg->expr->rank != rank)
1692 && !(isym && isym->id == GFC_ISYM_CONVERSION))
1694 gfc_warning ("'%s' at %L is an array and OPTIONAL; IF IT IS "
1695 "MISSING, it cannot be the actual argument of an "
1696 "ELEMENTAL procedure unless there is a non-optional "
1697 "argument with the same rank (12.4.1.5)",
1698 arg->expr->symtree->n.sym->name, &arg->expr->where);
1703 for (arg = arg0; arg; arg = arg->next)
1705 if (arg->expr == NULL || arg->expr->rank == 0)
1708 /* Being elemental, the last upper bound of an assumed size array
1709 argument must be present. */
1710 if (resolve_assumed_size_actual (arg->expr))
1713 /* Elemental procedure's array actual arguments must conform. */
1716 if (gfc_check_conformance (arg->expr, e,
1717 "elemental procedure") == FAILURE)
1724 /* INTENT(OUT) is only allowed for subroutines; if any actual argument
1725 is an array, the intent inout/out variable needs to be also an array. */
1726 if (rank > 0 && esym && expr == NULL)
1727 for (eformal = esym->formal, arg = arg0; arg && eformal;
1728 arg = arg->next, eformal = eformal->next)
1729 if ((eformal->sym->attr.intent == INTENT_OUT
1730 || eformal->sym->attr.intent == INTENT_INOUT)
1731 && arg->expr && arg->expr->rank == 0)
1733 gfc_error ("Actual argument at %L for INTENT(%s) dummy '%s' of "
1734 "ELEMENTAL subroutine '%s' is a scalar, but another "
1735 "actual argument is an array", &arg->expr->where,
1736 (eformal->sym->attr.intent == INTENT_OUT) ? "OUT"
1737 : "INOUT", eformal->sym->name, esym->name);
1744 /* Go through each actual argument in ACTUAL and see if it can be
1745 implemented as an inlined, non-copying intrinsic. FNSYM is the
1746 function being called, or NULL if not known. */
1749 find_noncopying_intrinsics (gfc_symbol *fnsym, gfc_actual_arglist *actual)
1751 gfc_actual_arglist *ap;
1754 for (ap = actual; ap; ap = ap->next)
1756 && (expr = gfc_get_noncopying_intrinsic_argument (ap->expr))
1757 && !gfc_check_fncall_dependency (expr, INTENT_IN, fnsym, actual,
1759 ap->expr->inline_noncopying_intrinsic = 1;
1763 /* This function does the checking of references to global procedures
1764 as defined in sections 18.1 and 14.1, respectively, of the Fortran
1765 77 and 95 standards. It checks for a gsymbol for the name, making
1766 one if it does not already exist. If it already exists, then the
1767 reference being resolved must correspond to the type of gsymbol.
1768 Otherwise, the new symbol is equipped with the attributes of the
1769 reference. The corresponding code that is called in creating
1770 global entities is parse.c.
1772 In addition, for all but -std=legacy, the gsymbols are used to
1773 check the interfaces of external procedures from the same file.
1774 The namespace of the gsymbol is resolved and then, once this is
1775 done the interface is checked. */
1779 not_in_recursive (gfc_symbol *sym, gfc_namespace *gsym_ns)
1781 if (!gsym_ns->proc_name->attr.recursive)
1784 if (sym->ns == gsym_ns)
1787 if (sym->ns->parent && sym->ns->parent == gsym_ns)
1794 not_entry_self_reference (gfc_symbol *sym, gfc_namespace *gsym_ns)
1796 if (gsym_ns->entries)
1798 gfc_entry_list *entry = gsym_ns->entries;
1800 for (; entry; entry = entry->next)
1802 if (strcmp (sym->name, entry->sym->name) == 0)
1804 if (strcmp (gsym_ns->proc_name->name,
1805 sym->ns->proc_name->name) == 0)
1809 && strcmp (gsym_ns->proc_name->name,
1810 sym->ns->parent->proc_name->name) == 0)
1819 resolve_global_procedure (gfc_symbol *sym, locus *where,
1820 gfc_actual_arglist **actual, int sub)
1824 enum gfc_symbol_type type;
1826 type = sub ? GSYM_SUBROUTINE : GSYM_FUNCTION;
1828 gsym = gfc_get_gsymbol (sym->name);
1830 if ((gsym->type != GSYM_UNKNOWN && gsym->type != type))
1831 gfc_global_used (gsym, where);
1833 if (gfc_option.flag_whole_file
1834 && sym->attr.if_source == IFSRC_UNKNOWN
1835 && gsym->type != GSYM_UNKNOWN
1837 && gsym->ns->resolved != -1
1838 && gsym->ns->proc_name
1839 && not_in_recursive (sym, gsym->ns)
1840 && not_entry_self_reference (sym, gsym->ns))
1842 /* Make sure that translation for the gsymbol occurs before
1843 the procedure currently being resolved. */
1844 ns = gsym->ns->resolved ? NULL : gfc_global_ns_list;
1845 for (; ns && ns != gsym->ns; ns = ns->sibling)
1847 if (ns->sibling == gsym->ns)
1849 ns->sibling = gsym->ns->sibling;
1850 gsym->ns->sibling = gfc_global_ns_list;
1851 gfc_global_ns_list = gsym->ns;
1856 if (!gsym->ns->resolved)
1858 gfc_dt_list *old_dt_list;
1860 /* Stash away derived types so that the backend_decls do not
1862 old_dt_list = gfc_derived_types;
1863 gfc_derived_types = NULL;
1865 gfc_resolve (gsym->ns);
1867 /* Store the new derived types with the global namespace. */
1868 if (gfc_derived_types)
1869 gsym->ns->derived_types = gfc_derived_types;
1871 /* Restore the derived types of this namespace. */
1872 gfc_derived_types = old_dt_list;
1875 if (gsym->ns->proc_name->attr.function
1876 && gsym->ns->proc_name->as
1877 && gsym->ns->proc_name->as->rank
1878 && (!sym->as || sym->as->rank != gsym->ns->proc_name->as->rank))
1879 gfc_error ("The reference to function '%s' at %L either needs an "
1880 "explicit INTERFACE or the rank is incorrect", sym->name,
1883 /* Non-assumed length character functions. */
1884 if (sym->attr.function && sym->ts.type == BT_CHARACTER
1885 && gsym->ns->proc_name->ts.u.cl->length != NULL)
1887 gfc_charlen *cl = sym->ts.u.cl;
1889 if (!sym->attr.entry_master && sym->attr.if_source == IFSRC_UNKNOWN
1890 && cl && cl->length && cl->length->expr_type != EXPR_CONSTANT)
1892 gfc_error ("Nonconstant character-length function '%s' at %L "
1893 "must have an explicit interface", sym->name,
1898 if (gfc_option.flag_whole_file == 1
1899 || ((gfc_option.warn_std & GFC_STD_LEGACY)
1901 !(gfc_option.warn_std & GFC_STD_GNU)))
1902 gfc_errors_to_warnings (1);
1904 gfc_procedure_use (gsym->ns->proc_name, actual, where);
1906 gfc_errors_to_warnings (0);
1909 if (gsym->type == GSYM_UNKNOWN)
1912 gsym->where = *where;
1919 /************* Function resolution *************/
1921 /* Resolve a function call known to be generic.
1922 Section 14.1.2.4.1. */
1925 resolve_generic_f0 (gfc_expr *expr, gfc_symbol *sym)
1929 if (sym->attr.generic)
1931 s = gfc_search_interface (sym->generic, 0, &expr->value.function.actual);
1934 expr->value.function.name = s->name;
1935 expr->value.function.esym = s;
1937 if (s->ts.type != BT_UNKNOWN)
1939 else if (s->result != NULL && s->result->ts.type != BT_UNKNOWN)
1940 expr->ts = s->result->ts;
1943 expr->rank = s->as->rank;
1944 else if (s->result != NULL && s->result->as != NULL)
1945 expr->rank = s->result->as->rank;
1947 gfc_set_sym_referenced (expr->value.function.esym);
1952 /* TODO: Need to search for elemental references in generic
1956 if (sym->attr.intrinsic)
1957 return gfc_intrinsic_func_interface (expr, 0);
1964 resolve_generic_f (gfc_expr *expr)
1969 sym = expr->symtree->n.sym;
1973 m = resolve_generic_f0 (expr, sym);
1976 else if (m == MATCH_ERROR)
1980 if (sym->ns->parent == NULL)
1982 gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
1986 if (!generic_sym (sym))
1990 /* Last ditch attempt. See if the reference is to an intrinsic
1991 that possesses a matching interface. 14.1.2.4 */
1992 if (sym && !gfc_is_intrinsic (sym, 0, expr->where))
1994 gfc_error ("There is no specific function for the generic '%s' at %L",
1995 expr->symtree->n.sym->name, &expr->where);
1999 m = gfc_intrinsic_func_interface (expr, 0);
2003 gfc_error ("Generic function '%s' at %L is not consistent with a "
2004 "specific intrinsic interface", expr->symtree->n.sym->name,
2011 /* Resolve a function call known to be specific. */
2014 resolve_specific_f0 (gfc_symbol *sym, gfc_expr *expr)
2018 if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
2020 if (sym->attr.dummy)
2022 sym->attr.proc = PROC_DUMMY;
2026 sym->attr.proc = PROC_EXTERNAL;
2030 if (sym->attr.proc == PROC_MODULE
2031 || sym->attr.proc == PROC_ST_FUNCTION
2032 || sym->attr.proc == PROC_INTERNAL)
2035 if (sym->attr.intrinsic)
2037 m = gfc_intrinsic_func_interface (expr, 1);
2041 gfc_error ("Function '%s' at %L is INTRINSIC but is not compatible "
2042 "with an intrinsic", sym->name, &expr->where);
2050 gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2053 expr->ts = sym->result->ts;
2056 expr->value.function.name = sym->name;
2057 expr->value.function.esym = sym;
2058 if (sym->as != NULL)
2059 expr->rank = sym->as->rank;
2066 resolve_specific_f (gfc_expr *expr)
2071 sym = expr->symtree->n.sym;
2075 m = resolve_specific_f0 (sym, expr);
2078 if (m == MATCH_ERROR)
2081 if (sym->ns->parent == NULL)
2084 gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2090 gfc_error ("Unable to resolve the specific function '%s' at %L",
2091 expr->symtree->n.sym->name, &expr->where);
2097 /* Resolve a procedure call not known to be generic nor specific. */
2100 resolve_unknown_f (gfc_expr *expr)
2105 sym = expr->symtree->n.sym;
2107 if (sym->attr.dummy)
2109 sym->attr.proc = PROC_DUMMY;
2110 expr->value.function.name = sym->name;
2114 /* See if we have an intrinsic function reference. */
2116 if (gfc_is_intrinsic (sym, 0, expr->where))
2118 if (gfc_intrinsic_func_interface (expr, 1) == MATCH_YES)
2123 /* The reference is to an external name. */
2125 sym->attr.proc = PROC_EXTERNAL;
2126 expr->value.function.name = sym->name;
2127 expr->value.function.esym = expr->symtree->n.sym;
2129 if (sym->as != NULL)
2130 expr->rank = sym->as->rank;
2132 /* Type of the expression is either the type of the symbol or the
2133 default type of the symbol. */
2136 gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2138 if (sym->ts.type != BT_UNKNOWN)
2142 ts = gfc_get_default_type (sym->name, sym->ns);
2144 if (ts->type == BT_UNKNOWN)
2146 gfc_error ("Function '%s' at %L has no IMPLICIT type",
2147 sym->name, &expr->where);
2158 /* Return true, if the symbol is an external procedure. */
2160 is_external_proc (gfc_symbol *sym)
2162 if (!sym->attr.dummy && !sym->attr.contained
2163 && !(sym->attr.intrinsic
2164 || gfc_is_intrinsic (sym, sym->attr.subroutine, sym->declared_at))
2165 && sym->attr.proc != PROC_ST_FUNCTION
2166 && !sym->attr.use_assoc
2174 /* Figure out if a function reference is pure or not. Also set the name
2175 of the function for a potential error message. Return nonzero if the
2176 function is PURE, zero if not. */
2178 pure_stmt_function (gfc_expr *, gfc_symbol *);
2181 pure_function (gfc_expr *e, const char **name)
2187 if (e->symtree != NULL
2188 && e->symtree->n.sym != NULL
2189 && e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2190 return pure_stmt_function (e, e->symtree->n.sym);
2192 if (e->value.function.esym)
2194 pure = gfc_pure (e->value.function.esym);
2195 *name = e->value.function.esym->name;
2197 else if (e->value.function.isym)
2199 pure = e->value.function.isym->pure
2200 || e->value.function.isym->elemental;
2201 *name = e->value.function.isym->name;
2205 /* Implicit functions are not pure. */
2207 *name = e->value.function.name;
2215 impure_stmt_fcn (gfc_expr *e, gfc_symbol *sym,
2216 int *f ATTRIBUTE_UNUSED)
2220 /* Don't bother recursing into other statement functions
2221 since they will be checked individually for purity. */
2222 if (e->expr_type != EXPR_FUNCTION
2224 || e->symtree->n.sym == sym
2225 || e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2228 return pure_function (e, &name) ? false : true;
2233 pure_stmt_function (gfc_expr *e, gfc_symbol *sym)
2235 return gfc_traverse_expr (e, sym, impure_stmt_fcn, 0) ? 0 : 1;
2240 is_scalar_expr_ptr (gfc_expr *expr)
2242 gfc_try retval = SUCCESS;
2247 /* See if we have a gfc_ref, which means we have a substring, array
2248 reference, or a component. */
2249 if (expr->ref != NULL)
2252 while (ref->next != NULL)
2258 if (ref->u.ss.length != NULL
2259 && ref->u.ss.length->length != NULL
2261 && ref->u.ss.start->expr_type == EXPR_CONSTANT
2263 && ref->u.ss.end->expr_type == EXPR_CONSTANT)
2265 start = (int) mpz_get_si (ref->u.ss.start->value.integer);
2266 end = (int) mpz_get_si (ref->u.ss.end->value.integer);
2267 if (end - start + 1 != 1)
2274 if (ref->u.ar.type == AR_ELEMENT)
2276 else if (ref->u.ar.type == AR_FULL)
2278 /* The user can give a full array if the array is of size 1. */
2279 if (ref->u.ar.as != NULL
2280 && ref->u.ar.as->rank == 1
2281 && ref->u.ar.as->type == AS_EXPLICIT
2282 && ref->u.ar.as->lower[0] != NULL
2283 && ref->u.ar.as->lower[0]->expr_type == EXPR_CONSTANT
2284 && ref->u.ar.as->upper[0] != NULL
2285 && ref->u.ar.as->upper[0]->expr_type == EXPR_CONSTANT)
2287 /* If we have a character string, we need to check if
2288 its length is one. */
2289 if (expr->ts.type == BT_CHARACTER)
2291 if (expr->ts.u.cl == NULL
2292 || expr->ts.u.cl->length == NULL
2293 || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1)
2299 /* We have constant lower and upper bounds. If the
2300 difference between is 1, it can be considered a
2302 start = (int) mpz_get_si
2303 (ref->u.ar.as->lower[0]->value.integer);
2304 end = (int) mpz_get_si
2305 (ref->u.ar.as->upper[0]->value.integer);
2306 if (end - start + 1 != 1)
2321 else if (expr->ts.type == BT_CHARACTER && expr->rank == 0)
2323 /* Character string. Make sure it's of length 1. */
2324 if (expr->ts.u.cl == NULL
2325 || expr->ts.u.cl->length == NULL
2326 || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1) != 0)
2329 else if (expr->rank != 0)
2336 /* Match one of the iso_c_binding functions (c_associated or c_loc)
2337 and, in the case of c_associated, set the binding label based on
2341 gfc_iso_c_func_interface (gfc_symbol *sym, gfc_actual_arglist *args,
2342 gfc_symbol **new_sym)
2344 char name[GFC_MAX_SYMBOL_LEN + 1];
2345 char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
2346 int optional_arg = 0, is_pointer = 0;
2347 gfc_try retval = SUCCESS;
2348 gfc_symbol *args_sym;
2349 gfc_typespec *arg_ts;
2351 if (args->expr->expr_type == EXPR_CONSTANT
2352 || args->expr->expr_type == EXPR_OP
2353 || args->expr->expr_type == EXPR_NULL)
2355 gfc_error ("Argument to '%s' at %L is not a variable",
2356 sym->name, &(args->expr->where));
2360 args_sym = args->expr->symtree->n.sym;
2362 /* The typespec for the actual arg should be that stored in the expr
2363 and not necessarily that of the expr symbol (args_sym), because
2364 the actual expression could be a part-ref of the expr symbol. */
2365 arg_ts = &(args->expr->ts);
2367 is_pointer = gfc_is_data_pointer (args->expr);
2369 if (sym->intmod_sym_id == ISOCBINDING_ASSOCIATED)
2371 /* If the user gave two args then they are providing something for
2372 the optional arg (the second cptr). Therefore, set the name and
2373 binding label to the c_associated for two cptrs. Otherwise,
2374 set c_associated to expect one cptr. */
2378 sprintf (name, "%s_2", sym->name);
2379 sprintf (binding_label, "%s_2", sym->binding_label);
2385 sprintf (name, "%s_1", sym->name);
2386 sprintf (binding_label, "%s_1", sym->binding_label);
2390 /* Get a new symbol for the version of c_associated that
2392 *new_sym = get_iso_c_sym (sym, name, binding_label, optional_arg);
2394 else if (sym->intmod_sym_id == ISOCBINDING_LOC
2395 || sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2397 sprintf (name, "%s", sym->name);
2398 sprintf (binding_label, "%s", sym->binding_label);
2400 /* Error check the call. */
2401 if (args->next != NULL)
2403 gfc_error_now ("More actual than formal arguments in '%s' "
2404 "call at %L", name, &(args->expr->where));
2407 else if (sym->intmod_sym_id == ISOCBINDING_LOC)
2409 /* Make sure we have either the target or pointer attribute. */
2410 if (!args_sym->attr.target && !is_pointer)
2412 gfc_error_now ("Parameter '%s' to '%s' at %L must be either "
2413 "a TARGET or an associated pointer",
2415 sym->name, &(args->expr->where));
2419 /* See if we have interoperable type and type param. */
2420 if (verify_c_interop (arg_ts) == SUCCESS
2421 || gfc_check_any_c_kind (arg_ts) == SUCCESS)
2423 if (args_sym->attr.target == 1)
2425 /* Case 1a, section 15.1.2.5, J3/04-007: variable that
2426 has the target attribute and is interoperable. */
2427 /* Case 1b, section 15.1.2.5, J3/04-007: allocated
2428 allocatable variable that has the TARGET attribute and
2429 is not an array of zero size. */
2430 if (args_sym->attr.allocatable == 1)
2432 if (args_sym->attr.dimension != 0
2433 && (args_sym->as && args_sym->as->rank == 0))
2435 gfc_error_now ("Allocatable variable '%s' used as a "
2436 "parameter to '%s' at %L must not be "
2437 "an array of zero size",
2438 args_sym->name, sym->name,
2439 &(args->expr->where));
2445 /* A non-allocatable target variable with C
2446 interoperable type and type parameters must be
2448 if (args_sym && args_sym->attr.dimension)
2450 if (args_sym->as->type == AS_ASSUMED_SHAPE)
2452 gfc_error ("Assumed-shape array '%s' at %L "
2453 "cannot be an argument to the "
2454 "procedure '%s' because "
2455 "it is not C interoperable",
2457 &(args->expr->where), sym->name);
2460 else if (args_sym->as->type == AS_DEFERRED)
2462 gfc_error ("Deferred-shape array '%s' at %L "
2463 "cannot be an argument to the "
2464 "procedure '%s' because "
2465 "it is not C interoperable",
2467 &(args->expr->where), sym->name);
2472 /* Make sure it's not a character string. Arrays of
2473 any type should be ok if the variable is of a C
2474 interoperable type. */
2475 if (arg_ts->type == BT_CHARACTER)
2476 if (arg_ts->u.cl != NULL
2477 && (arg_ts->u.cl->length == NULL
2478 || arg_ts->u.cl->length->expr_type
2481 (arg_ts->u.cl->length->value.integer, 1)
2483 && is_scalar_expr_ptr (args->expr) != SUCCESS)
2485 gfc_error_now ("CHARACTER argument '%s' to '%s' "
2486 "at %L must have a length of 1",
2487 args_sym->name, sym->name,
2488 &(args->expr->where));
2494 && is_scalar_expr_ptr (args->expr) != SUCCESS)
2496 /* Case 1c, section 15.1.2.5, J3/04-007: an associated
2498 gfc_error_now ("Argument '%s' to '%s' at %L must be an "
2499 "associated scalar POINTER", args_sym->name,
2500 sym->name, &(args->expr->where));
2506 /* The parameter is not required to be C interoperable. If it
2507 is not C interoperable, it must be a nonpolymorphic scalar
2508 with no length type parameters. It still must have either
2509 the pointer or target attribute, and it can be
2510 allocatable (but must be allocated when c_loc is called). */
2511 if (args->expr->rank != 0
2512 && is_scalar_expr_ptr (args->expr) != SUCCESS)
2514 gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2515 "scalar", args_sym->name, sym->name,
2516 &(args->expr->where));
2519 else if (arg_ts->type == BT_CHARACTER
2520 && is_scalar_expr_ptr (args->expr) != SUCCESS)
2522 gfc_error_now ("CHARACTER argument '%s' to '%s' at "
2523 "%L must have a length of 1",
2524 args_sym->name, sym->name,
2525 &(args->expr->where));
2530 else if (sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2532 if (args_sym->attr.flavor != FL_PROCEDURE)
2534 /* TODO: Update this error message to allow for procedure
2535 pointers once they are implemented. */
2536 gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2538 args_sym->name, sym->name,
2539 &(args->expr->where));
2542 else if (args_sym->attr.is_bind_c != 1)
2544 gfc_error_now ("Parameter '%s' to '%s' at %L must be "
2546 args_sym->name, sym->name,
2547 &(args->expr->where));
2552 /* for c_loc/c_funloc, the new symbol is the same as the old one */
2557 gfc_internal_error ("gfc_iso_c_func_interface(): Unhandled "
2558 "iso_c_binding function: '%s'!\n", sym->name);
2565 /* Resolve a function call, which means resolving the arguments, then figuring
2566 out which entity the name refers to. */
2567 /* TODO: Check procedure arguments so that an INTENT(IN) isn't passed
2568 to INTENT(OUT) or INTENT(INOUT). */
2571 resolve_function (gfc_expr *expr)
2573 gfc_actual_arglist *arg;
2578 procedure_type p = PROC_INTRINSIC;
2579 bool no_formal_args;
2583 sym = expr->symtree->n.sym;
2585 /* If this is a procedure pointer component, it has already been resolved. */
2586 if (gfc_is_proc_ptr_comp (expr, NULL))
2589 if (sym && sym->attr.intrinsic
2590 && resolve_intrinsic (sym, &expr->where) == FAILURE)
2593 if (sym && (sym->attr.flavor == FL_VARIABLE || sym->attr.subroutine))
2595 gfc_error ("'%s' at %L is not a function", sym->name, &expr->where);
2599 /* If this ia a deferred TBP with an abstract interface (which may
2600 of course be referenced), expr->value.function.esym will be set. */
2601 if (sym && sym->attr.abstract && !expr->value.function.esym)
2603 gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
2604 sym->name, &expr->where);
2608 /* Switch off assumed size checking and do this again for certain kinds
2609 of procedure, once the procedure itself is resolved. */
2610 need_full_assumed_size++;
2612 if (expr->symtree && expr->symtree->n.sym)
2613 p = expr->symtree->n.sym->attr.proc;
2615 if (expr->value.function.isym && expr->value.function.isym->inquiry)
2616 inquiry_argument = true;
2617 no_formal_args = sym && is_external_proc (sym) && sym->formal == NULL;
2619 if (resolve_actual_arglist (expr->value.function.actual,
2620 p, no_formal_args) == FAILURE)
2622 inquiry_argument = false;
2626 inquiry_argument = false;
2628 /* Need to setup the call to the correct c_associated, depending on
2629 the number of cptrs to user gives to compare. */
2630 if (sym && sym->attr.is_iso_c == 1)
2632 if (gfc_iso_c_func_interface (sym, expr->value.function.actual, &sym)
2636 /* Get the symtree for the new symbol (resolved func).
2637 the old one will be freed later, when it's no longer used. */
2638 gfc_find_sym_tree (sym->name, sym->ns, 1, &(expr->symtree));
2641 /* Resume assumed_size checking. */
2642 need_full_assumed_size--;
2644 /* If the procedure is external, check for usage. */
2645 if (sym && is_external_proc (sym))
2646 resolve_global_procedure (sym, &expr->where,
2647 &expr->value.function.actual, 0);
2649 if (sym && sym->ts.type == BT_CHARACTER
2651 && sym->ts.u.cl->length == NULL
2653 && expr->value.function.esym == NULL
2654 && !sym->attr.contained)
2656 /* Internal procedures are taken care of in resolve_contained_fntype. */
2657 gfc_error ("Function '%s' is declared CHARACTER(*) and cannot "
2658 "be used at %L since it is not a dummy argument",
2659 sym->name, &expr->where);
2663 /* See if function is already resolved. */
2665 if (expr->value.function.name != NULL)
2667 if (expr->ts.type == BT_UNKNOWN)
2673 /* Apply the rules of section 14.1.2. */
2675 switch (procedure_kind (sym))
2678 t = resolve_generic_f (expr);
2681 case PTYPE_SPECIFIC:
2682 t = resolve_specific_f (expr);
2686 t = resolve_unknown_f (expr);
2690 gfc_internal_error ("resolve_function(): bad function type");
2694 /* If the expression is still a function (it might have simplified),
2695 then we check to see if we are calling an elemental function. */
2697 if (expr->expr_type != EXPR_FUNCTION)
2700 temp = need_full_assumed_size;
2701 need_full_assumed_size = 0;
2703 if (resolve_elemental_actual (expr, NULL) == FAILURE)
2706 if (omp_workshare_flag
2707 && expr->value.function.esym
2708 && ! gfc_elemental (expr->value.function.esym))
2710 gfc_error ("User defined non-ELEMENTAL function '%s' at %L not allowed "
2711 "in WORKSHARE construct", expr->value.function.esym->name,
2716 #define GENERIC_ID expr->value.function.isym->id
2717 else if (expr->value.function.actual != NULL
2718 && expr->value.function.isym != NULL
2719 && GENERIC_ID != GFC_ISYM_LBOUND
2720 && GENERIC_ID != GFC_ISYM_LEN
2721 && GENERIC_ID != GFC_ISYM_LOC
2722 && GENERIC_ID != GFC_ISYM_PRESENT)
2724 /* Array intrinsics must also have the last upper bound of an
2725 assumed size array argument. UBOUND and SIZE have to be
2726 excluded from the check if the second argument is anything
2729 for (arg = expr->value.function.actual; arg; arg = arg->next)
2731 if ((GENERIC_ID == GFC_ISYM_UBOUND || GENERIC_ID == GFC_ISYM_SIZE)
2732 && arg->next != NULL && arg->next->expr)
2734 if (arg->next->expr->expr_type != EXPR_CONSTANT)
2737 if (arg->next->name && strncmp(arg->next->name, "kind", 4) == 0)
2740 if ((int)mpz_get_si (arg->next->expr->value.integer)
2745 if (arg->expr != NULL
2746 && arg->expr->rank > 0
2747 && resolve_assumed_size_actual (arg->expr))
2753 need_full_assumed_size = temp;
2756 if (!pure_function (expr, &name) && name)
2760 gfc_error ("reference to non-PURE function '%s' at %L inside a "
2761 "FORALL %s", name, &expr->where,
2762 forall_flag == 2 ? "mask" : "block");
2765 else if (gfc_pure (NULL))
2767 gfc_error ("Function reference to '%s' at %L is to a non-PURE "
2768 "procedure within a PURE procedure", name, &expr->where);
2773 /* Functions without the RECURSIVE attribution are not allowed to
2774 * call themselves. */
2775 if (expr->value.function.esym && !expr->value.function.esym->attr.recursive)
2778 esym = expr->value.function.esym;
2780 if (is_illegal_recursion (esym, gfc_current_ns))
2782 if (esym->attr.entry && esym->ns->entries)
2783 gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
2784 " function '%s' is not RECURSIVE",
2785 esym->name, &expr->where, esym->ns->entries->sym->name);
2787 gfc_error ("Function '%s' at %L cannot be called recursively, as it"
2788 " is not RECURSIVE", esym->name, &expr->where);
2794 /* Character lengths of use associated functions may contains references to
2795 symbols not referenced from the current program unit otherwise. Make sure
2796 those symbols are marked as referenced. */
2798 if (expr->ts.type == BT_CHARACTER && expr->value.function.esym
2799 && expr->value.function.esym->attr.use_assoc)
2801 gfc_expr_set_symbols_referenced (expr->ts.u.cl->length);
2805 && !((expr->value.function.esym
2806 && expr->value.function.esym->attr.elemental)
2808 (expr->value.function.isym
2809 && expr->value.function.isym->elemental)))
2810 find_noncopying_intrinsics (expr->value.function.esym,
2811 expr->value.function.actual);
2813 /* Make sure that the expression has a typespec that works. */
2814 if (expr->ts.type == BT_UNKNOWN)
2816 if (expr->symtree->n.sym->result
2817 && expr->symtree->n.sym->result->ts.type != BT_UNKNOWN
2818 && !expr->symtree->n.sym->result->attr.proc_pointer)
2819 expr->ts = expr->symtree->n.sym->result->ts;
2826 /************* Subroutine resolution *************/
2829 pure_subroutine (gfc_code *c, gfc_symbol *sym)
2835 gfc_error ("Subroutine call to '%s' in FORALL block at %L is not PURE",
2836 sym->name, &c->loc);
2837 else if (gfc_pure (NULL))
2838 gfc_error ("Subroutine call to '%s' at %L is not PURE", sym->name,
2844 resolve_generic_s0 (gfc_code *c, gfc_symbol *sym)
2848 if (sym->attr.generic)
2850 s = gfc_search_interface (sym->generic, 1, &c->ext.actual);
2853 c->resolved_sym = s;
2854 pure_subroutine (c, s);
2858 /* TODO: Need to search for elemental references in generic interface. */
2861 if (sym->attr.intrinsic)
2862 return gfc_intrinsic_sub_interface (c, 0);
2869 resolve_generic_s (gfc_code *c)
2874 sym = c->symtree->n.sym;
2878 m = resolve_generic_s0 (c, sym);
2881 else if (m == MATCH_ERROR)
2885 if (sym->ns->parent == NULL)
2887 gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2891 if (!generic_sym (sym))
2895 /* Last ditch attempt. See if the reference is to an intrinsic
2896 that possesses a matching interface. 14.1.2.4 */
2897 sym = c->symtree->n.sym;
2899 if (!gfc_is_intrinsic (sym, 1, c->loc))
2901 gfc_error ("There is no specific subroutine for the generic '%s' at %L",
2902 sym->name, &c->loc);
2906 m = gfc_intrinsic_sub_interface (c, 0);
2910 gfc_error ("Generic subroutine '%s' at %L is not consistent with an "
2911 "intrinsic subroutine interface", sym->name, &c->loc);
2917 /* Set the name and binding label of the subroutine symbol in the call
2918 expression represented by 'c' to include the type and kind of the
2919 second parameter. This function is for resolving the appropriate
2920 version of c_f_pointer() and c_f_procpointer(). For example, a
2921 call to c_f_pointer() for a default integer pointer could have a
2922 name of c_f_pointer_i4. If no second arg exists, which is an error
2923 for these two functions, it defaults to the generic symbol's name
2924 and binding label. */
2927 set_name_and_label (gfc_code *c, gfc_symbol *sym,
2928 char *name, char *binding_label)
2930 gfc_expr *arg = NULL;
2934 /* The second arg of c_f_pointer and c_f_procpointer determines
2935 the type and kind for the procedure name. */
2936 arg = c->ext.actual->next->expr;
2940 /* Set up the name to have the given symbol's name,
2941 plus the type and kind. */
2942 /* a derived type is marked with the type letter 'u' */
2943 if (arg->ts.type == BT_DERIVED)
2946 kind = 0; /* set the kind as 0 for now */
2950 type = gfc_type_letter (arg->ts.type);
2951 kind = arg->ts.kind;
2954 if (arg->ts.type == BT_CHARACTER)
2955 /* Kind info for character strings not needed. */
2958 sprintf (name, "%s_%c%d", sym->name, type, kind);
2959 /* Set up the binding label as the given symbol's label plus
2960 the type and kind. */
2961 sprintf (binding_label, "%s_%c%d", sym->binding_label, type, kind);
2965 /* If the second arg is missing, set the name and label as
2966 was, cause it should at least be found, and the missing
2967 arg error will be caught by compare_parameters(). */
2968 sprintf (name, "%s", sym->name);
2969 sprintf (binding_label, "%s", sym->binding_label);
2976 /* Resolve a generic version of the iso_c_binding procedure given
2977 (sym) to the specific one based on the type and kind of the
2978 argument(s). Currently, this function resolves c_f_pointer() and
2979 c_f_procpointer based on the type and kind of the second argument
2980 (FPTR). Other iso_c_binding procedures aren't specially handled.
2981 Upon successfully exiting, c->resolved_sym will hold the resolved
2982 symbol. Returns MATCH_ERROR if an error occurred; MATCH_YES
2986 gfc_iso_c_sub_interface (gfc_code *c, gfc_symbol *sym)
2988 gfc_symbol *new_sym;
2989 /* this is fine, since we know the names won't use the max */
2990 char name[GFC_MAX_SYMBOL_LEN + 1];
2991 char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
2992 /* default to success; will override if find error */
2993 match m = MATCH_YES;
2995 /* Make sure the actual arguments are in the necessary order (based on the
2996 formal args) before resolving. */
2997 gfc_procedure_use (sym, &c->ext.actual, &(c->loc));
2999 if ((sym->intmod_sym_id == ISOCBINDING_F_POINTER) ||
3000 (sym->intmod_sym_id == ISOCBINDING_F_PROCPOINTER))
3002 set_name_and_label (c, sym, name, binding_label);
3004 if (sym->intmod_sym_id == ISOCBINDING_F_POINTER)
3006 if (c->ext.actual != NULL && c->ext.actual->next != NULL)
3008 /* Make sure we got a third arg if the second arg has non-zero
3009 rank. We must also check that the type and rank are
3010 correct since we short-circuit this check in
3011 gfc_procedure_use() (called above to sort actual args). */
3012 if (c->ext.actual->next->expr->rank != 0)
3014 if(c->ext.actual->next->next == NULL
3015 || c->ext.actual->next->next->expr == NULL)
3018 gfc_error ("Missing SHAPE parameter for call to %s "
3019 "at %L", sym->name, &(c->loc));
3021 else if (c->ext.actual->next->next->expr->ts.type
3023 || c->ext.actual->next->next->expr->rank != 1)
3026 gfc_error ("SHAPE parameter for call to %s at %L must "
3027 "be a rank 1 INTEGER array", sym->name,
3034 if (m != MATCH_ERROR)
3036 /* the 1 means to add the optional arg to formal list */
3037 new_sym = get_iso_c_sym (sym, name, binding_label, 1);
3039 /* for error reporting, say it's declared where the original was */
3040 new_sym->declared_at = sym->declared_at;
3045 /* no differences for c_loc or c_funloc */
3049 /* set the resolved symbol */
3050 if (m != MATCH_ERROR)
3051 c->resolved_sym = new_sym;
3053 c->resolved_sym = sym;
3059 /* Resolve a subroutine call known to be specific. */
3062 resolve_specific_s0 (gfc_code *c, gfc_symbol *sym)
3066 if(sym->attr.is_iso_c)
3068 m = gfc_iso_c_sub_interface (c,sym);
3072 if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
3074 if (sym->attr.dummy)
3076 sym->attr.proc = PROC_DUMMY;
3080 sym->attr.proc = PROC_EXTERNAL;
3084 if (sym->attr.proc == PROC_MODULE || sym->attr.proc == PROC_INTERNAL)
3087 if (sym->attr.intrinsic)
3089 m = gfc_intrinsic_sub_interface (c, 1);
3093 gfc_error ("Subroutine '%s' at %L is INTRINSIC but is not compatible "
3094 "with an intrinsic", sym->name, &c->loc);
3102 gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3104 c->resolved_sym = sym;
3105 pure_subroutine (c, sym);
3112 resolve_specific_s (gfc_code *c)
3117 sym = c->symtree->n.sym;
3121 m = resolve_specific_s0 (c, sym);
3124 if (m == MATCH_ERROR)
3127 if (sym->ns->parent == NULL)
3130 gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
3136 sym = c->symtree->n.sym;
3137 gfc_error ("Unable to resolve the specific subroutine '%s' at %L",
3138 sym->name, &c->loc);
3144 /* Resolve a subroutine call not known to be generic nor specific. */
3147 resolve_unknown_s (gfc_code *c)
3151 sym = c->symtree->n.sym;
3153 if (sym->attr.dummy)
3155 sym->attr.proc = PROC_DUMMY;
3159 /* See if we have an intrinsic function reference. */
3161 if (gfc_is_intrinsic (sym, 1, c->loc))
3163 if (gfc_intrinsic_sub_interface (c, 1) == MATCH_YES)
3168 /* The reference is to an external name. */
3171 gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3173 c->resolved_sym = sym;
3175 pure_subroutine (c, sym);
3181 /* Resolve a subroutine call. Although it was tempting to use the same code
3182 for functions, subroutines and functions are stored differently and this
3183 makes things awkward. */
3186 resolve_call (gfc_code *c)
3189 procedure_type ptype = PROC_INTRINSIC;
3190 gfc_symbol *csym, *sym;
3191 bool no_formal_args;
3193 csym = c->symtree ? c->symtree->n.sym : NULL;
3195 if (csym && csym->ts.type != BT_UNKNOWN)
3197 gfc_error ("'%s' at %L has a type, which is not consistent with "
3198 "the CALL at %L", csym->name, &csym->declared_at, &c->loc);
3202 if (csym && gfc_current_ns->parent && csym->ns != gfc_current_ns)
3205 gfc_find_sym_tree (csym->name, gfc_current_ns, 1, &st);
3206 sym = st ? st->n.sym : NULL;
3207 if (sym && csym != sym
3208 && sym->ns == gfc_current_ns
3209 && sym->attr.flavor == FL_PROCEDURE
3210 && sym->attr.contained)
3213 if (csym->attr.generic)
3214 c->symtree->n.sym = sym;
3217 csym = c->symtree->n.sym;
3221 /* If this ia a deferred TBP with an abstract interface
3222 (which may of course be referenced), c->expr1 will be set. */
3223 if (csym && csym->attr.abstract && !c->expr1)
3225 gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
3226 csym->name, &c->loc);
3230 /* Subroutines without the RECURSIVE attribution are not allowed to
3231 * call themselves. */
3232 if (csym && is_illegal_recursion (csym, gfc_current_ns))
3234 if (csym->attr.entry && csym->ns->entries)
3235 gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
3236 " subroutine '%s' is not RECURSIVE",
3237 csym->name, &c->loc, csym->ns->entries->sym->name);
3239 gfc_error ("SUBROUTINE '%s' at %L cannot be called recursively, as it"
3240 " is not RECURSIVE", csym->name, &c->loc);
3245 /* Switch off assumed size checking and do this again for certain kinds
3246 of procedure, once the procedure itself is resolved. */
3247 need_full_assumed_size++;
3250 ptype = csym->attr.proc;
3252 no_formal_args = csym && is_external_proc (csym) && csym->formal == NULL;
3253 if (resolve_actual_arglist (c->ext.actual, ptype,
3254 no_formal_args) == FAILURE)
3257 /* Resume assumed_size checking. */
3258 need_full_assumed_size--;
3260 /* If external, check for usage. */
3261 if (csym && is_external_proc (csym))
3262 resolve_global_procedure (csym, &c->loc, &c->ext.actual, 1);
3265 if (c->resolved_sym == NULL)
3267 c->resolved_isym = NULL;
3268 switch (procedure_kind (csym))
3271 t = resolve_generic_s (c);
3274 case PTYPE_SPECIFIC:
3275 t = resolve_specific_s (c);
3279 t = resolve_unknown_s (c);
3283 gfc_internal_error ("resolve_subroutine(): bad function type");
3287 /* Some checks of elemental subroutine actual arguments. */
3288 if (resolve_elemental_actual (NULL, c) == FAILURE)
3291 if (t == SUCCESS && !(c->resolved_sym && c->resolved_sym->attr.elemental))
3292 find_noncopying_intrinsics (c->resolved_sym, c->ext.actual);
3297 /* Compare the shapes of two arrays that have non-NULL shapes. If both
3298 op1->shape and op2->shape are non-NULL return SUCCESS if their shapes
3299 match. If both op1->shape and op2->shape are non-NULL return FAILURE
3300 if their shapes do not match. If either op1->shape or op2->shape is
3301 NULL, return SUCCESS. */
3304 compare_shapes (gfc_expr *op1, gfc_expr *op2)
3311 if (op1->shape != NULL && op2->shape != NULL)
3313 for (i = 0; i < op1->rank; i++)
3315 if (mpz_cmp (op1->shape[i], op2->shape[i]) != 0)
3317 gfc_error ("Shapes for operands at %L and %L are not conformable",
3318 &op1->where, &op2->where);
3329 /* Resolve an operator expression node. This can involve replacing the
3330 operation with a user defined function call. */
3333 resolve_operator (gfc_expr *e)
3335 gfc_expr *op1, *op2;
3337 bool dual_locus_error;
3340 /* Resolve all subnodes-- give them types. */
3342 switch (e->value.op.op)
3345 if (gfc_resolve_expr (e->value.op.op2) == FAILURE)
3348 /* Fall through... */
3351 case INTRINSIC_UPLUS:
3352 case INTRINSIC_UMINUS:
3353 case INTRINSIC_PARENTHESES:
3354 if (gfc_resolve_expr (e->value.op.op1) == FAILURE)
3359 /* Typecheck the new node. */
3361 op1 = e->value.op.op1;
3362 op2 = e->value.op.op2;
3363 dual_locus_error = false;
3365 if ((op1 && op1->expr_type == EXPR_NULL)
3366 || (op2 && op2->expr_type == EXPR_NULL))
3368 sprintf (msg, _("Invalid context for NULL() pointer at %%L"));
3372 switch (e->value.op.op)
3374 case INTRINSIC_UPLUS:
3375 case INTRINSIC_UMINUS:
3376 if (op1->ts.type == BT_INTEGER
3377 || op1->ts.type == BT_REAL
3378 || op1->ts.type == BT_COMPLEX)
3384 sprintf (msg, _("Operand of unary numeric operator '%s' at %%L is %s"),
3385 gfc_op2string (e->value.op.op), gfc_typename (&e->ts));
3388 case INTRINSIC_PLUS:
3389 case INTRINSIC_MINUS:
3390 case INTRINSIC_TIMES:
3391 case INTRINSIC_DIVIDE:
3392 case INTRINSIC_POWER:
3393 if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3395 gfc_type_convert_binary (e, 1);