1 /* Perform type resolution on the various structures.
2 Copyright (C) 2001, 2002, 2003, 2004, 2005, 2006, 2007, 2008
3 Free Software Foundation, Inc.
4 Contributed by Andy Vaught
6 This file is part of GCC.
8 GCC is free software; you can redistribute it and/or modify it under
9 the terms of the GNU General Public License as published by the Free
10 Software Foundation; either version 3, or (at your option) any later
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 */
33 /* Types used in equivalence statements. */
37 SEQ_NONDEFAULT, SEQ_NUMERIC, SEQ_CHARACTER, SEQ_MIXED
41 /* Stack to keep track of the nesting of blocks as we move through the
42 code. See resolve_branch() and resolve_code(). */
44 typedef struct code_stack
46 struct gfc_code *head, *current, *tail;
47 struct code_stack *prev;
49 /* This bitmap keeps track of the targets valid for a branch from
51 bitmap reachable_labels;
55 static code_stack *cs_base = NULL;
58 /* Nonzero if we're inside a FORALL block. */
60 static int forall_flag;
62 /* Nonzero if we're inside a OpenMP WORKSHARE or PARALLEL WORKSHARE block. */
64 static int omp_workshare_flag;
66 /* Nonzero if we are processing a formal arglist. The corresponding function
67 resets the flag each time that it is read. */
68 static int formal_arg_flag = 0;
70 /* True if we are resolving a specification expression. */
71 static int specification_expr = 0;
73 /* The id of the last entry seen. */
74 static int current_entry_id;
76 /* We use bitmaps to determine if a branch target is valid. */
77 static bitmap_obstack labels_obstack;
80 gfc_is_formal_arg (void)
82 return formal_arg_flag;
86 /* Ensure a typespec used is valid; for instance, TYPE(t) is invalid if t is
87 an ABSTRACT derived-type. If where is not NULL, an error message with that
88 locus is printed, optionally using name. */
91 resolve_typespec_used (gfc_typespec* ts, locus* where, const char* name)
93 if (ts->type == BT_DERIVED && ts->derived->attr.abstract)
98 gfc_error ("'%s' at %L is of the ABSTRACT type '%s'",
99 name, where, ts->derived->name);
101 gfc_error ("ABSTRACT type '%s' used at %L",
102 ts->derived->name, where);
112 /* Resolve types of formal argument lists. These have to be done early so that
113 the formal argument lists of module procedures can be copied to the
114 containing module before the individual procedures are resolved
115 individually. We also resolve argument lists of procedures in interface
116 blocks because they are self-contained scoping units.
118 Since a dummy argument cannot be a non-dummy procedure, the only
119 resort left for untyped names are the IMPLICIT types. */
122 resolve_formal_arglist (gfc_symbol *proc)
124 gfc_formal_arglist *f;
128 if (proc->result != NULL)
133 if (gfc_elemental (proc)
134 || sym->attr.pointer || sym->attr.allocatable
135 || (sym->as && sym->as->rank > 0))
137 proc->attr.always_explicit = 1;
138 sym->attr.always_explicit = 1;
143 for (f = proc->formal; f; f = f->next)
149 /* Alternate return placeholder. */
150 if (gfc_elemental (proc))
151 gfc_error ("Alternate return specifier in elemental subroutine "
152 "'%s' at %L is not allowed", proc->name,
154 if (proc->attr.function)
155 gfc_error ("Alternate return specifier in function "
156 "'%s' at %L is not allowed", proc->name,
161 if (sym->attr.if_source != IFSRC_UNKNOWN)
162 resolve_formal_arglist (sym);
164 if (sym->attr.subroutine || sym->attr.external || sym->attr.intrinsic)
166 if (gfc_pure (proc) && !gfc_pure (sym))
168 gfc_error ("Dummy procedure '%s' of PURE procedure at %L must "
169 "also be PURE", sym->name, &sym->declared_at);
173 if (gfc_elemental (proc))
175 gfc_error ("Dummy procedure at %L not allowed in ELEMENTAL "
176 "procedure", &sym->declared_at);
180 if (sym->attr.function
181 && sym->ts.type == BT_UNKNOWN
182 && sym->attr.intrinsic)
184 gfc_intrinsic_sym *isym;
185 isym = gfc_find_function (sym->name);
186 if (isym == NULL || !isym->specific)
188 gfc_error ("Unable to find a specific INTRINSIC procedure "
189 "for the reference '%s' at %L", sym->name,
198 if (sym->ts.type == BT_UNKNOWN)
200 if (!sym->attr.function || sym->result == sym)
201 gfc_set_default_type (sym, 1, sym->ns);
204 gfc_resolve_array_spec (sym->as, 0);
206 /* We can't tell if an array with dimension (:) is assumed or deferred
207 shape until we know if it has the pointer or allocatable attributes.
209 if (sym->as && sym->as->rank > 0 && sym->as->type == AS_DEFERRED
210 && !(sym->attr.pointer || sym->attr.allocatable))
212 sym->as->type = AS_ASSUMED_SHAPE;
213 for (i = 0; i < sym->as->rank; i++)
214 sym->as->lower[i] = gfc_int_expr (1);
217 if ((sym->as && sym->as->rank > 0 && sym->as->type == AS_ASSUMED_SHAPE)
218 || sym->attr.pointer || sym->attr.allocatable || sym->attr.target
219 || sym->attr.optional)
221 proc->attr.always_explicit = 1;
223 proc->result->attr.always_explicit = 1;
226 /* If the flavor is unknown at this point, it has to be a variable.
227 A procedure specification would have already set the type. */
229 if (sym->attr.flavor == FL_UNKNOWN)
230 gfc_add_flavor (&sym->attr, FL_VARIABLE, sym->name, &sym->declared_at);
232 if (gfc_pure (proc) && !sym->attr.pointer
233 && sym->attr.flavor != FL_PROCEDURE)
235 if (proc->attr.function && sym->attr.intent != INTENT_IN)
236 gfc_error ("Argument '%s' of pure function '%s' at %L must be "
237 "INTENT(IN)", sym->name, proc->name,
240 if (proc->attr.subroutine && sym->attr.intent == INTENT_UNKNOWN)
241 gfc_error ("Argument '%s' of pure subroutine '%s' at %L must "
242 "have its INTENT specified", sym->name, proc->name,
246 if (gfc_elemental (proc))
250 gfc_error ("Argument '%s' of elemental procedure at %L must "
251 "be scalar", sym->name, &sym->declared_at);
255 if (sym->attr.pointer)
257 gfc_error ("Argument '%s' of elemental procedure at %L cannot "
258 "have the POINTER attribute", sym->name,
263 if (sym->attr.flavor == FL_PROCEDURE)
265 gfc_error ("Dummy procedure '%s' not allowed in elemental "
266 "procedure '%s' at %L", sym->name, proc->name,
272 /* Each dummy shall be specified to be scalar. */
273 if (proc->attr.proc == PROC_ST_FUNCTION)
277 gfc_error ("Argument '%s' of statement function at %L must "
278 "be scalar", sym->name, &sym->declared_at);
282 if (sym->ts.type == BT_CHARACTER)
284 gfc_charlen *cl = sym->ts.cl;
285 if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
287 gfc_error ("Character-valued argument '%s' of statement "
288 "function at %L must have constant length",
289 sym->name, &sym->declared_at);
299 /* Work function called when searching for symbols that have argument lists
300 associated with them. */
303 find_arglists (gfc_symbol *sym)
305 if (sym->attr.if_source == IFSRC_UNKNOWN || sym->ns != gfc_current_ns)
308 resolve_formal_arglist (sym);
312 /* Given a namespace, resolve all formal argument lists within the namespace.
316 resolve_formal_arglists (gfc_namespace *ns)
321 gfc_traverse_ns (ns, find_arglists);
326 resolve_contained_fntype (gfc_symbol *sym, gfc_namespace *ns)
330 /* If this namespace is not a function or an entry master function,
332 if (! sym || !(sym->attr.function || sym->attr.flavor == FL_VARIABLE)
333 || sym->attr.entry_master)
336 /* Try to find out of what the return type is. */
337 if (sym->result->ts.type == BT_UNKNOWN)
339 t = gfc_set_default_type (sym->result, 0, ns);
341 if (t == FAILURE && !sym->result->attr.untyped)
343 if (sym->result == sym)
344 gfc_error ("Contained function '%s' at %L has no IMPLICIT type",
345 sym->name, &sym->declared_at);
347 gfc_error ("Result '%s' of contained function '%s' at %L has "
348 "no IMPLICIT type", sym->result->name, sym->name,
349 &sym->result->declared_at);
350 sym->result->attr.untyped = 1;
354 /* Fortran 95 Draft Standard, page 51, Section 5.1.1.5, on the Character
355 type, lists the only ways a character length value of * can be used:
356 dummy arguments of procedures, named constants, and function results
357 in external functions. Internal function results are not on that list;
358 ergo, not permitted. */
360 if (sym->result->ts.type == BT_CHARACTER)
362 gfc_charlen *cl = sym->result->ts.cl;
363 if (!cl || !cl->length)
364 gfc_error ("Character-valued internal function '%s' at %L must "
365 "not be assumed length", sym->name, &sym->declared_at);
370 /* Add NEW_ARGS to the formal argument list of PROC, taking care not to
371 introduce duplicates. */
374 merge_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
376 gfc_formal_arglist *f, *new_arglist;
379 for (; new_args != NULL; new_args = new_args->next)
381 new_sym = new_args->sym;
382 /* See if this arg is already in the formal argument list. */
383 for (f = proc->formal; f; f = f->next)
385 if (new_sym == f->sym)
392 /* Add a new argument. Argument order is not important. */
393 new_arglist = gfc_get_formal_arglist ();
394 new_arglist->sym = new_sym;
395 new_arglist->next = proc->formal;
396 proc->formal = new_arglist;
401 /* Flag the arguments that are not present in all entries. */
404 check_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
406 gfc_formal_arglist *f, *head;
409 for (f = proc->formal; f; f = f->next)
414 for (new_args = head; new_args; new_args = new_args->next)
416 if (new_args->sym == f->sym)
423 f->sym->attr.not_always_present = 1;
428 /* Resolve alternate entry points. If a symbol has multiple entry points we
429 create a new master symbol for the main routine, and turn the existing
430 symbol into an entry point. */
433 resolve_entries (gfc_namespace *ns)
435 gfc_namespace *old_ns;
439 char name[GFC_MAX_SYMBOL_LEN + 1];
440 static int master_count = 0;
442 if (ns->proc_name == NULL)
445 /* No need to do anything if this procedure doesn't have alternate entry
450 /* We may already have resolved alternate entry points. */
451 if (ns->proc_name->attr.entry_master)
454 /* If this isn't a procedure something has gone horribly wrong. */
455 gcc_assert (ns->proc_name->attr.flavor == FL_PROCEDURE);
457 /* Remember the current namespace. */
458 old_ns = gfc_current_ns;
462 /* Add the main entry point to the list of entry points. */
463 el = gfc_get_entry_list ();
464 el->sym = ns->proc_name;
466 el->next = ns->entries;
468 ns->proc_name->attr.entry = 1;
470 /* If it is a module function, it needs to be in the right namespace
471 so that gfc_get_fake_result_decl can gather up the results. The
472 need for this arose in get_proc_name, where these beasts were
473 left in their own namespace, to keep prior references linked to
474 the entry declaration.*/
475 if (ns->proc_name->attr.function
476 && ns->parent && ns->parent->proc_name->attr.flavor == FL_MODULE)
479 /* Do the same for entries where the master is not a module
480 procedure. These are retained in the module namespace because
481 of the module procedure declaration. */
482 for (el = el->next; el; el = el->next)
483 if (el->sym->ns->proc_name->attr.flavor == FL_MODULE
484 && el->sym->attr.mod_proc)
488 /* Add an entry statement for it. */
495 /* Create a new symbol for the master function. */
496 /* Give the internal function a unique name (within this file).
497 Also include the function name so the user has some hope of figuring
498 out what is going on. */
499 snprintf (name, GFC_MAX_SYMBOL_LEN, "master.%d.%s",
500 master_count++, ns->proc_name->name);
501 gfc_get_ha_symbol (name, &proc);
502 gcc_assert (proc != NULL);
504 gfc_add_procedure (&proc->attr, PROC_INTERNAL, proc->name, NULL);
505 if (ns->proc_name->attr.subroutine)
506 gfc_add_subroutine (&proc->attr, proc->name, NULL);
510 gfc_typespec *ts, *fts;
511 gfc_array_spec *as, *fas;
512 gfc_add_function (&proc->attr, proc->name, NULL);
514 fas = ns->entries->sym->as;
515 fas = fas ? fas : ns->entries->sym->result->as;
516 fts = &ns->entries->sym->result->ts;
517 if (fts->type == BT_UNKNOWN)
518 fts = gfc_get_default_type (ns->entries->sym->result, NULL);
519 for (el = ns->entries->next; el; el = el->next)
521 ts = &el->sym->result->ts;
523 as = as ? as : el->sym->result->as;
524 if (ts->type == BT_UNKNOWN)
525 ts = gfc_get_default_type (el->sym->result, NULL);
527 if (! gfc_compare_types (ts, fts)
528 || (el->sym->result->attr.dimension
529 != ns->entries->sym->result->attr.dimension)
530 || (el->sym->result->attr.pointer
531 != ns->entries->sym->result->attr.pointer))
533 else if (as && fas && ns->entries->sym->result != el->sym->result
534 && gfc_compare_array_spec (as, fas) == 0)
535 gfc_error ("Function %s at %L has entries with mismatched "
536 "array specifications", ns->entries->sym->name,
537 &ns->entries->sym->declared_at);
538 /* The characteristics need to match and thus both need to have
539 the same string length, i.e. both len=*, or both len=4.
540 Having both len=<variable> is also possible, but difficult to
541 check at compile time. */
542 else if (ts->type == BT_CHARACTER && ts->cl && fts->cl
543 && (((ts->cl->length && !fts->cl->length)
544 ||(!ts->cl->length && fts->cl->length))
546 && ts->cl->length->expr_type
547 != fts->cl->length->expr_type)
549 && ts->cl->length->expr_type == EXPR_CONSTANT
550 && mpz_cmp (ts->cl->length->value.integer,
551 fts->cl->length->value.integer) != 0)))
552 gfc_notify_std (GFC_STD_GNU, "Extension: Function %s at %L with "
553 "entries returning variables of different "
554 "string lengths", ns->entries->sym->name,
555 &ns->entries->sym->declared_at);
560 sym = ns->entries->sym->result;
561 /* All result types the same. */
563 if (sym->attr.dimension)
564 gfc_set_array_spec (proc, gfc_copy_array_spec (sym->as), NULL);
565 if (sym->attr.pointer)
566 gfc_add_pointer (&proc->attr, NULL);
570 /* Otherwise the result will be passed through a union by
572 proc->attr.mixed_entry_master = 1;
573 for (el = ns->entries; el; el = el->next)
575 sym = el->sym->result;
576 if (sym->attr.dimension)
578 if (el == ns->entries)
579 gfc_error ("FUNCTION result %s can't be an array in "
580 "FUNCTION %s at %L", sym->name,
581 ns->entries->sym->name, &sym->declared_at);
583 gfc_error ("ENTRY result %s can't be an array in "
584 "FUNCTION %s at %L", sym->name,
585 ns->entries->sym->name, &sym->declared_at);
587 else if (sym->attr.pointer)
589 if (el == ns->entries)
590 gfc_error ("FUNCTION result %s can't be a POINTER in "
591 "FUNCTION %s at %L", sym->name,
592 ns->entries->sym->name, &sym->declared_at);
594 gfc_error ("ENTRY result %s can't be a POINTER in "
595 "FUNCTION %s at %L", sym->name,
596 ns->entries->sym->name, &sym->declared_at);
601 if (ts->type == BT_UNKNOWN)
602 ts = gfc_get_default_type (sym, NULL);
606 if (ts->kind == gfc_default_integer_kind)
610 if (ts->kind == gfc_default_real_kind
611 || ts->kind == gfc_default_double_kind)
615 if (ts->kind == gfc_default_complex_kind)
619 if (ts->kind == gfc_default_logical_kind)
623 /* We will issue error elsewhere. */
631 if (el == ns->entries)
632 gfc_error ("FUNCTION result %s can't be of type %s "
633 "in FUNCTION %s at %L", sym->name,
634 gfc_typename (ts), ns->entries->sym->name,
637 gfc_error ("ENTRY result %s can't be of type %s "
638 "in FUNCTION %s at %L", sym->name,
639 gfc_typename (ts), ns->entries->sym->name,
646 proc->attr.access = ACCESS_PRIVATE;
647 proc->attr.entry_master = 1;
649 /* Merge all the entry point arguments. */
650 for (el = ns->entries; el; el = el->next)
651 merge_argument_lists (proc, el->sym->formal);
653 /* Check the master formal arguments for any that are not
654 present in all entry points. */
655 for (el = ns->entries; el; el = el->next)
656 check_argument_lists (proc, el->sym->formal);
658 /* Use the master function for the function body. */
659 ns->proc_name = proc;
661 /* Finalize the new symbols. */
662 gfc_commit_symbols ();
664 /* Restore the original namespace. */
665 gfc_current_ns = old_ns;
670 has_default_initializer (gfc_symbol *der)
674 gcc_assert (der->attr.flavor == FL_DERIVED);
675 for (c = der->components; c; c = c->next)
676 if ((c->ts.type != BT_DERIVED && c->initializer)
677 || (c->ts.type == BT_DERIVED
678 && (!c->attr.pointer && has_default_initializer (c->ts.derived))))
684 /* Resolve common variables. */
686 resolve_common_vars (gfc_symbol *sym, bool named_common)
688 gfc_symbol *csym = sym;
690 for (; csym; csym = csym->common_next)
692 if (csym->value || csym->attr.data)
694 if (!csym->ns->is_block_data)
695 gfc_notify_std (GFC_STD_GNU, "Variable '%s' at %L is in COMMON "
696 "but only in BLOCK DATA initialization is "
697 "allowed", csym->name, &csym->declared_at);
698 else if (!named_common)
699 gfc_notify_std (GFC_STD_GNU, "Initialized variable '%s' at %L is "
700 "in a blank COMMON but initialization is only "
701 "allowed in named common blocks", csym->name,
705 if (csym->ts.type != BT_DERIVED)
708 if (!(csym->ts.derived->attr.sequence
709 || csym->ts.derived->attr.is_bind_c))
710 gfc_error_now ("Derived type variable '%s' in COMMON at %L "
711 "has neither the SEQUENCE nor the BIND(C) "
712 "attribute", csym->name, &csym->declared_at);
713 if (csym->ts.derived->attr.alloc_comp)
714 gfc_error_now ("Derived type variable '%s' in COMMON at %L "
715 "has an ultimate component that is "
716 "allocatable", csym->name, &csym->declared_at);
717 if (has_default_initializer (csym->ts.derived))
718 gfc_error_now ("Derived type variable '%s' in COMMON at %L "
719 "may not have default initializer", csym->name,
724 /* Resolve common blocks. */
726 resolve_common_blocks (gfc_symtree *common_root)
730 if (common_root == NULL)
733 if (common_root->left)
734 resolve_common_blocks (common_root->left);
735 if (common_root->right)
736 resolve_common_blocks (common_root->right);
738 resolve_common_vars (common_root->n.common->head, true);
740 gfc_find_symbol (common_root->name, gfc_current_ns, 0, &sym);
744 if (sym->attr.flavor == FL_PARAMETER)
745 gfc_error ("COMMON block '%s' at %L is used as PARAMETER at %L",
746 sym->name, &common_root->n.common->where, &sym->declared_at);
748 if (sym->attr.intrinsic)
749 gfc_error ("COMMON block '%s' at %L is also an intrinsic procedure",
750 sym->name, &common_root->n.common->where);
751 else if (sym->attr.result
752 ||(sym->attr.function && gfc_current_ns->proc_name == sym))
753 gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
754 "that is also a function result", sym->name,
755 &common_root->n.common->where);
756 else if (sym->attr.flavor == FL_PROCEDURE && sym->attr.proc != PROC_INTERNAL
757 && sym->attr.proc != PROC_ST_FUNCTION)
758 gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
759 "that is also a global procedure", sym->name,
760 &common_root->n.common->where);
764 /* Resolve contained function types. Because contained functions can call one
765 another, they have to be worked out before any of the contained procedures
768 The good news is that if a function doesn't already have a type, the only
769 way it can get one is through an IMPLICIT type or a RESULT variable, because
770 by definition contained functions are contained namespace they're contained
771 in, not in a sibling or parent namespace. */
774 resolve_contained_functions (gfc_namespace *ns)
776 gfc_namespace *child;
779 resolve_formal_arglists (ns);
781 for (child = ns->contained; child; child = child->sibling)
783 /* Resolve alternate entry points first. */
784 resolve_entries (child);
786 /* Then check function return types. */
787 resolve_contained_fntype (child->proc_name, child);
788 for (el = child->entries; el; el = el->next)
789 resolve_contained_fntype (el->sym, child);
794 /* Resolve all of the elements of a structure constructor and make sure that
795 the types are correct. */
798 resolve_structure_cons (gfc_expr *expr)
800 gfc_constructor *cons;
806 cons = expr->value.constructor;
807 /* A constructor may have references if it is the result of substituting a
808 parameter variable. In this case we just pull out the component we
811 comp = expr->ref->u.c.sym->components;
813 comp = expr->ts.derived->components;
815 /* See if the user is trying to invoke a structure constructor for one of
816 the iso_c_binding derived types. */
817 if (expr->ts.derived && expr->ts.derived->ts.is_iso_c && cons
818 && cons->expr != NULL)
820 gfc_error ("Components of structure constructor '%s' at %L are PRIVATE",
821 expr->ts.derived->name, &(expr->where));
825 for (; comp; comp = comp->next, cons = cons->next)
832 if (gfc_resolve_expr (cons->expr) == FAILURE)
838 rank = comp->as ? comp->as->rank : 0;
839 if (cons->expr->expr_type != EXPR_NULL && rank != cons->expr->rank
840 && (comp->attr.allocatable || cons->expr->rank))
842 gfc_error ("The rank of the element in the derived type "
843 "constructor at %L does not match that of the "
844 "component (%d/%d)", &cons->expr->where,
845 cons->expr->rank, rank);
849 /* If we don't have the right type, try to convert it. */
851 if (!gfc_compare_types (&cons->expr->ts, &comp->ts))
854 if (comp->attr.pointer && cons->expr->ts.type != BT_UNKNOWN)
855 gfc_error ("The element in the derived type constructor at %L, "
856 "for pointer component '%s', is %s but should be %s",
857 &cons->expr->where, comp->name,
858 gfc_basic_typename (cons->expr->ts.type),
859 gfc_basic_typename (comp->ts.type));
861 t = gfc_convert_type (cons->expr, &comp->ts, 1);
864 if (cons->expr->expr_type == EXPR_NULL
865 && !(comp->attr.pointer || comp->attr.allocatable))
868 gfc_error ("The NULL in the derived type constructor at %L is "
869 "being applied to component '%s', which is neither "
870 "a POINTER nor ALLOCATABLE", &cons->expr->where,
874 if (!comp->attr.pointer || cons->expr->expr_type == EXPR_NULL)
877 a = gfc_expr_attr (cons->expr);
879 if (!a.pointer && !a.target)
882 gfc_error ("The element in the derived type constructor at %L, "
883 "for pointer component '%s' should be a POINTER or "
884 "a TARGET", &cons->expr->where, comp->name);
892 /****************** Expression name resolution ******************/
894 /* Returns 0 if a symbol was not declared with a type or
895 attribute declaration statement, nonzero otherwise. */
898 was_declared (gfc_symbol *sym)
904 if (!a.implicit_type && sym->ts.type != BT_UNKNOWN)
907 if (a.allocatable || a.dimension || a.dummy || a.external || a.intrinsic
908 || a.optional || a.pointer || a.save || a.target || a.volatile_
909 || a.value || a.access != ACCESS_UNKNOWN || a.intent != INTENT_UNKNOWN)
916 /* Determine if a symbol is generic or not. */
919 generic_sym (gfc_symbol *sym)
923 if (sym->attr.generic ||
924 (sym->attr.intrinsic && gfc_generic_intrinsic (sym->name)))
927 if (was_declared (sym) || sym->ns->parent == NULL)
930 gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
937 return generic_sym (s);
944 /* Determine if a symbol is specific or not. */
947 specific_sym (gfc_symbol *sym)
951 if (sym->attr.if_source == IFSRC_IFBODY
952 || sym->attr.proc == PROC_MODULE
953 || sym->attr.proc == PROC_INTERNAL
954 || sym->attr.proc == PROC_ST_FUNCTION
955 || (sym->attr.intrinsic && gfc_specific_intrinsic (sym->name))
956 || sym->attr.external)
959 if (was_declared (sym) || sym->ns->parent == NULL)
962 gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
964 return (s == NULL) ? 0 : specific_sym (s);
968 /* Figure out if the procedure is specific, generic or unknown. */
971 { PTYPE_GENERIC = 1, PTYPE_SPECIFIC, PTYPE_UNKNOWN }
975 procedure_kind (gfc_symbol *sym)
977 if (generic_sym (sym))
978 return PTYPE_GENERIC;
980 if (specific_sym (sym))
981 return PTYPE_SPECIFIC;
983 return PTYPE_UNKNOWN;
986 /* Check references to assumed size arrays. The flag need_full_assumed_size
987 is nonzero when matching actual arguments. */
989 static int need_full_assumed_size = 0;
992 check_assumed_size_reference (gfc_symbol *sym, gfc_expr *e)
994 if (need_full_assumed_size || !(sym->as && sym->as->type == AS_ASSUMED_SIZE))
997 /* FIXME: The comparison "e->ref->u.ar.type == AR_FULL" is wrong.
998 What should it be? */
999 if ((e->ref->u.ar.end[e->ref->u.ar.as->rank - 1] == NULL)
1000 && (e->ref->u.ar.as->type == AS_ASSUMED_SIZE)
1001 && (e->ref->u.ar.type == AR_FULL))
1003 gfc_error ("The upper bound in the last dimension must "
1004 "appear in the reference to the assumed size "
1005 "array '%s' at %L", sym->name, &e->where);
1012 /* Look for bad assumed size array references in argument expressions
1013 of elemental and array valued intrinsic procedures. Since this is
1014 called from procedure resolution functions, it only recurses at
1018 resolve_assumed_size_actual (gfc_expr *e)
1023 switch (e->expr_type)
1026 if (e->symtree && check_assumed_size_reference (e->symtree->n.sym, e))
1031 if (resolve_assumed_size_actual (e->value.op.op1)
1032 || resolve_assumed_size_actual (e->value.op.op2))
1043 /* Check a generic procedure, passed as an actual argument, to see if
1044 there is a matching specific name. If none, it is an error, and if
1045 more than one, the reference is ambiguous. */
1047 count_specific_procs (gfc_expr *e)
1054 sym = e->symtree->n.sym;
1056 for (p = sym->generic; p; p = p->next)
1057 if (strcmp (sym->name, p->sym->name) == 0)
1059 e->symtree = gfc_find_symtree (p->sym->ns->sym_root,
1065 gfc_error ("'%s' at %L is ambiguous", e->symtree->n.sym->name,
1069 gfc_error ("GENERIC procedure '%s' is not allowed as an actual "
1070 "argument at %L", sym->name, &e->where);
1075 /* Resolve an actual argument list. Most of the time, this is just
1076 resolving the expressions in the list.
1077 The exception is that we sometimes have to decide whether arguments
1078 that look like procedure arguments are really simple variable
1082 resolve_actual_arglist (gfc_actual_arglist *arg, procedure_type ptype,
1083 bool no_formal_args)
1086 gfc_symtree *parent_st;
1088 int save_need_full_assumed_size;
1090 for (; arg; arg = arg->next)
1095 /* Check the label is a valid branching target. */
1098 if (arg->label->defined == ST_LABEL_UNKNOWN)
1100 gfc_error ("Label %d referenced at %L is never defined",
1101 arg->label->value, &arg->label->where);
1108 if (e->expr_type == EXPR_VARIABLE
1109 && e->symtree->n.sym->attr.generic
1111 && count_specific_procs (e) != 1)
1114 if (e->ts.type != BT_PROCEDURE)
1116 save_need_full_assumed_size = need_full_assumed_size;
1117 if (e->expr_type != EXPR_VARIABLE)
1118 need_full_assumed_size = 0;
1119 if (gfc_resolve_expr (e) != SUCCESS)
1121 need_full_assumed_size = save_need_full_assumed_size;
1125 /* See if the expression node should really be a variable reference. */
1127 sym = e->symtree->n.sym;
1129 if (sym->attr.flavor == FL_PROCEDURE
1130 || sym->attr.intrinsic
1131 || sym->attr.external)
1135 /* If a procedure is not already determined to be something else
1136 check if it is intrinsic. */
1137 if (!sym->attr.intrinsic
1138 && !(sym->attr.external || sym->attr.use_assoc
1139 || sym->attr.if_source == IFSRC_IFBODY)
1140 && gfc_is_intrinsic (sym, sym->attr.subroutine, e->where))
1141 sym->attr.intrinsic = 1;
1143 if (sym->attr.proc == PROC_ST_FUNCTION)
1145 gfc_error ("Statement function '%s' at %L is not allowed as an "
1146 "actual argument", sym->name, &e->where);
1149 actual_ok = gfc_intrinsic_actual_ok (sym->name,
1150 sym->attr.subroutine);
1151 if (sym->attr.intrinsic && actual_ok == 0)
1153 gfc_error ("Intrinsic '%s' at %L is not allowed as an "
1154 "actual argument", sym->name, &e->where);
1157 if (sym->attr.contained && !sym->attr.use_assoc
1158 && sym->ns->proc_name->attr.flavor != FL_MODULE)
1160 gfc_error ("Internal procedure '%s' is not allowed as an "
1161 "actual argument at %L", sym->name, &e->where);
1164 if (sym->attr.elemental && !sym->attr.intrinsic)
1166 gfc_error ("ELEMENTAL non-INTRINSIC procedure '%s' is not "
1167 "allowed as an actual argument at %L", sym->name,
1171 /* Check if a generic interface has a specific procedure
1172 with the same name before emitting an error. */
1173 if (sym->attr.generic && count_specific_procs (e) != 1)
1176 /* Just in case a specific was found for the expression. */
1177 sym = e->symtree->n.sym;
1179 if (sym->attr.entry && sym->ns->entries
1180 && sym->ns == gfc_current_ns
1181 && !sym->ns->entries->sym->attr.recursive)
1183 gfc_error ("Reference to ENTRY '%s' at %L is recursive, but procedure "
1184 "'%s' is not declared as RECURSIVE",
1185 sym->name, &e->where, sym->ns->entries->sym->name);
1188 /* If the symbol is the function that names the current (or
1189 parent) scope, then we really have a variable reference. */
1191 if (sym->attr.function && sym->result == sym
1192 && (sym->ns->proc_name == sym
1193 || (sym->ns->parent != NULL
1194 && sym->ns->parent->proc_name == sym)))
1197 /* If all else fails, see if we have a specific intrinsic. */
1198 if (sym->ts.type == BT_UNKNOWN && sym->attr.intrinsic)
1200 gfc_intrinsic_sym *isym;
1202 isym = gfc_find_function (sym->name);
1203 if (isym == NULL || !isym->specific)
1205 gfc_error ("Unable to find a specific INTRINSIC procedure "
1206 "for the reference '%s' at %L", sym->name,
1211 sym->attr.intrinsic = 1;
1212 sym->attr.function = 1;
1217 /* See if the name is a module procedure in a parent unit. */
1219 if (was_declared (sym) || sym->ns->parent == NULL)
1222 if (gfc_find_sym_tree (sym->name, sym->ns->parent, 1, &parent_st))
1224 gfc_error ("Symbol '%s' at %L is ambiguous", sym->name, &e->where);
1228 if (parent_st == NULL)
1231 sym = parent_st->n.sym;
1232 e->symtree = parent_st; /* Point to the right thing. */
1234 if (sym->attr.flavor == FL_PROCEDURE
1235 || sym->attr.intrinsic
1236 || sym->attr.external)
1242 e->expr_type = EXPR_VARIABLE;
1244 if (sym->as != NULL)
1246 e->rank = sym->as->rank;
1247 e->ref = gfc_get_ref ();
1248 e->ref->type = REF_ARRAY;
1249 e->ref->u.ar.type = AR_FULL;
1250 e->ref->u.ar.as = sym->as;
1253 /* Expressions are assigned a default ts.type of BT_PROCEDURE in
1254 primary.c (match_actual_arg). If above code determines that it
1255 is a variable instead, it needs to be resolved as it was not
1256 done at the beginning of this function. */
1257 save_need_full_assumed_size = need_full_assumed_size;
1258 if (e->expr_type != EXPR_VARIABLE)
1259 need_full_assumed_size = 0;
1260 if (gfc_resolve_expr (e) != SUCCESS)
1262 need_full_assumed_size = save_need_full_assumed_size;
1265 /* Check argument list functions %VAL, %LOC and %REF. There is
1266 nothing to do for %REF. */
1267 if (arg->name && arg->name[0] == '%')
1269 if (strncmp ("%VAL", arg->name, 4) == 0)
1271 if (e->ts.type == BT_CHARACTER || e->ts.type == BT_DERIVED)
1273 gfc_error ("By-value argument at %L is not of numeric "
1280 gfc_error ("By-value argument at %L cannot be an array or "
1281 "an array section", &e->where);
1285 /* Intrinsics are still PROC_UNKNOWN here. However,
1286 since same file external procedures are not resolvable
1287 in gfortran, it is a good deal easier to leave them to
1289 if (ptype != PROC_UNKNOWN
1290 && ptype != PROC_DUMMY
1291 && ptype != PROC_EXTERNAL
1292 && ptype != PROC_MODULE)
1294 gfc_error ("By-value argument at %L is not allowed "
1295 "in this context", &e->where);
1300 /* Statement functions have already been excluded above. */
1301 else if (strncmp ("%LOC", arg->name, 4) == 0
1302 && e->ts.type == BT_PROCEDURE)
1304 if (e->symtree->n.sym->attr.proc == PROC_INTERNAL)
1306 gfc_error ("Passing internal procedure at %L by location "
1307 "not allowed", &e->where);
1318 /* Do the checks of the actual argument list that are specific to elemental
1319 procedures. If called with c == NULL, we have a function, otherwise if
1320 expr == NULL, we have a subroutine. */
1323 resolve_elemental_actual (gfc_expr *expr, gfc_code *c)
1325 gfc_actual_arglist *arg0;
1326 gfc_actual_arglist *arg;
1327 gfc_symbol *esym = NULL;
1328 gfc_intrinsic_sym *isym = NULL;
1330 gfc_intrinsic_arg *iformal = NULL;
1331 gfc_formal_arglist *eformal = NULL;
1332 bool formal_optional = false;
1333 bool set_by_optional = false;
1337 /* Is this an elemental procedure? */
1338 if (expr && expr->value.function.actual != NULL)
1340 if (expr->value.function.esym != NULL
1341 && expr->value.function.esym->attr.elemental)
1343 arg0 = expr->value.function.actual;
1344 esym = expr->value.function.esym;
1346 else if (expr->value.function.isym != NULL
1347 && expr->value.function.isym->elemental)
1349 arg0 = expr->value.function.actual;
1350 isym = expr->value.function.isym;
1355 else if (c && c->ext.actual != NULL)
1357 arg0 = c->ext.actual;
1359 if (c->resolved_sym)
1360 esym = c->resolved_sym;
1362 esym = c->symtree->n.sym;
1365 if (!esym->attr.elemental)
1371 /* The rank of an elemental is the rank of its array argument(s). */
1372 for (arg = arg0; arg; arg = arg->next)
1374 if (arg->expr != NULL && arg->expr->rank > 0)
1376 rank = arg->expr->rank;
1377 if (arg->expr->expr_type == EXPR_VARIABLE
1378 && arg->expr->symtree->n.sym->attr.optional)
1379 set_by_optional = true;
1381 /* Function specific; set the result rank and shape. */
1385 if (!expr->shape && arg->expr->shape)
1387 expr->shape = gfc_get_shape (rank);
1388 for (i = 0; i < rank; i++)
1389 mpz_init_set (expr->shape[i], arg->expr->shape[i]);
1396 /* If it is an array, it shall not be supplied as an actual argument
1397 to an elemental procedure unless an array of the same rank is supplied
1398 as an actual argument corresponding to a nonoptional dummy argument of
1399 that elemental procedure(12.4.1.5). */
1400 formal_optional = false;
1402 iformal = isym->formal;
1404 eformal = esym->formal;
1406 for (arg = arg0; arg; arg = arg->next)
1410 if (eformal->sym && eformal->sym->attr.optional)
1411 formal_optional = true;
1412 eformal = eformal->next;
1414 else if (isym && iformal)
1416 if (iformal->optional)
1417 formal_optional = true;
1418 iformal = iformal->next;
1421 formal_optional = true;
1423 if (pedantic && arg->expr != NULL
1424 && arg->expr->expr_type == EXPR_VARIABLE
1425 && arg->expr->symtree->n.sym->attr.optional
1428 && (set_by_optional || arg->expr->rank != rank)
1429 && !(isym && isym->id == GFC_ISYM_CONVERSION))
1431 gfc_warning ("'%s' at %L is an array and OPTIONAL; IF IT IS "
1432 "MISSING, it cannot be the actual argument of an "
1433 "ELEMENTAL procedure unless there is a non-optional "
1434 "argument with the same rank (12.4.1.5)",
1435 arg->expr->symtree->n.sym->name, &arg->expr->where);
1440 for (arg = arg0; arg; arg = arg->next)
1442 if (arg->expr == NULL || arg->expr->rank == 0)
1445 /* Being elemental, the last upper bound of an assumed size array
1446 argument must be present. */
1447 if (resolve_assumed_size_actual (arg->expr))
1450 /* Elemental procedure's array actual arguments must conform. */
1453 if (gfc_check_conformance ("elemental procedure", arg->expr, e)
1461 /* INTENT(OUT) is only allowed for subroutines; if any actual argument
1462 is an array, the intent inout/out variable needs to be also an array. */
1463 if (rank > 0 && esym && expr == NULL)
1464 for (eformal = esym->formal, arg = arg0; arg && eformal;
1465 arg = arg->next, eformal = eformal->next)
1466 if ((eformal->sym->attr.intent == INTENT_OUT
1467 || eformal->sym->attr.intent == INTENT_INOUT)
1468 && arg->expr && arg->expr->rank == 0)
1470 gfc_error ("Actual argument at %L for INTENT(%s) dummy '%s' of "
1471 "ELEMENTAL subroutine '%s' is a scalar, but another "
1472 "actual argument is an array", &arg->expr->where,
1473 (eformal->sym->attr.intent == INTENT_OUT) ? "OUT"
1474 : "INOUT", eformal->sym->name, esym->name);
1481 /* Go through each actual argument in ACTUAL and see if it can be
1482 implemented as an inlined, non-copying intrinsic. FNSYM is the
1483 function being called, or NULL if not known. */
1486 find_noncopying_intrinsics (gfc_symbol *fnsym, gfc_actual_arglist *actual)
1488 gfc_actual_arglist *ap;
1491 for (ap = actual; ap; ap = ap->next)
1493 && (expr = gfc_get_noncopying_intrinsic_argument (ap->expr))
1494 && !gfc_check_fncall_dependency (expr, INTENT_IN, fnsym, actual,
1496 ap->expr->inline_noncopying_intrinsic = 1;
1500 /* This function does the checking of references to global procedures
1501 as defined in sections 18.1 and 14.1, respectively, of the Fortran
1502 77 and 95 standards. It checks for a gsymbol for the name, making
1503 one if it does not already exist. If it already exists, then the
1504 reference being resolved must correspond to the type of gsymbol.
1505 Otherwise, the new symbol is equipped with the attributes of the
1506 reference. The corresponding code that is called in creating
1507 global entities is parse.c. */
1510 resolve_global_procedure (gfc_symbol *sym, locus *where, int sub)
1515 type = sub ? GSYM_SUBROUTINE : GSYM_FUNCTION;
1517 gsym = gfc_get_gsymbol (sym->name);
1519 if ((gsym->type != GSYM_UNKNOWN && gsym->type != type))
1520 gfc_global_used (gsym, where);
1522 if (gsym->type == GSYM_UNKNOWN)
1525 gsym->where = *where;
1532 /************* Function resolution *************/
1534 /* Resolve a function call known to be generic.
1535 Section 14.1.2.4.1. */
1538 resolve_generic_f0 (gfc_expr *expr, gfc_symbol *sym)
1542 if (sym->attr.generic)
1544 s = gfc_search_interface (sym->generic, 0, &expr->value.function.actual);
1547 expr->value.function.name = s->name;
1548 expr->value.function.esym = s;
1550 if (s->ts.type != BT_UNKNOWN)
1552 else if (s->result != NULL && s->result->ts.type != BT_UNKNOWN)
1553 expr->ts = s->result->ts;
1556 expr->rank = s->as->rank;
1557 else if (s->result != NULL && s->result->as != NULL)
1558 expr->rank = s->result->as->rank;
1560 gfc_set_sym_referenced (expr->value.function.esym);
1565 /* TODO: Need to search for elemental references in generic
1569 if (sym->attr.intrinsic)
1570 return gfc_intrinsic_func_interface (expr, 0);
1577 resolve_generic_f (gfc_expr *expr)
1582 sym = expr->symtree->n.sym;
1586 m = resolve_generic_f0 (expr, sym);
1589 else if (m == MATCH_ERROR)
1593 if (sym->ns->parent == NULL)
1595 gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
1599 if (!generic_sym (sym))
1603 /* Last ditch attempt. See if the reference is to an intrinsic
1604 that possesses a matching interface. 14.1.2.4 */
1605 if (sym && !gfc_is_intrinsic (sym, 0, expr->where))
1607 gfc_error ("There is no specific function for the generic '%s' at %L",
1608 expr->symtree->n.sym->name, &expr->where);
1612 m = gfc_intrinsic_func_interface (expr, 0);
1616 gfc_error ("Generic function '%s' at %L is not consistent with a "
1617 "specific intrinsic interface", expr->symtree->n.sym->name,
1624 /* Resolve a function call known to be specific. */
1627 resolve_specific_f0 (gfc_symbol *sym, gfc_expr *expr)
1631 /* See if we have an intrinsic interface. */
1633 if (sym->ts.interface != NULL && sym->ts.interface->attr.intrinsic)
1635 gfc_intrinsic_sym *isym;
1636 isym = gfc_find_function (sym->ts.interface->name);
1638 /* Existence of isym should be checked already. */
1641 sym->ts.type = isym->ts.type;
1642 sym->ts.kind = isym->ts.kind;
1643 sym->attr.function = 1;
1644 sym->attr.proc = PROC_EXTERNAL;
1648 if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
1650 if (sym->attr.dummy)
1652 sym->attr.proc = PROC_DUMMY;
1656 sym->attr.proc = PROC_EXTERNAL;
1660 if (sym->attr.proc == PROC_MODULE
1661 || sym->attr.proc == PROC_ST_FUNCTION
1662 || sym->attr.proc == PROC_INTERNAL)
1665 if (sym->attr.intrinsic)
1667 m = gfc_intrinsic_func_interface (expr, 1);
1671 gfc_error ("Function '%s' at %L is INTRINSIC but is not compatible "
1672 "with an intrinsic", sym->name, &expr->where);
1680 gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
1683 expr->value.function.name = sym->name;
1684 expr->value.function.esym = sym;
1685 if (sym->as != NULL)
1686 expr->rank = sym->as->rank;
1693 resolve_specific_f (gfc_expr *expr)
1698 sym = expr->symtree->n.sym;
1702 m = resolve_specific_f0 (sym, expr);
1705 if (m == MATCH_ERROR)
1708 if (sym->ns->parent == NULL)
1711 gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
1717 gfc_error ("Unable to resolve the specific function '%s' at %L",
1718 expr->symtree->n.sym->name, &expr->where);
1724 /* Resolve a procedure call not known to be generic nor specific. */
1727 resolve_unknown_f (gfc_expr *expr)
1732 sym = expr->symtree->n.sym;
1734 if (sym->attr.dummy)
1736 sym->attr.proc = PROC_DUMMY;
1737 expr->value.function.name = sym->name;
1741 /* See if we have an intrinsic function reference. */
1743 if (gfc_is_intrinsic (sym, 0, expr->where))
1745 if (gfc_intrinsic_func_interface (expr, 1) == MATCH_YES)
1750 /* The reference is to an external name. */
1752 sym->attr.proc = PROC_EXTERNAL;
1753 expr->value.function.name = sym->name;
1754 expr->value.function.esym = expr->symtree->n.sym;
1756 if (sym->as != NULL)
1757 expr->rank = sym->as->rank;
1759 /* Type of the expression is either the type of the symbol or the
1760 default type of the symbol. */
1763 gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
1765 if (sym->ts.type != BT_UNKNOWN)
1769 ts = gfc_get_default_type (sym, sym->ns);
1771 if (ts->type == BT_UNKNOWN)
1773 gfc_error ("Function '%s' at %L has no IMPLICIT type",
1774 sym->name, &expr->where);
1785 /* Return true, if the symbol is an external procedure. */
1787 is_external_proc (gfc_symbol *sym)
1789 if (!sym->attr.dummy && !sym->attr.contained
1790 && !(sym->attr.intrinsic
1791 || gfc_is_intrinsic (sym, sym->attr.subroutine, sym->declared_at))
1792 && sym->attr.proc != PROC_ST_FUNCTION
1793 && !sym->attr.use_assoc
1801 /* Figure out if a function reference is pure or not. Also set the name
1802 of the function for a potential error message. Return nonzero if the
1803 function is PURE, zero if not. */
1805 pure_stmt_function (gfc_expr *, gfc_symbol *);
1808 pure_function (gfc_expr *e, const char **name)
1814 if (e->symtree != NULL
1815 && e->symtree->n.sym != NULL
1816 && e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
1817 return pure_stmt_function (e, e->symtree->n.sym);
1819 if (e->value.function.esym)
1821 pure = gfc_pure (e->value.function.esym);
1822 *name = e->value.function.esym->name;
1824 else if (e->value.function.isym)
1826 pure = e->value.function.isym->pure
1827 || e->value.function.isym->elemental;
1828 *name = e->value.function.isym->name;
1832 /* Implicit functions are not pure. */
1834 *name = e->value.function.name;
1842 impure_stmt_fcn (gfc_expr *e, gfc_symbol *sym,
1843 int *f ATTRIBUTE_UNUSED)
1847 /* Don't bother recursing into other statement functions
1848 since they will be checked individually for purity. */
1849 if (e->expr_type != EXPR_FUNCTION
1851 || e->symtree->n.sym == sym
1852 || e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
1855 return pure_function (e, &name) ? false : true;
1860 pure_stmt_function (gfc_expr *e, gfc_symbol *sym)
1862 return gfc_traverse_expr (e, sym, impure_stmt_fcn, 0) ? 0 : 1;
1867 is_scalar_expr_ptr (gfc_expr *expr)
1869 gfc_try retval = SUCCESS;
1874 /* See if we have a gfc_ref, which means we have a substring, array
1875 reference, or a component. */
1876 if (expr->ref != NULL)
1879 while (ref->next != NULL)
1885 if (ref->u.ss.length != NULL
1886 && ref->u.ss.length->length != NULL
1888 && ref->u.ss.start->expr_type == EXPR_CONSTANT
1890 && ref->u.ss.end->expr_type == EXPR_CONSTANT)
1892 start = (int) mpz_get_si (ref->u.ss.start->value.integer);
1893 end = (int) mpz_get_si (ref->u.ss.end->value.integer);
1894 if (end - start + 1 != 1)
1901 if (ref->u.ar.type == AR_ELEMENT)
1903 else if (ref->u.ar.type == AR_FULL)
1905 /* The user can give a full array if the array is of size 1. */
1906 if (ref->u.ar.as != NULL
1907 && ref->u.ar.as->rank == 1
1908 && ref->u.ar.as->type == AS_EXPLICIT
1909 && ref->u.ar.as->lower[0] != NULL
1910 && ref->u.ar.as->lower[0]->expr_type == EXPR_CONSTANT
1911 && ref->u.ar.as->upper[0] != NULL
1912 && ref->u.ar.as->upper[0]->expr_type == EXPR_CONSTANT)
1914 /* If we have a character string, we need to check if
1915 its length is one. */
1916 if (expr->ts.type == BT_CHARACTER)
1918 if (expr->ts.cl == NULL
1919 || expr->ts.cl->length == NULL
1920 || mpz_cmp_si (expr->ts.cl->length->value.integer, 1)
1926 /* We have constant lower and upper bounds. If the
1927 difference between is 1, it can be considered a
1929 start = (int) mpz_get_si
1930 (ref->u.ar.as->lower[0]->value.integer);
1931 end = (int) mpz_get_si
1932 (ref->u.ar.as->upper[0]->value.integer);
1933 if (end - start + 1 != 1)
1948 else if (expr->ts.type == BT_CHARACTER && expr->rank == 0)
1950 /* Character string. Make sure it's of length 1. */
1951 if (expr->ts.cl == NULL
1952 || expr->ts.cl->length == NULL
1953 || mpz_cmp_si (expr->ts.cl->length->value.integer, 1) != 0)
1956 else if (expr->rank != 0)
1963 /* Match one of the iso_c_binding functions (c_associated or c_loc)
1964 and, in the case of c_associated, set the binding label based on
1968 gfc_iso_c_func_interface (gfc_symbol *sym, gfc_actual_arglist *args,
1969 gfc_symbol **new_sym)
1971 char name[GFC_MAX_SYMBOL_LEN + 1];
1972 char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
1973 int optional_arg = 0;
1974 gfc_try retval = SUCCESS;
1975 gfc_symbol *args_sym;
1976 gfc_typespec *arg_ts;
1977 gfc_ref *parent_ref;
1980 if (args->expr->expr_type == EXPR_CONSTANT
1981 || args->expr->expr_type == EXPR_OP
1982 || args->expr->expr_type == EXPR_NULL)
1984 gfc_error ("Argument to '%s' at %L is not a variable",
1985 sym->name, &(args->expr->where));
1989 args_sym = args->expr->symtree->n.sym;
1991 /* The typespec for the actual arg should be that stored in the expr
1992 and not necessarily that of the expr symbol (args_sym), because
1993 the actual expression could be a part-ref of the expr symbol. */
1994 arg_ts = &(args->expr->ts);
1996 /* Get the parent reference (if any) for the expression. This happens for
1997 cases such as a%b%c. */
1998 parent_ref = args->expr->ref;
2000 if (parent_ref != NULL)
2002 curr_ref = parent_ref->next;
2003 while (curr_ref != NULL && curr_ref->next != NULL)
2005 parent_ref = curr_ref;
2006 curr_ref = curr_ref->next;
2010 /* If curr_ref is non-NULL, we had a part-ref expression. If the curr_ref
2011 is for a REF_COMPONENT, then we need to use it as the parent_ref for
2012 the name, etc. Otherwise, the current parent_ref should be correct. */
2013 if (curr_ref != NULL && curr_ref->type == REF_COMPONENT)
2014 parent_ref = curr_ref;
2016 if (parent_ref == args->expr->ref)
2018 else if (parent_ref != NULL && parent_ref->type != REF_COMPONENT)
2019 gfc_internal_error ("Unexpected expression reference type in "
2020 "gfc_iso_c_func_interface");
2022 if (sym->intmod_sym_id == ISOCBINDING_ASSOCIATED)
2024 /* If the user gave two args then they are providing something for
2025 the optional arg (the second cptr). Therefore, set the name and
2026 binding label to the c_associated for two cptrs. Otherwise,
2027 set c_associated to expect one cptr. */
2031 sprintf (name, "%s_2", sym->name);
2032 sprintf (binding_label, "%s_2", sym->binding_label);
2038 sprintf (name, "%s_1", sym->name);
2039 sprintf (binding_label, "%s_1", sym->binding_label);
2043 /* Get a new symbol for the version of c_associated that
2045 *new_sym = get_iso_c_sym (sym, name, binding_label, optional_arg);
2047 else if (sym->intmod_sym_id == ISOCBINDING_LOC
2048 || sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2050 sprintf (name, "%s", sym->name);
2051 sprintf (binding_label, "%s", sym->binding_label);
2053 /* Error check the call. */
2054 if (args->next != NULL)
2056 gfc_error_now ("More actual than formal arguments in '%s' "
2057 "call at %L", name, &(args->expr->where));
2060 else if (sym->intmod_sym_id == ISOCBINDING_LOC)
2062 /* Make sure we have either the target or pointer attribute. */
2063 if (!(args_sym->attr.target)
2064 && !(args_sym->attr.pointer)
2065 && (parent_ref == NULL ||
2066 !parent_ref->u.c.component->attr.pointer))
2068 gfc_error_now ("Parameter '%s' to '%s' at %L must be either "
2069 "a TARGET or an associated pointer",
2071 sym->name, &(args->expr->where));
2075 /* See if we have interoperable type and type param. */
2076 if (verify_c_interop (arg_ts,
2077 (parent_ref ? parent_ref->u.c.component->name
2079 &(args->expr->where)) == SUCCESS
2080 || gfc_check_any_c_kind (arg_ts) == SUCCESS)
2082 if (args_sym->attr.target == 1)
2084 /* Case 1a, section 15.1.2.5, J3/04-007: variable that
2085 has the target attribute and is interoperable. */
2086 /* Case 1b, section 15.1.2.5, J3/04-007: allocated
2087 allocatable variable that has the TARGET attribute and
2088 is not an array of zero size. */
2089 if (args_sym->attr.allocatable == 1)
2091 if (args_sym->attr.dimension != 0
2092 && (args_sym->as && args_sym->as->rank == 0))
2094 gfc_error_now ("Allocatable variable '%s' used as a "
2095 "parameter to '%s' at %L must not be "
2096 "an array of zero size",
2097 args_sym->name, sym->name,
2098 &(args->expr->where));
2104 /* A non-allocatable target variable with C
2105 interoperable type and type parameters must be
2107 if (args_sym && args_sym->attr.dimension)
2109 if (args_sym->as->type == AS_ASSUMED_SHAPE)
2111 gfc_error ("Assumed-shape array '%s' at %L "
2112 "cannot be an argument to the "
2113 "procedure '%s' because "
2114 "it is not C interoperable",
2116 &(args->expr->where), sym->name);
2119 else if (args_sym->as->type == AS_DEFERRED)
2121 gfc_error ("Deferred-shape array '%s' at %L "
2122 "cannot be an argument to the "
2123 "procedure '%s' because "
2124 "it is not C interoperable",
2126 &(args->expr->where), sym->name);
2131 /* Make sure it's not a character string. Arrays of
2132 any type should be ok if the variable is of a C
2133 interoperable type. */
2134 if (arg_ts->type == BT_CHARACTER)
2135 if (arg_ts->cl != NULL
2136 && (arg_ts->cl->length == NULL
2137 || arg_ts->cl->length->expr_type
2140 (arg_ts->cl->length->value.integer, 1)
2142 && is_scalar_expr_ptr (args->expr) != SUCCESS)
2144 gfc_error_now ("CHARACTER argument '%s' to '%s' "
2145 "at %L must have a length of 1",
2146 args_sym->name, sym->name,
2147 &(args->expr->where));
2152 else if ((args_sym->attr.pointer == 1 ||
2154 && parent_ref->u.c.component->attr.pointer))
2155 && is_scalar_expr_ptr (args->expr) != SUCCESS)
2157 /* Case 1c, section 15.1.2.5, J3/04-007: an associated
2159 gfc_error_now ("Argument '%s' to '%s' at %L must be an "
2160 "associated scalar POINTER", args_sym->name,
2161 sym->name, &(args->expr->where));
2167 /* The parameter is not required to be C interoperable. If it
2168 is not C interoperable, it must be a nonpolymorphic scalar
2169 with no length type parameters. It still must have either
2170 the pointer or target attribute, and it can be
2171 allocatable (but must be allocated when c_loc is called). */
2172 if (args->expr->rank != 0
2173 && is_scalar_expr_ptr (args->expr) != SUCCESS)
2175 gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2176 "scalar", args_sym->name, sym->name,
2177 &(args->expr->where));
2180 else if (arg_ts->type == BT_CHARACTER
2181 && is_scalar_expr_ptr (args->expr) != SUCCESS)
2183 gfc_error_now ("CHARACTER argument '%s' to '%s' at "
2184 "%L must have a length of 1",
2185 args_sym->name, sym->name,
2186 &(args->expr->where));
2191 else if (sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2193 if (args_sym->attr.flavor != FL_PROCEDURE)
2195 /* TODO: Update this error message to allow for procedure
2196 pointers once they are implemented. */
2197 gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2199 args_sym->name, sym->name,
2200 &(args->expr->where));
2203 else if (args_sym->attr.is_bind_c != 1)
2205 gfc_error_now ("Parameter '%s' to '%s' at %L must be "
2207 args_sym->name, sym->name,
2208 &(args->expr->where));
2213 /* for c_loc/c_funloc, the new symbol is the same as the old one */
2218 gfc_internal_error ("gfc_iso_c_func_interface(): Unhandled "
2219 "iso_c_binding function: '%s'!\n", sym->name);
2226 /* Resolve a function call, which means resolving the arguments, then figuring
2227 out which entity the name refers to. */
2228 /* TODO: Check procedure arguments so that an INTENT(IN) isn't passed
2229 to INTENT(OUT) or INTENT(INOUT). */
2232 resolve_function (gfc_expr *expr)
2234 gfc_actual_arglist *arg;
2239 procedure_type p = PROC_INTRINSIC;
2240 bool no_formal_args;
2244 sym = expr->symtree->n.sym;
2246 if (sym && sym->attr.intrinsic
2247 && !gfc_find_function (sym->name)
2248 && gfc_find_subroutine (sym->name)
2249 && sym->attr.function)
2251 gfc_error ("Intrinsic subroutine '%s' used as "
2252 "a function at %L", sym->name, &expr->where);
2256 if (sym && sym->attr.flavor == FL_VARIABLE)
2258 gfc_error ("'%s' at %L is not a function", sym->name, &expr->where);
2262 if (sym && sym->attr.abstract)
2264 gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
2265 sym->name, &expr->where);
2269 /* If the procedure is external, check for usage. */
2270 if (sym && is_external_proc (sym))
2271 resolve_global_procedure (sym, &expr->where, 0);
2273 /* Switch off assumed size checking and do this again for certain kinds
2274 of procedure, once the procedure itself is resolved. */
2275 need_full_assumed_size++;
2277 if (expr->symtree && expr->symtree->n.sym)
2278 p = expr->symtree->n.sym->attr.proc;
2280 no_formal_args = sym && is_external_proc (sym) && sym->formal == NULL;
2281 if (resolve_actual_arglist (expr->value.function.actual,
2282 p, no_formal_args) == FAILURE)
2285 /* Need to setup the call to the correct c_associated, depending on
2286 the number of cptrs to user gives to compare. */
2287 if (sym && sym->attr.is_iso_c == 1)
2289 if (gfc_iso_c_func_interface (sym, expr->value.function.actual, &sym)
2293 /* Get the symtree for the new symbol (resolved func).
2294 the old one will be freed later, when it's no longer used. */
2295 gfc_find_sym_tree (sym->name, sym->ns, 1, &(expr->symtree));
2298 /* Resume assumed_size checking. */
2299 need_full_assumed_size--;
2301 if (sym && sym->ts.type == BT_CHARACTER
2303 && sym->ts.cl->length == NULL
2305 && expr->value.function.esym == NULL
2306 && !sym->attr.contained)
2308 /* Internal procedures are taken care of in resolve_contained_fntype. */
2309 gfc_error ("Function '%s' is declared CHARACTER(*) and cannot "
2310 "be used at %L since it is not a dummy argument",
2311 sym->name, &expr->where);
2315 /* See if function is already resolved. */
2317 if (expr->value.function.name != NULL)
2319 if (expr->ts.type == BT_UNKNOWN)
2325 /* Apply the rules of section 14.1.2. */
2327 switch (procedure_kind (sym))
2330 t = resolve_generic_f (expr);
2333 case PTYPE_SPECIFIC:
2334 t = resolve_specific_f (expr);
2338 t = resolve_unknown_f (expr);
2342 gfc_internal_error ("resolve_function(): bad function type");
2346 /* If the expression is still a function (it might have simplified),
2347 then we check to see if we are calling an elemental function. */
2349 if (expr->expr_type != EXPR_FUNCTION)
2352 temp = need_full_assumed_size;
2353 need_full_assumed_size = 0;
2355 if (resolve_elemental_actual (expr, NULL) == FAILURE)
2358 if (omp_workshare_flag
2359 && expr->value.function.esym
2360 && ! gfc_elemental (expr->value.function.esym))
2362 gfc_error ("User defined non-ELEMENTAL function '%s' at %L not allowed "
2363 "in WORKSHARE construct", expr->value.function.esym->name,
2368 #define GENERIC_ID expr->value.function.isym->id
2369 else if (expr->value.function.actual != NULL
2370 && expr->value.function.isym != NULL
2371 && GENERIC_ID != GFC_ISYM_LBOUND
2372 && GENERIC_ID != GFC_ISYM_LEN
2373 && GENERIC_ID != GFC_ISYM_LOC
2374 && GENERIC_ID != GFC_ISYM_PRESENT)
2376 /* Array intrinsics must also have the last upper bound of an
2377 assumed size array argument. UBOUND and SIZE have to be
2378 excluded from the check if the second argument is anything
2381 for (arg = expr->value.function.actual; arg; arg = arg->next)
2383 if ((GENERIC_ID == GFC_ISYM_UBOUND || GENERIC_ID == GFC_ISYM_SIZE)
2384 && arg->next != NULL && arg->next->expr)
2386 if (arg->next->expr->expr_type != EXPR_CONSTANT)
2389 if (arg->next->name && strncmp(arg->next->name, "kind", 4) == 0)
2392 if ((int)mpz_get_si (arg->next->expr->value.integer)
2397 if (arg->expr != NULL
2398 && arg->expr->rank > 0
2399 && resolve_assumed_size_actual (arg->expr))
2405 need_full_assumed_size = temp;
2408 if (!pure_function (expr, &name) && name)
2412 gfc_error ("reference to non-PURE function '%s' at %L inside a "
2413 "FORALL %s", name, &expr->where,
2414 forall_flag == 2 ? "mask" : "block");
2417 else if (gfc_pure (NULL))
2419 gfc_error ("Function reference to '%s' at %L is to a non-PURE "
2420 "procedure within a PURE procedure", name, &expr->where);
2425 /* Functions without the RECURSIVE attribution are not allowed to
2426 * call themselves. */
2427 if (expr->value.function.esym && !expr->value.function.esym->attr.recursive)
2429 gfc_symbol *esym, *proc;
2430 esym = expr->value.function.esym;
2431 proc = gfc_current_ns->proc_name;
2434 gfc_error ("Function '%s' at %L cannot call itself, as it is not "
2435 "RECURSIVE", name, &expr->where);
2439 if (esym->attr.entry && esym->ns->entries && proc->ns->entries
2440 && esym->ns->entries->sym == proc->ns->entries->sym)
2442 gfc_error ("Call to ENTRY '%s' at %L is recursive, but function "
2443 "'%s' is not declared as RECURSIVE",
2444 esym->name, &expr->where, esym->ns->entries->sym->name);
2449 /* Character lengths of use associated functions may contains references to
2450 symbols not referenced from the current program unit otherwise. Make sure
2451 those symbols are marked as referenced. */
2453 if (expr->ts.type == BT_CHARACTER && expr->value.function.esym
2454 && expr->value.function.esym->attr.use_assoc)
2456 gfc_expr_set_symbols_referenced (expr->ts.cl->length);
2460 && !((expr->value.function.esym
2461 && expr->value.function.esym->attr.elemental)
2463 (expr->value.function.isym
2464 && expr->value.function.isym->elemental)))
2465 find_noncopying_intrinsics (expr->value.function.esym,
2466 expr->value.function.actual);
2468 /* Make sure that the expression has a typespec that works. */
2469 if (expr->ts.type == BT_UNKNOWN)
2471 if (expr->symtree->n.sym->result
2472 && expr->symtree->n.sym->result->ts.type != BT_UNKNOWN)
2473 expr->ts = expr->symtree->n.sym->result->ts;
2480 /************* Subroutine resolution *************/
2483 pure_subroutine (gfc_code *c, gfc_symbol *sym)
2489 gfc_error ("Subroutine call to '%s' in FORALL block at %L is not PURE",
2490 sym->name, &c->loc);
2491 else if (gfc_pure (NULL))
2492 gfc_error ("Subroutine call to '%s' at %L is not PURE", sym->name,
2498 resolve_generic_s0 (gfc_code *c, gfc_symbol *sym)
2502 if (sym->attr.generic)
2504 s = gfc_search_interface (sym->generic, 1, &c->ext.actual);
2507 c->resolved_sym = s;
2508 pure_subroutine (c, s);
2512 /* TODO: Need to search for elemental references in generic interface. */
2515 if (sym->attr.intrinsic)
2516 return gfc_intrinsic_sub_interface (c, 0);
2523 resolve_generic_s (gfc_code *c)
2528 sym = c->symtree->n.sym;
2532 m = resolve_generic_s0 (c, sym);
2535 else if (m == MATCH_ERROR)
2539 if (sym->ns->parent == NULL)
2541 gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2545 if (!generic_sym (sym))
2549 /* Last ditch attempt. See if the reference is to an intrinsic
2550 that possesses a matching interface. 14.1.2.4 */
2551 sym = c->symtree->n.sym;
2553 if (!gfc_is_intrinsic (sym, 1, c->loc))
2555 gfc_error ("There is no specific subroutine for the generic '%s' at %L",
2556 sym->name, &c->loc);
2560 m = gfc_intrinsic_sub_interface (c, 0);
2564 gfc_error ("Generic subroutine '%s' at %L is not consistent with an "
2565 "intrinsic subroutine interface", sym->name, &c->loc);
2571 /* Set the name and binding label of the subroutine symbol in the call
2572 expression represented by 'c' to include the type and kind of the
2573 second parameter. This function is for resolving the appropriate
2574 version of c_f_pointer() and c_f_procpointer(). For example, a
2575 call to c_f_pointer() for a default integer pointer could have a
2576 name of c_f_pointer_i4. If no second arg exists, which is an error
2577 for these two functions, it defaults to the generic symbol's name
2578 and binding label. */
2581 set_name_and_label (gfc_code *c, gfc_symbol *sym,
2582 char *name, char *binding_label)
2584 gfc_expr *arg = NULL;
2588 /* The second arg of c_f_pointer and c_f_procpointer determines
2589 the type and kind for the procedure name. */
2590 arg = c->ext.actual->next->expr;
2594 /* Set up the name to have the given symbol's name,
2595 plus the type and kind. */
2596 /* a derived type is marked with the type letter 'u' */
2597 if (arg->ts.type == BT_DERIVED)
2600 kind = 0; /* set the kind as 0 for now */
2604 type = gfc_type_letter (arg->ts.type);
2605 kind = arg->ts.kind;
2608 if (arg->ts.type == BT_CHARACTER)
2609 /* Kind info for character strings not needed. */
2612 sprintf (name, "%s_%c%d", sym->name, type, kind);
2613 /* Set up the binding label as the given symbol's label plus
2614 the type and kind. */
2615 sprintf (binding_label, "%s_%c%d", sym->binding_label, type, kind);
2619 /* If the second arg is missing, set the name and label as
2620 was, cause it should at least be found, and the missing
2621 arg error will be caught by compare_parameters(). */
2622 sprintf (name, "%s", sym->name);
2623 sprintf (binding_label, "%s", sym->binding_label);
2630 /* Resolve a generic version of the iso_c_binding procedure given
2631 (sym) to the specific one based on the type and kind of the
2632 argument(s). Currently, this function resolves c_f_pointer() and
2633 c_f_procpointer based on the type and kind of the second argument
2634 (FPTR). Other iso_c_binding procedures aren't specially handled.
2635 Upon successfully exiting, c->resolved_sym will hold the resolved
2636 symbol. Returns MATCH_ERROR if an error occurred; MATCH_YES
2640 gfc_iso_c_sub_interface (gfc_code *c, gfc_symbol *sym)
2642 gfc_symbol *new_sym;
2643 /* this is fine, since we know the names won't use the max */
2644 char name[GFC_MAX_SYMBOL_LEN + 1];
2645 char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
2646 /* default to success; will override if find error */
2647 match m = MATCH_YES;
2649 /* Make sure the actual arguments are in the necessary order (based on the
2650 formal args) before resolving. */
2651 gfc_procedure_use (sym, &c->ext.actual, &(c->loc));
2653 if ((sym->intmod_sym_id == ISOCBINDING_F_POINTER) ||
2654 (sym->intmod_sym_id == ISOCBINDING_F_PROCPOINTER))
2656 set_name_and_label (c, sym, name, binding_label);
2658 if (sym->intmod_sym_id == ISOCBINDING_F_POINTER)
2660 if (c->ext.actual != NULL && c->ext.actual->next != NULL)
2662 /* Make sure we got a third arg if the second arg has non-zero
2663 rank. We must also check that the type and rank are
2664 correct since we short-circuit this check in
2665 gfc_procedure_use() (called above to sort actual args). */
2666 if (c->ext.actual->next->expr->rank != 0)
2668 if(c->ext.actual->next->next == NULL
2669 || c->ext.actual->next->next->expr == NULL)
2672 gfc_error ("Missing SHAPE parameter for call to %s "
2673 "at %L", sym->name, &(c->loc));
2675 else if (c->ext.actual->next->next->expr->ts.type
2677 || c->ext.actual->next->next->expr->rank != 1)
2680 gfc_error ("SHAPE parameter for call to %s at %L must "
2681 "be a rank 1 INTEGER array", sym->name,
2688 if (m != MATCH_ERROR)
2690 /* the 1 means to add the optional arg to formal list */
2691 new_sym = get_iso_c_sym (sym, name, binding_label, 1);
2693 /* for error reporting, say it's declared where the original was */
2694 new_sym->declared_at = sym->declared_at;
2699 /* no differences for c_loc or c_funloc */
2703 /* set the resolved symbol */
2704 if (m != MATCH_ERROR)
2705 c->resolved_sym = new_sym;
2707 c->resolved_sym = sym;
2713 /* Resolve a subroutine call known to be specific. */
2716 resolve_specific_s0 (gfc_code *c, gfc_symbol *sym)
2720 /* See if we have an intrinsic interface. */
2721 if (sym->ts.interface != NULL && !sym->ts.interface->attr.abstract
2722 && !sym->ts.interface->attr.subroutine)
2724 gfc_intrinsic_sym *isym;
2726 isym = gfc_find_function (sym->ts.interface->name);
2728 /* Existence of isym should be checked already. */
2731 sym->ts.type = isym->ts.type;
2732 sym->ts.kind = isym->ts.kind;
2733 sym->attr.subroutine = 1;
2737 if(sym->attr.is_iso_c)
2739 m = gfc_iso_c_sub_interface (c,sym);
2743 if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
2745 if (sym->attr.dummy)
2747 sym->attr.proc = PROC_DUMMY;
2751 sym->attr.proc = PROC_EXTERNAL;
2755 if (sym->attr.proc == PROC_MODULE || sym->attr.proc == PROC_INTERNAL)
2758 if (sym->attr.intrinsic)
2760 m = gfc_intrinsic_sub_interface (c, 1);
2764 gfc_error ("Subroutine '%s' at %L is INTRINSIC but is not compatible "
2765 "with an intrinsic", sym->name, &c->loc);
2773 gfc_procedure_use (sym, &c->ext.actual, &c->loc);
2775 c->resolved_sym = sym;
2776 pure_subroutine (c, sym);
2783 resolve_specific_s (gfc_code *c)
2788 sym = c->symtree->n.sym;
2792 m = resolve_specific_s0 (c, sym);
2795 if (m == MATCH_ERROR)
2798 if (sym->ns->parent == NULL)
2801 gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2807 sym = c->symtree->n.sym;
2808 gfc_error ("Unable to resolve the specific subroutine '%s' at %L",
2809 sym->name, &c->loc);
2815 /* Resolve a subroutine call not known to be generic nor specific. */
2818 resolve_unknown_s (gfc_code *c)
2822 sym = c->symtree->n.sym;
2824 if (sym->attr.dummy)
2826 sym->attr.proc = PROC_DUMMY;
2830 /* See if we have an intrinsic function reference. */
2832 if (gfc_is_intrinsic (sym, 1, c->loc))
2834 if (gfc_intrinsic_sub_interface (c, 1) == MATCH_YES)
2839 /* The reference is to an external name. */
2842 gfc_procedure_use (sym, &c->ext.actual, &c->loc);
2844 c->resolved_sym = sym;
2846 pure_subroutine (c, sym);
2852 /* Resolve a subroutine call. Although it was tempting to use the same code
2853 for functions, subroutines and functions are stored differently and this
2854 makes things awkward. */
2857 resolve_call (gfc_code *c)
2860 procedure_type ptype = PROC_INTRINSIC;
2861 gfc_symbol *csym, *sym;
2862 bool no_formal_args;
2864 csym = c->symtree ? c->symtree->n.sym : NULL;
2866 if (csym && csym->ts.type != BT_UNKNOWN)
2868 gfc_error ("'%s' at %L has a type, which is not consistent with "
2869 "the CALL at %L", csym->name, &csym->declared_at, &c->loc);
2873 if (csym && gfc_current_ns->parent && csym->ns != gfc_current_ns)
2875 gfc_find_symbol (csym->name, gfc_current_ns, 1, &sym);
2876 if (sym && csym != sym
2877 && sym->ns == gfc_current_ns
2878 && sym->attr.flavor == FL_PROCEDURE
2879 && sym->attr.contained)
2883 c->symtree->n.sym = sym;
2887 /* If external, check for usage. */
2888 if (csym && is_external_proc (csym))
2889 resolve_global_procedure (csym, &c->loc, 1);
2891 /* Subroutines without the RECURSIVE attribution are not allowed to
2892 * call themselves. */
2893 if (csym && !csym->attr.recursive)
2896 proc = gfc_current_ns->proc_name;
2899 gfc_error ("SUBROUTINE '%s' at %L cannot call itself, as it is not "
2900 "RECURSIVE", csym->name, &c->loc);
2904 if (csym->attr.entry && csym->ns->entries && proc->ns->entries
2905 && csym->ns->entries->sym == proc->ns->entries->sym)
2907 gfc_error ("Call to ENTRY '%s' at %L is recursive, but subroutine "
2908 "'%s' is not declared as RECURSIVE",
2909 csym->name, &c->loc, csym->ns->entries->sym->name);
2914 /* Switch off assumed size checking and do this again for certain kinds
2915 of procedure, once the procedure itself is resolved. */
2916 need_full_assumed_size++;
2919 ptype = csym->attr.proc;
2921 no_formal_args = csym && is_external_proc (csym) && csym->formal == NULL;
2922 if (resolve_actual_arglist (c->ext.actual, ptype,
2923 no_formal_args) == FAILURE)
2926 /* Resume assumed_size checking. */
2927 need_full_assumed_size--;
2930 if (c->resolved_sym == NULL)
2932 c->resolved_isym = NULL;
2933 switch (procedure_kind (csym))
2936 t = resolve_generic_s (c);
2939 case PTYPE_SPECIFIC:
2940 t = resolve_specific_s (c);
2944 t = resolve_unknown_s (c);
2948 gfc_internal_error ("resolve_subroutine(): bad function type");
2952 /* Some checks of elemental subroutine actual arguments. */
2953 if (resolve_elemental_actual (NULL, c) == FAILURE)
2956 if (t == SUCCESS && !(c->resolved_sym && c->resolved_sym->attr.elemental))
2957 find_noncopying_intrinsics (c->resolved_sym, c->ext.actual);
2962 /* Compare the shapes of two arrays that have non-NULL shapes. If both
2963 op1->shape and op2->shape are non-NULL return SUCCESS if their shapes
2964 match. If both op1->shape and op2->shape are non-NULL return FAILURE
2965 if their shapes do not match. If either op1->shape or op2->shape is
2966 NULL, return SUCCESS. */
2969 compare_shapes (gfc_expr *op1, gfc_expr *op2)
2976 if (op1->shape != NULL && op2->shape != NULL)
2978 for (i = 0; i < op1->rank; i++)
2980 if (mpz_cmp (op1->shape[i], op2->shape[i]) != 0)
2982 gfc_error ("Shapes for operands at %L and %L are not conformable",
2983 &op1->where, &op2->where);
2994 /* Resolve an operator expression node. This can involve replacing the
2995 operation with a user defined function call. */
2998 resolve_operator (gfc_expr *e)
3000 gfc_expr *op1, *op2;
3002 bool dual_locus_error;
3005 /* Resolve all subnodes-- give them types. */
3007 switch (e->value.op.op)
3010 if (gfc_resolve_expr (e->value.op.op2) == FAILURE)
3013 /* Fall through... */
3016 case INTRINSIC_UPLUS:
3017 case INTRINSIC_UMINUS:
3018 case INTRINSIC_PARENTHESES:
3019 if (gfc_resolve_expr (e->value.op.op1) == FAILURE)
3024 /* Typecheck the new node. */
3026 op1 = e->value.op.op1;
3027 op2 = e->value.op.op2;
3028 dual_locus_error = false;
3030 if ((op1 && op1->expr_type == EXPR_NULL)
3031 || (op2 && op2->expr_type == EXPR_NULL))
3033 sprintf (msg, _("Invalid context for NULL() pointer at %%L"));
3037 switch (e->value.op.op)
3039 case INTRINSIC_UPLUS:
3040 case INTRINSIC_UMINUS:
3041 if (op1->ts.type == BT_INTEGER
3042 || op1->ts.type == BT_REAL
3043 || op1->ts.type == BT_COMPLEX)
3049 sprintf (msg, _("Operand of unary numeric operator '%s' at %%L is %s"),
3050 gfc_op2string (e->value.op.op), gfc_typename (&e->ts));
3053 case INTRINSIC_PLUS:
3054 case INTRINSIC_MINUS:
3055 case INTRINSIC_TIMES:
3056 case INTRINSIC_DIVIDE:
3057 case INTRINSIC_POWER:
3058 if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3060 gfc_type_convert_binary (e);
3065 _("Operands of binary numeric operator '%s' at %%L are %s/%s"),
3066 gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3067 gfc_typename (&op2->ts));
3070 case INTRINSIC_CONCAT:
3071 if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3072 && op1->ts.kind == op2->ts.kind)
3074 e->ts.type = BT_CHARACTER;
3075 e->ts.kind = op1->ts.kind;
3080 _("Operands of string concatenation operator at %%L are %s/%s"),
3081 gfc_typename (&op1->ts), gfc_typename (&op2->ts));
3087 case INTRINSIC_NEQV:
3088 if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3090 e->ts.type = BT_LOGICAL;
3091 e->ts.kind = gfc_kind_max (op1, op2);
3092 if (op1->ts.kind < e->ts.kind)
3093 gfc_convert_type (op1, &e->ts, 2);
3094 else if (op2->ts.kind < e->ts.kind)
3095 gfc_convert_type (op2, &e->ts, 2);
3099 sprintf (msg, _("Operands of logical operator '%s' at %%L are %s/%s"),
3100 gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3101 gfc_typename (&op2->ts));
3106 if (op1->ts.type == BT_LOGICAL)
3108 e->ts.type = BT_LOGICAL;
3109 e->ts.kind = op1->ts.kind;
3113 sprintf (msg, _("Operand of .not. operator at %%L is %s"),
3114 gfc_typename (&op1->ts));
3118 case INTRINSIC_GT_OS:
3120 case INTRINSIC_GE_OS:
3122 case INTRINSIC_LT_OS:
3124 case INTRINSIC_LE_OS:
3125 if (op1->ts.type == BT_COMPLEX || op2->ts.type == BT_COMPLEX)
3127 strcpy (msg, _("COMPLEX quantities cannot be compared at %L"));
3131 /* Fall through... */
3134 case INTRINSIC_EQ_OS:
3136 case INTRINSIC_NE_OS:
3137 if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3138 && op1->ts.kind == op2->ts.kind)
3140 e->ts.type = BT_LOGICAL;
3141 e->ts.kind = gfc_default_logical_kind;
3145 if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3147 gfc_type_convert_binary (e);
3149 e->ts.type = BT_LOGICAL;
3150 e->ts.kind = gfc_default_logical_kind;
3154 if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3156 _("Logicals at %%L must be compared with %s instead of %s"),
3157 (e->value.op.op == INTRINSIC_EQ
3158 || e->value.op.op == INTRINSIC_EQ_OS)
3159 ? ".eqv." : ".neqv.", gfc_op2string (e->value.op.op));
3162 _("Operands of comparison operator '%s' at %%L are %s/%s"),
3163 gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3164 gfc_typename (&op2->ts));
3168 case INTRINSIC_USER:
3169 if (e->value.op.uop->op == NULL)
3170 sprintf (msg, _("Unknown operator '%s' at %%L"), e->value.op.uop->name);
3171 else if (op2 == NULL)
3172 sprintf (msg, _("Operand of user operator '%s' at %%L is %s"),
3173 e->value.op.uop->name, gfc_typename (&op1->ts));
3175 sprintf (msg, _("Operands of user operator '%s' at %%L are %s/%s"),
3176 e->value.op.uop->name, gfc_typename (&op1->ts),
3177 gfc_typename (&op2->ts));
3181 case INTRINSIC_PARENTHESES:
3183 if (e->ts.type == BT_CHARACTER)
3184 e->ts.cl = op1->ts.cl;
3188 gfc_internal_error ("resolve_operator(): Bad intrinsic");
3191 /* Deal with arrayness of an operand through an operator. */
3195 switch (e->value.op.op)
3197 case INTRINSIC_PLUS:
3198 case INTRINSIC_MINUS:
3199 case INTRINSIC_TIMES:
3200 case INTRINSIC_DIVIDE:
3201 case INTRINSIC_POWER:
3202 case INTRINSIC_CONCAT:
3206 case INTRINSIC_NEQV:
3208 case INTRINSIC_EQ_OS:
3210 case INTRINSIC_NE_OS:
3212 case INTRINSIC_GT_OS:
3214 case INTRINSIC_GE_OS:
3216 case INTRINSIC_LT_OS:
3218 case INTRINSIC_LE_OS:
3220 if (op1->rank == 0 && op2->rank == 0)
3223 if (op1->rank == 0 && op2->rank != 0)
3225 e->rank = op2->rank;
3227 if (e->shape == NULL)
3228 e->shape = gfc_copy_shape (op2->shape, op2->rank);
3231 if (op1->rank != 0 && op2->rank == 0)
3233 e->rank = op1->rank;
3235 if (e->shape == NULL)
3236 e->shape = gfc_copy_shape (op1->shape, op1->rank);
3239 if (op1->rank != 0 && op2->rank != 0)
3241 if (op1->rank == op2->rank)
3243 e->rank = op1->rank;
3244 if (e->shape == NULL)
3246 t = compare_shapes(op1, op2);
3250 e->shape = gfc_copy_shape (op1->shape, op1->rank);
3255 /* Allow higher level expressions to work. */
3258 /* Try user-defined operators, and otherwise throw an error. */
3259 dual_locus_error = true;
3261 _("Inconsistent ranks for operator at %%L and %%L"));
3268 case INTRINSIC_PARENTHESES:
3270 case INTRINSIC_UPLUS:
3271 case INTRINSIC_UMINUS:
3272 /* Simply copy arrayness attribute */
3273 e->rank = op1->rank;
3275 if (e->shape == NULL)
3276 e->shape = gfc_copy_shape (op1->shape, op1->rank);
3284 /* Attempt to simplify the expression. */
3287 t = gfc_simplify_expr (e, 0);
3288 /* Some calls do not succeed in simplification and return FAILURE
3289 even though there is no error; e.g. variable references to
3290 PARAMETER arrays. */
3291 if (!gfc_is_constant_expr (e))
3298 if (gfc_extend_expr (e) == SUCCESS)
3301 if (dual_locus_error)
3302 gfc_error (msg, &op1->where, &op2->where);
3304 gfc_error (msg, &e->where);
3310 /************** Array resolution subroutines **************/
3313 { CMP_LT, CMP_EQ, CMP_GT, CMP_UNKNOWN }
3316 /* Compare two integer expressions. */
3319 compare_bound (gfc_expr *a, gfc_expr *b)
3323 if (a == NULL || a->expr_type != EXPR_CONSTANT
3324 || b == NULL || b->expr_type != EXPR_CONSTANT)
3327 /* If either of the types isn't INTEGER, we must have
3328 raised an error earlier. */
3330 if (a->ts.type != BT_INTEGER || b->ts.type != BT_INTEGER)
3333 i = mpz_cmp (a->value.integer, b->value.integer);
3343 /* Compare an integer expression with an integer. */
3346 compare_bound_int (gfc_expr *a, int b)
3350 if (a == NULL || a->expr_type != EXPR_CONSTANT)
3353 if (a->ts.type != BT_INTEGER)
3354 gfc_internal_error ("compare_bound_int(): Bad expression");
3356 i = mpz_cmp_si (a->value.integer, b);
3366 /* Compare an integer expression with a mpz_t. */
3369 compare_bound_mpz_t (gfc_expr *a, mpz_t b)
3373 if (a == NULL || a->expr_type != EXPR_CONSTANT)
3376 if (a->ts.type != BT_INTEGER)
3377 gfc_internal_error ("compare_bound_int(): Bad expression");
3379 i = mpz_cmp (a->value.integer, b);
3389 /* Compute the last value of a sequence given by a triplet.
3390 Return 0 if it wasn't able to compute the last value, or if the
3391 sequence if empty, and 1 otherwise. */
3394 compute_last_value_for_triplet (gfc_expr *start, gfc_expr *end,
3395 gfc_expr *stride, mpz_t last)
3399 if (start == NULL || start->expr_type != EXPR_CONSTANT
3400 || end == NULL || end->expr_type != EXPR_CONSTANT
3401 || (stride != NULL && stride->expr_type != EXPR_CONSTANT))
3404 if (start->ts.type != BT_INTEGER || end->ts.type != BT_INTEGER
3405 || (stride != NULL && stride->ts.type != BT_INTEGER))
3408 if (stride == NULL || compare_bound_int(stride, 1) == CMP_EQ)
3410 if (compare_bound (start, end) == CMP_GT)
3412 mpz_set (last, end->value.integer);