1 /* Perform type resolution on the various structures.
2 Copyright (C) 2001, 2002, 2003, 2004, 2005, 2006, 2007, 2008, 2009
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;
47 struct code_stack *prev;
49 /* This bitmap keeps track of the targets valid for a branch from
50 inside this block except for END {IF|SELECT}s of enclosing
52 bitmap reachable_labels;
56 static code_stack *cs_base = NULL;
59 /* Nonzero if we're inside a FORALL block. */
61 static int forall_flag;
63 /* Nonzero if we're inside a OpenMP WORKSHARE or PARALLEL WORKSHARE block. */
65 static int omp_workshare_flag;
67 /* Nonzero if we are processing a formal arglist. The corresponding function
68 resets the flag each time that it is read. */
69 static int formal_arg_flag = 0;
71 /* True if we are resolving a specification expression. */
72 static int specification_expr = 0;
74 /* The id of the last entry seen. */
75 static int current_entry_id;
77 /* We use bitmaps to determine if a branch target is valid. */
78 static bitmap_obstack labels_obstack;
81 gfc_is_formal_arg (void)
83 return formal_arg_flag;
86 /* Is the symbol host associated? */
88 is_sym_host_assoc (gfc_symbol *sym, gfc_namespace *ns)
90 for (ns = ns->parent; ns; ns = ns->parent)
99 /* Ensure a typespec used is valid; for instance, TYPE(t) is invalid if t is
100 an ABSTRACT derived-type. If where is not NULL, an error message with that
101 locus is printed, optionally using name. */
104 resolve_typespec_used (gfc_typespec* ts, locus* where, const char* name)
106 if (ts->type == BT_DERIVED && ts->u.derived->attr.abstract)
111 gfc_error ("'%s' at %L is of the ABSTRACT type '%s'",
112 name, where, ts->u.derived->name);
114 gfc_error ("ABSTRACT type '%s' used at %L",
115 ts->u.derived->name, where);
125 /* Resolve types of formal argument lists. These have to be done early so that
126 the formal argument lists of module procedures can be copied to the
127 containing module before the individual procedures are resolved
128 individually. We also resolve argument lists of procedures in interface
129 blocks because they are self-contained scoping units.
131 Since a dummy argument cannot be a non-dummy procedure, the only
132 resort left for untyped names are the IMPLICIT types. */
135 resolve_formal_arglist (gfc_symbol *proc)
137 gfc_formal_arglist *f;
141 if (proc->result != NULL)
146 if (gfc_elemental (proc)
147 || sym->attr.pointer || sym->attr.allocatable
148 || (sym->as && sym->as->rank > 0))
150 proc->attr.always_explicit = 1;
151 sym->attr.always_explicit = 1;
156 for (f = proc->formal; f; f = f->next)
162 /* Alternate return placeholder. */
163 if (gfc_elemental (proc))
164 gfc_error ("Alternate return specifier in elemental subroutine "
165 "'%s' at %L is not allowed", proc->name,
167 if (proc->attr.function)
168 gfc_error ("Alternate return specifier in function "
169 "'%s' at %L is not allowed", proc->name,
174 if (sym->attr.if_source != IFSRC_UNKNOWN)
175 resolve_formal_arglist (sym);
177 if (sym->attr.subroutine || sym->attr.external || sym->attr.intrinsic)
179 if (gfc_pure (proc) && !gfc_pure (sym))
181 gfc_error ("Dummy procedure '%s' of PURE procedure at %L must "
182 "also be PURE", sym->name, &sym->declared_at);
186 if (gfc_elemental (proc))
188 gfc_error ("Dummy procedure at %L not allowed in ELEMENTAL "
189 "procedure", &sym->declared_at);
193 if (sym->attr.function
194 && sym->ts.type == BT_UNKNOWN
195 && sym->attr.intrinsic)
197 gfc_intrinsic_sym *isym;
198 isym = gfc_find_function (sym->name);
199 if (isym == NULL || !isym->specific)
201 gfc_error ("Unable to find a specific INTRINSIC procedure "
202 "for the reference '%s' at %L", sym->name,
211 if (sym->ts.type == BT_UNKNOWN)
213 if (!sym->attr.function || sym->result == sym)
214 gfc_set_default_type (sym, 1, sym->ns);
217 gfc_resolve_array_spec (sym->as, 0);
219 /* We can't tell if an array with dimension (:) is assumed or deferred
220 shape until we know if it has the pointer or allocatable attributes.
222 if (sym->as && sym->as->rank > 0 && sym->as->type == AS_DEFERRED
223 && !(sym->attr.pointer || sym->attr.allocatable))
225 sym->as->type = AS_ASSUMED_SHAPE;
226 for (i = 0; i < sym->as->rank; i++)
227 sym->as->lower[i] = gfc_int_expr (1);
230 if ((sym->as && sym->as->rank > 0 && sym->as->type == AS_ASSUMED_SHAPE)
231 || sym->attr.pointer || sym->attr.allocatable || sym->attr.target
232 || sym->attr.optional)
234 proc->attr.always_explicit = 1;
236 proc->result->attr.always_explicit = 1;
239 /* If the flavor is unknown at this point, it has to be a variable.
240 A procedure specification would have already set the type. */
242 if (sym->attr.flavor == FL_UNKNOWN)
243 gfc_add_flavor (&sym->attr, FL_VARIABLE, sym->name, &sym->declared_at);
245 if (gfc_pure (proc) && !sym->attr.pointer
246 && sym->attr.flavor != FL_PROCEDURE)
248 if (proc->attr.function && sym->attr.intent != INTENT_IN)
249 gfc_error ("Argument '%s' of pure function '%s' at %L must be "
250 "INTENT(IN)", sym->name, proc->name,
253 if (proc->attr.subroutine && sym->attr.intent == INTENT_UNKNOWN)
254 gfc_error ("Argument '%s' of pure subroutine '%s' at %L must "
255 "have its INTENT specified", sym->name, proc->name,
259 if (gfc_elemental (proc))
263 gfc_error ("Argument '%s' of elemental procedure at %L must "
264 "be scalar", sym->name, &sym->declared_at);
268 if (sym->attr.pointer)
270 gfc_error ("Argument '%s' of elemental procedure at %L cannot "
271 "have the POINTER attribute", sym->name,
276 if (sym->attr.flavor == FL_PROCEDURE)
278 gfc_error ("Dummy procedure '%s' not allowed in elemental "
279 "procedure '%s' at %L", sym->name, proc->name,
285 /* Each dummy shall be specified to be scalar. */
286 if (proc->attr.proc == PROC_ST_FUNCTION)
290 gfc_error ("Argument '%s' of statement function at %L must "
291 "be scalar", sym->name, &sym->declared_at);
295 if (sym->ts.type == BT_CHARACTER)
297 gfc_charlen *cl = sym->ts.u.cl;
298 if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
300 gfc_error ("Character-valued argument '%s' of statement "
301 "function at %L must have constant length",
302 sym->name, &sym->declared_at);
312 /* Work function called when searching for symbols that have argument lists
313 associated with them. */
316 find_arglists (gfc_symbol *sym)
318 if (sym->attr.if_source == IFSRC_UNKNOWN || sym->ns != gfc_current_ns)
321 resolve_formal_arglist (sym);
325 /* Given a namespace, resolve all formal argument lists within the namespace.
329 resolve_formal_arglists (gfc_namespace *ns)
334 gfc_traverse_ns (ns, find_arglists);
339 resolve_contained_fntype (gfc_symbol *sym, gfc_namespace *ns)
343 /* If this namespace is not a function or an entry master function,
345 if (! sym || !(sym->attr.function || sym->attr.flavor == FL_VARIABLE)
346 || sym->attr.entry_master)
349 /* Try to find out of what the return type is. */
350 if (sym->result->ts.type == BT_UNKNOWN && sym->result->ts.interface == NULL)
352 t = gfc_set_default_type (sym->result, 0, ns);
354 if (t == FAILURE && !sym->result->attr.untyped)
356 if (sym->result == sym)
357 gfc_error ("Contained function '%s' at %L has no IMPLICIT type",
358 sym->name, &sym->declared_at);
359 else if (!sym->result->attr.proc_pointer)
360 gfc_error ("Result '%s' of contained function '%s' at %L has "
361 "no IMPLICIT type", sym->result->name, sym->name,
362 &sym->result->declared_at);
363 sym->result->attr.untyped = 1;
367 /* Fortran 95 Draft Standard, page 51, Section 5.1.1.5, on the Character
368 type, lists the only ways a character length value of * can be used:
369 dummy arguments of procedures, named constants, and function results
370 in external functions. Internal function results and results of module
371 procedures are not on this list, ergo, not permitted. */
373 if (sym->result->ts.type == BT_CHARACTER)
375 gfc_charlen *cl = sym->result->ts.u.cl;
376 if (!cl || !cl->length)
378 /* See if this is a module-procedure and adapt error message
381 gcc_assert (ns->parent && ns->parent->proc_name);
382 module_proc = (ns->parent->proc_name->attr.flavor == FL_MODULE);
384 gfc_error ("Character-valued %s '%s' at %L must not be"
386 module_proc ? _("module procedure")
387 : _("internal function"),
388 sym->name, &sym->declared_at);
394 /* Add NEW_ARGS to the formal argument list of PROC, taking care not to
395 introduce duplicates. */
398 merge_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
400 gfc_formal_arglist *f, *new_arglist;
403 for (; new_args != NULL; new_args = new_args->next)
405 new_sym = new_args->sym;
406 /* See if this arg is already in the formal argument list. */
407 for (f = proc->formal; f; f = f->next)
409 if (new_sym == f->sym)
416 /* Add a new argument. Argument order is not important. */
417 new_arglist = gfc_get_formal_arglist ();
418 new_arglist->sym = new_sym;
419 new_arglist->next = proc->formal;
420 proc->formal = new_arglist;
425 /* Flag the arguments that are not present in all entries. */
428 check_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
430 gfc_formal_arglist *f, *head;
433 for (f = proc->formal; f; f = f->next)
438 for (new_args = head; new_args; new_args = new_args->next)
440 if (new_args->sym == f->sym)
447 f->sym->attr.not_always_present = 1;
452 /* Resolve alternate entry points. If a symbol has multiple entry points we
453 create a new master symbol for the main routine, and turn the existing
454 symbol into an entry point. */
457 resolve_entries (gfc_namespace *ns)
459 gfc_namespace *old_ns;
463 char name[GFC_MAX_SYMBOL_LEN + 1];
464 static int master_count = 0;
466 if (ns->proc_name == NULL)
469 /* No need to do anything if this procedure doesn't have alternate entry
474 /* We may already have resolved alternate entry points. */
475 if (ns->proc_name->attr.entry_master)
478 /* If this isn't a procedure something has gone horribly wrong. */
479 gcc_assert (ns->proc_name->attr.flavor == FL_PROCEDURE);
481 /* Remember the current namespace. */
482 old_ns = gfc_current_ns;
486 /* Add the main entry point to the list of entry points. */
487 el = gfc_get_entry_list ();
488 el->sym = ns->proc_name;
490 el->next = ns->entries;
492 ns->proc_name->attr.entry = 1;
494 /* If it is a module function, it needs to be in the right namespace
495 so that gfc_get_fake_result_decl can gather up the results. The
496 need for this arose in get_proc_name, where these beasts were
497 left in their own namespace, to keep prior references linked to
498 the entry declaration.*/
499 if (ns->proc_name->attr.function
500 && ns->parent && ns->parent->proc_name->attr.flavor == FL_MODULE)
503 /* Do the same for entries where the master is not a module
504 procedure. These are retained in the module namespace because
505 of the module procedure declaration. */
506 for (el = el->next; el; el = el->next)
507 if (el->sym->ns->proc_name->attr.flavor == FL_MODULE
508 && el->sym->attr.mod_proc)
512 /* Add an entry statement for it. */
519 /* Create a new symbol for the master function. */
520 /* Give the internal function a unique name (within this file).
521 Also include the function name so the user has some hope of figuring
522 out what is going on. */
523 snprintf (name, GFC_MAX_SYMBOL_LEN, "master.%d.%s",
524 master_count++, ns->proc_name->name);
525 gfc_get_ha_symbol (name, &proc);
526 gcc_assert (proc != NULL);
528 gfc_add_procedure (&proc->attr, PROC_INTERNAL, proc->name, NULL);
529 if (ns->proc_name->attr.subroutine)
530 gfc_add_subroutine (&proc->attr, proc->name, NULL);
534 gfc_typespec *ts, *fts;
535 gfc_array_spec *as, *fas;
536 gfc_add_function (&proc->attr, proc->name, NULL);
538 fas = ns->entries->sym->as;
539 fas = fas ? fas : ns->entries->sym->result->as;
540 fts = &ns->entries->sym->result->ts;
541 if (fts->type == BT_UNKNOWN)
542 fts = gfc_get_default_type (ns->entries->sym->result->name, NULL);
543 for (el = ns->entries->next; el; el = el->next)
545 ts = &el->sym->result->ts;
547 as = as ? as : el->sym->result->as;
548 if (ts->type == BT_UNKNOWN)
549 ts = gfc_get_default_type (el->sym->result->name, NULL);
551 if (! gfc_compare_types (ts, fts)
552 || (el->sym->result->attr.dimension
553 != ns->entries->sym->result->attr.dimension)
554 || (el->sym->result->attr.pointer
555 != ns->entries->sym->result->attr.pointer))
557 else if (as && fas && ns->entries->sym->result != el->sym->result
558 && gfc_compare_array_spec (as, fas) == 0)
559 gfc_error ("Function %s at %L has entries with mismatched "
560 "array specifications", ns->entries->sym->name,
561 &ns->entries->sym->declared_at);
562 /* The characteristics need to match and thus both need to have
563 the same string length, i.e. both len=*, or both len=4.
564 Having both len=<variable> is also possible, but difficult to
565 check at compile time. */
566 else if (ts->type == BT_CHARACTER && ts->u.cl && fts->u.cl
567 && (((ts->u.cl->length && !fts->u.cl->length)
568 ||(!ts->u.cl->length && fts->u.cl->length))
570 && ts->u.cl->length->expr_type
571 != fts->u.cl->length->expr_type)
573 && ts->u.cl->length->expr_type == EXPR_CONSTANT
574 && mpz_cmp (ts->u.cl->length->value.integer,
575 fts->u.cl->length->value.integer) != 0)))
576 gfc_notify_std (GFC_STD_GNU, "Extension: Function %s at %L with "
577 "entries returning variables of different "
578 "string lengths", ns->entries->sym->name,
579 &ns->entries->sym->declared_at);
584 sym = ns->entries->sym->result;
585 /* All result types the same. */
587 if (sym->attr.dimension)
588 gfc_set_array_spec (proc, gfc_copy_array_spec (sym->as), NULL);
589 if (sym->attr.pointer)
590 gfc_add_pointer (&proc->attr, NULL);
594 /* Otherwise the result will be passed through a union by
596 proc->attr.mixed_entry_master = 1;
597 for (el = ns->entries; el; el = el->next)
599 sym = el->sym->result;
600 if (sym->attr.dimension)
602 if (el == ns->entries)
603 gfc_error ("FUNCTION result %s can't be an array in "
604 "FUNCTION %s at %L", sym->name,
605 ns->entries->sym->name, &sym->declared_at);
607 gfc_error ("ENTRY result %s can't be an array in "
608 "FUNCTION %s at %L", sym->name,
609 ns->entries->sym->name, &sym->declared_at);
611 else if (sym->attr.pointer)
613 if (el == ns->entries)
614 gfc_error ("FUNCTION result %s can't be a POINTER in "
615 "FUNCTION %s at %L", sym->name,
616 ns->entries->sym->name, &sym->declared_at);
618 gfc_error ("ENTRY result %s can't be a POINTER in "
619 "FUNCTION %s at %L", sym->name,
620 ns->entries->sym->name, &sym->declared_at);
625 if (ts->type == BT_UNKNOWN)
626 ts = gfc_get_default_type (sym->name, NULL);
630 if (ts->kind == gfc_default_integer_kind)
634 if (ts->kind == gfc_default_real_kind
635 || ts->kind == gfc_default_double_kind)
639 if (ts->kind == gfc_default_complex_kind)
643 if (ts->kind == gfc_default_logical_kind)
647 /* We will issue error elsewhere. */
655 if (el == ns->entries)
656 gfc_error ("FUNCTION result %s can't be of type %s "
657 "in FUNCTION %s at %L", sym->name,
658 gfc_typename (ts), ns->entries->sym->name,
661 gfc_error ("ENTRY result %s can't be of type %s "
662 "in FUNCTION %s at %L", sym->name,
663 gfc_typename (ts), ns->entries->sym->name,
670 proc->attr.access = ACCESS_PRIVATE;
671 proc->attr.entry_master = 1;
673 /* Merge all the entry point arguments. */
674 for (el = ns->entries; el; el = el->next)
675 merge_argument_lists (proc, el->sym->formal);
677 /* Check the master formal arguments for any that are not
678 present in all entry points. */
679 for (el = ns->entries; el; el = el->next)
680 check_argument_lists (proc, el->sym->formal);
682 /* Use the master function for the function body. */
683 ns->proc_name = proc;
685 /* Finalize the new symbols. */
686 gfc_commit_symbols ();
688 /* Restore the original namespace. */
689 gfc_current_ns = old_ns;
694 has_default_initializer (gfc_symbol *der)
698 gcc_assert (der->attr.flavor == FL_DERIVED);
699 for (c = der->components; c; c = c->next)
700 if ((c->ts.type != BT_DERIVED && c->initializer)
701 || (c->ts.type == BT_DERIVED
702 && (!c->attr.pointer && has_default_initializer (c->ts.u.derived))))
708 /* Resolve common variables. */
710 resolve_common_vars (gfc_symbol *sym, bool named_common)
712 gfc_symbol *csym = sym;
714 for (; csym; csym = csym->common_next)
716 if (csym->value || csym->attr.data)
718 if (!csym->ns->is_block_data)
719 gfc_notify_std (GFC_STD_GNU, "Variable '%s' at %L is in COMMON "
720 "but only in BLOCK DATA initialization is "
721 "allowed", csym->name, &csym->declared_at);
722 else if (!named_common)
723 gfc_notify_std (GFC_STD_GNU, "Initialized variable '%s' at %L is "
724 "in a blank COMMON but initialization is only "
725 "allowed in named common blocks", csym->name,
729 if (csym->ts.type != BT_DERIVED)
732 if (!(csym->ts.u.derived->attr.sequence
733 || csym->ts.u.derived->attr.is_bind_c))
734 gfc_error_now ("Derived type variable '%s' in COMMON at %L "
735 "has neither the SEQUENCE nor the BIND(C) "
736 "attribute", csym->name, &csym->declared_at);
737 if (csym->ts.u.derived->attr.alloc_comp)
738 gfc_error_now ("Derived type variable '%s' in COMMON at %L "
739 "has an ultimate component that is "
740 "allocatable", csym->name, &csym->declared_at);
741 if (has_default_initializer (csym->ts.u.derived))
742 gfc_error_now ("Derived type variable '%s' in COMMON at %L "
743 "may not have default initializer", csym->name,
746 if (csym->attr.flavor == FL_UNKNOWN && !csym->attr.proc_pointer)
747 gfc_add_flavor (&csym->attr, FL_VARIABLE, csym->name, &csym->declared_at);
751 /* Resolve common blocks. */
753 resolve_common_blocks (gfc_symtree *common_root)
757 if (common_root == NULL)
760 if (common_root->left)
761 resolve_common_blocks (common_root->left);
762 if (common_root->right)
763 resolve_common_blocks (common_root->right);
765 resolve_common_vars (common_root->n.common->head, true);
767 gfc_find_symbol (common_root->name, gfc_current_ns, 0, &sym);
771 if (sym->attr.flavor == FL_PARAMETER)
772 gfc_error ("COMMON block '%s' at %L is used as PARAMETER at %L",
773 sym->name, &common_root->n.common->where, &sym->declared_at);
775 if (sym->attr.intrinsic)
776 gfc_error ("COMMON block '%s' at %L is also an intrinsic procedure",
777 sym->name, &common_root->n.common->where);
778 else if (sym->attr.result
779 ||(sym->attr.function && gfc_current_ns->proc_name == sym))
780 gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
781 "that is also a function result", sym->name,
782 &common_root->n.common->where);
783 else if (sym->attr.flavor == FL_PROCEDURE && sym->attr.proc != PROC_INTERNAL
784 && sym->attr.proc != PROC_ST_FUNCTION)
785 gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
786 "that is also a global procedure", sym->name,
787 &common_root->n.common->where);
791 /* Resolve contained function types. Because contained functions can call one
792 another, they have to be worked out before any of the contained procedures
795 The good news is that if a function doesn't already have a type, the only
796 way it can get one is through an IMPLICIT type or a RESULT variable, because
797 by definition contained functions are contained namespace they're contained
798 in, not in a sibling or parent namespace. */
801 resolve_contained_functions (gfc_namespace *ns)
803 gfc_namespace *child;
806 resolve_formal_arglists (ns);
808 for (child = ns->contained; child; child = child->sibling)
810 /* Resolve alternate entry points first. */
811 resolve_entries (child);
813 /* Then check function return types. */
814 resolve_contained_fntype (child->proc_name, child);
815 for (el = child->entries; el; el = el->next)
816 resolve_contained_fntype (el->sym, child);
821 /* Resolve all of the elements of a structure constructor and make sure that
822 the types are correct. */
825 resolve_structure_cons (gfc_expr *expr)
827 gfc_constructor *cons;
833 cons = expr->value.constructor;
834 /* A constructor may have references if it is the result of substituting a
835 parameter variable. In this case we just pull out the component we
838 comp = expr->ref->u.c.sym->components;
840 comp = expr->ts.u.derived->components;
842 /* See if the user is trying to invoke a structure constructor for one of
843 the iso_c_binding derived types. */
844 if (expr->ts.type == BT_DERIVED && expr->ts.u.derived
845 && expr->ts.u.derived->ts.is_iso_c && cons && cons->expr != NULL)
847 gfc_error ("Components of structure constructor '%s' at %L are PRIVATE",
848 expr->ts.u.derived->name, &(expr->where));
852 for (; comp; comp = comp->next, cons = cons->next)
859 if (gfc_resolve_expr (cons->expr) == FAILURE)
865 rank = comp->as ? comp->as->rank : 0;
866 if (cons->expr->expr_type != EXPR_NULL && rank != cons->expr->rank
867 && (comp->attr.allocatable || cons->expr->rank))
869 gfc_error ("The rank of the element in the derived type "
870 "constructor at %L does not match that of the "
871 "component (%d/%d)", &cons->expr->where,
872 cons->expr->rank, rank);
876 /* If we don't have the right type, try to convert it. */
878 if (!gfc_compare_types (&cons->expr->ts, &comp->ts))
881 if (comp->attr.pointer && cons->expr->ts.type != BT_UNKNOWN)
882 gfc_error ("The element in the derived type constructor at %L, "
883 "for pointer component '%s', is %s but should be %s",
884 &cons->expr->where, comp->name,
885 gfc_basic_typename (cons->expr->ts.type),
886 gfc_basic_typename (comp->ts.type));
888 t = gfc_convert_type (cons->expr, &comp->ts, 1);
891 if (cons->expr->expr_type == EXPR_NULL
892 && !(comp->attr.pointer || comp->attr.allocatable
893 || comp->attr.proc_pointer
894 || (comp->ts.type == BT_CLASS
895 && (comp->ts.u.derived->components->attr.pointer
896 || comp->ts.u.derived->components->attr.allocatable))))
899 gfc_error ("The NULL in the derived type constructor at %L is "
900 "being applied to component '%s', which is neither "
901 "a POINTER nor ALLOCATABLE", &cons->expr->where,
905 if (!comp->attr.pointer || cons->expr->expr_type == EXPR_NULL)
908 a = gfc_expr_attr (cons->expr);
910 if (!a.pointer && !a.target)
913 gfc_error ("The element in the derived type constructor at %L, "
914 "for pointer component '%s' should be a POINTER or "
915 "a TARGET", &cons->expr->where, comp->name);
923 /****************** Expression name resolution ******************/
925 /* Returns 0 if a symbol was not declared with a type or
926 attribute declaration statement, nonzero otherwise. */
929 was_declared (gfc_symbol *sym)
935 if (!a.implicit_type && sym->ts.type != BT_UNKNOWN)
938 if (a.allocatable || a.dimension || a.dummy || a.external || a.intrinsic
939 || a.optional || a.pointer || a.save || a.target || a.volatile_
940 || a.value || a.access != ACCESS_UNKNOWN || a.intent != INTENT_UNKNOWN)
947 /* Determine if a symbol is generic or not. */
950 generic_sym (gfc_symbol *sym)
954 if (sym->attr.generic ||
955 (sym->attr.intrinsic && gfc_generic_intrinsic (sym->name)))
958 if (was_declared (sym) || sym->ns->parent == NULL)
961 gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
968 return generic_sym (s);
975 /* Determine if a symbol is specific or not. */
978 specific_sym (gfc_symbol *sym)
982 if (sym->attr.if_source == IFSRC_IFBODY
983 || sym->attr.proc == PROC_MODULE
984 || sym->attr.proc == PROC_INTERNAL
985 || sym->attr.proc == PROC_ST_FUNCTION
986 || (sym->attr.intrinsic && gfc_specific_intrinsic (sym->name))
987 || sym->attr.external)
990 if (was_declared (sym) || sym->ns->parent == NULL)
993 gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
995 return (s == NULL) ? 0 : specific_sym (s);
999 /* Figure out if the procedure is specific, generic or unknown. */
1002 { PTYPE_GENERIC = 1, PTYPE_SPECIFIC, PTYPE_UNKNOWN }
1006 procedure_kind (gfc_symbol *sym)
1008 if (generic_sym (sym))
1009 return PTYPE_GENERIC;
1011 if (specific_sym (sym))
1012 return PTYPE_SPECIFIC;
1014 return PTYPE_UNKNOWN;
1017 /* Check references to assumed size arrays. The flag need_full_assumed_size
1018 is nonzero when matching actual arguments. */
1020 static int need_full_assumed_size = 0;
1023 check_assumed_size_reference (gfc_symbol *sym, gfc_expr *e)
1025 if (need_full_assumed_size || !(sym->as && sym->as->type == AS_ASSUMED_SIZE))
1028 /* FIXME: The comparison "e->ref->u.ar.type == AR_FULL" is wrong.
1029 What should it be? */
1030 if ((e->ref->u.ar.end[e->ref->u.ar.as->rank - 1] == NULL)
1031 && (e->ref->u.ar.as->type == AS_ASSUMED_SIZE)
1032 && (e->ref->u.ar.type == AR_FULL))
1034 gfc_error ("The upper bound in the last dimension must "
1035 "appear in the reference to the assumed size "
1036 "array '%s' at %L", sym->name, &e->where);
1043 /* Look for bad assumed size array references in argument expressions
1044 of elemental and array valued intrinsic procedures. Since this is
1045 called from procedure resolution functions, it only recurses at
1049 resolve_assumed_size_actual (gfc_expr *e)
1054 switch (e->expr_type)
1057 if (e->symtree && check_assumed_size_reference (e->symtree->n.sym, e))
1062 if (resolve_assumed_size_actual (e->value.op.op1)
1063 || resolve_assumed_size_actual (e->value.op.op2))
1074 /* Check a generic procedure, passed as an actual argument, to see if
1075 there is a matching specific name. If none, it is an error, and if
1076 more than one, the reference is ambiguous. */
1078 count_specific_procs (gfc_expr *e)
1085 sym = e->symtree->n.sym;
1087 for (p = sym->generic; p; p = p->next)
1088 if (strcmp (sym->name, p->sym->name) == 0)
1090 e->symtree = gfc_find_symtree (p->sym->ns->sym_root,
1096 gfc_error ("'%s' at %L is ambiguous", e->symtree->n.sym->name,
1100 gfc_error ("GENERIC procedure '%s' is not allowed as an actual "
1101 "argument at %L", sym->name, &e->where);
1107 /* See if a call to sym could possibly be a not allowed RECURSION because of
1108 a missing RECURIVE declaration. This means that either sym is the current
1109 context itself, or sym is the parent of a contained procedure calling its
1110 non-RECURSIVE containing procedure.
1111 This also works if sym is an ENTRY. */
1114 is_illegal_recursion (gfc_symbol* sym, gfc_namespace* context)
1116 gfc_symbol* proc_sym;
1117 gfc_symbol* context_proc;
1118 gfc_namespace* real_context;
1120 gcc_assert (sym->attr.flavor == FL_PROCEDURE);
1122 /* If we've got an ENTRY, find real procedure. */
1123 if (sym->attr.entry && sym->ns->entries)
1124 proc_sym = sym->ns->entries->sym;
1128 /* If sym is RECURSIVE, all is well of course. */
1129 if (proc_sym->attr.recursive || gfc_option.flag_recursive)
1132 /* Find the context procedure's "real" symbol if it has entries.
1133 We look for a procedure symbol, so recurse on the parents if we don't
1134 find one (like in case of a BLOCK construct). */
1135 for (real_context = context; ; real_context = real_context->parent)
1137 /* We should find something, eventually! */
1138 gcc_assert (real_context);
1140 context_proc = (real_context->entries ? real_context->entries->sym
1141 : real_context->proc_name);
1143 /* In some special cases, there may not be a proc_name, like for this
1145 real(bad_kind()) function foo () ...
1146 when checking the call to bad_kind ().
1147 In these cases, we simply return here and assume that the
1152 if (context_proc->attr.flavor != FL_LABEL)
1156 /* A call from sym's body to itself is recursion, of course. */
1157 if (context_proc == proc_sym)
1160 /* The same is true if context is a contained procedure and sym the
1162 if (context_proc->attr.contained)
1164 gfc_symbol* parent_proc;
1166 gcc_assert (context->parent);
1167 parent_proc = (context->parent->entries ? context->parent->entries->sym
1168 : context->parent->proc_name);
1170 if (parent_proc == proc_sym)
1178 /* Resolve an intrinsic procedure: Set its function/subroutine attribute,
1179 its typespec and formal argument list. */
1182 resolve_intrinsic (gfc_symbol *sym, locus *loc)
1184 gfc_intrinsic_sym* isym;
1190 /* We already know this one is an intrinsic, so we don't call
1191 gfc_is_intrinsic for full checking but rather use gfc_find_function and
1192 gfc_find_subroutine directly to check whether it is a function or
1195 if ((isym = gfc_find_function (sym->name)))
1197 if (sym->ts.type != BT_UNKNOWN && gfc_option.warn_surprising
1198 && !sym->attr.implicit_type)
1199 gfc_warning ("Type specified for intrinsic function '%s' at %L is"
1200 " ignored", sym->name, &sym->declared_at);
1202 if (!sym->attr.function &&
1203 gfc_add_function (&sym->attr, sym->name, loc) == FAILURE)
1208 else if ((isym = gfc_find_subroutine (sym->name)))
1210 if (sym->ts.type != BT_UNKNOWN && !sym->attr.implicit_type)
1212 gfc_error ("Intrinsic subroutine '%s' at %L shall not have a type"
1213 " specifier", sym->name, &sym->declared_at);
1217 if (!sym->attr.subroutine &&
1218 gfc_add_subroutine (&sym->attr, sym->name, loc) == FAILURE)
1223 gfc_error ("'%s' declared INTRINSIC at %L does not exist", sym->name,
1228 gfc_copy_formal_args_intr (sym, isym);
1230 /* Check it is actually available in the standard settings. */
1231 if (gfc_check_intrinsic_standard (isym, &symstd, false, sym->declared_at)
1234 gfc_error ("The intrinsic '%s' declared INTRINSIC at %L is not"
1235 " available in the current standard settings but %s. Use"
1236 " an appropriate -std=* option or enable -fall-intrinsics"
1237 " in order to use it.",
1238 sym->name, &sym->declared_at, symstd);
1246 /* Resolve a procedure expression, like passing it to a called procedure or as
1247 RHS for a procedure pointer assignment. */
1250 resolve_procedure_expression (gfc_expr* expr)
1254 if (expr->expr_type != EXPR_VARIABLE)
1256 gcc_assert (expr->symtree);
1258 sym = expr->symtree->n.sym;
1260 if (sym->attr.intrinsic)
1261 resolve_intrinsic (sym, &expr->where);
1263 if (sym->attr.flavor != FL_PROCEDURE
1264 || (sym->attr.function && sym->result == sym))
1267 /* A non-RECURSIVE procedure that is used as procedure expression within its
1268 own body is in danger of being called recursively. */
1269 if (is_illegal_recursion (sym, gfc_current_ns))
1270 gfc_warning ("Non-RECURSIVE procedure '%s' at %L is possibly calling"
1271 " itself recursively. Declare it RECURSIVE or use"
1272 " -frecursive", sym->name, &expr->where);
1278 /* Resolve an actual argument list. Most of the time, this is just
1279 resolving the expressions in the list.
1280 The exception is that we sometimes have to decide whether arguments
1281 that look like procedure arguments are really simple variable
1285 resolve_actual_arglist (gfc_actual_arglist *arg, procedure_type ptype,
1286 bool no_formal_args)
1289 gfc_symtree *parent_st;
1291 int save_need_full_assumed_size;
1292 gfc_component *comp;
1294 for (; arg; arg = arg->next)
1299 /* Check the label is a valid branching target. */
1302 if (arg->label->defined == ST_LABEL_UNKNOWN)
1304 gfc_error ("Label %d referenced at %L is never defined",
1305 arg->label->value, &arg->label->where);
1312 if (gfc_is_proc_ptr_comp (e, &comp))
1315 if (e->expr_type == EXPR_PPC)
1317 if (comp->as != NULL)
1318 e->rank = comp->as->rank;
1319 e->expr_type = EXPR_FUNCTION;
1324 if (e->expr_type == EXPR_VARIABLE
1325 && e->symtree->n.sym->attr.generic
1327 && count_specific_procs (e) != 1)
1330 if (e->ts.type != BT_PROCEDURE)
1332 save_need_full_assumed_size = need_full_assumed_size;
1333 if (e->expr_type != EXPR_VARIABLE)
1334 need_full_assumed_size = 0;
1335 if (gfc_resolve_expr (e) != SUCCESS)
1337 need_full_assumed_size = save_need_full_assumed_size;
1341 /* See if the expression node should really be a variable reference. */
1343 sym = e->symtree->n.sym;
1345 if (sym->attr.flavor == FL_PROCEDURE
1346 || sym->attr.intrinsic
1347 || sym->attr.external)
1351 /* If a procedure is not already determined to be something else
1352 check if it is intrinsic. */
1353 if (!sym->attr.intrinsic
1354 && !(sym->attr.external || sym->attr.use_assoc
1355 || sym->attr.if_source == IFSRC_IFBODY)
1356 && gfc_is_intrinsic (sym, sym->attr.subroutine, e->where))
1357 sym->attr.intrinsic = 1;
1359 if (sym->attr.proc == PROC_ST_FUNCTION)
1361 gfc_error ("Statement function '%s' at %L is not allowed as an "
1362 "actual argument", sym->name, &e->where);
1365 actual_ok = gfc_intrinsic_actual_ok (sym->name,
1366 sym->attr.subroutine);
1367 if (sym->attr.intrinsic && actual_ok == 0)
1369 gfc_error ("Intrinsic '%s' at %L is not allowed as an "
1370 "actual argument", sym->name, &e->where);
1373 if (sym->attr.contained && !sym->attr.use_assoc
1374 && sym->ns->proc_name->attr.flavor != FL_MODULE)
1376 gfc_error ("Internal procedure '%s' is not allowed as an "
1377 "actual argument at %L", sym->name, &e->where);
1380 if (sym->attr.elemental && !sym->attr.intrinsic)
1382 gfc_error ("ELEMENTAL non-INTRINSIC procedure '%s' is not "
1383 "allowed as an actual argument at %L", sym->name,
1387 /* Check if a generic interface has a specific procedure
1388 with the same name before emitting an error. */
1389 if (sym->attr.generic && count_specific_procs (e) != 1)
1392 /* Just in case a specific was found for the expression. */
1393 sym = e->symtree->n.sym;
1395 /* If the symbol is the function that names the current (or
1396 parent) scope, then we really have a variable reference. */
1398 if (sym->attr.function && sym->result == sym
1399 && (sym->ns->proc_name == sym
1400 || (sym->ns->parent != NULL
1401 && sym->ns->parent->proc_name == sym)))
1404 /* If all else fails, see if we have a specific intrinsic. */
1405 if (sym->ts.type == BT_UNKNOWN && sym->attr.intrinsic)
1407 gfc_intrinsic_sym *isym;
1409 isym = gfc_find_function (sym->name);
1410 if (isym == NULL || !isym->specific)
1412 gfc_error ("Unable to find a specific INTRINSIC procedure "
1413 "for the reference '%s' at %L", sym->name,
1418 sym->attr.intrinsic = 1;
1419 sym->attr.function = 1;
1422 if (gfc_resolve_expr (e) == FAILURE)
1427 /* See if the name is a module procedure in a parent unit. */
1429 if (was_declared (sym) || sym->ns->parent == NULL)
1432 if (gfc_find_sym_tree (sym->name, sym->ns->parent, 1, &parent_st))
1434 gfc_error ("Symbol '%s' at %L is ambiguous", sym->name, &e->where);
1438 if (parent_st == NULL)
1441 sym = parent_st->n.sym;
1442 e->symtree = parent_st; /* Point to the right thing. */
1444 if (sym->attr.flavor == FL_PROCEDURE
1445 || sym->attr.intrinsic
1446 || sym->attr.external)
1448 if (gfc_resolve_expr (e) == FAILURE)
1454 e->expr_type = EXPR_VARIABLE;
1456 if (sym->as != NULL)
1458 e->rank = sym->as->rank;
1459 e->ref = gfc_get_ref ();
1460 e->ref->type = REF_ARRAY;
1461 e->ref->u.ar.type = AR_FULL;
1462 e->ref->u.ar.as = sym->as;
1465 /* Expressions are assigned a default ts.type of BT_PROCEDURE in
1466 primary.c (match_actual_arg). If above code determines that it
1467 is a variable instead, it needs to be resolved as it was not
1468 done at the beginning of this function. */
1469 save_need_full_assumed_size = need_full_assumed_size;
1470 if (e->expr_type != EXPR_VARIABLE)
1471 need_full_assumed_size = 0;
1472 if (gfc_resolve_expr (e) != SUCCESS)
1474 need_full_assumed_size = save_need_full_assumed_size;
1477 /* Check argument list functions %VAL, %LOC and %REF. There is
1478 nothing to do for %REF. */
1479 if (arg->name && arg->name[0] == '%')
1481 if (strncmp ("%VAL", arg->name, 4) == 0)
1483 if (e->ts.type == BT_CHARACTER || e->ts.type == BT_DERIVED)
1485 gfc_error ("By-value argument at %L is not of numeric "
1492 gfc_error ("By-value argument at %L cannot be an array or "
1493 "an array section", &e->where);
1497 /* Intrinsics are still PROC_UNKNOWN here. However,
1498 since same file external procedures are not resolvable
1499 in gfortran, it is a good deal easier to leave them to
1501 if (ptype != PROC_UNKNOWN
1502 && ptype != PROC_DUMMY
1503 && ptype != PROC_EXTERNAL
1504 && ptype != PROC_MODULE)
1506 gfc_error ("By-value argument at %L is not allowed "
1507 "in this context", &e->where);
1512 /* Statement functions have already been excluded above. */
1513 else if (strncmp ("%LOC", arg->name, 4) == 0
1514 && e->ts.type == BT_PROCEDURE)
1516 if (e->symtree->n.sym->attr.proc == PROC_INTERNAL)
1518 gfc_error ("Passing internal procedure at %L by location "
1519 "not allowed", &e->where);
1530 /* Do the checks of the actual argument list that are specific to elemental
1531 procedures. If called with c == NULL, we have a function, otherwise if
1532 expr == NULL, we have a subroutine. */
1535 resolve_elemental_actual (gfc_expr *expr, gfc_code *c)
1537 gfc_actual_arglist *arg0;
1538 gfc_actual_arglist *arg;
1539 gfc_symbol *esym = NULL;
1540 gfc_intrinsic_sym *isym = NULL;
1542 gfc_intrinsic_arg *iformal = NULL;
1543 gfc_formal_arglist *eformal = NULL;
1544 bool formal_optional = false;
1545 bool set_by_optional = false;
1549 /* Is this an elemental procedure? */
1550 if (expr && expr->value.function.actual != NULL)
1552 if (expr->value.function.esym != NULL
1553 && expr->value.function.esym->attr.elemental)
1555 arg0 = expr->value.function.actual;
1556 esym = expr->value.function.esym;
1558 else if (expr->value.function.isym != NULL
1559 && expr->value.function.isym->elemental)
1561 arg0 = expr->value.function.actual;
1562 isym = expr->value.function.isym;
1567 else if (c && c->ext.actual != NULL)
1569 arg0 = c->ext.actual;
1571 if (c->resolved_sym)
1572 esym = c->resolved_sym;
1574 esym = c->symtree->n.sym;
1577 if (!esym->attr.elemental)
1583 /* The rank of an elemental is the rank of its array argument(s). */
1584 for (arg = arg0; arg; arg = arg->next)
1586 if (arg->expr != NULL && arg->expr->rank > 0)
1588 rank = arg->expr->rank;
1589 if (arg->expr->expr_type == EXPR_VARIABLE
1590 && arg->expr->symtree->n.sym->attr.optional)
1591 set_by_optional = true;
1593 /* Function specific; set the result rank and shape. */
1597 if (!expr->shape && arg->expr->shape)
1599 expr->shape = gfc_get_shape (rank);
1600 for (i = 0; i < rank; i++)
1601 mpz_init_set (expr->shape[i], arg->expr->shape[i]);
1608 /* If it is an array, it shall not be supplied as an actual argument
1609 to an elemental procedure unless an array of the same rank is supplied
1610 as an actual argument corresponding to a nonoptional dummy argument of
1611 that elemental procedure(12.4.1.5). */
1612 formal_optional = false;
1614 iformal = isym->formal;
1616 eformal = esym->formal;
1618 for (arg = arg0; arg; arg = arg->next)
1622 if (eformal->sym && eformal->sym->attr.optional)
1623 formal_optional = true;
1624 eformal = eformal->next;
1626 else if (isym && iformal)
1628 if (iformal->optional)
1629 formal_optional = true;
1630 iformal = iformal->next;
1633 formal_optional = true;
1635 if (pedantic && arg->expr != NULL
1636 && arg->expr->expr_type == EXPR_VARIABLE
1637 && arg->expr->symtree->n.sym->attr.optional
1640 && (set_by_optional || arg->expr->rank != rank)
1641 && !(isym && isym->id == GFC_ISYM_CONVERSION))
1643 gfc_warning ("'%s' at %L is an array and OPTIONAL; IF IT IS "
1644 "MISSING, it cannot be the actual argument of an "
1645 "ELEMENTAL procedure unless there is a non-optional "
1646 "argument with the same rank (12.4.1.5)",
1647 arg->expr->symtree->n.sym->name, &arg->expr->where);
1652 for (arg = arg0; arg; arg = arg->next)
1654 if (arg->expr == NULL || arg->expr->rank == 0)
1657 /* Being elemental, the last upper bound of an assumed size array
1658 argument must be present. */
1659 if (resolve_assumed_size_actual (arg->expr))
1662 /* Elemental procedure's array actual arguments must conform. */
1665 if (gfc_check_conformance (arg->expr, e,
1666 "elemental procedure") == FAILURE)
1673 /* INTENT(OUT) is only allowed for subroutines; if any actual argument
1674 is an array, the intent inout/out variable needs to be also an array. */
1675 if (rank > 0 && esym && expr == NULL)
1676 for (eformal = esym->formal, arg = arg0; arg && eformal;
1677 arg = arg->next, eformal = eformal->next)
1678 if ((eformal->sym->attr.intent == INTENT_OUT
1679 || eformal->sym->attr.intent == INTENT_INOUT)
1680 && arg->expr && arg->expr->rank == 0)
1682 gfc_error ("Actual argument at %L for INTENT(%s) dummy '%s' of "
1683 "ELEMENTAL subroutine '%s' is a scalar, but another "
1684 "actual argument is an array", &arg->expr->where,
1685 (eformal->sym->attr.intent == INTENT_OUT) ? "OUT"
1686 : "INOUT", eformal->sym->name, esym->name);
1693 /* Go through each actual argument in ACTUAL and see if it can be
1694 implemented as an inlined, non-copying intrinsic. FNSYM is the
1695 function being called, or NULL if not known. */
1698 find_noncopying_intrinsics (gfc_symbol *fnsym, gfc_actual_arglist *actual)
1700 gfc_actual_arglist *ap;
1703 for (ap = actual; ap; ap = ap->next)
1705 && (expr = gfc_get_noncopying_intrinsic_argument (ap->expr))
1706 && !gfc_check_fncall_dependency (expr, INTENT_IN, fnsym, actual,
1708 ap->expr->inline_noncopying_intrinsic = 1;
1712 /* This function does the checking of references to global procedures
1713 as defined in sections 18.1 and 14.1, respectively, of the Fortran
1714 77 and 95 standards. It checks for a gsymbol for the name, making
1715 one if it does not already exist. If it already exists, then the
1716 reference being resolved must correspond to the type of gsymbol.
1717 Otherwise, the new symbol is equipped with the attributes of the
1718 reference. The corresponding code that is called in creating
1719 global entities is parse.c.
1721 In addition, for all but -std=legacy, the gsymbols are used to
1722 check the interfaces of external procedures from the same file.
1723 The namespace of the gsymbol is resolved and then, once this is
1724 done the interface is checked. */
1728 not_in_recursive (gfc_symbol *sym, gfc_namespace *gsym_ns)
1730 if (!gsym_ns->proc_name->attr.recursive)
1733 if (sym->ns == gsym_ns)
1736 if (sym->ns->parent && sym->ns->parent == gsym_ns)
1743 not_entry_self_reference (gfc_symbol *sym, gfc_namespace *gsym_ns)
1745 if (gsym_ns->entries)
1747 gfc_entry_list *entry = gsym_ns->entries;
1749 for (; entry; entry = entry->next)
1751 if (strcmp (sym->name, entry->sym->name) == 0)
1753 if (strcmp (gsym_ns->proc_name->name,
1754 sym->ns->proc_name->name) == 0)
1758 && strcmp (gsym_ns->proc_name->name,
1759 sym->ns->parent->proc_name->name) == 0)
1768 resolve_global_procedure (gfc_symbol *sym, locus *where,
1769 gfc_actual_arglist **actual, int sub)
1773 enum gfc_symbol_type type;
1775 type = sub ? GSYM_SUBROUTINE : GSYM_FUNCTION;
1777 gsym = gfc_get_gsymbol (sym->name);
1779 if ((gsym->type != GSYM_UNKNOWN && gsym->type != type))
1780 gfc_global_used (gsym, where);
1782 if (gfc_option.flag_whole_file
1783 && sym->attr.if_source == IFSRC_UNKNOWN
1784 && gsym->type != GSYM_UNKNOWN
1786 && gsym->ns->resolved != -1
1787 && gsym->ns->proc_name
1788 && not_in_recursive (sym, gsym->ns)
1789 && not_entry_self_reference (sym, gsym->ns))
1791 /* Make sure that translation for the gsymbol occurs before
1792 the procedure currently being resolved. */
1793 ns = gsym->ns->resolved ? NULL : gfc_global_ns_list;
1794 for (; ns && ns != gsym->ns; ns = ns->sibling)
1796 if (ns->sibling == gsym->ns)
1798 ns->sibling = gsym->ns->sibling;
1799 gsym->ns->sibling = gfc_global_ns_list;
1800 gfc_global_ns_list = gsym->ns;
1805 if (!gsym->ns->resolved)
1807 gfc_dt_list *old_dt_list;
1809 /* Stash away derived types so that the backend_decls do not
1811 old_dt_list = gfc_derived_types;
1812 gfc_derived_types = NULL;
1814 gfc_resolve (gsym->ns);
1816 /* Store the new derived types with the global namespace. */
1817 if (gfc_derived_types)
1818 gsym->ns->derived_types = gfc_derived_types;
1820 /* Restore the derived types of this namespace. */
1821 gfc_derived_types = old_dt_list;
1824 if (gsym->ns->proc_name->attr.function
1825 && gsym->ns->proc_name->as
1826 && gsym->ns->proc_name->as->rank
1827 && (!sym->as || sym->as->rank != gsym->ns->proc_name->as->rank))
1828 gfc_error ("The reference to function '%s' at %L either needs an "
1829 "explicit INTERFACE or the rank is incorrect", sym->name,
1832 if (gfc_option.flag_whole_file == 1
1833 || ((gfc_option.warn_std & GFC_STD_LEGACY)
1835 !(gfc_option.warn_std & GFC_STD_GNU)))
1836 gfc_errors_to_warnings (1);
1838 gfc_procedure_use (gsym->ns->proc_name, actual, where);
1840 gfc_errors_to_warnings (0);
1843 if (gsym->type == GSYM_UNKNOWN)
1846 gsym->where = *where;
1853 /************* Function resolution *************/
1855 /* Resolve a function call known to be generic.
1856 Section 14.1.2.4.1. */
1859 resolve_generic_f0 (gfc_expr *expr, gfc_symbol *sym)
1863 if (sym->attr.generic)
1865 s = gfc_search_interface (sym->generic, 0, &expr->value.function.actual);
1868 expr->value.function.name = s->name;
1869 expr->value.function.esym = s;
1871 if (s->ts.type != BT_UNKNOWN)
1873 else if (s->result != NULL && s->result->ts.type != BT_UNKNOWN)
1874 expr->ts = s->result->ts;
1877 expr->rank = s->as->rank;
1878 else if (s->result != NULL && s->result->as != NULL)
1879 expr->rank = s->result->as->rank;
1881 gfc_set_sym_referenced (expr->value.function.esym);
1886 /* TODO: Need to search for elemental references in generic
1890 if (sym->attr.intrinsic)
1891 return gfc_intrinsic_func_interface (expr, 0);
1898 resolve_generic_f (gfc_expr *expr)
1903 sym = expr->symtree->n.sym;
1907 m = resolve_generic_f0 (expr, sym);
1910 else if (m == MATCH_ERROR)
1914 if (sym->ns->parent == NULL)
1916 gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
1920 if (!generic_sym (sym))
1924 /* Last ditch attempt. See if the reference is to an intrinsic
1925 that possesses a matching interface. 14.1.2.4 */
1926 if (sym && !gfc_is_intrinsic (sym, 0, expr->where))
1928 gfc_error ("There is no specific function for the generic '%s' at %L",
1929 expr->symtree->n.sym->name, &expr->where);
1933 m = gfc_intrinsic_func_interface (expr, 0);
1937 gfc_error ("Generic function '%s' at %L is not consistent with a "
1938 "specific intrinsic interface", expr->symtree->n.sym->name,
1945 /* Resolve a function call known to be specific. */
1948 resolve_specific_f0 (gfc_symbol *sym, gfc_expr *expr)
1952 if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
1954 if (sym->attr.dummy)
1956 sym->attr.proc = PROC_DUMMY;
1960 sym->attr.proc = PROC_EXTERNAL;
1964 if (sym->attr.proc == PROC_MODULE
1965 || sym->attr.proc == PROC_ST_FUNCTION
1966 || sym->attr.proc == PROC_INTERNAL)
1969 if (sym->attr.intrinsic)
1971 m = gfc_intrinsic_func_interface (expr, 1);
1975 gfc_error ("Function '%s' at %L is INTRINSIC but is not compatible "
1976 "with an intrinsic", sym->name, &expr->where);
1984 gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
1987 expr->ts = sym->result->ts;
1990 expr->value.function.name = sym->name;
1991 expr->value.function.esym = sym;
1992 if (sym->as != NULL)
1993 expr->rank = sym->as->rank;
2000 resolve_specific_f (gfc_expr *expr)
2005 sym = expr->symtree->n.sym;
2009 m = resolve_specific_f0 (sym, expr);
2012 if (m == MATCH_ERROR)
2015 if (sym->ns->parent == NULL)
2018 gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2024 gfc_error ("Unable to resolve the specific function '%s' at %L",
2025 expr->symtree->n.sym->name, &expr->where);
2031 /* Resolve a procedure call not known to be generic nor specific. */
2034 resolve_unknown_f (gfc_expr *expr)
2039 sym = expr->symtree->n.sym;
2041 if (sym->attr.dummy)
2043 sym->attr.proc = PROC_DUMMY;
2044 expr->value.function.name = sym->name;
2048 /* See if we have an intrinsic function reference. */
2050 if (gfc_is_intrinsic (sym, 0, expr->where))
2052 if (gfc_intrinsic_func_interface (expr, 1) == MATCH_YES)
2057 /* The reference is to an external name. */
2059 sym->attr.proc = PROC_EXTERNAL;
2060 expr->value.function.name = sym->name;
2061 expr->value.function.esym = expr->symtree->n.sym;
2063 if (sym->as != NULL)
2064 expr->rank = sym->as->rank;
2066 /* Type of the expression is either the type of the symbol or the
2067 default type of the symbol. */
2070 gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2072 if (sym->ts.type != BT_UNKNOWN)
2076 ts = gfc_get_default_type (sym->name, sym->ns);
2078 if (ts->type == BT_UNKNOWN)
2080 gfc_error ("Function '%s' at %L has no IMPLICIT type",
2081 sym->name, &expr->where);
2092 /* Return true, if the symbol is an external procedure. */
2094 is_external_proc (gfc_symbol *sym)
2096 if (!sym->attr.dummy && !sym->attr.contained
2097 && !(sym->attr.intrinsic
2098 || gfc_is_intrinsic (sym, sym->attr.subroutine, sym->declared_at))
2099 && sym->attr.proc != PROC_ST_FUNCTION
2100 && !sym->attr.use_assoc
2108 /* Figure out if a function reference is pure or not. Also set the name
2109 of the function for a potential error message. Return nonzero if the
2110 function is PURE, zero if not. */
2112 pure_stmt_function (gfc_expr *, gfc_symbol *);
2115 pure_function (gfc_expr *e, const char **name)
2121 if (e->symtree != NULL
2122 && e->symtree->n.sym != NULL
2123 && e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2124 return pure_stmt_function (e, e->symtree->n.sym);
2126 if (e->value.function.esym)
2128 pure = gfc_pure (e->value.function.esym);
2129 *name = e->value.function.esym->name;
2131 else if (e->value.function.isym)
2133 pure = e->value.function.isym->pure
2134 || e->value.function.isym->elemental;
2135 *name = e->value.function.isym->name;
2139 /* Implicit functions are not pure. */
2141 *name = e->value.function.name;
2149 impure_stmt_fcn (gfc_expr *e, gfc_symbol *sym,
2150 int *f ATTRIBUTE_UNUSED)
2154 /* Don't bother recursing into other statement functions
2155 since they will be checked individually for purity. */
2156 if (e->expr_type != EXPR_FUNCTION
2158 || e->symtree->n.sym == sym
2159 || e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2162 return pure_function (e, &name) ? false : true;
2167 pure_stmt_function (gfc_expr *e, gfc_symbol *sym)
2169 return gfc_traverse_expr (e, sym, impure_stmt_fcn, 0) ? 0 : 1;
2174 is_scalar_expr_ptr (gfc_expr *expr)
2176 gfc_try retval = SUCCESS;
2181 /* See if we have a gfc_ref, which means we have a substring, array
2182 reference, or a component. */
2183 if (expr->ref != NULL)
2186 while (ref->next != NULL)
2192 if (ref->u.ss.length != NULL
2193 && ref->u.ss.length->length != NULL
2195 && ref->u.ss.start->expr_type == EXPR_CONSTANT
2197 && ref->u.ss.end->expr_type == EXPR_CONSTANT)
2199 start = (int) mpz_get_si (ref->u.ss.start->value.integer);
2200 end = (int) mpz_get_si (ref->u.ss.end->value.integer);
2201 if (end - start + 1 != 1)
2208 if (ref->u.ar.type == AR_ELEMENT)
2210 else if (ref->u.ar.type == AR_FULL)
2212 /* The user can give a full array if the array is of size 1. */
2213 if (ref->u.ar.as != NULL
2214 && ref->u.ar.as->rank == 1
2215 && ref->u.ar.as->type == AS_EXPLICIT
2216 && ref->u.ar.as->lower[0] != NULL
2217 && ref->u.ar.as->lower[0]->expr_type == EXPR_CONSTANT
2218 && ref->u.ar.as->upper[0] != NULL
2219 && ref->u.ar.as->upper[0]->expr_type == EXPR_CONSTANT)
2221 /* If we have a character string, we need to check if
2222 its length is one. */
2223 if (expr->ts.type == BT_CHARACTER)
2225 if (expr->ts.u.cl == NULL
2226 || expr->ts.u.cl->length == NULL
2227 || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1)
2233 /* We have constant lower and upper bounds. If the
2234 difference between is 1, it can be considered a
2236 start = (int) mpz_get_si
2237 (ref->u.ar.as->lower[0]->value.integer);
2238 end = (int) mpz_get_si
2239 (ref->u.ar.as->upper[0]->value.integer);
2240 if (end - start + 1 != 1)
2255 else if (expr->ts.type == BT_CHARACTER && expr->rank == 0)
2257 /* Character string. Make sure it's of length 1. */
2258 if (expr->ts.u.cl == NULL
2259 || expr->ts.u.cl->length == NULL
2260 || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1) != 0)
2263 else if (expr->rank != 0)
2270 /* Match one of the iso_c_binding functions (c_associated or c_loc)
2271 and, in the case of c_associated, set the binding label based on
2275 gfc_iso_c_func_interface (gfc_symbol *sym, gfc_actual_arglist *args,
2276 gfc_symbol **new_sym)
2278 char name[GFC_MAX_SYMBOL_LEN + 1];
2279 char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
2280 int optional_arg = 0, is_pointer = 0;
2281 gfc_try retval = SUCCESS;
2282 gfc_symbol *args_sym;
2283 gfc_typespec *arg_ts;
2285 if (args->expr->expr_type == EXPR_CONSTANT
2286 || args->expr->expr_type == EXPR_OP
2287 || args->expr->expr_type == EXPR_NULL)
2289 gfc_error ("Argument to '%s' at %L is not a variable",
2290 sym->name, &(args->expr->where));
2294 args_sym = args->expr->symtree->n.sym;
2296 /* The typespec for the actual arg should be that stored in the expr
2297 and not necessarily that of the expr symbol (args_sym), because
2298 the actual expression could be a part-ref of the expr symbol. */
2299 arg_ts = &(args->expr->ts);
2301 is_pointer = gfc_is_data_pointer (args->expr);
2303 if (sym->intmod_sym_id == ISOCBINDING_ASSOCIATED)
2305 /* If the user gave two args then they are providing something for
2306 the optional arg (the second cptr). Therefore, set the name and
2307 binding label to the c_associated for two cptrs. Otherwise,
2308 set c_associated to expect one cptr. */
2312 sprintf (name, "%s_2", sym->name);
2313 sprintf (binding_label, "%s_2", sym->binding_label);
2319 sprintf (name, "%s_1", sym->name);
2320 sprintf (binding_label, "%s_1", sym->binding_label);
2324 /* Get a new symbol for the version of c_associated that
2326 *new_sym = get_iso_c_sym (sym, name, binding_label, optional_arg);
2328 else if (sym->intmod_sym_id == ISOCBINDING_LOC
2329 || sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2331 sprintf (name, "%s", sym->name);
2332 sprintf (binding_label, "%s", sym->binding_label);
2334 /* Error check the call. */
2335 if (args->next != NULL)
2337 gfc_error_now ("More actual than formal arguments in '%s' "
2338 "call at %L", name, &(args->expr->where));
2341 else if (sym->intmod_sym_id == ISOCBINDING_LOC)
2343 /* Make sure we have either the target or pointer attribute. */
2344 if (!args_sym->attr.target && !is_pointer)
2346 gfc_error_now ("Parameter '%s' to '%s' at %L must be either "
2347 "a TARGET or an associated pointer",
2349 sym->name, &(args->expr->where));
2353 /* See if we have interoperable type and type param. */
2354 if (verify_c_interop (arg_ts) == SUCCESS
2355 || gfc_check_any_c_kind (arg_ts) == SUCCESS)
2357 if (args_sym->attr.target == 1)
2359 /* Case 1a, section 15.1.2.5, J3/04-007: variable that
2360 has the target attribute and is interoperable. */
2361 /* Case 1b, section 15.1.2.5, J3/04-007: allocated
2362 allocatable variable that has the TARGET attribute and
2363 is not an array of zero size. */
2364 if (args_sym->attr.allocatable == 1)
2366 if (args_sym->attr.dimension != 0
2367 && (args_sym->as && args_sym->as->rank == 0))
2369 gfc_error_now ("Allocatable variable '%s' used as a "
2370 "parameter to '%s' at %L must not be "
2371 "an array of zero size",
2372 args_sym->name, sym->name,
2373 &(args->expr->where));
2379 /* A non-allocatable target variable with C
2380 interoperable type and type parameters must be
2382 if (args_sym && args_sym->attr.dimension)
2384 if (args_sym->as->type == AS_ASSUMED_SHAPE)
2386 gfc_error ("Assumed-shape array '%s' at %L "
2387 "cannot be an argument to the "
2388 "procedure '%s' because "
2389 "it is not C interoperable",
2391 &(args->expr->where), sym->name);
2394 else if (args_sym->as->type == AS_DEFERRED)
2396 gfc_error ("Deferred-shape array '%s' at %L "
2397 "cannot be an argument to the "
2398 "procedure '%s' because "
2399 "it is not C interoperable",
2401 &(args->expr->where), sym->name);
2406 /* Make sure it's not a character string. Arrays of
2407 any type should be ok if the variable is of a C
2408 interoperable type. */
2409 if (arg_ts->type == BT_CHARACTER)
2410 if (arg_ts->u.cl != NULL
2411 && (arg_ts->u.cl->length == NULL
2412 || arg_ts->u.cl->length->expr_type
2415 (arg_ts->u.cl->length->value.integer, 1)
2417 && is_scalar_expr_ptr (args->expr) != SUCCESS)
2419 gfc_error_now ("CHARACTER argument '%s' to '%s' "
2420 "at %L must have a length of 1",
2421 args_sym->name, sym->name,
2422 &(args->expr->where));
2428 && is_scalar_expr_ptr (args->expr) != SUCCESS)
2430 /* Case 1c, section 15.1.2.5, J3/04-007: an associated
2432 gfc_error_now ("Argument '%s' to '%s' at %L must be an "
2433 "associated scalar POINTER", args_sym->name,
2434 sym->name, &(args->expr->where));
2440 /* The parameter is not required to be C interoperable. If it
2441 is not C interoperable, it must be a nonpolymorphic scalar
2442 with no length type parameters. It still must have either
2443 the pointer or target attribute, and it can be
2444 allocatable (but must be allocated when c_loc is called). */
2445 if (args->expr->rank != 0
2446 && is_scalar_expr_ptr (args->expr) != SUCCESS)
2448 gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2449 "scalar", args_sym->name, sym->name,
2450 &(args->expr->where));
2453 else if (arg_ts->type == BT_CHARACTER
2454 && is_scalar_expr_ptr (args->expr) != SUCCESS)
2456 gfc_error_now ("CHARACTER argument '%s' to '%s' at "
2457 "%L must have a length of 1",
2458 args_sym->name, sym->name,
2459 &(args->expr->where));
2464 else if (sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2466 if (args_sym->attr.flavor != FL_PROCEDURE)
2468 /* TODO: Update this error message to allow for procedure
2469 pointers once they are implemented. */
2470 gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2472 args_sym->name, sym->name,
2473 &(args->expr->where));
2476 else if (args_sym->attr.is_bind_c != 1)
2478 gfc_error_now ("Parameter '%s' to '%s' at %L must be "
2480 args_sym->name, sym->name,
2481 &(args->expr->where));
2486 /* for c_loc/c_funloc, the new symbol is the same as the old one */
2491 gfc_internal_error ("gfc_iso_c_func_interface(): Unhandled "
2492 "iso_c_binding function: '%s'!\n", sym->name);
2499 /* Resolve a function call, which means resolving the arguments, then figuring
2500 out which entity the name refers to. */
2501 /* TODO: Check procedure arguments so that an INTENT(IN) isn't passed
2502 to INTENT(OUT) or INTENT(INOUT). */
2505 resolve_function (gfc_expr *expr)
2507 gfc_actual_arglist *arg;
2512 procedure_type p = PROC_INTRINSIC;
2513 bool no_formal_args;
2517 sym = expr->symtree->n.sym;
2519 if (sym && sym->attr.intrinsic
2520 && resolve_intrinsic (sym, &expr->where) == FAILURE)
2523 if (sym && (sym->attr.flavor == FL_VARIABLE || sym->attr.subroutine))
2525 gfc_error ("'%s' at %L is not a function", sym->name, &expr->where);
2529 if (sym && sym->attr.abstract)
2531 gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
2532 sym->name, &expr->where);
2536 /* Switch off assumed size checking and do this again for certain kinds
2537 of procedure, once the procedure itself is resolved. */
2538 need_full_assumed_size++;
2540 if (expr->symtree && expr->symtree->n.sym)
2541 p = expr->symtree->n.sym->attr.proc;
2543 no_formal_args = sym && is_external_proc (sym) && sym->formal == NULL;
2544 if (resolve_actual_arglist (expr->value.function.actual,
2545 p, no_formal_args) == FAILURE)
2548 /* Need to setup the call to the correct c_associated, depending on
2549 the number of cptrs to user gives to compare. */
2550 if (sym && sym->attr.is_iso_c == 1)
2552 if (gfc_iso_c_func_interface (sym, expr->value.function.actual, &sym)
2556 /* Get the symtree for the new symbol (resolved func).
2557 the old one will be freed later, when it's no longer used. */
2558 gfc_find_sym_tree (sym->name, sym->ns, 1, &(expr->symtree));
2561 /* Resume assumed_size checking. */
2562 need_full_assumed_size--;
2564 /* If the procedure is external, check for usage. */
2565 if (sym && is_external_proc (sym))
2566 resolve_global_procedure (sym, &expr->where,
2567 &expr->value.function.actual, 0);
2569 if (sym && sym->ts.type == BT_CHARACTER
2571 && sym->ts.u.cl->length == NULL
2573 && expr->value.function.esym == NULL
2574 && !sym->attr.contained)
2576 /* Internal procedures are taken care of in resolve_contained_fntype. */
2577 gfc_error ("Function '%s' is declared CHARACTER(*) and cannot "
2578 "be used at %L since it is not a dummy argument",
2579 sym->name, &expr->where);
2583 /* See if function is already resolved. */
2585 if (expr->value.function.name != NULL)
2587 if (expr->ts.type == BT_UNKNOWN)
2593 /* Apply the rules of section 14.1.2. */
2595 switch (procedure_kind (sym))
2598 t = resolve_generic_f (expr);
2601 case PTYPE_SPECIFIC:
2602 t = resolve_specific_f (expr);
2606 t = resolve_unknown_f (expr);
2610 gfc_internal_error ("resolve_function(): bad function type");
2614 /* If the expression is still a function (it might have simplified),
2615 then we check to see if we are calling an elemental function. */
2617 if (expr->expr_type != EXPR_FUNCTION)
2620 temp = need_full_assumed_size;
2621 need_full_assumed_size = 0;
2623 if (resolve_elemental_actual (expr, NULL) == FAILURE)
2626 if (omp_workshare_flag
2627 && expr->value.function.esym
2628 && ! gfc_elemental (expr->value.function.esym))
2630 gfc_error ("User defined non-ELEMENTAL function '%s' at %L not allowed "
2631 "in WORKSHARE construct", expr->value.function.esym->name,
2636 #define GENERIC_ID expr->value.function.isym->id
2637 else if (expr->value.function.actual != NULL
2638 && expr->value.function.isym != NULL
2639 && GENERIC_ID != GFC_ISYM_LBOUND
2640 && GENERIC_ID != GFC_ISYM_LEN
2641 && GENERIC_ID != GFC_ISYM_LOC
2642 && GENERIC_ID != GFC_ISYM_PRESENT)
2644 /* Array intrinsics must also have the last upper bound of an
2645 assumed size array argument. UBOUND and SIZE have to be
2646 excluded from the check if the second argument is anything
2649 for (arg = expr->value.function.actual; arg; arg = arg->next)
2651 if ((GENERIC_ID == GFC_ISYM_UBOUND || GENERIC_ID == GFC_ISYM_SIZE)
2652 && arg->next != NULL && arg->next->expr)
2654 if (arg->next->expr->expr_type != EXPR_CONSTANT)
2657 if (arg->next->name && strncmp(arg->next->name, "kind", 4) == 0)
2660 if ((int)mpz_get_si (arg->next->expr->value.integer)
2665 if (arg->expr != NULL
2666 && arg->expr->rank > 0
2667 && resolve_assumed_size_actual (arg->expr))
2673 need_full_assumed_size = temp;
2676 if (!pure_function (expr, &name) && name)
2680 gfc_error ("reference to non-PURE function '%s' at %L inside a "
2681 "FORALL %s", name, &expr->where,
2682 forall_flag == 2 ? "mask" : "block");
2685 else if (gfc_pure (NULL))
2687 gfc_error ("Function reference to '%s' at %L is to a non-PURE "
2688 "procedure within a PURE procedure", name, &expr->where);
2693 /* Functions without the RECURSIVE attribution are not allowed to
2694 * call themselves. */
2695 if (expr->value.function.esym && !expr->value.function.esym->attr.recursive)
2698 esym = expr->value.function.esym;
2700 if (is_illegal_recursion (esym, gfc_current_ns))
2702 if (esym->attr.entry && esym->ns->entries)
2703 gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
2704 " function '%s' is not RECURSIVE",
2705 esym->name, &expr->where, esym->ns->entries->sym->name);
2707 gfc_error ("Function '%s' at %L cannot be called recursively, as it"
2708 " is not RECURSIVE", esym->name, &expr->where);
2714 /* Character lengths of use associated functions may contains references to
2715 symbols not referenced from the current program unit otherwise. Make sure
2716 those symbols are marked as referenced. */
2718 if (expr->ts.type == BT_CHARACTER && expr->value.function.esym
2719 && expr->value.function.esym->attr.use_assoc)
2721 gfc_expr_set_symbols_referenced (expr->ts.u.cl->length);
2725 && !((expr->value.function.esym
2726 && expr->value.function.esym->attr.elemental)
2728 (expr->value.function.isym
2729 && expr->value.function.isym->elemental)))
2730 find_noncopying_intrinsics (expr->value.function.esym,
2731 expr->value.function.actual);
2733 /* Make sure that the expression has a typespec that works. */
2734 if (expr->ts.type == BT_UNKNOWN)
2736 if (expr->symtree->n.sym->result
2737 && expr->symtree->n.sym->result->ts.type != BT_UNKNOWN
2738 && !expr->symtree->n.sym->result->attr.proc_pointer)
2739 expr->ts = expr->symtree->n.sym->result->ts;
2746 /************* Subroutine resolution *************/
2749 pure_subroutine (gfc_code *c, gfc_symbol *sym)
2755 gfc_error ("Subroutine call to '%s' in FORALL block at %L is not PURE",
2756 sym->name, &c->loc);
2757 else if (gfc_pure (NULL))
2758 gfc_error ("Subroutine call to '%s' at %L is not PURE", sym->name,
2764 resolve_generic_s0 (gfc_code *c, gfc_symbol *sym)
2768 if (sym->attr.generic)
2770 s = gfc_search_interface (sym->generic, 1, &c->ext.actual);
2773 c->resolved_sym = s;
2774 pure_subroutine (c, s);
2778 /* TODO: Need to search for elemental references in generic interface. */
2781 if (sym->attr.intrinsic)
2782 return gfc_intrinsic_sub_interface (c, 0);
2789 resolve_generic_s (gfc_code *c)
2794 sym = c->symtree->n.sym;
2798 m = resolve_generic_s0 (c, sym);
2801 else if (m == MATCH_ERROR)
2805 if (sym->ns->parent == NULL)
2807 gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2811 if (!generic_sym (sym))
2815 /* Last ditch attempt. See if the reference is to an intrinsic
2816 that possesses a matching interface. 14.1.2.4 */
2817 sym = c->symtree->n.sym;
2819 if (!gfc_is_intrinsic (sym, 1, c->loc))
2821 gfc_error ("There is no specific subroutine for the generic '%s' at %L",
2822 sym->name, &c->loc);
2826 m = gfc_intrinsic_sub_interface (c, 0);
2830 gfc_error ("Generic subroutine '%s' at %L is not consistent with an "
2831 "intrinsic subroutine interface", sym->name, &c->loc);
2837 /* Set the name and binding label of the subroutine symbol in the call
2838 expression represented by 'c' to include the type and kind of the
2839 second parameter. This function is for resolving the appropriate
2840 version of c_f_pointer() and c_f_procpointer(). For example, a
2841 call to c_f_pointer() for a default integer pointer could have a
2842 name of c_f_pointer_i4. If no second arg exists, which is an error
2843 for these two functions, it defaults to the generic symbol's name
2844 and binding label. */
2847 set_name_and_label (gfc_code *c, gfc_symbol *sym,
2848 char *name, char *binding_label)
2850 gfc_expr *arg = NULL;
2854 /* The second arg of c_f_pointer and c_f_procpointer determines
2855 the type and kind for the procedure name. */
2856 arg = c->ext.actual->next->expr;
2860 /* Set up the name to have the given symbol's name,
2861 plus the type and kind. */
2862 /* a derived type is marked with the type letter 'u' */
2863 if (arg->ts.type == BT_DERIVED)
2866 kind = 0; /* set the kind as 0 for now */
2870 type = gfc_type_letter (arg->ts.type);
2871 kind = arg->ts.kind;
2874 if (arg->ts.type == BT_CHARACTER)
2875 /* Kind info for character strings not needed. */
2878 sprintf (name, "%s_%c%d", sym->name, type, kind);
2879 /* Set up the binding label as the given symbol's label plus
2880 the type and kind. */
2881 sprintf (binding_label, "%s_%c%d", sym->binding_label, type, kind);
2885 /* If the second arg is missing, set the name and label as
2886 was, cause it should at least be found, and the missing
2887 arg error will be caught by compare_parameters(). */
2888 sprintf (name, "%s", sym->name);
2889 sprintf (binding_label, "%s", sym->binding_label);
2896 /* Resolve a generic version of the iso_c_binding procedure given
2897 (sym) to the specific one based on the type and kind of the
2898 argument(s). Currently, this function resolves c_f_pointer() and
2899 c_f_procpointer based on the type and kind of the second argument
2900 (FPTR). Other iso_c_binding procedures aren't specially handled.
2901 Upon successfully exiting, c->resolved_sym will hold the resolved
2902 symbol. Returns MATCH_ERROR if an error occurred; MATCH_YES
2906 gfc_iso_c_sub_interface (gfc_code *c, gfc_symbol *sym)
2908 gfc_symbol *new_sym;
2909 /* this is fine, since we know the names won't use the max */
2910 char name[GFC_MAX_SYMBOL_LEN + 1];
2911 char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
2912 /* default to success; will override if find error */
2913 match m = MATCH_YES;
2915 /* Make sure the actual arguments are in the necessary order (based on the
2916 formal args) before resolving. */
2917 gfc_procedure_use (sym, &c->ext.actual, &(c->loc));
2919 if ((sym->intmod_sym_id == ISOCBINDING_F_POINTER) ||
2920 (sym->intmod_sym_id == ISOCBINDING_F_PROCPOINTER))
2922 set_name_and_label (c, sym, name, binding_label);
2924 if (sym->intmod_sym_id == ISOCBINDING_F_POINTER)
2926 if (c->ext.actual != NULL && c->ext.actual->next != NULL)
2928 /* Make sure we got a third arg if the second arg has non-zero
2929 rank. We must also check that the type and rank are
2930 correct since we short-circuit this check in
2931 gfc_procedure_use() (called above to sort actual args). */
2932 if (c->ext.actual->next->expr->rank != 0)
2934 if(c->ext.actual->next->next == NULL
2935 || c->ext.actual->next->next->expr == NULL)
2938 gfc_error ("Missing SHAPE parameter for call to %s "
2939 "at %L", sym->name, &(c->loc));
2941 else if (c->ext.actual->next->next->expr->ts.type
2943 || c->ext.actual->next->next->expr->rank != 1)
2946 gfc_error ("SHAPE parameter for call to %s at %L must "
2947 "be a rank 1 INTEGER array", sym->name,
2954 if (m != MATCH_ERROR)
2956 /* the 1 means to add the optional arg to formal list */
2957 new_sym = get_iso_c_sym (sym, name, binding_label, 1);
2959 /* for error reporting, say it's declared where the original was */
2960 new_sym->declared_at = sym->declared_at;
2965 /* no differences for c_loc or c_funloc */
2969 /* set the resolved symbol */
2970 if (m != MATCH_ERROR)
2971 c->resolved_sym = new_sym;
2973 c->resolved_sym = sym;
2979 /* Resolve a subroutine call known to be specific. */
2982 resolve_specific_s0 (gfc_code *c, gfc_symbol *sym)
2986 if(sym->attr.is_iso_c)
2988 m = gfc_iso_c_sub_interface (c,sym);
2992 if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
2994 if (sym->attr.dummy)
2996 sym->attr.proc = PROC_DUMMY;
3000 sym->attr.proc = PROC_EXTERNAL;
3004 if (sym->attr.proc == PROC_MODULE || sym->attr.proc == PROC_INTERNAL)
3007 if (sym->attr.intrinsic)
3009 m = gfc_intrinsic_sub_interface (c, 1);
3013 gfc_error ("Subroutine '%s' at %L is INTRINSIC but is not compatible "
3014 "with an intrinsic", sym->name, &c->loc);
3022 gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3024 c->resolved_sym = sym;
3025 pure_subroutine (c, sym);
3032 resolve_specific_s (gfc_code *c)
3037 sym = c->symtree->n.sym;
3041 m = resolve_specific_s0 (c, sym);
3044 if (m == MATCH_ERROR)
3047 if (sym->ns->parent == NULL)
3050 gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
3056 sym = c->symtree->n.sym;
3057 gfc_error ("Unable to resolve the specific subroutine '%s' at %L",
3058 sym->name, &c->loc);
3064 /* Resolve a subroutine call not known to be generic nor specific. */
3067 resolve_unknown_s (gfc_code *c)
3071 sym = c->symtree->n.sym;
3073 if (sym->attr.dummy)
3075 sym->attr.proc = PROC_DUMMY;
3079 /* See if we have an intrinsic function reference. */
3081 if (gfc_is_intrinsic (sym, 1, c->loc))
3083 if (gfc_intrinsic_sub_interface (c, 1) == MATCH_YES)
3088 /* The reference is to an external name. */
3091 gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3093 c->resolved_sym = sym;
3095 pure_subroutine (c, sym);
3101 /* Resolve a subroutine call. Although it was tempting to use the same code
3102 for functions, subroutines and functions are stored differently and this
3103 makes things awkward. */
3106 resolve_call (gfc_code *c)
3109 procedure_type ptype = PROC_INTRINSIC;
3110 gfc_symbol *csym, *sym;
3111 bool no_formal_args;
3113 csym = c->symtree ? c->symtree->n.sym : NULL;
3115 if (csym && csym->ts.type != BT_UNKNOWN)
3117 gfc_error ("'%s' at %L has a type, which is not consistent with "
3118 "the CALL at %L", csym->name, &csym->declared_at, &c->loc);
3122 if (csym && gfc_current_ns->parent && csym->ns != gfc_current_ns)
3125 gfc_find_sym_tree (csym->name, gfc_current_ns, 1, &st);
3126 sym = st ? st->n.sym : NULL;
3127 if (sym && csym != sym
3128 && sym->ns == gfc_current_ns
3129 && sym->attr.flavor == FL_PROCEDURE
3130 && sym->attr.contained)
3133 if (csym->attr.generic)
3134 c->symtree->n.sym = sym;
3137 csym = c->symtree->n.sym;
3141 /* Subroutines without the RECURSIVE attribution are not allowed to
3142 * call themselves. */
3143 if (csym && is_illegal_recursion (csym, gfc_current_ns))
3145 if (csym->attr.entry && csym->ns->entries)
3146 gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
3147 " subroutine '%s' is not RECURSIVE",
3148 csym->name, &c->loc, csym->ns->entries->sym->name);
3150 gfc_error ("SUBROUTINE '%s' at %L cannot be called recursively, as it"
3151 " is not RECURSIVE", csym->name, &c->loc);
3156 /* Switch off assumed size checking and do this again for certain kinds
3157 of procedure, once the procedure itself is resolved. */
3158 need_full_assumed_size++;
3161 ptype = csym->attr.proc;
3163 no_formal_args = csym && is_external_proc (csym) && csym->formal == NULL;
3164 if (resolve_actual_arglist (c->ext.actual, ptype,
3165 no_formal_args) == FAILURE)
3168 /* Resume assumed_size checking. */
3169 need_full_assumed_size--;
3171 /* If external, check for usage. */
3172 if (csym && is_external_proc (csym))
3173 resolve_global_procedure (csym, &c->loc, &c->ext.actual, 1);
3176 if (c->resolved_sym == NULL)
3178 c->resolved_isym = NULL;
3179 switch (procedure_kind (csym))
3182 t = resolve_generic_s (c);
3185 case PTYPE_SPECIFIC:
3186 t = resolve_specific_s (c);
3190 t = resolve_unknown_s (c);
3194 gfc_internal_error ("resolve_subroutine(): bad function type");
3198 /* Some checks of elemental subroutine actual arguments. */
3199 if (resolve_elemental_actual (NULL, c) == FAILURE)
3202 if (t == SUCCESS && !(c->resolved_sym && c->resolved_sym->attr.elemental))
3203 find_noncopying_intrinsics (c->resolved_sym, c->ext.actual);
3208 /* Compare the shapes of two arrays that have non-NULL shapes. If both
3209 op1->shape and op2->shape are non-NULL return SUCCESS if their shapes
3210 match. If both op1->shape and op2->shape are non-NULL return FAILURE
3211 if their shapes do not match. If either op1->shape or op2->shape is
3212 NULL, return SUCCESS. */
3215 compare_shapes (gfc_expr *op1, gfc_expr *op2)
3222 if (op1->shape != NULL && op2->shape != NULL)
3224 for (i = 0; i < op1->rank; i++)
3226 if (mpz_cmp (op1->shape[i], op2->shape[i]) != 0)
3228 gfc_error ("Shapes for operands at %L and %L are not conformable",
3229 &op1->where, &op2->where);
3240 /* Resolve an operator expression node. This can involve replacing the
3241 operation with a user defined function call. */
3244 resolve_operator (gfc_expr *e)
3246 gfc_expr *op1, *op2;
3248 bool dual_locus_error;
3251 /* Resolve all subnodes-- give them types. */
3253 switch (e->value.op.op)
3256 if (gfc_resolve_expr (e->value.op.op2) == FAILURE)
3259 /* Fall through... */
3262 case INTRINSIC_UPLUS:
3263 case INTRINSIC_UMINUS:
3264 case INTRINSIC_PARENTHESES:
3265 if (gfc_resolve_expr (e->value.op.op1) == FAILURE)
3270 /* Typecheck the new node. */
3272 op1 = e->value.op.op1;
3273 op2 = e->value.op.op2;
3274 dual_locus_error = false;
3276 if ((op1 && op1->expr_type == EXPR_NULL)
3277 || (op2 && op2->expr_type == EXPR_NULL))
3279 sprintf (msg, _("Invalid context for NULL() pointer at %%L"));
3283 switch (e->value.op.op)
3285 case INTRINSIC_UPLUS:
3286 case INTRINSIC_UMINUS:
3287 if (op1->ts.type == BT_INTEGER
3288 || op1->ts.type == BT_REAL
3289 || op1->ts.type == BT_COMPLEX)
3295 sprintf (msg, _("Operand of unary numeric operator '%s' at %%L is %s"),
3296 gfc_op2string (e->value.op.op), gfc_typename (&e->ts));
3299 case INTRINSIC_PLUS:
3300 case INTRINSIC_MINUS:
3301 case INTRINSIC_TIMES:
3302 case INTRINSIC_DIVIDE:
3303 case INTRINSIC_POWER:
3304 if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3306 gfc_type_convert_binary (e);
3311 _("Operands of binary numeric operator '%s' at %%L are %s/%s"),
3312 gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3313 gfc_typename (&op2->ts));
3316 case INTRINSIC_CONCAT:
3317 if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3318 && op1->ts.kind == op2->ts.kind)
3320 e->ts.type = BT_CHARACTER;
3321 e->ts.kind = op1->ts.kind;
3326 _("Operands of string concatenation operator at %%L are %s/%s"),
3327 gfc_typename (&op1->ts), gfc_typename (&op2->ts));
3333 case INTRINSIC_NEQV:
3334 if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3336 e->ts.type = BT_LOGICAL;
3337 e->ts.kind = gfc_kind_max (op1, op2);
3338 if (op1->ts.kind < e->ts.kind)
3339 gfc_convert_type (op1, &e->ts, 2);
3340 else if (op2->ts.kind < e->ts.kind)
3341 gfc_convert_type (op2, &e->ts, 2);
3345 sprintf (msg, _("Operands of logical operator '%s' at %%L are %s/%s"),
3346 gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3347 gfc_typename (&op2->ts));
3352 if (op1->ts.type == BT_LOGICAL)
3354 e->ts.type = BT_LOGICAL;
3355 e->ts.kind = op1->ts.kind;
3359 sprintf (msg, _("Operand of .not. operator at %%L is %s"),
3360 gfc_typename (&op1->ts));
3364 case INTRINSIC_GT_OS:
3366 case INTRINSIC_GE_OS:
3368 case INTRINSIC_LT_OS:
3370 case INTRINSIC_LE_OS:
3371 if (op1->ts.type == BT_COMPLEX || op2->ts.type == BT_COMPLEX)
3373 strcpy (msg, _("COMPLEX quantities cannot be compared at %L"));
3377 /* Fall through... */
3380 case INTRINSIC_EQ_OS:
3382 case INTRINSIC_NE_OS:
3383 if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3384 && op1->ts.kind == op2->ts.kind)
3386 e->ts.type = BT_LOGICAL;
3387 e->ts.kind = gfc_default_logical_kind;
3391 if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3393 gfc_type_convert_binary (e);
3395 e->ts.type = BT_LOGICAL;
3396 e->ts.kind = gfc_default_logical_kind;
3400 if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3402 _("Logicals at %%L must be compared with %s instead of %s"),
3403 (e->value.op.op == INTRINSIC_EQ
3404 || e->value.op.op == INTRINSIC_EQ_OS)
3405 ? ".eqv." : ".neqv.", gfc_op2string (e->value.op.op));
3408 _("Operands of comparison operator '%s' at %%L are %s/%s"),
3409 gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3410 gfc_typename (&op2->ts));
3414 case INTRINSIC_USER:
3415 if (e->value.op.uop->op == NULL)
3416 sprintf (msg, _("Unknown operator '%s' at %%L"), e->value.op.uop->name);
3417 else if (op2 == NULL)
3418 sprintf (msg, _("Operand of user operator '%s' at %%L is %s"),
3419 e->value.op.uop->name, gfc_typename (&op1->ts));
3421 sprintf (msg, _("Operands of user operator '%s' at %%L are %s/%s"),
3422 e->value.op.uop->name, gfc_typename (&op1->ts),
3423 gfc_typename (&op2->ts));
3427 case INTRINSIC_PARENTHESES:
3429 if (e->ts.type == BT_CHARACTER)
3430 e->ts.u.cl = op1->ts.u.cl;
3434 gfc_internal_error ("resolve_operator(): Bad intrinsic");
3437 /* Deal with arrayness of an operand through an operator. */
3441 switch (e->value.op.op)
3443 case INTRINSIC_PLUS:
3444 case INTRINSIC_MINUS:
3445 case INTRINSIC_TIMES:
3446 case INTRINSIC_DIVIDE:
3447 case INTRINSIC_POWER:
3448 case INTRINSIC_CONCAT:
3452 case INTRINSIC_NEQV:
3454 case INTRINSIC_EQ_OS:
3456 case INTRINSIC_NE_OS:
3458 case INTRINSIC_GT_OS:
3460 case INTRINSIC_GE_OS:
3462 case INTRINSIC_LT_OS:
3464 case INTRINSIC_LE_OS:
3466 if (op1->rank == 0 && op2->rank == 0)
3469 if (op1->rank == 0 && op2->rank != 0)
3471 e->rank = op2->rank;
3473 if (e->shape == NULL)
3474 e->shape = gfc_copy_shape (op2->shape, op2->rank);
3477 if (op1->rank != 0 && op2->rank == 0)
3479 e->rank = op1->rank;
3481 if (e->shape == NULL)
3482 e->shape = gfc_copy_shape (op1->shape, op1->rank);
3485 if (op1->rank != 0 && op2->rank != 0)
3487 if (op1->rank == op2->rank)
3489 e->rank = op1->rank;
3490 if (e->shape == NULL)
3492 t = compare_shapes(op1, op2);
3496 e->shape = gfc_copy_shape (op1->shape, op1->rank);
3501 /* Allow higher level expressions to work. */
3504 /* Try user-defined operators, and otherwise throw an error. */
3505 dual_locus_error = true;
3507 _("Inconsistent ranks for operator at %%L and %%L"));
3514 case INTRINSIC_PARENTHESES:
3516 case INTRINSIC_UPLUS:
3517 case INTRINSIC_UMINUS:
3518 /* Simply copy arrayness attribute */
3519 e->rank = op1->rank;
3521 if (e->shape == NULL)
3522 e->shape = gfc_copy_shape (op1->shape, op1->rank);
3530 /* Attempt to simplify the expression. */
3533 t = gfc_simplify_expr (e, 0);
3534 /* Some calls do not succeed in simplification and return FAILURE
3535 even though there is no error; e.g. variable references to
3536 PARAMETER arrays. */
3537 if (!gfc_is_constant_expr (e))
3546 if (gfc_extend_expr (e, &real_error) == SUCCESS)
3553 if (dual_locus_error)
3554 gfc_error (msg, &op1->where, &op2->where);
3556 gfc_error (msg, &e->where);
3562 /************** Array resolution subroutines **************/
3565 { CMP_LT, CMP_EQ, CMP_GT, CMP_UNKNOWN }
3568 /* Compare two integer expressions. */
3571 compare_bound (gfc_expr *a, gfc_expr *b)
3575 if (a == NULL || a->expr_type != EXPR_CONSTANT
3576 || b == NULL || b->expr_type != EXPR_CONSTANT)
3579 /* If either of the types isn't INTEGER, we must have
3580 raised an error earlier. */
3582 if (a->ts.type != BT_INTEGER || b->ts.type != BT_INTEGER)
3585 i = mpz_cmp (a->value.integer, b->value.integer);
3595 /* Compare an integer expression with an integer. */
3598 compare_bound_int (gfc_expr *a, int b)
3602 if (a == NULL || a->expr_type != EXPR_CONSTANT)
3605 if (a->ts.type != BT_INTEGER)
3606 gfc_internal_error ("compare_bound_int(): Bad expression");
3608 i = mpz_cmp_si (a->value.integer, b);
3618 /* Compare an integer expression with a mpz_t. */
3621 compare_bound_mpz_t (gfc_expr *a, mpz_t b)
3625 if (a == NULL || a->expr_type != EXPR_CONSTANT)
3628 if (a->ts.type != BT_INTEGER)
3629 gfc_internal_error ("compare_bound_int(): Bad expression");
3631 i = mpz_cmp (a->value.integer, b);
3641 /* Compute the last value of a sequence given by a triplet.
3642 Return 0 if it wasn't able to compute the last value, or if the
3643 sequence if empty, and 1 otherwise. */
3646 compute_last_value_for_triplet (gfc_expr *start, gfc_expr *end,
3647 gfc_expr *stride, mpz_t last)
3651 if (start == NULL || start->expr_type != EXPR_CONSTANT
3652 || end == NULL || end->expr_type != EXPR_CONSTANT
3653 || (stride != NULL && stride->expr_type != EXPR_CONSTANT))
3656 if (start->ts.type != BT_INTEGER || end->ts.type != BT_INTEGER
3657 || (stride != NULL && stride->ts.type != BT_INTEGER))
3660 if (stride == NULL || compare_bound_int(stride, 1) == CMP_EQ)
3662 if (compare_bound (start, end) == CMP_GT)
3664 mpz_set (last, end->value.integer);
3668 if (compare_bound_int (stride, 0) == CMP_GT)
3670 /* Stride is positive */
3671 if (mpz_cmp (start->value.integer, end->value.integer) > 0)
3676 /* Stride is negative */
3677 if (mpz_cmp (start->value.integer, end->value.integer) < 0)
3682 mpz_sub (rem, end->value.integer, start->value.integer);
3683 mpz_tdiv_r (rem, rem, stride->value.integer);
3684 mpz_sub (last, end->value.integer, rem);
3691 /* Compare a single dimension of an array reference to the array
3695 check_dimension (int i, gfc_array_ref *ar, gfc_array_spec *as)
3699 /* Given start, end and stride values, calculate the minimum and
3700 maximum referenced indexes. */
3702 switch (ar->dimen_type[i])
3708 if (compare_bound (ar->start[i], as->lower[i]) == CMP_LT)
3710 gfc_warning ("Array reference at %L is out of bounds "
3711 "(%ld < %ld) in dimension %d", &ar->c_where[i],
3712 mpz_get_si (ar->start[i]->value.integer),
3713 mpz_get_si (as->lower[i]->value.integer), i+1);
3716 if (compare_bound (ar->start[i], as->upper[i]) == CMP_GT)
3718 gfc_warning ("Array reference at %L is out of bounds "
3719 "(%ld > %ld) in dimension %d", &ar->c_where[i],
3720 mpz_get_si (ar->start[i]->value.integer),
3721 mpz_get_si (as->upper[i]->value.integer), i+1);
3729 #define AR_START (ar->start[i] ? ar->start[i] : as->lower[i])
3730 #define AR_END (ar->end[i] ? ar->end[i] : as->upper[i])
3732 comparison comp_start_end = compare_bound (AR_START, AR_END);
3734 /* Check for zero stride, which is not allowed. */
3735 if (compare_bound_int (ar->stride[i], 0) == CMP_EQ)
3737 gfc_error ("Illegal stride of zero at %L", &ar->c_where[i]);
3741 /* if start == len || (stride > 0 && start < len)
3742 || (stride < 0 && start > len),
3743 then the array section contains at least one element. In this
3744 case, there is an out-of-bounds access if
3745 (start < lower || start > upper). */
3746 if (compare_bound (AR_START, AR_END) == CMP_EQ
3747 || ((compare_bound_int (ar->stride[i], 0) == CMP_GT
3748 || ar->stride[i] == NULL) && comp_start_end == CMP_LT)
3749 || (compare_bound_int (ar->stride[i], 0) == CMP_LT
3750 && comp_start_end == CMP_GT))
3752 if (compare_bound (AR_START, as->lower[i]) == CMP_LT)
3754 gfc_warning ("Lower array reference at %L is out of bounds "
3755 "(%ld < %ld) in dimension %d", &ar->c_where[i],
3756 mpz_get_si (AR_START->value.integer),
3757 mpz_get_si (as->lower[i]->value.integer), i+1);
3760 if (compare_bound (AR_START, as->upper[i]) == CMP_GT)
3762 gfc_warning ("Lower array reference at %L is out of bounds "
3763 "(%ld > %ld) in dimension %d", &ar->c_where[i],
3764 mpz_get_si (AR_START->value.integer),
3765 mpz_get_si (as->upper[i]->value.integer), i+1);
3770 /* If we can compute the highest index of the array section,
3771 then it also has to be between lower and upper. */
3772 mpz_init (last_value);
3773 if (compute_last_value_for_triplet (AR_START, AR_END, ar->stride[i],
3776 if (compare_bound_mpz_t (as->lower[i], last_value) == CMP_GT)
3778 gfc_warning ("Upper array reference at %L is out of bounds "
3779 "(%ld < %ld) in dimension %d", &ar->c_where[i],
3780 mpz_get_si (last_value),
3781 mpz_get_si (as->lower[i]->value.integer), i+1);
3782 mpz_clear (last_value);
3785 if (compare_bound_mpz_t (as->upper[i], last_value) == CMP_LT)
3787 gfc_warning ("Upper array reference at %L is out of bounds "
3788 "(%ld > %ld) in dimension %d", &ar->c_where[i],
3789 mpz_get_si (last_value),
3790 mpz_get_si (as->upper[i]->value.integer), i+1);
3791 mpz_clear (last_value);
3795 mpz_clear (last_value);
3803 gfc_internal_error ("check_dimension(): Bad array reference");
3810 /* Compare an array reference with an array specification. */
3813 compare_spec_to_ref (gfc_array_ref *ar)
3820 /* TODO: Full array sections are only allowed as actual parameters. */
3821 if (as->type == AS_ASSUMED_SIZE
3822 && (/*ar->type == AR_FULL
3823 ||*/ (ar->type == AR_SECTION
3824 && ar->dimen_type[i] == DIMEN_RANGE && ar->end[i] == NULL)))
3826 gfc_error ("Rightmost upper bound of assumed size array section "
3827 "not specified at %L", &ar->where);
3831 if (ar->type == AR_FULL)
3834 if (as->rank != ar->dimen)
3836 gfc_error ("Rank mismatch in array reference at %L (%d/%d)",
3837 &ar->where, ar->dimen, as->rank);
3841 for (i = 0; i < as->rank; i++)
3842 if (check_dimension (i, ar, as) == FAILURE)
3849 /* Resolve one part of an array index. */
3852 gfc_resolve_index (gfc_expr *index, int check_scalar)
3859 if (gfc_resolve_expr (index) == FAILURE)
3862 if (check_scalar && index->rank != 0)
3864 gfc_error ("Array index at %L must be scalar", &index->where);
3868 if (index->ts.type != BT_INTEGER && index->ts.type != BT_REAL)
3870 gfc_error ("Array index at %L must be of INTEGER type, found %s",
3871 &index->where, gfc_basic_typename (index->ts.type));
3875 if (index->ts.type == BT_REAL)
3876 if (gfc_notify_std (GFC_STD_LEGACY, "Extension: REAL array index at %L",
3877 &index->where) == FAILURE)
3880 if (index->ts.kind != gfc_index_integer_kind
3881 || index->ts.type != BT_INTEGER)
3884 ts.type = BT_INTEGER;
3885 ts.kind = gfc_index_integer_kind;
3887 gfc_convert_type_warn (index, &ts, 2, 0);
3893 /* Resolve a dim argument to an intrinsic function. */
3896 gfc_resolve_dim_arg (gfc_expr *dim)
3901 if (gfc_resolve_expr (dim) == FAILURE)
3906 gfc_error ("Argument dim at %L must be scalar", &dim->where);
3911 if (dim->ts.type != BT_INTEGER)
3913 gfc_error ("Argument dim at %L must be of INTEGER type", &dim->where);
3917 if (dim->ts.kind != gfc_index_integer_kind)
3921 ts.type = BT_INTEGER;
3922 ts.kind = gfc_index_integer_kind;
3924 gfc_convert_type_warn (dim, &ts, 2, 0);
3930 /* Given an expression that contains array references, update those array
3931 references to point to the right array specifications. While this is
3932 filled in during matching, this information is difficult to save and load
3933 in a module, so we take care of it here.
3935 The idea here is that the original array reference comes from the
3936 base symbol. We traverse the list of reference structures, setting
3937 the stored reference to references. Component references can
3938 provide an additional array specification. */
3941 find_array_spec (gfc_expr *e)
3945 gfc_symbol *derived;
3948 if (e->symtree->n.sym->ts.type == BT_CLASS)
3949 as = e->symtree->n.sym->ts.u.derived->components->as;
3951 as = e->symtree->n.sym->as;
3954 for (ref = e->ref; ref; ref = ref->next)
3959 gfc_internal_error ("find_array_spec(): Missing spec");
3966 if (derived == NULL)
3967 derived = e->symtree->n.sym->ts.u.derived;
3969 c = derived->components;
3971 for (; c; c = c->next)
3972 if (c == ref->u.c.component)
3974 /* Track the sequence of component references. */
3975 if (c->ts.type == BT_DERIVED)
3976 derived = c->ts.u.derived;
3981 gfc_internal_error ("find_array_spec(): Component not found");
3983 if (c->attr.dimension)
3986 gfc_internal_error ("find_array_spec(): unused as(1)");
3997 gfc_internal_error ("find_array_spec(): unused as(2)");
4001 /* Resolve an array reference. */
4004 resolve_array_ref (gfc_array_ref *ar)
4006 int i, check_scalar;
4009 for (i = 0; i < ar->dimen; i++)