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 /* Differences in constant character lengths. */
1862 if (sym->attr.function && sym->ts.type == BT_CHARACTER)
1864 long int l1 = 0, l2 = 0;
1865 gfc_charlen *cl1 = sym->ts.u.cl;
1866 gfc_charlen *cl2 = gsym->ns->proc_name->ts.u.cl;
1869 && cl1->length != NULL
1870 && cl1->length->expr_type == EXPR_CONSTANT)
1871 l1 = mpz_get_si (cl1->length->value.integer);
1874 && cl2->length != NULL
1875 && cl2->length->expr_type == EXPR_CONSTANT)
1876 l2 = mpz_get_si (cl2->length->value.integer);
1878 if (l1 && l2 && l1 != l2)
1879 gfc_error ("Character length mismatch in return type of "
1880 "function '%s' at %L (%ld/%ld)", sym->name,
1881 &sym->declared_at, l1, l2);
1884 /* Type mismatch of function return type and expected type. */
1885 if (sym->attr.function
1886 && !gfc_compare_types (&sym->ts, &gsym->ns->proc_name->ts))
1887 gfc_error ("Return type mismatch of function '%s' at %L (%s/%s)",
1888 sym->name, &sym->declared_at, gfc_typename (&sym->ts),
1889 gfc_typename (&gsym->ns->proc_name->ts));
1891 if (gsym->ns->proc_name->formal)
1893 gfc_formal_arglist *arg = gsym->ns->proc_name->formal;
1894 for ( ; arg; arg = arg->next)
1897 /* F2003, 12.3.1.1 (2a); F2008, 12.4.2.2 (2a) */
1898 else if (arg->sym->attr.allocatable
1899 || arg->sym->attr.asynchronous
1900 || arg->sym->attr.optional
1901 || arg->sym->attr.pointer
1902 || arg->sym->attr.target
1903 || arg->sym->attr.value
1904 || arg->sym->attr.volatile_)
1906 gfc_error ("Dummy argument '%s' of procedure '%s' at %L "
1907 "has an attribute that requires an explicit "
1908 "interface for this procedure", arg->sym->name,
1909 sym->name, &sym->declared_at);
1912 /* F2003, 12.3.1.1 (2b); F2008, 12.4.2.2 (2b) */
1913 else if (arg->sym && arg->sym->as
1914 && arg->sym->as->type == AS_ASSUMED_SHAPE)
1916 gfc_error ("Procedure '%s' at %L with assumed-shape dummy "
1917 "argument '%s' must have an explicit interface",
1918 sym->name, &sym->declared_at, arg->sym->name);
1921 /* F2008, 12.4.2.2 (2c) */
1922 else if (arg->sym->attr.codimension)
1924 gfc_error ("Procedure '%s' at %L with coarray dummy argument "
1925 "'%s' must have an explicit interface",
1926 sym->name, &sym->declared_at, arg->sym->name);
1929 /* F2003, 12.3.1.1 (2c); F2008, 12.4.2.2 (2d) */
1930 else if (false) /* TODO: is a parametrized derived type */
1932 gfc_error ("Procedure '%s' at %L with parametrized derived "
1933 "type argument '%s' must have an explicit "
1934 "interface", sym->name, &sym->declared_at,
1938 /* F2003, 12.3.1.1 (2d); F2008, 12.4.2.2 (2e) */
1939 else if (arg->sym->ts.type == BT_CLASS)
1941 gfc_error ("Procedure '%s' at %L with polymorphic dummy "
1942 "argument '%s' must have an explicit interface",
1943 sym->name, &sym->declared_at, arg->sym->name);
1948 if (gsym->ns->proc_name->attr.function)
1950 /* F2003, 12.3.1.1 (3a); F2008, 12.4.2.2 (3a) */
1951 if (gsym->ns->proc_name->as
1952 && gsym->ns->proc_name->as->rank
1953 && (!sym->as || sym->as->rank != gsym->ns->proc_name->as->rank))
1954 gfc_error ("The reference to function '%s' at %L either needs an "
1955 "explicit INTERFACE or the rank is incorrect", sym->name,
1958 /* F2003, 12.3.1.1 (3b); F2008, 12.4.2.2 (3b) */
1959 if (gsym->ns->proc_name->result->attr.pointer
1960 || gsym->ns->proc_name->result->attr.allocatable)
1961 gfc_error ("Function '%s' at %L with a POINTER or ALLOCATABLE "
1962 "result must have an explicit interface", sym->name,
1965 /* F2003, 12.3.1.1 (3c); F2008, 12.4.2.2 (3c) */
1966 if (sym->ts.type == BT_CHARACTER
1967 && gsym->ns->proc_name->ts.u.cl->length != NULL)
1969 gfc_charlen *cl = sym->ts.u.cl;
1971 if (!sym->attr.entry_master && sym->attr.if_source == IFSRC_UNKNOWN
1972 && cl && cl->length && cl->length->expr_type != EXPR_CONSTANT)
1974 gfc_error ("Nonconstant character-length function '%s' at %L "
1975 "must have an explicit interface", sym->name,
1981 /* F2003, 12.3.1.1 (4); F2008, 12.4.2.2 (4) */
1982 if (gsym->ns->proc_name->attr.elemental)
1984 gfc_error ("ELEMENTAL procedure '%s' at %L must have an explicit "
1985 "interface", sym->name, &sym->declared_at);
1988 /* F2003, 12.3.1.1 (5); F2008, 12.4.2.2 (5) */
1989 if (gsym->ns->proc_name->attr.is_bind_c)
1991 gfc_error ("Procedure '%s' at %L with BIND(C) attribute must have "
1992 "an explicit interface", sym->name, &sym->declared_at);
1995 if (gfc_option.flag_whole_file == 1
1996 || ((gfc_option.warn_std & GFC_STD_LEGACY)
1997 && !(gfc_option.warn_std & GFC_STD_GNU)))
1998 gfc_errors_to_warnings (1);
2000 gfc_procedure_use (gsym->ns->proc_name, actual, where);
2002 gfc_errors_to_warnings (0);
2005 if (gsym->type == GSYM_UNKNOWN)
2008 gsym->where = *where;
2015 /************* Function resolution *************/
2017 /* Resolve a function call known to be generic.
2018 Section 14.1.2.4.1. */
2021 resolve_generic_f0 (gfc_expr *expr, gfc_symbol *sym)
2025 if (sym->attr.generic)
2027 s = gfc_search_interface (sym->generic, 0, &expr->value.function.actual);
2030 expr->value.function.name = s->name;
2031 expr->value.function.esym = s;
2033 if (s->ts.type != BT_UNKNOWN)
2035 else if (s->result != NULL && s->result->ts.type != BT_UNKNOWN)
2036 expr->ts = s->result->ts;
2039 expr->rank = s->as->rank;
2040 else if (s->result != NULL && s->result->as != NULL)
2041 expr->rank = s->result->as->rank;
2043 gfc_set_sym_referenced (expr->value.function.esym);
2048 /* TODO: Need to search for elemental references in generic
2052 if (sym->attr.intrinsic)
2053 return gfc_intrinsic_func_interface (expr, 0);
2060 resolve_generic_f (gfc_expr *expr)
2065 sym = expr->symtree->n.sym;
2069 m = resolve_generic_f0 (expr, sym);
2072 else if (m == MATCH_ERROR)
2076 if (sym->ns->parent == NULL)
2078 gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2082 if (!generic_sym (sym))
2086 /* Last ditch attempt. See if the reference is to an intrinsic
2087 that possesses a matching interface. 14.1.2.4 */
2088 if (sym && !gfc_is_intrinsic (sym, 0, expr->where))
2090 gfc_error ("There is no specific function for the generic '%s' at %L",
2091 expr->symtree->n.sym->name, &expr->where);
2095 m = gfc_intrinsic_func_interface (expr, 0);
2099 gfc_error ("Generic function '%s' at %L is not consistent with a "
2100 "specific intrinsic interface", expr->symtree->n.sym->name,
2107 /* Resolve a function call known to be specific. */
2110 resolve_specific_f0 (gfc_symbol *sym, gfc_expr *expr)
2114 if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
2116 if (sym->attr.dummy)
2118 sym->attr.proc = PROC_DUMMY;
2122 sym->attr.proc = PROC_EXTERNAL;
2126 if (sym->attr.proc == PROC_MODULE
2127 || sym->attr.proc == PROC_ST_FUNCTION
2128 || sym->attr.proc == PROC_INTERNAL)
2131 if (sym->attr.intrinsic)
2133 m = gfc_intrinsic_func_interface (expr, 1);
2137 gfc_error ("Function '%s' at %L is INTRINSIC but is not compatible "
2138 "with an intrinsic", sym->name, &expr->where);
2146 gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2149 expr->ts = sym->result->ts;
2152 expr->value.function.name = sym->name;
2153 expr->value.function.esym = sym;
2154 if (sym->as != NULL)
2155 expr->rank = sym->as->rank;
2162 resolve_specific_f (gfc_expr *expr)
2167 sym = expr->symtree->n.sym;
2171 m = resolve_specific_f0 (sym, expr);
2174 if (m == MATCH_ERROR)
2177 if (sym->ns->parent == NULL)
2180 gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2186 gfc_error ("Unable to resolve the specific function '%s' at %L",
2187 expr->symtree->n.sym->name, &expr->where);
2193 /* Resolve a procedure call not known to be generic nor specific. */
2196 resolve_unknown_f (gfc_expr *expr)
2201 sym = expr->symtree->n.sym;
2203 if (sym->attr.dummy)
2205 sym->attr.proc = PROC_DUMMY;
2206 expr->value.function.name = sym->name;
2210 /* See if we have an intrinsic function reference. */
2212 if (gfc_is_intrinsic (sym, 0, expr->where))
2214 if (gfc_intrinsic_func_interface (expr, 1) == MATCH_YES)
2219 /* The reference is to an external name. */
2221 sym->attr.proc = PROC_EXTERNAL;
2222 expr->value.function.name = sym->name;
2223 expr->value.function.esym = expr->symtree->n.sym;
2225 if (sym->as != NULL)
2226 expr->rank = sym->as->rank;
2228 /* Type of the expression is either the type of the symbol or the
2229 default type of the symbol. */
2232 gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2234 if (sym->ts.type != BT_UNKNOWN)
2238 ts = gfc_get_default_type (sym->name, sym->ns);
2240 if (ts->type == BT_UNKNOWN)
2242 gfc_error ("Function '%s' at %L has no IMPLICIT type",
2243 sym->name, &expr->where);
2254 /* Return true, if the symbol is an external procedure. */
2256 is_external_proc (gfc_symbol *sym)
2258 if (!sym->attr.dummy && !sym->attr.contained
2259 && !(sym->attr.intrinsic
2260 || gfc_is_intrinsic (sym, sym->attr.subroutine, sym->declared_at))
2261 && sym->attr.proc != PROC_ST_FUNCTION
2262 && !sym->attr.use_assoc
2270 /* Figure out if a function reference is pure or not. Also set the name
2271 of the function for a potential error message. Return nonzero if the
2272 function is PURE, zero if not. */
2274 pure_stmt_function (gfc_expr *, gfc_symbol *);
2277 pure_function (gfc_expr *e, const char **name)
2283 if (e->symtree != NULL
2284 && e->symtree->n.sym != NULL
2285 && e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2286 return pure_stmt_function (e, e->symtree->n.sym);
2288 if (e->value.function.esym)
2290 pure = gfc_pure (e->value.function.esym);
2291 *name = e->value.function.esym->name;
2293 else if (e->value.function.isym)
2295 pure = e->value.function.isym->pure
2296 || e->value.function.isym->elemental;
2297 *name = e->value.function.isym->name;
2301 /* Implicit functions are not pure. */
2303 *name = e->value.function.name;
2311 impure_stmt_fcn (gfc_expr *e, gfc_symbol *sym,
2312 int *f ATTRIBUTE_UNUSED)
2316 /* Don't bother recursing into other statement functions
2317 since they will be checked individually for purity. */
2318 if (e->expr_type != EXPR_FUNCTION
2320 || e->symtree->n.sym == sym
2321 || e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2324 return pure_function (e, &name) ? false : true;
2329 pure_stmt_function (gfc_expr *e, gfc_symbol *sym)
2331 return gfc_traverse_expr (e, sym, impure_stmt_fcn, 0) ? 0 : 1;
2336 is_scalar_expr_ptr (gfc_expr *expr)
2338 gfc_try retval = SUCCESS;
2343 /* See if we have a gfc_ref, which means we have a substring, array
2344 reference, or a component. */
2345 if (expr->ref != NULL)
2348 while (ref->next != NULL)
2354 if (ref->u.ss.length != NULL
2355 && ref->u.ss.length->length != NULL
2357 && ref->u.ss.start->expr_type == EXPR_CONSTANT
2359 && ref->u.ss.end->expr_type == EXPR_CONSTANT)
2361 start = (int) mpz_get_si (ref->u.ss.start->value.integer);
2362 end = (int) mpz_get_si (ref->u.ss.end->value.integer);
2363 if (end - start + 1 != 1)
2370 if (ref->u.ar.type == AR_ELEMENT)
2372 else if (ref->u.ar.type == AR_FULL)
2374 /* The user can give a full array if the array is of size 1. */
2375 if (ref->u.ar.as != NULL
2376 && ref->u.ar.as->rank == 1
2377 && ref->u.ar.as->type == AS_EXPLICIT
2378 && ref->u.ar.as->lower[0] != NULL
2379 && ref->u.ar.as->lower[0]->expr_type == EXPR_CONSTANT
2380 && ref->u.ar.as->upper[0] != NULL
2381 && ref->u.ar.as->upper[0]->expr_type == EXPR_CONSTANT)
2383 /* If we have a character string, we need to check if
2384 its length is one. */
2385 if (expr->ts.type == BT_CHARACTER)
2387 if (expr->ts.u.cl == NULL
2388 || expr->ts.u.cl->length == NULL
2389 || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1)
2395 /* We have constant lower and upper bounds. If the
2396 difference between is 1, it can be considered a
2398 start = (int) mpz_get_si
2399 (ref->u.ar.as->lower[0]->value.integer);
2400 end = (int) mpz_get_si
2401 (ref->u.ar.as->upper[0]->value.integer);
2402 if (end - start + 1 != 1)
2417 else if (expr->ts.type == BT_CHARACTER && expr->rank == 0)
2419 /* Character string. Make sure it's of length 1. */
2420 if (expr->ts.u.cl == NULL
2421 || expr->ts.u.cl->length == NULL
2422 || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1) != 0)
2425 else if (expr->rank != 0)
2432 /* Match one of the iso_c_binding functions (c_associated or c_loc)
2433 and, in the case of c_associated, set the binding label based on
2437 gfc_iso_c_func_interface (gfc_symbol *sym, gfc_actual_arglist *args,
2438 gfc_symbol **new_sym)
2440 char name[GFC_MAX_SYMBOL_LEN + 1];
2441 char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
2442 int optional_arg = 0, is_pointer = 0;
2443 gfc_try retval = SUCCESS;
2444 gfc_symbol *args_sym;
2445 gfc_typespec *arg_ts;
2447 if (args->expr->expr_type == EXPR_CONSTANT
2448 || args->expr->expr_type == EXPR_OP
2449 || args->expr->expr_type == EXPR_NULL)
2451 gfc_error ("Argument to '%s' at %L is not a variable",
2452 sym->name, &(args->expr->where));
2456 args_sym = args->expr->symtree->n.sym;
2458 /* The typespec for the actual arg should be that stored in the expr
2459 and not necessarily that of the expr symbol (args_sym), because
2460 the actual expression could be a part-ref of the expr symbol. */
2461 arg_ts = &(args->expr->ts);
2463 is_pointer = gfc_is_data_pointer (args->expr);
2465 if (sym->intmod_sym_id == ISOCBINDING_ASSOCIATED)
2467 /* If the user gave two args then they are providing something for
2468 the optional arg (the second cptr). Therefore, set the name and
2469 binding label to the c_associated for two cptrs. Otherwise,
2470 set c_associated to expect one cptr. */
2474 sprintf (name, "%s_2", sym->name);
2475 sprintf (binding_label, "%s_2", sym->binding_label);
2481 sprintf (name, "%s_1", sym->name);
2482 sprintf (binding_label, "%s_1", sym->binding_label);
2486 /* Get a new symbol for the version of c_associated that
2488 *new_sym = get_iso_c_sym (sym, name, binding_label, optional_arg);
2490 else if (sym->intmod_sym_id == ISOCBINDING_LOC
2491 || sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2493 sprintf (name, "%s", sym->name);
2494 sprintf (binding_label, "%s", sym->binding_label);
2496 /* Error check the call. */
2497 if (args->next != NULL)
2499 gfc_error_now ("More actual than formal arguments in '%s' "
2500 "call at %L", name, &(args->expr->where));
2503 else if (sym->intmod_sym_id == ISOCBINDING_LOC)
2505 /* Make sure we have either the target or pointer attribute. */
2506 if (!args_sym->attr.target && !is_pointer)
2508 gfc_error_now ("Parameter '%s' to '%s' at %L must be either "
2509 "a TARGET or an associated pointer",
2511 sym->name, &(args->expr->where));
2515 /* See if we have interoperable type and type param. */
2516 if (verify_c_interop (arg_ts) == SUCCESS
2517 || gfc_check_any_c_kind (arg_ts) == SUCCESS)
2519 if (args_sym->attr.target == 1)
2521 /* Case 1a, section 15.1.2.5, J3/04-007: variable that
2522 has the target attribute and is interoperable. */
2523 /* Case 1b, section 15.1.2.5, J3/04-007: allocated
2524 allocatable variable that has the TARGET attribute and
2525 is not an array of zero size. */
2526 if (args_sym->attr.allocatable == 1)
2528 if (args_sym->attr.dimension != 0
2529 && (args_sym->as && args_sym->as->rank == 0))
2531 gfc_error_now ("Allocatable variable '%s' used as a "
2532 "parameter to '%s' at %L must not be "
2533 "an array of zero size",
2534 args_sym->name, sym->name,
2535 &(args->expr->where));
2541 /* A non-allocatable target variable with C
2542 interoperable type and type parameters must be
2544 if (args_sym && args_sym->attr.dimension)
2546 if (args_sym->as->type == AS_ASSUMED_SHAPE)
2548 gfc_error ("Assumed-shape array '%s' at %L "
2549 "cannot be an argument to the "
2550 "procedure '%s' because "
2551 "it is not C interoperable",
2553 &(args->expr->where), sym->name);
2556 else if (args_sym->as->type == AS_DEFERRED)
2558 gfc_error ("Deferred-shape array '%s' at %L "
2559 "cannot be an argument to the "
2560 "procedure '%s' because "
2561 "it is not C interoperable",
2563 &(args->expr->where), sym->name);
2568 /* Make sure it's not a character string. Arrays of
2569 any type should be ok if the variable is of a C
2570 interoperable type. */
2571 if (arg_ts->type == BT_CHARACTER)
2572 if (arg_ts->u.cl != NULL
2573 && (arg_ts->u.cl->length == NULL
2574 || arg_ts->u.cl->length->expr_type
2577 (arg_ts->u.cl->length->value.integer, 1)
2579 && is_scalar_expr_ptr (args->expr) != SUCCESS)
2581 gfc_error_now ("CHARACTER argument '%s' to '%s' "
2582 "at %L must have a length of 1",
2583 args_sym->name, sym->name,
2584 &(args->expr->where));
2590 && is_scalar_expr_ptr (args->expr) != SUCCESS)
2592 /* Case 1c, section 15.1.2.5, J3/04-007: an associated
2594 gfc_error_now ("Argument '%s' to '%s' at %L must be an "
2595 "associated scalar POINTER", args_sym->name,
2596 sym->name, &(args->expr->where));
2602 /* The parameter is not required to be C interoperable. If it
2603 is not C interoperable, it must be a nonpolymorphic scalar
2604 with no length type parameters. It still must have either
2605 the pointer or target attribute, and it can be
2606 allocatable (but must be allocated when c_loc is called). */
2607 if (args->expr->rank != 0
2608 && is_scalar_expr_ptr (args->expr) != SUCCESS)
2610 gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2611 "scalar", args_sym->name, sym->name,
2612 &(args->expr->where));
2615 else if (arg_ts->type == BT_CHARACTER
2616 && is_scalar_expr_ptr (args->expr) != SUCCESS)
2618 gfc_error_now ("CHARACTER argument '%s' to '%s' at "
2619 "%L must have a length of 1",
2620 args_sym->name, sym->name,
2621 &(args->expr->where));
2626 else if (sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2628 if (args_sym->attr.flavor != FL_PROCEDURE)
2630 /* TODO: Update this error message to allow for procedure
2631 pointers once they are implemented. */
2632 gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2634 args_sym->name, sym->name,
2635 &(args->expr->where));
2638 else if (args_sym->attr.is_bind_c != 1)
2640 gfc_error_now ("Parameter '%s' to '%s' at %L must be "
2642 args_sym->name, sym->name,
2643 &(args->expr->where));
2648 /* for c_loc/c_funloc, the new symbol is the same as the old one */
2653 gfc_internal_error ("gfc_iso_c_func_interface(): Unhandled "
2654 "iso_c_binding function: '%s'!\n", sym->name);
2661 /* Resolve a function call, which means resolving the arguments, then figuring
2662 out which entity the name refers to. */
2663 /* TODO: Check procedure arguments so that an INTENT(IN) isn't passed
2664 to INTENT(OUT) or INTENT(INOUT). */
2667 resolve_function (gfc_expr *expr)
2669 gfc_actual_arglist *arg;
2674 procedure_type p = PROC_INTRINSIC;
2675 bool no_formal_args;
2679 sym = expr->symtree->n.sym;
2681 /* If this is a procedure pointer component, it has already been resolved. */
2682 if (gfc_is_proc_ptr_comp (expr, NULL))
2685 if (sym && sym->attr.intrinsic
2686 && resolve_intrinsic (sym, &expr->where) == FAILURE)
2689 if (sym && (sym->attr.flavor == FL_VARIABLE || sym->attr.subroutine))
2691 gfc_error ("'%s' at %L is not a function", sym->name, &expr->where);
2695 /* If this ia a deferred TBP with an abstract interface (which may
2696 of course be referenced), expr->value.function.esym will be set. */
2697 if (sym && sym->attr.abstract && !expr->value.function.esym)
2699 gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
2700 sym->name, &expr->where);
2704 /* Switch off assumed size checking and do this again for certain kinds
2705 of procedure, once the procedure itself is resolved. */
2706 need_full_assumed_size++;
2708 if (expr->symtree && expr->symtree->n.sym)
2709 p = expr->symtree->n.sym->attr.proc;
2711 if (expr->value.function.isym && expr->value.function.isym->inquiry)
2712 inquiry_argument = true;
2713 no_formal_args = sym && is_external_proc (sym) && sym->formal == NULL;
2715 if (resolve_actual_arglist (expr->value.function.actual,
2716 p, no_formal_args) == FAILURE)
2718 inquiry_argument = false;
2722 inquiry_argument = false;
2724 /* Need to setup the call to the correct c_associated, depending on
2725 the number of cptrs to user gives to compare. */
2726 if (sym && sym->attr.is_iso_c == 1)
2728 if (gfc_iso_c_func_interface (sym, expr->value.function.actual, &sym)
2732 /* Get the symtree for the new symbol (resolved func).
2733 the old one will be freed later, when it's no longer used. */
2734 gfc_find_sym_tree (sym->name, sym->ns, 1, &(expr->symtree));
2737 /* Resume assumed_size checking. */
2738 need_full_assumed_size--;
2740 /* If the procedure is external, check for usage. */
2741 if (sym && is_external_proc (sym))
2742 resolve_global_procedure (sym, &expr->where,
2743 &expr->value.function.actual, 0);
2745 if (sym && sym->ts.type == BT_CHARACTER
2747 && sym->ts.u.cl->length == NULL
2749 && expr->value.function.esym == NULL
2750 && !sym->attr.contained)
2752 /* Internal procedures are taken care of in resolve_contained_fntype. */
2753 gfc_error ("Function '%s' is declared CHARACTER(*) and cannot "
2754 "be used at %L since it is not a dummy argument",
2755 sym->name, &expr->where);
2759 /* See if function is already resolved. */
2761 if (expr->value.function.name != NULL)
2763 if (expr->ts.type == BT_UNKNOWN)
2769 /* Apply the rules of section 14.1.2. */
2771 switch (procedure_kind (sym))
2774 t = resolve_generic_f (expr);
2777 case PTYPE_SPECIFIC:
2778 t = resolve_specific_f (expr);
2782 t = resolve_unknown_f (expr);
2786 gfc_internal_error ("resolve_function(): bad function type");
2790 /* If the expression is still a function (it might have simplified),
2791 then we check to see if we are calling an elemental function. */
2793 if (expr->expr_type != EXPR_FUNCTION)
2796 temp = need_full_assumed_size;
2797 need_full_assumed_size = 0;
2799 if (resolve_elemental_actual (expr, NULL) == FAILURE)
2802 if (omp_workshare_flag
2803 && expr->value.function.esym
2804 && ! gfc_elemental (expr->value.function.esym))
2806 gfc_error ("User defined non-ELEMENTAL function '%s' at %L not allowed "
2807 "in WORKSHARE construct", expr->value.function.esym->name,
2812 #define GENERIC_ID expr->value.function.isym->id
2813 else if (expr->value.function.actual != NULL
2814 && expr->value.function.isym != NULL
2815 && GENERIC_ID != GFC_ISYM_LBOUND
2816 && GENERIC_ID != GFC_ISYM_LEN
2817 && GENERIC_ID != GFC_ISYM_LOC
2818 && GENERIC_ID != GFC_ISYM_PRESENT)
2820 /* Array intrinsics must also have the last upper bound of an
2821 assumed size array argument. UBOUND and SIZE have to be
2822 excluded from the check if the second argument is anything
2825 for (arg = expr->value.function.actual; arg; arg = arg->next)
2827 if ((GENERIC_ID == GFC_ISYM_UBOUND || GENERIC_ID == GFC_ISYM_SIZE)
2828 && arg->next != NULL && arg->next->expr)
2830 if (arg->next->expr->expr_type != EXPR_CONSTANT)
2833 if (arg->next->name && strncmp(arg->next->name, "kind", 4) == 0)
2836 if ((int)mpz_get_si (arg->next->expr->value.integer)
2841 if (arg->expr != NULL
2842 && arg->expr->rank > 0
2843 && resolve_assumed_size_actual (arg->expr))
2849 need_full_assumed_size = temp;
2852 if (!pure_function (expr, &name) && name)
2856 gfc_error ("reference to non-PURE function '%s' at %L inside a "
2857 "FORALL %s", name, &expr->where,
2858 forall_flag == 2 ? "mask" : "block");
2861 else if (gfc_pure (NULL))
2863 gfc_error ("Function reference to '%s' at %L is to a non-PURE "
2864 "procedure within a PURE procedure", name, &expr->where);
2869 /* Functions without the RECURSIVE attribution are not allowed to
2870 * call themselves. */
2871 if (expr->value.function.esym && !expr->value.function.esym->attr.recursive)
2874 esym = expr->value.function.esym;
2876 if (is_illegal_recursion (esym, gfc_current_ns))
2878 if (esym->attr.entry && esym->ns->entries)
2879 gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
2880 " function '%s' is not RECURSIVE",
2881 esym->name, &expr->where, esym->ns->entries->sym->name);
2883 gfc_error ("Function '%s' at %L cannot be called recursively, as it"
2884 " is not RECURSIVE", esym->name, &expr->where);
2890 /* Character lengths of use associated functions may contains references to
2891 symbols not referenced from the current program unit otherwise. Make sure
2892 those symbols are marked as referenced. */
2894 if (expr->ts.type == BT_CHARACTER && expr->value.function.esym
2895 && expr->value.function.esym->attr.use_assoc)
2897 gfc_expr_set_symbols_referenced (expr->ts.u.cl->length);
2901 && !((expr->value.function.esym
2902 && expr->value.function.esym->attr.elemental)
2904 (expr->value.function.isym
2905 && expr->value.function.isym->elemental)))
2906 find_noncopying_intrinsics (expr->value.function.esym,
2907 expr->value.function.actual);
2909 /* Make sure that the expression has a typespec that works. */
2910 if (expr->ts.type == BT_UNKNOWN)
2912 if (expr->symtree->n.sym->result
2913 && expr->symtree->n.sym->result->ts.type != BT_UNKNOWN
2914 && !expr->symtree->n.sym->result->attr.proc_pointer)
2915 expr->ts = expr->symtree->n.sym->result->ts;
2922 /************* Subroutine resolution *************/
2925 pure_subroutine (gfc_code *c, gfc_symbol *sym)
2931 gfc_error ("Subroutine call to '%s' in FORALL block at %L is not PURE",
2932 sym->name, &c->loc);
2933 else if (gfc_pure (NULL))
2934 gfc_error ("Subroutine call to '%s' at %L is not PURE", sym->name,
2940 resolve_generic_s0 (gfc_code *c, gfc_symbol *sym)
2944 if (sym->attr.generic)
2946 s = gfc_search_interface (sym->generic, 1, &c->ext.actual);
2949 c->resolved_sym = s;
2950 pure_subroutine (c, s);
2954 /* TODO: Need to search for elemental references in generic interface. */
2957 if (sym->attr.intrinsic)
2958 return gfc_intrinsic_sub_interface (c, 0);
2965 resolve_generic_s (gfc_code *c)
2970 sym = c->symtree->n.sym;
2974 m = resolve_generic_s0 (c, sym);
2977 else if (m == MATCH_ERROR)
2981 if (sym->ns->parent == NULL)
2983 gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2987 if (!generic_sym (sym))
2991 /* Last ditch attempt. See if the reference is to an intrinsic
2992 that possesses a matching interface. 14.1.2.4 */
2993 sym = c->symtree->n.sym;
2995 if (!gfc_is_intrinsic (sym, 1, c->loc))
2997 gfc_error ("There is no specific subroutine for the generic '%s' at %L",
2998 sym->name, &c->loc);
3002 m = gfc_intrinsic_sub_interface (c, 0);
3006 gfc_error ("Generic subroutine '%s' at %L is not consistent with an "
3007 "intrinsic subroutine interface", sym->name, &c->loc);
3013 /* Set the name and binding label of the subroutine symbol in the call
3014 expression represented by 'c' to include the type and kind of the
3015 second parameter. This function is for resolving the appropriate
3016 version of c_f_pointer() and c_f_procpointer(). For example, a
3017 call to c_f_pointer() for a default integer pointer could have a
3018 name of c_f_pointer_i4. If no second arg exists, which is an error
3019 for these two functions, it defaults to the generic symbol's name
3020 and binding label. */
3023 set_name_and_label (gfc_code *c, gfc_symbol *sym,
3024 char *name, char *binding_label)
3026 gfc_expr *arg = NULL;
3030 /* The second arg of c_f_pointer and c_f_procpointer determines
3031 the type and kind for the procedure name. */
3032 arg = c->ext.actual->next->expr;
3036 /* Set up the name to have the given symbol's name,
3037 plus the type and kind. */
3038 /* a derived type is marked with the type letter 'u' */
3039 if (arg->ts.type == BT_DERIVED)
3042 kind = 0; /* set the kind as 0 for now */
3046 type = gfc_type_letter (arg->ts.type);
3047 kind = arg->ts.kind;
3050 if (arg->ts.type == BT_CHARACTER)
3051 /* Kind info for character strings not needed. */
3054 sprintf (name, "%s_%c%d", sym->name, type, kind);
3055 /* Set up the binding label as the given symbol's label plus
3056 the type and kind. */
3057 sprintf (binding_label, "%s_%c%d", sym->binding_label, type, kind);
3061 /* If the second arg is missing, set the name and label as
3062 was, cause it should at least be found, and the missing
3063 arg error will be caught by compare_parameters(). */
3064 sprintf (name, "%s", sym->name);
3065 sprintf (binding_label, "%s", sym->binding_label);
3072 /* Resolve a generic version of the iso_c_binding procedure given
3073 (sym) to the specific one based on the type and kind of the
3074 argument(s). Currently, this function resolves c_f_pointer() and
3075 c_f_procpointer based on the type and kind of the second argument
3076 (FPTR). Other iso_c_binding procedures aren't specially handled.
3077 Upon successfully exiting, c->resolved_sym will hold the resolved
3078 symbol. Returns MATCH_ERROR if an error occurred; MATCH_YES
3082 gfc_iso_c_sub_interface (gfc_code *c, gfc_symbol *sym)
3084 gfc_symbol *new_sym;
3085 /* this is fine, since we know the names won't use the max */
3086 char name[GFC_MAX_SYMBOL_LEN + 1];
3087 char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
3088 /* default to success; will override if find error */
3089 match m = MATCH_YES;
3091 /* Make sure the actual arguments are in the necessary order (based on the
3092 formal args) before resolving. */
3093 gfc_procedure_use (sym, &c->ext.actual, &(c->loc));
3095 if ((sym->intmod_sym_id == ISOCBINDING_F_POINTER) ||
3096 (sym->intmod_sym_id == ISOCBINDING_F_PROCPOINTER))
3098 set_name_and_label (c, sym, name, binding_label);
3100 if (sym->intmod_sym_id == ISOCBINDING_F_POINTER)
3102 if (c->ext.actual != NULL && c->ext.actual->next != NULL)
3104 /* Make sure we got a third arg if the second arg has non-zero
3105 rank. We must also check that the type and rank are
3106 correct since we short-circuit this check in
3107 gfc_procedure_use() (called above to sort actual args). */
3108 if (c->ext.actual->next->expr->rank != 0)
3110 if(c->ext.actual->next->next == NULL
3111 || c->ext.actual->next->next->expr == NULL)
3114 gfc_error ("Missing SHAPE parameter for call to %s "
3115 "at %L", sym->name, &(c->loc));
3117 else if (c->ext.actual->next->next->expr->ts.type
3119 || c->ext.actual->next->next->expr->rank != 1)
3122 gfc_error ("SHAPE parameter for call to %s at %L must "
3123 "be a rank 1 INTEGER array", sym->name,
3130 if (m != MATCH_ERROR)
3132 /* the 1 means to add the optional arg to formal list */
3133 new_sym = get_iso_c_sym (sym, name, binding_label, 1);
3135 /* for error reporting, say it's declared where the original was */
3136 new_sym->declared_at = sym->declared_at;
3141 /* no differences for c_loc or c_funloc */
3145 /* set the resolved symbol */
3146 if (m != MATCH_ERROR)
3147 c->resolved_sym = new_sym;
3149 c->resolved_sym = sym;
3155 /* Resolve a subroutine call known to be specific. */
3158 resolve_specific_s0 (gfc_code *c, gfc_symbol *sym)
3162 if(sym->attr.is_iso_c)
3164 m = gfc_iso_c_sub_interface (c,sym);
3168 if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
3170 if (sym->attr.dummy)
3172 sym->attr.proc = PROC_DUMMY;
3176 sym->attr.proc = PROC_EXTERNAL;
3180 if (sym->attr.proc == PROC_MODULE || sym->attr.proc == PROC_INTERNAL)
3183 if (sym->attr.intrinsic)
3185 m = gfc_intrinsic_sub_interface (c, 1);
3189 gfc_error ("Subroutine '%s' at %L is INTRINSIC but is not compatible "
3190 "with an intrinsic", sym->name, &c->loc);
3198 gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3200 c->resolved_sym = sym;
3201 pure_subroutine (c, sym);
3208 resolve_specific_s (gfc_code *c)
3213 sym = c->symtree->n.sym;
3217 m = resolve_specific_s0 (c, sym);
3220 if (m == MATCH_ERROR)
3223 if (sym->ns->parent == NULL)
3226 gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
3232 sym = c->symtree->n.sym;
3233 gfc_error ("Unable to resolve the specific subroutine '%s' at %L",
3234 sym->name, &c->loc);
3240 /* Resolve a subroutine call not known to be generic nor specific. */
3243 resolve_unknown_s (gfc_code *c)
3247 sym = c->symtree->n.sym;
3249 if (sym->attr.dummy)
3251 sym->attr.proc = PROC_DUMMY;
3255 /* See if we have an intrinsic function reference. */
3257 if (gfc_is_intrinsic (sym, 1, c->loc))
3259 if (gfc_intrinsic_sub_interface (c, 1) == MATCH_YES)
3264 /* The reference is to an external name. */
3267 gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3269 c->resolved_sym = sym;
3271 pure_subroutine (c, sym);
3277 /* Resolve a subroutine call. Although it was tempting to use the same code
3278 for functions, subroutines and functions are stored differently and this
3279 makes things awkward. */
3282 resolve_call (gfc_code *c)
3285 procedure_type ptype = PROC_INTRINSIC;
3286 gfc_symbol *csym, *sym;
3287 bool no_formal_args;
3289 csym = c->symtree ? c->symtree->n.sym : NULL;
3291 if (csym && csym->ts.type != BT_UNKNOWN)
3293 gfc_error ("'%s' at %L has a type, which is not consistent with "
3294 "the CALL at %L", csym->name, &csym->declared_at, &c->loc);
3298 if (csym && gfc_current_ns->parent && csym->ns != gfc_current_ns)
3301 gfc_find_sym_tree (csym->name, gfc_current_ns, 1, &st);
3302 sym = st ? st->n.sym : NULL;
3303 if (sym && csym != sym
3304 && sym->ns == gfc_current_ns
3305 && sym->attr.flavor == FL_PROCEDURE
3306 && sym->attr.contained)
3309 if (csym->attr.generic)
3310 c->symtree->n.sym = sym;
3313 csym = c->symtree->n.sym;
3317 /* If this ia a deferred TBP with an abstract interface
3318 (which may of course be referenced), c->expr1 will be set. */
3319 if (csym && csym->attr.abstract && !c->expr1)
3321 gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
3322 csym->name, &c->loc);
3326 /* Subroutines without the RECURSIVE attribution are not allowed to
3327 * call themselves. */
3328 if (csym && is_illegal_recursion (csym, gfc_current_ns))
3330 if (csym->attr.entry && csym->ns->entries)
3331 gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
3332 " subroutine '%s' is not RECURSIVE",
3333 csym->name, &c->loc, csym->ns->entries->sym->name);
3335 gfc_error ("SUBROUTINE '%s' at %L cannot be called recursively, as it"
3336 " is not RECURSIVE", csym->name, &c->loc);
3341 /* Switch off assumed size checking and do this again for certain kinds
3342 of procedure, once the procedure itself is resolved. */
3343 need_full_assumed_size++;
3346 ptype = csym->attr.proc;
3348 no_formal_args = csym && is_external_proc (csym) && csym->formal == NULL;
3349 if (resolve_actual_arglist (c->ext.actual, ptype,
3350 no_formal_args) == FAILURE)
3353 /* Resume assumed_size checking. */
3354 need_full_assumed_size--;
3356 /* If external, check for usage. */
3357 if (csym && is_external_proc (csym))
3358 resolve_global_procedure (csym, &c->loc, &c->ext.actual, 1);
3361 if (c->resolved_sym == NULL)
3363 c->resolved_isym = NULL;
3364 switch (procedure_kind (csym))