1/* Perform type resolution on the various structures.
2   Copyright (C) 2001-2016 Free Software Foundation, Inc.
3   Contributed by Andy Vaught
4
5This file is part of GCC.
6
7GCC is free software; you can redistribute it and/or modify it under
8the terms of the GNU General Public License as published by the Free
9Software Foundation; either version 3, or (at your option) any later
10version.
11
12GCC is distributed in the hope that it will be useful, but WITHOUT ANY
13WARRANTY; without even the implied warranty of MERCHANTABILITY or
14FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
15for more details.
16
17You should have received a copy of the GNU General Public License
18along with GCC; see the file COPYING3.  If not see
19<http://www.gnu.org/licenses/>.  */
20
21#include "config.h"
22#include "system.h"
23#include "coretypes.h"
24#include "flags.h"
25#include "gfortran.h"
26#include "obstack.h"
27#include "bitmap.h"
28#include "arith.h"  /* For gfc_compare_expr().  */
29#include "dependency.h"
30#include "data.h"
31#include "target-memory.h" /* for gfc_simplify_transfer */
32#include "constructor.h"
33
34/* Types used in equivalence statements.  */
35
36typedef enum seq_type
37{
38  SEQ_NONDEFAULT, SEQ_NUMERIC, SEQ_CHARACTER, SEQ_MIXED
39}
40seq_type;
41
42/* Stack to keep track of the nesting of blocks as we move through the
43   code.  See resolve_branch() and gfc_resolve_code().  */
44
45typedef struct code_stack
46{
47  struct gfc_code *head, *current;
48  struct code_stack *prev;
49
50  /* This bitmap keeps track of the targets valid for a branch from
51     inside this block except for END {IF|SELECT}s of enclosing
52     blocks.  */
53  bitmap reachable_labels;
54}
55code_stack;
56
57static code_stack *cs_base = NULL;
58
59
60/* Nonzero if we're inside a FORALL or DO CONCURRENT block.  */
61
62static int forall_flag;
63int gfc_do_concurrent_flag;
64
65/* True when we are resolving an expression that is an actual argument to
66   a procedure.  */
67static bool actual_arg = false;
68/* True when we are resolving an expression that is the first actual argument
69   to a procedure.  */
70static bool first_actual_arg = false;
71
72
73/* Nonzero if we're inside a OpenMP WORKSHARE or PARALLEL WORKSHARE block.  */
74
75static int omp_workshare_flag;
76
77/* Nonzero if we are processing a formal arglist. The corresponding function
78   resets the flag each time that it is read.  */
79static int formal_arg_flag = 0;
80
81/* True if we are resolving a specification expression.  */
82static bool specification_expr = false;
83
84/* The id of the last entry seen.  */
85static int current_entry_id;
86
87/* We use bitmaps to determine if a branch target is valid.  */
88static bitmap_obstack labels_obstack;
89
90/* True when simplifying a EXPR_VARIABLE argument to an inquiry function.  */
91static bool inquiry_argument = false;
92
93
94int
95gfc_is_formal_arg (void)
96{
97  return formal_arg_flag;
98}
99
100/* Is the symbol host associated?  */
101static bool
102is_sym_host_assoc (gfc_symbol *sym, gfc_namespace *ns)
103{
104  for (ns = ns->parent; ns; ns = ns->parent)
105    {
106      if (sym->ns == ns)
107	return true;
108    }
109
110  return false;
111}
112
113/* Ensure a typespec used is valid; for instance, TYPE(t) is invalid if t is
114   an ABSTRACT derived-type.  If where is not NULL, an error message with that
115   locus is printed, optionally using name.  */
116
117static bool
118resolve_typespec_used (gfc_typespec* ts, locus* where, const char* name)
119{
120  if (ts->type == BT_DERIVED && ts->u.derived->attr.abstract)
121    {
122      if (where)
123	{
124	  if (name)
125	    gfc_error ("%qs at %L is of the ABSTRACT type %qs",
126		       name, where, ts->u.derived->name);
127	  else
128	    gfc_error ("ABSTRACT type %qs used at %L",
129		       ts->u.derived->name, where);
130	}
131
132      return false;
133    }
134
135  return true;
136}
137
138
139static bool
140check_proc_interface (gfc_symbol *ifc, locus *where)
141{
142  /* Several checks for F08:C1216.  */
143  if (ifc->attr.procedure)
144    {
145      gfc_error ("Interface %qs at %L is declared "
146		 "in a later PROCEDURE statement", ifc->name, where);
147      return false;
148    }
149  if (ifc->generic)
150    {
151      /* For generic interfaces, check if there is
152	 a specific procedure with the same name.  */
153      gfc_interface *gen = ifc->generic;
154      while (gen && strcmp (gen->sym->name, ifc->name) != 0)
155	gen = gen->next;
156      if (!gen)
157	{
158	  gfc_error ("Interface %qs at %L may not be generic",
159		     ifc->name, where);
160	  return false;
161	}
162    }
163  if (ifc->attr.proc == PROC_ST_FUNCTION)
164    {
165      gfc_error ("Interface %qs at %L may not be a statement function",
166		 ifc->name, where);
167      return false;
168    }
169  if (gfc_is_intrinsic (ifc, 0, ifc->declared_at)
170      || gfc_is_intrinsic (ifc, 1, ifc->declared_at))
171    ifc->attr.intrinsic = 1;
172  if (ifc->attr.intrinsic && !gfc_intrinsic_actual_ok (ifc->name, 0))
173    {
174      gfc_error ("Intrinsic procedure %qs not allowed in "
175		 "PROCEDURE statement at %L", ifc->name, where);
176      return false;
177    }
178  if (!ifc->attr.if_source && !ifc->attr.intrinsic && ifc->name[0] != '\0')
179    {
180      gfc_error ("Interface %qs at %L must be explicit", ifc->name, where);
181      return false;
182    }
183  return true;
184}
185
186
187static void resolve_symbol (gfc_symbol *sym);
188
189
190/* Resolve the interface for a PROCEDURE declaration or procedure pointer.  */
191
192static bool
193resolve_procedure_interface (gfc_symbol *sym)
194{
195  gfc_symbol *ifc = sym->ts.interface;
196
197  if (!ifc)
198    return true;
199
200  if (ifc == sym)
201    {
202      gfc_error ("PROCEDURE %qs at %L may not be used as its own interface",
203		 sym->name, &sym->declared_at);
204      return false;
205    }
206  if (!check_proc_interface (ifc, &sym->declared_at))
207    return false;
208
209  if (ifc->attr.if_source || ifc->attr.intrinsic)
210    {
211      /* Resolve interface and copy attributes.  */
212      resolve_symbol (ifc);
213      if (ifc->attr.intrinsic)
214	gfc_resolve_intrinsic (ifc, &ifc->declared_at);
215
216      if (ifc->result)
217	{
218	  sym->ts = ifc->result->ts;
219	  sym->result = sym;
220	}
221      else
222	sym->ts = ifc->ts;
223      sym->ts.interface = ifc;
224      sym->attr.function = ifc->attr.function;
225      sym->attr.subroutine = ifc->attr.subroutine;
226
227      sym->attr.allocatable = ifc->attr.allocatable;
228      sym->attr.pointer = ifc->attr.pointer;
229      sym->attr.pure = ifc->attr.pure;
230      sym->attr.elemental = ifc->attr.elemental;
231      sym->attr.dimension = ifc->attr.dimension;
232      sym->attr.contiguous = ifc->attr.contiguous;
233      sym->attr.recursive = ifc->attr.recursive;
234      sym->attr.always_explicit = ifc->attr.always_explicit;
235      sym->attr.ext_attr |= ifc->attr.ext_attr;
236      sym->attr.is_bind_c = ifc->attr.is_bind_c;
237      sym->attr.class_ok = ifc->attr.class_ok;
238      /* Copy array spec.  */
239      sym->as = gfc_copy_array_spec (ifc->as);
240      /* Copy char length.  */
241      if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
242	{
243	  sym->ts.u.cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
244	  if (sym->ts.u.cl->length && !sym->ts.u.cl->resolved
245	      && !gfc_resolve_expr (sym->ts.u.cl->length))
246	    return false;
247	}
248    }
249
250  return true;
251}
252
253
254/* Resolve types of formal argument lists.  These have to be done early so that
255   the formal argument lists of module procedures can be copied to the
256   containing module before the individual procedures are resolved
257   individually.  We also resolve argument lists of procedures in interface
258   blocks because they are self-contained scoping units.
259
260   Since a dummy argument cannot be a non-dummy procedure, the only
261   resort left for untyped names are the IMPLICIT types.  */
262
263static void
264resolve_formal_arglist (gfc_symbol *proc)
265{
266  gfc_formal_arglist *f;
267  gfc_symbol *sym;
268  bool saved_specification_expr;
269  int i;
270
271  if (proc->result != NULL)
272    sym = proc->result;
273  else
274    sym = proc;
275
276  if (gfc_elemental (proc)
277      || sym->attr.pointer || sym->attr.allocatable
278      || (sym->as && sym->as->rank != 0))
279    {
280      proc->attr.always_explicit = 1;
281      sym->attr.always_explicit = 1;
282    }
283
284  formal_arg_flag = 1;
285
286  for (f = proc->formal; f; f = f->next)
287    {
288      gfc_array_spec *as;
289
290      sym = f->sym;
291
292      if (sym == NULL)
293	{
294	  /* Alternate return placeholder.  */
295	  if (gfc_elemental (proc))
296	    gfc_error ("Alternate return specifier in elemental subroutine "
297		       "%qs at %L is not allowed", proc->name,
298		       &proc->declared_at);
299	  if (proc->attr.function)
300	    gfc_error ("Alternate return specifier in function "
301		       "%qs at %L is not allowed", proc->name,
302		       &proc->declared_at);
303	  continue;
304	}
305      else if (sym->attr.procedure && sym->attr.if_source != IFSRC_DECL
306	       && !resolve_procedure_interface (sym))
307	return;
308
309      if (strcmp (proc->name, sym->name) == 0)
310        {
311          gfc_error ("Self-referential argument "
312                     "%qs at %L is not allowed", sym->name,
313                     &proc->declared_at);
314          return;
315        }
316
317      if (sym->attr.if_source != IFSRC_UNKNOWN)
318	resolve_formal_arglist (sym);
319
320      if (sym->attr.subroutine || sym->attr.external)
321	{
322	  if (sym->attr.flavor == FL_UNKNOWN)
323	    gfc_add_flavor (&sym->attr, FL_PROCEDURE, sym->name, &sym->declared_at);
324	}
325      else
326	{
327	  if (sym->ts.type == BT_UNKNOWN && !proc->attr.intrinsic
328	      && (!sym->attr.function || sym->result == sym))
329	    gfc_set_default_type (sym, 1, sym->ns);
330	}
331
332      as = sym->ts.type == BT_CLASS && sym->attr.class_ok
333	   ? CLASS_DATA (sym)->as : sym->as;
334
335      saved_specification_expr = specification_expr;
336      specification_expr = true;
337      gfc_resolve_array_spec (as, 0);
338      specification_expr = saved_specification_expr;
339
340      /* We can't tell if an array with dimension (:) is assumed or deferred
341	 shape until we know if it has the pointer or allocatable attributes.
342      */
343      if (as && as->rank > 0 && as->type == AS_DEFERRED
344	  && ((sym->ts.type != BT_CLASS
345	       && !(sym->attr.pointer || sym->attr.allocatable))
346              || (sym->ts.type == BT_CLASS
347		  && !(CLASS_DATA (sym)->attr.class_pointer
348		       || CLASS_DATA (sym)->attr.allocatable)))
349	  && sym->attr.flavor != FL_PROCEDURE)
350	{
351	  as->type = AS_ASSUMED_SHAPE;
352	  for (i = 0; i < as->rank; i++)
353	    as->lower[i] = gfc_get_int_expr (gfc_default_integer_kind, NULL, 1);
354	}
355
356      if ((as && as->rank > 0 && as->type == AS_ASSUMED_SHAPE)
357	  || (as && as->type == AS_ASSUMED_RANK)
358	  || sym->attr.pointer || sym->attr.allocatable || sym->attr.target
359	  || (sym->ts.type == BT_CLASS && sym->attr.class_ok
360	      && (CLASS_DATA (sym)->attr.class_pointer
361		  || CLASS_DATA (sym)->attr.allocatable
362		  || CLASS_DATA (sym)->attr.target))
363	  || sym->attr.optional)
364	{
365	  proc->attr.always_explicit = 1;
366	  if (proc->result)
367	    proc->result->attr.always_explicit = 1;
368	}
369
370      /* If the flavor is unknown at this point, it has to be a variable.
371	 A procedure specification would have already set the type.  */
372
373      if (sym->attr.flavor == FL_UNKNOWN)
374	gfc_add_flavor (&sym->attr, FL_VARIABLE, sym->name, &sym->declared_at);
375
376      if (gfc_pure (proc))
377	{
378	  if (sym->attr.flavor == FL_PROCEDURE)
379	    {
380	      /* F08:C1279.  */
381	      if (!gfc_pure (sym))
382		{
383		  gfc_error ("Dummy procedure %qs of PURE procedure at %L must "
384			    "also be PURE", sym->name, &sym->declared_at);
385		  continue;
386		}
387	    }
388	  else if (!sym->attr.pointer)
389	    {
390	      if (proc->attr.function && sym->attr.intent != INTENT_IN)
391		{
392		  if (sym->attr.value)
393		    gfc_notify_std (GFC_STD_F2008, "Argument %qs"
394				    " of pure function %qs at %L with VALUE "
395				    "attribute but without INTENT(IN)",
396				    sym->name, proc->name, &sym->declared_at);
397		  else
398		    gfc_error ("Argument %qs of pure function %qs at %L must "
399			       "be INTENT(IN) or VALUE", sym->name, proc->name,
400			       &sym->declared_at);
401		}
402
403	      if (proc->attr.subroutine && sym->attr.intent == INTENT_UNKNOWN)
404		{
405		  if (sym->attr.value)
406		    gfc_notify_std (GFC_STD_F2008, "Argument %qs"
407				    " of pure subroutine %qs at %L with VALUE "
408				    "attribute but without INTENT", sym->name,
409				    proc->name, &sym->declared_at);
410		  else
411		    gfc_error ("Argument %qs of pure subroutine %qs at %L "
412			       "must have its INTENT specified or have the "
413			       "VALUE attribute", sym->name, proc->name,
414			       &sym->declared_at);
415		}
416	    }
417
418	  /* F08:C1278a.  */
419	  if (sym->ts.type == BT_CLASS && sym->attr.intent == INTENT_OUT)
420	    {
421	      gfc_error ("INTENT(OUT) argument '%s' of pure procedure %qs at %L"
422			 " may not be polymorphic", sym->name, proc->name,
423			 &sym->declared_at);
424	      continue;
425	    }
426	}
427
428      if (proc->attr.implicit_pure)
429	{
430	  if (sym->attr.flavor == FL_PROCEDURE)
431	    {
432	      if (!gfc_pure (sym))
433		proc->attr.implicit_pure = 0;
434	    }
435	  else if (!sym->attr.pointer)
436	    {
437	      if (proc->attr.function && sym->attr.intent != INTENT_IN
438		  && !sym->value)
439		proc->attr.implicit_pure = 0;
440
441	      if (proc->attr.subroutine && sym->attr.intent == INTENT_UNKNOWN
442		  && !sym->value)
443		proc->attr.implicit_pure = 0;
444	    }
445	}
446
447      if (gfc_elemental (proc))
448	{
449	  /* F08:C1289.  */
450	  if (sym->attr.codimension
451	      || (sym->ts.type == BT_CLASS && CLASS_DATA (sym)
452		  && CLASS_DATA (sym)->attr.codimension))
453	    {
454	      gfc_error ("Coarray dummy argument %qs at %L to elemental "
455			 "procedure", sym->name, &sym->declared_at);
456	      continue;
457	    }
458
459	  if (sym->as || (sym->ts.type == BT_CLASS && CLASS_DATA (sym)
460			  && CLASS_DATA (sym)->as))
461	    {
462	      gfc_error ("Argument %qs of elemental procedure at %L must "
463			 "be scalar", sym->name, &sym->declared_at);
464	      continue;
465	    }
466
467	  if (sym->attr.allocatable
468	      || (sym->ts.type == BT_CLASS && CLASS_DATA (sym)
469		  && CLASS_DATA (sym)->attr.allocatable))
470	    {
471	      gfc_error ("Argument %qs of elemental procedure at %L cannot "
472			 "have the ALLOCATABLE attribute", sym->name,
473			 &sym->declared_at);
474	      continue;
475	    }
476
477	  if (sym->attr.pointer
478	      || (sym->ts.type == BT_CLASS && CLASS_DATA (sym)
479		  && CLASS_DATA (sym)->attr.class_pointer))
480	    {
481	      gfc_error ("Argument %qs of elemental procedure at %L cannot "
482			 "have the POINTER attribute", sym->name,
483			 &sym->declared_at);
484	      continue;
485	    }
486
487	  if (sym->attr.flavor == FL_PROCEDURE)
488	    {
489	      gfc_error ("Dummy procedure %qs not allowed in elemental "
490			 "procedure %qs at %L", sym->name, proc->name,
491			 &sym->declared_at);
492	      continue;
493	    }
494
495	  /* Fortran 2008 Corrigendum 1, C1290a.  */
496	  if (sym->attr.intent == INTENT_UNKNOWN && !sym->attr.value)
497	    {
498	      gfc_error ("Argument %qs of elemental procedure %qs at %L must "
499			 "have its INTENT specified or have the VALUE "
500			 "attribute", sym->name, proc->name,
501			 &sym->declared_at);
502	      continue;
503	    }
504	}
505
506      /* Each dummy shall be specified to be scalar.  */
507      if (proc->attr.proc == PROC_ST_FUNCTION)
508	{
509	  if (sym->as != NULL)
510	    {
511	      gfc_error ("Argument %qs of statement function at %L must "
512			 "be scalar", sym->name, &sym->declared_at);
513	      continue;
514	    }
515
516	  if (sym->ts.type == BT_CHARACTER)
517	    {
518	      gfc_charlen *cl = sym->ts.u.cl;
519	      if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
520		{
521		  gfc_error ("Character-valued argument %qs of statement "
522			     "function at %L must have constant length",
523			     sym->name, &sym->declared_at);
524		  continue;
525		}
526	    }
527	}
528    }
529  formal_arg_flag = 0;
530}
531
532
533/* Work function called when searching for symbols that have argument lists
534   associated with them.  */
535
536static void
537find_arglists (gfc_symbol *sym)
538{
539  if (sym->attr.if_source == IFSRC_UNKNOWN || sym->ns != gfc_current_ns
540      || sym->attr.flavor == FL_DERIVED || sym->attr.intrinsic)
541    return;
542
543  resolve_formal_arglist (sym);
544}
545
546
547/* Given a namespace, resolve all formal argument lists within the namespace.
548 */
549
550static void
551resolve_formal_arglists (gfc_namespace *ns)
552{
553  if (ns == NULL)
554    return;
555
556  gfc_traverse_ns (ns, find_arglists);
557}
558
559
560static void
561resolve_contained_fntype (gfc_symbol *sym, gfc_namespace *ns)
562{
563  bool t;
564
565  /* If this namespace is not a function or an entry master function,
566     ignore it.  */
567  if (! sym || !(sym->attr.function || sym->attr.flavor == FL_VARIABLE)
568      || sym->attr.entry_master)
569    return;
570
571  /* Try to find out of what the return type is.  */
572  if (sym->result->ts.type == BT_UNKNOWN && sym->result->ts.interface == NULL)
573    {
574      t = gfc_set_default_type (sym->result, 0, ns);
575
576      if (!t && !sym->result->attr.untyped)
577	{
578	  if (sym->result == sym)
579	    gfc_error ("Contained function %qs at %L has no IMPLICIT type",
580		       sym->name, &sym->declared_at);
581	  else if (!sym->result->attr.proc_pointer)
582	    gfc_error ("Result %qs of contained function %qs at %L has "
583		       "no IMPLICIT type", sym->result->name, sym->name,
584		       &sym->result->declared_at);
585	  sym->result->attr.untyped = 1;
586	}
587    }
588
589  /* Fortran 95 Draft Standard, page 51, Section 5.1.1.5, on the Character
590     type, lists the only ways a character length value of * can be used:
591     dummy arguments of procedures, named constants, and function results
592     in external functions.  Internal function results and results of module
593     procedures are not on this list, ergo, not permitted.  */
594
595  if (sym->result->ts.type == BT_CHARACTER)
596    {
597      gfc_charlen *cl = sym->result->ts.u.cl;
598      if ((!cl || !cl->length) && !sym->result->ts.deferred)
599	{
600	  /* See if this is a module-procedure and adapt error message
601	     accordingly.  */
602	  bool module_proc;
603	  gcc_assert (ns->parent && ns->parent->proc_name);
604	  module_proc = (ns->parent->proc_name->attr.flavor == FL_MODULE);
605
606	  gfc_error ("Character-valued %s %qs at %L must not be"
607		     " assumed length",
608		     module_proc ? _("module procedure")
609				 : _("internal function"),
610		     sym->name, &sym->declared_at);
611	}
612    }
613}
614
615
616/* Add NEW_ARGS to the formal argument list of PROC, taking care not to
617   introduce duplicates.  */
618
619static void
620merge_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
621{
622  gfc_formal_arglist *f, *new_arglist;
623  gfc_symbol *new_sym;
624
625  for (; new_args != NULL; new_args = new_args->next)
626    {
627      new_sym = new_args->sym;
628      /* See if this arg is already in the formal argument list.  */
629      for (f = proc->formal; f; f = f->next)
630	{
631	  if (new_sym == f->sym)
632	    break;
633	}
634
635      if (f)
636	continue;
637
638      /* Add a new argument.  Argument order is not important.  */
639      new_arglist = gfc_get_formal_arglist ();
640      new_arglist->sym = new_sym;
641      new_arglist->next = proc->formal;
642      proc->formal  = new_arglist;
643    }
644}
645
646
647/* Flag the arguments that are not present in all entries.  */
648
649static void
650check_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
651{
652  gfc_formal_arglist *f, *head;
653  head = new_args;
654
655  for (f = proc->formal; f; f = f->next)
656    {
657      if (f->sym == NULL)
658	continue;
659
660      for (new_args = head; new_args; new_args = new_args->next)
661	{
662	  if (new_args->sym == f->sym)
663	    break;
664	}
665
666      if (new_args)
667	continue;
668
669      f->sym->attr.not_always_present = 1;
670    }
671}
672
673
674/* Resolve alternate entry points.  If a symbol has multiple entry points we
675   create a new master symbol for the main routine, and turn the existing
676   symbol into an entry point.  */
677
678static void
679resolve_entries (gfc_namespace *ns)
680{
681  gfc_namespace *old_ns;
682  gfc_code *c;
683  gfc_symbol *proc;
684  gfc_entry_list *el;
685  char name[GFC_MAX_SYMBOL_LEN + 1];
686  static int master_count = 0;
687
688  if (ns->proc_name == NULL)
689    return;
690
691  /* No need to do anything if this procedure doesn't have alternate entry
692     points.  */
693  if (!ns->entries)
694    return;
695
696  /* We may already have resolved alternate entry points.  */
697  if (ns->proc_name->attr.entry_master)
698    return;
699
700  /* If this isn't a procedure something has gone horribly wrong.  */
701  gcc_assert (ns->proc_name->attr.flavor == FL_PROCEDURE);
702
703  /* Remember the current namespace.  */
704  old_ns = gfc_current_ns;
705
706  gfc_current_ns = ns;
707
708  /* Add the main entry point to the list of entry points.  */
709  el = gfc_get_entry_list ();
710  el->sym = ns->proc_name;
711  el->id = 0;
712  el->next = ns->entries;
713  ns->entries = el;
714  ns->proc_name->attr.entry = 1;
715
716  /* If it is a module function, it needs to be in the right namespace
717     so that gfc_get_fake_result_decl can gather up the results. The
718     need for this arose in get_proc_name, where these beasts were
719     left in their own namespace, to keep prior references linked to
720     the entry declaration.*/
721  if (ns->proc_name->attr.function
722      && ns->parent && ns->parent->proc_name->attr.flavor == FL_MODULE)
723    el->sym->ns = ns;
724
725  /* Do the same for entries where the master is not a module
726     procedure.  These are retained in the module namespace because
727     of the module procedure declaration.  */
728  for (el = el->next; el; el = el->next)
729    if (el->sym->ns->proc_name->attr.flavor == FL_MODULE
730	  && el->sym->attr.mod_proc)
731      el->sym->ns = ns;
732  el = ns->entries;
733
734  /* Add an entry statement for it.  */
735  c = gfc_get_code (EXEC_ENTRY);
736  c->ext.entry = el;
737  c->next = ns->code;
738  ns->code = c;
739
740  /* Create a new symbol for the master function.  */
741  /* Give the internal function a unique name (within this file).
742     Also include the function name so the user has some hope of figuring
743     out what is going on.  */
744  snprintf (name, GFC_MAX_SYMBOL_LEN, "master.%d.%s",
745	    master_count++, ns->proc_name->name);
746  gfc_get_ha_symbol (name, &proc);
747  gcc_assert (proc != NULL);
748
749  gfc_add_procedure (&proc->attr, PROC_INTERNAL, proc->name, NULL);
750  if (ns->proc_name->attr.subroutine)
751    gfc_add_subroutine (&proc->attr, proc->name, NULL);
752  else
753    {
754      gfc_symbol *sym;
755      gfc_typespec *ts, *fts;
756      gfc_array_spec *as, *fas;
757      gfc_add_function (&proc->attr, proc->name, NULL);
758      proc->result = proc;
759      fas = ns->entries->sym->as;
760      fas = fas ? fas : ns->entries->sym->result->as;
761      fts = &ns->entries->sym->result->ts;
762      if (fts->type == BT_UNKNOWN)
763	fts = gfc_get_default_type (ns->entries->sym->result->name, NULL);
764      for (el = ns->entries->next; el; el = el->next)
765	{
766	  ts = &el->sym->result->ts;
767	  as = el->sym->as;
768	  as = as ? as : el->sym->result->as;
769	  if (ts->type == BT_UNKNOWN)
770	    ts = gfc_get_default_type (el->sym->result->name, NULL);
771
772	  if (! gfc_compare_types (ts, fts)
773	      || (el->sym->result->attr.dimension
774		  != ns->entries->sym->result->attr.dimension)
775	      || (el->sym->result->attr.pointer
776		  != ns->entries->sym->result->attr.pointer))
777	    break;
778	  else if (as && fas && ns->entries->sym->result != el->sym->result
779		      && gfc_compare_array_spec (as, fas) == 0)
780	    gfc_error ("Function %s at %L has entries with mismatched "
781		       "array specifications", ns->entries->sym->name,
782		       &ns->entries->sym->declared_at);
783	  /* The characteristics need to match and thus both need to have
784	     the same string length, i.e. both len=*, or both len=4.
785	     Having both len=<variable> is also possible, but difficult to
786	     check at compile time.  */
787	  else if (ts->type == BT_CHARACTER && ts->u.cl && fts->u.cl
788		   && (((ts->u.cl->length && !fts->u.cl->length)
789			||(!ts->u.cl->length && fts->u.cl->length))
790		       || (ts->u.cl->length
791			   && ts->u.cl->length->expr_type
792			      != fts->u.cl->length->expr_type)
793		       || (ts->u.cl->length
794			   && ts->u.cl->length->expr_type == EXPR_CONSTANT
795		           && mpz_cmp (ts->u.cl->length->value.integer,
796				       fts->u.cl->length->value.integer) != 0)))
797	    gfc_notify_std (GFC_STD_GNU, "Function %s at %L with "
798			    "entries returning variables of different "
799			    "string lengths", ns->entries->sym->name,
800			    &ns->entries->sym->declared_at);
801	}
802
803      if (el == NULL)
804	{
805	  sym = ns->entries->sym->result;
806	  /* All result types the same.  */
807	  proc->ts = *fts;
808	  if (sym->attr.dimension)
809	    gfc_set_array_spec (proc, gfc_copy_array_spec (sym->as), NULL);
810	  if (sym->attr.pointer)
811	    gfc_add_pointer (&proc->attr, NULL);
812	}
813      else
814	{
815	  /* Otherwise the result will be passed through a union by
816	     reference.  */
817	  proc->attr.mixed_entry_master = 1;
818	  for (el = ns->entries; el; el = el->next)
819	    {
820	      sym = el->sym->result;
821	      if (sym->attr.dimension)
822		{
823		  if (el == ns->entries)
824		    gfc_error ("FUNCTION result %s can't be an array in "
825			       "FUNCTION %s at %L", sym->name,
826			       ns->entries->sym->name, &sym->declared_at);
827		  else
828		    gfc_error ("ENTRY result %s can't be an array in "
829			       "FUNCTION %s at %L", sym->name,
830			       ns->entries->sym->name, &sym->declared_at);
831		}
832	      else if (sym->attr.pointer)
833		{
834		  if (el == ns->entries)
835		    gfc_error ("FUNCTION result %s can't be a POINTER in "
836			       "FUNCTION %s at %L", sym->name,
837			       ns->entries->sym->name, &sym->declared_at);
838		  else
839		    gfc_error ("ENTRY result %s can't be a POINTER in "
840			       "FUNCTION %s at %L", sym->name,
841			       ns->entries->sym->name, &sym->declared_at);
842		}
843	      else
844		{
845		  ts = &sym->ts;
846		  if (ts->type == BT_UNKNOWN)
847		    ts = gfc_get_default_type (sym->name, NULL);
848		  switch (ts->type)
849		    {
850		    case BT_INTEGER:
851		      if (ts->kind == gfc_default_integer_kind)
852			sym = NULL;
853		      break;
854		    case BT_REAL:
855		      if (ts->kind == gfc_default_real_kind
856			  || ts->kind == gfc_default_double_kind)
857			sym = NULL;
858		      break;
859		    case BT_COMPLEX:
860		      if (ts->kind == gfc_default_complex_kind)
861			sym = NULL;
862		      break;
863		    case BT_LOGICAL:
864		      if (ts->kind == gfc_default_logical_kind)
865			sym = NULL;
866		      break;
867		    case BT_UNKNOWN:
868		      /* We will issue error elsewhere.  */
869		      sym = NULL;
870		      break;
871		    default:
872		      break;
873		    }
874		  if (sym)
875		    {
876		      if (el == ns->entries)
877			gfc_error ("FUNCTION result %s can't be of type %s "
878				   "in FUNCTION %s at %L", sym->name,
879				   gfc_typename (ts), ns->entries->sym->name,
880				   &sym->declared_at);
881		      else
882			gfc_error ("ENTRY result %s can't be of type %s "
883				   "in FUNCTION %s at %L", sym->name,
884				   gfc_typename (ts), ns->entries->sym->name,
885				   &sym->declared_at);
886		    }
887		}
888	    }
889	}
890    }
891  proc->attr.access = ACCESS_PRIVATE;
892  proc->attr.entry_master = 1;
893
894  /* Merge all the entry point arguments.  */
895  for (el = ns->entries; el; el = el->next)
896    merge_argument_lists (proc, el->sym->formal);
897
898  /* Check the master formal arguments for any that are not
899     present in all entry points.  */
900  for (el = ns->entries; el; el = el->next)
901    check_argument_lists (proc, el->sym->formal);
902
903  /* Use the master function for the function body.  */
904  ns->proc_name = proc;
905
906  /* Finalize the new symbols.  */
907  gfc_commit_symbols ();
908
909  /* Restore the original namespace.  */
910  gfc_current_ns = old_ns;
911}
912
913
914/* Resolve common variables.  */
915static void
916resolve_common_vars (gfc_symbol *sym, bool named_common)
917{
918  gfc_symbol *csym = sym;
919
920  for (; csym; csym = csym->common_next)
921    {
922      if (csym->value || csym->attr.data)
923	{
924	  if (!csym->ns->is_block_data)
925	    gfc_notify_std (GFC_STD_GNU, "Variable %qs at %L is in COMMON "
926			    "but only in BLOCK DATA initialization is "
927			    "allowed", csym->name, &csym->declared_at);
928	  else if (!named_common)
929	    gfc_notify_std (GFC_STD_GNU, "Initialized variable %qs at %L is "
930			    "in a blank COMMON but initialization is only "
931			    "allowed in named common blocks", csym->name,
932			    &csym->declared_at);
933	}
934
935      if (UNLIMITED_POLY (csym))
936	gfc_error_now ("%qs in cannot appear in COMMON at %L "
937		       "[F2008:C5100]", csym->name, &csym->declared_at);
938
939      if (csym->ts.type != BT_DERIVED)
940	continue;
941
942      if (!(csym->ts.u.derived->attr.sequence
943	    || csym->ts.u.derived->attr.is_bind_c))
944	gfc_error_now ("Derived type variable %qs in COMMON at %L "
945		       "has neither the SEQUENCE nor the BIND(C) "
946		       "attribute", csym->name, &csym->declared_at);
947      if (csym->ts.u.derived->attr.alloc_comp)
948	gfc_error_now ("Derived type variable %qs in COMMON at %L "
949		       "has an ultimate component that is "
950		       "allocatable", csym->name, &csym->declared_at);
951      if (gfc_has_default_initializer (csym->ts.u.derived))
952	gfc_error_now ("Derived type variable %qs in COMMON at %L "
953		       "may not have default initializer", csym->name,
954		       &csym->declared_at);
955
956      if (csym->attr.flavor == FL_UNKNOWN && !csym->attr.proc_pointer)
957	gfc_add_flavor (&csym->attr, FL_VARIABLE, csym->name, &csym->declared_at);
958    }
959}
960
961/* Resolve common blocks.  */
962static void
963resolve_common_blocks (gfc_symtree *common_root)
964{
965  gfc_symbol *sym;
966  gfc_gsymbol * gsym;
967
968  if (common_root == NULL)
969    return;
970
971  if (common_root->left)
972    resolve_common_blocks (common_root->left);
973  if (common_root->right)
974    resolve_common_blocks (common_root->right);
975
976  resolve_common_vars (common_root->n.common->head, true);
977
978  /* The common name is a global name - in Fortran 2003 also if it has a
979     C binding name, since Fortran 2008 only the C binding name is a global
980     identifier.  */
981  if (!common_root->n.common->binding_label
982      || gfc_notification_std (GFC_STD_F2008))
983    {
984      gsym = gfc_find_gsymbol (gfc_gsym_root,
985			       common_root->n.common->name);
986
987      if (gsym && gfc_notification_std (GFC_STD_F2008)
988	  && gsym->type == GSYM_COMMON
989	  && ((common_root->n.common->binding_label
990	       && (!gsym->binding_label
991		   || strcmp (common_root->n.common->binding_label,
992			      gsym->binding_label) != 0))
993	      || (!common_root->n.common->binding_label
994		  && gsym->binding_label)))
995	{
996	  gfc_error_1 ("In Fortran 2003 COMMON '%s' block at %L is a global "
997		     "identifier and must thus have the same binding name "
998		     "as the same-named COMMON block at %L: %s vs %s",
999		     common_root->n.common->name, &common_root->n.common->where,
1000		     &gsym->where,
1001		     common_root->n.common->binding_label
1002		     ? common_root->n.common->binding_label : "(blank)",
1003		     gsym->binding_label ? gsym->binding_label : "(blank)");
1004	  return;
1005	}
1006
1007      if (gsym && gsym->type != GSYM_COMMON
1008	  && !common_root->n.common->binding_label)
1009	{
1010	  gfc_error_1 ("COMMON block '%s' at %L uses the same global identifier "
1011		     "as entity at %L",
1012		     common_root->n.common->name, &common_root->n.common->where,
1013		     &gsym->where);
1014	  return;
1015	}
1016      if (gsym && gsym->type != GSYM_COMMON)
1017	{
1018	  gfc_error_1 ("Fortran 2008: COMMON block '%s' with binding label at "
1019		     "%L sharing the identifier with global non-COMMON-block "
1020		     "entity at %L", common_root->n.common->name,
1021		     &common_root->n.common->where, &gsym->where);
1022	  return;
1023	}
1024      if (!gsym)
1025	{
1026	  gsym = gfc_get_gsymbol (common_root->n.common->name);
1027	  gsym->type = GSYM_COMMON;
1028	  gsym->where = common_root->n.common->where;
1029	  gsym->defined = 1;
1030	}
1031      gsym->used = 1;
1032    }
1033
1034  if (common_root->n.common->binding_label)
1035    {
1036      gsym = gfc_find_gsymbol (gfc_gsym_root,
1037			       common_root->n.common->binding_label);
1038      if (gsym && gsym->type != GSYM_COMMON)
1039	{
1040	  gfc_error_1 ("COMMON block at %L with binding label %s uses the same "
1041		     "global identifier as entity at %L",
1042		     &common_root->n.common->where,
1043		     common_root->n.common->binding_label, &gsym->where);
1044	  return;
1045	}
1046      if (!gsym)
1047	{
1048	  gsym = gfc_get_gsymbol (common_root->n.common->binding_label);
1049	  gsym->type = GSYM_COMMON;
1050	  gsym->where = common_root->n.common->where;
1051	  gsym->defined = 1;
1052	}
1053      gsym->used = 1;
1054    }
1055
1056  gfc_find_symbol (common_root->name, gfc_current_ns, 0, &sym);
1057  if (sym == NULL)
1058    return;
1059
1060  if (sym->attr.flavor == FL_PARAMETER)
1061    gfc_error_1 ("COMMON block '%s' at %L is used as PARAMETER at %L",
1062	       sym->name, &common_root->n.common->where, &sym->declared_at);
1063
1064  if (sym->attr.external)
1065    gfc_error ("COMMON block %qs at %L can not have the EXTERNAL attribute",
1066	       sym->name, &common_root->n.common->where);
1067
1068  if (sym->attr.intrinsic)
1069    gfc_error ("COMMON block %qs at %L is also an intrinsic procedure",
1070	       sym->name, &common_root->n.common->where);
1071  else if (sym->attr.result
1072	   || gfc_is_function_return_value (sym, gfc_current_ns))
1073    gfc_notify_std (GFC_STD_F2003, "COMMON block %qs at %L "
1074		    "that is also a function result", sym->name,
1075		    &common_root->n.common->where);
1076  else if (sym->attr.flavor == FL_PROCEDURE && sym->attr.proc != PROC_INTERNAL
1077	   && sym->attr.proc != PROC_ST_FUNCTION)
1078    gfc_notify_std (GFC_STD_F2003, "COMMON block %qs at %L "
1079		    "that is also a global procedure", sym->name,
1080		    &common_root->n.common->where);
1081}
1082
1083
1084/* Resolve contained function types.  Because contained functions can call one
1085   another, they have to be worked out before any of the contained procedures
1086   can be resolved.
1087
1088   The good news is that if a function doesn't already have a type, the only
1089   way it can get one is through an IMPLICIT type or a RESULT variable, because
1090   by definition contained functions are contained namespace they're contained
1091   in, not in a sibling or parent namespace.  */
1092
1093static void
1094resolve_contained_functions (gfc_namespace *ns)
1095{
1096  gfc_namespace *child;
1097  gfc_entry_list *el;
1098
1099  resolve_formal_arglists (ns);
1100
1101  for (child = ns->contained; child; child = child->sibling)
1102    {
1103      /* Resolve alternate entry points first.  */
1104      resolve_entries (child);
1105
1106      /* Then check function return types.  */
1107      resolve_contained_fntype (child->proc_name, child);
1108      for (el = child->entries; el; el = el->next)
1109	resolve_contained_fntype (el->sym, child);
1110    }
1111}
1112
1113
1114static bool resolve_fl_derived0 (gfc_symbol *sym);
1115
1116
1117/* Resolve all of the elements of a structure constructor and make sure that
1118   the types are correct. The 'init' flag indicates that the given
1119   constructor is an initializer.  */
1120
1121static bool
1122resolve_structure_cons (gfc_expr *expr, int init)
1123{
1124  gfc_constructor *cons;
1125  gfc_component *comp;
1126  bool t;
1127  symbol_attribute a;
1128
1129  t = true;
1130
1131  if (expr->ts.type == BT_DERIVED)
1132    resolve_fl_derived0 (expr->ts.u.derived);
1133
1134  cons = gfc_constructor_first (expr->value.constructor);
1135
1136  /* A constructor may have references if it is the result of substituting a
1137     parameter variable.  In this case we just pull out the component we
1138     want.  */
1139  if (expr->ref)
1140    comp = expr->ref->u.c.sym->components;
1141  else
1142    comp = expr->ts.u.derived->components;
1143
1144  for (; comp && cons; comp = comp->next, cons = gfc_constructor_next (cons))
1145    {
1146      int rank;
1147
1148      if (!cons->expr)
1149	continue;
1150
1151      if (!gfc_resolve_expr (cons->expr))
1152	{
1153	  t = false;
1154	  continue;
1155	}
1156
1157      rank = comp->as ? comp->as->rank : 0;
1158      if (comp->ts.type == BT_CLASS && CLASS_DATA (comp)->as)
1159 	rank = CLASS_DATA (comp)->as->rank;
1160
1161      if (cons->expr->expr_type != EXPR_NULL && rank != cons->expr->rank
1162	  && (comp->attr.allocatable || cons->expr->rank))
1163	{
1164	  gfc_error ("The rank of the element in the structure "
1165		     "constructor at %L does not match that of the "
1166		     "component (%d/%d)", &cons->expr->where,
1167		     cons->expr->rank, rank);
1168	  t = false;
1169	}
1170
1171      /* If we don't have the right type, try to convert it.  */
1172
1173      if (!comp->attr.proc_pointer &&
1174	  !gfc_compare_types (&cons->expr->ts, &comp->ts))
1175	{
1176	  if (strcmp (comp->name, "_extends") == 0)
1177	    {
1178	      /* Can afford to be brutal with the _extends initializer.
1179		 The derived type can get lost because it is PRIVATE
1180		 but it is not usage constrained by the standard.  */
1181	      cons->expr->ts = comp->ts;
1182	    }
1183	  else if (comp->attr.pointer && cons->expr->ts.type != BT_UNKNOWN)
1184	    {
1185	      gfc_error ("The element in the structure constructor at %L, "
1186			 "for pointer component %qs, is %s but should be %s",
1187			 &cons->expr->where, comp->name,
1188			 gfc_basic_typename (cons->expr->ts.type),
1189			 gfc_basic_typename (comp->ts.type));
1190	      t = false;
1191	    }
1192	  else
1193	    {
1194	      bool t2 = gfc_convert_type (cons->expr, &comp->ts, 1);
1195	      if (t)
1196		t = t2;
1197	    }
1198	}
1199
1200      /* For strings, the length of the constructor should be the same as
1201	 the one of the structure, ensure this if the lengths are known at
1202 	 compile time and when we are dealing with PARAMETER or structure
1203	 constructors.  */
1204      if (cons->expr->ts.type == BT_CHARACTER && comp->ts.u.cl
1205	  && comp->ts.u.cl->length
1206	  && comp->ts.u.cl->length->expr_type == EXPR_CONSTANT
1207	  && cons->expr->ts.u.cl && cons->expr->ts.u.cl->length
1208	  && cons->expr->ts.u.cl->length->expr_type == EXPR_CONSTANT
1209	  && cons->expr->rank != 0
1210	  && mpz_cmp (cons->expr->ts.u.cl->length->value.integer,
1211		      comp->ts.u.cl->length->value.integer) != 0)
1212	{
1213	  if (cons->expr->expr_type == EXPR_VARIABLE
1214	      && cons->expr->symtree->n.sym->attr.flavor == FL_PARAMETER)
1215	    {
1216	      /* Wrap the parameter in an array constructor (EXPR_ARRAY)
1217		 to make use of the gfc_resolve_character_array_constructor
1218		 machinery.  The expression is later simplified away to
1219		 an array of string literals.  */
1220	      gfc_expr *para = cons->expr;
1221	      cons->expr = gfc_get_expr ();
1222	      cons->expr->ts = para->ts;
1223	      cons->expr->where = para->where;
1224	      cons->expr->expr_type = EXPR_ARRAY;
1225	      cons->expr->rank = para->rank;
1226	      cons->expr->shape = gfc_copy_shape (para->shape, para->rank);
1227	      gfc_constructor_append_expr (&cons->expr->value.constructor,
1228					   para, &cons->expr->where);
1229	    }
1230	  if (cons->expr->expr_type == EXPR_ARRAY)
1231	    {
1232	      gfc_constructor *p;
1233	      p = gfc_constructor_first (cons->expr->value.constructor);
1234	      if (cons->expr->ts.u.cl != p->expr->ts.u.cl)
1235		{
1236		  gfc_charlen *cl, *cl2;
1237
1238		  cl2 = NULL;
1239		  for (cl = gfc_current_ns->cl_list; cl; cl = cl->next)
1240		    {
1241		      if (cl == cons->expr->ts.u.cl)
1242			break;
1243		      cl2 = cl;
1244		    }
1245
1246		  gcc_assert (cl);
1247
1248		  if (cl2)
1249		    cl2->next = cl->next;
1250
1251		  gfc_free_expr (cl->length);
1252		  free (cl);
1253		}
1254
1255	      cons->expr->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
1256	      cons->expr->ts.u.cl->length_from_typespec = true;
1257	      cons->expr->ts.u.cl->length = gfc_copy_expr (comp->ts.u.cl->length);
1258	      gfc_resolve_character_array_constructor (cons->expr);
1259	    }
1260	}
1261
1262      if (cons->expr->expr_type == EXPR_NULL
1263	  && !(comp->attr.pointer || comp->attr.allocatable
1264	       || comp->attr.proc_pointer || comp->ts.f90_type == BT_VOID
1265	       || (comp->ts.type == BT_CLASS
1266		   && (CLASS_DATA (comp)->attr.class_pointer
1267		       || CLASS_DATA (comp)->attr.allocatable))))
1268	{
1269	  t = false;
1270	  gfc_error ("The NULL in the structure constructor at %L is "
1271		     "being applied to component %qs, which is neither "
1272		     "a POINTER nor ALLOCATABLE", &cons->expr->where,
1273		     comp->name);
1274	}
1275
1276      if (comp->attr.proc_pointer && comp->ts.interface)
1277	{
1278	  /* Check procedure pointer interface.  */
1279	  gfc_symbol *s2 = NULL;
1280	  gfc_component *c2;
1281	  const char *name;
1282	  char err[200];
1283
1284	  c2 = gfc_get_proc_ptr_comp (cons->expr);
1285	  if (c2)
1286	    {
1287	      s2 = c2->ts.interface;
1288	      name = c2->name;
1289	    }
1290	  else if (cons->expr->expr_type == EXPR_FUNCTION)
1291	    {
1292	      s2 = cons->expr->symtree->n.sym->result;
1293	      name = cons->expr->symtree->n.sym->result->name;
1294	    }
1295	  else if (cons->expr->expr_type != EXPR_NULL)
1296	    {
1297	      s2 = cons->expr->symtree->n.sym;
1298	      name = cons->expr->symtree->n.sym->name;
1299	    }
1300
1301	  if (s2 && !gfc_compare_interfaces (comp->ts.interface, s2, name, 0, 1,
1302					     err, sizeof (err), NULL, NULL))
1303	    {
1304	      gfc_error ("Interface mismatch for procedure-pointer component "
1305			 "%qs in structure constructor at %L: %s",
1306			 comp->name, &cons->expr->where, err);
1307	      return false;
1308	    }
1309	}
1310
1311      if (!comp->attr.pointer || comp->attr.proc_pointer
1312	  || cons->expr->expr_type == EXPR_NULL)
1313	continue;
1314
1315      a = gfc_expr_attr (cons->expr);
1316
1317      if (!a.pointer && !a.target)
1318	{
1319	  t = false;
1320	  gfc_error ("The element in the structure constructor at %L, "
1321		     "for pointer component %qs should be a POINTER or "
1322		     "a TARGET", &cons->expr->where, comp->name);
1323	}
1324
1325      if (init)
1326	{
1327	  /* F08:C461. Additional checks for pointer initialization.  */
1328	  if (a.allocatable)
1329	    {
1330	      t = false;
1331	      gfc_error ("Pointer initialization target at %L "
1332			 "must not be ALLOCATABLE ", &cons->expr->where);
1333	    }
1334	  if (!a.save)
1335	    {
1336	      t = false;
1337	      gfc_error ("Pointer initialization target at %L "
1338			 "must have the SAVE attribute", &cons->expr->where);
1339	    }
1340	}
1341
1342      /* F2003, C1272 (3).  */
1343      bool impure = cons->expr->expr_type == EXPR_VARIABLE
1344		    && (gfc_impure_variable (cons->expr->symtree->n.sym)
1345			|| gfc_is_coindexed (cons->expr));
1346      if (impure && gfc_pure (NULL))
1347	{
1348	  t = false;
1349	  gfc_error ("Invalid expression in the structure constructor for "
1350		     "pointer component %qs at %L in PURE procedure",
1351		     comp->name, &cons->expr->where);
1352	}
1353
1354      if (impure)
1355	gfc_unset_implicit_pure (NULL);
1356    }
1357
1358  return t;
1359}
1360
1361
1362/****************** Expression name resolution ******************/
1363
1364/* Returns 0 if a symbol was not declared with a type or
1365   attribute declaration statement, nonzero otherwise.  */
1366
1367static int
1368was_declared (gfc_symbol *sym)
1369{
1370  symbol_attribute a;
1371
1372  a = sym->attr;
1373
1374  if (!a.implicit_type && sym->ts.type != BT_UNKNOWN)
1375    return 1;
1376
1377  if (a.allocatable || a.dimension || a.dummy || a.external || a.intrinsic
1378      || a.optional || a.pointer || a.save || a.target || a.volatile_
1379      || a.value || a.access != ACCESS_UNKNOWN || a.intent != INTENT_UNKNOWN
1380      || a.asynchronous || a.codimension)
1381    return 1;
1382
1383  return 0;
1384}
1385
1386
1387/* Determine if a symbol is generic or not.  */
1388
1389static int
1390generic_sym (gfc_symbol *sym)
1391{
1392  gfc_symbol *s;
1393
1394  if (sym->attr.generic ||
1395      (sym->attr.intrinsic && gfc_generic_intrinsic (sym->name)))
1396    return 1;
1397
1398  if (was_declared (sym) || sym->ns->parent == NULL)
1399    return 0;
1400
1401  gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
1402
1403  if (s != NULL)
1404    {
1405      if (s == sym)
1406	return 0;
1407      else
1408	return generic_sym (s);
1409    }
1410
1411  return 0;
1412}
1413
1414
1415/* Determine if a symbol is specific or not.  */
1416
1417static int
1418specific_sym (gfc_symbol *sym)
1419{
1420  gfc_symbol *s;
1421
1422  if (sym->attr.if_source == IFSRC_IFBODY
1423      || sym->attr.proc == PROC_MODULE
1424      || sym->attr.proc == PROC_INTERNAL
1425      || sym->attr.proc == PROC_ST_FUNCTION
1426      || (sym->attr.intrinsic && gfc_specific_intrinsic (sym->name))
1427      || sym->attr.external)
1428    return 1;
1429
1430  if (was_declared (sym) || sym->ns->parent == NULL)
1431    return 0;
1432
1433  gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
1434
1435  return (s == NULL) ? 0 : specific_sym (s);
1436}
1437
1438
1439/* Figure out if the procedure is specific, generic or unknown.  */
1440
1441typedef enum
1442{ PTYPE_GENERIC = 1, PTYPE_SPECIFIC, PTYPE_UNKNOWN }
1443proc_type;
1444
1445static proc_type
1446procedure_kind (gfc_symbol *sym)
1447{
1448  if (generic_sym (sym))
1449    return PTYPE_GENERIC;
1450
1451  if (specific_sym (sym))
1452    return PTYPE_SPECIFIC;
1453
1454  return PTYPE_UNKNOWN;
1455}
1456
1457/* Check references to assumed size arrays.  The flag need_full_assumed_size
1458   is nonzero when matching actual arguments.  */
1459
1460static int need_full_assumed_size = 0;
1461
1462static bool
1463check_assumed_size_reference (gfc_symbol *sym, gfc_expr *e)
1464{
1465  if (need_full_assumed_size || !(sym->as && sym->as->type == AS_ASSUMED_SIZE))
1466      return false;
1467
1468  /* FIXME: The comparison "e->ref->u.ar.type == AR_FULL" is wrong.
1469     What should it be?  */
1470  if (e->ref && (e->ref->u.ar.end[e->ref->u.ar.as->rank - 1] == NULL)
1471	  && (e->ref->u.ar.as->type == AS_ASSUMED_SIZE)
1472	       && (e->ref->u.ar.type == AR_FULL))
1473    {
1474      gfc_error ("The upper bound in the last dimension must "
1475		 "appear in the reference to the assumed size "
1476		 "array %qs at %L", sym->name, &e->where);
1477      return true;
1478    }
1479  return false;
1480}
1481
1482
1483/* Look for bad assumed size array references in argument expressions
1484  of elemental and array valued intrinsic procedures.  Since this is
1485  called from procedure resolution functions, it only recurses at
1486  operators.  */
1487
1488static bool
1489resolve_assumed_size_actual (gfc_expr *e)
1490{
1491  if (e == NULL)
1492   return false;
1493
1494  switch (e->expr_type)
1495    {
1496    case EXPR_VARIABLE:
1497      if (e->symtree && check_assumed_size_reference (e->symtree->n.sym, e))
1498	return true;
1499      break;
1500
1501    case EXPR_OP:
1502      if (resolve_assumed_size_actual (e->value.op.op1)
1503	  || resolve_assumed_size_actual (e->value.op.op2))
1504	return true;
1505      break;
1506
1507    default:
1508      break;
1509    }
1510  return false;
1511}
1512
1513
1514/* Check a generic procedure, passed as an actual argument, to see if
1515   there is a matching specific name.  If none, it is an error, and if
1516   more than one, the reference is ambiguous.  */
1517static int
1518count_specific_procs (gfc_expr *e)
1519{
1520  int n;
1521  gfc_interface *p;
1522  gfc_symbol *sym;
1523
1524  n = 0;
1525  sym = e->symtree->n.sym;
1526
1527  for (p = sym->generic; p; p = p->next)
1528    if (strcmp (sym->name, p->sym->name) == 0)
1529      {
1530	e->symtree = gfc_find_symtree (p->sym->ns->sym_root,
1531				       sym->name);
1532	n++;
1533      }
1534
1535  if (n > 1)
1536    gfc_error ("%qs at %L is ambiguous", e->symtree->n.sym->name,
1537	       &e->where);
1538
1539  if (n == 0)
1540    gfc_error ("GENERIC procedure %qs is not allowed as an actual "
1541	       "argument at %L", sym->name, &e->where);
1542
1543  return n;
1544}
1545
1546
1547/* See if a call to sym could possibly be a not allowed RECURSION because of
1548   a missing RECURSIVE declaration.  This means that either sym is the current
1549   context itself, or sym is the parent of a contained procedure calling its
1550   non-RECURSIVE containing procedure.
1551   This also works if sym is an ENTRY.  */
1552
1553static bool
1554is_illegal_recursion (gfc_symbol* sym, gfc_namespace* context)
1555{
1556  gfc_symbol* proc_sym;
1557  gfc_symbol* context_proc;
1558  gfc_namespace* real_context;
1559
1560  if (sym->attr.flavor == FL_PROGRAM
1561      || sym->attr.flavor == FL_DERIVED)
1562    return false;
1563
1564  gcc_assert (sym->attr.flavor == FL_PROCEDURE);
1565
1566  /* If we've got an ENTRY, find real procedure.  */
1567  if (sym->attr.entry && sym->ns->entries)
1568    proc_sym = sym->ns->entries->sym;
1569  else
1570    proc_sym = sym;
1571
1572  /* If sym is RECURSIVE, all is well of course.  */
1573  if (proc_sym->attr.recursive || flag_recursive)
1574    return false;
1575
1576  /* Find the context procedure's "real" symbol if it has entries.
1577     We look for a procedure symbol, so recurse on the parents if we don't
1578     find one (like in case of a BLOCK construct).  */
1579  for (real_context = context; ; real_context = real_context->parent)
1580    {
1581      /* We should find something, eventually!  */
1582      gcc_assert (real_context);
1583
1584      context_proc = (real_context->entries ? real_context->entries->sym
1585					    : real_context->proc_name);
1586
1587      /* In some special cases, there may not be a proc_name, like for this
1588	 invalid code:
1589	 real(bad_kind()) function foo () ...
1590	 when checking the call to bad_kind ().
1591	 In these cases, we simply return here and assume that the
1592	 call is ok.  */
1593      if (!context_proc)
1594	return false;
1595
1596      if (context_proc->attr.flavor != FL_LABEL)
1597	break;
1598    }
1599
1600  /* A call from sym's body to itself is recursion, of course.  */
1601  if (context_proc == proc_sym)
1602    return true;
1603
1604  /* The same is true if context is a contained procedure and sym the
1605     containing one.  */
1606  if (context_proc->attr.contained)
1607    {
1608      gfc_symbol* parent_proc;
1609
1610      gcc_assert (context->parent);
1611      parent_proc = (context->parent->entries ? context->parent->entries->sym
1612					      : context->parent->proc_name);
1613
1614      if (parent_proc == proc_sym)
1615	return true;
1616    }
1617
1618  return false;
1619}
1620
1621
1622/* Resolve an intrinsic procedure: Set its function/subroutine attribute,
1623   its typespec and formal argument list.  */
1624
1625bool
1626gfc_resolve_intrinsic (gfc_symbol *sym, locus *loc)
1627{
1628  gfc_intrinsic_sym* isym = NULL;
1629  const char* symstd;
1630
1631  if (sym->formal)
1632    return true;
1633
1634  /* Already resolved.  */
1635  if (sym->from_intmod && sym->ts.type != BT_UNKNOWN)
1636    return true;
1637
1638  /* We already know this one is an intrinsic, so we don't call
1639     gfc_is_intrinsic for full checking but rather use gfc_find_function and
1640     gfc_find_subroutine directly to check whether it is a function or
1641     subroutine.  */
1642
1643  if (sym->intmod_sym_id && sym->attr.subroutine)
1644    {
1645      gfc_isym_id id = gfc_isym_id_by_intmod_sym (sym);
1646      isym = gfc_intrinsic_subroutine_by_id (id);
1647    }
1648  else if (sym->intmod_sym_id)
1649    {
1650      gfc_isym_id id = gfc_isym_id_by_intmod_sym (sym);
1651      isym = gfc_intrinsic_function_by_id (id);
1652    }
1653  else if (!sym->attr.subroutine)
1654    isym = gfc_find_function (sym->name);
1655
1656  if (isym && !sym->attr.subroutine)
1657    {
1658      if (sym->ts.type != BT_UNKNOWN && warn_surprising
1659	  && !sym->attr.implicit_type)
1660	gfc_warning (OPT_Wsurprising,
1661		     "Type specified for intrinsic function %qs at %L is"
1662		      " ignored", sym->name, &sym->declared_at);
1663
1664      if (!sym->attr.function &&
1665	  !gfc_add_function(&sym->attr, sym->name, loc))
1666	return false;
1667
1668      sym->ts = isym->ts;
1669    }
1670  else if (isym || (isym = gfc_find_subroutine (sym->name)))
1671    {
1672      if (sym->ts.type != BT_UNKNOWN && !sym->attr.implicit_type)
1673	{
1674	  gfc_error ("Intrinsic subroutine %qs at %L shall not have a type"
1675		      " specifier", sym->name, &sym->declared_at);
1676	  return false;
1677	}
1678
1679      if (!sym->attr.subroutine &&
1680	  !gfc_add_subroutine(&sym->attr, sym->name, loc))
1681	return false;
1682    }
1683  else
1684    {
1685      gfc_error ("%qs declared INTRINSIC at %L does not exist", sym->name,
1686		 &sym->declared_at);
1687      return false;
1688    }
1689
1690  gfc_copy_formal_args_intr (sym, isym, NULL);
1691
1692  sym->attr.pure = isym->pure;
1693  sym->attr.elemental = isym->elemental;
1694
1695  /* Check it is actually available in the standard settings.  */
1696  if (!gfc_check_intrinsic_standard (isym, &symstd, false, sym->declared_at))
1697    {
1698      gfc_error ("The intrinsic %qs declared INTRINSIC at %L is not "
1699		 "available in the current standard settings but %s. Use "
1700		 "an appropriate %<-std=*%> option or enable "
1701		 "%<-fall-intrinsics%> in order to use it.",
1702		 sym->name, &sym->declared_at, symstd);
1703      return false;
1704    }
1705
1706  return true;
1707}
1708
1709
1710/* Resolve a procedure expression, like passing it to a called procedure or as
1711   RHS for a procedure pointer assignment.  */
1712
1713static bool
1714resolve_procedure_expression (gfc_expr* expr)
1715{
1716  gfc_symbol* sym;
1717
1718  if (expr->expr_type != EXPR_VARIABLE)
1719    return true;
1720  gcc_assert (expr->symtree);
1721
1722  sym = expr->symtree->n.sym;
1723
1724  if (sym->attr.intrinsic)
1725    gfc_resolve_intrinsic (sym, &expr->where);
1726
1727  if (sym->attr.flavor != FL_PROCEDURE
1728      || (sym->attr.function && sym->result == sym))
1729    return true;
1730
1731  /* A non-RECURSIVE procedure that is used as procedure expression within its
1732     own body is in danger of being called recursively.  */
1733  if (is_illegal_recursion (sym, gfc_current_ns))
1734    gfc_warning (0, "Non-RECURSIVE procedure %qs at %L is possibly calling"
1735		 " itself recursively.  Declare it RECURSIVE or use"
1736		 " %<-frecursive%>", sym->name, &expr->where);
1737
1738  return true;
1739}
1740
1741
1742/* Resolve an actual argument list.  Most of the time, this is just
1743   resolving the expressions in the list.
1744   The exception is that we sometimes have to decide whether arguments
1745   that look like procedure arguments are really simple variable
1746   references.  */
1747
1748static bool
1749resolve_actual_arglist (gfc_actual_arglist *arg, procedure_type ptype,
1750			bool no_formal_args)
1751{
1752  gfc_symbol *sym;
1753  gfc_symtree *parent_st;
1754  gfc_expr *e;
1755  gfc_component *comp;
1756  int save_need_full_assumed_size;
1757  bool return_value = false;
1758  bool actual_arg_sav = actual_arg, first_actual_arg_sav = first_actual_arg;
1759
1760  actual_arg = true;
1761  first_actual_arg = true;
1762
1763  for (; arg; arg = arg->next)
1764    {
1765      e = arg->expr;
1766      if (e == NULL)
1767	{
1768	  /* Check the label is a valid branching target.  */
1769	  if (arg->label)
1770	    {
1771	      if (arg->label->defined == ST_LABEL_UNKNOWN)
1772		{
1773		  gfc_error ("Label %d referenced at %L is never defined",
1774			     arg->label->value, &arg->label->where);
1775		  goto cleanup;
1776		}
1777	    }
1778	  first_actual_arg = false;
1779	  continue;
1780	}
1781
1782      if (e->expr_type == EXPR_VARIABLE
1783	    && e->symtree->n.sym->attr.generic
1784	    && no_formal_args
1785	    && count_specific_procs (e) != 1)
1786	goto cleanup;
1787
1788      if (e->ts.type != BT_PROCEDURE)
1789	{
1790	  save_need_full_assumed_size = need_full_assumed_size;
1791	  if (e->expr_type != EXPR_VARIABLE)
1792	    need_full_assumed_size = 0;
1793	  if (!gfc_resolve_expr (e))
1794	    goto cleanup;
1795	  need_full_assumed_size = save_need_full_assumed_size;
1796	  goto argument_list;
1797	}
1798
1799      /* See if the expression node should really be a variable reference.  */
1800
1801      sym = e->symtree->n.sym;
1802
1803      if (sym->attr.flavor == FL_PROCEDURE
1804	  || sym->attr.intrinsic
1805	  || sym->attr.external)
1806	{
1807	  int actual_ok;
1808
1809	  /* If a procedure is not already determined to be something else
1810	     check if it is intrinsic.  */
1811	  if (gfc_is_intrinsic (sym, sym->attr.subroutine, e->where))
1812	    sym->attr.intrinsic = 1;
1813
1814	  if (sym->attr.proc == PROC_ST_FUNCTION)
1815	    {
1816	      gfc_error ("Statement function %qs at %L is not allowed as an "
1817			 "actual argument", sym->name, &e->where);
1818	    }
1819
1820	  actual_ok = gfc_intrinsic_actual_ok (sym->name,
1821					       sym->attr.subroutine);
1822	  if (sym->attr.intrinsic && actual_ok == 0)
1823	    {
1824	      gfc_error ("Intrinsic %qs at %L is not allowed as an "
1825			 "actual argument", sym->name, &e->where);
1826	    }
1827
1828	  if (sym->attr.contained && !sym->attr.use_assoc
1829	      && sym->ns->proc_name->attr.flavor != FL_MODULE)
1830	    {
1831	      if (!gfc_notify_std (GFC_STD_F2008, "Internal procedure %qs is"
1832				   " used as actual argument at %L",
1833				   sym->name, &e->where))
1834		goto cleanup;
1835	    }
1836
1837	  if (sym->attr.elemental && !sym->attr.intrinsic)
1838	    {
1839	      gfc_error ("ELEMENTAL non-INTRINSIC procedure %qs is not "
1840			 "allowed as an actual argument at %L", sym->name,
1841			 &e->where);
1842	    }
1843
1844	  /* Check if a generic interface has a specific procedure
1845	    with the same name before emitting an error.  */
1846	  if (sym->attr.generic && count_specific_procs (e) != 1)
1847	    goto cleanup;
1848
1849	  /* Just in case a specific was found for the expression.  */
1850	  sym = e->symtree->n.sym;
1851
1852	  /* If the symbol is the function that names the current (or
1853	     parent) scope, then we really have a variable reference.  */
1854
1855	  if (gfc_is_function_return_value (sym, sym->ns))
1856	    goto got_variable;
1857
1858	  /* If all else fails, see if we have a specific intrinsic.  */
1859	  if (sym->ts.type == BT_UNKNOWN && sym->attr.intrinsic)
1860	    {
1861	      gfc_intrinsic_sym *isym;
1862
1863	      isym = gfc_find_function (sym->name);
1864	      if (isym == NULL || !isym->specific)
1865		{
1866		  gfc_error ("Unable to find a specific INTRINSIC procedure "
1867			     "for the reference %qs at %L", sym->name,
1868			     &e->where);
1869		  goto cleanup;
1870		}
1871	      sym->ts = isym->ts;
1872	      sym->attr.intrinsic = 1;
1873	      sym->attr.function = 1;
1874	    }
1875
1876	  if (!gfc_resolve_expr (e))
1877	    goto cleanup;
1878	  goto argument_list;
1879	}
1880
1881      /* See if the name is a module procedure in a parent unit.  */
1882
1883      if (was_declared (sym) || sym->ns->parent == NULL)
1884	goto got_variable;
1885
1886      if (gfc_find_sym_tree (sym->name, sym->ns->parent, 1, &parent_st))
1887	{
1888	  gfc_error ("Symbol %qs at %L is ambiguous", sym->name, &e->where);
1889	  goto cleanup;
1890	}
1891
1892      if (parent_st == NULL)
1893	goto got_variable;
1894
1895      sym = parent_st->n.sym;
1896      e->symtree = parent_st;		/* Point to the right thing.  */
1897
1898      if (sym->attr.flavor == FL_PROCEDURE
1899	  || sym->attr.intrinsic
1900	  || sym->attr.external)
1901	{
1902	  if (!gfc_resolve_expr (e))
1903	    goto cleanup;
1904	  goto argument_list;
1905	}
1906
1907    got_variable:
1908      e->expr_type = EXPR_VARIABLE;
1909      e->ts = sym->ts;
1910      if ((sym->as != NULL && sym->ts.type != BT_CLASS)
1911	  || (sym->ts.type == BT_CLASS && sym->attr.class_ok
1912	      && CLASS_DATA (sym)->as))
1913	{
1914	  e->rank = sym->ts.type == BT_CLASS
1915		    ? CLASS_DATA (sym)->as->rank : sym->as->rank;
1916	  e->ref = gfc_get_ref ();
1917	  e->ref->type = REF_ARRAY;
1918	  e->ref->u.ar.type = AR_FULL;
1919	  e->ref->u.ar.as = sym->ts.type == BT_CLASS
1920			    ? CLASS_DATA (sym)->as : sym->as;
1921	}
1922
1923      /* Expressions are assigned a default ts.type of BT_PROCEDURE in
1924	 primary.c (match_actual_arg). If above code determines that it
1925	 is a  variable instead, it needs to be resolved as it was not
1926	 done at the beginning of this function.  */
1927      save_need_full_assumed_size = need_full_assumed_size;
1928      if (e->expr_type != EXPR_VARIABLE)
1929	need_full_assumed_size = 0;
1930      if (!gfc_resolve_expr (e))
1931	goto cleanup;
1932      need_full_assumed_size = save_need_full_assumed_size;
1933
1934    argument_list:
1935      /* Check argument list functions %VAL, %LOC and %REF.  There is
1936	 nothing to do for %REF.  */
1937      if (arg->name && arg->name[0] == '%')
1938	{
1939	  if (strncmp ("%VAL", arg->name, 4) == 0)
1940	    {
1941	      if (e->ts.type == BT_CHARACTER || e->ts.type == BT_DERIVED)
1942		{
1943		  gfc_error ("By-value argument at %L is not of numeric "
1944			     "type", &e->where);
1945		  goto cleanup;
1946		}
1947
1948	      if (e->rank)
1949		{
1950		  gfc_error ("By-value argument at %L cannot be an array or "
1951			     "an array section", &e->where);
1952		  goto cleanup;
1953		}
1954
1955	      /* Intrinsics are still PROC_UNKNOWN here.  However,
1956		 since same file external procedures are not resolvable
1957		 in gfortran, it is a good deal easier to leave them to
1958		 intrinsic.c.  */
1959	      if (ptype != PROC_UNKNOWN
1960		  && ptype != PROC_DUMMY
1961		  && ptype != PROC_EXTERNAL
1962		  && ptype != PROC_MODULE)
1963		{
1964		  gfc_error ("By-value argument at %L is not allowed "
1965			     "in this context", &e->where);
1966		  goto cleanup;
1967		}
1968	    }
1969
1970	  /* Statement functions have already been excluded above.  */
1971	  else if (strncmp ("%LOC", arg->name, 4) == 0
1972		   && e->ts.type == BT_PROCEDURE)
1973	    {
1974	      if (e->symtree->n.sym->attr.proc == PROC_INTERNAL)
1975		{
1976		  gfc_error ("Passing internal procedure at %L by location "
1977			     "not allowed", &e->where);
1978		  goto cleanup;
1979		}
1980	    }
1981	}
1982
1983      comp = gfc_get_proc_ptr_comp(e);
1984      if (e->expr_type == EXPR_VARIABLE
1985	  && comp && comp->attr.elemental)
1986	{
1987	    gfc_error ("ELEMENTAL procedure pointer component %qs is not "
1988		       "allowed as an actual argument at %L", comp->name,
1989		       &e->where);
1990	}
1991
1992      /* Fortran 2008, C1237.  */
1993      if (e->expr_type == EXPR_VARIABLE && gfc_is_coindexed (e)
1994	  && gfc_has_ultimate_pointer (e))
1995	{
1996	  gfc_error ("Coindexed actual argument at %L with ultimate pointer "
1997		     "component", &e->where);
1998	  goto cleanup;
1999	}
2000
2001      first_actual_arg = false;
2002    }
2003
2004  return_value = true;
2005
2006cleanup:
2007  actual_arg = actual_arg_sav;
2008  first_actual_arg = first_actual_arg_sav;
2009
2010  return return_value;
2011}
2012
2013
2014/* Do the checks of the actual argument list that are specific to elemental
2015   procedures.  If called with c == NULL, we have a function, otherwise if
2016   expr == NULL, we have a subroutine.  */
2017
2018static bool
2019resolve_elemental_actual (gfc_expr *expr, gfc_code *c)
2020{
2021  gfc_actual_arglist *arg0;
2022  gfc_actual_arglist *arg;
2023  gfc_symbol *esym = NULL;
2024  gfc_intrinsic_sym *isym = NULL;
2025  gfc_expr *e = NULL;
2026  gfc_intrinsic_arg *iformal = NULL;
2027  gfc_formal_arglist *eformal = NULL;
2028  bool formal_optional = false;
2029  bool set_by_optional = false;
2030  int i;
2031  int rank = 0;
2032
2033  /* Is this an elemental procedure?  */
2034  if (expr && expr->value.function.actual != NULL)
2035    {
2036      if (expr->value.function.esym != NULL
2037	  && expr->value.function.esym->attr.elemental)
2038	{
2039	  arg0 = expr->value.function.actual;
2040	  esym = expr->value.function.esym;
2041	}
2042      else if (expr->value.function.isym != NULL
2043	       && expr->value.function.isym->elemental)
2044	{
2045	  arg0 = expr->value.function.actual;
2046	  isym = expr->value.function.isym;
2047	}
2048      else
2049	return true;
2050    }
2051  else if (c && c->ext.actual != NULL)
2052    {
2053      arg0 = c->ext.actual;
2054
2055      if (c->resolved_sym)
2056	esym = c->resolved_sym;
2057      else
2058	esym = c->symtree->n.sym;
2059      gcc_assert (esym);
2060
2061      if (!esym->attr.elemental)
2062	return true;
2063    }
2064  else
2065    return true;
2066
2067  /* The rank of an elemental is the rank of its array argument(s).  */
2068  for (arg = arg0; arg; arg = arg->next)
2069    {
2070      if (arg->expr != NULL && arg->expr->rank != 0)
2071	{
2072	  rank = arg->expr->rank;
2073	  if (arg->expr->expr_type == EXPR_VARIABLE
2074	      && arg->expr->symtree->n.sym->attr.optional)
2075	    set_by_optional = true;
2076
2077	  /* Function specific; set the result rank and shape.  */
2078	  if (expr)
2079	    {
2080	      expr->rank = rank;
2081	      if (!expr->shape && arg->expr->shape)
2082		{
2083		  expr->shape = gfc_get_shape (rank);
2084		  for (i = 0; i < rank; i++)
2085		    mpz_init_set (expr->shape[i], arg->expr->shape[i]);
2086		}
2087	    }
2088	  break;
2089	}
2090    }
2091
2092  /* If it is an array, it shall not be supplied as an actual argument
2093     to an elemental procedure unless an array of the same rank is supplied
2094     as an actual argument corresponding to a nonoptional dummy argument of
2095     that elemental procedure(12.4.1.5).  */
2096  formal_optional = false;
2097  if (isym)
2098    iformal = isym->formal;
2099  else
2100    eformal = esym->formal;
2101
2102  for (arg = arg0; arg; arg = arg->next)
2103    {
2104      if (eformal)
2105	{
2106	  if (eformal->sym && eformal->sym->attr.optional)
2107	    formal_optional = true;
2108	  eformal = eformal->next;
2109	}
2110      else if (isym && iformal)
2111	{
2112	  if (iformal->optional)
2113	    formal_optional = true;
2114	  iformal = iformal->next;
2115	}
2116      else if (isym)
2117	formal_optional = true;
2118
2119      if (pedantic && arg->expr != NULL
2120	  && arg->expr->expr_type == EXPR_VARIABLE
2121	  && arg->expr->symtree->n.sym->attr.optional
2122	  && formal_optional
2123	  && arg->expr->rank
2124	  && (set_by_optional || arg->expr->rank != rank)
2125	  && !(isym && isym->id == GFC_ISYM_CONVERSION))
2126	{
2127	  gfc_warning (0, "%qs at %L is an array and OPTIONAL; IF IT IS "
2128		       "MISSING, it cannot be the actual argument of an "
2129		       "ELEMENTAL procedure unless there is a non-optional "
2130		       "argument with the same rank (12.4.1.5)",
2131		       arg->expr->symtree->n.sym->name, &arg->expr->where);
2132	}
2133    }
2134
2135  for (arg = arg0; arg; arg = arg->next)
2136    {
2137      if (arg->expr == NULL || arg->expr->rank == 0)
2138	continue;
2139
2140      /* Being elemental, the last upper bound of an assumed size array
2141	 argument must be present.  */
2142      if (resolve_assumed_size_actual (arg->expr))
2143	return false;
2144
2145      /* Elemental procedure's array actual arguments must conform.  */
2146      if (e != NULL)
2147	{
2148	  if (!gfc_check_conformance (arg->expr, e, "elemental procedure"))
2149	    return false;
2150	}
2151      else
2152	e = arg->expr;
2153    }
2154
2155  /* INTENT(OUT) is only allowed for subroutines; if any actual argument
2156     is an array, the intent inout/out variable needs to be also an array.  */
2157  if (rank > 0 && esym && expr == NULL)
2158    for (eformal = esym->formal, arg = arg0; arg && eformal;
2159	 arg = arg->next, eformal = eformal->next)
2160      if ((eformal->sym->attr.intent == INTENT_OUT
2161	   || eformal->sym->attr.intent == INTENT_INOUT)
2162	  && arg->expr && arg->expr->rank == 0)
2163	{
2164	  gfc_error ("Actual argument at %L for INTENT(%s) dummy %qs of "
2165		     "ELEMENTAL subroutine %qs is a scalar, but another "
2166		     "actual argument is an array", &arg->expr->where,
2167		     (eformal->sym->attr.intent == INTENT_OUT) ? "OUT"
2168		     : "INOUT", eformal->sym->name, esym->name);
2169	  return false;
2170	}
2171  return true;
2172}
2173
2174
2175/* This function does the checking of references to global procedures
2176   as defined in sections 18.1 and 14.1, respectively, of the Fortran
2177   77 and 95 standards.  It checks for a gsymbol for the name, making
2178   one if it does not already exist.  If it already exists, then the
2179   reference being resolved must correspond to the type of gsymbol.
2180   Otherwise, the new symbol is equipped with the attributes of the
2181   reference.  The corresponding code that is called in creating
2182   global entities is parse.c.
2183
2184   In addition, for all but -std=legacy, the gsymbols are used to
2185   check the interfaces of external procedures from the same file.
2186   The namespace of the gsymbol is resolved and then, once this is
2187   done the interface is checked.  */
2188
2189
2190static bool
2191not_in_recursive (gfc_symbol *sym, gfc_namespace *gsym_ns)
2192{
2193  if (!gsym_ns->proc_name->attr.recursive)
2194    return true;
2195
2196  if (sym->ns == gsym_ns)
2197    return false;
2198
2199  if (sym->ns->parent && sym->ns->parent == gsym_ns)
2200    return false;
2201
2202  return true;
2203}
2204
2205static bool
2206not_entry_self_reference  (gfc_symbol *sym, gfc_namespace *gsym_ns)
2207{
2208  if (gsym_ns->entries)
2209    {
2210      gfc_entry_list *entry = gsym_ns->entries;
2211
2212      for (; entry; entry = entry->next)
2213	{
2214	  if (strcmp (sym->name, entry->sym->name) == 0)
2215	    {
2216	      if (strcmp (gsym_ns->proc_name->name,
2217			  sym->ns->proc_name->name) == 0)
2218		return false;
2219
2220	      if (sym->ns->parent
2221		  && strcmp (gsym_ns->proc_name->name,
2222			     sym->ns->parent->proc_name->name) == 0)
2223		return false;
2224	    }
2225	}
2226    }
2227  return true;
2228}
2229
2230
2231/* Check for the requirement of an explicit interface. F08:12.4.2.2.  */
2232
2233bool
2234gfc_explicit_interface_required (gfc_symbol *sym, char *errmsg, int err_len)
2235{
2236  gfc_formal_arglist *arg = gfc_sym_get_dummy_args (sym);
2237
2238  for ( ; arg; arg = arg->next)
2239    {
2240      if (!arg->sym)
2241	continue;
2242
2243      if (arg->sym->attr.allocatable)  /* (2a)  */
2244	{
2245	  strncpy (errmsg, _("allocatable argument"), err_len);
2246	  return true;
2247	}
2248      else if (arg->sym->attr.asynchronous)
2249	{
2250	  strncpy (errmsg, _("asynchronous argument"), err_len);
2251	  return true;
2252	}
2253      else if (arg->sym->attr.optional)
2254	{
2255	  strncpy (errmsg, _("optional argument"), err_len);
2256	  return true;
2257	}
2258      else if (arg->sym->attr.pointer)
2259	{
2260	  strncpy (errmsg, _("pointer argument"), err_len);
2261	  return true;
2262	}
2263      else if (arg->sym->attr.target)
2264	{
2265	  strncpy (errmsg, _("target argument"), err_len);
2266	  return true;
2267	}
2268      else if (arg->sym->attr.value)
2269	{
2270	  strncpy (errmsg, _("value argument"), err_len);
2271	  return true;
2272	}
2273      else if (arg->sym->attr.volatile_)
2274	{
2275	  strncpy (errmsg, _("volatile argument"), err_len);
2276	  return true;
2277	}
2278      else if (arg->sym->as && arg->sym->as->type == AS_ASSUMED_SHAPE)  /* (2b)  */
2279	{
2280	  strncpy (errmsg, _("assumed-shape argument"), err_len);
2281	  return true;
2282	}
2283      else if (arg->sym->as && arg->sym->as->type == AS_ASSUMED_RANK)  /* TS 29113, 6.2.  */
2284	{
2285	  strncpy (errmsg, _("assumed-rank argument"), err_len);
2286	  return true;
2287	}
2288      else if (arg->sym->attr.codimension)  /* (2c)  */
2289	{
2290	  strncpy (errmsg, _("coarray argument"), err_len);
2291	  return true;
2292	}
2293      else if (false)  /* (2d) TODO: parametrized derived type  */
2294	{
2295	  strncpy (errmsg, _("parametrized derived type argument"), err_len);
2296	  return true;
2297	}
2298      else if (arg->sym->ts.type == BT_CLASS)  /* (2e)  */
2299	{
2300	  strncpy (errmsg, _("polymorphic argument"), err_len);
2301	  return true;
2302	}
2303      else if (arg->sym->attr.ext_attr & (1 << EXT_ATTR_NO_ARG_CHECK))
2304	{
2305	  strncpy (errmsg, _("NO_ARG_CHECK attribute"), err_len);
2306	  return true;
2307	}
2308      else if (arg->sym->ts.type == BT_ASSUMED)
2309	{
2310	  /* As assumed-type is unlimited polymorphic (cf. above).
2311	     See also TS 29113, Note 6.1.  */
2312	  strncpy (errmsg, _("assumed-type argument"), err_len);
2313	  return true;
2314	}
2315    }
2316
2317  if (sym->attr.function)
2318    {
2319      gfc_symbol *res = sym->result ? sym->result : sym;
2320
2321      if (res->attr.dimension)  /* (3a)  */
2322	{
2323	  strncpy (errmsg, _("array result"), err_len);
2324	  return true;
2325	}
2326      else if (res->attr.pointer || res->attr.allocatable)  /* (3b)  */
2327	{
2328	  strncpy (errmsg, _("pointer or allocatable result"), err_len);
2329	  return true;
2330	}
2331      else if (res->ts.type == BT_CHARACTER && res->ts.u.cl
2332	       && res->ts.u.cl->length
2333	       && res->ts.u.cl->length->expr_type != EXPR_CONSTANT)  /* (3c)  */
2334	{
2335	  strncpy (errmsg, _("result with non-constant character length"), err_len);
2336	  return true;
2337	}
2338    }
2339
2340  if (sym->attr.elemental && !sym->attr.intrinsic)  /* (4)  */
2341    {
2342      strncpy (errmsg, _("elemental procedure"), err_len);
2343      return true;
2344    }
2345  else if (sym->attr.is_bind_c)  /* (5)  */
2346    {
2347      strncpy (errmsg, _("bind(c) procedure"), err_len);
2348      return true;
2349    }
2350
2351  return false;
2352}
2353
2354
2355static void
2356resolve_global_procedure (gfc_symbol *sym, locus *where,
2357			  gfc_actual_arglist **actual, int sub)
2358{
2359  gfc_gsymbol * gsym;
2360  gfc_namespace *ns;
2361  enum gfc_symbol_type type;
2362  char reason[200];
2363
2364  type = sub ? GSYM_SUBROUTINE : GSYM_FUNCTION;
2365
2366  gsym = gfc_get_gsymbol (sym->binding_label ? sym->binding_label : sym->name);
2367
2368  if ((gsym->type != GSYM_UNKNOWN && gsym->type != type))
2369    gfc_global_used (gsym, where);
2370
2371  if ((sym->attr.if_source == IFSRC_UNKNOWN
2372       || sym->attr.if_source == IFSRC_IFBODY)
2373      && gsym->type != GSYM_UNKNOWN
2374      && !gsym->binding_label
2375      && gsym->ns
2376      && gsym->ns->resolved != -1
2377      && gsym->ns->proc_name
2378      && not_in_recursive (sym, gsym->ns)
2379      && not_entry_self_reference (sym, gsym->ns))
2380    {
2381      gfc_symbol *def_sym;
2382
2383      /* Resolve the gsymbol namespace if needed.  */
2384      if (!gsym->ns->resolved)
2385	{
2386	  gfc_dt_list *old_dt_list;
2387
2388	  /* Stash away derived types so that the backend_decls do not
2389	     get mixed up.  */
2390	  old_dt_list = gfc_derived_types;
2391	  gfc_derived_types = NULL;
2392
2393	  gfc_resolve (gsym->ns);
2394
2395	  /* Store the new derived types with the global namespace.  */
2396	  if (gfc_derived_types)
2397	    gsym->ns->derived_types = gfc_derived_types;
2398
2399	  /* Restore the derived types of this namespace.  */
2400	  gfc_derived_types = old_dt_list;
2401	}
2402
2403      /* Make sure that translation for the gsymbol occurs before
2404	 the procedure currently being resolved.  */
2405      ns = gfc_global_ns_list;
2406      for (; ns && ns != gsym->ns; ns = ns->sibling)
2407	{
2408	  if (ns->sibling == gsym->ns)
2409	    {
2410	      ns->sibling = gsym->ns->sibling;
2411	      gsym->ns->sibling = gfc_global_ns_list;
2412	      gfc_global_ns_list = gsym->ns;
2413	      break;
2414	    }
2415	}
2416
2417      def_sym = gsym->ns->proc_name;
2418
2419      /* This can happen if a binding name has been specified.  */
2420      if (gsym->binding_label && gsym->sym_name != def_sym->name)
2421	gfc_find_symbol (gsym->sym_name, gsym->ns, 0, &def_sym);
2422
2423      if (def_sym->attr.entry_master)
2424	{
2425	  gfc_entry_list *entry;
2426	  for (entry = gsym->ns->entries; entry; entry = entry->next)
2427	    if (strcmp (entry->sym->name, sym->name) == 0)
2428	      {
2429		def_sym = entry->sym;
2430		break;
2431	      }
2432	}
2433
2434      if (sym->attr.function && !gfc_compare_types (&sym->ts, &def_sym->ts))
2435	{
2436	  gfc_error ("Return type mismatch of function %qs at %L (%s/%s)",
2437		     sym->name, &sym->declared_at, gfc_typename (&sym->ts),
2438		     gfc_typename (&def_sym->ts));
2439	  goto done;
2440	}
2441
2442      if (sym->attr.if_source == IFSRC_UNKNOWN
2443	  && gfc_explicit_interface_required (def_sym, reason, sizeof(reason)))
2444	{
2445	  gfc_error ("Explicit interface required for %qs at %L: %s",
2446		     sym->name, &sym->declared_at, reason);
2447	  goto done;
2448	}
2449
2450      if (!pedantic && (gfc_option.allow_std & GFC_STD_GNU))
2451	/* Turn erros into warnings with -std=gnu and -std=legacy.  */
2452	gfc_errors_to_warnings (true);
2453
2454      if (!gfc_compare_interfaces (sym, def_sym, sym->name, 0, 1,
2455				   reason, sizeof(reason), NULL, NULL))
2456	{
2457	  gfc_error ("Interface mismatch in global procedure %qs at %L: %s ",
2458		    sym->name, &sym->declared_at, reason);
2459	  goto done;
2460	}
2461
2462      if (!pedantic
2463	  || ((gfc_option.warn_std & GFC_STD_LEGACY)
2464	      && !(gfc_option.warn_std & GFC_STD_GNU)))
2465	gfc_errors_to_warnings (true);
2466
2467      if (sym->attr.if_source != IFSRC_IFBODY)
2468	gfc_procedure_use (def_sym, actual, where);
2469    }
2470
2471done:
2472  gfc_errors_to_warnings (false);
2473
2474  if (gsym->type == GSYM_UNKNOWN)
2475    {
2476      gsym->type = type;
2477      gsym->where = *where;
2478    }
2479
2480  gsym->used = 1;
2481}
2482
2483
2484/************* Function resolution *************/
2485
2486/* Resolve a function call known to be generic.
2487   Section 14.1.2.4.1.  */
2488
2489static match
2490resolve_generic_f0 (gfc_expr *expr, gfc_symbol *sym)
2491{
2492  gfc_symbol *s;
2493
2494  if (sym->attr.generic)
2495    {
2496      s = gfc_search_interface (sym->generic, 0, &expr->value.function.actual);
2497      if (s != NULL)
2498	{
2499	  expr->value.function.name = s->name;
2500	  expr->value.function.esym = s;
2501
2502	  if (s->ts.type != BT_UNKNOWN)
2503	    expr->ts = s->ts;
2504	  else if (s->result != NULL && s->result->ts.type != BT_UNKNOWN)
2505	    expr->ts = s->result->ts;
2506
2507	  if (s->as != NULL)
2508	    expr->rank = s->as->rank;
2509	  else if (s->result != NULL && s->result->as != NULL)
2510	    expr->rank = s->result->as->rank;
2511
2512	  gfc_set_sym_referenced (expr->value.function.esym);
2513
2514	  return MATCH_YES;
2515	}
2516
2517      /* TODO: Need to search for elemental references in generic
2518	 interface.  */
2519    }
2520
2521  if (sym->attr.intrinsic)
2522    return gfc_intrinsic_func_interface (expr, 0);
2523
2524  return MATCH_NO;
2525}
2526
2527
2528static bool
2529resolve_generic_f (gfc_expr *expr)
2530{
2531  gfc_symbol *sym;
2532  match m;
2533  gfc_interface *intr = NULL;
2534
2535  sym = expr->symtree->n.sym;
2536
2537  for (;;)
2538    {
2539      m = resolve_generic_f0 (expr, sym);
2540      if (m == MATCH_YES)
2541	return true;
2542      else if (m == MATCH_ERROR)
2543	return false;
2544
2545generic:
2546      if (!intr)
2547	for (intr = sym->generic; intr; intr = intr->next)
2548	  if (intr->sym->attr.flavor == FL_DERIVED)
2549	    break;
2550
2551      if (sym->ns->parent == NULL)
2552	break;
2553      gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2554
2555      if (sym == NULL)
2556	break;
2557      if (!generic_sym (sym))
2558	goto generic;
2559    }
2560
2561  /* Last ditch attempt.  See if the reference is to an intrinsic
2562     that possesses a matching interface.  14.1.2.4  */
2563  if (sym  && !intr && !gfc_is_intrinsic (sym, 0, expr->where))
2564    {
2565      gfc_error ("There is no specific function for the generic %qs "
2566		 "at %L", expr->symtree->n.sym->name, &expr->where);
2567      return false;
2568    }
2569
2570  if (intr)
2571    {
2572      if (!gfc_convert_to_structure_constructor (expr, intr->sym, NULL,
2573						 NULL, false))
2574	return false;
2575      return resolve_structure_cons (expr, 0);
2576    }
2577
2578  m = gfc_intrinsic_func_interface (expr, 0);
2579  if (m == MATCH_YES)
2580    return true;
2581
2582  if (m == MATCH_NO)
2583    gfc_error ("Generic function %qs at %L is not consistent with a "
2584	       "specific intrinsic interface", expr->symtree->n.sym->name,
2585	       &expr->where);
2586
2587  return false;
2588}
2589
2590
2591/* Resolve a function call known to be specific.  */
2592
2593static match
2594resolve_specific_f0 (gfc_symbol *sym, gfc_expr *expr)
2595{
2596  match m;
2597
2598  if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
2599    {
2600      if (sym->attr.dummy)
2601	{
2602	  sym->attr.proc = PROC_DUMMY;
2603	  goto found;
2604	}
2605
2606      sym->attr.proc = PROC_EXTERNAL;
2607      goto found;
2608    }
2609
2610  if (sym->attr.proc == PROC_MODULE
2611      || sym->attr.proc == PROC_ST_FUNCTION
2612      || sym->attr.proc == PROC_INTERNAL)
2613    goto found;
2614
2615  if (sym->attr.intrinsic)
2616    {
2617      m = gfc_intrinsic_func_interface (expr, 1);
2618      if (m == MATCH_YES)
2619	return MATCH_YES;
2620      if (m == MATCH_NO)
2621	gfc_error ("Function %qs at %L is INTRINSIC but is not compatible "
2622		   "with an intrinsic", sym->name, &expr->where);
2623
2624      return MATCH_ERROR;
2625    }
2626
2627  return MATCH_NO;
2628
2629found:
2630  gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2631
2632  if (sym->result)
2633    expr->ts = sym->result->ts;
2634  else
2635    expr->ts = sym->ts;
2636  expr->value.function.name = sym->name;
2637  expr->value.function.esym = sym;
2638  /* Prevent crash when sym->ts.u.derived->components is not set due to previous
2639     error(s).  */
2640  if (sym->ts.type == BT_CLASS && !CLASS_DATA (sym))
2641    return MATCH_ERROR;
2642  if (sym->ts.type == BT_CLASS && CLASS_DATA (sym)->as)
2643    expr->rank = CLASS_DATA (sym)->as->rank;
2644  else if (sym->as != NULL)
2645    expr->rank = sym->as->rank;
2646
2647  return MATCH_YES;
2648}
2649
2650
2651static bool
2652resolve_specific_f (gfc_expr *expr)
2653{
2654  gfc_symbol *sym;
2655  match m;
2656
2657  sym = expr->symtree->n.sym;
2658
2659  for (;;)
2660    {
2661      m = resolve_specific_f0 (sym, expr);
2662      if (m == MATCH_YES)
2663	return true;
2664      if (m == MATCH_ERROR)
2665	return false;
2666
2667      if (sym->ns->parent == NULL)
2668	break;
2669
2670      gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2671
2672      if (sym == NULL)
2673	break;
2674    }
2675
2676  gfc_error ("Unable to resolve the specific function %qs at %L",
2677	     expr->symtree->n.sym->name, &expr->where);
2678
2679  return true;
2680}
2681
2682
2683/* Resolve a procedure call not known to be generic nor specific.  */
2684
2685static bool
2686resolve_unknown_f (gfc_expr *expr)
2687{
2688  gfc_symbol *sym;
2689  gfc_typespec *ts;
2690
2691  sym = expr->symtree->n.sym;
2692
2693  if (sym->attr.dummy)
2694    {
2695      sym->attr.proc = PROC_DUMMY;
2696      expr->value.function.name = sym->name;
2697      goto set_type;
2698    }
2699
2700  /* See if we have an intrinsic function reference.  */
2701
2702  if (gfc_is_intrinsic (sym, 0, expr->where))
2703    {
2704      if (gfc_intrinsic_func_interface (expr, 1) == MATCH_YES)
2705	return true;
2706      return false;
2707    }
2708
2709  /* The reference is to an external name.  */
2710
2711  sym->attr.proc = PROC_EXTERNAL;
2712  expr->value.function.name = sym->name;
2713  expr->value.function.esym = expr->symtree->n.sym;
2714
2715  if (sym->as != NULL)
2716    expr->rank = sym->as->rank;
2717
2718  /* Type of the expression is either the type of the symbol or the
2719     default type of the symbol.  */
2720
2721set_type:
2722  gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2723
2724  if (sym->ts.type != BT_UNKNOWN)
2725    expr->ts = sym->ts;
2726  else
2727    {
2728      ts = gfc_get_default_type (sym->name, sym->ns);
2729
2730      if (ts->type == BT_UNKNOWN)
2731	{
2732	  gfc_error ("Function %qs at %L has no IMPLICIT type",
2733		     sym->name, &expr->where);
2734	  return false;
2735	}
2736      else
2737	expr->ts = *ts;
2738    }
2739
2740  return true;
2741}
2742
2743
2744/* Return true, if the symbol is an external procedure.  */
2745static bool
2746is_external_proc (gfc_symbol *sym)
2747{
2748  if (!sym->attr.dummy && !sym->attr.contained
2749	&& !gfc_is_intrinsic (sym, sym->attr.subroutine, sym->declared_at)
2750	&& sym->attr.proc != PROC_ST_FUNCTION
2751	&& !sym->attr.proc_pointer
2752	&& !sym->attr.use_assoc
2753	&& sym->name)
2754    return true;
2755
2756  return false;
2757}
2758
2759
2760/* Figure out if a function reference is pure or not.  Also set the name
2761   of the function for a potential error message.  Return nonzero if the
2762   function is PURE, zero if not.  */
2763static int
2764pure_stmt_function (gfc_expr *, gfc_symbol *);
2765
2766static int
2767pure_function (gfc_expr *e, const char **name)
2768{
2769  int pure;
2770  gfc_component *comp;
2771
2772  *name = NULL;
2773
2774  if (e->symtree != NULL
2775        && e->symtree->n.sym != NULL
2776        && e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2777    return pure_stmt_function (e, e->symtree->n.sym);
2778
2779  comp = gfc_get_proc_ptr_comp (e);
2780  if (comp)
2781    {
2782      pure = gfc_pure (comp->ts.interface);
2783      *name = comp->name;
2784    }
2785  else if (e->value.function.esym)
2786    {
2787      pure = gfc_pure (e->value.function.esym);
2788      *name = e->value.function.esym->name;
2789    }
2790  else if (e->value.function.isym)
2791    {
2792      pure = e->value.function.isym->pure
2793	     || e->value.function.isym->elemental;
2794      *name = e->value.function.isym->name;
2795    }
2796  else
2797    {
2798      /* Implicit functions are not pure.  */
2799      pure = 0;
2800      *name = e->value.function.name;
2801    }
2802
2803  return pure;
2804}
2805
2806
2807static bool
2808impure_stmt_fcn (gfc_expr *e, gfc_symbol *sym,
2809		 int *f ATTRIBUTE_UNUSED)
2810{
2811  const char *name;
2812
2813  /* Don't bother recursing into other statement functions
2814     since they will be checked individually for purity.  */
2815  if (e->expr_type != EXPR_FUNCTION
2816	|| !e->symtree
2817	|| e->symtree->n.sym == sym
2818	|| e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2819    return false;
2820
2821  return pure_function (e, &name) ? false : true;
2822}
2823
2824
2825static int
2826pure_stmt_function (gfc_expr *e, gfc_symbol *sym)
2827{
2828  return gfc_traverse_expr (e, sym, impure_stmt_fcn, 0) ? 0 : 1;
2829}
2830
2831
2832/* Check if an impure function is allowed in the current context. */
2833
2834static bool check_pure_function (gfc_expr *e)
2835{
2836  const char *name = NULL;
2837  if (!pure_function (e, &name) && name)
2838    {
2839      if (forall_flag)
2840	{
2841	  gfc_error ("Reference to impure function %qs at %L inside a "
2842		     "FORALL %s", name, &e->where,
2843		     forall_flag == 2 ? "mask" : "block");
2844	  return false;
2845	}
2846      else if (gfc_do_concurrent_flag)
2847	{
2848	  gfc_error ("Reference to impure function %qs at %L inside a "
2849		     "DO CONCURRENT %s", name, &e->where,
2850		     gfc_do_concurrent_flag == 2 ? "mask" : "block");
2851	  return false;
2852	}
2853      else if (gfc_pure (NULL))
2854	{
2855	  gfc_error ("Reference to impure function %qs at %L "
2856		     "within a PURE procedure", name, &e->where);
2857	  return false;
2858	}
2859      gfc_unset_implicit_pure (NULL);
2860    }
2861  return true;
2862}
2863
2864
2865/* Update current procedure's array_outer_dependency flag, considering
2866   a call to procedure SYM.  */
2867
2868static void
2869update_current_proc_array_outer_dependency (gfc_symbol *sym)
2870{
2871  /* Check to see if this is a sibling function that has not yet
2872     been resolved.  */
2873  gfc_namespace *sibling = gfc_current_ns->sibling;
2874  for (; sibling; sibling = sibling->sibling)
2875    {
2876      if (sibling->proc_name == sym)
2877	{
2878	  gfc_resolve (sibling);
2879	  break;
2880	}
2881    }
2882
2883  /* If SYM has references to outer arrays, so has the procedure calling
2884     SYM.  If SYM is a procedure pointer, we can assume the worst.  */
2885  if (sym->attr.array_outer_dependency
2886      || sym->attr.proc_pointer)
2887    gfc_current_ns->proc_name->attr.array_outer_dependency = 1;
2888}
2889
2890
2891/* Resolve a function call, which means resolving the arguments, then figuring
2892   out which entity the name refers to.  */
2893
2894static bool
2895resolve_function (gfc_expr *expr)
2896{
2897  gfc_actual_arglist *arg;
2898  gfc_symbol *sym;
2899  bool t;
2900  int temp;
2901  procedure_type p = PROC_INTRINSIC;
2902  bool no_formal_args;
2903
2904  sym = NULL;
2905  if (expr->symtree)
2906    sym = expr->symtree->n.sym;
2907
2908  /* If this is a procedure pointer component, it has already been resolved.  */
2909  if (gfc_is_proc_ptr_comp (expr))
2910    return true;
2911
2912  if (sym && sym->attr.intrinsic
2913      && !gfc_resolve_intrinsic (sym, &expr->where))
2914    return false;
2915
2916  if (sym && (sym->attr.flavor == FL_VARIABLE || sym->attr.subroutine))
2917    {
2918      gfc_error ("%qs at %L is not a function", sym->name, &expr->where);
2919      return false;
2920    }
2921
2922  /* If this ia a deferred TBP with an abstract interface (which may
2923     of course be referenced), expr->value.function.esym will be set.  */
2924  if (sym && sym->attr.abstract && !expr->value.function.esym)
2925    {
2926      gfc_error ("ABSTRACT INTERFACE %qs must not be referenced at %L",
2927		 sym->name, &expr->where);
2928      return false;
2929    }
2930
2931  /* Switch off assumed size checking and do this again for certain kinds
2932     of procedure, once the procedure itself is resolved.  */
2933  need_full_assumed_size++;
2934
2935  if (expr->symtree && expr->symtree->n.sym)
2936    p = expr->symtree->n.sym->attr.proc;
2937
2938  if (expr->value.function.isym && expr->value.function.isym->inquiry)
2939    inquiry_argument = true;
2940  no_formal_args = sym && is_external_proc (sym)
2941  		       && gfc_sym_get_dummy_args (sym) == NULL;
2942
2943  if (!resolve_actual_arglist (expr->value.function.actual,
2944			       p, no_formal_args))
2945    {
2946      inquiry_argument = false;
2947      return false;
2948    }
2949
2950  inquiry_argument = false;
2951
2952  /* Resume assumed_size checking.  */
2953  need_full_assumed_size--;
2954
2955  /* If the procedure is external, check for usage.  */
2956  if (sym && is_external_proc (sym))
2957    resolve_global_procedure (sym, &expr->where,
2958			      &expr->value.function.actual, 0);
2959
2960  if (sym && sym->ts.type == BT_CHARACTER
2961      && sym->ts.u.cl
2962      && sym->ts.u.cl->length == NULL
2963      && !sym->attr.dummy
2964      && !sym->ts.deferred
2965      && expr->value.function.esym == NULL
2966      && !sym->attr.contained)
2967    {
2968      /* Internal procedures are taken care of in resolve_contained_fntype.  */
2969      gfc_error ("Function %qs is declared CHARACTER(*) and cannot "
2970		 "be used at %L since it is not a dummy argument",
2971		 sym->name, &expr->where);
2972      return false;
2973    }
2974
2975  /* See if function is already resolved.  */
2976
2977  if (expr->value.function.name != NULL
2978      || expr->value.function.isym != NULL)
2979    {
2980      if (expr->ts.type == BT_UNKNOWN)
2981	expr->ts = sym->ts;
2982      t = true;
2983    }
2984  else
2985    {
2986      /* Apply the rules of section 14.1.2.  */
2987
2988      switch (procedure_kind (sym))
2989	{
2990	case PTYPE_GENERIC:
2991	  t = resolve_generic_f (expr);
2992	  break;
2993
2994	case PTYPE_SPECIFIC:
2995	  t = resolve_specific_f (expr);
2996	  break;
2997
2998	case PTYPE_UNKNOWN:
2999	  t = resolve_unknown_f (expr);
3000	  break;
3001
3002	default:
3003	  gfc_internal_error ("resolve_function(): bad function type");
3004	}
3005    }
3006
3007  /* If the expression is still a function (it might have simplified),
3008     then we check to see if we are calling an elemental function.  */
3009
3010  if (expr->expr_type != EXPR_FUNCTION)
3011    return t;
3012
3013  temp = need_full_assumed_size;
3014  need_full_assumed_size = 0;
3015
3016  if (!resolve_elemental_actual (expr, NULL))
3017    return false;
3018
3019  if (omp_workshare_flag
3020      && expr->value.function.esym
3021      && ! gfc_elemental (expr->value.function.esym))
3022    {
3023      gfc_error ("User defined non-ELEMENTAL function %qs at %L not allowed "
3024		 "in WORKSHARE construct", expr->value.function.esym->name,
3025		 &expr->where);
3026      t = false;
3027    }
3028
3029#define GENERIC_ID expr->value.function.isym->id
3030  else if (expr->value.function.actual != NULL
3031	   && expr->value.function.isym != NULL
3032	   && GENERIC_ID != GFC_ISYM_LBOUND
3033	   && GENERIC_ID != GFC_ISYM_LCOBOUND
3034	   && GENERIC_ID != GFC_ISYM_UCOBOUND
3035	   && GENERIC_ID != GFC_ISYM_LEN
3036	   && GENERIC_ID != GFC_ISYM_LOC
3037	   && GENERIC_ID != GFC_ISYM_C_LOC
3038	   && GENERIC_ID != GFC_ISYM_PRESENT)
3039    {
3040      /* Array intrinsics must also have the last upper bound of an
3041	 assumed size array argument.  UBOUND and SIZE have to be
3042	 excluded from the check if the second argument is anything
3043	 than a constant.  */
3044
3045      for (arg = expr->value.function.actual; arg; arg = arg->next)
3046	{
3047	  if ((GENERIC_ID == GFC_ISYM_UBOUND || GENERIC_ID == GFC_ISYM_SIZE)
3048	      && arg == expr->value.function.actual
3049	      && arg->next != NULL && arg->next->expr)
3050	    {
3051	      if (arg->next->expr->expr_type != EXPR_CONSTANT)
3052		break;
3053
3054	      if (arg->next->name && strncmp (arg->next->name, "kind", 4) == 0)
3055		break;
3056
3057	      if ((int)mpz_get_si (arg->next->expr->value.integer)
3058			< arg->expr->rank)
3059		break;
3060	    }
3061
3062	  if (arg->expr != NULL
3063	      && arg->expr->rank > 0
3064	      && resolve_assumed_size_actual (arg->expr))
3065	    return false;
3066	}
3067    }
3068#undef GENERIC_ID
3069
3070  need_full_assumed_size = temp;
3071
3072  if (!check_pure_function(expr))
3073    t = false;
3074
3075  /* Functions without the RECURSIVE attribution are not allowed to
3076   * call themselves.  */
3077  if (expr->value.function.esym && !expr->value.function.esym->attr.recursive)
3078    {
3079      gfc_symbol *esym;
3080      esym = expr->value.function.esym;
3081
3082      if (is_illegal_recursion (esym, gfc_current_ns))
3083      {
3084	if (esym->attr.entry && esym->ns->entries)
3085	  gfc_error ("ENTRY %qs at %L cannot be called recursively, as"
3086		     " function %qs is not RECURSIVE",
3087		     esym->name, &expr->where, esym->ns->entries->sym->name);
3088	else
3089	  gfc_error ("Function %qs at %L cannot be called recursively, as it"
3090		     " is not RECURSIVE", esym->name, &expr->where);
3091
3092	t = false;
3093      }
3094    }
3095
3096  /* Character lengths of use associated functions may contains references to
3097     symbols not referenced from the current program unit otherwise.  Make sure
3098     those symbols are marked as referenced.  */
3099
3100  if (expr->ts.type == BT_CHARACTER && expr->value.function.esym
3101      && expr->value.function.esym->attr.use_assoc)
3102    {
3103      gfc_expr_set_symbols_referenced (expr->ts.u.cl->length);
3104    }
3105
3106  /* Make sure that the expression has a typespec that works.  */
3107  if (expr->ts.type == BT_UNKNOWN)
3108    {
3109      if (expr->symtree->n.sym->result
3110	    && expr->symtree->n.sym->result->ts.type != BT_UNKNOWN
3111	    && !expr->symtree->n.sym->result->attr.proc_pointer)
3112	expr->ts = expr->symtree->n.sym->result->ts;
3113    }
3114
3115  if (!expr->ref && !expr->value.function.isym)
3116    {
3117      if (expr->value.function.esym)
3118	update_current_proc_array_outer_dependency (expr->value.function.esym);
3119      else
3120	update_current_proc_array_outer_dependency (sym);
3121    }
3122  else if (expr->ref)
3123    /* typebound procedure: Assume the worst.  */
3124    gfc_current_ns->proc_name->attr.array_outer_dependency = 1;
3125
3126  return t;
3127}
3128
3129
3130/************* Subroutine resolution *************/
3131
3132static bool
3133pure_subroutine (gfc_symbol *sym, const char *name, locus *loc)
3134{
3135  if (gfc_pure (sym))
3136    return true;
3137
3138  if (forall_flag)
3139    {
3140      gfc_error ("Subroutine call to %qs in FORALL block at %L is not PURE",
3141		 name, loc);
3142      return false;
3143    }
3144  else if (gfc_do_concurrent_flag)
3145    {
3146      gfc_error ("Subroutine call to %qs in DO CONCURRENT block at %L is not "
3147		 "PURE", name, loc);
3148      return false;
3149    }
3150  else if (gfc_pure (NULL))
3151    {
3152      gfc_error ("Subroutine call to %qs at %L is not PURE", name, loc);
3153      return false;
3154    }
3155
3156  gfc_unset_implicit_pure (NULL);
3157  return true;
3158}
3159
3160
3161static match
3162resolve_generic_s0 (gfc_code *c, gfc_symbol *sym)
3163{
3164  gfc_symbol *s;
3165
3166  if (sym->attr.generic)
3167    {
3168      s = gfc_search_interface (sym->generic, 1, &c->ext.actual);
3169      if (s != NULL)
3170	{
3171	  c->resolved_sym = s;
3172	  if (!pure_subroutine (s, s->name, &c->loc))
3173	    return MATCH_ERROR;
3174	  return MATCH_YES;
3175	}
3176
3177      /* TODO: Need to search for elemental references in generic interface.  */
3178    }
3179
3180  if (sym->attr.intrinsic)
3181    return gfc_intrinsic_sub_interface (c, 0);
3182
3183  return MATCH_NO;
3184}
3185
3186
3187static bool
3188resolve_generic_s (gfc_code *c)
3189{
3190  gfc_symbol *sym;
3191  match m;
3192
3193  sym = c->symtree->n.sym;
3194
3195  for (;;)
3196    {
3197      m = resolve_generic_s0 (c, sym);
3198      if (m == MATCH_YES)
3199	return true;
3200      else if (m == MATCH_ERROR)
3201	return false;
3202
3203generic:
3204      if (sym->ns->parent == NULL)
3205	break;
3206      gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
3207
3208      if (sym == NULL)
3209	break;
3210      if (!generic_sym (sym))
3211	goto generic;
3212    }
3213
3214  /* Last ditch attempt.  See if the reference is to an intrinsic
3215     that possesses a matching interface.  14.1.2.4  */
3216  sym = c->symtree->n.sym;
3217
3218  if (!gfc_is_intrinsic (sym, 1, c->loc))
3219    {
3220      gfc_error ("There is no specific subroutine for the generic %qs at %L",
3221		 sym->name, &c->loc);
3222      return false;
3223    }
3224
3225  m = gfc_intrinsic_sub_interface (c, 0);
3226  if (m == MATCH_YES)
3227    return true;
3228  if (m == MATCH_NO)
3229    gfc_error ("Generic subroutine %qs at %L is not consistent with an "
3230	       "intrinsic subroutine interface", sym->name, &c->loc);
3231
3232  return false;
3233}
3234
3235
3236/* Resolve a subroutine call known to be specific.  */
3237
3238static match
3239resolve_specific_s0 (gfc_code *c, gfc_symbol *sym)
3240{
3241  match m;
3242
3243  if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
3244    {
3245      if (sym->attr.dummy)
3246	{
3247	  sym->attr.proc = PROC_DUMMY;
3248	  goto found;
3249	}
3250
3251      sym->attr.proc = PROC_EXTERNAL;
3252      goto found;
3253    }
3254
3255  if (sym->attr.proc == PROC_MODULE || sym->attr.proc == PROC_INTERNAL)
3256    goto found;
3257
3258  if (sym->attr.intrinsic)
3259    {
3260      m = gfc_intrinsic_sub_interface (c, 1);
3261      if (m == MATCH_YES)
3262	return MATCH_YES;
3263      if (m == MATCH_NO)
3264	gfc_error ("Subroutine %qs at %L is INTRINSIC but is not compatible "
3265		   "with an intrinsic", sym->name, &c->loc);
3266
3267      return MATCH_ERROR;
3268    }
3269
3270  return MATCH_NO;
3271
3272found:
3273  gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3274
3275  c->resolved_sym = sym;
3276  if (!pure_subroutine (sym, sym->name, &c->loc))
3277    return MATCH_ERROR;
3278
3279  return MATCH_YES;
3280}
3281
3282
3283static bool
3284resolve_specific_s (gfc_code *c)
3285{
3286  gfc_symbol *sym;
3287  match m;
3288
3289  sym = c->symtree->n.sym;
3290
3291  for (;;)
3292    {
3293      m = resolve_specific_s0 (c, sym);
3294      if (m == MATCH_YES)
3295	return true;
3296      if (m == MATCH_ERROR)
3297	return false;
3298
3299      if (sym->ns->parent == NULL)
3300	break;
3301
3302      gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
3303
3304      if (sym == NULL)
3305	break;
3306    }
3307
3308  sym = c->symtree->n.sym;
3309  gfc_error ("Unable to resolve the specific subroutine %qs at %L",
3310	     sym->name, &c->loc);
3311
3312  return false;
3313}
3314
3315
3316/* Resolve a subroutine call not known to be generic nor specific.  */
3317
3318static bool
3319resolve_unknown_s (gfc_code *c)
3320{
3321  gfc_symbol *sym;
3322
3323  sym = c->symtree->n.sym;
3324
3325  if (sym->attr.dummy)
3326    {
3327      sym->attr.proc = PROC_DUMMY;
3328      goto found;
3329    }
3330
3331  /* See if we have an intrinsic function reference.  */
3332
3333  if (gfc_is_intrinsic (sym, 1, c->loc))
3334    {
3335      if (gfc_intrinsic_sub_interface (c, 1) == MATCH_YES)
3336	return true;
3337      return false;
3338    }
3339
3340  /* The reference is to an external name.  */
3341
3342found:
3343  gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3344
3345  c->resolved_sym = sym;
3346
3347  return pure_subroutine (sym, sym->name, &c->loc);
3348}
3349
3350
3351/* Resolve a subroutine call.  Although it was tempting to use the same code
3352   for functions, subroutines and functions are stored differently and this
3353   makes things awkward.  */
3354
3355static bool
3356resolve_call (gfc_code *c)
3357{
3358  bool t;
3359  procedure_type ptype = PROC_INTRINSIC;
3360  gfc_symbol *csym, *sym;
3361  bool no_formal_args;
3362
3363  csym = c->symtree ? c->symtree->n.sym : NULL;
3364
3365  if (csym && csym->ts.type != BT_UNKNOWN)
3366    {
3367      gfc_error_1 ("'%s' at %L has a type, which is not consistent with "
3368		 "the CALL at %L", csym->name, &csym->declared_at, &c->loc);
3369      return false;
3370    }
3371
3372  if (csym && gfc_current_ns->parent && csym->ns != gfc_current_ns)
3373    {
3374      gfc_symtree *st;
3375      gfc_find_sym_tree (c->symtree->name, gfc_current_ns, 1, &st);
3376      sym = st ? st->n.sym : NULL;
3377      if (sym && csym != sym
3378	      && sym->ns == gfc_current_ns
3379	      && sym->attr.flavor == FL_PROCEDURE
3380	      && sym->attr.contained)
3381	{
3382	  sym->refs++;
3383	  if (csym->attr.generic)
3384	    c->symtree->n.sym = sym;
3385	  else
3386	    c->symtree = st;
3387	  csym = c->symtree->n.sym;
3388	}
3389    }
3390
3391  /* If this ia a deferred TBP, c->expr1 will be set.  */
3392  if (!c->expr1 && csym)
3393    {
3394      if (csym->attr.abstract)
3395	{
3396	  gfc_error ("ABSTRACT INTERFACE %qs must not be referenced at %L",
3397		    csym->name, &c->loc);
3398	  return false;
3399	}
3400
3401      /* Subroutines without the RECURSIVE attribution are not allowed to
3402	 call themselves.  */
3403      if (is_illegal_recursion (csym, gfc_current_ns))
3404	{
3405	  if (csym->attr.entry && csym->ns->entries)
3406	    gfc_error ("ENTRY %qs at %L cannot be called recursively, "
3407		       "as subroutine %qs is not RECURSIVE",
3408		       csym->name, &c->loc, csym->ns->entries->sym->name);
3409	  else
3410	    gfc_error ("SUBROUTINE %qs at %L cannot be called recursively, "
3411		       "as it is not RECURSIVE", csym->name, &c->loc);
3412
3413	  t = false;
3414	}
3415    }
3416
3417  /* Switch off assumed size checking and do this again for certain kinds
3418     of procedure, once the procedure itself is resolved.  */
3419  need_full_assumed_size++;
3420
3421  if (csym)
3422    ptype = csym->attr.proc;
3423
3424  no_formal_args = csym && is_external_proc (csym)
3425			&& gfc_sym_get_dummy_args (csym) == NULL;
3426  if (!resolve_actual_arglist (c->ext.actual, ptype, no_formal_args))
3427    return false;
3428
3429  /* Resume assumed_size checking.  */
3430  need_full_assumed_size--;
3431
3432  /* If external, check for usage.  */
3433  if (csym && is_external_proc (csym))
3434    resolve_global_procedure (csym, &c->loc, &c->ext.actual, 1);
3435
3436  t = true;
3437  if (c->resolved_sym == NULL)
3438    {
3439      c->resolved_isym = NULL;
3440      switch (procedure_kind (csym))
3441	{
3442	case PTYPE_GENERIC:
3443	  t = resolve_generic_s (c);
3444	  break;
3445
3446	case PTYPE_SPECIFIC:
3447	  t = resolve_specific_s (c);
3448	  break;
3449
3450	case PTYPE_UNKNOWN:
3451	  t = resolve_unknown_s (c);
3452	  break;
3453
3454	default:
3455	  gfc_internal_error ("resolve_subroutine(): bad function type");
3456	}
3457    }
3458
3459  /* Some checks of elemental subroutine actual arguments.  */
3460  if (!resolve_elemental_actual (NULL, c))
3461    return false;
3462
3463  if (!c->expr1)
3464    update_current_proc_array_outer_dependency (csym);
3465  else
3466    /* Typebound procedure: Assume the worst.  */
3467    gfc_current_ns->proc_name->attr.array_outer_dependency = 1;
3468
3469  return t;
3470}
3471
3472
3473/* Compare the shapes of two arrays that have non-NULL shapes.  If both
3474   op1->shape and op2->shape are non-NULL return true if their shapes
3475   match.  If both op1->shape and op2->shape are non-NULL return false
3476   if their shapes do not match.  If either op1->shape or op2->shape is
3477   NULL, return true.  */
3478
3479static bool
3480compare_shapes (gfc_expr *op1, gfc_expr *op2)
3481{
3482  bool t;
3483  int i;
3484
3485  t = true;
3486
3487  if (op1->shape != NULL && op2->shape != NULL)
3488    {
3489      for (i = 0; i < op1->rank; i++)
3490	{
3491	  if (mpz_cmp (op1->shape[i], op2->shape[i]) != 0)
3492	   {
3493	     gfc_error_1 ("Shapes for operands at %L and %L are not conformable",
3494			 &op1->where, &op2->where);
3495	     t = false;
3496	     break;
3497	   }
3498	}
3499    }
3500
3501  return t;
3502}
3503
3504
3505/* Resolve an operator expression node.  This can involve replacing the
3506   operation with a user defined function call.  */
3507
3508static bool
3509resolve_operator (gfc_expr *e)
3510{
3511  gfc_expr *op1, *op2;
3512  char msg[200];
3513  bool dual_locus_error;
3514  bool t;
3515
3516  /* Resolve all subnodes-- give them types.  */
3517
3518  switch (e->value.op.op)
3519    {
3520    default:
3521      if (!gfc_resolve_expr (e->value.op.op2))
3522	return false;
3523
3524    /* Fall through...  */
3525
3526    case INTRINSIC_NOT:
3527    case INTRINSIC_UPLUS:
3528    case INTRINSIC_UMINUS:
3529    case INTRINSIC_PARENTHESES:
3530      if (!gfc_resolve_expr (e->value.op.op1))
3531	return false;
3532      break;
3533    }
3534
3535  /* Typecheck the new node.  */
3536
3537  op1 = e->value.op.op1;
3538  op2 = e->value.op.op2;
3539  dual_locus_error = false;
3540
3541  if ((op1 && op1->expr_type == EXPR_NULL)
3542      || (op2 && op2->expr_type == EXPR_NULL))
3543    {
3544      sprintf (msg, _("Invalid context for NULL() pointer at %%L"));
3545      goto bad_op;
3546    }
3547
3548  switch (e->value.op.op)
3549    {
3550    case INTRINSIC_UPLUS:
3551    case INTRINSIC_UMINUS:
3552      if (op1->ts.type == BT_INTEGER
3553	  || op1->ts.type == BT_REAL
3554	  || op1->ts.type == BT_COMPLEX)
3555	{
3556	  e->ts = op1->ts;
3557	  break;
3558	}
3559
3560      sprintf (msg, _("Operand of unary numeric operator '%s' at %%L is %s"),
3561	       gfc_op2string (e->value.op.op), gfc_typename (&e->ts));
3562      goto bad_op;
3563
3564    case INTRINSIC_PLUS:
3565    case INTRINSIC_MINUS:
3566    case INTRINSIC_TIMES:
3567    case INTRINSIC_DIVIDE:
3568    case INTRINSIC_POWER:
3569      if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3570	{
3571	  gfc_type_convert_binary (e, 1);
3572	  break;
3573	}
3574
3575      sprintf (msg,
3576	       _("Operands of binary numeric operator '%s' at %%L are %s/%s"),
3577	       gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3578	       gfc_typename (&op2->ts));
3579      goto bad_op;
3580
3581    case INTRINSIC_CONCAT:
3582      if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3583	  && op1->ts.kind == op2->ts.kind)
3584	{
3585	  e->ts.type = BT_CHARACTER;
3586	  e->ts.kind = op1->ts.kind;
3587	  break;
3588	}
3589
3590      sprintf (msg,
3591	       _("Operands of string concatenation operator at %%L are %s/%s"),
3592	       gfc_typename (&op1->ts), gfc_typename (&op2->ts));
3593      goto bad_op;
3594
3595    case INTRINSIC_AND:
3596    case INTRINSIC_OR:
3597    case INTRINSIC_EQV:
3598    case INTRINSIC_NEQV:
3599      if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3600	{
3601	  e->ts.type = BT_LOGICAL;
3602	  e->ts.kind = gfc_kind_max (op1, op2);
3603	  if (op1->ts.kind < e->ts.kind)
3604	    gfc_convert_type (op1, &e->ts, 2);
3605	  else if (op2->ts.kind < e->ts.kind)
3606	    gfc_convert_type (op2, &e->ts, 2);
3607	  break;
3608	}
3609
3610      sprintf (msg, _("Operands of logical operator '%s' at %%L are %s/%s"),
3611	       gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3612	       gfc_typename (&op2->ts));
3613
3614      goto bad_op;
3615
3616    case INTRINSIC_NOT:
3617      if (op1->ts.type == BT_LOGICAL)
3618	{
3619	  e->ts.type = BT_LOGICAL;
3620	  e->ts.kind = op1->ts.kind;
3621	  break;
3622	}
3623
3624      sprintf (msg, _("Operand of .not. operator at %%L is %s"),
3625	       gfc_typename (&op1->ts));
3626      goto bad_op;
3627
3628    case INTRINSIC_GT:
3629    case INTRINSIC_GT_OS:
3630    case INTRINSIC_GE:
3631    case INTRINSIC_GE_OS:
3632    case INTRINSIC_LT:
3633    case INTRINSIC_LT_OS:
3634    case INTRINSIC_LE:
3635    case INTRINSIC_LE_OS:
3636      if (op1->ts.type == BT_COMPLEX || op2->ts.type == BT_COMPLEX)
3637	{
3638	  strcpy (msg, _("COMPLEX quantities cannot be compared at %L"));
3639	  goto bad_op;
3640	}
3641
3642      /* Fall through...  */
3643
3644    case INTRINSIC_EQ:
3645    case INTRINSIC_EQ_OS:
3646    case INTRINSIC_NE:
3647    case INTRINSIC_NE_OS:
3648      if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3649	  && op1->ts.kind == op2->ts.kind)
3650	{
3651	  e->ts.type = BT_LOGICAL;
3652	  e->ts.kind = gfc_default_logical_kind;
3653	  break;
3654	}
3655
3656      if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3657	{
3658	  gfc_type_convert_binary (e, 1);
3659
3660	  e->ts.type = BT_LOGICAL;
3661	  e->ts.kind = gfc_default_logical_kind;
3662
3663	  if (warn_compare_reals)
3664	    {
3665	      gfc_intrinsic_op op = e->value.op.op;
3666
3667	      /* Type conversion has made sure that the types of op1 and op2
3668		 agree, so it is only necessary to check the first one.   */
3669	      if ((op1->ts.type == BT_REAL || op1->ts.type == BT_COMPLEX)
3670		  && (op == INTRINSIC_EQ || op == INTRINSIC_EQ_OS
3671		      || op == INTRINSIC_NE || op == INTRINSIC_NE_OS))
3672		{
3673		  const char *msg;
3674
3675		  if (op == INTRINSIC_EQ || op == INTRINSIC_EQ_OS)
3676		    msg = "Equality comparison for %s at %L";
3677		  else
3678		    msg = "Inequality comparison for %s at %L";
3679
3680		  gfc_warning (0, msg, gfc_typename (&op1->ts), &op1->where);
3681		}
3682	    }
3683
3684	  break;
3685	}
3686
3687      if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3688	sprintf (msg,
3689		 _("Logicals at %%L must be compared with %s instead of %s"),
3690		 (e->value.op.op == INTRINSIC_EQ
3691		  || e->value.op.op == INTRINSIC_EQ_OS)
3692		 ? ".eqv." : ".neqv.", gfc_op2string (e->value.op.op));
3693      else
3694	sprintf (msg,
3695		 _("Operands of comparison operator '%s' at %%L are %s/%s"),
3696		 gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3697		 gfc_typename (&op2->ts));
3698
3699      goto bad_op;
3700
3701    case INTRINSIC_USER:
3702      if (e->value.op.uop->op == NULL)
3703	sprintf (msg, _("Unknown operator '%s' at %%L"), e->value.op.uop->name);
3704      else if (op2 == NULL)
3705	sprintf (msg, _("Operand of user operator '%s' at %%L is %s"),
3706		 e->value.op.uop->name, gfc_typename (&op1->ts));
3707      else
3708	{
3709	  sprintf (msg, _("Operands of user operator '%s' at %%L are %s/%s"),
3710		   e->value.op.uop->name, gfc_typename (&op1->ts),
3711		   gfc_typename (&op2->ts));
3712	  e->value.op.uop->op->sym->attr.referenced = 1;
3713	}
3714
3715      goto bad_op;
3716
3717    case INTRINSIC_PARENTHESES:
3718      e->ts = op1->ts;
3719      if (e->ts.type == BT_CHARACTER)
3720	e->ts.u.cl = op1->ts.u.cl;
3721      break;
3722
3723    default:
3724      gfc_internal_error ("resolve_operator(): Bad intrinsic");
3725    }
3726
3727  /* Deal with arrayness of an operand through an operator.  */
3728
3729  t = true;
3730
3731  switch (e->value.op.op)
3732    {
3733    case INTRINSIC_PLUS:
3734    case INTRINSIC_MINUS:
3735    case INTRINSIC_TIMES:
3736    case INTRINSIC_DIVIDE:
3737    case INTRINSIC_POWER:
3738    case INTRINSIC_CONCAT:
3739    case INTRINSIC_AND:
3740    case INTRINSIC_OR:
3741    case INTRINSIC_EQV:
3742    case INTRINSIC_NEQV:
3743    case INTRINSIC_EQ:
3744    case INTRINSIC_EQ_OS:
3745    case INTRINSIC_NE:
3746    case INTRINSIC_NE_OS:
3747    case INTRINSIC_GT:
3748    case INTRINSIC_GT_OS:
3749    case INTRINSIC_GE:
3750    case INTRINSIC_GE_OS:
3751    case INTRINSIC_LT:
3752    case INTRINSIC_LT_OS:
3753    case INTRINSIC_LE:
3754    case INTRINSIC_LE_OS:
3755
3756      if (op1->rank == 0 && op2->rank == 0)
3757	e->rank = 0;
3758
3759      if (op1->rank == 0 && op2->rank != 0)
3760	{
3761	  e->rank = op2->rank;
3762
3763	  if (e->shape == NULL)
3764	    e->shape = gfc_copy_shape (op2->shape, op2->rank);
3765	}
3766
3767      if (op1->rank != 0 && op2->rank == 0)
3768	{
3769	  e->rank = op1->rank;
3770
3771	  if (e->shape == NULL)
3772	    e->shape = gfc_copy_shape (op1->shape, op1->rank);
3773	}
3774
3775      if (op1->rank != 0 && op2->rank != 0)
3776	{
3777	  if (op1->rank == op2->rank)
3778	    {
3779	      e->rank = op1->rank;
3780	      if (e->shape == NULL)
3781		{
3782		  t = compare_shapes (op1, op2);
3783		  if (!t)
3784		    e->shape = NULL;
3785		  else
3786		    e->shape = gfc_copy_shape (op1->shape, op1->rank);
3787		}
3788	    }
3789	  else
3790	    {
3791	      /* Allow higher level expressions to work.  */
3792	      e->rank = 0;
3793
3794	      /* Try user-defined operators, and otherwise throw an error.  */
3795	      dual_locus_error = true;
3796	      sprintf (msg,
3797		       _("Inconsistent ranks for operator at %%L and %%L"));
3798	      goto bad_op;
3799	    }
3800	}
3801
3802      break;
3803
3804    case INTRINSIC_PARENTHESES:
3805    case INTRINSIC_NOT:
3806    case INTRINSIC_UPLUS:
3807    case INTRINSIC_UMINUS:
3808      /* Simply copy arrayness attribute */
3809      e->rank = op1->rank;
3810
3811      if (e->shape == NULL)
3812	e->shape = gfc_copy_shape (op1->shape, op1->rank);
3813
3814      break;
3815
3816    default:
3817      break;
3818    }
3819
3820  /* Attempt to simplify the expression.  */
3821  if (t)
3822    {
3823      t = gfc_simplify_expr (e, 0);
3824      /* Some calls do not succeed in simplification and return false
3825	 even though there is no error; e.g. variable references to
3826	 PARAMETER arrays.  */
3827      if (!gfc_is_constant_expr (e))
3828	t = true;
3829    }
3830  return t;
3831
3832bad_op:
3833
3834  {
3835    match m = gfc_extend_expr (e);
3836    if (m == MATCH_YES)
3837      return true;
3838    if (m == MATCH_ERROR)
3839      return false;
3840  }
3841
3842  if (dual_locus_error)
3843    gfc_error (msg, &op1->where, &op2->where);
3844  else
3845    gfc_error (msg, &e->where);
3846
3847  return false;
3848}
3849
3850
3851/************** Array resolution subroutines **************/
3852
3853typedef enum
3854{ CMP_LT, CMP_EQ, CMP_GT, CMP_UNKNOWN }
3855compare_result;
3856
3857/* Compare two integer expressions.  */
3858
3859static compare_result
3860compare_bound (gfc_expr *a, gfc_expr *b)
3861{
3862  int i;
3863
3864  if (a == NULL || a->expr_type != EXPR_CONSTANT
3865      || b == NULL || b->expr_type != EXPR_CONSTANT)
3866    return CMP_UNKNOWN;
3867
3868  /* If either of the types isn't INTEGER, we must have
3869     raised an error earlier.  */
3870
3871  if (a->ts.type != BT_INTEGER || b->ts.type != BT_INTEGER)
3872    return CMP_UNKNOWN;
3873
3874  i = mpz_cmp (a->value.integer, b->value.integer);
3875
3876  if (i < 0)
3877    return CMP_LT;
3878  if (i > 0)
3879    return CMP_GT;
3880  return CMP_EQ;
3881}
3882
3883
3884/* Compare an integer expression with an integer.  */
3885
3886static compare_result
3887compare_bound_int (gfc_expr *a, int b)
3888{
3889  int i;
3890
3891  if (a == NULL || a->expr_type != EXPR_CONSTANT)
3892    return CMP_UNKNOWN;
3893
3894  if (a->ts.type != BT_INTEGER)
3895    gfc_internal_error ("compare_bound_int(): Bad expression");
3896
3897  i = mpz_cmp_si (a->value.integer, b);
3898
3899  if (i < 0)
3900    return CMP_LT;
3901  if (i > 0)
3902    return CMP_GT;
3903  return CMP_EQ;
3904}
3905
3906
3907/* Compare an integer expression with a mpz_t.  */
3908
3909static compare_result
3910compare_bound_mpz_t (gfc_expr *a, mpz_t b)
3911{
3912  int i;
3913
3914  if (a == NULL || a->expr_type != EXPR_CONSTANT)
3915    return CMP_UNKNOWN;
3916
3917  if (a->ts.type != BT_INTEGER)
3918    gfc_internal_error ("compare_bound_int(): Bad expression");
3919
3920  i = mpz_cmp (a->value.integer, b);
3921
3922  if (i < 0)
3923    return CMP_LT;
3924  if (i > 0)
3925    return CMP_GT;
3926  return CMP_EQ;
3927}
3928
3929
3930/* Compute the last value of a sequence given by a triplet.
3931   Return 0 if it wasn't able to compute the last value, or if the
3932   sequence if empty, and 1 otherwise.  */
3933
3934static int
3935compute_last_value_for_triplet (gfc_expr *start, gfc_expr *end,
3936				gfc_expr *stride, mpz_t last)
3937{
3938  mpz_t rem;
3939
3940  if (start == NULL || start->expr_type != EXPR_CONSTANT
3941      || end == NULL || end->expr_type != EXPR_CONSTANT
3942      || (stride != NULL && stride->expr_type != EXPR_CONSTANT))
3943    return 0;
3944
3945  if (start->ts.type != BT_INTEGER || end->ts.type != BT_INTEGER
3946      || (stride != NULL && stride->ts.type != BT_INTEGER))
3947    return 0;
3948
3949  if (stride == NULL || compare_bound_int (stride, 1) == CMP_EQ)
3950    {
3951      if (compare_bound (start, end) == CMP_GT)
3952	return 0;
3953      mpz_set (last, end->value.integer);
3954      return 1;
3955    }
3956
3957  if (compare_bound_int (stride, 0) == CMP_GT)
3958    {
3959      /* Stride is positive */
3960      if (mpz_cmp (start->value.integer, end->value.integer) > 0)
3961	return 0;
3962    }
3963  else
3964    {
3965      /* Stride is negative */
3966      if (mpz_cmp (start->value.integer, end->value.integer) < 0)
3967	return 0;
3968    }
3969
3970  mpz_init (rem);
3971  mpz_sub (rem, end->value.integer, start->value.integer);
3972  mpz_tdiv_r (rem, rem, stride->value.integer);
3973  mpz_sub (last, end->value.integer, rem);
3974  mpz_clear (rem);
3975
3976  return 1;
3977}
3978
3979
3980/* Compare a single dimension of an array reference to the array
3981   specification.  */
3982
3983static bool
3984check_dimension (int i, gfc_array_ref *ar, gfc_array_spec *as)
3985{
3986  mpz_t last_value;
3987
3988  if (ar->dimen_type[i] == DIMEN_STAR)
3989    {
3990      gcc_assert (ar->stride[i] == NULL);
3991      /* This implies [*] as [*:] and [*:3] are not possible.  */
3992      if (ar->start[i] == NULL)
3993	{
3994	  gcc_assert (ar->end[i] == NULL);
3995	  return true;
3996	}
3997    }
3998
3999/* Given start, end and stride values, calculate the minimum and
4000   maximum referenced indexes.  */
4001
4002  switch (ar->dimen_type[i])
4003    {
4004    case DIMEN_VECTOR:
4005    case DIMEN_THIS_IMAGE:
4006      break;
4007
4008    case DIMEN_STAR:
4009    case DIMEN_ELEMENT:
4010      if (compare_bound (ar->start[i], as->lower[i]) == CMP_LT)
4011	{
4012	  if (i < as->rank)
4013	    gfc_warning (0, "Array reference at %L is out of bounds "
4014			 "(%ld < %ld) in dimension %d", &ar->c_where[i],
4015			 mpz_get_si (ar->start[i]->value.integer),
4016			 mpz_get_si (as->lower[i]->value.integer), i+1);
4017	  else
4018	    gfc_warning (0, "Array reference at %L is out of bounds "
4019			 "(%ld < %ld) in codimension %d", &ar->c_where[i],
4020			 mpz_get_si (ar->start[i]->value.integer),
4021			 mpz_get_si (as->lower[i]->value.integer),
4022			 i + 1 - as->rank);
4023	  return true;
4024	}
4025      if (compare_bound (ar->start[i], as->upper[i]) == CMP_GT)
4026	{
4027	  if (i < as->rank)
4028	    gfc_warning (0, "Array reference at %L is out of bounds "
4029			 "(%ld > %ld) in dimension %d", &ar->c_where[i],
4030			 mpz_get_si (ar->start[i]->value.integer),
4031			 mpz_get_si (as->upper[i]->value.integer), i+1);
4032	  else
4033	    gfc_warning (0, "Array reference at %L is out of bounds "
4034			 "(%ld > %ld) in codimension %d", &ar->c_where[i],
4035			 mpz_get_si (ar->start[i]->value.integer),
4036			 mpz_get_si (as->upper[i]->value.integer),
4037			 i + 1 - as->rank);
4038	  return true;
4039	}
4040
4041      break;
4042
4043    case DIMEN_RANGE:
4044      {
4045#define AR_START (ar->start[i] ? ar->start[i] : as->lower[i])
4046#define AR_END (ar->end[i] ? ar->end[i] : as->upper[i])
4047
4048	compare_result comp_start_end = compare_bound (AR_START, AR_END);
4049
4050	/* Check for zero stride, which is not allowed.  */
4051	if (compare_bound_int (ar->stride[i], 0) == CMP_EQ)
4052	  {
4053	    gfc_error ("Illegal stride of zero at %L", &ar->c_where[i]);
4054	    return false;
4055	  }
4056
4057	/* if start == len || (stride > 0 && start < len)
4058			   || (stride < 0 && start > len),
4059	   then the array section contains at least one element.  In this
4060	   case, there is an out-of-bounds access if
4061	   (start < lower || start > upper).  */
4062	if (compare_bound (AR_START, AR_END) == CMP_EQ
4063	    || ((compare_bound_int (ar->stride[i], 0) == CMP_GT
4064		 || ar->stride[i] == NULL) && comp_start_end == CMP_LT)
4065	    || (compare_bound_int (ar->stride[i], 0) == CMP_LT
4066	        && comp_start_end == CMP_GT))
4067	  {
4068	    if (compare_bound (AR_START, as->lower[i]) == CMP_LT)
4069	      {
4070		gfc_warning (0, "Lower array reference at %L is out of bounds "
4071		       "(%ld < %ld) in dimension %d", &ar->c_where[i],
4072		       mpz_get_si (AR_START->value.integer),
4073		       mpz_get_si (as->lower[i]->value.integer), i+1);
4074		return true;
4075	      }
4076	    if (compare_bound (AR_START, as->upper[i]) == CMP_GT)
4077	      {
4078		gfc_warning (0, "Lower array reference at %L is out of bounds "
4079		       "(%ld > %ld) in dimension %d", &ar->c_where[i],
4080		       mpz_get_si (AR_START->value.integer),
4081		       mpz_get_si (as->upper[i]->value.integer), i+1);
4082		return true;
4083	      }
4084	  }
4085
4086	/* If we can compute the highest index of the array section,
4087	   then it also has to be between lower and upper.  */
4088	mpz_init (last_value);
4089	if (compute_last_value_for_triplet (AR_START, AR_END, ar->stride[i],
4090					    last_value))
4091	  {
4092	    if (compare_bound_mpz_t (as->lower[i], last_value) == CMP_GT)
4093	      {
4094		gfc_warning (0, "Upper array reference at %L is out of bounds "
4095		       "(%ld < %ld) in dimension %d", &ar->c_where[i],
4096		       mpz_get_si (last_value),
4097		       mpz_get_si (as->lower[i]->value.integer), i+1);
4098	        mpz_clear (last_value);
4099		return true;
4100	      }
4101	    if (compare_bound_mpz_t (as->upper[i], last_value) == CMP_LT)
4102	      {
4103		gfc_warning (0, "Upper array reference at %L is out of bounds "
4104		       "(%ld > %ld) in dimension %d", &ar->c_where[i],
4105		       mpz_get_si (last_value),
4106		       mpz_get_si (as->upper[i]->value.integer), i+1);
4107	        mpz_clear (last_value);
4108		return true;
4109	      }
4110	  }
4111	mpz_clear (last_value);
4112
4113#undef AR_START
4114#undef AR_END
4115      }
4116      break;
4117
4118    default:
4119      gfc_internal_error ("check_dimension(): Bad array reference");
4120    }
4121
4122  return true;
4123}
4124
4125
4126/* Compare an array reference with an array specification.  */
4127
4128static bool
4129compare_spec_to_ref (gfc_array_ref *ar)
4130{
4131  gfc_array_spec *as;
4132  int i;
4133
4134  as = ar->as;
4135  i = as->rank - 1;
4136  /* TODO: Full array sections are only allowed as actual parameters.  */
4137  if (as->type == AS_ASSUMED_SIZE
4138      && (/*ar->type == AR_FULL
4139	  ||*/ (ar->type == AR_SECTION
4140	      && ar->dimen_type[i] == DIMEN_RANGE && ar->end[i] == NULL)))
4141    {
4142      gfc_error ("Rightmost upper bound of assumed size array section "
4143		 "not specified at %L", &ar->where);
4144      return false;
4145    }
4146
4147  if (ar->type == AR_FULL)
4148    return true;
4149
4150  if (as->rank != ar->dimen)
4151    {
4152      gfc_error ("Rank mismatch in array reference at %L (%d/%d)",
4153		 &ar->where, ar->dimen, as->rank);
4154      return false;
4155    }
4156
4157  /* ar->codimen == 0 is a local array.  */
4158  if (as->corank != ar->codimen && ar->codimen != 0)
4159    {
4160      gfc_error ("Coindex rank mismatch in array reference at %L (%d/%d)",
4161		 &ar->where, ar->codimen, as->corank);
4162      return false;
4163    }
4164
4165  for (i = 0; i < as->rank; i++)
4166    if (!check_dimension (i, ar, as))
4167      return false;
4168
4169  /* Local access has no coarray spec.  */
4170  if (ar->codimen != 0)
4171    for (i = as->rank; i < as->rank + as->corank; i++)
4172      {
4173	if (ar->dimen_type[i] != DIMEN_ELEMENT && !ar->in_allocate
4174	    && ar->dimen_type[i] != DIMEN_THIS_IMAGE)
4175	  {
4176	    gfc_error ("Coindex of codimension %d must be a scalar at %L",
4177		       i + 1 - as->rank, &ar->where);
4178	    return false;
4179	  }
4180	if (!check_dimension (i, ar, as))
4181	  return false;
4182      }
4183
4184  return true;
4185}
4186
4187
4188/* Resolve one part of an array index.  */
4189
4190static bool
4191gfc_resolve_index_1 (gfc_expr *index, int check_scalar,
4192		     int force_index_integer_kind)
4193{
4194  gfc_typespec ts;
4195
4196  if (index == NULL)
4197    return true;
4198
4199  if (!gfc_resolve_expr (index))
4200    return false;
4201
4202  if (check_scalar && index->rank != 0)
4203    {
4204      gfc_error ("Array index at %L must be scalar", &index->where);
4205      return false;
4206    }
4207
4208  if (index->ts.type != BT_INTEGER && index->ts.type != BT_REAL)
4209    {
4210      gfc_error ("Array index at %L must be of INTEGER type, found %s",
4211		 &index->where, gfc_basic_typename (index->ts.type));
4212      return false;
4213    }
4214
4215  if (index->ts.type == BT_REAL)
4216    if (!gfc_notify_std (GFC_STD_LEGACY, "REAL array index at %L",
4217			 &index->where))
4218      return false;
4219
4220  if ((index->ts.kind != gfc_index_integer_kind
4221       && force_index_integer_kind)
4222      || index->ts.type != BT_INTEGER)
4223    {
4224      gfc_clear_ts (&ts);
4225      ts.type = BT_INTEGER;
4226      ts.kind = gfc_index_integer_kind;
4227
4228      gfc_convert_type_warn (index, &ts, 2, 0);
4229    }
4230
4231  return true;
4232}
4233
4234/* Resolve one part of an array index.  */
4235
4236bool
4237gfc_resolve_index (gfc_expr *index, int check_scalar)
4238{
4239  return gfc_resolve_index_1 (index, check_scalar, 1);
4240}
4241
4242/* Resolve a dim argument to an intrinsic function.  */
4243
4244bool
4245gfc_resolve_dim_arg (gfc_expr *dim)
4246{
4247  if (dim == NULL)
4248    return true;
4249
4250  if (!gfc_resolve_expr (dim))
4251    return false;
4252
4253  if (dim->rank != 0)
4254    {
4255      gfc_error ("Argument dim at %L must be scalar", &dim->where);
4256      return false;
4257
4258    }
4259
4260  if (dim->ts.type != BT_INTEGER)
4261    {
4262      gfc_error ("Argument dim at %L must be of INTEGER type", &dim->where);
4263      return false;
4264    }
4265
4266  if (dim->ts.kind != gfc_index_integer_kind)
4267    {
4268      gfc_typespec ts;
4269
4270      gfc_clear_ts (&ts);
4271      ts.type = BT_INTEGER;
4272      ts.kind = gfc_index_integer_kind;
4273
4274      gfc_convert_type_warn (dim, &ts, 2, 0);
4275    }
4276
4277  return true;
4278}
4279
4280/* Given an expression that contains array references, update those array
4281   references to point to the right array specifications.  While this is
4282   filled in during matching, this information is difficult to save and load
4283   in a module, so we take care of it here.
4284
4285   The idea here is that the original array reference comes from the
4286   base symbol.  We traverse the list of reference structures, setting
4287   the stored reference to references.  Component references can
4288   provide an additional array specification.  */
4289
4290static void
4291find_array_spec (gfc_expr *e)
4292{
4293  gfc_array_spec *as;
4294  gfc_component *c;
4295  gfc_ref *ref;
4296
4297  if (e->symtree->n.sym->ts.type == BT_CLASS)
4298    as = CLASS_DATA (e->symtree->n.sym)->as;
4299  else
4300    as = e->symtree->n.sym->as;
4301
4302  for (ref = e->ref; ref; ref = ref->next)
4303    switch (ref->type)
4304      {
4305      case REF_ARRAY:
4306	if (as == NULL)
4307	  gfc_internal_error ("find_array_spec(): Missing spec");
4308
4309	ref->u.ar.as = as;
4310	as = NULL;
4311	break;
4312
4313      case REF_COMPONENT:
4314	c = ref->u.c.component;
4315	if (c->attr.dimension)
4316	  {
4317	    if (as != NULL)
4318	      gfc_internal_error ("find_array_spec(): unused as(1)");
4319	    as = c->as;
4320	  }
4321
4322	break;
4323
4324      case REF_SUBSTRING:
4325	break;
4326      }
4327
4328  if (as != NULL)
4329    gfc_internal_error ("find_array_spec(): unused as(2)");
4330}
4331
4332
4333/* Resolve an array reference.  */
4334
4335static bool
4336resolve_array_ref (gfc_array_ref *ar)
4337{
4338  int i, check_scalar;
4339  gfc_expr *e;
4340
4341  for (i = 0; i < ar->dimen + ar->codimen; i++)
4342    {
4343      check_scalar = ar->dimen_type[i] == DIMEN_RANGE;
4344
4345      /* Do not force gfc_index_integer_kind for the start.  We can
4346         do fine with any integer kind.  This avoids temporary arrays
4347	 created for indexing with a vector.  */
4348      if (!gfc_resolve_index_1 (ar->start[i], check_scalar, 0))
4349	return false;
4350      if (!gfc_resolve_index (ar->end[i], check_scalar))
4351	return false;
4352      if (!gfc_resolve_index (ar->stride[i], check_scalar))
4353	return false;
4354
4355      e = ar->start[i];
4356
4357      if (ar->dimen_type[i] == DIMEN_UNKNOWN)
4358	switch (e->rank)
4359	  {
4360	  case 0:
4361	    ar->dimen_type[i] = DIMEN_ELEMENT;
4362	    break;
4363
4364	  case 1:
4365	    ar->dimen_type[i] = DIMEN_VECTOR;
4366	    if (e->expr_type == EXPR_VARIABLE
4367		&& e->symtree->n.sym->ts.type == BT_DERIVED)
4368	      ar->start[i] = gfc_get_parentheses (e);
4369	    break;
4370
4371	  default:
4372	    gfc_error ("Array index at %L is an array of rank %d",
4373		       &ar->c_where[i], e->rank);
4374	    return false;
4375	  }
4376
4377      /* Fill in the upper bound, which may be lower than the
4378	 specified one for something like a(2:10:5), which is
4379	 identical to a(2:7:5).  Only relevant for strides not equal
4380	 to one.  Don't try a division by zero.  */
4381      if (ar->dimen_type[i] == DIMEN_RANGE
4382	  && ar->stride[i] != NULL && ar->stride[i]->expr_type == EXPR_CONSTANT
4383	  && mpz_cmp_si (ar->stride[i]->value.integer, 1L) != 0
4384	  && mpz_cmp_si (ar->stride[i]->value.integer, 0L) != 0)
4385	{
4386	  mpz_t size, end;
4387
4388	  if (gfc_ref_dimen_size (ar, i, &size, &end))
4389	    {
4390	      if (ar->end[i] == NULL)
4391		{
4392		  ar->end[i] =
4393		    gfc_get_constant_expr (BT_INTEGER, gfc_index_integer_kind,
4394					   &ar->where);
4395		  mpz_set (ar->end[i]->value.integer, end);
4396		}
4397	      else if (ar->end[i]->ts.type == BT_INTEGER
4398		       && ar->end[i]->expr_type == EXPR_CONSTANT)
4399		{
4400		  mpz_set (ar->end[i]->value.integer, end);
4401		}
4402	      else
4403		gcc_unreachable ();
4404
4405	      mpz_clear (size);
4406	      mpz_clear (end);
4407	    }
4408	}
4409    }
4410
4411  if (ar->type == AR_FULL)
4412    {
4413      if (ar->as->rank == 0)
4414	ar->type = AR_ELEMENT;
4415
4416      /* Make sure array is the same as array(:,:), this way
4417	 we don't need to special case all the time.  */
4418      ar->dimen = ar->as->rank;
4419      for (i = 0; i < ar->dimen; i++)
4420	{
4421	  ar->dimen_type[i] = DIMEN_RANGE;
4422
4423	  gcc_assert (ar->start[i] == NULL);
4424	  gcc_assert (ar->end[i] == NULL);
4425	  gcc_assert (ar->stride[i] == NULL);
4426	}
4427    }
4428
4429  /* If the reference type is unknown, figure out what kind it is.  */
4430
4431  if (ar->type == AR_UNKNOWN)
4432    {
4433      ar->type = AR_ELEMENT;
4434      for (i = 0; i < ar->dimen; i++)
4435	if (ar->dimen_type[i] == DIMEN_RANGE
4436	    || ar->dimen_type[i] == DIMEN_VECTOR)
4437	  {
4438	    ar->type = AR_SECTION;
4439	    break;
4440	  }
4441    }
4442
4443  if (!ar->as->cray_pointee && !compare_spec_to_ref (ar))
4444    return false;
4445
4446  if (ar->as->corank && ar->codimen == 0)
4447    {
4448      int n;
4449      ar->codimen = ar->as->corank;
4450      for (n = ar->dimen; n < ar->dimen + ar->codimen; n++)
4451	ar->dimen_type[n] = DIMEN_THIS_IMAGE;
4452    }
4453
4454  return true;
4455}
4456
4457
4458static bool
4459resolve_substring (gfc_ref *ref)
4460{
4461  int k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
4462
4463  if (ref->u.ss.start != NULL)
4464    {
4465      if (!gfc_resolve_expr (ref->u.ss.start))
4466	return false;
4467
4468      if (ref->u.ss.start->ts.type != BT_INTEGER)
4469	{
4470	  gfc_error ("Substring start index at %L must be of type INTEGER",
4471		     &ref->u.ss.start->where);
4472	  return false;
4473	}
4474
4475      if (ref->u.ss.start->rank != 0)
4476	{
4477	  gfc_error ("Substring start index at %L must be scalar",
4478		     &ref->u.ss.start->where);
4479	  return false;
4480	}
4481
4482      if (compare_bound_int (ref->u.ss.start, 1) == CMP_LT
4483	  && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4484	      || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4485	{
4486	  gfc_error ("Substring start index at %L is less than one",
4487		     &ref->u.ss.start->where);
4488	  return false;
4489	}
4490    }
4491
4492  if (ref->u.ss.end != NULL)
4493    {
4494      if (!gfc_resolve_expr (ref->u.ss.end))
4495	return false;
4496
4497      if (ref->u.ss.end->ts.type != BT_INTEGER)
4498	{
4499	  gfc_error ("Substring end index at %L must be of type INTEGER",
4500		     &ref->u.ss.end->where);
4501	  return false;
4502	}
4503
4504      if (ref->u.ss.end->rank != 0)
4505	{
4506	  gfc_error ("Substring end index at %L must be scalar",
4507		     &ref->u.ss.end->where);
4508	  return false;
4509	}
4510
4511      if (ref->u.ss.length != NULL
4512	  && compare_bound (ref->u.ss.end, ref->u.ss.length->length) == CMP_GT
4513	  && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4514	      || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4515	{
4516	  gfc_error ("Substring end index at %L exceeds the string length",
4517		     &ref->u.ss.start->where);
4518	  return false;
4519	}
4520
4521      if (compare_bound_mpz_t (ref->u.ss.end,
4522			       gfc_integer_kinds[k].huge) == CMP_GT
4523	  && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4524	      || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4525	{
4526	  gfc_error ("Substring end index at %L is too large",
4527		     &ref->u.ss.end->where);
4528	  return false;
4529	}
4530    }
4531
4532  return true;
4533}
4534
4535
4536/* This function supplies missing substring charlens.  */
4537
4538void
4539gfc_resolve_substring_charlen (gfc_expr *e)
4540{
4541  gfc_ref *char_ref;
4542  gfc_expr *start, *end;
4543
4544  for (char_ref = e->ref; char_ref; char_ref = char_ref->next)
4545    if (char_ref->type == REF_SUBSTRING)
4546      break;
4547
4548  if (!char_ref)
4549    return;
4550
4551  gcc_assert (char_ref->next == NULL);
4552
4553  if (e->ts.u.cl)
4554    {
4555      if (e->ts.u.cl->length)
4556	gfc_free_expr (e->ts.u.cl->length);
4557      else if (e->expr_type == EXPR_VARIABLE && e->symtree->n.sym->attr.dummy)
4558	return;
4559    }
4560
4561  e->ts.type = BT_CHARACTER;
4562  e->ts.kind = gfc_default_character_kind;
4563
4564  if (!e->ts.u.cl)
4565    e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
4566
4567  if (char_ref->u.ss.start)
4568    start = gfc_copy_expr (char_ref->u.ss.start);
4569  else
4570    start = gfc_get_int_expr (gfc_default_integer_kind, NULL, 1);
4571
4572  if (char_ref->u.ss.end)
4573    end = gfc_copy_expr (char_ref->u.ss.end);
4574  else if (e->expr_type == EXPR_VARIABLE)
4575    end = gfc_copy_expr (e->symtree->n.sym->ts.u.cl->length);
4576  else
4577    end = NULL;
4578
4579  if (!start || !end)
4580    {
4581      gfc_free_expr (start);
4582      gfc_free_expr (end);
4583      return;
4584    }
4585
4586  /* Length = (end - start + 1).  */
4587  e->ts.u.cl->length = gfc_subtract (end, start);
4588  e->ts.u.cl->length = gfc_add (e->ts.u.cl->length,
4589				gfc_get_int_expr (gfc_default_integer_kind,
4590						  NULL, 1));
4591
4592  /* F2008, 6.4.1:  Both the starting point and the ending point shall
4593     be within the range 1, 2, ..., n unless the starting point exceeds
4594     the ending point, in which case the substring has length zero.  */
4595
4596  if (mpz_cmp_si (e->ts.u.cl->length->value.integer, 0) < 0)
4597    mpz_set_si (e->ts.u.cl->length->value.integer, 0);
4598
4599  e->ts.u.cl->length->ts.type = BT_INTEGER;
4600  e->ts.u.cl->length->ts.kind = gfc_charlen_int_kind;
4601
4602  /* Make sure that the length is simplified.  */
4603  gfc_simplify_expr (e->ts.u.cl->length, 1);
4604  gfc_resolve_expr (e->ts.u.cl->length);
4605}
4606
4607
4608/* Resolve subtype references.  */
4609
4610static bool
4611resolve_ref (gfc_expr *expr)
4612{
4613  int current_part_dimension, n_components, seen_part_dimension;
4614  gfc_ref *ref;
4615
4616  for (ref = expr->ref; ref; ref = ref->next)
4617    if (ref->type == REF_ARRAY && ref->u.ar.as == NULL)
4618      {
4619	find_array_spec (expr);
4620	break;
4621      }
4622
4623  for (ref = expr->ref; ref; ref = ref->next)
4624    switch (ref->type)
4625      {
4626      case REF_ARRAY:
4627	if (!resolve_array_ref (&ref->u.ar))
4628	  return false;
4629	break;
4630
4631      case REF_COMPONENT:
4632	break;
4633
4634      case REF_SUBSTRING:
4635	if (!resolve_substring (ref))
4636	  return false;
4637	break;
4638      }
4639
4640  /* Check constraints on part references.  */
4641
4642  current_part_dimension = 0;
4643  seen_part_dimension = 0;
4644  n_components = 0;
4645
4646  for (ref = expr->ref; ref; ref = ref->next)
4647    {
4648      switch (ref->type)
4649	{
4650	case REF_ARRAY:
4651	  switch (ref->u.ar.type)
4652	    {
4653	    case AR_FULL:
4654	      /* Coarray scalar.  */
4655	      if (ref->u.ar.as->rank == 0)
4656		{
4657		  current_part_dimension = 0;
4658		  break;
4659		}
4660	      /* Fall through.  */
4661	    case AR_SECTION:
4662	      current_part_dimension = 1;
4663	      break;
4664
4665	    case AR_ELEMENT:
4666	      current_part_dimension = 0;
4667	      break;
4668
4669	    case AR_UNKNOWN:
4670	      gfc_internal_error ("resolve_ref(): Bad array reference");
4671	    }
4672
4673	  break;
4674
4675	case REF_COMPONENT:
4676	  if (current_part_dimension || seen_part_dimension)
4677	    {
4678	      /* F03:C614.  */
4679	      if (ref->u.c.component->attr.pointer
4680		  || ref->u.c.component->attr.proc_pointer
4681		  || (ref->u.c.component->ts.type == BT_CLASS
4682			&& CLASS_DATA (ref->u.c.component)->attr.pointer))
4683		{
4684		  gfc_error ("Component to the right of a part reference "
4685			     "with nonzero rank must not have the POINTER "
4686			     "attribute at %L", &expr->where);
4687		  return false;
4688		}
4689	      else if (ref->u.c.component->attr.allocatable
4690			|| (ref->u.c.component->ts.type == BT_CLASS
4691			    && CLASS_DATA (ref->u.c.component)->attr.allocatable))
4692
4693		{
4694		  gfc_error ("Component to the right of a part reference "
4695			     "with nonzero rank must not have the ALLOCATABLE "
4696			     "attribute at %L", &expr->where);
4697		  return false;
4698		}
4699	    }
4700
4701	  n_components++;
4702	  break;
4703
4704	case REF_SUBSTRING:
4705	  break;
4706	}
4707
4708      if (((ref->type == REF_COMPONENT && n_components > 1)
4709	   || ref->next == NULL)
4710	  && current_part_dimension
4711	  && seen_part_dimension)
4712	{
4713	  gfc_error ("Two or more part references with nonzero rank must "
4714		     "not be specified at %L", &expr->where);
4715	  return false;
4716	}
4717
4718      if (ref->type == REF_COMPONENT)
4719	{
4720	  if (current_part_dimension)
4721	    seen_part_dimension = 1;
4722
4723	  /* reset to make sure */
4724	  current_part_dimension = 0;
4725	}
4726    }
4727
4728  return true;
4729}
4730
4731
4732/* Given an expression, determine its shape.  This is easier than it sounds.
4733   Leaves the shape array NULL if it is not possible to determine the shape.  */
4734
4735static void
4736expression_shape (gfc_expr *e)
4737{
4738  mpz_t array[GFC_MAX_DIMENSIONS];
4739  int i;
4740
4741  if (e->rank <= 0 || e->shape != NULL)
4742    return;
4743
4744  for (i = 0; i < e->rank; i++)
4745    if (!gfc_array_dimen_size (e, i, &array[i]))
4746      goto fail;
4747
4748  e->shape = gfc_get_shape (e->rank);
4749
4750  memcpy (e->shape, array, e->rank * sizeof (mpz_t));
4751
4752  return;
4753
4754fail:
4755  for (i--; i >= 0; i--)
4756    mpz_clear (array[i]);
4757}
4758
4759
4760/* Given a variable expression node, compute the rank of the expression by
4761   examining the base symbol and any reference structures it may have.  */
4762
4763static void
4764expression_rank (gfc_expr *e)
4765{
4766  gfc_ref *ref;
4767  int i, rank;
4768
4769  /* Just to make sure, because EXPR_COMPCALL's also have an e->ref and that
4770     could lead to serious confusion...  */
4771  gcc_assert (e->expr_type != EXPR_COMPCALL);
4772
4773  if (e->ref == NULL)
4774    {
4775      if (e->expr_type == EXPR_ARRAY)
4776	goto done;
4777      /* Constructors can have a rank different from one via RESHAPE().  */
4778
4779      if (e->symtree == NULL)
4780	{
4781	  e->rank = 0;
4782	  goto done;
4783	}
4784
4785      e->rank = (e->symtree->n.sym->as == NULL)
4786		? 0 : e->symtree->n.sym->as->rank;
4787      goto done;
4788    }
4789
4790  rank = 0;
4791
4792  for (ref = e->ref; ref; ref = ref->next)
4793    {
4794      if (ref->type == REF_COMPONENT && ref->u.c.component->attr.proc_pointer
4795	  && ref->u.c.component->attr.function && !ref->next)
4796	rank = ref->u.c.component->as ? ref->u.c.component->as->rank : 0;
4797
4798      if (ref->type != REF_ARRAY)
4799	continue;
4800
4801      if (ref->u.ar.type == AR_FULL)
4802	{
4803	  rank = ref->u.ar.as->rank;
4804	  break;
4805	}
4806
4807      if (ref->u.ar.type == AR_SECTION)
4808	{
4809	  /* Figure out the rank of the section.  */
4810	  if (rank != 0)
4811	    gfc_internal_error ("expression_rank(): Two array specs");
4812
4813	  for (i = 0; i < ref->u.ar.dimen; i++)
4814	    if (ref->u.ar.dimen_type[i] == DIMEN_RANGE
4815		|| ref->u.ar.dimen_type[i] == DIMEN_VECTOR)
4816	      rank++;
4817
4818	  break;
4819	}
4820    }
4821
4822  e->rank = rank;
4823
4824done:
4825  expression_shape (e);
4826}
4827
4828
4829static void
4830add_caf_get_intrinsic (gfc_expr *e)
4831{
4832  gfc_expr *wrapper, *tmp_expr;
4833  gfc_ref *ref;
4834  int n;
4835
4836  for (ref = e->ref; ref; ref = ref->next)
4837    if (ref->type == REF_ARRAY && ref->u.ar.codimen > 0)
4838      break;
4839  if (ref == NULL)
4840    return;
4841
4842  for (n = ref->u.ar.dimen; n < ref->u.ar.dimen + ref->u.ar.codimen; n++)
4843    if (ref->u.ar.dimen_type[n] != DIMEN_ELEMENT)
4844      return;
4845
4846  tmp_expr = XCNEW (gfc_expr);
4847  *tmp_expr = *e;
4848  wrapper = gfc_build_intrinsic_call (gfc_current_ns, GFC_ISYM_CAF_GET,
4849				      "caf_get", tmp_expr->where, 1, tmp_expr);
4850  wrapper->ts = e->ts;
4851  wrapper->rank = e->rank;
4852  if (e->rank)
4853    wrapper->shape = gfc_copy_shape (e->shape, e->rank);
4854  *e = *wrapper;
4855  free (wrapper);
4856}
4857
4858
4859static void
4860remove_caf_get_intrinsic (gfc_expr *e)
4861{
4862  gcc_assert (e->expr_type == EXPR_FUNCTION && e->value.function.isym
4863	      && e->value.function.isym->id == GFC_ISYM_CAF_GET);
4864  gfc_expr *e2 = e->value.function.actual->expr;
4865  e->value.function.actual->expr = NULL;
4866  gfc_free_actual_arglist (e->value.function.actual);
4867  gfc_free_shape (&e->shape, e->rank);
4868  *e = *e2;
4869  free (e2);
4870}
4871
4872
4873/* Resolve a variable expression.  */
4874
4875static bool
4876resolve_variable (gfc_expr *e)
4877{
4878  gfc_symbol *sym;
4879  bool t;
4880
4881  t = true;
4882
4883  if (e->symtree == NULL)
4884    return false;
4885  sym = e->symtree->n.sym;
4886
4887  /* Use same check as for TYPE(*) below; this check has to be before TYPE(*)
4888     as ts.type is set to BT_ASSUMED in resolve_symbol.  */
4889  if (sym->attr.ext_attr & (1 << EXT_ATTR_NO_ARG_CHECK))
4890    {
4891      if (!actual_arg || inquiry_argument)
4892	{
4893	  gfc_error ("Variable %s at %L with NO_ARG_CHECK attribute may only "
4894		     "be used as actual argument", sym->name, &e->where);
4895	  return false;
4896	}
4897    }
4898  /* TS 29113, 407b.  */
4899  else if (e->ts.type == BT_ASSUMED)
4900    {
4901      if (!actual_arg)
4902	{
4903	  gfc_error ("Assumed-type variable %s at %L may only be used "
4904		     "as actual argument", sym->name, &e->where);
4905	  return false;
4906	}
4907      else if (inquiry_argument && !first_actual_arg)
4908	{
4909	  /* FIXME: It doesn't work reliably as inquiry_argument is not set
4910	     for all inquiry functions in resolve_function; the reason is
4911	     that the function-name resolution happens too late in that
4912	     function.  */
4913	  gfc_error ("Assumed-type variable %s at %L as actual argument to "
4914		     "an inquiry function shall be the first argument",
4915		     sym->name, &e->where);
4916	  return false;
4917	}
4918    }
4919  /* TS 29113, C535b.  */
4920  else if ((sym->ts.type == BT_CLASS && sym->attr.class_ok
4921	    && CLASS_DATA (sym)->as
4922	    && CLASS_DATA (sym)->as->type == AS_ASSUMED_RANK)
4923	   || (sym->ts.type != BT_CLASS && sym->as
4924	       && sym->as->type == AS_ASSUMED_RANK))
4925    {
4926      if (!actual_arg)
4927	{
4928	  gfc_error ("Assumed-rank variable %s at %L may only be used as "
4929		     "actual argument", sym->name, &e->where);
4930	  return false;
4931	}
4932      else if (inquiry_argument && !first_actual_arg)
4933	{
4934	  /* FIXME: It doesn't work reliably as inquiry_argument is not set
4935	     for all inquiry functions in resolve_function; the reason is
4936	     that the function-name resolution happens too late in that
4937	     function.  */
4938	  gfc_error ("Assumed-rank variable %s at %L as actual argument "
4939		     "to an inquiry function shall be the first argument",
4940		     sym->name, &e->where);
4941	  return false;
4942	}
4943    }
4944
4945  if ((sym->attr.ext_attr & (1 << EXT_ATTR_NO_ARG_CHECK)) && e->ref
4946      && !(e->ref->type == REF_ARRAY && e->ref->u.ar.type == AR_FULL
4947	   && e->ref->next == NULL))
4948    {
4949      gfc_error ("Variable %s at %L with NO_ARG_CHECK attribute shall not have "
4950		 "a subobject reference", sym->name, &e->ref->u.ar.where);
4951      return false;
4952    }
4953  /* TS 29113, 407b.  */
4954  else if (e->ts.type == BT_ASSUMED && e->ref
4955	   && !(e->ref->type == REF_ARRAY && e->ref->u.ar.type == AR_FULL
4956		&& e->ref->next == NULL))
4957    {
4958      gfc_error ("Assumed-type variable %s at %L shall not have a subobject "
4959		 "reference", sym->name, &e->ref->u.ar.where);
4960      return false;
4961    }
4962
4963  /* TS 29113, C535b.  */
4964  if (((sym->ts.type == BT_CLASS && sym->attr.class_ok
4965	&& CLASS_DATA (sym)->as
4966	&& CLASS_DATA (sym)->as->type == AS_ASSUMED_RANK)
4967       || (sym->ts.type != BT_CLASS && sym->as
4968	   && sym->as->type == AS_ASSUMED_RANK))
4969      && e->ref
4970      && !(e->ref->type == REF_ARRAY && e->ref->u.ar.type == AR_FULL
4971	   && e->ref->next == NULL))
4972    {
4973      gfc_error ("Assumed-rank variable %s at %L shall not have a subobject "
4974		 "reference", sym->name, &e->ref->u.ar.where);
4975      return false;
4976    }
4977
4978
4979  /* If this is an associate-name, it may be parsed with an array reference
4980     in error even though the target is scalar.  Fail directly in this case.
4981     TODO Understand why class scalar expressions must be excluded.  */
4982  if (sym->assoc && !(sym->ts.type == BT_CLASS && e->rank == 0))
4983    {
4984      if (sym->ts.type == BT_CLASS)
4985	gfc_fix_class_refs (e);
4986      if (!sym->attr.dimension && e->ref && e->ref->type == REF_ARRAY)
4987	return false;
4988    }
4989
4990  if (sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.generic)
4991    sym->ts.u.derived = gfc_find_dt_in_generic (sym->ts.u.derived);
4992
4993  /* On the other hand, the parser may not have known this is an array;
4994     in this case, we have to add a FULL reference.  */
4995  if (sym->assoc && sym->attr.dimension && !e->ref)
4996    {
4997      e->ref = gfc_get_ref ();
4998      e->ref->type = REF_ARRAY;
4999      e->ref->u.ar.type = AR_FULL;
5000      e->ref->u.ar.dimen = 0;
5001    }
5002
5003  if (e->ref && !resolve_ref (e))
5004    return false;
5005
5006  if (sym->attr.flavor == FL_PROCEDURE
5007      && (!sym->attr.function
5008	  || (sym->attr.function && sym->result
5009	      && sym->result->attr.proc_pointer
5010	      && !sym->result->attr.function)))
5011    {
5012      e->ts.type = BT_PROCEDURE;
5013      goto resolve_procedure;
5014    }
5015
5016  if (sym->ts.type != BT_UNKNOWN)
5017    gfc_variable_attr (e, &e->ts);
5018  else
5019    {
5020      /* Must be a simple variable reference.  */
5021      if (!gfc_set_default_type (sym, 1, sym->ns))
5022	return false;
5023      e->ts = sym->ts;
5024    }
5025
5026  if (check_assumed_size_reference (sym, e))
5027    return false;
5028
5029  /* Deal with forward references to entries during gfc_resolve_code, to
5030     satisfy, at least partially, 12.5.2.5.  */
5031  if (gfc_current_ns->entries
5032      && current_entry_id == sym->entry_id
5033      && cs_base
5034      && cs_base->current
5035      && cs_base->current->op != EXEC_ENTRY)
5036    {
5037      gfc_entry_list *entry;
5038      gfc_formal_arglist *formal;
5039      int n;
5040      bool seen, saved_specification_expr;
5041
5042      /* If the symbol is a dummy...  */
5043      if (sym->attr.dummy && sym->ns == gfc_current_ns)
5044	{
5045	  entry = gfc_current_ns->entries;
5046	  seen = false;
5047
5048	  /* ...test if the symbol is a parameter of previous entries.  */
5049	  for (; entry && entry->id <= current_entry_id; entry = entry->next)
5050	    for (formal = entry->sym->formal; formal; formal = formal->next)
5051	      {
5052		if (formal->sym && sym->name == formal->sym->name)
5053		  {
5054		    seen = true;
5055		    break;
5056		  }
5057	      }
5058
5059	  /*  If it has not been seen as a dummy, this is an error.  */
5060	  if (!seen)
5061	    {
5062	      if (specification_expr)
5063		gfc_error ("Variable %qs, used in a specification expression"
5064			   ", is referenced at %L before the ENTRY statement "
5065			   "in which it is a parameter",
5066			   sym->name, &cs_base->current->loc);
5067	      else
5068		gfc_error ("Variable %qs is used at %L before the ENTRY "
5069			   "statement in which it is a parameter",
5070			   sym->name, &cs_base->current->loc);
5071	      t = false;
5072	    }
5073	}
5074
5075      /* Now do the same check on the specification expressions.  */
5076      saved_specification_expr = specification_expr;
5077      specification_expr = true;
5078      if (sym->ts.type == BT_CHARACTER
5079	  && !gfc_resolve_expr (sym->ts.u.cl->length))
5080	t = false;
5081
5082      if (sym->as)
5083	for (n = 0; n < sym->as->rank; n++)
5084	  {
5085	     if (!gfc_resolve_expr (sym->as->lower[n]))
5086	       t = false;
5087	     if (!gfc_resolve_expr (sym->as->upper[n]))
5088	       t = false;
5089	  }
5090      specification_expr = saved_specification_expr;
5091
5092      if (t)
5093	/* Update the symbol's entry level.  */
5094	sym->entry_id = current_entry_id + 1;
5095    }
5096
5097  /* If a symbol has been host_associated mark it.  This is used latter,
5098     to identify if aliasing is possible via host association.  */
5099  if (sym->attr.flavor == FL_VARIABLE
5100	&& gfc_current_ns->parent
5101	&& (gfc_current_ns->parent == sym->ns
5102	      || (gfc_current_ns->parent->parent
5103		    && gfc_current_ns->parent->parent == sym->ns)))
5104    sym->attr.host_assoc = 1;
5105
5106  if (gfc_current_ns->proc_name
5107      && sym->attr.dimension
5108      && (sym->ns != gfc_current_ns
5109	  || sym->attr.use_assoc
5110	  || sym->attr.in_common))
5111    gfc_current_ns->proc_name->attr.array_outer_dependency = 1;
5112
5113resolve_procedure:
5114  if (t && !resolve_procedure_expression (e))
5115    t = false;
5116
5117  /* F2008, C617 and C1229.  */
5118  if (!inquiry_argument && (e->ts.type == BT_CLASS || e->ts.type == BT_DERIVED)
5119      && gfc_is_coindexed (e))
5120    {
5121      gfc_ref *ref, *ref2 = NULL;
5122
5123      for (ref = e->ref; ref; ref = ref->next)
5124	{
5125	  if (ref->type == REF_COMPONENT)
5126	    ref2 = ref;
5127	  if (ref->type == REF_ARRAY && ref->u.ar.codimen > 0)
5128	    break;
5129	}
5130
5131      for ( ; ref; ref = ref->next)
5132	if (ref->type == REF_COMPONENT)
5133	  break;
5134
5135      /* Expression itself is not coindexed object.  */
5136      if (ref && e->ts.type == BT_CLASS)
5137	{
5138	  gfc_error ("Polymorphic subobject of coindexed object at %L",
5139		     &e->where);
5140	  t = false;
5141	}
5142
5143      /* Expression itself is coindexed object.  */
5144      if (ref == NULL)
5145	{
5146	  gfc_component *c;
5147	  c = ref2 ? ref2->u.c.component : e->symtree->n.sym->components;
5148	  for ( ; c; c = c->next)
5149	    if (c->attr.allocatable && c->ts.type == BT_CLASS)
5150	      {
5151		gfc_error ("Coindexed object with polymorphic allocatable "
5152			 "subcomponent at %L", &e->where);
5153		t = false;
5154		break;
5155	      }
5156	}
5157    }
5158
5159  if (t)
5160    expression_rank (e);
5161
5162  if (t && flag_coarray == GFC_FCOARRAY_LIB && gfc_is_coindexed (e))
5163    add_caf_get_intrinsic (e);
5164
5165  return t;
5166}
5167
5168
5169/* Checks to see that the correct symbol has been host associated.
5170   The only situation where this arises is that in which a twice
5171   contained function is parsed after the host association is made.
5172   Therefore, on detecting this, change the symbol in the expression
5173   and convert the array reference into an actual arglist if the old
5174   symbol is a variable.  */
5175static bool
5176check_host_association (gfc_expr *e)
5177{
5178  gfc_symbol *sym, *old_sym;
5179  gfc_symtree *st;
5180  int n;
5181  gfc_ref *ref;
5182  gfc_actual_arglist *arg, *tail = NULL;
5183  bool retval = e->expr_type == EXPR_FUNCTION;
5184
5185  /*  If the expression is the result of substitution in
5186      interface.c(gfc_extend_expr) because there is no way in
5187      which the host association can be wrong.  */
5188  if (e->symtree == NULL
5189	|| e->symtree->n.sym == NULL
5190	|| e->user_operator)
5191    return retval;
5192
5193  old_sym = e->symtree->n.sym;
5194
5195  if (gfc_current_ns->parent
5196	&& old_sym->ns != gfc_current_ns)
5197    {
5198      /* Use the 'USE' name so that renamed module symbols are
5199	 correctly handled.  */
5200      gfc_find_symbol (e->symtree->name, gfc_current_ns, 1, &sym);
5201
5202      if (sym && old_sym != sym
5203	      && sym->ts.type == old_sym->ts.type
5204	      && sym->attr.flavor == FL_PROCEDURE
5205	      && sym->attr.contained)
5206	{
5207	  /* Clear the shape, since it might not be valid.  */
5208	  gfc_free_shape (&e->shape, e->rank);
5209
5210	  /* Give the expression the right symtree!  */
5211	  gfc_find_sym_tree (e->symtree->name, NULL, 1, &st);
5212	  gcc_assert (st != NULL);
5213
5214	  if (old_sym->attr.flavor == FL_PROCEDURE
5215		|| e->expr_type == EXPR_FUNCTION)
5216  	    {
5217	      /* Original was function so point to the new symbol, since
5218		 the actual argument list is already attached to the
5219		 expression.  */
5220	      e->value.function.esym = NULL;
5221	      e->symtree = st;
5222	    }
5223	  else
5224	    {
5225	      /* Original was variable so convert array references into
5226		 an actual arglist. This does not need any checking now
5227		 since resolve_function will take care of it.  */
5228	      e->value.function.actual = NULL;
5229	      e->expr_type = EXPR_FUNCTION;
5230	      e->symtree = st;
5231
5232	      /* Ambiguity will not arise if the array reference is not
5233		 the last reference.  */
5234	      for (ref = e->ref; ref; ref = ref->next)
5235		if (ref->type == REF_ARRAY && ref->next == NULL)
5236		  break;
5237
5238	      gcc_assert (ref->type == REF_ARRAY);
5239
5240	      /* Grab the start expressions from the array ref and
5241		 copy them into actual arguments.  */
5242	      for (n = 0; n < ref->u.ar.dimen; n++)
5243		{
5244		  arg = gfc_get_actual_arglist ();
5245		  arg->expr = gfc_copy_expr (ref->u.ar.start[n]);
5246		  if (e->value.function.actual == NULL)
5247		    tail = e->value.function.actual = arg;
5248	          else
5249		    {
5250		      tail->next = arg;
5251		      tail = arg;
5252		    }
5253		}
5254
5255	      /* Dump the reference list and set the rank.  */
5256	      gfc_free_ref_list (e->ref);
5257	      e->ref = NULL;
5258	      e->rank = sym->as ? sym->as->rank : 0;
5259	    }
5260
5261	  gfc_resolve_expr (e);
5262	  sym->refs++;
5263	}
5264    }
5265  /* This might have changed!  */
5266  return e->expr_type == EXPR_FUNCTION;
5267}
5268
5269
5270static void
5271gfc_resolve_character_operator (gfc_expr *e)
5272{
5273  gfc_expr *op1 = e->value.op.op1;
5274  gfc_expr *op2 = e->value.op.op2;
5275  gfc_expr *e1 = NULL;
5276  gfc_expr *e2 = NULL;
5277
5278  gcc_assert (e->value.op.op == INTRINSIC_CONCAT);
5279
5280  if (op1->ts.u.cl && op1->ts.u.cl->length)
5281    e1 = gfc_copy_expr (op1->ts.u.cl->length);
5282  else if (op1->expr_type == EXPR_CONSTANT)
5283    e1 = gfc_get_int_expr (gfc_default_integer_kind, NULL,
5284			   op1->value.character.length);
5285
5286  if (op2->ts.u.cl && op2->ts.u.cl->length)
5287    e2 = gfc_copy_expr (op2->ts.u.cl->length);
5288  else if (op2->expr_type == EXPR_CONSTANT)
5289    e2 = gfc_get_int_expr (gfc_default_integer_kind, NULL,
5290			   op2->value.character.length);
5291
5292  e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
5293
5294  if (!e1 || !e2)
5295    {
5296      gfc_free_expr (e1);
5297      gfc_free_expr (e2);
5298
5299      return;
5300    }
5301
5302  e->ts.u.cl->length = gfc_add (e1, e2);
5303  e->ts.u.cl->length->ts.type = BT_INTEGER;
5304  e->ts.u.cl->length->ts.kind = gfc_charlen_int_kind;
5305  gfc_simplify_expr (e->ts.u.cl->length, 0);
5306  gfc_resolve_expr (e->ts.u.cl->length);
5307
5308  return;
5309}
5310
5311
5312/*  Ensure that an character expression has a charlen and, if possible, a
5313    length expression.  */
5314
5315static void
5316fixup_charlen (gfc_expr *e)
5317{
5318  /* The cases fall through so that changes in expression type and the need
5319     for multiple fixes are picked up.  In all circumstances, a charlen should
5320     be available for the middle end to hang a backend_decl on.  */
5321  switch (e->expr_type)
5322    {
5323    case EXPR_OP:
5324      gfc_resolve_character_operator (e);
5325
5326    case EXPR_ARRAY:
5327      if (e->expr_type == EXPR_ARRAY)
5328	gfc_resolve_character_array_constructor (e);
5329
5330    case EXPR_SUBSTRING:
5331      if (!e->ts.u.cl && e->ref)
5332	gfc_resolve_substring_charlen (e);
5333
5334    default:
5335      if (!e->ts.u.cl)
5336	e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
5337
5338      break;
5339    }
5340}
5341
5342
5343/* Update an actual argument to include the passed-object for type-bound
5344   procedures at the right position.  */
5345
5346static gfc_actual_arglist*
5347update_arglist_pass (gfc_actual_arglist* lst, gfc_expr* po, unsigned argpos,
5348		     const char *name)
5349{
5350  gcc_assert (argpos > 0);
5351
5352  if (argpos == 1)
5353    {
5354      gfc_actual_arglist* result;
5355
5356      result = gfc_get_actual_arglist ();
5357      result->expr = po;
5358      result->next = lst;
5359      if (name)
5360        result->name = name;
5361
5362      return result;
5363    }
5364
5365  if (lst)
5366    lst->next = update_arglist_pass (lst->next, po, argpos - 1, name);
5367  else
5368    lst = update_arglist_pass (NULL, po, argpos - 1, name);
5369  return lst;
5370}
5371
5372
5373/* Extract the passed-object from an EXPR_COMPCALL (a copy of it).  */
5374
5375static gfc_expr*
5376extract_compcall_passed_object (gfc_expr* e)
5377{
5378  gfc_expr* po;
5379
5380  gcc_assert (e->expr_type == EXPR_COMPCALL);
5381
5382  if (e->value.compcall.base_object)
5383    po = gfc_copy_expr (e->value.compcall.base_object);
5384  else
5385    {
5386      po = gfc_get_expr ();
5387      po->expr_type = EXPR_VARIABLE;
5388      po->symtree = e->symtree;
5389      po->ref = gfc_copy_ref (e->ref);
5390      po->where = e->where;
5391    }
5392
5393  if (!gfc_resolve_expr (po))
5394    return NULL;
5395
5396  return po;
5397}
5398
5399
5400/* Update the arglist of an EXPR_COMPCALL expression to include the
5401   passed-object.  */
5402
5403static bool
5404update_compcall_arglist (gfc_expr* e)
5405{
5406  gfc_expr* po;
5407  gfc_typebound_proc* tbp;
5408
5409  tbp = e->value.compcall.tbp;
5410
5411  if (tbp->error)
5412    return false;
5413
5414  po = extract_compcall_passed_object (e);
5415  if (!po)
5416    return false;
5417
5418  if (tbp->nopass || e->value.compcall.ignore_pass)
5419    {
5420      gfc_free_expr (po);
5421      return true;
5422    }
5423
5424  gcc_assert (tbp->pass_arg_num > 0);
5425  e->value.compcall.actual = update_arglist_pass (e->value.compcall.actual, po,
5426						  tbp->pass_arg_num,
5427						  tbp->pass_arg);
5428
5429  return true;
5430}
5431
5432
5433/* Extract the passed object from a PPC call (a copy of it).  */
5434
5435static gfc_expr*
5436extract_ppc_passed_object (gfc_expr *e)
5437{
5438  gfc_expr *po;
5439  gfc_ref **ref;
5440
5441  po = gfc_get_expr ();
5442  po->expr_type = EXPR_VARIABLE;
5443  po->symtree = e->symtree;
5444  po->ref = gfc_copy_ref (e->ref);
5445  po->where = e->where;
5446
5447  /* Remove PPC reference.  */
5448  ref = &po->ref;
5449  while ((*ref)->next)
5450    ref = &(*ref)->next;
5451  gfc_free_ref_list (*ref);
5452  *ref = NULL;
5453
5454  if (!gfc_resolve_expr (po))
5455    return NULL;
5456
5457  return po;
5458}
5459
5460
5461/* Update the actual arglist of a procedure pointer component to include the
5462   passed-object.  */
5463
5464static bool
5465update_ppc_arglist (gfc_expr* e)
5466{
5467  gfc_expr* po;
5468  gfc_component *ppc;
5469  gfc_typebound_proc* tb;
5470
5471  ppc = gfc_get_proc_ptr_comp (e);
5472  if (!ppc)
5473    return false;
5474
5475  tb = ppc->tb;
5476
5477  if (tb->error)
5478    return false;
5479  else if (tb->nopass)
5480    return true;
5481
5482  po = extract_ppc_passed_object (e);
5483  if (!po)
5484    return false;
5485
5486  /* F08:R739.  */
5487  if (po->rank != 0)
5488    {
5489      gfc_error ("Passed-object at %L must be scalar", &e->where);
5490      return false;
5491    }
5492
5493  /* F08:C611.  */
5494  if (po->ts.type == BT_DERIVED && po->ts.u.derived->attr.abstract)
5495    {
5496      gfc_error ("Base object for procedure-pointer component call at %L is of"
5497		 " ABSTRACT type %qs", &e->where, po->ts.u.derived->name);
5498      return false;
5499    }
5500
5501  gcc_assert (tb->pass_arg_num > 0);
5502  e->value.compcall.actual = update_arglist_pass (e->value.compcall.actual, po,
5503						  tb->pass_arg_num,
5504						  tb->pass_arg);
5505
5506  return true;
5507}
5508
5509
5510/* Check that the object a TBP is called on is valid, i.e. it must not be
5511   of ABSTRACT type (as in subobject%abstract_parent%tbp()).  */
5512
5513static bool
5514check_typebound_baseobject (gfc_expr* e)
5515{
5516  gfc_expr* base;
5517  bool return_value = false;
5518
5519  base = extract_compcall_passed_object (e);
5520  if (!base)
5521    return false;
5522
5523  gcc_assert (base->ts.type == BT_DERIVED || base->ts.type == BT_CLASS);
5524
5525  if (base->ts.type == BT_CLASS && !gfc_expr_attr (base).class_ok)
5526    return false;
5527
5528  /* F08:C611.  */
5529  if (base->ts.type == BT_DERIVED && base->ts.u.derived->attr.abstract)
5530    {
5531      gfc_error ("Base object for type-bound procedure call at %L is of"
5532		 " ABSTRACT type %qs", &e->where, base->ts.u.derived->name);
5533      goto cleanup;
5534    }
5535
5536  /* F08:C1230. If the procedure called is NOPASS,
5537     the base object must be scalar.  */
5538  if (e->value.compcall.tbp->nopass && base->rank != 0)
5539    {
5540      gfc_error ("Base object for NOPASS type-bound procedure call at %L must"
5541		 " be scalar", &e->where);
5542      goto cleanup;
5543    }
5544
5545  return_value = true;
5546
5547cleanup:
5548  gfc_free_expr (base);
5549  return return_value;
5550}
5551
5552
5553/* Resolve a call to a type-bound procedure, either function or subroutine,
5554   statically from the data in an EXPR_COMPCALL expression.  The adapted
5555   arglist and the target-procedure symtree are returned.  */
5556
5557static bool
5558resolve_typebound_static (gfc_expr* e, gfc_symtree** target,
5559			  gfc_actual_arglist** actual)
5560{
5561  gcc_assert (e->expr_type == EXPR_COMPCALL);
5562  gcc_assert (!e->value.compcall.tbp->is_generic);
5563
5564  /* Update the actual arglist for PASS.  */
5565  if (!update_compcall_arglist (e))
5566    return false;
5567
5568  *actual = e->value.compcall.actual;
5569  *target = e->value.compcall.tbp->u.specific;
5570
5571  gfc_free_ref_list (e->ref);
5572  e->ref = NULL;
5573  e->value.compcall.actual = NULL;
5574
5575  /* If we find a deferred typebound procedure, check for derived types
5576     that an overriding typebound procedure has not been missed.  */
5577  if (e->value.compcall.name
5578      && !e->value.compcall.tbp->non_overridable
5579      && e->value.compcall.base_object
5580      && e->value.compcall.base_object->ts.type == BT_DERIVED)
5581    {
5582      gfc_symtree *st;
5583      gfc_symbol *derived;
5584
5585      /* Use the derived type of the base_object.  */
5586      derived = e->value.compcall.base_object->ts.u.derived;
5587      st = NULL;
5588
5589      /* If necessary, go through the inheritance chain.  */
5590      while (!st && derived)
5591	{
5592	  /* Look for the typebound procedure 'name'.  */
5593	  if (derived->f2k_derived && derived->f2k_derived->tb_sym_root)
5594	    st = gfc_find_symtree (derived->f2k_derived->tb_sym_root,
5595				   e->value.compcall.name);
5596	  if (!st)
5597	    derived = gfc_get_derived_super_type (derived);
5598	}
5599
5600      /* Now find the specific name in the derived type namespace.  */
5601      if (st && st->n.tb && st->n.tb->u.specific)
5602	gfc_find_sym_tree (st->n.tb->u.specific->name,
5603			   derived->ns, 1, &st);
5604      if (st)
5605	*target = st;
5606    }
5607  return true;
5608}
5609
5610
5611/* Get the ultimate declared type from an expression.  In addition,
5612   return the last class/derived type reference and the copy of the
5613   reference list.  If check_types is set true, derived types are
5614   identified as well as class references.  */
5615static gfc_symbol*
5616get_declared_from_expr (gfc_ref **class_ref, gfc_ref **new_ref,
5617			gfc_expr *e, bool check_types)
5618{
5619  gfc_symbol *declared;
5620  gfc_ref *ref;
5621
5622  declared = NULL;
5623  if (class_ref)
5624    *class_ref = NULL;
5625  if (new_ref)
5626    *new_ref = gfc_copy_ref (e->ref);
5627
5628  for (ref = e->ref; ref; ref = ref->next)
5629    {
5630      if (ref->type != REF_COMPONENT)
5631	continue;
5632
5633      if ((ref->u.c.component->ts.type == BT_CLASS
5634	     || (check_types && ref->u.c.component->ts.type == BT_DERIVED))
5635	  && ref->u.c.component->attr.flavor != FL_PROCEDURE)
5636	{
5637	  declared = ref->u.c.component->ts.u.derived;
5638	  if (class_ref)
5639	    *class_ref = ref;
5640	}
5641    }
5642
5643  if (declared == NULL)
5644    declared = e->symtree->n.sym->ts.u.derived;
5645
5646  return declared;
5647}
5648
5649
5650/* Given an EXPR_COMPCALL calling a GENERIC typebound procedure, figure out
5651   which of the specific bindings (if any) matches the arglist and transform
5652   the expression into a call of that binding.  */
5653
5654static bool
5655resolve_typebound_generic_call (gfc_expr* e, const char **name)
5656{
5657  gfc_typebound_proc* genproc;
5658  const char* genname;
5659  gfc_symtree *st;
5660  gfc_symbol *derived;
5661
5662  gcc_assert (e->expr_type == EXPR_COMPCALL);
5663  genname = e->value.compcall.name;
5664  genproc = e->value.compcall.tbp;
5665
5666  if (!genproc->is_generic)
5667    return true;
5668
5669  /* Try the bindings on this type and in the inheritance hierarchy.  */
5670  for (; genproc; genproc = genproc->overridden)
5671    {
5672      gfc_tbp_generic* g;
5673
5674      gcc_assert (genproc->is_generic);
5675      for (g = genproc->u.generic; g; g = g->next)
5676	{
5677	  gfc_symbol* target;
5678	  gfc_actual_arglist* args;
5679	  bool matches;
5680
5681	  gcc_assert (g->specific);
5682
5683	  if (g->specific->error)
5684	    continue;
5685
5686	  target = g->specific->u.specific->n.sym;
5687
5688	  /* Get the right arglist by handling PASS/NOPASS.  */
5689	  args = gfc_copy_actual_arglist (e->value.compcall.actual);
5690	  if (!g->specific->nopass)
5691	    {
5692	      gfc_expr* po;
5693	      po = extract_compcall_passed_object (e);
5694	      if (!po)
5695		{
5696		  gfc_free_actual_arglist (args);
5697		  return false;
5698		}
5699
5700	      gcc_assert (g->specific->pass_arg_num > 0);
5701	      gcc_assert (!g->specific->error);
5702	      args = update_arglist_pass (args, po, g->specific->pass_arg_num,
5703					  g->specific->pass_arg);
5704	    }
5705	  resolve_actual_arglist (args, target->attr.proc,
5706				  is_external_proc (target)
5707				  && gfc_sym_get_dummy_args (target) == NULL);
5708
5709	  /* Check if this arglist matches the formal.  */
5710	  matches = gfc_arglist_matches_symbol (&args, target);
5711
5712	  /* Clean up and break out of the loop if we've found it.  */
5713	  gfc_free_actual_arglist (args);
5714	  if (matches)
5715	    {
5716	      e->value.compcall.tbp = g->specific;
5717	      genname = g->specific_st->name;
5718	      /* Pass along the name for CLASS methods, where the vtab
5719		 procedure pointer component has to be referenced.  */
5720	      if (name)
5721		*name = genname;
5722	      goto success;
5723	    }
5724	}
5725    }
5726
5727  /* Nothing matching found!  */
5728  gfc_error ("Found no matching specific binding for the call to the GENERIC"
5729	     " %qs at %L", genname, &e->where);
5730  return false;
5731
5732success:
5733  /* Make sure that we have the right specific instance for the name.  */
5734  derived = get_declared_from_expr (NULL, NULL, e, true);
5735
5736  st = gfc_find_typebound_proc (derived, NULL, genname, true, &e->where);
5737  if (st)
5738    e->value.compcall.tbp = st->n.tb;
5739
5740  return true;
5741}
5742
5743
5744/* Resolve a call to a type-bound subroutine.  */
5745
5746static bool
5747resolve_typebound_call (gfc_code* c, const char **name, bool *overridable)
5748{
5749  gfc_actual_arglist* newactual;
5750  gfc_symtree* target;
5751
5752  /* Check that's really a SUBROUTINE.  */
5753  if (!c->expr1->value.compcall.tbp->subroutine)
5754    {
5755      gfc_error ("%qs at %L should be a SUBROUTINE",
5756		 c->expr1->value.compcall.name, &c->loc);
5757      return false;
5758    }
5759
5760  if (!check_typebound_baseobject (c->expr1))
5761    return false;
5762
5763  /* Pass along the name for CLASS methods, where the vtab
5764     procedure pointer component has to be referenced.  */
5765  if (name)
5766    *name = c->expr1->value.compcall.name;
5767
5768  if (!resolve_typebound_generic_call (c->expr1, name))
5769    return false;
5770
5771  /* Pass along the NON_OVERRIDABLE attribute of the specific TBP. */
5772  if (overridable)
5773    *overridable = !c->expr1->value.compcall.tbp->non_overridable;
5774
5775  /* Transform into an ordinary EXEC_CALL for now.  */
5776
5777  if (!resolve_typebound_static (c->expr1, &target, &newactual))
5778    return false;
5779
5780  c->ext.actual = newactual;
5781  c->symtree = target;
5782  c->op = (c->expr1->value.compcall.assign ? EXEC_ASSIGN_CALL : EXEC_CALL);
5783
5784  gcc_assert (!c->expr1->ref && !c->expr1->value.compcall.actual);
5785
5786  gfc_free_expr (c->expr1);
5787  c->expr1 = gfc_get_expr ();
5788  c->expr1->expr_type = EXPR_FUNCTION;
5789  c->expr1->symtree = target;
5790  c->expr1->where = c->loc;
5791
5792  return resolve_call (c);
5793}
5794
5795
5796/* Resolve a component-call expression.  */
5797static bool
5798resolve_compcall (gfc_expr* e, const char **name)
5799{
5800  gfc_actual_arglist* newactual;
5801  gfc_symtree* target;
5802
5803  /* Check that's really a FUNCTION.  */
5804  if (!e->value.compcall.tbp->function)
5805    {
5806      gfc_error ("%qs at %L should be a FUNCTION",
5807		 e->value.compcall.name, &e->where);
5808      return false;
5809    }
5810
5811  /* These must not be assign-calls!  */
5812  gcc_assert (!e->value.compcall.assign);
5813
5814  if (!check_typebound_baseobject (e))
5815    return false;
5816
5817  /* Pass along the name for CLASS methods, where the vtab
5818     procedure pointer component has to be referenced.  */
5819  if (name)
5820    *name = e->value.compcall.name;
5821
5822  if (!resolve_typebound_generic_call (e, name))
5823    return false;
5824  gcc_assert (!e->value.compcall.tbp->is_generic);
5825
5826  /* Take the rank from the function's symbol.  */
5827  if (e->value.compcall.tbp->u.specific->n.sym->as)
5828    e->rank = e->value.compcall.tbp->u.specific->n.sym->as->rank;
5829
5830  /* For now, we simply transform it into an EXPR_FUNCTION call with the same
5831     arglist to the TBP's binding target.  */
5832
5833  if (!resolve_typebound_static (e, &target, &newactual))
5834    return false;
5835
5836  e->value.function.actual = newactual;
5837  e->value.function.name = NULL;
5838  e->value.function.esym = target->n.sym;
5839  e->value.function.isym = NULL;
5840  e->symtree = target;
5841  e->ts = target->n.sym->ts;
5842  e->expr_type = EXPR_FUNCTION;
5843
5844  /* Resolution is not necessary if this is a class subroutine; this
5845     function only has to identify the specific proc. Resolution of
5846     the call will be done next in resolve_typebound_call.  */
5847  return gfc_resolve_expr (e);
5848}
5849
5850
5851static bool resolve_fl_derived (gfc_symbol *sym);
5852
5853
5854/* Resolve a typebound function, or 'method'. First separate all
5855   the non-CLASS references by calling resolve_compcall directly.  */
5856
5857static bool
5858resolve_typebound_function (gfc_expr* e)
5859{
5860  gfc_symbol *declared;
5861  gfc_component *c;
5862  gfc_ref *new_ref;
5863  gfc_ref *class_ref;
5864  gfc_symtree *st;
5865  const char *name;
5866  gfc_typespec ts;
5867  gfc_expr *expr;
5868  bool overridable;
5869
5870  st = e->symtree;
5871
5872  /* Deal with typebound operators for CLASS objects.  */
5873  expr = e->value.compcall.base_object;
5874  overridable = !e->value.compcall.tbp->non_overridable;
5875  if (expr && expr->ts.type == BT_CLASS && e->value.compcall.name)
5876    {
5877      /* If the base_object is not a variable, the corresponding actual
5878	 argument expression must be stored in e->base_expression so
5879	 that the corresponding tree temporary can be used as the base
5880	 object in gfc_conv_procedure_call.  */
5881      if (expr->expr_type != EXPR_VARIABLE)
5882	{
5883	  gfc_actual_arglist *args;
5884
5885	  for (args= e->value.function.actual; args; args = args->next)
5886	    {
5887	      if (expr == args->expr)
5888		expr = args->expr;
5889	    }
5890	}
5891
5892      /* Since the typebound operators are generic, we have to ensure
5893	 that any delays in resolution are corrected and that the vtab
5894	 is present.  */
5895      ts = expr->ts;
5896      declared = ts.u.derived;
5897      c = gfc_find_component (declared, "_vptr", true, true);
5898      if (c->ts.u.derived == NULL)
5899	c->ts.u.derived = gfc_find_derived_vtab (declared);
5900
5901      if (!resolve_compcall (e, &name))
5902	return false;
5903
5904      /* Use the generic name if it is there.  */
5905      name = name ? name : e->value.function.esym->name;
5906      e->symtree = expr->symtree;
5907      e->ref = gfc_copy_ref (expr->ref);
5908      get_declared_from_expr (&class_ref, NULL, e, false);
5909
5910      /* Trim away the extraneous references that emerge from nested
5911	 use of interface.c (extend_expr).  */
5912      if (class_ref && class_ref->next)
5913	{
5914	  gfc_free_ref_list (class_ref->next);
5915	  class_ref->next = NULL;
5916	}
5917      else if (e->ref && !class_ref)
5918	{
5919	  gfc_free_ref_list (e->ref);
5920	  e->ref = NULL;
5921	}
5922
5923      gfc_add_vptr_component (e);
5924      gfc_add_component_ref (e, name);
5925      e->value.function.esym = NULL;
5926      if (expr->expr_type != EXPR_VARIABLE)
5927	e->base_expr = expr;
5928      return true;
5929    }
5930
5931  if (st == NULL)
5932    return resolve_compcall (e, NULL);
5933
5934  if (!resolve_ref (e))
5935    return false;
5936
5937  /* Get the CLASS declared type.  */
5938  declared = get_declared_from_expr (&class_ref, &new_ref, e, true);
5939
5940  if (!resolve_fl_derived (declared))
5941    return false;
5942
5943  /* Weed out cases of the ultimate component being a derived type.  */
5944  if ((class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
5945	 || (!class_ref && st->n.sym->ts.type != BT_CLASS))
5946    {
5947      gfc_free_ref_list (new_ref);
5948      return resolve_compcall (e, NULL);
5949    }
5950
5951  c = gfc_find_component (declared, "_data", true, true);
5952  declared = c->ts.u.derived;
5953
5954  /* Treat the call as if it is a typebound procedure, in order to roll
5955     out the correct name for the specific function.  */
5956  if (!resolve_compcall (e, &name))
5957    {
5958      gfc_free_ref_list (new_ref);
5959      return false;
5960    }
5961  ts = e->ts;
5962
5963  if (overridable)
5964    {
5965      /* Convert the expression to a procedure pointer component call.  */
5966      e->value.function.esym = NULL;
5967      e->symtree = st;
5968
5969      if (new_ref)
5970	e->ref = new_ref;
5971
5972      /* '_vptr' points to the vtab, which contains the procedure pointers.  */
5973      gfc_add_vptr_component (e);
5974      gfc_add_component_ref (e, name);
5975
5976      /* Recover the typespec for the expression.  This is really only
5977	necessary for generic procedures, where the additional call
5978	to gfc_add_component_ref seems to throw the collection of the
5979	correct typespec.  */
5980      e->ts = ts;
5981    }
5982  else if (new_ref)
5983    gfc_free_ref_list (new_ref);
5984
5985  return true;
5986}
5987
5988/* Resolve a typebound subroutine, or 'method'. First separate all
5989   the non-CLASS references by calling resolve_typebound_call
5990   directly.  */
5991
5992static bool
5993resolve_typebound_subroutine (gfc_code *code)
5994{
5995  gfc_symbol *declared;
5996  gfc_component *c;
5997  gfc_ref *new_ref;
5998  gfc_ref *class_ref;
5999  gfc_symtree *st;
6000  const char *name;
6001  gfc_typespec ts;
6002  gfc_expr *expr;
6003  bool overridable;
6004
6005  st = code->expr1->symtree;
6006
6007  /* Deal with typebound operators for CLASS objects.  */
6008  expr = code->expr1->value.compcall.base_object;
6009  overridable = !code->expr1->value.compcall.tbp->non_overridable;
6010  if (expr && expr->ts.type == BT_CLASS && code->expr1->value.compcall.name)
6011    {
6012      /* If the base_object is not a variable, the corresponding actual
6013	 argument expression must be stored in e->base_expression so
6014	 that the corresponding tree temporary can be used as the base
6015	 object in gfc_conv_procedure_call.  */
6016      if (expr->expr_type != EXPR_VARIABLE)
6017	{
6018	  gfc_actual_arglist *args;
6019
6020	  args= code->expr1->value.function.actual;
6021	  for (; args; args = args->next)
6022	    if (expr == args->expr)
6023	      expr = args->expr;
6024	}
6025
6026      /* Since the typebound operators are generic, we have to ensure
6027	 that any delays in resolution are corrected and that the vtab
6028	 is present.  */
6029      declared = expr->ts.u.derived;
6030      c = gfc_find_component (declared, "_vptr", true, true);
6031      if (c->ts.u.derived == NULL)
6032	c->ts.u.derived = gfc_find_derived_vtab (declared);
6033
6034      if (!resolve_typebound_call (code, &name, NULL))
6035	return false;
6036
6037      /* Use the generic name if it is there.  */
6038      name = name ? name : code->expr1->value.function.esym->name;
6039      code->expr1->symtree = expr->symtree;
6040      code->expr1->ref = gfc_copy_ref (expr->ref);
6041
6042      /* Trim away the extraneous references that emerge from nested
6043	 use of interface.c (extend_expr).  */
6044      get_declared_from_expr (&class_ref, NULL, code->expr1, false);
6045      if (class_ref && class_ref->next)
6046	{
6047	  gfc_free_ref_list (class_ref->next);
6048	  class_ref->next = NULL;
6049	}
6050      else if (code->expr1->ref && !class_ref)
6051	{
6052	  gfc_free_ref_list (code->expr1->ref);
6053	  code->expr1->ref = NULL;
6054	}
6055
6056      /* Now use the procedure in the vtable.  */
6057      gfc_add_vptr_component (code->expr1);
6058      gfc_add_component_ref (code->expr1, name);
6059      code->expr1->value.function.esym = NULL;
6060      if (expr->expr_type != EXPR_VARIABLE)
6061	code->expr1->base_expr = expr;
6062      return true;
6063    }
6064
6065  if (st == NULL)
6066    return resolve_typebound_call (code, NULL, NULL);
6067
6068  if (!resolve_ref (code->expr1))
6069    return false;
6070
6071  /* Get the CLASS declared type.  */
6072  get_declared_from_expr (&class_ref, &new_ref, code->expr1, true);
6073
6074  /* Weed out cases of the ultimate component being a derived type.  */
6075  if ((class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
6076	 || (!class_ref && st->n.sym->ts.type != BT_CLASS))
6077    {
6078      gfc_free_ref_list (new_ref);
6079      return resolve_typebound_call (code, NULL, NULL);
6080    }
6081
6082  if (!resolve_typebound_call (code, &name, &overridable))
6083    {
6084      gfc_free_ref_list (new_ref);
6085      return false;
6086    }
6087  ts = code->expr1->ts;
6088
6089  if (overridable)
6090    {
6091      /* Convert the expression to a procedure pointer component call.  */
6092      code->expr1->value.function.esym = NULL;
6093      code->expr1->symtree = st;
6094
6095      if (new_ref)
6096	code->expr1->ref = new_ref;
6097
6098      /* '_vptr' points to the vtab, which contains the procedure pointers.  */
6099      gfc_add_vptr_component (code->expr1);
6100      gfc_add_component_ref (code->expr1, name);
6101
6102      /* Recover the typespec for the expression.  This is really only
6103	necessary for generic procedures, where the additional call
6104	to gfc_add_component_ref seems to throw the collection of the
6105	correct typespec.  */
6106      code->expr1->ts = ts;
6107    }
6108  else if (new_ref)
6109    gfc_free_ref_list (new_ref);
6110
6111  return true;
6112}
6113
6114
6115/* Resolve a CALL to a Procedure Pointer Component (Subroutine).  */
6116
6117static bool
6118resolve_ppc_call (gfc_code* c)
6119{
6120  gfc_component *comp;
6121
6122  comp = gfc_get_proc_ptr_comp (c->expr1);
6123  gcc_assert (comp != NULL);
6124
6125  c->resolved_sym = c->expr1->symtree->n.sym;
6126  c->expr1->expr_type = EXPR_VARIABLE;
6127
6128  if (!comp->attr.subroutine)
6129    gfc_add_subroutine (&comp->attr, comp->name, &c->expr1->where);
6130
6131  if (!resolve_ref (c->expr1))
6132    return false;
6133
6134  if (!update_ppc_arglist (c->expr1))
6135    return false;
6136
6137  c->ext.actual = c->expr1->value.compcall.actual;
6138
6139  if (!resolve_actual_arglist (c->ext.actual, comp->attr.proc,
6140			       !(comp->ts.interface
6141				 && comp->ts.interface->formal)))
6142    return false;
6143
6144  if (!pure_subroutine (comp->ts.interface, comp->name, &c->expr1->where))
6145    return false;
6146
6147  gfc_ppc_use (comp, &c->expr1->value.compcall.actual, &c->expr1->where);
6148
6149  return true;
6150}
6151
6152
6153/* Resolve a Function Call to a Procedure Pointer Component (Function).  */
6154
6155static bool
6156resolve_expr_ppc (gfc_expr* e)
6157{
6158  gfc_component *comp;
6159
6160  comp = gfc_get_proc_ptr_comp (e);
6161  gcc_assert (comp != NULL);
6162
6163  /* Convert to EXPR_FUNCTION.  */
6164  e->expr_type = EXPR_FUNCTION;
6165  e->value.function.isym = NULL;
6166  e->value.function.actual = e->value.compcall.actual;
6167  e->ts = comp->ts;
6168  if (comp->as != NULL)
6169    e->rank = comp->as->rank;
6170
6171  if (!comp->attr.function)
6172    gfc_add_function (&comp->attr, comp->name, &e->where);
6173
6174  if (!resolve_ref (e))
6175    return false;
6176
6177  if (!resolve_actual_arglist (e->value.function.actual, comp->attr.proc,
6178			       !(comp->ts.interface
6179				 && comp->ts.interface->formal)))
6180    return false;
6181
6182  if (!update_ppc_arglist (e))
6183    return false;
6184
6185  if (!check_pure_function(e))
6186    return false;
6187
6188  gfc_ppc_use (comp, &e->value.compcall.actual, &e->where);
6189
6190  return true;
6191}
6192
6193
6194static bool
6195gfc_is_expandable_expr (gfc_expr *e)
6196{
6197  gfc_constructor *con;
6198
6199  if (e->expr_type == EXPR_ARRAY)
6200    {
6201      /* Traverse the constructor looking for variables that are flavor
6202	 parameter.  Parameters must be expanded since they are fully used at
6203	 compile time.  */
6204      con = gfc_constructor_first (e->value.constructor);
6205      for (; con; con = gfc_constructor_next (con))
6206	{
6207	  if (con->expr->expr_type == EXPR_VARIABLE
6208	      && con->expr->symtree
6209	      && (con->expr->symtree->n.sym->attr.flavor == FL_PARAMETER
6210	      || con->expr->symtree->n.sym->attr.flavor == FL_VARIABLE))
6211	    return true;
6212	  if (con->expr->expr_type == EXPR_ARRAY
6213	      && gfc_is_expandable_expr (con->expr))
6214	    return true;
6215	}
6216    }
6217
6218  return false;
6219}
6220
6221/* Resolve an expression.  That is, make sure that types of operands agree
6222   with their operators, intrinsic operators are converted to function calls
6223   for overloaded types and unresolved function references are resolved.  */
6224
6225bool
6226gfc_resolve_expr (gfc_expr *e)
6227{
6228  bool t;
6229  bool inquiry_save, actual_arg_save, first_actual_arg_save;
6230
6231  if (e == NULL)
6232    return true;
6233
6234  /* inquiry_argument only applies to variables.  */
6235  inquiry_save = inquiry_argument;
6236  actual_arg_save = actual_arg;
6237  first_actual_arg_save = first_actual_arg;
6238
6239  if (e->expr_type != EXPR_VARIABLE)
6240    {
6241      inquiry_argument = false;
6242      actual_arg = false;
6243      first_actual_arg = false;
6244    }
6245
6246  switch (e->expr_type)
6247    {
6248    case EXPR_OP:
6249      t = resolve_operator (e);
6250      break;
6251
6252    case EXPR_FUNCTION:
6253    case EXPR_VARIABLE:
6254
6255      if (check_host_association (e))
6256	t = resolve_function (e);
6257      else
6258	t = resolve_variable (e);
6259
6260      if (e->ts.type == BT_CHARACTER && e->ts.u.cl == NULL && e->ref
6261	  && e->ref->type != REF_SUBSTRING)
6262	gfc_resolve_substring_charlen (e);
6263
6264      break;
6265
6266    case EXPR_COMPCALL:
6267      t = resolve_typebound_function (e);
6268      break;
6269
6270    case EXPR_SUBSTRING:
6271      t = resolve_ref (e);
6272      break;
6273
6274    case EXPR_CONSTANT:
6275    case EXPR_NULL:
6276      t = true;
6277      break;
6278
6279    case EXPR_PPC:
6280      t = resolve_expr_ppc (e);
6281      break;
6282
6283    case EXPR_ARRAY:
6284      t = false;
6285      if (!resolve_ref (e))
6286	break;
6287
6288      t = gfc_resolve_array_constructor (e);
6289      /* Also try to expand a constructor.  */
6290      if (t)
6291	{
6292	  expression_rank (e);
6293	  if (gfc_is_constant_expr (e) || gfc_is_expandable_expr (e))
6294	    gfc_expand_constructor (e, false);
6295	}
6296
6297      /* This provides the opportunity for the length of constructors with
6298	 character valued function elements to propagate the string length
6299	 to the expression.  */
6300      if (t && e->ts.type == BT_CHARACTER)
6301        {
6302	  /* For efficiency, we call gfc_expand_constructor for BT_CHARACTER
6303	     here rather then add a duplicate test for it above.  */
6304	  gfc_expand_constructor (e, false);
6305	  t = gfc_resolve_character_array_constructor (e);
6306	}
6307
6308      break;
6309
6310    case EXPR_STRUCTURE:
6311      t = resolve_ref (e);
6312      if (!t)
6313	break;
6314
6315      t = resolve_structure_cons (e, 0);
6316      if (!t)
6317	break;
6318
6319      t = gfc_simplify_expr (e, 0);
6320      break;
6321
6322    default:
6323      gfc_internal_error ("gfc_resolve_expr(): Bad expression type");
6324    }
6325
6326  if (e->ts.type == BT_CHARACTER && t && !e->ts.u.cl)
6327    fixup_charlen (e);
6328
6329  inquiry_argument = inquiry_save;
6330  actual_arg = actual_arg_save;
6331  first_actual_arg = first_actual_arg_save;
6332
6333  return t;
6334}
6335
6336
6337/* Resolve an expression from an iterator.  They must be scalar and have
6338   INTEGER or (optionally) REAL type.  */
6339
6340static bool
6341gfc_resolve_iterator_expr (gfc_expr *expr, bool real_ok,
6342			   const char *name_msgid)
6343{
6344  if (!gfc_resolve_expr (expr))
6345    return false;
6346
6347  if (expr->rank != 0)
6348    {
6349      gfc_error ("%s at %L must be a scalar", _(name_msgid), &expr->where);
6350      return false;
6351    }
6352
6353  if (expr->ts.type != BT_INTEGER)
6354    {
6355      if (expr->ts.type == BT_REAL)
6356	{
6357	  if (real_ok)
6358	    return gfc_notify_std (GFC_STD_F95_DEL,
6359				   "%s at %L must be integer",
6360				   _(name_msgid), &expr->where);
6361	  else
6362	    {
6363	      gfc_error ("%s at %L must be INTEGER", _(name_msgid),
6364			 &expr->where);
6365	      return false;
6366	    }
6367	}
6368      else
6369	{
6370	  gfc_error ("%s at %L must be INTEGER", _(name_msgid), &expr->where);
6371	  return false;
6372	}
6373    }
6374  return true;
6375}
6376
6377
6378/* Resolve the expressions in an iterator structure.  If REAL_OK is
6379   false allow only INTEGER type iterators, otherwise allow REAL types.
6380   Set own_scope to true for ac-implied-do and data-implied-do as those
6381   have a separate scope such that, e.g., a INTENT(IN) doesn't apply.  */
6382
6383bool
6384gfc_resolve_iterator (gfc_iterator *iter, bool real_ok, bool own_scope)
6385{
6386  if (!gfc_resolve_iterator_expr (iter->var, real_ok, "Loop variable"))
6387    return false;
6388
6389  if (!gfc_check_vardef_context (iter->var, false, false, own_scope,
6390				 _("iterator variable")))
6391    return false;
6392
6393  if (!gfc_resolve_iterator_expr (iter->start, real_ok,
6394				  "Start expression in DO loop"))
6395    return false;
6396
6397  if (!gfc_resolve_iterator_expr (iter->end, real_ok,
6398				  "End expression in DO loop"))
6399    return false;
6400
6401  if (!gfc_resolve_iterator_expr (iter->step, real_ok,
6402				  "Step expression in DO loop"))
6403    return false;
6404
6405  if (iter->step->expr_type == EXPR_CONSTANT)
6406    {
6407      if ((iter->step->ts.type == BT_INTEGER
6408	   && mpz_cmp_ui (iter->step->value.integer, 0) == 0)
6409	  || (iter->step->ts.type == BT_REAL
6410	      && mpfr_sgn (iter->step->value.real) == 0))
6411	{
6412	  gfc_error ("Step expression in DO loop at %L cannot be zero",
6413		     &iter->step->where);
6414	  return false;
6415	}
6416    }
6417
6418  /* Convert start, end, and step to the same type as var.  */
6419  if (iter->start->ts.kind != iter->var->ts.kind
6420      || iter->start->ts.type != iter->var->ts.type)
6421    gfc_convert_type (iter->start, &iter->var->ts, 2);
6422
6423  if (iter->end->ts.kind != iter->var->ts.kind
6424      || iter->end->ts.type != iter->var->ts.type)
6425    gfc_convert_type (iter->end, &iter->var->ts, 2);
6426
6427  if (iter->step->ts.kind != iter->var->ts.kind
6428      || iter->step->ts.type != iter->var->ts.type)
6429    gfc_convert_type (iter->step, &iter->var->ts, 2);
6430
6431  if (iter->start->expr_type == EXPR_CONSTANT
6432      && iter->end->expr_type == EXPR_CONSTANT
6433      && iter->step->expr_type == EXPR_CONSTANT)
6434    {
6435      int sgn, cmp;
6436      if (iter->start->ts.type == BT_INTEGER)
6437	{
6438	  sgn = mpz_cmp_ui (iter->step->value.integer, 0);
6439	  cmp = mpz_cmp (iter->end->value.integer, iter->start->value.integer);
6440	}
6441      else
6442	{
6443	  sgn = mpfr_sgn (iter->step->value.real);
6444	  cmp = mpfr_cmp (iter->end->value.real, iter->start->value.real);
6445	}
6446      if (warn_zerotrip && ((sgn > 0 && cmp < 0) || (sgn < 0 && cmp > 0)))
6447	gfc_warning (OPT_Wzerotrip,
6448		     "DO loop at %L will be executed zero times",
6449		     &iter->step->where);
6450    }
6451
6452  return true;
6453}
6454
6455
6456/* Traversal function for find_forall_index.  f == 2 signals that
6457   that variable itself is not to be checked - only the references.  */
6458
6459static bool
6460forall_index (gfc_expr *expr, gfc_symbol *sym, int *f)
6461{
6462  if (expr->expr_type != EXPR_VARIABLE)
6463    return false;
6464
6465  /* A scalar assignment  */
6466  if (!expr->ref || *f == 1)
6467    {
6468      if (expr->symtree->n.sym == sym)
6469	return true;
6470      else
6471	return false;
6472    }
6473
6474  if (*f == 2)
6475    *f = 1;
6476  return false;
6477}
6478
6479
6480/* Check whether the FORALL index appears in the expression or not.
6481   Returns true if SYM is found in EXPR.  */
6482
6483bool
6484find_forall_index (gfc_expr *expr, gfc_symbol *sym, int f)
6485{
6486  if (gfc_traverse_expr (expr, sym, forall_index, f))
6487    return true;
6488  else
6489    return false;
6490}
6491
6492
6493/* Resolve a list of FORALL iterators.  The FORALL index-name is constrained
6494   to be a scalar INTEGER variable.  The subscripts and stride are scalar
6495   INTEGERs, and if stride is a constant it must be nonzero.
6496   Furthermore "A subscript or stride in a forall-triplet-spec shall
6497   not contain a reference to any index-name in the
6498   forall-triplet-spec-list in which it appears." (7.5.4.1)  */
6499
6500static void
6501resolve_forall_iterators (gfc_forall_iterator *it)
6502{
6503  gfc_forall_iterator *iter, *iter2;
6504
6505  for (iter = it; iter; iter = iter->next)
6506    {
6507      if (gfc_resolve_expr (iter->var)
6508	  && (iter->var->ts.type != BT_INTEGER || iter->var->rank != 0))
6509	gfc_error ("FORALL index-name at %L must be a scalar INTEGER",
6510		   &iter->var->where);
6511
6512      if (gfc_resolve_expr (iter->start)
6513	  && (iter->start->ts.type != BT_INTEGER || iter->start->rank != 0))
6514	gfc_error ("FORALL start expression at %L must be a scalar INTEGER",
6515		   &iter->start->where);
6516      if (iter->var->ts.kind != iter->start->ts.kind)
6517	gfc_convert_type (iter->start, &iter->var->ts, 1);
6518
6519      if (gfc_resolve_expr (iter->end)
6520	  && (iter->end->ts.type != BT_INTEGER || iter->end->rank != 0))
6521	gfc_error ("FORALL end expression at %L must be a scalar INTEGER",
6522		   &iter->end->where);
6523      if (iter->var->ts.kind != iter->end->ts.kind)
6524	gfc_convert_type (iter->end, &iter->var->ts, 1);
6525
6526      if (gfc_resolve_expr (iter->stride))
6527	{
6528	  if (iter->stride->ts.type != BT_INTEGER || iter->stride->rank != 0)
6529	    gfc_error ("FORALL stride expression at %L must be a scalar %s",
6530		       &iter->stride->where, "INTEGER");
6531
6532	  if (iter->stride->expr_type == EXPR_CONSTANT
6533	      && mpz_cmp_ui (iter->stride->value.integer, 0) == 0)
6534	    gfc_error ("FORALL stride expression at %L cannot be zero",
6535		       &iter->stride->where);
6536	}
6537      if (iter->var->ts.kind != iter->stride->ts.kind)
6538	gfc_convert_type (iter->stride, &iter->var->ts, 1);
6539    }
6540
6541  for (iter = it; iter; iter = iter->next)
6542    for (iter2 = iter; iter2; iter2 = iter2->next)
6543      {
6544	if (find_forall_index (iter2->start, iter->var->symtree->n.sym, 0)
6545	    || find_forall_index (iter2->end, iter->var->symtree->n.sym, 0)
6546	    || find_forall_index (iter2->stride, iter->var->symtree->n.sym, 0))
6547	  gfc_error ("FORALL index %qs may not appear in triplet "
6548		     "specification at %L", iter->var->symtree->name,
6549		     &iter2->start->where);
6550      }
6551}
6552
6553
6554/* Given a pointer to a symbol that is a derived type, see if it's
6555   inaccessible, i.e. if it's defined in another module and the components are
6556   PRIVATE.  The search is recursive if necessary.  Returns zero if no
6557   inaccessible components are found, nonzero otherwise.  */
6558
6559static int
6560derived_inaccessible (gfc_symbol *sym)
6561{
6562  gfc_component *c;
6563
6564  if (sym->attr.use_assoc && sym->attr.private_comp)
6565    return 1;
6566
6567  for (c = sym->components; c; c = c->next)
6568    {
6569	if (c->ts.type == BT_DERIVED && derived_inaccessible (c->ts.u.derived))
6570	  return 1;
6571    }
6572
6573  return 0;
6574}
6575
6576
6577/* Resolve the argument of a deallocate expression.  The expression must be
6578   a pointer or a full array.  */
6579
6580static bool
6581resolve_deallocate_expr (gfc_expr *e)
6582{
6583  symbol_attribute attr;
6584  int allocatable, pointer;
6585  gfc_ref *ref;
6586  gfc_symbol *sym;
6587  gfc_component *c;
6588  bool unlimited;
6589
6590  if (!gfc_resolve_expr (e))
6591    return false;
6592
6593  if (e->expr_type != EXPR_VARIABLE)
6594    goto bad;
6595
6596  sym = e->symtree->n.sym;
6597  unlimited = UNLIMITED_POLY(sym);
6598
6599  if (sym->ts.type == BT_CLASS)
6600    {
6601      allocatable = CLASS_DATA (sym)->attr.allocatable;
6602      pointer = CLASS_DATA (sym)->attr.class_pointer;
6603    }
6604  else
6605    {
6606      allocatable = sym->attr.allocatable;
6607      pointer = sym->attr.pointer;
6608    }
6609  for (ref = e->ref; ref; ref = ref->next)
6610    {
6611      switch (ref->type)
6612	{
6613	case REF_ARRAY:
6614	  if (ref->u.ar.type != AR_FULL
6615	      && !(ref->u.ar.type == AR_ELEMENT && ref->u.ar.as->rank == 0
6616	           && ref->u.ar.codimen && gfc_ref_this_image (ref)))
6617	    allocatable = 0;
6618	  break;
6619
6620	case REF_COMPONENT:
6621	  c = ref->u.c.component;
6622	  if (c->ts.type == BT_CLASS)
6623	    {
6624	      allocatable = CLASS_DATA (c)->attr.allocatable;
6625	      pointer = CLASS_DATA (c)->attr.class_pointer;
6626	    }
6627	  else
6628	    {
6629	      allocatable = c->attr.allocatable;
6630	      pointer = c->attr.pointer;
6631	    }
6632	  break;
6633
6634	case REF_SUBSTRING:
6635	  allocatable = 0;
6636	  break;
6637	}
6638    }
6639
6640  attr = gfc_expr_attr (e);
6641
6642  if (allocatable == 0 && attr.pointer == 0 && !unlimited)
6643    {
6644    bad:
6645      gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
6646		 &e->where);
6647      return false;
6648    }
6649
6650  /* F2008, C644.  */
6651  if (gfc_is_coindexed (e))
6652    {
6653      gfc_error ("Coindexed allocatable object at %L", &e->where);
6654      return false;
6655    }
6656
6657  if (pointer
6658      && !gfc_check_vardef_context (e, true, true, false,
6659				    _("DEALLOCATE object")))
6660    return false;
6661  if (!gfc_check_vardef_context (e, false, true, false,
6662				 _("DEALLOCATE object")))
6663    return false;
6664
6665  return true;
6666}
6667
6668
6669/* Returns true if the expression e contains a reference to the symbol sym.  */
6670static bool
6671sym_in_expr (gfc_expr *e, gfc_symbol *sym, int *f ATTRIBUTE_UNUSED)
6672{
6673  if (e->expr_type == EXPR_VARIABLE && e->symtree->n.sym == sym)
6674    return true;
6675
6676  return false;
6677}
6678
6679bool
6680gfc_find_sym_in_expr (gfc_symbol *sym, gfc_expr *e)
6681{
6682  return gfc_traverse_expr (e, sym, sym_in_expr, 0);
6683}
6684
6685
6686/* Given the expression node e for an allocatable/pointer of derived type to be
6687   allocated, get the expression node to be initialized afterwards (needed for
6688   derived types with default initializers, and derived types with allocatable
6689   components that need nullification.)  */
6690
6691gfc_expr *
6692gfc_expr_to_initialize (gfc_expr *e)
6693{
6694  gfc_expr *result;
6695  gfc_ref *ref;
6696  int i;
6697
6698  result = gfc_copy_expr (e);
6699
6700  /* Change the last array reference from AR_ELEMENT to AR_FULL.  */
6701  for (ref = result->ref; ref; ref = ref->next)
6702    if (ref->type == REF_ARRAY && ref->next == NULL)
6703      {
6704	ref->u.ar.type = AR_FULL;
6705
6706	for (i = 0; i < ref->u.ar.dimen; i++)
6707	  ref->u.ar.start[i] = ref->u.ar.end[i] = ref->u.ar.stride[i] = NULL;
6708
6709	break;
6710      }
6711
6712  gfc_free_shape (&result->shape, result->rank);
6713
6714  /* Recalculate rank, shape, etc.  */
6715  gfc_resolve_expr (result);
6716  return result;
6717}
6718
6719
6720/* If the last ref of an expression is an array ref, return a copy of the
6721   expression with that one removed.  Otherwise, a copy of the original
6722   expression.  This is used for allocate-expressions and pointer assignment
6723   LHS, where there may be an array specification that needs to be stripped
6724   off when using gfc_check_vardef_context.  */
6725
6726static gfc_expr*
6727remove_last_array_ref (gfc_expr* e)
6728{
6729  gfc_expr* e2;
6730  gfc_ref** r;
6731
6732  e2 = gfc_copy_expr (e);
6733  for (r = &e2->ref; *r; r = &(*r)->next)
6734    if ((*r)->type == REF_ARRAY && !(*r)->next)
6735      {
6736	gfc_free_ref_list (*r);
6737	*r = NULL;
6738	break;
6739      }
6740
6741  return e2;
6742}
6743
6744
6745/* Used in resolve_allocate_expr to check that a allocation-object and
6746   a source-expr are conformable.  This does not catch all possible
6747   cases; in particular a runtime checking is needed.  */
6748
6749static bool
6750conformable_arrays (gfc_expr *e1, gfc_expr *e2)
6751{
6752  gfc_ref *tail;
6753  for (tail = e2->ref; tail && tail->next; tail = tail->next);
6754
6755  /* First compare rank.  */
6756  if ((tail && e1->rank != tail->u.ar.as->rank)
6757      || (!tail && e1->rank != e2->rank))
6758    {
6759      gfc_error ("Source-expr at %L must be scalar or have the "
6760		 "same rank as the allocate-object at %L",
6761		 &e1->where, &e2->where);
6762      return false;
6763    }
6764
6765  if (e1->shape)
6766    {
6767      int i;
6768      mpz_t s;
6769
6770      mpz_init (s);
6771
6772      for (i = 0; i < e1->rank; i++)
6773	{
6774	  if (tail->u.ar.start[i] == NULL)
6775	    break;
6776
6777	  if (tail->u.ar.end[i])
6778	    {
6779	      mpz_set (s, tail->u.ar.end[i]->value.integer);
6780	      mpz_sub (s, s, tail->u.ar.start[i]->value.integer);
6781	      mpz_add_ui (s, s, 1);
6782	    }
6783	  else
6784	    {
6785	      mpz_set (s, tail->u.ar.start[i]->value.integer);
6786	    }
6787
6788	  if (mpz_cmp (e1->shape[i], s) != 0)
6789	    {
6790	      gfc_error_1 ("Source-expr at %L and allocate-object at %L must "
6791			 "have the same shape", &e1->where, &e2->where);
6792	      mpz_clear (s);
6793   	      return false;
6794	    }
6795	}
6796
6797      mpz_clear (s);
6798    }
6799
6800  return true;
6801}
6802
6803
6804/* Resolve the expression in an ALLOCATE statement, doing the additional
6805   checks to see whether the expression is OK or not.  The expression must
6806   have a trailing array reference that gives the size of the array.  */
6807
6808static bool
6809resolve_allocate_expr (gfc_expr *e, gfc_code *code)
6810{
6811  int i, pointer, allocatable, dimension, is_abstract;
6812  int codimension;
6813  bool coindexed;
6814  bool unlimited;
6815  symbol_attribute attr;
6816  gfc_ref *ref, *ref2;
6817  gfc_expr *e2;
6818  gfc_array_ref *ar;
6819  gfc_symbol *sym = NULL;
6820  gfc_alloc *a;
6821  gfc_component *c;
6822  bool t;
6823
6824  /* Mark the utmost array component as being in allocate to allow DIMEN_STAR
6825     checking of coarrays.  */
6826  for (ref = e->ref; ref; ref = ref->next)
6827    if (ref->next == NULL)
6828      break;
6829
6830  if (ref && ref->type == REF_ARRAY)
6831    ref->u.ar.in_allocate = true;
6832
6833  if (!gfc_resolve_expr (e))
6834    goto failure;
6835
6836  /* Make sure the expression is allocatable or a pointer.  If it is
6837     pointer, the next-to-last reference must be a pointer.  */
6838
6839  ref2 = NULL;
6840  if (e->symtree)
6841    sym = e->symtree->n.sym;
6842
6843  /* Check whether ultimate component is abstract and CLASS.  */
6844  is_abstract = 0;
6845
6846  /* Is the allocate-object unlimited polymorphic?  */
6847  unlimited = UNLIMITED_POLY(e);
6848
6849  if (e->expr_type != EXPR_VARIABLE)
6850    {
6851      allocatable = 0;
6852      attr = gfc_expr_attr (e);
6853      pointer = attr.pointer;
6854      dimension = attr.dimension;
6855      codimension = attr.codimension;
6856    }
6857  else
6858    {
6859      if (sym->ts.type == BT_CLASS && CLASS_DATA (sym))
6860	{
6861	  allocatable = CLASS_DATA (sym)->attr.allocatable;
6862	  pointer = CLASS_DATA (sym)->attr.class_pointer;
6863	  dimension = CLASS_DATA (sym)->attr.dimension;
6864	  codimension = CLASS_DATA (sym)->attr.codimension;
6865	  is_abstract = CLASS_DATA (sym)->attr.abstract;
6866	}
6867      else
6868	{
6869	  allocatable = sym->attr.allocatable;
6870	  pointer = sym->attr.pointer;
6871	  dimension = sym->attr.dimension;
6872	  codimension = sym->attr.codimension;
6873	}
6874
6875      coindexed = false;
6876
6877      for (ref = e->ref; ref; ref2 = ref, ref = ref->next)
6878	{
6879	  switch (ref->type)
6880	    {
6881 	      case REF_ARRAY:
6882                if (ref->u.ar.codimen > 0)
6883		  {
6884		    int n;
6885		    for (n = ref->u.ar.dimen;
6886			 n < ref->u.ar.dimen + ref->u.ar.codimen; n++)
6887		      if (ref->u.ar.dimen_type[n] != DIMEN_THIS_IMAGE)
6888			{
6889			  coindexed = true;
6890			  break;
6891			}
6892		   }
6893
6894		if (ref->next != NULL)
6895		  pointer = 0;
6896		break;
6897
6898	      case REF_COMPONENT:
6899		/* F2008, C644.  */
6900		if (coindexed)
6901		  {
6902		    gfc_error ("Coindexed allocatable object at %L",
6903			       &e->where);
6904		    goto failure;
6905		  }
6906
6907		c = ref->u.c.component;
6908		if (c->ts.type == BT_CLASS)
6909		  {
6910		    allocatable = CLASS_DATA (c)->attr.allocatable;
6911		    pointer = CLASS_DATA (c)->attr.class_pointer;
6912		    dimension = CLASS_DATA (c)->attr.dimension;
6913		    codimension = CLASS_DATA (c)->attr.codimension;
6914		    is_abstract = CLASS_DATA (c)->attr.abstract;
6915		  }
6916		else
6917		  {
6918		    allocatable = c->attr.allocatable;
6919		    pointer = c->attr.pointer;
6920		    dimension = c->attr.dimension;
6921		    codimension = c->attr.codimension;
6922		    is_abstract = c->attr.abstract;
6923		  }
6924		break;
6925
6926	      case REF_SUBSTRING:
6927		allocatable = 0;
6928		pointer = 0;
6929		break;
6930	    }
6931	}
6932    }
6933
6934  /* Check for F08:C628.  */
6935  if (allocatable == 0 && pointer == 0 && !unlimited)
6936    {
6937      gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
6938		 &e->where);
6939      goto failure;
6940    }
6941
6942  /* Some checks for the SOURCE tag.  */
6943  if (code->expr3)
6944    {
6945      /* Check F03:C631.  */
6946      if (!gfc_type_compatible (&e->ts, &code->expr3->ts))
6947	{
6948	  gfc_error_1 ("Type of entity at %L is type incompatible with "
6949		       "source-expr at %L", &e->where, &code->expr3->where);
6950	  goto failure;
6951	}
6952
6953      /* Check F03:C632 and restriction following Note 6.18.  */
6954      if (code->expr3->rank > 0 && !conformable_arrays (code->expr3, e))
6955	goto failure;
6956
6957      /* Check F03:C633.  */
6958      if (code->expr3->ts.kind != e->ts.kind && !unlimited)
6959	{
6960	  gfc_error_1 ("The allocate-object at %L and the source-expr at %L "
6961		      "shall have the same kind type parameter",
6962		      &e->where, &code->expr3->where);
6963	  goto failure;
6964	}
6965
6966      /* Check F2008, C642.  */
6967      if (code->expr3->ts.type == BT_DERIVED
6968	  && ((codimension && gfc_expr_attr (code->expr3).lock_comp)
6969	      || (code->expr3->ts.u.derived->from_intmod
6970		     == INTMOD_ISO_FORTRAN_ENV
6971		  && code->expr3->ts.u.derived->intmod_sym_id
6972		     == ISOFORTRAN_LOCK_TYPE)))
6973	{
6974	  gfc_error_1 ("The source-expr at %L shall neither be of type "
6975		     "LOCK_TYPE nor have a LOCK_TYPE component if "
6976		      "allocate-object at %L is a coarray",
6977		      &code->expr3->where, &e->where);
6978	  goto failure;
6979	}
6980
6981      /* Check TS18508, C702/C703.  */
6982      if (code->expr3->ts.type == BT_DERIVED
6983	  && ((codimension && gfc_expr_attr (code->expr3).event_comp)
6984	      || (code->expr3->ts.u.derived->from_intmod
6985		     == INTMOD_ISO_FORTRAN_ENV
6986		  && code->expr3->ts.u.derived->intmod_sym_id
6987		     == ISOFORTRAN_EVENT_TYPE)))
6988	{
6989	  gfc_error ("The source-expr at %L shall neither be of type "
6990		     "EVENT_TYPE nor have a EVENT_TYPE component if "
6991		      "allocate-object at %L is a coarray",
6992		      &code->expr3->where, &e->where);
6993	  goto failure;
6994	}
6995    }
6996
6997  /* Check F08:C629.  */
6998  if (is_abstract && code->ext.alloc.ts.type == BT_UNKNOWN
6999      && !code->expr3)
7000    {
7001      gcc_assert (e->ts.type == BT_CLASS);
7002      gfc_error ("Allocating %s of ABSTRACT base type at %L requires a "
7003		 "type-spec or source-expr", sym->name, &e->where);
7004      goto failure;
7005    }
7006
7007  /* Check F08:C632.  */
7008  if (code->ext.alloc.ts.type == BT_CHARACTER && !e->ts.deferred
7009      && !UNLIMITED_POLY (e))
7010    {
7011      int cmp = gfc_dep_compare_expr (e->ts.u.cl->length,
7012				      code->ext.alloc.ts.u.cl->length);
7013      if (cmp == 1 || cmp == -1 || cmp == -3)
7014	{
7015	  gfc_error ("Allocating %s at %L with type-spec requires the same "
7016		     "character-length parameter as in the declaration",
7017		     sym->name, &e->where);
7018	  goto failure;
7019	}
7020    }
7021
7022  /* In the variable definition context checks, gfc_expr_attr is used
7023     on the expression.  This is fooled by the array specification
7024     present in e, thus we have to eliminate that one temporarily.  */
7025  e2 = remove_last_array_ref (e);
7026  t = true;
7027  if (t && pointer)
7028    t = gfc_check_vardef_context (e2, true, true, false,
7029				  _("ALLOCATE object"));
7030  if (t)
7031    t = gfc_check_vardef_context (e2, false, true, false,
7032				  _("ALLOCATE object"));
7033  gfc_free_expr (e2);
7034  if (!t)
7035    goto failure;
7036
7037  if (e->ts.type == BT_CLASS && CLASS_DATA (e)->attr.dimension
7038	&& !code->expr3 && code->ext.alloc.ts.type == BT_DERIVED)
7039    {
7040      /* For class arrays, the initialization with SOURCE is done
7041	 using _copy and trans_call. It is convenient to exploit that
7042	 when the allocated type is different from the declared type but
7043	 no SOURCE exists by setting expr3.  */
7044      code->expr3 = gfc_default_initializer (&code->ext.alloc.ts);
7045    }
7046  else if (flag_coarray != GFC_FCOARRAY_LIB && e->ts.type == BT_DERIVED
7047	   && e->ts.u.derived->from_intmod == INTMOD_ISO_FORTRAN_ENV
7048	   && e->ts.u.derived->intmod_sym_id == ISOFORTRAN_EVENT_TYPE)
7049    {
7050      /* We have to zero initialize the integer variable.  */
7051      code->expr3 = gfc_get_int_expr (gfc_default_integer_kind, &e->where, 0);
7052    }
7053  else if (!code->expr3)
7054    {
7055      /* Set up default initializer if needed.  */
7056      gfc_typespec ts;
7057      gfc_expr *init_e;
7058
7059      if (code->ext.alloc.ts.type == BT_DERIVED)
7060	ts = code->ext.alloc.ts;
7061      else
7062	ts = e->ts;
7063
7064      if (ts.type == BT_CLASS)
7065	ts = ts.u.derived->components->ts;
7066
7067      if (ts.type == BT_DERIVED && (init_e = gfc_default_initializer (&ts)))
7068	{
7069	  gfc_code *init_st = gfc_get_code (EXEC_INIT_ASSIGN);
7070	  init_st->loc = code->loc;
7071	  init_st->expr1 = gfc_expr_to_initialize (e);
7072	  init_st->expr2 = init_e;
7073	  init_st->next = code->next;
7074	  code->next = init_st;
7075	}
7076    }
7077  else if (code->expr3->mold && code->expr3->ts.type == BT_DERIVED)
7078    {
7079      /* Default initialization via MOLD (non-polymorphic).  */
7080      gfc_expr *rhs = gfc_default_initializer (&code->expr3->ts);
7081      if (rhs != NULL)
7082	{
7083	  gfc_resolve_expr (rhs);
7084	  gfc_free_expr (code->expr3);
7085	  code->expr3 = rhs;
7086	}
7087    }
7088
7089  if (e->ts.type == BT_CLASS && !unlimited && !UNLIMITED_POLY (code->expr3))
7090    {
7091      /* Make sure the vtab symbol is present when
7092	 the module variables are generated.  */
7093      gfc_typespec ts = e->ts;
7094      if (code->expr3)
7095	ts = code->expr3->ts;
7096      else if (code->ext.alloc.ts.type == BT_DERIVED)
7097	ts = code->ext.alloc.ts;
7098
7099      gfc_find_derived_vtab (ts.u.derived);
7100
7101      if (dimension)
7102	e = gfc_expr_to_initialize (e);
7103    }
7104  else if (unlimited && !UNLIMITED_POLY (code->expr3))
7105    {
7106      /* Again, make sure the vtab symbol is present when
7107	 the module variables are generated.  */
7108      gfc_typespec *ts = NULL;
7109      if (code->expr3)
7110	ts = &code->expr3->ts;
7111      else
7112	ts = &code->ext.alloc.ts;
7113
7114      gcc_assert (ts);
7115
7116      gfc_find_vtab (ts);
7117
7118      if (dimension)
7119	e = gfc_expr_to_initialize (e);
7120    }
7121
7122  if (dimension == 0 && codimension == 0)
7123    goto success;
7124
7125  /* Make sure the last reference node is an array specification.  */
7126
7127  if (!ref2 || ref2->type != REF_ARRAY || ref2->u.ar.type == AR_FULL
7128      || (dimension && ref2->u.ar.dimen == 0))
7129    {
7130      gfc_error ("Array specification required in ALLOCATE statement "
7131		 "at %L", &e->where);
7132      goto failure;
7133    }
7134
7135  /* Make sure that the array section reference makes sense in the
7136    context of an ALLOCATE specification.  */
7137
7138  ar = &ref2->u.ar;
7139
7140  if (codimension)
7141    for (i = ar->dimen; i < ar->dimen + ar->codimen; i++)
7142      if (ar->dimen_type[i] == DIMEN_THIS_IMAGE)
7143	{
7144	  gfc_error ("Coarray specification required in ALLOCATE statement "
7145		     "at %L", &e->where);
7146	  goto failure;
7147	}
7148
7149  for (i = 0; i < ar->dimen; i++)
7150    {
7151      if (ref2->u.ar.type == AR_ELEMENT)
7152	goto check_symbols;
7153
7154      switch (ar->dimen_type[i])
7155	{
7156	case DIMEN_ELEMENT:
7157	  break;
7158
7159	case DIMEN_RANGE:
7160	  if (ar->start[i] != NULL
7161	      && ar->end[i] != NULL
7162	      && ar->stride[i] == NULL)
7163	    break;
7164
7165	  /* Fall Through...  */
7166
7167	case DIMEN_UNKNOWN:
7168	case DIMEN_VECTOR:
7169	case DIMEN_STAR:
7170	case DIMEN_THIS_IMAGE:
7171	  gfc_error ("Bad array specification in ALLOCATE statement at %L",
7172		     &e->where);
7173	  goto failure;
7174	}
7175
7176check_symbols:
7177      for (a = code->ext.alloc.list; a; a = a->next)
7178	{
7179	  sym = a->expr->symtree->n.sym;
7180
7181	  /* TODO - check derived type components.  */
7182	  if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
7183	    continue;
7184
7185	  if ((ar->start[i] != NULL
7186	       && gfc_find_sym_in_expr (sym, ar->start[i]))
7187	      || (ar->end[i] != NULL
7188		  && gfc_find_sym_in_expr (sym, ar->end[i])))
7189	    {
7190	      gfc_error ("%qs must not appear in the array specification at "
7191			 "%L in the same ALLOCATE statement where it is "
7192			 "itself allocated", sym->name, &ar->where);
7193	      goto failure;
7194	    }
7195	}
7196    }
7197
7198  for (i = ar->dimen; i < ar->codimen + ar->dimen; i++)
7199    {
7200      if (ar->dimen_type[i] == DIMEN_ELEMENT
7201	  || ar->dimen_type[i] == DIMEN_RANGE)
7202	{
7203	  if (i == (ar->dimen + ar->codimen - 1))
7204	    {
7205	      gfc_error ("Expected '*' in coindex specification in ALLOCATE "
7206			 "statement at %L", &e->where);
7207	      goto failure;
7208	    }
7209	  continue;
7210	}
7211
7212      if (ar->dimen_type[i] == DIMEN_STAR && i == (ar->dimen + ar->codimen - 1)
7213	  && ar->stride[i] == NULL)
7214	break;
7215
7216      gfc_error ("Bad coarray specification in ALLOCATE statement at %L",
7217		 &e->where);
7218      goto failure;
7219    }
7220
7221success:
7222  return true;
7223
7224failure:
7225  return false;
7226}
7227
7228static void
7229resolve_allocate_deallocate (gfc_code *code, const char *fcn)
7230{
7231  gfc_expr *stat, *errmsg, *pe, *qe;
7232  gfc_alloc *a, *p, *q;
7233
7234  stat = code->expr1;
7235  errmsg = code->expr2;
7236
7237  /* Check the stat variable.  */
7238  if (stat)
7239    {
7240      gfc_check_vardef_context (stat, false, false, false,
7241				_("STAT variable"));
7242
7243      if ((stat->ts.type != BT_INTEGER
7244	   && !(stat->ref && (stat->ref->type == REF_ARRAY
7245			      || stat->ref->type == REF_COMPONENT)))
7246	  || stat->rank > 0)
7247	gfc_error ("Stat-variable at %L must be a scalar INTEGER "
7248		   "variable", &stat->where);
7249
7250      for (p = code->ext.alloc.list; p; p = p->next)
7251	if (p->expr->symtree->n.sym->name == stat->symtree->n.sym->name)
7252	  {
7253	    gfc_ref *ref1, *ref2;
7254	    bool found = true;
7255
7256	    for (ref1 = p->expr->ref, ref2 = stat->ref; ref1 && ref2;
7257		 ref1 = ref1->next, ref2 = ref2->next)
7258	      {
7259		if (ref1->type != REF_COMPONENT || ref2->type != REF_COMPONENT)
7260		  continue;
7261		if (ref1->u.c.component->name != ref2->u.c.component->name)
7262		  {
7263		    found = false;
7264		    break;
7265		  }
7266	      }
7267
7268	    if (found)
7269	      {
7270		gfc_error ("Stat-variable at %L shall not be %sd within "
7271			   "the same %s statement", &stat->where, fcn, fcn);
7272		break;
7273	      }
7274	  }
7275    }
7276
7277  /* Check the errmsg variable.  */
7278  if (errmsg)
7279    {
7280      if (!stat)
7281	gfc_warning (0, "ERRMSG at %L is useless without a STAT tag",
7282		     &errmsg->where);
7283
7284      gfc_check_vardef_context (errmsg, false, false, false,
7285				_("ERRMSG variable"));
7286
7287      if ((errmsg->ts.type != BT_CHARACTER
7288	   && !(errmsg->ref
7289		&& (errmsg->ref->type == REF_ARRAY
7290		    || errmsg->ref->type == REF_COMPONENT)))
7291	  || errmsg->rank > 0 )
7292	gfc_error ("Errmsg-variable at %L must be a scalar CHARACTER "
7293		   "variable", &errmsg->where);
7294
7295      for (p = code->ext.alloc.list; p; p = p->next)
7296	if (p->expr->symtree->n.sym->name == errmsg->symtree->n.sym->name)
7297	  {
7298	    gfc_ref *ref1, *ref2;
7299	    bool found = true;
7300
7301	    for (ref1 = p->expr->ref, ref2 = errmsg->ref; ref1 && ref2;
7302		 ref1 = ref1->next, ref2 = ref2->next)
7303	      {
7304		if (ref1->type != REF_COMPONENT || ref2->type != REF_COMPONENT)
7305		  continue;
7306		if (ref1->u.c.component->name != ref2->u.c.component->name)
7307		  {
7308		    found = false;
7309		    break;
7310		  }
7311	      }
7312
7313	    if (found)
7314	      {
7315		gfc_error ("Errmsg-variable at %L shall not be %sd within "
7316			   "the same %s statement", &errmsg->where, fcn, fcn);
7317		break;
7318	      }
7319	  }
7320    }
7321
7322  /* Check that an allocate-object appears only once in the statement.  */
7323
7324  for (p = code->ext.alloc.list; p; p = p->next)
7325    {
7326      pe = p->expr;
7327      for (q = p->next; q; q = q->next)
7328	{
7329	  qe = q->expr;
7330	  if (pe->symtree->n.sym->name == qe->symtree->n.sym->name)
7331	    {
7332	      /* This is a potential collision.  */
7333	      gfc_ref *pr = pe->ref;
7334	      gfc_ref *qr = qe->ref;
7335
7336	      /* Follow the references  until
7337		 a) They start to differ, in which case there is no error;
7338		 you can deallocate a%b and a%c in a single statement
7339		 b) Both of them stop, which is an error
7340		 c) One of them stops, which is also an error.  */
7341	      while (1)
7342		{
7343		  if (pr == NULL && qr == NULL)
7344		    {
7345		      gfc_error_1 ("Allocate-object at %L also appears at %L",
7346				   &pe->where, &qe->where);
7347		      break;
7348		    }
7349		  else if (pr != NULL && qr == NULL)
7350		    {
7351		      gfc_error_1 ("Allocate-object at %L is subobject of"
7352				   " object at %L", &pe->where, &qe->where);
7353		      break;
7354		    }
7355		  else if (pr == NULL && qr != NULL)
7356		    {
7357		      gfc_error_1 ("Allocate-object at %L is subobject of"
7358				   " object at %L", &qe->where, &pe->where);
7359		      break;
7360		    }
7361		  /* Here, pr != NULL && qr != NULL  */
7362		  gcc_assert(pr->type == qr->type);
7363		  if (pr->type == REF_ARRAY)
7364		    {
7365		      /* Handle cases like allocate(v(3)%x(3), v(2)%x(3)),
7366			 which are legal.  */
7367		      gcc_assert (qr->type == REF_ARRAY);
7368
7369		      if (pr->next && qr->next)
7370			{
7371			  int i;
7372			  gfc_array_ref *par = &(pr->u.ar);
7373			  gfc_array_ref *qar = &(qr->u.ar);
7374
7375			  for (i=0; i<par->dimen; i++)
7376			    {
7377			      if ((par->start[i] != NULL
7378				   || qar->start[i] != NULL)
7379				  && gfc_dep_compare_expr (par->start[i],
7380							   qar->start[i]) != 0)
7381				goto break_label;
7382			    }
7383			}
7384		    }
7385		  else
7386		    {
7387		      if (pr->u.c.component->name != qr->u.c.component->name)
7388			break;
7389		    }
7390
7391		  pr = pr->next;
7392		  qr = qr->next;
7393		}
7394	    break_label:
7395	      ;
7396	    }
7397	}
7398    }
7399
7400  if (strcmp (fcn, "ALLOCATE") == 0)
7401    {
7402      for (a = code->ext.alloc.list; a; a = a->next)
7403	resolve_allocate_expr (a->expr, code);
7404    }
7405  else
7406    {
7407      for (a = code->ext.alloc.list; a; a = a->next)
7408	resolve_deallocate_expr (a->expr);
7409    }
7410}
7411
7412
7413/************ SELECT CASE resolution subroutines ************/
7414
7415/* Callback function for our mergesort variant.  Determines interval
7416   overlaps for CASEs. Return <0 if op1 < op2, 0 for overlap, >0 for
7417   op1 > op2.  Assumes we're not dealing with the default case.
7418   We have op1 = (:L), (K:L) or (K:) and op2 = (:N), (M:N) or (M:).
7419   There are nine situations to check.  */
7420
7421static int
7422compare_cases (const gfc_case *op1, const gfc_case *op2)
7423{
7424  int retval;
7425
7426  if (op1->low == NULL) /* op1 = (:L)  */
7427    {
7428      /* op2 = (:N), so overlap.  */
7429      retval = 0;
7430      /* op2 = (M:) or (M:N),  L < M  */
7431      if (op2->low != NULL
7432	  && gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
7433	retval = -1;
7434    }
7435  else if (op1->high == NULL) /* op1 = (K:)  */
7436    {
7437      /* op2 = (M:), so overlap.  */
7438      retval = 0;
7439      /* op2 = (:N) or (M:N), K > N  */
7440      if (op2->high != NULL
7441	  && gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
7442	retval = 1;
7443    }
7444  else /* op1 = (K:L)  */
7445    {
7446      if (op2->low == NULL)       /* op2 = (:N), K > N  */
7447	retval = (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
7448		 ? 1 : 0;
7449      else if (op2->high == NULL) /* op2 = (M:), L < M  */
7450	retval = (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
7451		 ? -1 : 0;
7452      else			/* op2 = (M:N)  */
7453	{
7454	  retval =  0;
7455	  /* L < M  */
7456	  if (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
7457	    retval =  -1;
7458	  /* K > N  */
7459	  else if (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
7460	    retval =  1;
7461	}
7462    }
7463
7464  return retval;
7465}
7466
7467
7468/* Merge-sort a double linked case list, detecting overlap in the
7469   process.  LIST is the head of the double linked case list before it
7470   is sorted.  Returns the head of the sorted list if we don't see any
7471   overlap, or NULL otherwise.  */
7472
7473static gfc_case *
7474check_case_overlap (gfc_case *list)
7475{
7476  gfc_case *p, *q, *e, *tail;
7477  int insize, nmerges, psize, qsize, cmp, overlap_seen;
7478
7479  /* If the passed list was empty, return immediately.  */
7480  if (!list)
7481    return NULL;
7482
7483  overlap_seen = 0;
7484  insize = 1;
7485
7486  /* Loop unconditionally.  The only exit from this loop is a return
7487     statement, when we've finished sorting the case list.  */
7488  for (;;)
7489    {
7490      p = list;
7491      list = NULL;
7492      tail = NULL;
7493
7494      /* Count the number of merges we do in this pass.  */
7495      nmerges = 0;
7496
7497      /* Loop while there exists a merge to be done.  */
7498      while (p)
7499	{
7500	  int i;
7501
7502	  /* Count this merge.  */
7503	  nmerges++;
7504
7505	  /* Cut the list in two pieces by stepping INSIZE places
7506	     forward in the list, starting from P.  */
7507	  psize = 0;
7508	  q = p;
7509	  for (i = 0; i < insize; i++)
7510	    {
7511	      psize++;
7512	      q = q->right;
7513	      if (!q)
7514		break;
7515	    }
7516	  qsize = insize;
7517
7518	  /* Now we have two lists.  Merge them!  */
7519	  while (psize > 0 || (qsize > 0 && q != NULL))
7520	    {
7521	      /* See from which the next case to merge comes from.  */
7522	      if (psize == 0)
7523		{
7524		  /* P is empty so the next case must come from Q.  */
7525		  e = q;
7526		  q = q->right;
7527		  qsize--;
7528		}
7529	      else if (qsize == 0 || q == NULL)
7530		{
7531		  /* Q is empty.  */
7532		  e = p;
7533		  p = p->right;
7534		  psize--;
7535		}
7536	      else
7537		{
7538		  cmp = compare_cases (p, q);
7539		  if (cmp < 0)
7540		    {
7541		      /* The whole case range for P is less than the
7542			 one for Q.  */
7543		      e = p;
7544		      p = p->right;
7545		      psize--;
7546		    }
7547		  else if (cmp > 0)
7548		    {
7549		      /* The whole case range for Q is greater than
7550			 the case range for P.  */
7551		      e = q;
7552		      q = q->right;
7553		      qsize--;
7554		    }
7555		  else
7556		    {
7557		      /* The cases overlap, or they are the same
7558			 element in the list.  Either way, we must
7559			 issue an error and get the next case from P.  */
7560		      /* FIXME: Sort P and Q by line number.  */
7561		      gfc_error_1 ("CASE label at %L overlaps with CASE "
7562				 "label at %L", &p->where, &q->where);
7563		      overlap_seen = 1;
7564		      e = p;
7565		      p = p->right;
7566		      psize--;
7567		    }
7568		}
7569
7570		/* Add the next element to the merged list.  */
7571	      if (tail)
7572		tail->right = e;
7573	      else
7574		list = e;
7575	      e->left = tail;
7576	      tail = e;
7577	    }
7578
7579	  /* P has now stepped INSIZE places along, and so has Q.  So
7580	     they're the same.  */
7581	  p = q;
7582	}
7583      tail->right = NULL;
7584
7585      /* If we have done only one merge or none at all, we've
7586	 finished sorting the cases.  */
7587      if (nmerges <= 1)
7588	{
7589	  if (!overlap_seen)
7590	    return list;
7591	  else
7592	    return NULL;
7593	}
7594
7595      /* Otherwise repeat, merging lists twice the size.  */
7596      insize *= 2;
7597    }
7598}
7599
7600
7601/* Check to see if an expression is suitable for use in a CASE statement.
7602   Makes sure that all case expressions are scalar constants of the same
7603   type.  Return false if anything is wrong.  */
7604
7605static bool
7606validate_case_label_expr (gfc_expr *e, gfc_expr *case_expr)
7607{
7608  if (e == NULL) return true;
7609
7610  if (e->ts.type != case_expr->ts.type)
7611    {
7612      gfc_error ("Expression in CASE statement at %L must be of type %s",
7613		 &e->where, gfc_basic_typename (case_expr->ts.type));
7614      return false;
7615    }
7616
7617  /* C805 (R808) For a given case-construct, each case-value shall be of
7618     the same type as case-expr.  For character type, length differences
7619     are allowed, but the kind type parameters shall be the same.  */
7620
7621  if (case_expr->ts.type == BT_CHARACTER && e->ts.kind != case_expr->ts.kind)
7622    {
7623      gfc_error ("Expression in CASE statement at %L must be of kind %d",
7624		 &e->where, case_expr->ts.kind);
7625      return false;
7626    }
7627
7628  /* Convert the case value kind to that of case expression kind,
7629     if needed */
7630
7631  if (e->ts.kind != case_expr->ts.kind)
7632    gfc_convert_type_warn (e, &case_expr->ts, 2, 0);
7633
7634  if (e->rank != 0)
7635    {
7636      gfc_error ("Expression in CASE statement at %L must be scalar",
7637		 &e->where);
7638      return false;
7639    }
7640
7641  return true;
7642}
7643
7644
7645/* Given a completely parsed select statement, we:
7646
7647     - Validate all expressions and code within the SELECT.
7648     - Make sure that the selection expression is not of the wrong type.
7649     - Make sure that no case ranges overlap.
7650     - Eliminate unreachable cases and unreachable code resulting from
7651       removing case labels.
7652
7653   The standard does allow unreachable cases, e.g. CASE (5:3).  But
7654   they are a hassle for code generation, and to prevent that, we just
7655   cut them out here.  This is not necessary for overlapping cases
7656   because they are illegal and we never even try to generate code.
7657
7658   We have the additional caveat that a SELECT construct could have
7659   been a computed GOTO in the source code. Fortunately we can fairly
7660   easily work around that here: The case_expr for a "real" SELECT CASE
7661   is in code->expr1, but for a computed GOTO it is in code->expr2. All
7662   we have to do is make sure that the case_expr is a scalar integer
7663   expression.  */
7664
7665static void
7666resolve_select (gfc_code *code, bool select_type)
7667{
7668  gfc_code *body;
7669  gfc_expr *case_expr;
7670  gfc_case *cp, *default_case, *tail, *head;
7671  int seen_unreachable;
7672  int seen_logical;
7673  int ncases;
7674  bt type;
7675  bool t;
7676
7677  if (code->expr1 == NULL)
7678    {
7679      /* This was actually a computed GOTO statement.  */
7680      case_expr = code->expr2;
7681      if (case_expr->ts.type != BT_INTEGER|| case_expr->rank != 0)
7682	gfc_error ("Selection expression in computed GOTO statement "
7683		   "at %L must be a scalar integer expression",
7684		   &case_expr->where);
7685
7686      /* Further checking is not necessary because this SELECT was built
7687	 by the compiler, so it should always be OK.  Just move the
7688	 case_expr from expr2 to expr so that we can handle computed
7689	 GOTOs as normal SELECTs from here on.  */
7690      code->expr1 = code->expr2;
7691      code->expr2 = NULL;
7692      return;
7693    }
7694
7695  case_expr = code->expr1;
7696  type = case_expr->ts.type;
7697
7698  /* F08:C830.  */
7699  if (type != BT_LOGICAL && type != BT_INTEGER && type != BT_CHARACTER)
7700    {
7701      gfc_error ("Argument of SELECT statement at %L cannot be %s",
7702		 &case_expr->where, gfc_typename (&case_expr->ts));
7703
7704      /* Punt. Going on here just produce more garbage error messages.  */
7705      return;
7706    }
7707
7708  /* F08:R842.  */
7709  if (!select_type && case_expr->rank != 0)
7710    {
7711      gfc_error ("Argument of SELECT statement at %L must be a scalar "
7712		 "expression", &case_expr->where);
7713
7714      /* Punt.  */
7715      return;
7716    }
7717
7718  /* Raise a warning if an INTEGER case value exceeds the range of
7719     the case-expr. Later, all expressions will be promoted to the
7720     largest kind of all case-labels.  */
7721
7722  if (type == BT_INTEGER)
7723    for (body = code->block; body; body = body->block)
7724      for (cp = body->ext.block.case_list; cp; cp = cp->next)
7725	{
7726	  if (cp->low
7727	      && gfc_check_integer_range (cp->low->value.integer,
7728					  case_expr->ts.kind) != ARITH_OK)
7729	    gfc_warning (0, "Expression in CASE statement at %L is "
7730			 "not in the range of %s", &cp->low->where,
7731			 gfc_typename (&case_expr->ts));
7732
7733	  if (cp->high
7734	      && cp->low != cp->high
7735	      && gfc_check_integer_range (cp->high->value.integer,
7736					  case_expr->ts.kind) != ARITH_OK)
7737	    gfc_warning (0, "Expression in CASE statement at %L is "
7738			 "not in the range of %s", &cp->high->where,
7739			 gfc_typename (&case_expr->ts));
7740	}
7741
7742  /* PR 19168 has a long discussion concerning a mismatch of the kinds
7743     of the SELECT CASE expression and its CASE values.  Walk the lists
7744     of case values, and if we find a mismatch, promote case_expr to
7745     the appropriate kind.  */
7746
7747  if (type == BT_LOGICAL || type == BT_INTEGER)
7748    {
7749      for (body = code->block; body; body = body->block)
7750	{
7751	  /* Walk the case label list.  */
7752	  for (cp = body->ext.block.case_list; cp; cp = cp->next)
7753	    {
7754	      /* Intercept the DEFAULT case.  It does not have a kind.  */
7755	      if (cp->low == NULL && cp->high == NULL)
7756		continue;
7757
7758	      /* Unreachable case ranges are discarded, so ignore.  */
7759	      if (cp->low != NULL && cp->high != NULL
7760		  && cp->low != cp->high
7761		  && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
7762		continue;
7763
7764	      if (cp->low != NULL
7765		  && case_expr->ts.kind != gfc_kind_max(case_expr, cp->low))
7766		gfc_convert_type_warn (case_expr, &cp->low->ts, 2, 0);
7767
7768	      if (cp->high != NULL
7769		  && case_expr->ts.kind != gfc_kind_max(case_expr, cp->high))
7770		gfc_convert_type_warn (case_expr, &cp->high->ts, 2, 0);
7771	    }
7772	 }
7773    }
7774
7775  /* Assume there is no DEFAULT case.  */
7776  default_case = NULL;
7777  head = tail = NULL;
7778  ncases = 0;
7779  seen_logical = 0;
7780
7781  for (body = code->block; body; body = body->block)
7782    {
7783      /* Assume the CASE list is OK, and all CASE labels can be matched.  */
7784      t = true;
7785      seen_unreachable = 0;
7786
7787      /* Walk the case label list, making sure that all case labels
7788	 are legal.  */
7789      for (cp = body->ext.block.case_list; cp; cp = cp->next)
7790	{
7791	  /* Count the number of cases in the whole construct.  */
7792	  ncases++;
7793
7794	  /* Intercept the DEFAULT case.  */
7795	  if (cp->low == NULL && cp->high == NULL)
7796	    {
7797	      if (default_case != NULL)
7798		{
7799		  gfc_error_1 ("The DEFAULT CASE at %L cannot be followed "
7800			     "by a second DEFAULT CASE at %L",
7801			     &default_case->where, &cp->where);
7802		  t = false;
7803		  break;
7804		}
7805	      else
7806		{
7807		  default_case = cp;
7808		  continue;
7809		}
7810	    }
7811
7812	  /* Deal with single value cases and case ranges.  Errors are
7813	     issued from the validation function.  */
7814	  if (!validate_case_label_expr (cp->low, case_expr)
7815	      || !validate_case_label_expr (cp->high, case_expr))
7816	    {
7817	      t = false;
7818	      break;
7819	    }
7820
7821	  if (type == BT_LOGICAL
7822	      && ((cp->low == NULL || cp->high == NULL)
7823		  || cp->low != cp->high))
7824	    {
7825	      gfc_error ("Logical range in CASE statement at %L is not "
7826			 "allowed", &cp->low->where);
7827	      t = false;
7828	      break;
7829	    }
7830
7831	  if (type == BT_LOGICAL && cp->low->expr_type == EXPR_CONSTANT)
7832	    {
7833	      int value;
7834	      value = cp->low->value.logical == 0 ? 2 : 1;
7835	      if (value & seen_logical)
7836		{
7837		  gfc_error ("Constant logical value in CASE statement "
7838			     "is repeated at %L",
7839			     &cp->low->where);
7840		  t = false;
7841		  break;
7842		}
7843	      seen_logical |= value;
7844	    }
7845
7846	  if (cp->low != NULL && cp->high != NULL
7847	      && cp->low != cp->high
7848	      && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
7849	    {
7850	      if (warn_surprising)
7851		gfc_warning (OPT_Wsurprising,
7852			     "Range specification at %L can never be matched",
7853			     &cp->where);
7854
7855	      cp->unreachable = 1;
7856	      seen_unreachable = 1;
7857	    }
7858	  else
7859	    {
7860	      /* If the case range can be matched, it can also overlap with
7861		 other cases.  To make sure it does not, we put it in a
7862		 double linked list here.  We sort that with a merge sort
7863		 later on to detect any overlapping cases.  */
7864	      if (!head)
7865		{
7866		  head = tail = cp;
7867		  head->right = head->left = NULL;
7868		}
7869	      else
7870		{
7871		  tail->right = cp;
7872		  tail->right->left = tail;
7873		  tail = tail->right;
7874		  tail->right = NULL;
7875		}
7876	    }
7877	}
7878
7879      /* It there was a failure in the previous case label, give up
7880	 for this case label list.  Continue with the next block.  */
7881      if (!t)
7882	continue;
7883
7884      /* See if any case labels that are unreachable have been seen.
7885	 If so, we eliminate them.  This is a bit of a kludge because
7886	 the case lists for a single case statement (label) is a
7887	 single forward linked lists.  */
7888      if (seen_unreachable)
7889      {
7890	/* Advance until the first case in the list is reachable.  */
7891	while (body->ext.block.case_list != NULL
7892	       && body->ext.block.case_list->unreachable)
7893	  {
7894	    gfc_case *n = body->ext.block.case_list;
7895	    body->ext.block.case_list = body->ext.block.case_list->next;
7896	    n->next = NULL;
7897	    gfc_free_case_list (n);
7898	  }
7899
7900	/* Strip all other unreachable cases.  */
7901	if (body->ext.block.case_list)
7902	  {
7903	    for (cp = body->ext.block.case_list; cp && cp->next; cp = cp->next)
7904	      {
7905		if (cp->next->unreachable)
7906		  {
7907		    gfc_case *n = cp->next;
7908		    cp->next = cp->next->next;
7909		    n->next = NULL;
7910		    gfc_free_case_list (n);
7911		  }
7912	      }
7913	  }
7914      }
7915    }
7916
7917  /* See if there were overlapping cases.  If the check returns NULL,
7918     there was overlap.  In that case we don't do anything.  If head
7919     is non-NULL, we prepend the DEFAULT case.  The sorted list can
7920     then used during code generation for SELECT CASE constructs with
7921     a case expression of a CHARACTER type.  */
7922  if (head)
7923    {
7924      head = check_case_overlap (head);
7925
7926      /* Prepend the default_case if it is there.  */
7927      if (head != NULL && default_case)
7928	{
7929	  default_case->left = NULL;
7930	  default_case->right = head;
7931	  head->left = default_case;
7932	}
7933    }
7934
7935  /* Eliminate dead blocks that may be the result if we've seen
7936     unreachable case labels for a block.  */
7937  for (body = code; body && body->block; body = body->block)
7938    {
7939      if (body->block->ext.block.case_list == NULL)
7940	{
7941	  /* Cut the unreachable block from the code chain.  */
7942	  gfc_code *c = body->block;
7943	  body->block = c->block;
7944
7945	  /* Kill the dead block, but not the blocks below it.  */
7946	  c->block = NULL;
7947	  gfc_free_statements (c);
7948	}
7949    }
7950
7951  /* More than two cases is legal but insane for logical selects.
7952     Issue a warning for it.  */
7953  if (warn_surprising && type == BT_LOGICAL && ncases > 2)
7954    gfc_warning (OPT_Wsurprising,
7955		 "Logical SELECT CASE block at %L has more that two cases",
7956		 &code->loc);
7957}
7958
7959
7960/* Check if a derived type is extensible.  */
7961
7962bool
7963gfc_type_is_extensible (gfc_symbol *sym)
7964{
7965  return !(sym->attr.is_bind_c || sym->attr.sequence
7966	   || (sym->attr.is_class
7967	       && sym->components->ts.u.derived->attr.unlimited_polymorphic));
7968}
7969
7970
7971/* Resolve an associate-name:  Resolve target and ensure the type-spec is
7972   correct as well as possibly the array-spec.  */
7973
7974static void
7975resolve_assoc_var (gfc_symbol* sym, bool resolve_target)
7976{
7977  gfc_expr* target;
7978
7979  gcc_assert (sym->assoc);
7980  gcc_assert (sym->attr.flavor == FL_VARIABLE);
7981
7982  /* If this is for SELECT TYPE, the target may not yet be set.  In that
7983     case, return.  Resolution will be called later manually again when
7984     this is done.  */
7985  target = sym->assoc->target;
7986  if (!target)
7987    return;
7988  gcc_assert (!sym->assoc->dangling);
7989
7990  if (resolve_target && !gfc_resolve_expr (target))
7991    return;
7992
7993  /* For variable targets, we get some attributes from the target.  */
7994  if (target->expr_type == EXPR_VARIABLE)
7995    {
7996      gfc_symbol* tsym;
7997
7998      gcc_assert (target->symtree);
7999      tsym = target->symtree->n.sym;
8000
8001      sym->attr.asynchronous = tsym->attr.asynchronous;
8002      sym->attr.volatile_ = tsym->attr.volatile_;
8003
8004      sym->attr.target = tsym->attr.target
8005			 || gfc_expr_attr (target).pointer;
8006      if (is_subref_array (target))
8007	sym->attr.subref_array_pointer = 1;
8008    }
8009
8010  /* Get type if this was not already set.  Note that it can be
8011     some other type than the target in case this is a SELECT TYPE
8012     selector!  So we must not update when the type is already there.  */
8013  if (sym->ts.type == BT_UNKNOWN)
8014    sym->ts = target->ts;
8015  gcc_assert (sym->ts.type != BT_UNKNOWN);
8016
8017  /* See if this is a valid association-to-variable.  */
8018  sym->assoc->variable = (target->expr_type == EXPR_VARIABLE
8019			  && !gfc_has_vector_subscript (target));
8020
8021  /* Finally resolve if this is an array or not.  */
8022  if (sym->attr.dimension && target->rank == 0)
8023    {
8024      /* primary.c makes the assumption that a reference to an associate
8025	 name followed by a left parenthesis is an array reference.  */
8026      if (sym->ts.type != BT_CHARACTER)
8027	gfc_error ("Associate-name %qs at %L is used as array",
8028		   sym->name, &sym->declared_at);
8029      sym->attr.dimension = 0;
8030      return;
8031    }
8032
8033  /* We cannot deal with class selectors that need temporaries.  */
8034  if (target->ts.type == BT_CLASS
8035	&& gfc_ref_needs_temporary_p (target->ref))
8036    {
8037      gfc_error ("CLASS selector at %L needs a temporary which is not "
8038		 "yet implemented", &target->where);
8039      return;
8040    }
8041
8042  if (target->ts.type != BT_CLASS && target->rank > 0)
8043    sym->attr.dimension = 1;
8044  else if (target->ts.type == BT_CLASS)
8045    gfc_fix_class_refs (target);
8046
8047  /* The associate-name will have a correct type by now. Make absolutely
8048     sure that it has not picked up a dimension attribute.  */
8049  if (sym->ts.type == BT_CLASS)
8050    sym->attr.dimension = 0;
8051
8052  if (sym->attr.dimension)
8053    {
8054      sym->as = gfc_get_array_spec ();
8055      sym->as->rank = target->rank;
8056      sym->as->type = AS_DEFERRED;
8057      sym->as->corank = gfc_get_corank (target);
8058    }
8059
8060  /* Mark this as an associate variable.  */
8061  sym->attr.associate_var = 1;
8062
8063  /* If the target is a good class object, so is the associate variable.  */
8064  if (sym->ts.type == BT_CLASS && gfc_expr_attr (target).class_ok)
8065    sym->attr.class_ok = 1;
8066}
8067
8068
8069/* Resolve a SELECT TYPE statement.  */
8070
8071static void
8072resolve_select_type (gfc_code *code, gfc_namespace *old_ns)
8073{
8074  gfc_symbol *selector_type;
8075  gfc_code *body, *new_st, *if_st, *tail;
8076  gfc_code *class_is = NULL, *default_case = NULL;
8077  gfc_case *c;
8078  gfc_symtree *st;
8079  char name[GFC_MAX_SYMBOL_LEN];
8080  gfc_namespace *ns;
8081  int error = 0;
8082  int charlen = 0;
8083
8084  ns = code->ext.block.ns;
8085  gfc_resolve (ns);
8086
8087  /* Check for F03:C813.  */
8088  if (code->expr1->ts.type != BT_CLASS
8089      && !(code->expr2 && code->expr2->ts.type == BT_CLASS))
8090    {
8091      gfc_error ("Selector shall be polymorphic in SELECT TYPE statement "
8092		 "at %L", &code->loc);
8093      return;
8094    }
8095
8096  if (!code->expr1->symtree->n.sym->attr.class_ok)
8097    return;
8098
8099  if (code->expr2)
8100    {
8101      if (code->expr1->symtree->n.sym->attr.untyped)
8102	code->expr1->symtree->n.sym->ts = code->expr2->ts;
8103      selector_type = CLASS_DATA (code->expr2)->ts.u.derived;
8104
8105      /* F2008: C803 The selector expression must not be coindexed.  */
8106      if (gfc_is_coindexed (code->expr2))
8107	{
8108	  gfc_error ("Selector at %L must not be coindexed",
8109		     &code->expr2->where);
8110	  return;
8111	}
8112
8113    }
8114  else
8115    {
8116      selector_type = CLASS_DATA (code->expr1)->ts.u.derived;
8117
8118      if (gfc_is_coindexed (code->expr1))
8119	{
8120	  gfc_error ("Selector at %L must not be coindexed",
8121		     &code->expr1->where);
8122	  return;
8123	}
8124    }
8125
8126  /* Loop over TYPE IS / CLASS IS cases.  */
8127  for (body = code->block; body; body = body->block)
8128    {
8129      c = body->ext.block.case_list;
8130
8131      /* Check F03:C815.  */
8132      if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
8133	  && !selector_type->attr.unlimited_polymorphic
8134	  && !gfc_type_is_extensible (c->ts.u.derived))
8135	{
8136	  gfc_error ("Derived type %qs at %L must be extensible",
8137		     c->ts.u.derived->name, &c->where);
8138	  error++;
8139	  continue;
8140	}
8141
8142      /* Check F03:C816.  */
8143      if (c->ts.type != BT_UNKNOWN && !selector_type->attr.unlimited_polymorphic
8144	  && ((c->ts.type != BT_DERIVED && c->ts.type != BT_CLASS)
8145	      || !gfc_type_is_extension_of (selector_type, c->ts.u.derived)))
8146	{
8147	  if (c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
8148	    gfc_error ("Derived type %qs at %L must be an extension of %qs",
8149		       c->ts.u.derived->name, &c->where, selector_type->name);
8150	  else
8151	    gfc_error ("Unexpected intrinsic type %qs at %L",
8152		       gfc_basic_typename (c->ts.type), &c->where);
8153	  error++;
8154	  continue;
8155	}
8156
8157      /* Check F03:C814.  */
8158      if (c->ts.type == BT_CHARACTER && c->ts.u.cl->length != NULL)
8159	{
8160	  gfc_error ("The type-spec at %L shall specify that each length "
8161		     "type parameter is assumed", &c->where);
8162	  error++;
8163	  continue;
8164	}
8165
8166      /* Intercept the DEFAULT case.  */
8167      if (c->ts.type == BT_UNKNOWN)
8168	{
8169	  /* Check F03:C818.  */
8170	  if (default_case)
8171	    {
8172	      gfc_error_1 ("The DEFAULT CASE at %L cannot be followed "
8173			 "by a second DEFAULT CASE at %L",
8174			 &default_case->ext.block.case_list->where, &c->where);
8175	      error++;
8176	      continue;
8177	    }
8178
8179	  default_case = body;
8180	}
8181    }
8182
8183  if (error > 0)
8184    return;
8185
8186  /* Transform SELECT TYPE statement to BLOCK and associate selector to
8187     target if present.  If there are any EXIT statements referring to the
8188     SELECT TYPE construct, this is no problem because the gfc_code
8189     reference stays the same and EXIT is equally possible from the BLOCK
8190     it is changed to.  */
8191  code->op = EXEC_BLOCK;
8192  if (code->expr2)
8193    {
8194      gfc_association_list* assoc;
8195
8196      assoc = gfc_get_association_list ();
8197      assoc->st = code->expr1->symtree;
8198      assoc->target = gfc_copy_expr (code->expr2);
8199      assoc->target->where = code->expr2->where;
8200      /* assoc->variable will be set by resolve_assoc_var.  */
8201
8202      code->ext.block.assoc = assoc;
8203      code->expr1->symtree->n.sym->assoc = assoc;
8204
8205      resolve_assoc_var (code->expr1->symtree->n.sym, false);
8206    }
8207  else
8208    code->ext.block.assoc = NULL;
8209
8210  /* Add EXEC_SELECT to switch on type.  */
8211  new_st = gfc_get_code (code->op);
8212  new_st->expr1 = code->expr1;
8213  new_st->expr2 = code->expr2;
8214  new_st->block = code->block;
8215  code->expr1 = code->expr2 =  NULL;
8216  code->block = NULL;
8217  if (!ns->code)
8218    ns->code = new_st;
8219  else
8220    ns->code->next = new_st;
8221  code = new_st;
8222  code->op = EXEC_SELECT;
8223
8224  gfc_add_vptr_component (code->expr1);
8225  gfc_add_hash_component (code->expr1);
8226
8227  /* Loop over TYPE IS / CLASS IS cases.  */
8228  for (body = code->block; body; body = body->block)
8229    {
8230      c = body->ext.block.case_list;
8231
8232      if (c->ts.type == BT_DERIVED)
8233	c->low = c->high = gfc_get_int_expr (gfc_default_integer_kind, NULL,
8234					     c->ts.u.derived->hash_value);
8235      else if (c->ts.type != BT_CLASS && c->ts.type != BT_UNKNOWN)
8236	{
8237	  gfc_symbol *ivtab;
8238	  gfc_expr *e;
8239
8240	  ivtab = gfc_find_vtab (&c->ts);
8241	  gcc_assert (ivtab && CLASS_DATA (ivtab)->initializer);
8242	  e = CLASS_DATA (ivtab)->initializer;
8243	  c->low = c->high = gfc_copy_expr (e);
8244	}
8245
8246      else if (c->ts.type == BT_UNKNOWN)
8247	continue;
8248
8249      /* Associate temporary to selector.  This should only be done
8250	 when this case is actually true, so build a new ASSOCIATE
8251	 that does precisely this here (instead of using the
8252	 'global' one).  */
8253
8254      if (c->ts.type == BT_CLASS)
8255	sprintf (name, "__tmp_class_%s", c->ts.u.derived->name);
8256      else if (c->ts.type == BT_DERIVED)
8257	sprintf (name, "__tmp_type_%s", c->ts.u.derived->name);
8258      else if (c->ts.type == BT_CHARACTER)
8259	{
8260	  if (c->ts.u.cl && c->ts.u.cl->length
8261	      && c->ts.u.cl->length->expr_type == EXPR_CONSTANT)
8262	    charlen = mpz_get_si (c->ts.u.cl->length->value.integer);
8263	  sprintf (name, "__tmp_%s_%d_%d", gfc_basic_typename (c->ts.type),
8264	           charlen, c->ts.kind);
8265	}
8266      else
8267	sprintf (name, "__tmp_%s_%d", gfc_basic_typename (c->ts.type),
8268	         c->ts.kind);
8269
8270      st = gfc_find_symtree (ns->sym_root, name);
8271      gcc_assert (st->n.sym->assoc);
8272      st->n.sym->assoc->target = gfc_get_variable_expr (code->expr1->symtree);
8273      st->n.sym->assoc->target->where = code->expr1->where;
8274      if (c->ts.type != BT_CLASS && c->ts.type != BT_UNKNOWN)
8275	gfc_add_data_component (st->n.sym->assoc->target);
8276
8277      new_st = gfc_get_code (EXEC_BLOCK);
8278      new_st->ext.block.ns = gfc_build_block_ns (ns);
8279      new_st->ext.block.ns->code = body->next;
8280      body->next = new_st;
8281
8282      /* Chain in the new list only if it is marked as dangling.  Otherwise
8283	 there is a CASE label overlap and this is already used.  Just ignore,
8284	 the error is diagnosed elsewhere.  */
8285      if (st->n.sym->assoc->dangling)
8286	{
8287	  new_st->ext.block.assoc = st->n.sym->assoc;
8288	  st->n.sym->assoc->dangling = 0;
8289	}
8290
8291      resolve_assoc_var (st->n.sym, false);
8292    }
8293
8294  /* Take out CLASS IS cases for separate treatment.  */
8295  body = code;
8296  while (body && body->block)
8297    {
8298      if (body->block->ext.block.case_list->ts.type == BT_CLASS)
8299	{
8300	  /* Add to class_is list.  */
8301	  if (class_is == NULL)
8302	    {
8303	      class_is = body->block;
8304	      tail = class_is;
8305	    }
8306	  else
8307	    {
8308	      for (tail = class_is; tail->block; tail = tail->block) ;
8309	      tail->block = body->block;
8310	      tail = tail->block;
8311	    }
8312	  /* Remove from EXEC_SELECT list.  */
8313	  body->block = body->block->block;
8314	  tail->block = NULL;
8315	}
8316      else
8317	body = body->block;
8318    }
8319
8320  if (class_is)
8321    {
8322      gfc_symbol *vtab;
8323
8324      if (!default_case)
8325	{
8326	  /* Add a default case to hold the CLASS IS cases.  */
8327	  for (tail = code; tail->block; tail = tail->block) ;
8328	  tail->block = gfc_get_code (EXEC_SELECT_TYPE);
8329	  tail = tail->block;
8330	  tail->ext.block.case_list = gfc_get_case ();
8331	  tail->ext.block.case_list->ts.type = BT_UNKNOWN;
8332	  tail->next = NULL;
8333	  default_case = tail;
8334	}
8335
8336      /* More than one CLASS IS block?  */
8337      if (class_is->block)
8338	{
8339	  gfc_code **c1,*c2;
8340	  bool swapped;
8341	  /* Sort CLASS IS blocks by extension level.  */
8342	  do
8343	    {
8344	      swapped = false;
8345	      for (c1 = &class_is; (*c1) && (*c1)->block; c1 = &((*c1)->block))
8346		{
8347		  c2 = (*c1)->block;
8348		  /* F03:C817 (check for doubles).  */
8349		  if ((*c1)->ext.block.case_list->ts.u.derived->hash_value
8350		      == c2->ext.block.case_list->ts.u.derived->hash_value)
8351		    {
8352		      gfc_error ("Double CLASS IS block in SELECT TYPE "
8353				 "statement at %L",
8354				 &c2->ext.block.case_list->where);
8355		      return;
8356		    }
8357		  if ((*c1)->ext.block.case_list->ts.u.derived->attr.extension
8358		      < c2->ext.block.case_list->ts.u.derived->attr.extension)
8359		    {
8360		      /* Swap.  */
8361		      (*c1)->block = c2->block;
8362		      c2->block = *c1;
8363		      *c1 = c2;
8364		      swapped = true;
8365		    }
8366		}
8367	    }
8368	  while (swapped);
8369	}
8370
8371      /* Generate IF chain.  */
8372      if_st = gfc_get_code (EXEC_IF);
8373      new_st = if_st;
8374      for (body = class_is; body; body = body->block)
8375	{
8376	  new_st->block = gfc_get_code (EXEC_IF);
8377	  new_st = new_st->block;
8378	  /* Set up IF condition: Call _gfortran_is_extension_of.  */
8379	  new_st->expr1 = gfc_get_expr ();
8380	  new_st->expr1->expr_type = EXPR_FUNCTION;
8381	  new_st->expr1->ts.type = BT_LOGICAL;
8382	  new_st->expr1->ts.kind = 4;
8383	  new_st->expr1->value.function.name = gfc_get_string (PREFIX ("is_extension_of"));
8384	  new_st->expr1->value.function.isym = XCNEW (gfc_intrinsic_sym);
8385	  new_st->expr1->value.function.isym->id = GFC_ISYM_EXTENDS_TYPE_OF;
8386	  /* Set up arguments.  */
8387	  new_st->expr1->value.function.actual = gfc_get_actual_arglist ();
8388	  new_st->expr1->value.function.actual->expr = gfc_get_variable_expr (code->expr1->symtree);
8389	  new_st->expr1->value.function.actual->expr->where = code->loc;
8390	  gfc_add_vptr_component (new_st->expr1->value.function.actual->expr);
8391	  vtab = gfc_find_derived_vtab (body->ext.block.case_list->ts.u.derived);
8392	  st = gfc_find_symtree (vtab->ns->sym_root, vtab->name);
8393	  new_st->expr1->value.function.actual->next = gfc_get_actual_arglist ();
8394	  new_st->expr1->value.function.actual->next->expr = gfc_get_variable_expr (st);
8395	  new_st->next = body->next;
8396	}
8397	if (default_case->next)
8398	  {
8399	    new_st->block = gfc_get_code (EXEC_IF);
8400	    new_st = new_st->block;
8401	    new_st->next = default_case->next;
8402	  }
8403
8404	/* Replace CLASS DEFAULT code by the IF chain.  */
8405	default_case->next = if_st;
8406    }
8407
8408  /* Resolve the internal code.  This can not be done earlier because
8409     it requires that the sym->assoc of selectors is set already.  */
8410  gfc_current_ns = ns;
8411  gfc_resolve_blocks (code->block, gfc_current_ns);
8412  gfc_current_ns = old_ns;
8413
8414  resolve_select (code, true);
8415}
8416
8417
8418/* Resolve a transfer statement. This is making sure that:
8419   -- a derived type being transferred has only non-pointer components
8420   -- a derived type being transferred doesn't have private components, unless
8421      it's being transferred from the module where the type was defined
8422   -- we're not trying to transfer a whole assumed size array.  */
8423
8424static void
8425resolve_transfer (gfc_code *code)
8426{
8427  gfc_typespec *ts;
8428  gfc_symbol *sym;
8429  gfc_ref *ref;
8430  gfc_expr *exp;
8431
8432  exp = code->expr1;
8433
8434  while (exp != NULL && exp->expr_type == EXPR_OP
8435	 && exp->value.op.op == INTRINSIC_PARENTHESES)
8436    exp = exp->value.op.op1;
8437
8438  if (exp && exp->expr_type == EXPR_NULL
8439      && code->ext.dt)
8440    {
8441      gfc_error ("Invalid context for NULL () intrinsic at %L",
8442		 &exp->where);
8443      return;
8444    }
8445
8446  if (exp == NULL || (exp->expr_type != EXPR_VARIABLE
8447		      && exp->expr_type != EXPR_FUNCTION
8448		      && exp->expr_type != EXPR_STRUCTURE))
8449    return;
8450
8451  /* If we are reading, the variable will be changed.  Note that
8452     code->ext.dt may be NULL if the TRANSFER is related to
8453     an INQUIRE statement -- but in this case, we are not reading, either.  */
8454  if (code->ext.dt && code->ext.dt->dt_io_kind->value.iokind == M_READ
8455      && !gfc_check_vardef_context (exp, false, false, false,
8456				    _("item in READ")))
8457    return;
8458
8459  ts = exp->expr_type == EXPR_STRUCTURE ? &exp->ts : &exp->symtree->n.sym->ts;
8460
8461  /* Go to actual component transferred.  */
8462  for (ref = exp->ref; ref; ref = ref->next)
8463    if (ref->type == REF_COMPONENT)
8464      ts = &ref->u.c.component->ts;
8465
8466  if (ts->type == BT_CLASS)
8467    {
8468      /* FIXME: Test for defined input/output.  */
8469      gfc_error ("Data transfer element at %L cannot be polymorphic unless "
8470                "it is processed by a defined input/output procedure",
8471                &code->loc);
8472      return;
8473    }
8474
8475  if (ts->type == BT_DERIVED)
8476    {
8477      /* Check that transferred derived type doesn't contain POINTER
8478	 components.  */
8479      if (ts->u.derived->attr.pointer_comp)
8480	{
8481	  gfc_error ("Data transfer element at %L cannot have POINTER "
8482		     "components unless it is processed by a defined "
8483		     "input/output procedure", &code->loc);
8484	  return;
8485	}
8486
8487      /* F08:C935.  */
8488      if (ts->u.derived->attr.proc_pointer_comp)
8489	{
8490	  gfc_error ("Data transfer element at %L cannot have "
8491		     "procedure pointer components", &code->loc);
8492	  return;
8493	}
8494
8495      if (ts->u.derived->attr.alloc_comp)
8496	{
8497	  gfc_error ("Data transfer element at %L cannot have ALLOCATABLE "
8498		     "components unless it is processed by a defined "
8499		     "input/output procedure", &code->loc);
8500	  return;
8501	}
8502
8503      /* C_PTR and C_FUNPTR have private components which means they can not
8504         be printed.  However, if -std=gnu and not -pedantic, allow
8505         the component to be printed to help debugging.  */
8506      if (ts->u.derived->ts.f90_type == BT_VOID)
8507	{
8508	  if (!gfc_notify_std (GFC_STD_GNU, "Data transfer element at %L "
8509			       "cannot have PRIVATE components", &code->loc))
8510	    return;
8511	}
8512      else if (derived_inaccessible (ts->u.derived))
8513	{
8514	  gfc_error ("Data transfer element at %L cannot have "
8515		     "PRIVATE components",&code->loc);
8516	  return;
8517	}
8518    }
8519
8520  if (exp->expr_type == EXPR_STRUCTURE)
8521    return;
8522
8523  sym = exp->symtree->n.sym;
8524
8525  if (sym->as != NULL && sym->as->type == AS_ASSUMED_SIZE && exp->ref
8526      && exp->ref->type == REF_ARRAY && exp->ref->u.ar.type == AR_FULL)
8527    {
8528      gfc_error ("Data transfer element at %L cannot be a full reference to "
8529		 "an assumed-size array", &code->loc);
8530      return;
8531    }
8532}
8533
8534
8535/*********** Toplevel code resolution subroutines ***********/
8536
8537/* Find the set of labels that are reachable from this block.  We also
8538   record the last statement in each block.  */
8539
8540static void
8541find_reachable_labels (gfc_code *block)
8542{
8543  gfc_code *c;
8544
8545  if (!block)
8546    return;
8547
8548  cs_base->reachable_labels = bitmap_obstack_alloc (&labels_obstack);
8549
8550  /* Collect labels in this block.  We don't keep those corresponding
8551     to END {IF|SELECT}, these are checked in resolve_branch by going
8552     up through the code_stack.  */
8553  for (c = block; c; c = c->next)
8554    {
8555      if (c->here && c->op != EXEC_END_NESTED_BLOCK)
8556	bitmap_set_bit (cs_base->reachable_labels, c->here->value);
8557    }
8558
8559  /* Merge with labels from parent block.  */
8560  if (cs_base->prev)
8561    {
8562      gcc_assert (cs_base->prev->reachable_labels);
8563      bitmap_ior_into (cs_base->reachable_labels,
8564		       cs_base->prev->reachable_labels);
8565    }
8566}
8567
8568
8569static void
8570resolve_lock_unlock_event (gfc_code *code)
8571{
8572  if (code->expr1->expr_type == EXPR_FUNCTION
8573      && code->expr1->value.function.isym
8574      && code->expr1->value.function.isym->id == GFC_ISYM_CAF_GET)
8575    remove_caf_get_intrinsic (code->expr1);
8576
8577  if ((code->op == EXEC_LOCK || code->op == EXEC_UNLOCK)
8578      && (code->expr1->ts.type != BT_DERIVED
8579	  || code->expr1->expr_type != EXPR_VARIABLE
8580	  || code->expr1->ts.u.derived->from_intmod != INTMOD_ISO_FORTRAN_ENV
8581	  || code->expr1->ts.u.derived->intmod_sym_id != ISOFORTRAN_LOCK_TYPE
8582	  || code->expr1->rank != 0
8583	  || (!gfc_is_coarray (code->expr1) &&
8584	      !gfc_is_coindexed (code->expr1))))
8585    gfc_error ("Lock variable at %L must be a scalar of type LOCK_TYPE",
8586	       &code->expr1->where);
8587  else if ((code->op == EXEC_EVENT_POST || code->op == EXEC_EVENT_WAIT)
8588	   && (code->expr1->ts.type != BT_DERIVED
8589	       || code->expr1->expr_type != EXPR_VARIABLE
8590	       || code->expr1->ts.u.derived->from_intmod
8591		  != INTMOD_ISO_FORTRAN_ENV
8592	       || code->expr1->ts.u.derived->intmod_sym_id
8593		  != ISOFORTRAN_EVENT_TYPE
8594	       || code->expr1->rank != 0))
8595    gfc_error ("Event variable at %L must be a scalar of type EVENT_TYPE",
8596	       &code->expr1->where);
8597  else if (code->op == EXEC_EVENT_POST && !gfc_is_coarray (code->expr1)
8598	   && !gfc_is_coindexed (code->expr1))
8599    gfc_error ("Event variable argument at %L must be a coarray or coindexed",
8600	       &code->expr1->where);
8601  else if (code->op == EXEC_EVENT_WAIT && !gfc_is_coarray (code->expr1))
8602    gfc_error ("Event variable argument at %L must be a coarray but not "
8603	       "coindexed", &code->expr1->where);
8604
8605  /* Check STAT.  */
8606  if (code->expr2
8607      && (code->expr2->ts.type != BT_INTEGER || code->expr2->rank != 0
8608	  || code->expr2->expr_type != EXPR_VARIABLE))
8609    gfc_error ("STAT= argument at %L must be a scalar INTEGER variable",
8610	       &code->expr2->where);
8611
8612  if (code->expr2
8613      && !gfc_check_vardef_context (code->expr2, false, false, false,
8614				    _("STAT variable")))
8615    return;
8616
8617  /* Check ERRMSG.  */
8618  if (code->expr3
8619      && (code->expr3->ts.type != BT_CHARACTER || code->expr3->rank != 0
8620	  || code->expr3->expr_type != EXPR_VARIABLE))
8621    gfc_error ("ERRMSG= argument at %L must be a scalar CHARACTER variable",
8622	       &code->expr3->where);
8623
8624  if (code->expr3
8625      && !gfc_check_vardef_context (code->expr3, false, false, false,
8626				    _("ERRMSG variable")))
8627    return;
8628
8629  /* Check for LOCK the ACQUIRED_LOCK.  */
8630  if (code->op != EXEC_EVENT_WAIT && code->expr4
8631      && (code->expr4->ts.type != BT_LOGICAL || code->expr4->rank != 0
8632	  || code->expr4->expr_type != EXPR_VARIABLE))
8633    gfc_error ("ACQUIRED_LOCK= argument at %L must be a scalar LOGICAL "
8634	       "variable", &code->expr4->where);
8635
8636  if (code->op != EXEC_EVENT_WAIT && code->expr4
8637      && !gfc_check_vardef_context (code->expr4, false, false, false,
8638				    _("ACQUIRED_LOCK variable")))
8639    return;
8640
8641  /* Check for EVENT WAIT the UNTIL_COUNT.  */
8642  if (code->op == EXEC_EVENT_WAIT && code->expr4
8643      && (code->expr4->ts.type != BT_INTEGER || code->expr4->rank != 0))
8644    gfc_error ("UNTIL_COUNT= argument at %L must be a scalar INTEGER "
8645	       "expression", &code->expr4->where);
8646}
8647
8648
8649static void
8650resolve_critical (gfc_code *code)
8651{
8652  gfc_symtree *symtree;
8653  gfc_symbol *lock_type;
8654  char name[GFC_MAX_SYMBOL_LEN];
8655  static int serial = 0;
8656
8657  if (flag_coarray != GFC_FCOARRAY_LIB)
8658    return;
8659
8660  symtree = gfc_find_symtree (gfc_current_ns->sym_root,
8661			      GFC_PREFIX ("lock_type"));
8662  if (symtree)
8663    lock_type = symtree->n.sym;
8664  else
8665    {
8666      if (gfc_get_sym_tree (GFC_PREFIX ("lock_type"), gfc_current_ns, &symtree,
8667			    false) != 0)
8668	gcc_unreachable ();
8669      lock_type = symtree->n.sym;
8670      lock_type->attr.flavor = FL_DERIVED;
8671      lock_type->attr.zero_comp = 1;
8672      lock_type->from_intmod = INTMOD_ISO_FORTRAN_ENV;
8673      lock_type->intmod_sym_id = ISOFORTRAN_LOCK_TYPE;
8674    }
8675
8676  sprintf(name, GFC_PREFIX ("lock_var") "%d",serial++);
8677  if (gfc_get_sym_tree (name, gfc_current_ns, &symtree, false) != 0)
8678    gcc_unreachable ();
8679
8680  code->resolved_sym = symtree->n.sym;
8681  symtree->n.sym->attr.flavor = FL_VARIABLE;
8682  symtree->n.sym->attr.referenced = 1;
8683  symtree->n.sym->attr.artificial = 1;
8684  symtree->n.sym->attr.codimension = 1;
8685  symtree->n.sym->ts.type = BT_DERIVED;
8686  symtree->n.sym->ts.u.derived = lock_type;
8687  symtree->n.sym->as = gfc_get_array_spec ();
8688  symtree->n.sym->as->corank = 1;
8689  symtree->n.sym->as->type = AS_EXPLICIT;
8690  symtree->n.sym->as->cotype = AS_EXPLICIT;
8691  symtree->n.sym->as->lower[0] = gfc_get_int_expr (gfc_default_integer_kind,
8692						   NULL, 1);
8693  gfc_commit_symbols();
8694}
8695
8696
8697static void
8698resolve_sync (gfc_code *code)
8699{
8700  /* Check imageset. The * case matches expr1 == NULL.  */
8701  if (code->expr1)
8702    {
8703      if (code->expr1->ts.type != BT_INTEGER || code->expr1->rank > 1)
8704	gfc_error ("Imageset argument at %L must be a scalar or rank-1 "
8705		   "INTEGER expression", &code->expr1->where);
8706      if (code->expr1->expr_type == EXPR_CONSTANT && code->expr1->rank == 0
8707	  && mpz_cmp_si (code->expr1->value.integer, 1) < 0)
8708	gfc_error ("Imageset argument at %L must between 1 and num_images()",
8709		   &code->expr1->where);
8710      else if (code->expr1->expr_type == EXPR_ARRAY
8711	       && gfc_simplify_expr (code->expr1, 0))
8712	{
8713	   gfc_constructor *cons;
8714	   cons = gfc_constructor_first (code->expr1->value.constructor);
8715	   for (; cons; cons = gfc_constructor_next (cons))
8716	     if (cons->expr->expr_type == EXPR_CONSTANT
8717		 &&  mpz_cmp_si (cons->expr->value.integer, 1) < 0)
8718	       gfc_error ("Imageset argument at %L must between 1 and "
8719			  "num_images()", &cons->expr->where);
8720	}
8721    }
8722
8723  /* Check STAT.  */
8724  if (code->expr2
8725      && (code->expr2->ts.type != BT_INTEGER || code->expr2->rank != 0
8726	  || code->expr2->expr_type != EXPR_VARIABLE))
8727    gfc_error ("STAT= argument at %L must be a scalar INTEGER variable",
8728	       &code->expr2->where);
8729
8730  /* Check ERRMSG.  */
8731  if (code->expr3
8732      && (code->expr3->ts.type != BT_CHARACTER || code->expr3->rank != 0
8733	  || code->expr3->expr_type != EXPR_VARIABLE))
8734    gfc_error ("ERRMSG= argument at %L must be a scalar CHARACTER variable",
8735	       &code->expr3->where);
8736}
8737
8738
8739/* Given a branch to a label, see if the branch is conforming.
8740   The code node describes where the branch is located.  */
8741
8742static void
8743resolve_branch (gfc_st_label *label, gfc_code *code)
8744{
8745  code_stack *stack;
8746
8747  if (label == NULL)
8748    return;
8749
8750  /* Step one: is this a valid branching target?  */
8751
8752  if (label->defined == ST_LABEL_UNKNOWN)
8753    {
8754      gfc_error ("Label %d referenced at %L is never defined", label->value,
8755		 &label->where);
8756      return;
8757    }
8758
8759  if (label->defined != ST_LABEL_TARGET && label->defined != ST_LABEL_DO_TARGET)
8760    {
8761      gfc_error_1 ("Statement at %L is not a valid branch target statement "
8762		 "for the branch statement at %L", &label->where, &code->loc);
8763      return;
8764    }
8765
8766  /* Step two: make sure this branch is not a branch to itself ;-)  */
8767
8768  if (code->here == label)
8769    {
8770      gfc_warning (0,
8771		   "Branch at %L may result in an infinite loop", &code->loc);
8772      return;
8773    }
8774
8775  /* Step three:  See if the label is in the same block as the
8776     branching statement.  The hard work has been done by setting up
8777     the bitmap reachable_labels.  */
8778
8779  if (bitmap_bit_p (cs_base->reachable_labels, label->value))
8780    {
8781      /* Check now whether there is a CRITICAL construct; if so, check
8782	 whether the label is still visible outside of the CRITICAL block,
8783	 which is invalid.  */
8784      for (stack = cs_base; stack; stack = stack->prev)
8785	{
8786	  if (stack->current->op == EXEC_CRITICAL
8787	      && bitmap_bit_p (stack->reachable_labels, label->value))
8788	    gfc_error_1 ("GOTO statement at %L leaves CRITICAL construct for "
8789		      "label at %L", &code->loc, &label->where);
8790	  else if (stack->current->op == EXEC_DO_CONCURRENT
8791		   && bitmap_bit_p (stack->reachable_labels, label->value))
8792	    gfc_error_1 ("GOTO statement at %L leaves DO CONCURRENT construct "
8793		      "for label at %L", &code->loc, &label->where);
8794	}
8795
8796      return;
8797    }
8798
8799  /* Step four:  If we haven't found the label in the bitmap, it may
8800    still be the label of the END of the enclosing block, in which
8801    case we find it by going up the code_stack.  */
8802
8803  for (stack = cs_base; stack; stack = stack->prev)
8804    {
8805      if (stack->current->next && stack->current->next->here == label)
8806	break;
8807      if (stack->current->op == EXEC_CRITICAL)
8808	{
8809	  /* Note: A label at END CRITICAL does not leave the CRITICAL
8810	     construct as END CRITICAL is still part of it.  */
8811	  gfc_error_1 ("GOTO statement at %L leaves CRITICAL construct for label"
8812		      " at %L", &code->loc, &label->where);
8813	  return;
8814	}
8815      else if (stack->current->op == EXEC_DO_CONCURRENT)
8816	{
8817	  gfc_error_1 ("GOTO statement at %L leaves DO CONCURRENT construct for "
8818		     "label at %L", &code->loc, &label->where);
8819	  return;
8820	}
8821    }
8822
8823  if (stack)
8824    {
8825      gcc_assert (stack->current->next->op == EXEC_END_NESTED_BLOCK);
8826      return;
8827    }
8828
8829  /* The label is not in an enclosing block, so illegal.  This was
8830     allowed in Fortran 66, so we allow it as extension.  No
8831     further checks are necessary in this case.  */
8832  gfc_notify_std_1 (GFC_STD_LEGACY, "Label at %L is not in the same block "
8833		  "as the GOTO statement at %L", &label->where,
8834		  &code->loc);
8835  return;
8836}
8837
8838
8839/* Check whether EXPR1 has the same shape as EXPR2.  */
8840
8841static bool
8842resolve_where_shape (gfc_expr *expr1, gfc_expr *expr2)
8843{
8844  mpz_t shape[GFC_MAX_DIMENSIONS];
8845  mpz_t shape2[GFC_MAX_DIMENSIONS];
8846  bool result = false;
8847  int i;
8848
8849  /* Compare the rank.  */
8850  if (expr1->rank != expr2->rank)
8851    return result;
8852
8853  /* Compare the size of each dimension.  */
8854  for (i=0; i<expr1->rank; i++)
8855    {
8856      if (!gfc_array_dimen_size (expr1, i, &shape[i]))
8857	goto ignore;
8858
8859      if (!gfc_array_dimen_size (expr2, i, &shape2[i]))
8860	goto ignore;
8861
8862      if (mpz_cmp (shape[i], shape2[i]))
8863	goto over;
8864    }
8865
8866  /* When either of the two expression is an assumed size array, we
8867     ignore the comparison of dimension sizes.  */
8868ignore:
8869  result = true;
8870
8871over:
8872  gfc_clear_shape (shape, i);
8873  gfc_clear_shape (shape2, i);
8874  return result;
8875}
8876
8877
8878/* Check whether a WHERE assignment target or a WHERE mask expression
8879   has the same shape as the outmost WHERE mask expression.  */
8880
8881static void
8882resolve_where (gfc_code *code, gfc_expr *mask)
8883{
8884  gfc_code *cblock;
8885  gfc_code *cnext;
8886  gfc_expr *e = NULL;
8887
8888  cblock = code->block;
8889
8890  /* Store the first WHERE mask-expr of the WHERE statement or construct.
8891     In case of nested WHERE, only the outmost one is stored.  */
8892  if (mask == NULL) /* outmost WHERE */
8893    e = cblock->expr1;
8894  else /* inner WHERE */
8895    e = mask;
8896
8897  while (cblock)
8898    {
8899      if (cblock->expr1)
8900	{
8901	  /* Check if the mask-expr has a consistent shape with the
8902	     outmost WHERE mask-expr.  */
8903	  if (!resolve_where_shape (cblock->expr1, e))
8904	    gfc_error ("WHERE mask at %L has inconsistent shape",
8905		       &cblock->expr1->where);
8906	 }
8907
8908      /* the assignment statement of a WHERE statement, or the first
8909	 statement in where-body-construct of a WHERE construct */
8910      cnext = cblock->next;
8911      while (cnext)
8912	{
8913	  switch (cnext->op)
8914	    {
8915	    /* WHERE assignment statement */
8916	    case EXEC_ASSIGN:
8917
8918	      /* Check shape consistent for WHERE assignment target.  */
8919	      if (e && !resolve_where_shape (cnext->expr1, e))
8920	       gfc_error ("WHERE assignment target at %L has "
8921			  "inconsistent shape", &cnext->expr1->where);
8922	      break;
8923
8924
8925	    case EXEC_ASSIGN_CALL:
8926	      resolve_call (cnext);
8927	      if (!cnext->resolved_sym->attr.elemental)
8928		gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
8929			  &cnext->ext.actual->expr->where);
8930	      break;
8931
8932	    /* WHERE or WHERE construct is part of a where-body-construct */
8933	    case EXEC_WHERE:
8934	      resolve_where (cnext, e);
8935	      break;
8936
8937	    default:
8938	      gfc_error ("Unsupported statement inside WHERE at %L",
8939			 &cnext->loc);
8940	    }
8941	 /* the next statement within the same where-body-construct */
8942	 cnext = cnext->next;
8943       }
8944    /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
8945    cblock = cblock->block;
8946  }
8947}
8948
8949
8950/* Resolve assignment in FORALL construct.
8951   NVAR is the number of FORALL index variables, and VAR_EXPR records the
8952   FORALL index variables.  */
8953
8954static void
8955gfc_resolve_assign_in_forall (gfc_code *code, int nvar, gfc_expr **var_expr)
8956{
8957  int n;
8958
8959  for (n = 0; n < nvar; n++)
8960    {
8961      gfc_symbol *forall_index;
8962
8963      forall_index = var_expr[n]->symtree->n.sym;
8964
8965      /* Check whether the assignment target is one of the FORALL index
8966	 variable.  */
8967      if ((code->expr1->expr_type == EXPR_VARIABLE)
8968	  && (code->expr1->symtree->n.sym == forall_index))
8969	gfc_error ("Assignment to a FORALL index variable at %L",
8970		   &code->expr1->where);
8971      else
8972	{
8973	  /* If one of the FORALL index variables doesn't appear in the
8974	     assignment variable, then there could be a many-to-one
8975	     assignment.  Emit a warning rather than an error because the
8976	     mask could be resolving this problem.  */
8977	  if (!find_forall_index (code->expr1, forall_index, 0))
8978	    gfc_warning (0, "The FORALL with index %qs is not used on the "
8979			 "left side of the assignment at %L and so might "
8980			 "cause multiple assignment to this object",
8981			 var_expr[n]->symtree->name, &code->expr1->where);
8982	}
8983    }
8984}
8985
8986
8987/* Resolve WHERE statement in FORALL construct.  */
8988
8989static void
8990gfc_resolve_where_code_in_forall (gfc_code *code, int nvar,
8991				  gfc_expr **var_expr)
8992{
8993  gfc_code *cblock;
8994  gfc_code *cnext;
8995
8996  cblock = code->block;
8997  while (cblock)
8998    {
8999      /* the assignment statement of a WHERE statement, or the first
9000	 statement in where-body-construct of a WHERE construct */
9001      cnext = cblock->next;
9002      while (cnext)
9003	{
9004	  switch (cnext->op)
9005	    {
9006	    /* WHERE assignment statement */
9007	    case EXEC_ASSIGN:
9008	      gfc_resolve_assign_in_forall (cnext, nvar, var_expr);
9009	      break;
9010
9011	    /* WHERE operator assignment statement */
9012	    case EXEC_ASSIGN_CALL:
9013	      resolve_call (cnext);
9014	      if (!cnext->resolved_sym->attr.elemental)
9015		gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
9016			  &cnext->ext.actual->expr->where);
9017	      break;
9018
9019	    /* WHERE or WHERE construct is part of a where-body-construct */
9020	    case EXEC_WHERE:
9021	      gfc_resolve_where_code_in_forall (cnext, nvar, var_expr);
9022	      break;
9023
9024	    default:
9025	      gfc_error ("Unsupported statement inside WHERE at %L",
9026			 &cnext->loc);
9027	    }
9028	  /* the next statement within the same where-body-construct */
9029	  cnext = cnext->next;
9030	}
9031      /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
9032      cblock = cblock->block;
9033    }
9034}
9035
9036
9037/* Traverse the FORALL body to check whether the following errors exist:
9038   1. For assignment, check if a many-to-one assignment happens.
9039   2. For WHERE statement, check the WHERE body to see if there is any
9040      many-to-one assignment.  */
9041
9042static void
9043gfc_resolve_forall_body (gfc_code *code, int nvar, gfc_expr **var_expr)
9044{
9045  gfc_code *c;
9046
9047  c = code->block->next;
9048  while (c)
9049    {
9050      switch (c->op)
9051	{
9052	case EXEC_ASSIGN:
9053	case EXEC_POINTER_ASSIGN:
9054	  gfc_resolve_assign_in_forall (c, nvar, var_expr);
9055	  break;
9056
9057	case EXEC_ASSIGN_CALL:
9058	  resolve_call (c);
9059	  break;
9060
9061	/* Because the gfc_resolve_blocks() will handle the nested FORALL,
9062	   there is no need to handle it here.  */
9063	case EXEC_FORALL:
9064	  break;
9065	case EXEC_WHERE:
9066	  gfc_resolve_where_code_in_forall(c, nvar, var_expr);
9067	  break;
9068	default:
9069	  break;
9070	}
9071      /* The next statement in the FORALL body.  */
9072      c = c->next;
9073    }
9074}
9075
9076
9077/* Counts the number of iterators needed inside a forall construct, including
9078   nested forall constructs. This is used to allocate the needed memory
9079   in gfc_resolve_forall.  */
9080
9081static int
9082gfc_count_forall_iterators (gfc_code *code)
9083{
9084  int max_iters, sub_iters, current_iters;
9085  gfc_forall_iterator *fa;
9086
9087  gcc_assert(code->op == EXEC_FORALL);
9088  max_iters = 0;
9089  current_iters = 0;
9090
9091  for (fa = code->ext.forall_iterator; fa; fa = fa->next)
9092    current_iters ++;
9093
9094  code = code->block->next;
9095
9096  while (code)
9097    {
9098      if (code->op == EXEC_FORALL)
9099        {
9100          sub_iters = gfc_count_forall_iterators (code);
9101          if (sub_iters > max_iters)
9102            max_iters = sub_iters;
9103        }
9104      code = code->next;
9105    }
9106
9107  return current_iters + max_iters;
9108}
9109
9110
9111/* Given a FORALL construct, first resolve the FORALL iterator, then call
9112   gfc_resolve_forall_body to resolve the FORALL body.  */
9113
9114static void
9115gfc_resolve_forall (gfc_code *code, gfc_namespace *ns, int forall_save)
9116{
9117  static gfc_expr **var_expr;
9118  static int total_var = 0;
9119  static int nvar = 0;
9120  int old_nvar, tmp;
9121  gfc_forall_iterator *fa;
9122  int i;
9123
9124  old_nvar = nvar;
9125
9126  /* Start to resolve a FORALL construct   */
9127  if (forall_save == 0)
9128    {
9129      /* Count the total number of FORALL index in the nested FORALL
9130         construct in order to allocate the VAR_EXPR with proper size.  */
9131      total_var = gfc_count_forall_iterators (code);
9132
9133      /* Allocate VAR_EXPR with NUMBER_OF_FORALL_INDEX elements.  */
9134      var_expr = XCNEWVEC (gfc_expr *, total_var);
9135    }
9136
9137  /* The information about FORALL iterator, including FORALL index start, end
9138     and stride. The FORALL index can not appear in start, end or stride.  */
9139  for (fa = code->ext.forall_iterator; fa; fa = fa->next)
9140    {
9141      /* Check if any outer FORALL index name is the same as the current
9142	 one.  */
9143      for (i = 0; i < nvar; i++)
9144	{
9145	  if (fa->var->symtree->n.sym == var_expr[i]->symtree->n.sym)
9146	    {
9147	      gfc_error ("An outer FORALL construct already has an index "
9148			 "with this name %L", &fa->var->where);
9149	    }
9150	}
9151
9152      /* Record the current FORALL index.  */
9153      var_expr[nvar] = gfc_copy_expr (fa->var);
9154
9155      nvar++;
9156
9157      /* No memory leak.  */
9158      gcc_assert (nvar <= total_var);
9159    }
9160
9161  /* Resolve the FORALL body.  */
9162  gfc_resolve_forall_body (code, nvar, var_expr);
9163
9164  /* May call gfc_resolve_forall to resolve the inner FORALL loop.  */
9165  gfc_resolve_blocks (code->block, ns);
9166
9167  tmp = nvar;
9168  nvar = old_nvar;
9169  /* Free only the VAR_EXPRs allocated in this frame.  */
9170  for (i = nvar; i < tmp; i++)
9171     gfc_free_expr (var_expr[i]);
9172
9173  if (nvar == 0)
9174    {
9175      /* We are in the outermost FORALL construct.  */
9176      gcc_assert (forall_save == 0);
9177
9178      /* VAR_EXPR is not needed any more.  */
9179      free (var_expr);
9180      total_var = 0;
9181    }
9182}
9183
9184
9185/* Resolve a BLOCK construct statement.  */
9186
9187static void
9188resolve_block_construct (gfc_code* code)
9189{
9190  /* Resolve the BLOCK's namespace.  */
9191  gfc_resolve (code->ext.block.ns);
9192
9193  /* For an ASSOCIATE block, the associations (and their targets) are already
9194     resolved during resolve_symbol.  */
9195}
9196
9197
9198/* Resolve lists of blocks found in IF, SELECT CASE, WHERE, FORALL, GOTO and
9199   DO code nodes.  */
9200
9201void
9202gfc_resolve_blocks (gfc_code *b, gfc_namespace *ns)
9203{
9204  bool t;
9205
9206  for (; b; b = b->block)
9207    {
9208      t = gfc_resolve_expr (b->expr1);
9209      if (!gfc_resolve_expr (b->expr2))
9210	t = false;
9211
9212      switch (b->op)
9213	{
9214	case EXEC_IF:
9215	  if (t && b->expr1 != NULL
9216	      && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank != 0))
9217	    gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
9218		       &b->expr1->where);
9219	  break;
9220
9221	case EXEC_WHERE:
9222	  if (t
9223	      && b->expr1 != NULL
9224	      && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank == 0))
9225	    gfc_error ("WHERE/ELSEWHERE clause at %L requires a LOGICAL array",
9226		       &b->expr1->where);
9227	  break;
9228
9229	case EXEC_GOTO:
9230	  resolve_branch (b->label1, b);
9231	  break;
9232
9233	case EXEC_BLOCK:
9234	  resolve_block_construct (b);
9235	  break;
9236
9237	case EXEC_SELECT:
9238	case EXEC_SELECT_TYPE:
9239	case EXEC_FORALL:
9240	case EXEC_DO:
9241	case EXEC_DO_WHILE:
9242	case EXEC_DO_CONCURRENT:
9243	case EXEC_CRITICAL:
9244	case EXEC_READ:
9245	case EXEC_WRITE:
9246	case EXEC_IOLENGTH:
9247	case EXEC_WAIT:
9248	  break;
9249
9250	case EXEC_OACC_PARALLEL_LOOP:
9251	case EXEC_OACC_PARALLEL:
9252	case EXEC_OACC_KERNELS_LOOP:
9253	case EXEC_OACC_KERNELS:
9254	case EXEC_OACC_DATA:
9255	case EXEC_OACC_HOST_DATA:
9256	case EXEC_OACC_LOOP:
9257	case EXEC_OACC_UPDATE:
9258	case EXEC_OACC_WAIT:
9259	case EXEC_OACC_CACHE:
9260	case EXEC_OACC_ENTER_DATA:
9261	case EXEC_OACC_EXIT_DATA:
9262	case EXEC_OMP_ATOMIC:
9263	case EXEC_OMP_CRITICAL:
9264	case EXEC_OMP_DISTRIBUTE:
9265	case EXEC_OMP_DISTRIBUTE_PARALLEL_DO:
9266	case EXEC_OMP_DISTRIBUTE_PARALLEL_DO_SIMD:
9267	case EXEC_OMP_DISTRIBUTE_SIMD:
9268	case EXEC_OMP_DO:
9269	case EXEC_OMP_DO_SIMD:
9270	case EXEC_OMP_MASTER:
9271	case EXEC_OMP_ORDERED:
9272	case EXEC_OMP_PARALLEL:
9273	case EXEC_OMP_PARALLEL_DO:
9274	case EXEC_OMP_PARALLEL_DO_SIMD:
9275	case EXEC_OMP_PARALLEL_SECTIONS:
9276	case EXEC_OMP_PARALLEL_WORKSHARE:
9277	case EXEC_OMP_SECTIONS:
9278	case EXEC_OMP_SIMD:
9279	case EXEC_OMP_SINGLE:
9280	case EXEC_OMP_TARGET:
9281	case EXEC_OMP_TARGET_DATA:
9282	case EXEC_OMP_TARGET_TEAMS:
9283	case EXEC_OMP_TARGET_TEAMS_DISTRIBUTE:
9284	case EXEC_OMP_TARGET_TEAMS_DISTRIBUTE_PARALLEL_DO:
9285	case EXEC_OMP_TARGET_TEAMS_DISTRIBUTE_PARALLEL_DO_SIMD:
9286	case EXEC_OMP_TARGET_TEAMS_DISTRIBUTE_SIMD:
9287	case EXEC_OMP_TARGET_UPDATE:
9288	case EXEC_OMP_TASK:
9289	case EXEC_OMP_TASKGROUP:
9290	case EXEC_OMP_TASKWAIT:
9291	case EXEC_OMP_TASKYIELD:
9292	case EXEC_OMP_TEAMS:
9293	case EXEC_OMP_TEAMS_DISTRIBUTE:
9294	case EXEC_OMP_TEAMS_DISTRIBUTE_PARALLEL_DO:
9295	case EXEC_OMP_TEAMS_DISTRIBUTE_PARALLEL_DO_SIMD:
9296	case EXEC_OMP_TEAMS_DISTRIBUTE_SIMD:
9297	case EXEC_OMP_WORKSHARE:
9298	  break;
9299
9300	default:
9301	  gfc_internal_error ("gfc_resolve_blocks(): Bad block type");
9302	}
9303
9304      gfc_resolve_code (b->next, ns);
9305    }
9306}
9307
9308
9309/* Does everything to resolve an ordinary assignment.  Returns true
9310   if this is an interface assignment.  */
9311static bool
9312resolve_ordinary_assign (gfc_code *code, gfc_namespace *ns)
9313{
9314  bool rval = false;
9315  gfc_expr *lhs;
9316  gfc_expr *rhs;
9317  int llen = 0;
9318  int rlen = 0;
9319  int n;
9320  gfc_ref *ref;
9321  symbol_attribute attr;
9322
9323  if (gfc_extend_assign (code, ns))
9324    {
9325      gfc_expr** rhsptr;
9326
9327      if (code->op == EXEC_ASSIGN_CALL)
9328	{
9329	  lhs = code->ext.actual->expr;
9330	  rhsptr = &code->ext.actual->next->expr;
9331	}
9332      else
9333	{
9334	  gfc_actual_arglist* args;
9335	  gfc_typebound_proc* tbp;
9336
9337	  gcc_assert (code->op == EXEC_COMPCALL);
9338
9339	  args = code->expr1->value.compcall.actual;
9340	  lhs = args->expr;
9341	  rhsptr = &args->next->expr;
9342
9343	  tbp = code->expr1->value.compcall.tbp;
9344	  gcc_assert (!tbp->is_generic);
9345	}
9346
9347      /* Make a temporary rhs when there is a default initializer
9348	 and rhs is the same symbol as the lhs.  */
9349      if ((*rhsptr)->expr_type == EXPR_VARIABLE
9350	    && (*rhsptr)->symtree->n.sym->ts.type == BT_DERIVED
9351	    && gfc_has_default_initializer ((*rhsptr)->symtree->n.sym->ts.u.derived)
9352	    && (lhs->symtree->n.sym == (*rhsptr)->symtree->n.sym))
9353	*rhsptr = gfc_get_parentheses (*rhsptr);
9354
9355      return true;
9356    }
9357
9358  lhs = code->expr1;
9359  rhs = code->expr2;
9360
9361  if (rhs->is_boz
9362      && !gfc_notify_std (GFC_STD_GNU, "BOZ literal at %L outside "
9363			  "a DATA statement and outside INT/REAL/DBLE/CMPLX",
9364			  &code->loc))
9365    return false;
9366
9367  /* Handle the case of a BOZ literal on the RHS.  */
9368  if (rhs->is_boz && lhs->ts.type != BT_INTEGER)
9369    {
9370      int rc;
9371      if (warn_surprising)
9372	gfc_warning (OPT_Wsurprising,
9373		     "BOZ literal at %L is bitwise transferred "
9374		     "non-integer symbol %qs", &code->loc,
9375		     lhs->symtree->n.sym->name);
9376
9377      if (!gfc_convert_boz (rhs, &lhs->ts))
9378	return false;
9379      if ((rc = gfc_range_check (rhs)) != ARITH_OK)
9380	{
9381	  if (rc == ARITH_UNDERFLOW)
9382	    gfc_error ("Arithmetic underflow of bit-wise transferred BOZ at %L"
9383		       ". This check can be disabled with the option "
9384		       "%<-fno-range-check%>", &rhs->where);
9385	  else if (rc == ARITH_OVERFLOW)
9386	    gfc_error ("Arithmetic overflow of bit-wise transferred BOZ at %L"
9387		       ". This check can be disabled with the option "
9388		       "%<-fno-range-check%>", &rhs->where);
9389	  else if (rc == ARITH_NAN)
9390	    gfc_error ("Arithmetic NaN of bit-wise transferred BOZ at %L"
9391		       ". This check can be disabled with the option "
9392		       "%<-fno-range-check%>", &rhs->where);
9393	  return false;
9394	}
9395    }
9396
9397  if (lhs->ts.type == BT_CHARACTER
9398	&& warn_character_truncation)
9399    {
9400      if (lhs->ts.u.cl != NULL
9401	    && lhs->ts.u.cl->length != NULL
9402	    && lhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
9403	llen = mpz_get_si (lhs->ts.u.cl->length->value.integer);
9404
9405      if (rhs->expr_type == EXPR_CONSTANT)
9406 	rlen = rhs->value.character.length;
9407
9408      else if (rhs->ts.u.cl != NULL
9409		 && rhs->ts.u.cl->length != NULL
9410		 && rhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
9411	rlen = mpz_get_si (rhs->ts.u.cl->length->value.integer);
9412
9413      if (rlen && llen && rlen > llen)
9414	gfc_warning_now (OPT_Wcharacter_truncation,
9415			 "CHARACTER expression will be truncated "
9416			 "in assignment (%d/%d) at %L",
9417			 llen, rlen, &code->loc);
9418    }
9419
9420  /* Ensure that a vector index expression for the lvalue is evaluated
9421     to a temporary if the lvalue symbol is referenced in it.  */
9422  if (lhs->rank)
9423    {
9424      for (ref = lhs->ref; ref; ref= ref->next)
9425	if (ref->type == REF_ARRAY)
9426	  {
9427	    for (n = 0; n < ref->u.ar.dimen; n++)
9428	      if (ref->u.ar.dimen_type[n] == DIMEN_VECTOR
9429		  && gfc_find_sym_in_expr (lhs->symtree->n.sym,
9430					   ref->u.ar.start[n]))
9431		ref->u.ar.start[n]
9432			= gfc_get_parentheses (ref->u.ar.start[n]);
9433	  }
9434    }
9435
9436  if (gfc_pure (NULL))
9437    {
9438      if (lhs->ts.type == BT_DERIVED
9439	    && lhs->expr_type == EXPR_VARIABLE
9440	    && lhs->ts.u.derived->attr.pointer_comp
9441	    && rhs->expr_type == EXPR_VARIABLE
9442	    && (gfc_impure_variable (rhs->symtree->n.sym)
9443		|| gfc_is_coindexed (rhs)))
9444	{
9445	  /* F2008, C1283.  */
9446	  if (gfc_is_coindexed (rhs))
9447	    gfc_error ("Coindexed expression at %L is assigned to "
9448			"a derived type variable with a POINTER "
9449			"component in a PURE procedure",
9450			&rhs->where);
9451	  else
9452	    gfc_error ("The impure variable at %L is assigned to "
9453			"a derived type variable with a POINTER "
9454			"component in a PURE procedure (12.6)",
9455			&rhs->where);
9456	  return rval;
9457	}
9458
9459      /* Fortran 2008, C1283.  */
9460      if (gfc_is_coindexed (lhs))
9461	{
9462	  gfc_error ("Assignment to coindexed variable at %L in a PURE "
9463		     "procedure", &rhs->where);
9464	  return rval;
9465	}
9466    }
9467
9468  if (gfc_implicit_pure (NULL))
9469    {
9470      if (lhs->expr_type == EXPR_VARIABLE
9471	    && lhs->symtree->n.sym != gfc_current_ns->proc_name
9472	    && lhs->symtree->n.sym->ns != gfc_current_ns)
9473	gfc_unset_implicit_pure (NULL);
9474
9475      if (lhs->ts.type == BT_DERIVED
9476	    && lhs->expr_type == EXPR_VARIABLE
9477	    && lhs->ts.u.derived->attr.pointer_comp
9478	    && rhs->expr_type == EXPR_VARIABLE
9479	    && (gfc_impure_variable (rhs->symtree->n.sym)
9480		|| gfc_is_coindexed (rhs)))
9481	gfc_unset_implicit_pure (NULL);
9482
9483      /* Fortran 2008, C1283.  */
9484      if (gfc_is_coindexed (lhs))
9485	gfc_unset_implicit_pure (NULL);
9486    }
9487
9488  /* F2008, 7.2.1.2.  */
9489  attr = gfc_expr_attr (lhs);
9490  if (lhs->ts.type == BT_CLASS && attr.allocatable)
9491    {
9492      if (attr.codimension)
9493	{
9494	  gfc_error ("Assignment to polymorphic coarray at %L is not "
9495		     "permitted", &lhs->where);
9496	  return false;
9497	}
9498      if (!gfc_notify_std (GFC_STD_F2008, "Assignment to an allocatable "
9499			   "polymorphic variable at %L", &lhs->where))
9500	return false;
9501      if (!flag_realloc_lhs)
9502	{
9503	  gfc_error ("Assignment to an allocatable polymorphic variable at %L "
9504		     "requires %<-frealloc-lhs%>", &lhs->where);
9505	  return false;
9506	}
9507      /* See PR 43366.  */
9508      gfc_error ("Assignment to an allocatable polymorphic variable at %L "
9509		 "is not yet supported", &lhs->where);
9510      return false;
9511    }
9512  else if (lhs->ts.type == BT_CLASS)
9513    {
9514      gfc_error ("Nonallocatable variable must not be polymorphic in intrinsic "
9515		 "assignment at %L - check that there is a matching specific "
9516		 "subroutine for '=' operator", &lhs->where);
9517      return false;
9518    }
9519
9520  bool lhs_coindexed = gfc_is_coindexed (lhs);
9521
9522  /* F2008, Section 7.2.1.2.  */
9523  if (lhs_coindexed && gfc_has_ultimate_allocatable (lhs))
9524    {
9525      gfc_error ("Coindexed variable must not have an allocatable ultimate "
9526		 "component in assignment at %L", &lhs->where);
9527      return false;
9528    }
9529
9530  gfc_check_assign (lhs, rhs, 1);
9531
9532  /* Assign the 'data' of a class object to a derived type.  */
9533  if (lhs->ts.type == BT_DERIVED
9534      && rhs->ts.type == BT_CLASS)
9535    gfc_add_data_component (rhs);
9536
9537  /* Insert a GFC_ISYM_CAF_SEND intrinsic, when the LHS is a coindexed variable.
9538     Additionally, insert this code when the RHS is a CAF as we then use the
9539     GFC_ISYM_CAF_SEND intrinsic just to avoid a temporary; but do not do so if
9540     the LHS is (re)allocatable or has a vector subscript.  If the LHS is a
9541     noncoindexed array and the RHS is a coindexed scalar, use the normal code
9542     path.  */
9543  if (flag_coarray == GFC_FCOARRAY_LIB
9544      && (lhs_coindexed
9545	  || (code->expr2->expr_type == EXPR_FUNCTION
9546	      && code->expr2->value.function.isym
9547	      && code->expr2->value.function.isym->id == GFC_ISYM_CAF_GET
9548	      && (code->expr1->rank == 0 || code->expr2->rank != 0)
9549	      && !gfc_expr_attr (rhs).allocatable
9550              && !gfc_has_vector_subscript (rhs))))
9551    {
9552      if (code->expr2->expr_type == EXPR_FUNCTION
9553	  && code->expr2->value.function.isym
9554	  && code->expr2->value.function.isym->id == GFC_ISYM_CAF_GET)
9555	remove_caf_get_intrinsic (code->expr2);
9556      code->op = EXEC_CALL;
9557      gfc_get_sym_tree (GFC_PREFIX ("caf_send"), ns, &code->symtree, true);
9558      code->resolved_sym = code->symtree->n.sym;
9559      code->resolved_sym->attr.flavor = FL_PROCEDURE;
9560      code->resolved_sym->attr.intrinsic = 1;
9561      code->resolved_sym->attr.subroutine = 1;
9562      code->resolved_isym = gfc_intrinsic_subroutine_by_id (GFC_ISYM_CAF_SEND);
9563      gfc_commit_symbol (code->resolved_sym);
9564      code->ext.actual = gfc_get_actual_arglist ();
9565      code->ext.actual->expr = lhs;
9566      code->ext.actual->next = gfc_get_actual_arglist ();
9567      code->ext.actual->next->expr = rhs;
9568      code->expr1 = NULL;
9569      code->expr2 = NULL;
9570    }
9571
9572  return false;
9573}
9574
9575
9576/* Add a component reference onto an expression.  */
9577
9578static void
9579add_comp_ref (gfc_expr *e, gfc_component *c)
9580{
9581  gfc_ref **ref;
9582  ref = &(e->ref);
9583  while (*ref)
9584    ref = &((*ref)->next);
9585  *ref = gfc_get_ref ();
9586  (*ref)->type = REF_COMPONENT;
9587  (*ref)->u.c.sym = e->ts.u.derived;
9588  (*ref)->u.c.component = c;
9589  e->ts = c->ts;
9590
9591  /* Add a full array ref, as necessary.  */
9592  if (c->as)
9593    {
9594      gfc_add_full_array_ref (e, c->as);
9595      e->rank = c->as->rank;
9596    }
9597}
9598
9599
9600/* Build an assignment.  Keep the argument 'op' for future use, so that
9601   pointer assignments can be made.  */
9602
9603static gfc_code *
9604build_assignment (gfc_exec_op op, gfc_expr *expr1, gfc_expr *expr2,
9605		  gfc_component *comp1, gfc_component *comp2, locus loc)
9606{
9607  gfc_code *this_code;
9608
9609  this_code = gfc_get_code (op);
9610  this_code->next = NULL;
9611  this_code->expr1 = gfc_copy_expr (expr1);
9612  this_code->expr2 = gfc_copy_expr (expr2);
9613  this_code->loc = loc;
9614  if (comp1 && comp2)
9615    {
9616      add_comp_ref (this_code->expr1, comp1);
9617      add_comp_ref (this_code->expr2, comp2);
9618    }
9619
9620  return this_code;
9621}
9622
9623
9624/* Makes a temporary variable expression based on the characteristics of
9625   a given variable expression.  */
9626
9627static gfc_expr*
9628get_temp_from_expr (gfc_expr *e, gfc_namespace *ns)
9629{
9630  static int serial = 0;
9631  char name[GFC_MAX_SYMBOL_LEN];
9632  gfc_symtree *tmp;
9633  gfc_array_spec *as;
9634  gfc_array_ref *aref;
9635  gfc_ref *ref;
9636
9637  sprintf (name, GFC_PREFIX("DA%d"), serial++);
9638  gfc_get_sym_tree (name, ns, &tmp, false);
9639  gfc_add_type (tmp->n.sym, &e->ts, NULL);
9640
9641  as = NULL;
9642  ref = NULL;
9643  aref = NULL;
9644
9645  /* This function could be expanded to support other expression type
9646     but this is not needed here.  */
9647  gcc_assert (e->expr_type == EXPR_VARIABLE);
9648
9649  /* Obtain the arrayspec for the temporary.  */
9650  if (e->rank)
9651    {
9652      aref = gfc_find_array_ref (e);
9653      if (e->expr_type == EXPR_VARIABLE
9654	  && e->symtree->n.sym->as == aref->as)
9655	as = aref->as;
9656      else
9657	{
9658	  for (ref = e->ref; ref; ref = ref->next)
9659	    if (ref->type == REF_COMPONENT
9660		&& ref->u.c.component->as == aref->as)
9661	      {
9662		as = aref->as;
9663		break;
9664	      }
9665	}
9666    }
9667
9668  /* Add the attributes and the arrayspec to the temporary.  */
9669  tmp->n.sym->attr = gfc_expr_attr (e);
9670  tmp->n.sym->attr.function = 0;
9671  tmp->n.sym->attr.result = 0;
9672  tmp->n.sym->attr.flavor = FL_VARIABLE;
9673
9674  if (as)
9675    {
9676      tmp->n.sym->as = gfc_copy_array_spec (as);
9677      if (!ref)
9678	ref = e->ref;
9679      if (as->type == AS_DEFERRED)
9680	tmp->n.sym->attr.allocatable = 1;
9681    }
9682  else
9683    tmp->n.sym->attr.dimension = 0;
9684
9685  gfc_set_sym_referenced (tmp->n.sym);
9686  gfc_commit_symbol (tmp->n.sym);
9687  e = gfc_lval_expr_from_sym (tmp->n.sym);
9688
9689  /* Should the lhs be a section, use its array ref for the
9690     temporary expression.  */
9691  if (aref && aref->type != AR_FULL)
9692    {
9693      gfc_free_ref_list (e->ref);
9694      e->ref = gfc_copy_ref (ref);
9695    }
9696  return e;
9697}
9698
9699
9700/* Add one line of code to the code chain, making sure that 'head' and
9701   'tail' are appropriately updated.  */
9702
9703static void
9704add_code_to_chain (gfc_code **this_code, gfc_code **head, gfc_code **tail)
9705{
9706  gcc_assert (this_code);
9707  if (*head == NULL)
9708    *head = *tail = *this_code;
9709  else
9710    *tail = gfc_append_code (*tail, *this_code);
9711  *this_code = NULL;
9712}
9713
9714
9715/* Counts the potential number of part array references that would
9716   result from resolution of typebound defined assignments.  */
9717
9718static int
9719nonscalar_typebound_assign (gfc_symbol *derived, int depth)
9720{
9721  gfc_component *c;
9722  int c_depth = 0, t_depth;
9723
9724  for (c= derived->components; c; c = c->next)
9725    {
9726      if ((c->ts.type != BT_DERIVED
9727	    || c->attr.pointer
9728	    || c->attr.allocatable
9729	    || c->attr.proc_pointer_comp
9730	    || c->attr.class_pointer
9731	    || c->attr.proc_pointer)
9732	  && !c->attr.defined_assign_comp)
9733	continue;
9734
9735      if (c->as && c_depth == 0)
9736	c_depth = 1;
9737
9738      if (c->ts.u.derived->attr.defined_assign_comp)
9739	t_depth = nonscalar_typebound_assign (c->ts.u.derived,
9740					      c->as ? 1 : 0);
9741      else
9742	t_depth = 0;
9743
9744      c_depth = t_depth > c_depth ? t_depth : c_depth;
9745    }
9746  return depth + c_depth;
9747}
9748
9749
9750/* Implement 7.2.1.3 of the F08 standard:
9751   "An intrinsic assignment where the variable is of derived type is
9752   performed as if each component of the variable were assigned from the
9753   corresponding component of expr using pointer assignment (7.2.2) for
9754   each pointer component, de���ned assignment for each nonpointer
9755   nonallocatable component of a type that has a type-bound de���ned
9756   assignment consistent with the component, intrinsic assignment for
9757   each other nonpointer nonallocatable component, ..."
9758
9759   The pointer assignments are taken care of by the intrinsic
9760   assignment of the structure itself.  This function recursively adds
9761   defined assignments where required.  The recursion is accomplished
9762   by calling gfc_resolve_code.
9763
9764   When the lhs in a defined assignment has intent INOUT, we need a
9765   temporary for the lhs.  In pseudo-code:
9766
9767   ! Only call function lhs once.
9768      if (lhs is not a constant or an variable)
9769	  temp_x = expr2
9770          expr2 => temp_x
9771   ! Do the intrinsic assignment
9772      expr1 = expr2
9773   ! Now do the defined assignments
9774      do over components with typebound defined assignment [%cmp]
9775	#if one component's assignment procedure is INOUT
9776	  t1 = expr1
9777	  #if expr2 non-variable
9778	    temp_x = expr2
9779	    expr2 => temp_x
9780	  # endif
9781	  expr1 = expr2
9782	  # for each cmp
9783	    t1%cmp {defined=} expr2%cmp
9784	    expr1%cmp = t1%cmp
9785	#else
9786	  expr1 = expr2
9787
9788	# for each cmp
9789	  expr1%cmp {defined=} expr2%cmp
9790	#endif
9791   */
9792
9793/* The temporary assignments have to be put on top of the additional
9794   code to avoid the result being changed by the intrinsic assignment.
9795   */
9796static int component_assignment_level = 0;
9797static gfc_code *tmp_head = NULL, *tmp_tail = NULL;
9798
9799static void
9800generate_component_assignments (gfc_code **code, gfc_namespace *ns)
9801{
9802  gfc_component *comp1, *comp2;
9803  gfc_code *this_code = NULL, *head = NULL, *tail = NULL;
9804  gfc_expr *t1;
9805  int error_count, depth;
9806
9807  gfc_get_errors (NULL, &error_count);
9808
9809  /* Filter out continuing processing after an error.  */
9810  if (error_count
9811      || (*code)->expr1->ts.type != BT_DERIVED
9812      || (*code)->expr2->ts.type != BT_DERIVED)
9813    return;
9814
9815  /* TODO: Handle more than one part array reference in assignments.  */
9816  depth = nonscalar_typebound_assign ((*code)->expr1->ts.u.derived,
9817				      (*code)->expr1->rank ? 1 : 0);
9818  if (depth > 1)
9819    {
9820      gfc_warning (0, "TODO: type-bound defined assignment(s) at %L not "
9821		   "done because multiple part array references would "
9822		   "occur in intermediate expressions.", &(*code)->loc);
9823      return;
9824    }
9825
9826  component_assignment_level++;
9827
9828  /* Create a temporary so that functions get called only once.  */
9829  if ((*code)->expr2->expr_type != EXPR_VARIABLE
9830      && (*code)->expr2->expr_type != EXPR_CONSTANT)
9831    {
9832      gfc_expr *tmp_expr;
9833
9834      /* Assign the rhs to the temporary.  */
9835      tmp_expr = get_temp_from_expr ((*code)->expr1, ns);
9836      this_code = build_assignment (EXEC_ASSIGN,
9837				    tmp_expr, (*code)->expr2,
9838				    NULL, NULL, (*code)->loc);
9839      /* Add the code and substitute the rhs expression.  */
9840      add_code_to_chain (&this_code, &tmp_head, &tmp_tail);
9841      gfc_free_expr ((*code)->expr2);
9842      (*code)->expr2 = tmp_expr;
9843    }
9844
9845  /* Do the intrinsic assignment.  This is not needed if the lhs is one
9846     of the temporaries generated here, since the intrinsic assignment
9847     to the final result already does this.  */
9848  if ((*code)->expr1->symtree->n.sym->name[2] != '@')
9849    {
9850      this_code = build_assignment (EXEC_ASSIGN,
9851				    (*code)->expr1, (*code)->expr2,
9852				    NULL, NULL, (*code)->loc);
9853      add_code_to_chain (&this_code, &head, &tail);
9854    }
9855
9856  comp1 = (*code)->expr1->ts.u.derived->components;
9857  comp2 = (*code)->expr2->ts.u.derived->components;
9858
9859  t1 = NULL;
9860  for (; comp1; comp1 = comp1->next, comp2 = comp2->next)
9861    {
9862      bool inout = false;
9863
9864      /* The intrinsic assignment does the right thing for pointers
9865	 of all kinds and allocatable components.  */
9866      if (comp1->ts.type != BT_DERIVED
9867	  || comp1->attr.pointer
9868	  || comp1->attr.allocatable
9869	  || comp1->attr.proc_pointer_comp
9870	  || comp1->attr.class_pointer
9871	  || comp1->attr.proc_pointer)
9872	continue;
9873
9874      /* Make an assigment for this component.  */
9875      this_code = build_assignment (EXEC_ASSIGN,
9876				    (*code)->expr1, (*code)->expr2,
9877				    comp1, comp2, (*code)->loc);
9878
9879      /* Convert the assignment if there is a defined assignment for
9880	 this type.  Otherwise, using the call from gfc_resolve_code,
9881	 recurse into its components.  */
9882      gfc_resolve_code (this_code, ns);
9883
9884      if (this_code->op == EXEC_ASSIGN_CALL)
9885	{
9886	  gfc_formal_arglist *dummy_args;
9887	  gfc_symbol *rsym;
9888	  /* Check that there is a typebound defined assignment.  If not,
9889	     then this must be a module defined assignment.  We cannot
9890	     use the defined_assign_comp attribute here because it must
9891	     be this derived type that has the defined assignment and not
9892	     a parent type.  */
9893	  if (!(comp1->ts.u.derived->f2k_derived
9894		&& comp1->ts.u.derived->f2k_derived
9895					->tb_op[INTRINSIC_ASSIGN]))
9896	    {
9897	      gfc_free_statements (this_code);
9898	      this_code = NULL;
9899	      continue;
9900	    }
9901
9902	  /* If the first argument of the subroutine has intent INOUT
9903	     a temporary must be generated and used instead.  */
9904	  rsym = this_code->resolved_sym;
9905	  dummy_args = gfc_sym_get_dummy_args (rsym);
9906	  if (dummy_args
9907	      && dummy_args->sym->attr.intent == INTENT_INOUT)
9908	    {
9909	      gfc_code *temp_code;
9910	      inout = true;
9911
9912	      /* Build the temporary required for the assignment and put
9913		 it at the head of the generated code.  */
9914	      if (!t1)
9915		{
9916		  t1 = get_temp_from_expr ((*code)->expr1, ns);
9917		  temp_code = build_assignment (EXEC_ASSIGN,
9918						t1, (*code)->expr1,
9919				NULL, NULL, (*code)->loc);
9920
9921		  /* For allocatable LHS, check whether it is allocated.  Note
9922		     that allocatable components with defined assignment are
9923		     not yet support.  See PR 57696.  */
9924		  if ((*code)->expr1->symtree->n.sym->attr.allocatable)
9925		    {
9926		      gfc_code *block;
9927		      gfc_expr *e =
9928			gfc_lval_expr_from_sym ((*code)->expr1->symtree->n.sym);
9929		      block = gfc_get_code (EXEC_IF);
9930		      block->block = gfc_get_code (EXEC_IF);
9931		      block->block->expr1
9932			  = gfc_build_intrinsic_call (ns,
9933				    GFC_ISYM_ALLOCATED, "allocated",
9934				    (*code)->loc, 1, e);
9935		      block->block->next = temp_code;
9936		      temp_code = block;
9937		    }
9938		  add_code_to_chain (&temp_code, &tmp_head, &tmp_tail);
9939		}
9940
9941	      /* Replace the first actual arg with the component of the
9942		 temporary.  */
9943	      gfc_free_expr (this_code->ext.actual->expr);
9944	      this_code->ext.actual->expr = gfc_copy_expr (t1);
9945	      add_comp_ref (this_code->ext.actual->expr, comp1);
9946
9947	      /* If the LHS variable is allocatable and wasn't allocated and
9948                 the temporary is allocatable, pointer assign the address of
9949                 the freshly allocated LHS to the temporary.  */
9950	      if ((*code)->expr1->symtree->n.sym->attr.allocatable
9951		  && gfc_expr_attr ((*code)->expr1).allocatable)
9952		{
9953		  gfc_code *block;
9954		  gfc_expr *cond;
9955
9956		  cond = gfc_get_expr ();
9957		  cond->ts.type = BT_LOGICAL;
9958		  cond->ts.kind = gfc_default_logical_kind;
9959		  cond->expr_type = EXPR_OP;
9960		  cond->where = (*code)->loc;
9961		  cond->value.op.op = INTRINSIC_NOT;
9962		  cond->value.op.op1 = gfc_build_intrinsic_call (ns,
9963					  GFC_ISYM_ALLOCATED, "allocated",
9964					  (*code)->loc, 1, gfc_copy_expr (t1));
9965		  block = gfc_get_code (EXEC_IF);
9966		  block->block = gfc_get_code (EXEC_IF);
9967		  block->block->expr1 = cond;
9968		  block->block->next = build_assignment (EXEC_POINTER_ASSIGN,
9969					t1, (*code)->expr1,
9970					NULL, NULL, (*code)->loc);
9971		  add_code_to_chain (&block, &head, &tail);
9972		}
9973	    }
9974	}
9975      else if (this_code->op == EXEC_ASSIGN && !this_code->next)
9976	{
9977	  /* Don't add intrinsic assignments since they are already
9978	     effected by the intrinsic assignment of the structure.  */
9979	  gfc_free_statements (this_code);
9980	  this_code = NULL;
9981	  continue;
9982	}
9983
9984      add_code_to_chain (&this_code, &head, &tail);
9985
9986      if (t1 && inout)
9987	{
9988	  /* Transfer the value to the final result.  */
9989	  this_code = build_assignment (EXEC_ASSIGN,
9990					(*code)->expr1, t1,
9991					comp1, comp2, (*code)->loc);
9992	  add_code_to_chain (&this_code, &head, &tail);
9993	}
9994    }
9995
9996  /* Put the temporary assignments at the top of the generated code.  */
9997  if (tmp_head && component_assignment_level == 1)
9998    {
9999      gfc_append_code (tmp_head, head);
10000      head = tmp_head;
10001      tmp_head = tmp_tail = NULL;
10002    }
10003
10004  // If we did a pointer assignment - thus, we need to ensure that the LHS is
10005  // not accidentally deallocated. Hence, nullify t1.
10006  if (t1 && (*code)->expr1->symtree->n.sym->attr.allocatable
10007      && gfc_expr_attr ((*code)->expr1).allocatable)
10008    {
10009      gfc_code *block;
10010      gfc_expr *cond;
10011      gfc_expr *e;
10012
10013      e = gfc_lval_expr_from_sym ((*code)->expr1->symtree->n.sym);
10014      cond = gfc_build_intrinsic_call (ns, GFC_ISYM_ASSOCIATED, "associated",
10015				       (*code)->loc, 2, gfc_copy_expr (t1), e);
10016      block = gfc_get_code (EXEC_IF);
10017      block->block = gfc_get_code (EXEC_IF);
10018      block->block->expr1 = cond;
10019      block->block->next = build_assignment (EXEC_POINTER_ASSIGN,
10020					t1, gfc_get_null_expr (&(*code)->loc),
10021					NULL, NULL, (*code)->loc);
10022      gfc_append_code (tail, block);
10023      tail = block;
10024    }
10025
10026  /* Now attach the remaining code chain to the input code.  Step on
10027     to the end of the new code since resolution is complete.  */
10028  gcc_assert ((*code)->op == EXEC_ASSIGN);
10029  tail->next = (*code)->next;
10030  /* Overwrite 'code' because this would place the intrinsic assignment
10031     before the temporary for the lhs is created.  */
10032  gfc_free_expr ((*code)->expr1);
10033  gfc_free_expr ((*code)->expr2);
10034  **code = *head;
10035  if (head != tail)
10036    free (head);
10037  *code = tail;
10038
10039  component_assignment_level--;
10040}
10041
10042
10043/* Deferred character length assignments from an operator expression
10044   require a temporary because the character length of the lhs can
10045   change in the course of the assignment.  */
10046
10047static bool
10048deferred_op_assign (gfc_code **code, gfc_namespace *ns)
10049{
10050  gfc_expr *tmp_expr;
10051  gfc_code *this_code;
10052
10053  if (!((*code)->expr1->ts.type == BT_CHARACTER
10054	 && (*code)->expr1->ts.deferred && (*code)->expr1->rank
10055	 && (*code)->expr2->expr_type == EXPR_OP))
10056    return false;
10057
10058  if (!gfc_check_dependency ((*code)->expr1, (*code)->expr2, 1))
10059    return false;
10060
10061  tmp_expr = get_temp_from_expr ((*code)->expr1, ns);
10062  tmp_expr->where = (*code)->loc;
10063
10064  /* A new charlen is required to ensure that the variable string
10065     length is different to that of the original lhs.  */
10066  tmp_expr->ts.u.cl = gfc_get_charlen();
10067  tmp_expr->symtree->n.sym->ts.u.cl = tmp_expr->ts.u.cl;
10068  tmp_expr->ts.u.cl->next = (*code)->expr2->ts.u.cl->next;
10069  (*code)->expr2->ts.u.cl->next = tmp_expr->ts.u.cl;
10070
10071  tmp_expr->symtree->n.sym->ts.deferred = 1;
10072
10073  this_code = build_assignment (EXEC_ASSIGN,
10074				(*code)->expr1,
10075				gfc_copy_expr (tmp_expr),
10076				NULL, NULL, (*code)->loc);
10077
10078  (*code)->expr1 = tmp_expr;
10079
10080  this_code->next = (*code)->next;
10081  (*code)->next = this_code;
10082
10083  return true;
10084}
10085
10086
10087/* Given a block of code, recursively resolve everything pointed to by this
10088   code block.  */
10089
10090void
10091gfc_resolve_code (gfc_code *code, gfc_namespace *ns)
10092{
10093  int omp_workshare_save;
10094  int forall_save, do_concurrent_save;
10095  code_stack frame;
10096  bool t;
10097
10098  frame.prev = cs_base;
10099  frame.head = code;
10100  cs_base = &frame;
10101
10102  find_reachable_labels (code);
10103
10104  for (; code; code = code->next)
10105    {
10106      frame.current = code;
10107      forall_save = forall_flag;
10108      do_concurrent_save = gfc_do_concurrent_flag;
10109
10110      if (code->op == EXEC_FORALL)
10111	{
10112	  forall_flag = 1;
10113	  gfc_resolve_forall (code, ns, forall_save);
10114	  forall_flag = 2;
10115	}
10116      else if (code->block)
10117	{
10118	  omp_workshare_save = -1;
10119	  switch (code->op)
10120	    {
10121	    case EXEC_OACC_PARALLEL_LOOP:
10122	    case EXEC_OACC_PARALLEL:
10123	    case EXEC_OACC_KERNELS_LOOP:
10124	    case EXEC_OACC_KERNELS:
10125	    case EXEC_OACC_DATA:
10126	    case EXEC_OACC_HOST_DATA:
10127	    case EXEC_OACC_LOOP:
10128	      gfc_resolve_oacc_blocks (code, ns);
10129	      break;
10130	    case EXEC_OMP_PARALLEL_WORKSHARE:
10131	      omp_workshare_save = omp_workshare_flag;
10132	      omp_workshare_flag = 1;
10133	      gfc_resolve_omp_parallel_blocks (code, ns);
10134	      break;
10135	    case EXEC_OMP_PARALLEL:
10136	    case EXEC_OMP_PARALLEL_DO:
10137	    case EXEC_OMP_PARALLEL_DO_SIMD:
10138	    case EXEC_OMP_PARALLEL_SECTIONS:
10139	    case EXEC_OMP_TARGET_TEAMS:
10140	    case EXEC_OMP_TARGET_TEAMS_DISTRIBUTE:
10141	    case EXEC_OMP_TARGET_TEAMS_DISTRIBUTE_PARALLEL_DO:
10142	    case EXEC_OMP_TARGET_TEAMS_DISTRIBUTE_PARALLEL_DO_SIMD:
10143	    case EXEC_OMP_TARGET_TEAMS_DISTRIBUTE_SIMD:
10144	    case EXEC_OMP_TASK:
10145	    case EXEC_OMP_TEAMS:
10146	    case EXEC_OMP_TEAMS_DISTRIBUTE:
10147	    case EXEC_OMP_TEAMS_DISTRIBUTE_PARALLEL_DO:
10148	    case EXEC_OMP_TEAMS_DISTRIBUTE_PARALLEL_DO_SIMD:
10149	    case EXEC_OMP_TEAMS_DISTRIBUTE_SIMD:
10150	      omp_workshare_save = omp_workshare_flag;
10151	      omp_workshare_flag = 0;
10152	      gfc_resolve_omp_parallel_blocks (code, ns);
10153	      break;
10154	    case EXEC_OMP_DISTRIBUTE:
10155	    case EXEC_OMP_DISTRIBUTE_SIMD:
10156	    case EXEC_OMP_DO:
10157	    case EXEC_OMP_DO_SIMD:
10158	    case EXEC_OMP_SIMD:
10159	      gfc_resolve_omp_do_blocks (code, ns);
10160	      break;
10161	    case EXEC_SELECT_TYPE:
10162	      /* Blocks are handled in resolve_select_type because we have
10163		 to transform the SELECT TYPE into ASSOCIATE first.  */
10164	      break;
10165            case EXEC_DO_CONCURRENT:
10166	      gfc_do_concurrent_flag = 1;
10167	      gfc_resolve_blocks (code->block, ns);
10168	      gfc_do_concurrent_flag = 2;
10169	      break;
10170	    case EXEC_OMP_WORKSHARE:
10171	      omp_workshare_save = omp_workshare_flag;
10172	      omp_workshare_flag = 1;
10173	      /* FALL THROUGH */
10174	    default:
10175	      gfc_resolve_blocks (code->block, ns);
10176	      break;
10177	    }
10178
10179	  if (omp_workshare_save != -1)
10180	    omp_workshare_flag = omp_workshare_save;
10181	}
10182
10183      t = true;
10184      if (code->op != EXEC_COMPCALL && code->op != EXEC_CALL_PPC)
10185	t = gfc_resolve_expr (code->expr1);
10186      forall_flag = forall_save;
10187      gfc_do_concurrent_flag = do_concurrent_save;
10188
10189      if (!gfc_resolve_expr (code->expr2))
10190	t = false;
10191
10192      if (code->op == EXEC_ALLOCATE
10193	  && !gfc_resolve_expr (code->expr3))
10194	t = false;
10195
10196      switch (code->op)
10197	{
10198	case EXEC_NOP:
10199	case EXEC_END_BLOCK:
10200	case EXEC_END_NESTED_BLOCK:
10201	case EXEC_CYCLE:
10202	case EXEC_PAUSE:
10203	case EXEC_STOP:
10204	case EXEC_ERROR_STOP:
10205	case EXEC_EXIT:
10206	case EXEC_CONTINUE:
10207	case EXEC_DT_END:
10208	case EXEC_ASSIGN_CALL:
10209	  break;
10210
10211	case EXEC_CRITICAL:
10212	  resolve_critical (code);
10213	  break;
10214
10215	case EXEC_SYNC_ALL:
10216	case EXEC_SYNC_IMAGES:
10217	case EXEC_SYNC_MEMORY:
10218	  resolve_sync (code);
10219	  break;
10220
10221	case EXEC_LOCK:
10222	case EXEC_UNLOCK:
10223	case EXEC_EVENT_POST:
10224	case EXEC_EVENT_WAIT:
10225	  resolve_lock_unlock_event (code);
10226	  break;
10227
10228	case EXEC_ENTRY:
10229	  /* Keep track of which entry we are up to.  */
10230	  current_entry_id = code->ext.entry->id;
10231	  break;
10232
10233	case EXEC_WHERE:
10234	  resolve_where (code, NULL);
10235	  break;
10236
10237	case EXEC_GOTO:
10238	  if (code->expr1 != NULL)
10239	    {
10240	      if (code->expr1->ts.type != BT_INTEGER)
10241		gfc_error ("ASSIGNED GOTO statement at %L requires an "
10242			   "INTEGER variable", &code->expr1->where);
10243	      else if (code->expr1->symtree->n.sym->attr.assign != 1)
10244		gfc_error ("Variable %qs has not been assigned a target "
10245			   "label at %L", code->expr1->symtree->n.sym->name,
10246			   &code->expr1->where);
10247	    }
10248	  else
10249	    resolve_branch (code->label1, code);
10250	  break;
10251
10252	case EXEC_RETURN:
10253	  if (code->expr1 != NULL
10254		&& (code->expr1->ts.type != BT_INTEGER || code->expr1->rank))
10255	    gfc_error ("Alternate RETURN statement at %L requires a SCALAR-"
10256		       "INTEGER return specifier", &code->expr1->where);
10257	  break;
10258
10259	case EXEC_INIT_ASSIGN:
10260	case EXEC_END_PROCEDURE:
10261	  break;
10262
10263	case EXEC_ASSIGN:
10264	  if (!t)
10265	    break;
10266
10267	  /* Remove a GFC_ISYM_CAF_GET inserted for a coindexed variable on
10268	     the LHS.  */
10269	  if (code->expr1->expr_type == EXPR_FUNCTION
10270	      && code->expr1->value.function.isym
10271	      && code->expr1->value.function.isym->id == GFC_ISYM_CAF_GET)
10272	    remove_caf_get_intrinsic (code->expr1);
10273
10274	  if (!gfc_check_vardef_context (code->expr1, false, false, false,
10275					 _("assignment")))
10276	    break;
10277
10278	  if (resolve_ordinary_assign (code, ns))
10279	    {
10280	      if (code->op == EXEC_COMPCALL)
10281		goto compcall;
10282	      else
10283		goto call;
10284	    }
10285
10286	  /* Check for dependencies in deferred character length array
10287	     assignments and generate a temporary, if necessary.  */
10288	  if (code->op == EXEC_ASSIGN && deferred_op_assign (&code, ns))
10289	    break;
10290
10291	  /* F03 7.4.1.3 for non-allocatable, non-pointer components.  */
10292	  if (code->op != EXEC_CALL && code->expr1->ts.type == BT_DERIVED
10293	      && code->expr1->ts.u.derived->attr.defined_assign_comp)
10294	    generate_component_assignments (&code, ns);
10295
10296	  break;
10297
10298	case EXEC_LABEL_ASSIGN:
10299	  if (code->label1->defined == ST_LABEL_UNKNOWN)
10300	    gfc_error ("Label %d referenced at %L is never defined",
10301		       code->label1->value, &code->label1->where);
10302	  if (t
10303	      && (code->expr1->expr_type != EXPR_VARIABLE
10304		  || code->expr1->symtree->n.sym->ts.type != BT_INTEGER
10305		  || code->expr1->symtree->n.sym->ts.kind
10306		     != gfc_default_integer_kind
10307		  || code->expr1->symtree->n.sym->as != NULL))
10308	    gfc_error ("ASSIGN statement at %L requires a scalar "
10309		       "default INTEGER variable", &code->expr1->where);
10310	  break;
10311
10312	case EXEC_POINTER_ASSIGN:
10313	  {
10314	    gfc_expr* e;
10315
10316	    if (!t)
10317	      break;
10318
10319	    /* This is both a variable definition and pointer assignment
10320	       context, so check both of them.  For rank remapping, a final
10321	       array ref may be present on the LHS and fool gfc_expr_attr
10322	       used in gfc_check_vardef_context.  Remove it.  */
10323	    e = remove_last_array_ref (code->expr1);
10324	    t = gfc_check_vardef_context (e, true, false, false,
10325					  _("pointer assignment"));
10326	    if (t)
10327	      t = gfc_check_vardef_context (e, false, false, false,
10328					    _("pointer assignment"));
10329	    gfc_free_expr (e);
10330	    if (!t)
10331	      break;
10332
10333	    gfc_check_pointer_assign (code->expr1, code->expr2);
10334	    break;
10335	  }
10336
10337	case EXEC_ARITHMETIC_IF:
10338	  {
10339	    gfc_expr *e = code->expr1;
10340
10341	    gfc_resolve_expr (e);
10342	    if (e->expr_type == EXPR_NULL)
10343	      gfc_error ("Invalid NULL at %L", &e->where);
10344
10345	    if (t && (e->rank > 0
10346		      || !(e->ts.type == BT_REAL || e->ts.type == BT_INTEGER)))
10347	      gfc_error ("Arithmetic IF statement at %L requires a scalar "
10348			 "REAL or INTEGER expression", &e->where);
10349
10350	    resolve_branch (code->label1, code);
10351	    resolve_branch (code->label2, code);
10352	    resolve_branch (code->label3, code);
10353	  }
10354	  break;
10355
10356	case EXEC_IF:
10357	  if (t && code->expr1 != NULL
10358	      && (code->expr1->ts.type != BT_LOGICAL
10359		  || code->expr1->rank != 0))
10360	    gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
10361		       &code->expr1->where);
10362	  break;
10363
10364	case EXEC_CALL:
10365	call:
10366	  resolve_call (code);
10367	  break;
10368
10369	case EXEC_COMPCALL:
10370	compcall:
10371	  resolve_typebound_subroutine (code);
10372	  break;
10373
10374	case EXEC_CALL_PPC:
10375	  resolve_ppc_call (code);
10376	  break;
10377
10378	case EXEC_SELECT:
10379	  /* Select is complicated. Also, a SELECT construct could be
10380	     a transformed computed GOTO.  */
10381	  resolve_select (code, false);
10382	  break;
10383
10384	case EXEC_SELECT_TYPE:
10385	  resolve_select_type (code, ns);
10386	  break;
10387
10388	case EXEC_BLOCK:
10389	  resolve_block_construct (code);
10390	  break;
10391
10392	case EXEC_DO:
10393	  if (code->ext.iterator != NULL)
10394	    {
10395	      gfc_iterator *iter = code->ext.iterator;
10396	      if (gfc_resolve_iterator (iter, true, false))
10397		gfc_resolve_do_iterator (code, iter->var->symtree->n.sym);
10398	    }
10399	  break;
10400
10401	case EXEC_DO_WHILE:
10402	  if (code->expr1 == NULL)
10403	    gfc_internal_error ("gfc_resolve_code(): No expression on "
10404				"DO WHILE");
10405	  if (t
10406	      && (code->expr1->rank != 0
10407		  || code->expr1->ts.type != BT_LOGICAL))
10408	    gfc_error ("Exit condition of DO WHILE loop at %L must be "
10409		       "a scalar LOGICAL expression", &code->expr1->where);
10410	  break;
10411
10412	case EXEC_ALLOCATE:
10413	  if (t)
10414	    resolve_allocate_deallocate (code, "ALLOCATE");
10415
10416	  break;
10417
10418	case EXEC_DEALLOCATE:
10419	  if (t)
10420	    resolve_allocate_deallocate (code, "DEALLOCATE");
10421
10422	  break;
10423
10424	case EXEC_OPEN:
10425	  if (!gfc_resolve_open (code->ext.open))
10426	    break;
10427
10428	  resolve_branch (code->ext.open->err, code);
10429	  break;
10430
10431	case EXEC_CLOSE:
10432	  if (!gfc_resolve_close (code->ext.close))
10433	    break;
10434
10435	  resolve_branch (code->ext.close->err, code);
10436	  break;
10437
10438	case EXEC_BACKSPACE:
10439	case EXEC_ENDFILE:
10440	case EXEC_REWIND:
10441	case EXEC_FLUSH:
10442	  if (!gfc_resolve_filepos (code->ext.filepos))
10443	    break;
10444
10445	  resolve_branch (code->ext.filepos->err, code);
10446	  break;
10447
10448	case EXEC_INQUIRE:
10449	  if (!gfc_resolve_inquire (code->ext.inquire))
10450	      break;
10451
10452	  resolve_branch (code->ext.inquire->err, code);
10453	  break;
10454
10455	case EXEC_IOLENGTH:
10456	  gcc_assert (code->ext.inquire != NULL);
10457	  if (!gfc_resolve_inquire (code->ext.inquire))
10458	    break;
10459
10460	  resolve_branch (code->ext.inquire->err, code);
10461	  break;
10462
10463	case EXEC_WAIT:
10464	  if (!gfc_resolve_wait (code->ext.wait))
10465	    break;
10466
10467	  resolve_branch (code->ext.wait->err, code);
10468	  resolve_branch (code->ext.wait->end, code);
10469	  resolve_branch (code->ext.wait->eor, code);
10470	  break;
10471
10472	case EXEC_READ:
10473	case EXEC_WRITE:
10474	  if (!gfc_resolve_dt (code->ext.dt, &code->loc))
10475	    break;
10476
10477	  resolve_branch (code->ext.dt->err, code);
10478	  resolve_branch (code->ext.dt->end, code);
10479	  resolve_branch (code->ext.dt->eor, code);
10480	  break;
10481
10482	case EXEC_TRANSFER:
10483	  resolve_transfer (code);
10484	  break;
10485
10486	case EXEC_DO_CONCURRENT:
10487	case EXEC_FORALL:
10488	  resolve_forall_iterators (code->ext.forall_iterator);
10489
10490	  if (code->expr1 != NULL
10491	      && (code->expr1->ts.type != BT_LOGICAL || code->expr1->rank))
10492	    gfc_error ("FORALL mask clause at %L requires a scalar LOGICAL "
10493		       "expression", &code->expr1->where);
10494	  break;
10495
10496	case EXEC_OACC_PARALLEL_LOOP:
10497	case EXEC_OACC_PARALLEL:
10498	case EXEC_OACC_KERNELS_LOOP:
10499	case EXEC_OACC_KERNELS:
10500	case EXEC_OACC_DATA:
10501	case EXEC_OACC_HOST_DATA:
10502	case EXEC_OACC_LOOP:
10503	case EXEC_OACC_UPDATE:
10504	case EXEC_OACC_WAIT:
10505	case EXEC_OACC_CACHE:
10506	case EXEC_OACC_ENTER_DATA:
10507	case EXEC_OACC_EXIT_DATA:
10508	  gfc_resolve_oacc_directive (code, ns);
10509	  break;
10510
10511	case EXEC_OMP_ATOMIC:
10512	case EXEC_OMP_BARRIER:
10513	case EXEC_OMP_CANCEL:
10514	case EXEC_OMP_CANCELLATION_POINT:
10515	case EXEC_OMP_CRITICAL:
10516	case EXEC_OMP_FLUSH:
10517	case EXEC_OMP_DISTRIBUTE:
10518	case EXEC_OMP_DISTRIBUTE_PARALLEL_DO:
10519	case EXEC_OMP_DISTRIBUTE_PARALLEL_DO_SIMD:
10520	case EXEC_OMP_DISTRIBUTE_SIMD:
10521	case EXEC_OMP_DO:
10522	case EXEC_OMP_DO_SIMD:
10523	case EXEC_OMP_MASTER:
10524	case EXEC_OMP_ORDERED:
10525	case EXEC_OMP_SECTIONS:
10526	case EXEC_OMP_SIMD:
10527	case EXEC_OMP_SINGLE:
10528	case EXEC_OMP_TARGET:
10529	case EXEC_OMP_TARGET_DATA:
10530	case EXEC_OMP_TARGET_TEAMS:
10531	case EXEC_OMP_TARGET_TEAMS_DISTRIBUTE:
10532	case EXEC_OMP_TARGET_TEAMS_DISTRIBUTE_PARALLEL_DO:
10533	case EXEC_OMP_TARGET_TEAMS_DISTRIBUTE_PARALLEL_DO_SIMD:
10534	case EXEC_OMP_TARGET_TEAMS_DISTRIBUTE_SIMD:
10535	case EXEC_OMP_TARGET_UPDATE:
10536	case EXEC_OMP_TASK:
10537	case EXEC_OMP_TASKGROUP:
10538	case EXEC_OMP_TASKWAIT:
10539	case EXEC_OMP_TASKYIELD:
10540	case EXEC_OMP_TEAMS:
10541	case EXEC_OMP_TEAMS_DISTRIBUTE:
10542	case EXEC_OMP_TEAMS_DISTRIBUTE_PARALLEL_DO:
10543	case EXEC_OMP_TEAMS_DISTRIBUTE_PARALLEL_DO_SIMD:
10544	case EXEC_OMP_TEAMS_DISTRIBUTE_SIMD:
10545	case EXEC_OMP_WORKSHARE:
10546	  gfc_resolve_omp_directive (code, ns);
10547	  break;
10548
10549	case EXEC_OMP_PARALLEL:
10550	case EXEC_OMP_PARALLEL_DO:
10551	case EXEC_OMP_PARALLEL_DO_SIMD:
10552	case EXEC_OMP_PARALLEL_SECTIONS:
10553	case EXEC_OMP_PARALLEL_WORKSHARE:
10554	  omp_workshare_save = omp_workshare_flag;
10555	  omp_workshare_flag = 0;
10556	  gfc_resolve_omp_directive (code, ns);
10557	  omp_workshare_flag = omp_workshare_save;
10558	  break;
10559
10560	default:
10561	  gfc_internal_error ("gfc_resolve_code(): Bad statement code");
10562	}
10563    }
10564
10565  cs_base = frame.prev;
10566}
10567
10568
10569/* Resolve initial values and make sure they are compatible with
10570   the variable.  */
10571
10572static void
10573resolve_values (gfc_symbol *sym)
10574{
10575  bool t;
10576
10577  if (sym->value == NULL)
10578    return;
10579
10580  if (sym->value->expr_type == EXPR_STRUCTURE)
10581    t= resolve_structure_cons (sym->value, 1);
10582  else
10583    t = gfc_resolve_expr (sym->value);
10584
10585  if (!t)
10586    return;
10587
10588  gfc_check_assign_symbol (sym, NULL, sym->value);
10589}
10590
10591
10592/* Verify any BIND(C) derived types in the namespace so we can report errors
10593   for them once, rather than for each variable declared of that type.  */
10594
10595static void
10596resolve_bind_c_derived_types (gfc_symbol *derived_sym)
10597{
10598  if (derived_sym != NULL && derived_sym->attr.flavor == FL_DERIVED
10599      && derived_sym->attr.is_bind_c == 1)
10600    verify_bind_c_derived_type (derived_sym);
10601
10602  return;
10603}
10604
10605
10606/* Verify that any binding labels used in a given namespace do not collide
10607   with the names or binding labels of any global symbols.  Multiple INTERFACE
10608   for the same procedure are permitted.  */
10609
10610static void
10611gfc_verify_binding_labels (gfc_symbol *sym)
10612{
10613  gfc_gsymbol *gsym;
10614  const char *module;
10615
10616  if (!sym || !sym->attr.is_bind_c || sym->attr.is_iso_c
10617      || sym->attr.flavor == FL_DERIVED || !sym->binding_label)
10618    return;
10619
10620  gsym = gfc_find_gsymbol (gfc_gsym_root, sym->binding_label);
10621
10622  if (sym->module)
10623    module = sym->module;
10624  else if (sym->ns && sym->ns->proc_name
10625	   && sym->ns->proc_name->attr.flavor == FL_MODULE)
10626    module = sym->ns->proc_name->name;
10627  else if (sym->ns && sym->ns->parent
10628	   && sym->ns && sym->ns->parent->proc_name
10629	   && sym->ns->parent->proc_name->attr.flavor == FL_MODULE)
10630    module = sym->ns->parent->proc_name->name;
10631  else
10632    module = NULL;
10633
10634  if (!gsym
10635      || (!gsym->defined
10636	  && (gsym->type == GSYM_FUNCTION || gsym->type == GSYM_SUBROUTINE)))
10637    {
10638      if (!gsym)
10639	gsym = gfc_get_gsymbol (sym->binding_label);
10640      gsym->where = sym->declared_at;
10641      gsym->sym_name = sym->name;
10642      gsym->binding_label = sym->binding_label;
10643      gsym->ns = sym->ns;
10644      gsym->mod_name = module;
10645      if (sym->attr.function)
10646        gsym->type = GSYM_FUNCTION;
10647      else if (sym->attr.subroutine)
10648	gsym->type = GSYM_SUBROUTINE;
10649      /* Mark as variable/procedure as defined, unless its an INTERFACE.  */
10650      gsym->defined = sym->attr.if_source != IFSRC_IFBODY;
10651      return;
10652    }
10653
10654  if (sym->attr.flavor == FL_VARIABLE && gsym->type != GSYM_UNKNOWN)
10655    {
10656      gfc_error_1 ("Variable %s with binding label %s at %L uses the same global "
10657		 "identifier as entity at %L", sym->name,
10658		 sym->binding_label, &sym->declared_at, &gsym->where);
10659      /* Clear the binding label to prevent checking multiple times.  */
10660      sym->binding_label = NULL;
10661
10662    }
10663  else if (sym->attr.flavor == FL_VARIABLE && module
10664	   && (strcmp (module, gsym->mod_name) != 0
10665	       || strcmp (sym->name, gsym->sym_name) != 0))
10666    {
10667      /* This can only happen if the variable is defined in a module - if it
10668	 isn't the same module, reject it.  */
10669      gfc_error_1 ("Variable %s from module %s with binding label %s at %L uses "
10670		   "the same global identifier as entity at %L from module %s",
10671		 sym->name, module, sym->binding_label,
10672		 &sym->declared_at, &gsym->where, gsym->mod_name);
10673      sym->binding_label = NULL;
10674    }
10675  else if ((sym->attr.function || sym->attr.subroutine)
10676	   && ((gsym->type != GSYM_SUBROUTINE && gsym->type != GSYM_FUNCTION)
10677	       || (gsym->defined && sym->attr.if_source != IFSRC_IFBODY))
10678	   && sym != gsym->ns->proc_name
10679	   && (module != gsym->mod_name
10680	       || strcmp (gsym->sym_name, sym->name) != 0
10681	       || (module && strcmp (module, gsym->mod_name) != 0)))
10682    {
10683      /* Print an error if the procedure is defined multiple times; we have to
10684	 exclude references to the same procedure via module association or
10685	 multiple checks for the same procedure.  */
10686      gfc_error_1 ("Procedure %s with binding label %s at %L uses the same "
10687		 "global identifier as entity at %L", sym->name,
10688		 sym->binding_label, &sym->declared_at, &gsym->where);
10689      sym->binding_label = NULL;
10690    }
10691}
10692
10693
10694/* Resolve an index expression.  */
10695
10696static bool
10697resolve_index_expr (gfc_expr *e)
10698{
10699  if (!gfc_resolve_expr (e))
10700    return false;
10701
10702  if (!gfc_simplify_expr (e, 0))
10703    return false;
10704
10705  if (!gfc_specification_expr (e))
10706    return false;
10707
10708  return true;
10709}
10710
10711
10712/* Resolve a charlen structure.  */
10713
10714static bool
10715resolve_charlen (gfc_charlen *cl)
10716{
10717  int i, k;
10718  bool saved_specification_expr;
10719
10720  if (cl->resolved)
10721    return true;
10722
10723  cl->resolved = 1;
10724  saved_specification_expr = specification_expr;
10725  specification_expr = true;
10726
10727  if (cl->length_from_typespec)
10728    {
10729      if (!gfc_resolve_expr (cl->length))
10730	{
10731	  specification_expr = saved_specification_expr;
10732	  return false;
10733	}
10734
10735      if (!gfc_simplify_expr (cl->length, 0))
10736	{
10737	  specification_expr = saved_specification_expr;
10738	  return false;
10739	}
10740    }
10741  else
10742    {
10743
10744      if (!resolve_index_expr (cl->length))
10745	{
10746	  specification_expr = saved_specification_expr;
10747	  return false;
10748	}
10749    }
10750
10751  /* F2008, 4.4.3.2:  If the character length parameter value evaluates to
10752     a negative value, the length of character entities declared is zero.  */
10753  if (cl->length && !gfc_extract_int (cl->length, &i) && i < 0)
10754    gfc_replace_expr (cl->length,
10755		      gfc_get_int_expr (gfc_default_integer_kind, NULL, 0));
10756
10757  /* Check that the character length is not too large.  */
10758  k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
10759  if (cl->length && cl->length->expr_type == EXPR_CONSTANT
10760      && cl->length->ts.type == BT_INTEGER
10761      && mpz_cmp (cl->length->value.integer, gfc_integer_kinds[k].huge) > 0)
10762    {
10763      gfc_error ("String length at %L is too large", &cl->length->where);
10764      specification_expr = saved_specification_expr;
10765      return false;
10766    }
10767
10768  specification_expr = saved_specification_expr;
10769  return true;
10770}
10771
10772
10773/* Test for non-constant shape arrays.  */
10774
10775static bool
10776is_non_constant_shape_array (gfc_symbol *sym)
10777{
10778  gfc_expr *e;
10779  int i;
10780  bool not_constant;
10781
10782  not_constant = false;
10783  if (sym->as != NULL)
10784    {
10785      /* Unfortunately, !gfc_is_compile_time_shape hits a legal case that
10786	 has not been simplified; parameter array references.  Do the
10787	 simplification now.  */
10788      for (i = 0; i < sym->as->rank + sym->as->corank; i++)
10789	{
10790	  e = sym->as->lower[i];
10791	  if (e && (!resolve_index_expr(e)
10792		    || !gfc_is_constant_expr (e)))
10793	    not_constant = true;
10794	  e = sym->as->upper[i];
10795	  if (e && (!resolve_index_expr(e)
10796		    || !gfc_is_constant_expr (e)))
10797	    not_constant = true;
10798	}
10799    }
10800  return not_constant;
10801}
10802
10803/* Given a symbol and an initialization expression, add code to initialize
10804   the symbol to the function entry.  */
10805static void
10806build_init_assign (gfc_symbol *sym, gfc_expr *init)
10807{
10808  gfc_expr *lval;
10809  gfc_code *init_st;
10810  gfc_namespace *ns = sym->ns;
10811
10812  /* Search for the function namespace if this is a contained
10813     function without an explicit result.  */
10814  if (sym->attr.function && sym == sym->result
10815      && sym->name != sym->ns->proc_name->name)
10816    {
10817      ns = ns->contained;
10818      for (;ns; ns = ns->sibling)
10819	if (strcmp (ns->proc_name->name, sym->name) == 0)
10820	  break;
10821    }
10822
10823  if (ns == NULL)
10824    {
10825      gfc_free_expr (init);
10826      return;
10827    }
10828
10829  /* Build an l-value expression for the result.  */
10830  lval = gfc_lval_expr_from_sym (sym);
10831
10832  /* Add the code at scope entry.  */
10833  init_st = gfc_get_code (EXEC_INIT_ASSIGN);
10834  init_st->next = ns->code;
10835  ns->code = init_st;
10836
10837  /* Assign the default initializer to the l-value.  */
10838  init_st->loc = sym->declared_at;
10839  init_st->expr1 = lval;
10840  init_st->expr2 = init;
10841}
10842
10843/* Assign the default initializer to a derived type variable or result.  */
10844
10845static void
10846apply_default_init (gfc_symbol *sym)
10847{
10848  gfc_expr *init = NULL;
10849
10850  if (sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
10851    return;
10852
10853  if (sym->ts.type == BT_DERIVED && sym->ts.u.derived)
10854    init = gfc_default_initializer (&sym->ts);
10855
10856  if (init == NULL && sym->ts.type != BT_CLASS)
10857    return;
10858
10859  build_init_assign (sym, init);
10860  sym->attr.referenced = 1;
10861}
10862
10863/* Build an initializer for a local integer, real, complex, logical, or
10864   character variable, based on the command line flags finit-local-zero,
10865   finit-integer=, finit-real=, finit-logical=, and finit-runtime.  Returns
10866   null if the symbol should not have a default initialization.  */
10867static gfc_expr *
10868build_default_init_expr (gfc_symbol *sym)
10869{
10870  int char_len;
10871  gfc_expr *init_expr;
10872  int i;
10873
10874  /* These symbols should never have a default initialization.  */
10875  if (sym->attr.allocatable
10876      || sym->attr.external
10877      || sym->attr.dummy
10878      || sym->attr.pointer
10879      || sym->attr.in_equivalence
10880      || sym->attr.in_common
10881      || sym->attr.data
10882      || sym->module
10883      || sym->attr.cray_pointee
10884      || sym->attr.cray_pointer
10885      || sym->assoc)
10886    return NULL;
10887
10888  /* Now we'll try to build an initializer expression.  */
10889  init_expr = gfc_get_constant_expr (sym->ts.type, sym->ts.kind,
10890				     &sym->declared_at);
10891
10892  /* We will only initialize integers, reals, complex, logicals, and
10893     characters, and only if the corresponding command-line flags
10894     were set.  Otherwise, we free init_expr and return null.  */
10895  switch (sym->ts.type)
10896    {
10897    case BT_INTEGER:
10898      if (gfc_option.flag_init_integer != GFC_INIT_INTEGER_OFF)
10899	mpz_set_si (init_expr->value.integer,
10900			 gfc_option.flag_init_integer_value);
10901      else
10902	{
10903	  gfc_free_expr (init_expr);
10904	  init_expr = NULL;
10905	}
10906      break;
10907
10908    case BT_REAL:
10909      switch (flag_init_real)
10910	{
10911	case GFC_INIT_REAL_SNAN:
10912	  init_expr->is_snan = 1;
10913	  /* Fall through.  */
10914	case GFC_INIT_REAL_NAN:
10915	  mpfr_set_nan (init_expr->value.real);
10916	  break;
10917
10918	case GFC_INIT_REAL_INF:
10919	  mpfr_set_inf (init_expr->value.real, 1);
10920	  break;
10921
10922	case GFC_INIT_REAL_NEG_INF:
10923	  mpfr_set_inf (init_expr->value.real, -1);
10924	  break;
10925
10926	case GFC_INIT_REAL_ZERO:
10927	  mpfr_set_ui (init_expr->value.real, 0.0, GFC_RND_MODE);
10928	  break;
10929
10930	default:
10931	  gfc_free_expr (init_expr);
10932	  init_expr = NULL;
10933	  break;
10934	}
10935      break;
10936
10937    case BT_COMPLEX:
10938      switch (flag_init_real)
10939	{
10940	case GFC_INIT_REAL_SNAN:
10941	  init_expr->is_snan = 1;
10942	  /* Fall through.  */
10943	case GFC_INIT_REAL_NAN:
10944	  mpfr_set_nan (mpc_realref (init_expr->value.complex));
10945	  mpfr_set_nan (mpc_imagref (init_expr->value.complex));
10946	  break;
10947
10948	case GFC_INIT_REAL_INF:
10949	  mpfr_set_inf (mpc_realref (init_expr->value.complex), 1);
10950	  mpfr_set_inf (mpc_imagref (init_expr->value.complex), 1);
10951	  break;
10952
10953	case GFC_INIT_REAL_NEG_INF:
10954	  mpfr_set_inf (mpc_realref (init_expr->value.complex), -1);
10955	  mpfr_set_inf (mpc_imagref (init_expr->value.complex), -1);
10956	  break;
10957
10958	case GFC_INIT_REAL_ZERO:
10959	  mpc_set_ui (init_expr->value.complex, 0, GFC_MPC_RND_MODE);
10960	  break;
10961
10962	default:
10963	  gfc_free_expr (init_expr);
10964	  init_expr = NULL;
10965	  break;
10966	}
10967      break;
10968
10969    case BT_LOGICAL:
10970      if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_FALSE)
10971	init_expr->value.logical = 0;
10972      else if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_TRUE)
10973	init_expr->value.logical = 1;
10974      else
10975	{
10976	  gfc_free_expr (init_expr);
10977	  init_expr = NULL;
10978	}
10979      break;
10980
10981    case BT_CHARACTER:
10982      /* For characters, the length must be constant in order to
10983	 create a default initializer.  */
10984      if (gfc_option.flag_init_character == GFC_INIT_CHARACTER_ON
10985	  && sym->ts.u.cl->length
10986	  && sym->ts.u.cl->length->expr_type == EXPR_CONSTANT)
10987	{
10988	  char_len = mpz_get_si (sym->ts.u.cl->length->value.integer);
10989	  init_expr->value.character.length = char_len;
10990	  init_expr->value.character.string = gfc_get_wide_string (char_len+1);
10991	  for (i = 0; i < char_len; i++)
10992	    init_expr->value.character.string[i]
10993	      = (unsigned char) gfc_option.flag_init_character_value;
10994	}
10995      else
10996	{
10997	  gfc_free_expr (init_expr);
10998	  init_expr = NULL;
10999	}
11000      if (!init_expr && gfc_option.flag_init_character == GFC_INIT_CHARACTER_ON
11001	  && sym->ts.u.cl->length && flag_max_stack_var_size != 0)
11002	{
11003	  gfc_actual_arglist *arg;
11004	  init_expr = gfc_get_expr ();
11005	  init_expr->where = sym->declared_at;
11006	  init_expr->ts = sym->ts;
11007	  init_expr->expr_type = EXPR_FUNCTION;
11008	  init_expr->value.function.isym =
11009		gfc_intrinsic_function_by_id (GFC_ISYM_REPEAT);
11010	  init_expr->value.function.name = "repeat";
11011	  arg = gfc_get_actual_arglist ();
11012	  arg->expr = gfc_get_character_expr (sym->ts.kind, &sym->declared_at,
11013					      NULL, 1);
11014	  arg->expr->value.character.string[0]
11015		= gfc_option.flag_init_character_value;
11016	  arg->next = gfc_get_actual_arglist ();
11017	  arg->next->expr = gfc_copy_expr (sym->ts.u.cl->length);
11018	  init_expr->value.function.actual = arg;
11019	}
11020      break;
11021
11022    default:
11023     gfc_free_expr (init_expr);
11024     init_expr = NULL;
11025    }
11026  return init_expr;
11027}
11028
11029/* Add an initialization expression to a local variable.  */
11030static void
11031apply_default_init_local (gfc_symbol *sym)
11032{
11033  gfc_expr *init = NULL;
11034
11035  /* The symbol should be a variable or a function return value.  */
11036  if ((sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
11037      || (sym->attr.function && sym->result != sym))
11038    return;
11039
11040  /* Try to build the initializer expression.  If we can't initialize
11041     this symbol, then init will be NULL.  */
11042  init = build_default_init_expr (sym);
11043  if (init == NULL)
11044    return;
11045
11046  /* For saved variables, we don't want to add an initializer at function
11047     entry, so we just add a static initializer. Note that automatic variables
11048     are stack allocated even with -fno-automatic; we have also to exclude
11049     result variable, which are also nonstatic.  */
11050  if (sym->attr.save || sym->ns->save_all
11051      || (flag_max_stack_var_size == 0 && !sym->attr.result
11052	  && (sym->ns->proc_name && !sym->ns->proc_name->attr.recursive)
11053	  && (!sym->attr.dimension || !is_non_constant_shape_array (sym))))
11054    {
11055      /* Don't clobber an existing initializer!  */
11056      gcc_assert (sym->value == NULL);
11057      sym->value = init;
11058      return;
11059    }
11060
11061  build_init_assign (sym, init);
11062}
11063
11064
11065/* Resolution of common features of flavors variable and procedure.  */
11066
11067static bool
11068resolve_fl_var_and_proc (gfc_symbol *sym, int mp_flag)
11069{
11070  gfc_array_spec *as;
11071
11072  if (sym->ts.type == BT_CLASS && sym->attr.class_ok)
11073    as = CLASS_DATA (sym)->as;
11074  else
11075    as = sym->as;
11076
11077  /* Constraints on deferred shape variable.  */
11078  if (as == NULL || as->type != AS_DEFERRED)
11079    {
11080      bool pointer, allocatable, dimension;
11081
11082      if (sym->ts.type == BT_CLASS && sym->attr.class_ok)
11083	{
11084	  pointer = CLASS_DATA (sym)->attr.class_pointer;
11085	  allocatable = CLASS_DATA (sym)->attr.allocatable;
11086	  dimension = CLASS_DATA (sym)->attr.dimension;
11087	}
11088      else
11089	{
11090	  pointer = sym->attr.pointer && !sym->attr.select_type_temporary;
11091	  allocatable = sym->attr.allocatable;
11092	  dimension = sym->attr.dimension;
11093	}
11094
11095      if (allocatable)
11096	{
11097	  if (dimension && as->type != AS_ASSUMED_RANK)
11098	    {
11099	      gfc_error ("Allocatable array %qs at %L must have a deferred "
11100			 "shape or assumed rank", sym->name, &sym->declared_at);
11101	      return false;
11102	    }
11103	  else if (!gfc_notify_std (GFC_STD_F2003, "Scalar object "
11104				    "%qs at %L may not be ALLOCATABLE",
11105				    sym->name, &sym->declared_at))
11106	    return false;
11107	}
11108
11109      if (pointer && dimension && as->type != AS_ASSUMED_RANK)
11110	{
11111	  gfc_error ("Array pointer %qs at %L must have a deferred shape or "
11112		     "assumed rank", sym->name, &sym->declared_at);
11113	  return false;
11114	}
11115    }
11116  else
11117    {
11118      if (!mp_flag && !sym->attr.allocatable && !sym->attr.pointer
11119	  && sym->ts.type != BT_CLASS && !sym->assoc)
11120	{
11121	  gfc_error ("Array %qs at %L cannot have a deferred shape",
11122		     sym->name, &sym->declared_at);
11123	  return false;
11124	 }
11125    }
11126
11127  /* Constraints on polymorphic variables.  */
11128  if (sym->ts.type == BT_CLASS && !(sym->result && sym->result != sym))
11129    {
11130      /* F03:C502.  */
11131      if (sym->attr.class_ok
11132	  && !sym->attr.select_type_temporary
11133	  && !UNLIMITED_POLY (sym)
11134	  && !gfc_type_is_extensible (CLASS_DATA (sym)->ts.u.derived))
11135	{
11136	  gfc_error ("Type %qs of CLASS variable %qs at %L is not extensible",
11137		     CLASS_DATA (sym)->ts.u.derived->name, sym->name,
11138		     &sym->declared_at);
11139	  return false;
11140	}
11141
11142      /* F03:C509.  */
11143      /* Assume that use associated symbols were checked in the module ns.
11144	 Class-variables that are associate-names are also something special
11145	 and excepted from the test.  */
11146      if (!sym->attr.class_ok && !sym->attr.use_assoc && !sym->assoc)
11147	{
11148	  gfc_error ("CLASS variable %qs at %L must be dummy, allocatable "
11149		     "or pointer", sym->name, &sym->declared_at);
11150	  return false;
11151	}
11152    }
11153
11154  return true;
11155}
11156
11157
11158/* Additional checks for symbols with flavor variable and derived
11159   type.  To be called from resolve_fl_variable.  */
11160
11161static bool
11162resolve_fl_variable_derived (gfc_symbol *sym, int no_init_flag)
11163{
11164  gcc_assert (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS);
11165
11166  /* Check to see if a derived type is blocked from being host
11167     associated by the presence of another class I symbol in the same
11168     namespace.  14.6.1.3 of the standard and the discussion on
11169     comp.lang.fortran.  */
11170  if (sym->ns != sym->ts.u.derived->ns
11171      && sym->ns->proc_name->attr.if_source != IFSRC_IFBODY)
11172    {
11173      gfc_symbol *s;
11174      gfc_find_symbol (sym->ts.u.derived->name, sym->ns, 0, &s);
11175      if (s && s->attr.generic)
11176	s = gfc_find_dt_in_generic (s);
11177      if (s && s->attr.flavor != FL_DERIVED)
11178	{
11179	  gfc_error_1 ("The type '%s' cannot be host associated at %L "
11180		     "because it is blocked by an incompatible object "
11181		     "of the same name declared at %L",
11182		     sym->ts.u.derived->name, &sym->declared_at,
11183		     &s->declared_at);
11184	  return false;
11185	}
11186    }
11187
11188  /* 4th constraint in section 11.3: "If an object of a type for which
11189     component-initialization is specified (R429) appears in the
11190     specification-part of a module and does not have the ALLOCATABLE
11191     or POINTER attribute, the object shall have the SAVE attribute."
11192
11193     The check for initializers is performed with
11194     gfc_has_default_initializer because gfc_default_initializer generates
11195     a hidden default for allocatable components.  */
11196  if (!(sym->value || no_init_flag) && sym->ns->proc_name
11197      && sym->ns->proc_name->attr.flavor == FL_MODULE
11198      && !sym->ns->save_all && !sym->attr.save
11199      && !sym->attr.pointer && !sym->attr.allocatable
11200      && gfc_has_default_initializer (sym->ts.u.derived)
11201      && !gfc_notify_std (GFC_STD_F2008, "Implied SAVE for module variable "
11202			  "%qs at %L, needed due to the default "
11203			  "initialization", sym->name, &sym->declared_at))
11204    return false;
11205
11206  /* Assign default initializer.  */
11207  if (!(sym->value || sym->attr.pointer || sym->attr.allocatable)
11208      && (!no_init_flag || sym->attr.intent == INTENT_OUT))
11209    {
11210      sym->value = gfc_default_initializer (&sym->ts);
11211    }
11212
11213  return true;
11214}
11215
11216
11217/* Resolve symbols with flavor variable.  */
11218
11219static bool
11220resolve_fl_variable (gfc_symbol *sym, int mp_flag)
11221{
11222  int no_init_flag, automatic_flag;
11223  gfc_expr *e;
11224  const char *auto_save_msg;
11225  bool saved_specification_expr;
11226
11227  auto_save_msg = "Automatic object %qs at %L cannot have the "
11228		  "SAVE attribute";
11229
11230  if (!resolve_fl_var_and_proc (sym, mp_flag))
11231    return false;
11232
11233  /* Set this flag to check that variables are parameters of all entries.
11234     This check is effected by the call to gfc_resolve_expr through
11235     is_non_constant_shape_array.  */
11236  saved_specification_expr = specification_expr;
11237  specification_expr = true;
11238
11239  if (sym->ns->proc_name
11240      && (sym->ns->proc_name->attr.flavor == FL_MODULE
11241	  || sym->ns->proc_name->attr.is_main_program)
11242      && !sym->attr.use_assoc
11243      && !sym->attr.allocatable
11244      && !sym->attr.pointer
11245      && is_non_constant_shape_array (sym))
11246    {
11247      /* The shape of a main program or module array needs to be
11248	 constant.  */
11249      gfc_error ("The module or main program array '%s' at %L must "
11250		 "have constant shape", sym->name, &sym->declared_at);
11251      specification_expr = saved_specification_expr;
11252      return false;
11253    }
11254
11255  /* Constraints on deferred type parameter.  */
11256  if (sym->ts.deferred
11257      && !(sym->attr.pointer
11258	   || sym->attr.allocatable
11259	   || sym->attr.omp_udr_artificial_var))
11260    {
11261      gfc_error ("Entity %qs at %L has a deferred type parameter and "
11262		 "requires either the pointer or allocatable attribute",
11263		     sym->name, &sym->declared_at);
11264      specification_expr = saved_specification_expr;
11265      return false;
11266    }
11267
11268  if (sym->ts.type == BT_CHARACTER)
11269    {
11270      /* Make sure that character string variables with assumed length are
11271	 dummy arguments.  */
11272      e = sym->ts.u.cl->length;
11273      if (e == NULL && !sym->attr.dummy && !sym->attr.result
11274	  && !sym->ts.deferred && !sym->attr.select_type_temporary
11275	  && !sym->attr.omp_udr_artificial_var)
11276	{
11277	  gfc_error ("Entity with assumed character length at %L must be a "
11278		     "dummy argument or a PARAMETER", &sym->declared_at);
11279	  specification_expr = saved_specification_expr;
11280	  return false;
11281	}
11282
11283      if (e && sym->attr.save == SAVE_EXPLICIT && !gfc_is_constant_expr (e))
11284	{
11285	  gfc_error (auto_save_msg, sym->name, &sym->declared_at);
11286	  specification_expr = saved_specification_expr;
11287	  return false;
11288	}
11289
11290      if (!gfc_is_constant_expr (e)
11291	  && !(e->expr_type == EXPR_VARIABLE
11292	       && e->symtree->n.sym->attr.flavor == FL_PARAMETER))
11293	{
11294	  if (!sym->attr.use_assoc && sym->ns->proc_name
11295	      && (sym->ns->proc_name->attr.flavor == FL_MODULE
11296		  || sym->ns->proc_name->attr.is_main_program))
11297	    {
11298	      gfc_error ("'%s' at %L must have constant character length "
11299			"in this context", sym->name, &sym->declared_at);
11300	      specification_expr = saved_specification_expr;
11301	      return false;
11302	    }
11303	  if (sym->attr.in_common)
11304	    {
11305	      gfc_error ("COMMON variable %qs at %L must have constant "
11306			 "character length", sym->name, &sym->declared_at);
11307	      specification_expr = saved_specification_expr;
11308	      return false;
11309	    }
11310	}
11311    }
11312
11313  if (sym->value == NULL && sym->attr.referenced)
11314    apply_default_init_local (sym); /* Try to apply a default initialization.  */
11315
11316  /* Determine if the symbol may not have an initializer.  */
11317  no_init_flag = automatic_flag = 0;
11318  if (sym->attr.allocatable || sym->attr.external || sym->attr.dummy
11319      || sym->attr.intrinsic || sym->attr.result)
11320    no_init_flag = 1;
11321  else if ((sym->attr.dimension || sym->attr.codimension) && !sym->attr.pointer
11322	   && is_non_constant_shape_array (sym))
11323    {
11324      no_init_flag = automatic_flag = 1;
11325
11326      /* Also, they must not have the SAVE attribute.
11327	 SAVE_IMPLICIT is checked below.  */
11328      if (sym->as && sym->attr.codimension)
11329	{
11330	  int corank = sym->as->corank;
11331	  sym->as->corank = 0;
11332	  no_init_flag = automatic_flag = is_non_constant_shape_array (sym);
11333	  sym->as->corank = corank;
11334	}
11335      if (automatic_flag && sym->attr.save == SAVE_EXPLICIT)
11336	{
11337	  gfc_error (auto_save_msg, sym->name, &sym->declared_at);
11338	  specification_expr = saved_specification_expr;
11339	  return false;
11340	}
11341    }
11342
11343  /* Ensure that any initializer is simplified.  */
11344  if (sym->value)
11345    gfc_simplify_expr (sym->value, 1);
11346
11347  /* Reject illegal initializers.  */
11348  if (!sym->mark && sym->value)
11349    {
11350      if (sym->attr.allocatable || (sym->ts.type == BT_CLASS
11351				    && CLASS_DATA (sym)->attr.allocatable))
11352	gfc_error ("Allocatable %qs at %L cannot have an initializer",
11353		   sym->name, &sym->declared_at);
11354      else if (sym->attr.external)
11355	gfc_error ("External %qs at %L cannot have an initializer",
11356		   sym->name, &sym->declared_at);
11357      else if (sym->attr.dummy
11358	&& !(sym->ts.type == BT_DERIVED && sym->attr.intent == INTENT_OUT))
11359	gfc_error ("Dummy %qs at %L cannot have an initializer",
11360		   sym->name, &sym->declared_at);
11361      else if (sym->attr.intrinsic)
11362	gfc_error ("Intrinsic %qs at %L cannot have an initializer",
11363		   sym->name, &sym->declared_at);
11364      else if (sym->attr.result)
11365	gfc_error ("Function result %qs at %L cannot have an initializer",
11366		   sym->name, &sym->declared_at);
11367      else if (automatic_flag)
11368	gfc_error ("Automatic array %qs at %L cannot have an initializer",
11369		   sym->name, &sym->declared_at);
11370      else
11371	goto no_init_error;
11372      specification_expr = saved_specification_expr;
11373      return false;
11374    }
11375
11376no_init_error:
11377  if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
11378    {
11379      bool res = resolve_fl_variable_derived (sym, no_init_flag);
11380      specification_expr = saved_specification_expr;
11381      return res;
11382    }
11383
11384  specification_expr = saved_specification_expr;
11385  return true;
11386}
11387
11388
11389/* Resolve a procedure.  */
11390
11391static bool
11392resolve_fl_procedure (gfc_symbol *sym, int mp_flag)
11393{
11394  gfc_formal_arglist *arg;
11395
11396  if (sym->attr.function
11397      && !resolve_fl_var_and_proc (sym, mp_flag))
11398    return false;
11399
11400  if (sym->ts.type == BT_CHARACTER)
11401    {
11402      gfc_charlen *cl = sym->ts.u.cl;
11403
11404      if (cl && cl->length && gfc_is_constant_expr (cl->length)
11405	     && !resolve_charlen (cl))
11406	return false;
11407
11408      if ((!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
11409	  && sym->attr.proc == PROC_ST_FUNCTION)
11410	{
11411	  gfc_error ("Character-valued statement function %qs at %L must "
11412		     "have constant length", sym->name, &sym->declared_at);
11413	  return false;
11414	}
11415    }
11416
11417  /* Ensure that derived type for are not of a private type.  Internal
11418     module procedures are excluded by 2.2.3.3 - i.e., they are not
11419     externally accessible and can access all the objects accessible in
11420     the host.  */
11421  if (!(sym->ns->parent
11422	&& sym->ns->parent->proc_name->attr.flavor == FL_MODULE)
11423      && gfc_check_symbol_access (sym))
11424    {
11425      gfc_interface *iface;
11426
11427      for (arg = gfc_sym_get_dummy_args (sym); arg; arg = arg->next)
11428	{
11429	  if (arg->sym
11430	      && arg->sym->ts.type == BT_DERIVED
11431	      && !arg->sym->ts.u.derived->attr.use_assoc
11432	      && !gfc_check_symbol_access (arg->sym->ts.u.derived)
11433	      && !gfc_notify_std (GFC_STD_F2003, "%qs is of a PRIVATE type "
11434				  "and cannot be a dummy argument"
11435				  " of %qs, which is PUBLIC at %L",
11436				  arg->sym->name, sym->name,
11437				  &sym->declared_at))
11438	    {
11439	      /* Stop this message from recurring.  */
11440	      arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
11441	      return false;
11442	    }
11443	}
11444
11445      /* PUBLIC interfaces may expose PRIVATE procedures that take types
11446	 PRIVATE to the containing module.  */
11447      for (iface = sym->generic; iface; iface = iface->next)
11448	{
11449	  for (arg = gfc_sym_get_dummy_args (iface->sym); arg; arg = arg->next)
11450	    {
11451	      if (arg->sym
11452		  && arg->sym->ts.type == BT_DERIVED
11453		  && !arg->sym->ts.u.derived->attr.use_assoc
11454		  && !gfc_check_symbol_access (arg->sym->ts.u.derived)
11455		  && !gfc_notify_std (GFC_STD_F2003, "Procedure %qs in "
11456				      "PUBLIC interface %qs at %L "
11457				      "takes dummy arguments of %qs which "
11458				      "is PRIVATE", iface->sym->name,
11459				      sym->name, &iface->sym->declared_at,
11460				      gfc_typename(&arg->sym->ts)))
11461		{
11462		  /* Stop this message from recurring.  */
11463		  arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
11464		  return false;
11465		}
11466	     }
11467	}
11468    }
11469
11470  if (sym->attr.function && sym->value && sym->attr.proc != PROC_ST_FUNCTION
11471      && !sym->attr.proc_pointer)
11472    {
11473      gfc_error ("Function %qs at %L cannot have an initializer",
11474		 sym->name, &sym->declared_at);
11475      return false;
11476    }
11477
11478  /* An external symbol may not have an initializer because it is taken to be
11479     a procedure. Exception: Procedure Pointers.  */
11480  if (sym->attr.external && sym->value && !sym->attr.proc_pointer)
11481    {
11482      gfc_error ("External object %qs at %L may not have an initializer",
11483		 sym->name, &sym->declared_at);
11484      return false;
11485    }
11486
11487  /* An elemental function is required to return a scalar 12.7.1  */
11488  if (sym->attr.elemental && sym->attr.function && sym->as)
11489    {
11490      gfc_error ("ELEMENTAL function %qs at %L must have a scalar "
11491		 "result", sym->name, &sym->declared_at);
11492      /* Reset so that the error only occurs once.  */
11493      sym->attr.elemental = 0;
11494      return false;
11495    }
11496
11497  if (sym->attr.proc == PROC_ST_FUNCTION
11498      && (sym->attr.allocatable || sym->attr.pointer))
11499    {
11500      gfc_error ("Statement function %qs at %L may not have pointer or "
11501		 "allocatable attribute", sym->name, &sym->declared_at);
11502      return false;
11503    }
11504
11505  /* 5.1.1.5 of the Standard: A function name declared with an asterisk
11506     char-len-param shall not be array-valued, pointer-valued, recursive
11507     or pure.  ....snip... A character value of * may only be used in the
11508     following ways: (i) Dummy arg of procedure - dummy associates with
11509     actual length; (ii) To declare a named constant; or (iii) External
11510     function - but length must be declared in calling scoping unit.  */
11511  if (sym->attr.function
11512      && sym->ts.type == BT_CHARACTER && !sym->ts.deferred
11513      && sym->ts.u.cl && sym->ts.u.cl->length == NULL)
11514    {
11515      if ((sym->as && sym->as->rank) || (sym->attr.pointer)
11516	  || (sym->attr.recursive) || (sym->attr.pure))
11517	{
11518	  if (sym->as && sym->as->rank)
11519	    gfc_error ("CHARACTER(*) function %qs at %L cannot be "
11520		       "array-valued", sym->name, &sym->declared_at);
11521
11522	  if (sym->attr.pointer)
11523	    gfc_error ("CHARACTER(*) function %qs at %L cannot be "
11524		       "pointer-valued", sym->name, &sym->declared_at);
11525
11526	  if (sym->attr.pure)
11527	    gfc_error ("CHARACTER(*) function %qs at %L cannot be "
11528		       "pure", sym->name, &sym->declared_at);
11529
11530	  if (sym->attr.recursive)
11531	    gfc_error ("CHARACTER(*) function %qs at %L cannot be "
11532		       "recursive", sym->name, &sym->declared_at);
11533
11534	  return false;
11535	}
11536
11537      /* Appendix B.2 of the standard.  Contained functions give an
11538	 error anyway.  Deferred character length is an F2003 feature.
11539	 Don't warn on intrinsic conversion functions, which start
11540	 with two underscores.  */
11541      if (!sym->attr.contained && !sym->ts.deferred
11542	  && (sym->name[0] != '_' || sym->name[1] != '_'))
11543	gfc_notify_std (GFC_STD_F95_OBS,
11544			"CHARACTER(*) function %qs at %L",
11545			sym->name, &sym->declared_at);
11546    }
11547
11548  /* F2008, C1218.  */
11549  if (sym->attr.elemental)
11550    {
11551      if (sym->attr.proc_pointer)
11552	{
11553	  gfc_error ("Procedure pointer %qs at %L shall not be elemental",
11554		     sym->name, &sym->declared_at);
11555	  return false;
11556	}
11557      if (sym->attr.dummy)
11558	{
11559	  gfc_error ("Dummy procedure %qs at %L shall not be elemental",
11560		     sym->name, &sym->declared_at);
11561	  return false;
11562	}
11563    }
11564
11565  if (sym->attr.is_bind_c && sym->attr.is_c_interop != 1)
11566    {
11567      gfc_formal_arglist *curr_arg;
11568      int has_non_interop_arg = 0;
11569
11570      if (!verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
11571			      sym->common_block))
11572        {
11573          /* Clear these to prevent looking at them again if there was an
11574             error.  */
11575          sym->attr.is_bind_c = 0;
11576          sym->attr.is_c_interop = 0;
11577          sym->ts.is_c_interop = 0;
11578        }
11579      else
11580        {
11581          /* So far, no errors have been found.  */
11582          sym->attr.is_c_interop = 1;
11583          sym->ts.is_c_interop = 1;
11584        }
11585
11586      curr_arg = gfc_sym_get_dummy_args (sym);
11587      while (curr_arg != NULL)
11588        {
11589          /* Skip implicitly typed dummy args here.  */
11590	  if (curr_arg->sym->attr.implicit_type == 0)
11591	    if (!gfc_verify_c_interop_param (curr_arg->sym))
11592	      /* If something is found to fail, record the fact so we
11593		 can mark the symbol for the procedure as not being
11594		 BIND(C) to try and prevent multiple errors being
11595		 reported.  */
11596	      has_non_interop_arg = 1;
11597
11598          curr_arg = curr_arg->next;
11599        }
11600
11601      /* See if any of the arguments were not interoperable and if so, clear
11602	 the procedure symbol to prevent duplicate error messages.  */
11603      if (has_non_interop_arg != 0)
11604	{
11605	  sym->attr.is_c_interop = 0;
11606	  sym->ts.is_c_interop = 0;
11607	  sym->attr.is_bind_c = 0;
11608	}
11609    }
11610
11611  if (!sym->attr.proc_pointer)
11612    {
11613      if (sym->attr.save == SAVE_EXPLICIT)
11614	{
11615	  gfc_error ("PROCEDURE attribute conflicts with SAVE attribute "
11616		     "in %qs at %L", sym->name, &sym->declared_at);
11617	  return false;
11618	}
11619      if (sym->attr.intent)
11620	{
11621	  gfc_error ("PROCEDURE attribute conflicts with INTENT attribute "
11622		     "in %qs at %L", sym->name, &sym->declared_at);
11623	  return false;
11624	}
11625      if (sym->attr.subroutine && sym->attr.result)
11626	{
11627	  gfc_error ("PROCEDURE attribute conflicts with RESULT attribute "
11628		     "in %qs at %L", sym->name, &sym->declared_at);
11629	  return false;
11630	}
11631      if (sym->attr.external && sym->attr.function
11632	  && ((sym->attr.if_source == IFSRC_DECL && !sym->attr.procedure)
11633	      || sym->attr.contained))
11634	{
11635	  gfc_error ("EXTERNAL attribute conflicts with FUNCTION attribute "
11636		     "in %qs at %L", sym->name, &sym->declared_at);
11637	  return false;
11638	}
11639      if (strcmp ("ppr@", sym->name) == 0)
11640	{
11641	  gfc_error ("Procedure pointer result %qs at %L "
11642		     "is missing the pointer attribute",
11643		     sym->ns->proc_name->name, &sym->declared_at);
11644	  return false;
11645	}
11646    }
11647
11648  /* Assume that a procedure whose body is not known has references
11649     to external arrays.  */
11650  if (sym->attr.if_source != IFSRC_DECL)
11651    sym->attr.array_outer_dependency = 1;
11652
11653  return true;
11654}
11655
11656
11657/* Resolve a list of finalizer procedures.  That is, after they have hopefully
11658   been defined and we now know their defined arguments, check that they fulfill
11659   the requirements of the standard for procedures used as finalizers.  */
11660
11661static bool
11662gfc_resolve_finalizers (gfc_symbol* derived, bool *finalizable)
11663{
11664  gfc_finalizer* list;
11665  gfc_finalizer** prev_link; /* For removing wrong entries from the list.  */
11666  bool result = true;
11667  bool seen_scalar = false;
11668  gfc_symbol *vtab;
11669  gfc_component *c;
11670  gfc_symbol *parent = gfc_get_derived_super_type (derived);
11671
11672  if (parent)
11673    gfc_resolve_finalizers (parent, finalizable);
11674
11675  /* Return early when not finalizable. Additionally, ensure that derived-type
11676     components have a their finalizables resolved.  */
11677  if (!derived->f2k_derived || !derived->f2k_derived->finalizers)
11678    {
11679      bool has_final = false;
11680      for (c = derived->components; c; c = c->next)
11681	if (c->ts.type == BT_DERIVED
11682	    && !c->attr.pointer && !c->attr.proc_pointer && !c->attr.allocatable)
11683	  {
11684	    bool has_final2 = false;
11685	    if (!gfc_resolve_finalizers (c->ts.u.derived, &has_final))
11686	      return false;  /* Error.  */
11687	    has_final = has_final || has_final2;
11688	  }
11689      if (!has_final)
11690	{
11691	  if (finalizable)
11692	    *finalizable = false;
11693	  return true;
11694	}
11695    }
11696
11697  /* Walk over the list of finalizer-procedures, check them, and if any one
11698     does not fit in with the standard's definition, print an error and remove
11699     it from the list.  */
11700  prev_link = &derived->f2k_derived->finalizers;
11701  for (list = derived->f2k_derived->finalizers; list; list = *prev_link)
11702    {
11703      gfc_formal_arglist *dummy_args;
11704      gfc_symbol* arg;
11705      gfc_finalizer* i;
11706      int my_rank;
11707
11708      /* Skip this finalizer if we already resolved it.  */
11709      if (list->proc_tree)
11710	{
11711	  prev_link = &(list->next);
11712	  continue;
11713	}
11714
11715      /* Check this exists and is a SUBROUTINE.  */
11716      if (!list->proc_sym->attr.subroutine)
11717	{
11718	  gfc_error ("FINAL procedure %qs at %L is not a SUBROUTINE",
11719		     list->proc_sym->name, &list->where);
11720	  goto error;
11721	}
11722
11723      /* We should have exactly one argument.  */
11724      dummy_args = gfc_sym_get_dummy_args (list->proc_sym);
11725      if (!dummy_args || dummy_args->next)
11726	{
11727	  gfc_error ("FINAL procedure at %L must have exactly one argument",
11728		     &list->where);
11729	  goto error;
11730	}
11731      arg = dummy_args->sym;
11732
11733      /* This argument must be of our type.  */
11734      if (arg->ts.type != BT_DERIVED || arg->ts.u.derived != derived)
11735	{
11736	  gfc_error ("Argument of FINAL procedure at %L must be of type %qs",
11737		     &arg->declared_at, derived->name);
11738	  goto error;
11739	}
11740
11741      /* It must neither be a pointer nor allocatable nor optional.  */
11742      if (arg->attr.pointer)
11743	{
11744	  gfc_error ("Argument of FINAL procedure at %L must not be a POINTER",
11745		     &arg->declared_at);
11746	  goto error;
11747	}
11748      if (arg->attr.allocatable)
11749	{
11750	  gfc_error ("Argument of FINAL procedure at %L must not be"
11751		     " ALLOCATABLE", &arg->declared_at);
11752	  goto error;
11753	}
11754      if (arg->attr.optional)
11755	{
11756	  gfc_error ("Argument of FINAL procedure at %L must not be OPTIONAL",
11757		     &arg->declared_at);
11758	  goto error;
11759	}
11760
11761      /* It must not be INTENT(OUT).  */
11762      if (arg->attr.intent == INTENT_OUT)
11763	{
11764	  gfc_error ("Argument of FINAL procedure at %L must not be"
11765		     " INTENT(OUT)", &arg->declared_at);
11766	  goto error;
11767	}
11768
11769      /* Warn if the procedure is non-scalar and not assumed shape.  */
11770      if (warn_surprising && arg->as && arg->as->rank != 0
11771	  && arg->as->type != AS_ASSUMED_SHAPE)
11772	gfc_warning (OPT_Wsurprising,
11773		     "Non-scalar FINAL procedure at %L should have assumed"
11774		     " shape argument", &arg->declared_at);
11775
11776      /* Check that it does not match in kind and rank with a FINAL procedure
11777	 defined earlier.  To really loop over the *earlier* declarations,
11778	 we need to walk the tail of the list as new ones were pushed at the
11779	 front.  */
11780      /* TODO: Handle kind parameters once they are implemented.  */
11781      my_rank = (arg->as ? arg->as->rank : 0);
11782      for (i = list->next; i; i = i->next)
11783	{
11784	  gfc_formal_arglist *dummy_args;
11785
11786	  /* Argument list might be empty; that is an error signalled earlier,
11787	     but we nevertheless continued resolving.  */
11788	  dummy_args = gfc_sym_get_dummy_args (i->proc_sym);
11789	  if (dummy_args)
11790	    {
11791	      gfc_symbol* i_arg = dummy_args->sym;
11792	      const int i_rank = (i_arg->as ? i_arg->as->rank : 0);
11793	      if (i_rank == my_rank)
11794		{
11795		  gfc_error ("FINAL procedure %qs declared at %L has the same"
11796			     " rank (%d) as %qs",
11797			     list->proc_sym->name, &list->where, my_rank,
11798			     i->proc_sym->name);
11799		  goto error;
11800		}
11801	    }
11802	}
11803
11804	/* Is this the/a scalar finalizer procedure?  */
11805	if (!arg->as || arg->as->rank == 0)
11806	  seen_scalar = true;
11807
11808	/* Find the symtree for this procedure.  */
11809	gcc_assert (!list->proc_tree);
11810	list->proc_tree = gfc_find_sym_in_symtree (list->proc_sym);
11811
11812	prev_link = &list->next;
11813	continue;
11814
11815	/* Remove wrong nodes immediately from the list so we don't risk any
11816	   troubles in the future when they might fail later expectations.  */
11817error:
11818	i = list;
11819	*prev_link = list->next;
11820	gfc_free_finalizer (i);
11821	result = false;
11822    }
11823
11824  if (result == false)
11825    return false;
11826
11827  /* Warn if we haven't seen a scalar finalizer procedure (but we know there
11828     were nodes in the list, must have been for arrays.  It is surely a good
11829     idea to have a scalar version there if there's something to finalize.  */
11830  if (warn_surprising && result && !seen_scalar)
11831    gfc_warning (OPT_Wsurprising,
11832		 "Only array FINAL procedures declared for derived type %qs"
11833		 " defined at %L, suggest also scalar one",
11834		 derived->name, &derived->declared_at);
11835
11836  vtab = gfc_find_derived_vtab (derived);
11837  c = vtab->ts.u.derived->components->next->next->next->next->next;
11838  gfc_set_sym_referenced (c->initializer->symtree->n.sym);
11839
11840  if (finalizable)
11841    *finalizable = true;
11842
11843  return true;
11844}
11845
11846
11847/* Check if two GENERIC targets are ambiguous and emit an error is they are.  */
11848
11849static bool
11850check_generic_tbp_ambiguity (gfc_tbp_generic* t1, gfc_tbp_generic* t2,
11851			     const char* generic_name, locus where)
11852{
11853  gfc_symbol *sym1, *sym2;
11854  const char *pass1, *pass2;
11855  gfc_formal_arglist *dummy_args;
11856
11857  gcc_assert (t1->specific && t2->specific);
11858  gcc_assert (!t1->specific->is_generic);
11859  gcc_assert (!t2->specific->is_generic);
11860  gcc_assert (t1->is_operator == t2->is_operator);
11861
11862  sym1 = t1->specific->u.specific->n.sym;
11863  sym2 = t2->specific->u.specific->n.sym;
11864
11865  if (sym1 == sym2)
11866    return true;
11867
11868  /* Both must be SUBROUTINEs or both must be FUNCTIONs.  */
11869  if (sym1->attr.subroutine != sym2->attr.subroutine
11870      || sym1->attr.function != sym2->attr.function)
11871    {
11872      gfc_error ("%qs and %qs can't be mixed FUNCTION/SUBROUTINE for"
11873		 " GENERIC %qs at %L",
11874		 sym1->name, sym2->name, generic_name, &where);
11875      return false;
11876    }
11877
11878  /* Determine PASS arguments.  */
11879  if (t1->specific->nopass)
11880    pass1 = NULL;
11881  else if (t1->specific->pass_arg)
11882    pass1 = t1->specific->pass_arg;
11883  else
11884    {
11885      dummy_args = gfc_sym_get_dummy_args (t1->specific->u.specific->n.sym);
11886      if (dummy_args)
11887	pass1 = dummy_args->sym->name;
11888      else
11889	pass1 = NULL;
11890    }
11891  if (t2->specific->nopass)
11892    pass2 = NULL;
11893  else if (t2->specific->pass_arg)
11894    pass2 = t2->specific->pass_arg;
11895  else
11896    {
11897      dummy_args = gfc_sym_get_dummy_args (t2->specific->u.specific->n.sym);
11898      if (dummy_args)
11899	pass2 = dummy_args->sym->name;
11900      else
11901	pass2 = NULL;
11902    }
11903
11904  /* Compare the interfaces.  */
11905  if (gfc_compare_interfaces (sym1, sym2, sym2->name, !t1->is_operator, 0,
11906			      NULL, 0, pass1, pass2))
11907    {
11908      gfc_error ("%qs and %qs for GENERIC %qs at %L are ambiguous",
11909		 sym1->name, sym2->name, generic_name, &where);
11910      return false;
11911    }
11912
11913  return true;
11914}
11915
11916
11917/* Worker function for resolving a generic procedure binding; this is used to
11918   resolve GENERIC as well as user and intrinsic OPERATOR typebound procedures.
11919
11920   The difference between those cases is finding possible inherited bindings
11921   that are overridden, as one has to look for them in tb_sym_root,
11922   tb_uop_root or tb_op, respectively.  Thus the caller must already find
11923   the super-type and set p->overridden correctly.  */
11924
11925static bool
11926resolve_tb_generic_targets (gfc_symbol* super_type,
11927			    gfc_typebound_proc* p, const char* name)
11928{
11929  gfc_tbp_generic* target;
11930  gfc_symtree* first_target;
11931  gfc_symtree* inherited;
11932
11933  gcc_assert (p && p->is_generic);
11934
11935  /* Try to find the specific bindings for the symtrees in our target-list.  */
11936  gcc_assert (p->u.generic);
11937  for (target = p->u.generic; target; target = target->next)
11938    if (!target->specific)
11939      {
11940	gfc_typebound_proc* overridden_tbp;
11941	gfc_tbp_generic* g;
11942	const char* target_name;
11943
11944	target_name = target->specific_st->name;
11945
11946	/* Defined for this type directly.  */
11947	if (target->specific_st->n.tb && !target->specific_st->n.tb->error)
11948	  {
11949	    target->specific = target->specific_st->n.tb;
11950	    goto specific_found;
11951	  }
11952
11953	/* Look for an inherited specific binding.  */
11954	if (super_type)
11955	  {
11956	    inherited = gfc_find_typebound_proc (super_type, NULL, target_name,
11957						 true, NULL);
11958
11959	    if (inherited)
11960	      {
11961		gcc_assert (inherited->n.tb);
11962		target->specific = inherited->n.tb;
11963		goto specific_found;
11964	      }
11965	  }
11966
11967	gfc_error ("Undefined specific binding %qs as target of GENERIC %qs"
11968		   " at %L", target_name, name, &p->where);
11969	return false;
11970
11971	/* Once we've found the specific binding, check it is not ambiguous with
11972	   other specifics already found or inherited for the same GENERIC.  */
11973specific_found:
11974	gcc_assert (target->specific);
11975
11976	/* This must really be a specific binding!  */
11977	if (target->specific->is_generic)
11978	  {
11979	    gfc_error ("GENERIC %qs at %L must target a specific binding,"
11980		       " %qs is GENERIC, too", name, &p->where, target_name);
11981	    return false;
11982	  }
11983
11984	/* Check those already resolved on this type directly.  */
11985	for (g = p->u.generic; g; g = g->next)
11986	  if (g != target && g->specific
11987	      && !check_generic_tbp_ambiguity (target, g, name, p->where))
11988	    return false;
11989
11990	/* Check for ambiguity with inherited specific targets.  */
11991	for (overridden_tbp = p->overridden; overridden_tbp;
11992	     overridden_tbp = overridden_tbp->overridden)
11993	  if (overridden_tbp->is_generic)
11994	    {
11995	      for (g = overridden_tbp->u.generic; g; g = g->next)
11996		{
11997		  gcc_assert (g->specific);
11998		  if (!check_generic_tbp_ambiguity (target, g, name, p->where))
11999		    return false;
12000		}
12001	    }
12002      }
12003
12004  /* If we attempt to "overwrite" a specific binding, this is an error.  */
12005  if (p->overridden && !p->overridden->is_generic)
12006    {
12007      gfc_error ("GENERIC %qs at %L can't overwrite specific binding with"
12008		 " the same name", name, &p->where);
12009      return false;
12010    }
12011
12012  /* Take the SUBROUTINE/FUNCTION attributes of the first specific target, as
12013     all must have the same attributes here.  */
12014  first_target = p->u.generic->specific->u.specific;
12015  gcc_assert (first_target);
12016  p->subroutine = first_target->n.sym->attr.subroutine;
12017  p->function = first_target->n.sym->attr.function;
12018
12019  return true;
12020}
12021
12022
12023/* Resolve a GENERIC procedure binding for a derived type.  */
12024
12025static bool
12026resolve_typebound_generic (gfc_symbol* derived, gfc_symtree* st)
12027{
12028  gfc_symbol* super_type;
12029
12030  /* Find the overridden binding if any.  */
12031  st->n.tb->overridden = NULL;
12032  super_type = gfc_get_derived_super_type (derived);
12033  if (super_type)
12034    {
12035      gfc_symtree* overridden;
12036      overridden = gfc_find_typebound_proc (super_type, NULL, st->name,
12037					    true, NULL);
12038
12039      if (overridden && overridden->n.tb)
12040	st->n.tb->overridden = overridden->n.tb;
12041    }
12042
12043  /* Resolve using worker function.  */
12044  return resolve_tb_generic_targets (super_type, st->n.tb, st->name);
12045}
12046
12047
12048/* Retrieve the target-procedure of an operator binding and do some checks in
12049   common for intrinsic and user-defined type-bound operators.  */
12050
12051static gfc_symbol*
12052get_checked_tb_operator_target (gfc_tbp_generic* target, locus where)
12053{
12054  gfc_symbol* target_proc;
12055
12056  gcc_assert (target->specific && !target->specific->is_generic);
12057  target_proc = target->specific->u.specific->n.sym;
12058  gcc_assert (target_proc);
12059
12060  /* F08:C468. All operator bindings must have a passed-object dummy argument.  */
12061  if (target->specific->nopass)
12062    {
12063      gfc_error ("Type-bound operator at %L can't be NOPASS", &where);
12064      return NULL;
12065    }
12066
12067  return target_proc;
12068}
12069
12070
12071/* Resolve a type-bound intrinsic operator.  */
12072
12073static bool
12074resolve_typebound_intrinsic_op (gfc_symbol* derived, gfc_intrinsic_op op,
12075				gfc_typebound_proc* p)
12076{
12077  gfc_symbol* super_type;
12078  gfc_tbp_generic* target;
12079
12080  /* If there's already an error here, do nothing (but don't fail again).  */
12081  if (p->error)
12082    return true;
12083
12084  /* Operators should always be GENERIC bindings.  */
12085  gcc_assert (p->is_generic);
12086
12087  /* Look for an overridden binding.  */
12088  super_type = gfc_get_derived_super_type (derived);
12089  if (super_type && super_type->f2k_derived)
12090    p->overridden = gfc_find_typebound_intrinsic_op (super_type, NULL,
12091						     op, true, NULL);
12092  else
12093    p->overridden = NULL;
12094
12095  /* Resolve general GENERIC properties using worker function.  */
12096  if (!resolve_tb_generic_targets (super_type, p, gfc_op2string(op)))
12097    goto error;
12098
12099  /* Check the targets to be procedures of correct interface.  */
12100  for (target = p->u.generic; target; target = target->next)
12101    {
12102      gfc_symbol* target_proc;
12103
12104      target_proc = get_checked_tb_operator_target (target, p->where);
12105      if (!target_proc)
12106	goto error;
12107
12108      if (!gfc_check_operator_interface (target_proc, op, p->where))
12109	goto error;
12110
12111      /* Add target to non-typebound operator list.  */
12112      if (!target->specific->deferred && !derived->attr.use_assoc
12113	  && p->access != ACCESS_PRIVATE && derived->ns == gfc_current_ns)
12114	{
12115	  gfc_interface *head, *intr;
12116	  if (!gfc_check_new_interface (derived->ns->op[op], target_proc, p->where))
12117	    return false;
12118	  head = derived->ns->op[op];
12119	  intr = gfc_get_interface ();
12120	  intr->sym = target_proc;
12121	  intr->where = p->where;
12122	  intr->next = head;
12123	  derived->ns->op[op] = intr;
12124	}
12125    }
12126
12127  return true;
12128
12129error:
12130  p->error = 1;
12131  return false;
12132}
12133
12134
12135/* Resolve a type-bound user operator (tree-walker callback).  */
12136
12137static gfc_symbol* resolve_bindings_derived;
12138static bool resolve_bindings_result;
12139
12140static bool check_uop_procedure (gfc_symbol* sym, locus where);
12141
12142static void
12143resolve_typebound_user_op (gfc_symtree* stree)
12144{
12145  gfc_symbol* super_type;
12146  gfc_tbp_generic* target;
12147
12148  gcc_assert (stree && stree->n.tb);
12149
12150  if (stree->n.tb->error)
12151    return;
12152
12153  /* Operators should always be GENERIC bindings.  */
12154  gcc_assert (stree->n.tb->is_generic);
12155
12156  /* Find overridden procedure, if any.  */
12157  super_type = gfc_get_derived_super_type (resolve_bindings_derived);
12158  if (super_type && super_type->f2k_derived)
12159    {
12160      gfc_symtree* overridden;
12161      overridden = gfc_find_typebound_user_op (super_type, NULL,
12162					       stree->name, true, NULL);
12163
12164      if (overridden && overridden->n.tb)
12165	stree->n.tb->overridden = overridden->n.tb;
12166    }
12167  else
12168    stree->n.tb->overridden = NULL;
12169
12170  /* Resolve basically using worker function.  */
12171  if (!resolve_tb_generic_targets (super_type, stree->n.tb, stree->name))
12172    goto error;
12173
12174  /* Check the targets to be functions of correct interface.  */
12175  for (target = stree->n.tb->u.generic; target; target = target->next)
12176    {
12177      gfc_symbol* target_proc;
12178
12179      target_proc = get_checked_tb_operator_target (target, stree->n.tb->where);
12180      if (!target_proc)
12181	goto error;
12182
12183      if (!check_uop_procedure (target_proc, stree->n.tb->where))
12184	goto error;
12185    }
12186
12187  return;
12188
12189error:
12190  resolve_bindings_result = false;
12191  stree->n.tb->error = 1;
12192}
12193
12194
12195/* Resolve the type-bound procedures for a derived type.  */
12196
12197static void
12198resolve_typebound_procedure (gfc_symtree* stree)
12199{
12200  gfc_symbol* proc;
12201  locus where;
12202  gfc_symbol* me_arg;
12203  gfc_symbol* super_type;
12204  gfc_component* comp;
12205
12206  gcc_assert (stree);
12207
12208  /* Undefined specific symbol from GENERIC target definition.  */
12209  if (!stree->n.tb)
12210    return;
12211
12212  if (stree->n.tb->error)
12213    return;
12214
12215  /* If this is a GENERIC binding, use that routine.  */
12216  if (stree->n.tb->is_generic)
12217    {
12218      if (!resolve_typebound_generic (resolve_bindings_derived, stree))
12219	goto error;
12220      return;
12221    }
12222
12223  /* Get the target-procedure to check it.  */
12224  gcc_assert (!stree->n.tb->is_generic);
12225  gcc_assert (stree->n.tb->u.specific);
12226  proc = stree->n.tb->u.specific->n.sym;
12227  where = stree->n.tb->where;
12228
12229  /* Default access should already be resolved from the parser.  */
12230  gcc_assert (stree->n.tb->access != ACCESS_UNKNOWN);
12231
12232  if (stree->n.tb->deferred)
12233    {
12234      if (!check_proc_interface (proc, &where))
12235	goto error;
12236    }
12237  else
12238    {
12239      /* Check for F08:C465.  */
12240      if ((!proc->attr.subroutine && !proc->attr.function)
12241	  || (proc->attr.proc != PROC_MODULE
12242	      && proc->attr.if_source != IFSRC_IFBODY)
12243	  || proc->attr.abstract)
12244	{
12245	  gfc_error ("%qs must be a module procedure or an external procedure with"
12246		    " an explicit interface at %L", proc->name, &where);
12247	  goto error;
12248	}
12249    }
12250
12251  stree->n.tb->subroutine = proc->attr.subroutine;
12252  stree->n.tb->function = proc->attr.function;
12253
12254  /* Find the super-type of the current derived type.  We could do this once and
12255     store in a global if speed is needed, but as long as not I believe this is
12256     more readable and clearer.  */
12257  super_type = gfc_get_derived_super_type (resolve_bindings_derived);
12258
12259  /* If PASS, resolve and check arguments if not already resolved / loaded
12260     from a .mod file.  */
12261  if (!stree->n.tb->nopass && stree->n.tb->pass_arg_num == 0)
12262    {
12263      gfc_formal_arglist *dummy_args;
12264
12265      dummy_args = gfc_sym_get_dummy_args (proc);
12266      if (stree->n.tb->pass_arg)
12267	{
12268	  gfc_formal_arglist *i;
12269
12270	  /* If an explicit passing argument name is given, walk the arg-list
12271	     and look for it.  */
12272
12273	  me_arg = NULL;
12274	  stree->n.tb->pass_arg_num = 1;
12275	  for (i = dummy_args; i; i = i->next)
12276	    {
12277	      if (!strcmp (i->sym->name, stree->n.tb->pass_arg))
12278		{
12279		  me_arg = i->sym;
12280		  break;
12281		}
12282	      ++stree->n.tb->pass_arg_num;
12283	    }
12284
12285	  if (!me_arg)
12286	    {
12287	      gfc_error ("Procedure %qs with PASS(%s) at %L has no"
12288			 " argument %qs",
12289			 proc->name, stree->n.tb->pass_arg, &where,
12290			 stree->n.tb->pass_arg);
12291	      goto error;
12292	    }
12293	}
12294      else
12295	{
12296	  /* Otherwise, take the first one; there should in fact be at least
12297	     one.  */
12298	  stree->n.tb->pass_arg_num = 1;
12299	  if (!dummy_args)
12300	    {
12301	      gfc_error ("Procedure %qs with PASS at %L must have at"
12302			 " least one argument", proc->name, &where);
12303	      goto error;
12304	    }
12305	  me_arg = dummy_args->sym;
12306	}
12307
12308      /* Now check that the argument-type matches and the passed-object
12309	 dummy argument is generally fine.  */
12310
12311      gcc_assert (me_arg);
12312
12313      if (me_arg->ts.type != BT_CLASS)
12314	{
12315	  gfc_error ("Non-polymorphic passed-object dummy argument of %qs"
12316		     " at %L", proc->name, &where);
12317	  goto error;
12318	}
12319
12320      if (CLASS_DATA (me_arg)->ts.u.derived
12321	  != resolve_bindings_derived)
12322	{
12323	  gfc_error ("Argument %qs of %qs with PASS(%s) at %L must be of"
12324		     " the derived-type %qs", me_arg->name, proc->name,
12325		     me_arg->name, &where, resolve_bindings_derived->name);
12326	  goto error;
12327	}
12328
12329      gcc_assert (me_arg->ts.type == BT_CLASS);
12330      if (CLASS_DATA (me_arg)->as && CLASS_DATA (me_arg)->as->rank != 0)
12331	{
12332	  gfc_error ("Passed-object dummy argument of %qs at %L must be"
12333		     " scalar", proc->name, &where);
12334	  goto error;
12335	}
12336      if (CLASS_DATA (me_arg)->attr.allocatable)
12337	{
12338	  gfc_error ("Passed-object dummy argument of %qs at %L must not"
12339		     " be ALLOCATABLE", proc->name, &where);
12340	  goto error;
12341	}
12342      if (CLASS_DATA (me_arg)->attr.class_pointer)
12343	{
12344	  gfc_error ("Passed-object dummy argument of %qs at %L must not"
12345		     " be POINTER", proc->name, &where);
12346	  goto error;
12347	}
12348    }
12349
12350  /* If we are extending some type, check that we don't override a procedure
12351     flagged NON_OVERRIDABLE.  */
12352  stree->n.tb->overridden = NULL;
12353  if (super_type)
12354    {
12355      gfc_symtree* overridden;
12356      overridden = gfc_find_typebound_proc (super_type, NULL,
12357					    stree->name, true, NULL);
12358
12359      if (overridden)
12360	{
12361	  if (overridden->n.tb)
12362	    stree->n.tb->overridden = overridden->n.tb;
12363
12364	  if (!gfc_check_typebound_override (stree, overridden))
12365	    goto error;
12366	}
12367    }
12368
12369  /* See if there's a name collision with a component directly in this type.  */
12370  for (comp = resolve_bindings_derived->components; comp; comp = comp->next)
12371    if (!strcmp (comp->name, stree->name))
12372      {
12373	gfc_error ("Procedure %qs at %L has the same name as a component of"
12374		   " %qs",
12375		   stree->name, &where, resolve_bindings_derived->name);
12376	goto error;
12377      }
12378
12379  /* Try to find a name collision with an inherited component.  */
12380  if (super_type && gfc_find_component (super_type, stree->name, true, true))
12381    {
12382      gfc_error ("Procedure %qs at %L has the same name as an inherited"
12383		 " component of %qs",
12384		 stree->name, &where, resolve_bindings_derived->name);
12385      goto error;
12386    }
12387
12388  stree->n.tb->error = 0;
12389  return;
12390
12391error:
12392  resolve_bindings_result = false;
12393  stree->n.tb->error = 1;
12394}
12395
12396
12397static bool
12398resolve_typebound_procedures (gfc_symbol* derived)
12399{
12400  int op;
12401  gfc_symbol* super_type;
12402
12403  if (!derived->f2k_derived || !derived->f2k_derived->tb_sym_root)
12404    return true;
12405
12406  super_type = gfc_get_derived_super_type (derived);
12407  if (super_type)
12408    resolve_symbol (super_type);
12409
12410  resolve_bindings_derived = derived;
12411  resolve_bindings_result = true;
12412
12413  if (derived->f2k_derived->tb_sym_root)
12414    gfc_traverse_symtree (derived->f2k_derived->tb_sym_root,
12415			  &resolve_typebound_procedure);
12416
12417  if (derived->f2k_derived->tb_uop_root)
12418    gfc_traverse_symtree (derived->f2k_derived->tb_uop_root,
12419			  &resolve_typebound_user_op);
12420
12421  for (op = 0; op != GFC_INTRINSIC_OPS; ++op)
12422    {
12423      gfc_typebound_proc* p = derived->f2k_derived->tb_op[op];
12424      if (p && !resolve_typebound_intrinsic_op (derived,
12425						(gfc_intrinsic_op)op, p))
12426	resolve_bindings_result = false;
12427    }
12428
12429  return resolve_bindings_result;
12430}
12431
12432
12433/* Add a derived type to the dt_list.  The dt_list is used in trans-types.c
12434   to give all identical derived types the same backend_decl.  */
12435static void
12436add_dt_to_dt_list (gfc_symbol *derived)
12437{
12438  gfc_dt_list *dt_list;
12439
12440  for (dt_list = gfc_derived_types; dt_list; dt_list = dt_list->next)
12441    if (derived == dt_list->derived)
12442      return;
12443
12444  dt_list = gfc_get_dt_list ();
12445  dt_list->next = gfc_derived_types;
12446  dt_list->derived = derived;
12447  gfc_derived_types = dt_list;
12448}
12449
12450
12451/* Ensure that a derived-type is really not abstract, meaning that every
12452   inherited DEFERRED binding is overridden by a non-DEFERRED one.  */
12453
12454static bool
12455ensure_not_abstract_walker (gfc_symbol* sub, gfc_symtree* st)
12456{
12457  if (!st)
12458    return true;
12459
12460  if (!ensure_not_abstract_walker (sub, st->left))
12461    return false;
12462  if (!ensure_not_abstract_walker (sub, st->right))
12463    return false;
12464
12465  if (st->n.tb && st->n.tb->deferred)
12466    {
12467      gfc_symtree* overriding;
12468      overriding = gfc_find_typebound_proc (sub, NULL, st->name, true, NULL);
12469      if (!overriding)
12470	return false;
12471      gcc_assert (overriding->n.tb);
12472      if (overriding->n.tb->deferred)
12473	{
12474	  gfc_error ("Derived-type %qs declared at %L must be ABSTRACT because"
12475		     " %qs is DEFERRED and not overridden",
12476		     sub->name, &sub->declared_at, st->name);
12477	  return false;
12478	}
12479    }
12480
12481  return true;
12482}
12483
12484static bool
12485ensure_not_abstract (gfc_symbol* sub, gfc_symbol* ancestor)
12486{
12487  /* The algorithm used here is to recursively travel up the ancestry of sub
12488     and for each ancestor-type, check all bindings.  If any of them is
12489     DEFERRED, look it up starting from sub and see if the found (overriding)
12490     binding is not DEFERRED.
12491     This is not the most efficient way to do this, but it should be ok and is
12492     clearer than something sophisticated.  */
12493
12494  gcc_assert (ancestor && !sub->attr.abstract);
12495
12496  if (!ancestor->attr.abstract)
12497    return true;
12498
12499  /* Walk bindings of this ancestor.  */
12500  if (ancestor->f2k_derived)
12501    {
12502      bool t;
12503      t = ensure_not_abstract_walker (sub, ancestor->f2k_derived->tb_sym_root);
12504      if (!t)
12505	return false;
12506    }
12507
12508  /* Find next ancestor type and recurse on it.  */
12509  ancestor = gfc_get_derived_super_type (ancestor);
12510  if (ancestor)
12511    return ensure_not_abstract (sub, ancestor);
12512
12513  return true;
12514}
12515
12516
12517/* This check for typebound defined assignments is done recursively
12518   since the order in which derived types are resolved is not always in
12519   order of the declarations.  */
12520
12521static void
12522check_defined_assignments (gfc_symbol *derived)
12523{
12524  gfc_component *c;
12525
12526  for (c = derived->components; c; c = c->next)
12527    {
12528      if (c->ts.type != BT_DERIVED
12529	  || c->attr.pointer
12530	  || c->attr.allocatable
12531	  || c->attr.proc_pointer_comp
12532	  || c->attr.class_pointer
12533	  || c->attr.proc_pointer)
12534	continue;
12535
12536      if (c->ts.u.derived->attr.defined_assign_comp
12537	  || (c->ts.u.derived->f2k_derived
12538	     && c->ts.u.derived->f2k_derived->tb_op[INTRINSIC_ASSIGN]))
12539	{
12540	  derived->attr.defined_assign_comp = 1;
12541	  return;
12542	}
12543
12544      check_defined_assignments (c->ts.u.derived);
12545      if (c->ts.u.derived->attr.defined_assign_comp)
12546	{
12547	  derived->attr.defined_assign_comp = 1;
12548	  return;
12549	}
12550    }
12551}
12552
12553
12554/* Resolve the components of a derived type. This does not have to wait until
12555   resolution stage, but can be done as soon as the dt declaration has been
12556   parsed.  */
12557
12558static bool
12559resolve_fl_derived0 (gfc_symbol *sym)
12560{
12561  gfc_symbol* super_type;
12562  gfc_component *c;
12563
12564  if (sym->attr.unlimited_polymorphic)
12565    return true;
12566
12567  super_type = gfc_get_derived_super_type (sym);
12568
12569  /* F2008, C432.  */
12570  if (super_type && sym->attr.coarray_comp && !super_type->attr.coarray_comp)
12571    {
12572      gfc_error ("As extending type %qs at %L has a coarray component, "
12573		 "parent type %qs shall also have one", sym->name,
12574		 &sym->declared_at, super_type->name);
12575      return false;
12576    }
12577
12578  /* Ensure the extended type gets resolved before we do.  */
12579  if (super_type && !resolve_fl_derived0 (super_type))
12580    return false;
12581
12582  /* An ABSTRACT type must be extensible.  */
12583  if (sym->attr.abstract && !gfc_type_is_extensible (sym))
12584    {
12585      gfc_error ("Non-extensible derived-type %qs at %L must not be ABSTRACT",
12586		 sym->name, &sym->declared_at);
12587      return false;
12588    }
12589
12590  c = (sym->attr.is_class) ? sym->components->ts.u.derived->components
12591			   : sym->components;
12592
12593  bool success = true;
12594
12595  for ( ; c != NULL; c = c->next)
12596    {
12597      if (c->attr.artificial)
12598	continue;
12599
12600      /* F2008, C442.  */
12601      if ((!sym->attr.is_class || c != sym->components)
12602	  && c->attr.codimension
12603	  && (!c->attr.allocatable || (c->as && c->as->type != AS_DEFERRED)))
12604	{
12605	  gfc_error ("Coarray component %qs at %L must be allocatable with "
12606		     "deferred shape", c->name, &c->loc);
12607	  success = false;
12608	  continue;
12609	}
12610
12611      /* F2008, C443.  */
12612      if (c->attr.codimension && c->ts.type == BT_DERIVED
12613	  && c->ts.u.derived->ts.is_iso_c)
12614	{
12615	  gfc_error ("Component %qs at %L of TYPE(C_PTR) or TYPE(C_FUNPTR) "
12616		     "shall not be a coarray", c->name, &c->loc);
12617	  success = false;
12618	  continue;
12619	}
12620
12621      /* F2008, C444.  */
12622      if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.coarray_comp
12623	  && (c->attr.codimension || c->attr.pointer || c->attr.dimension
12624	      || c->attr.allocatable))
12625	{
12626	  gfc_error ("Component %qs at %L with coarray component "
12627		     "shall be a nonpointer, nonallocatable scalar",
12628		     c->name, &c->loc);
12629	  success = false;
12630	  continue;
12631	}
12632
12633      /* F2008, C448.  */
12634      if (c->attr.contiguous && (!c->attr.dimension || !c->attr.pointer))
12635	{
12636	  gfc_error ("Component %qs at %L has the CONTIGUOUS attribute but "
12637		     "is not an array pointer", c->name, &c->loc);
12638	  success = false;
12639	  continue;
12640	}
12641
12642      if (c->attr.proc_pointer && c->ts.interface)
12643	{
12644	  gfc_symbol *ifc = c->ts.interface;
12645
12646	  if (!sym->attr.vtype && !check_proc_interface (ifc, &c->loc))
12647	    {
12648	      c->tb->error = 1;
12649	      success = false;
12650	      continue;
12651	    }
12652
12653	  if (ifc->attr.if_source || ifc->attr.intrinsic)
12654	    {
12655	      /* Resolve interface and copy attributes.  */
12656	      if (ifc->formal && !ifc->formal_ns)
12657		resolve_symbol (ifc);
12658	      if (ifc->attr.intrinsic)
12659		gfc_resolve_intrinsic (ifc, &ifc->declared_at);
12660
12661	      if (ifc->result)
12662		{
12663		  c->ts = ifc->result->ts;
12664		  c->attr.allocatable = ifc->result->attr.allocatable;
12665		  c->attr.pointer = ifc->result->attr.pointer;
12666		  c->attr.dimension = ifc->result->attr.dimension;
12667		  c->as = gfc_copy_array_spec (ifc->result->as);
12668		  c->attr.class_ok = ifc->result->attr.class_ok;
12669		}
12670	      else
12671		{
12672		  c->ts = ifc->ts;
12673		  c->attr.allocatable = ifc->attr.allocatable;
12674		  c->attr.pointer = ifc->attr.pointer;
12675		  c->attr.dimension = ifc->attr.dimension;
12676		  c->as = gfc_copy_array_spec (ifc->as);
12677		  c->attr.class_ok = ifc->attr.class_ok;
12678		}
12679	      c->ts.interface = ifc;
12680	      c->attr.function = ifc->attr.function;
12681	      c->attr.subroutine = ifc->attr.subroutine;
12682
12683	      c->attr.pure = ifc->attr.pure;
12684	      c->attr.elemental = ifc->attr.elemental;
12685	      c->attr.recursive = ifc->attr.recursive;
12686	      c->attr.always_explicit = ifc->attr.always_explicit;
12687	      c->attr.ext_attr |= ifc->attr.ext_attr;
12688	      /* Copy char length.  */
12689	      if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
12690		{
12691		  gfc_charlen *cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
12692		  if (cl->length && !cl->resolved
12693		      && !gfc_resolve_expr (cl->length))
12694		    {
12695		      c->tb->error = 1;
12696		      success = false;
12697		      continue;
12698		    }
12699		  c->ts.u.cl = cl;
12700		}
12701	    }
12702	}
12703      else if (c->attr.proc_pointer && c->ts.type == BT_UNKNOWN)
12704	{
12705	  /* Since PPCs are not implicitly typed, a PPC without an explicit
12706	     interface must be a subroutine.  */
12707	  gfc_add_subroutine (&c->attr, c->name, &c->loc);
12708	}
12709
12710      /* Procedure pointer components: Check PASS arg.  */
12711      if (c->attr.proc_pointer && !c->tb->nopass && c->tb->pass_arg_num == 0
12712	  && !sym->attr.vtype)
12713	{
12714	  gfc_symbol* me_arg;
12715
12716	  if (c->tb->pass_arg)
12717	    {
12718	      gfc_formal_arglist* i;
12719
12720	      /* If an explicit passing argument name is given, walk the arg-list
12721		and look for it.  */
12722
12723	      me_arg = NULL;
12724	      c->tb->pass_arg_num = 1;
12725	      for (i = c->ts.interface->formal; i; i = i->next)
12726		{
12727		  if (!strcmp (i->sym->name, c->tb->pass_arg))
12728		    {
12729		      me_arg = i->sym;
12730		      break;
12731		    }
12732		  c->tb->pass_arg_num++;
12733		}
12734
12735	      if (!me_arg)
12736		{
12737		  gfc_error ("Procedure pointer component %qs with PASS(%s) "
12738			     "at %L has no argument %qs", c->name,
12739			     c->tb->pass_arg, &c->loc, c->tb->pass_arg);
12740		  c->tb->error = 1;
12741		  success = false;
12742		  continue;
12743		}
12744	    }
12745	  else
12746	    {
12747	      /* Otherwise, take the first one; there should in fact be at least
12748		one.  */
12749	      c->tb->pass_arg_num = 1;
12750	      if (!c->ts.interface->formal)
12751		{
12752		  gfc_error ("Procedure pointer component %qs with PASS at %L "
12753			     "must have at least one argument",
12754			     c->name, &c->loc);
12755		  c->tb->error = 1;
12756		  success = false;
12757		  continue;
12758		}
12759	      me_arg = c->ts.interface->formal->sym;
12760	    }
12761
12762	  /* Now check that the argument-type matches.  */
12763	  gcc_assert (me_arg);
12764	  if ((me_arg->ts.type != BT_DERIVED && me_arg->ts.type != BT_CLASS)
12765	      || (me_arg->ts.type == BT_DERIVED && me_arg->ts.u.derived != sym)
12766	      || (me_arg->ts.type == BT_CLASS
12767		  && CLASS_DATA (me_arg)->ts.u.derived != sym))
12768	    {
12769	      gfc_error ("Argument %qs of %qs with PASS(%s) at %L must be of"
12770			 " the derived type %qs", me_arg->name, c->name,
12771			 me_arg->name, &c->loc, sym->name);
12772	      c->tb->error = 1;
12773	      success = false;
12774	      continue;
12775	    }
12776
12777	  /* Check for C453.  */
12778	  if (me_arg->attr.dimension)
12779	    {
12780	      gfc_error ("Argument %qs of %qs with PASS(%s) at %L "
12781			 "must be scalar", me_arg->name, c->name, me_arg->name,
12782			 &c->loc);
12783	      c->tb->error = 1;
12784	      success = false;
12785	      continue;
12786	    }
12787
12788	  if (me_arg->attr.pointer)
12789	    {
12790	      gfc_error ("Argument %qs of %qs with PASS(%s) at %L "
12791			 "may not have the POINTER attribute", me_arg->name,
12792			 c->name, me_arg->name, &c->loc);
12793	      c->tb->error = 1;
12794	      success = false;
12795	      continue;
12796	    }
12797
12798	  if (me_arg->attr.allocatable)
12799	    {
12800	      gfc_error ("Argument %qs of %qs with PASS(%s) at %L "
12801			 "may not be ALLOCATABLE", me_arg->name, c->name,
12802			 me_arg->name, &c->loc);
12803	      c->tb->error = 1;
12804	      success = false;
12805	      continue;
12806	    }
12807
12808	  if (gfc_type_is_extensible (sym) && me_arg->ts.type != BT_CLASS)
12809	    {
12810	      gfc_error ("Non-polymorphic passed-object dummy argument of %qs"
12811			 " at %L", c->name, &c->loc);
12812	      success = false;
12813	      continue;
12814	    }
12815
12816	}
12817
12818      /* Check type-spec if this is not the parent-type component.  */
12819      if (((sym->attr.is_class
12820	    && (!sym->components->ts.u.derived->attr.extension
12821		|| c != sym->components->ts.u.derived->components))
12822	   || (!sym->attr.is_class
12823	       && (!sym->attr.extension || c != sym->components)))
12824	  && !sym->attr.vtype
12825	  && !resolve_typespec_used (&c->ts, &c->loc, c->name))
12826	return false;
12827
12828      /* If this type is an extension, set the accessibility of the parent
12829	 component.  */
12830      if (super_type
12831	  && ((sym->attr.is_class
12832	       && c == sym->components->ts.u.derived->components)
12833	      || (!sym->attr.is_class && c == sym->components))
12834	  && strcmp (super_type->name, c->name) == 0)
12835	c->attr.access = super_type->attr.access;
12836
12837      /* If this type is an extension, see if this component has the same name
12838	 as an inherited type-bound procedure.  */
12839      if (super_type && !sym->attr.is_class
12840	  && gfc_find_typebound_proc (super_type, NULL, c->name, true, NULL))
12841	{
12842	  gfc_error ("Component %qs of %qs at %L has the same name as an"
12843		     " inherited type-bound procedure",
12844		     c->name, sym->name, &c->loc);
12845	  return false;
12846	}
12847
12848      if (c->ts.type == BT_CHARACTER && !c->attr.proc_pointer
12849	    && !c->ts.deferred)
12850	{
12851	 if (c->ts.u.cl->length == NULL
12852	     || (!resolve_charlen(c->ts.u.cl))
12853	     || !gfc_is_constant_expr (c->ts.u.cl->length))
12854	   {
12855	     gfc_error ("Character length of component %qs needs to "
12856			"be a constant specification expression at %L",
12857			c->name,
12858			c->ts.u.cl->length ? &c->ts.u.cl->length->where : &c->loc);
12859	     return false;
12860	   }
12861	}
12862
12863      if (c->ts.type == BT_CHARACTER && c->ts.deferred
12864	  && !c->attr.pointer && !c->attr.allocatable)
12865	{
12866	  gfc_error ("Character component %qs of %qs at %L with deferred "
12867		     "length must be a POINTER or ALLOCATABLE",
12868		     c->name, sym->name, &c->loc);
12869	  return false;
12870	}
12871
12872      /* Add the hidden deferred length field.  */
12873      if (c->ts.type == BT_CHARACTER && c->ts.deferred && !c->attr.function
12874	  && !sym->attr.is_class)
12875	{
12876	  char name[GFC_MAX_SYMBOL_LEN+9];
12877	  gfc_component *strlen;
12878	  sprintf (name, "_%s_length", c->name);
12879	  strlen = gfc_find_component (sym, name, true, true);
12880	  if (strlen == NULL)
12881	    {
12882	      if (!gfc_add_component (sym, name, &strlen))
12883		return false;
12884	      strlen->ts.type = BT_INTEGER;
12885	      strlen->ts.kind = gfc_charlen_int_kind;
12886	      strlen->attr.access = ACCESS_PRIVATE;
12887	      strlen->attr.artificial = 1;
12888	    }
12889	}
12890
12891      if (c->ts.type == BT_DERIVED
12892	  && sym->component_access != ACCESS_PRIVATE
12893	  && gfc_check_symbol_access (sym)
12894	  && !is_sym_host_assoc (c->ts.u.derived, sym->ns)
12895	  && !c->ts.u.derived->attr.use_assoc
12896	  && !gfc_check_symbol_access (c->ts.u.derived)
12897	  && !gfc_notify_std (GFC_STD_F2003, "the component %qs is a "
12898			      "PRIVATE type and cannot be a component of "
12899			      "%qs, which is PUBLIC at %L", c->name,
12900			      sym->name, &sym->declared_at))
12901	return false;
12902
12903      if ((sym->attr.sequence || sym->attr.is_bind_c) && c->ts.type == BT_CLASS)
12904	{
12905	  gfc_error ("Polymorphic component %s at %L in SEQUENCE or BIND(C) "
12906		     "type %s", c->name, &c->loc, sym->name);
12907	  return false;
12908	}
12909
12910      if (sym->attr.sequence)
12911	{
12912	  if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.sequence == 0)
12913	    {
12914	      gfc_error ("Component %s of SEQUENCE type declared at %L does "
12915			 "not have the SEQUENCE attribute",
12916			 c->ts.u.derived->name, &sym->declared_at);
12917	      return false;
12918	    }
12919	}
12920
12921      if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.generic)
12922	c->ts.u.derived = gfc_find_dt_in_generic (c->ts.u.derived);
12923      else if (c->ts.type == BT_CLASS && c->attr.class_ok
12924	       && CLASS_DATA (c)->ts.u.derived->attr.generic)
12925	CLASS_DATA (c)->ts.u.derived
12926			= gfc_find_dt_in_generic (CLASS_DATA (c)->ts.u.derived);
12927
12928      if (!sym->attr.is_class && c->ts.type == BT_DERIVED && !sym->attr.vtype
12929	  && c->attr.pointer && c->ts.u.derived->components == NULL
12930	  && !c->ts.u.derived->attr.zero_comp)
12931	{
12932	  gfc_error ("The pointer component %qs of %qs at %L is a type "
12933		     "that has not been declared", c->name, sym->name,
12934		     &c->loc);
12935	  return false;
12936	}
12937
12938      if (c->ts.type == BT_CLASS && c->attr.class_ok
12939	  && CLASS_DATA (c)->attr.class_pointer
12940	  && CLASS_DATA (c)->ts.u.derived->components == NULL
12941	  && !CLASS_DATA (c)->ts.u.derived->attr.zero_comp
12942	  && !UNLIMITED_POLY (c))
12943	{
12944	  gfc_error ("The pointer component %qs of %qs at %L is a type "
12945		     "that has not been declared", c->name, sym->name,
12946		     &c->loc);
12947	  return false;
12948	}
12949
12950      /* C437.  */
12951      if (c->ts.type == BT_CLASS && c->attr.flavor != FL_PROCEDURE
12952	  && (!c->attr.class_ok
12953	      || !(CLASS_DATA (c)->attr.class_pointer
12954		   || CLASS_DATA (c)->attr.allocatable)))
12955	{
12956	  gfc_error ("Component %qs with CLASS at %L must be allocatable "
12957		     "or pointer", c->name, &c->loc);
12958	  /* Prevent a recurrence of the error.  */
12959	  c->ts.type = BT_UNKNOWN;
12960	  return false;
12961	}
12962
12963      /* Ensure that all the derived type components are put on the
12964	 derived type list; even in formal namespaces, where derived type
12965	 pointer components might not have been declared.  */
12966      if (c->ts.type == BT_DERIVED
12967	    && c->ts.u.derived
12968	    && c->ts.u.derived->components
12969	    && c->attr.pointer
12970	    && sym != c->ts.u.derived)
12971	add_dt_to_dt_list (c->ts.u.derived);
12972
12973      if (!gfc_resolve_array_spec (c->as,
12974				   !(c->attr.pointer || c->attr.proc_pointer
12975				     || c->attr.allocatable)))
12976	return false;
12977
12978      if (c->initializer && !sym->attr.vtype
12979	  && !gfc_check_assign_symbol (sym, c, c->initializer))
12980	return false;
12981    }
12982
12983  if (!success)
12984    return false;
12985
12986  check_defined_assignments (sym);
12987
12988  if (!sym->attr.defined_assign_comp && super_type)
12989    sym->attr.defined_assign_comp
12990			= super_type->attr.defined_assign_comp;
12991
12992  /* If this is a non-ABSTRACT type extending an ABSTRACT one, ensure that
12993     all DEFERRED bindings are overridden.  */
12994  if (super_type && super_type->attr.abstract && !sym->attr.abstract
12995      && !sym->attr.is_class
12996      && !ensure_not_abstract (sym, super_type))
12997    return false;
12998
12999  /* Add derived type to the derived type list.  */
13000  add_dt_to_dt_list (sym);
13001
13002  return true;
13003}
13004
13005
13006/* The following procedure does the full resolution of a derived type,
13007   including resolution of all type-bound procedures (if present). In contrast
13008   to 'resolve_fl_derived0' this can only be done after the module has been
13009   parsed completely.  */
13010
13011static bool
13012resolve_fl_derived (gfc_symbol *sym)
13013{
13014  gfc_symbol *gen_dt = NULL;
13015
13016  if (sym->attr.unlimited_polymorphic)
13017    return true;
13018
13019  if (!sym->attr.is_class)
13020    gfc_find_symbol (sym->name, sym->ns, 0, &gen_dt);
13021  if (gen_dt && gen_dt->generic && gen_dt->generic->next
13022      && (!gen_dt->generic->sym->attr.use_assoc
13023	  || gen_dt->generic->sym->module != gen_dt->generic->next->sym->module)
13024      && !gfc_notify_std_1 (GFC_STD_F2003, "Generic name '%s' of function "
13025			  "'%s' at %L being the same name as derived "
13026			  "type at %L", sym->name,
13027			  gen_dt->generic->sym == sym
13028			  ? gen_dt->generic->next->sym->name
13029			  : gen_dt->generic->sym->name,
13030			  gen_dt->generic->sym == sym
13031			  ? &gen_dt->generic->next->sym->declared_at
13032			  : &gen_dt->generic->sym->declared_at,
13033			  &sym->declared_at))
13034    return false;
13035
13036  /* Resolve the finalizer procedures.  */
13037  if (!gfc_resolve_finalizers (sym, NULL))
13038    return false;
13039
13040  if (sym->attr.is_class && sym->ts.u.derived == NULL)
13041    {
13042      /* Fix up incomplete CLASS symbols.  */
13043      gfc_component *data = gfc_find_component (sym, "_data", true, true);
13044      gfc_component *vptr = gfc_find_component (sym, "_vptr", true, true);
13045
13046      /* Nothing more to do for unlimited polymorphic entities.  */
13047      if (data->ts.u.derived->attr.unlimited_polymorphic)
13048	return true;
13049      else if (vptr->ts.u.derived == NULL)
13050	{
13051	  gfc_symbol *vtab = gfc_find_derived_vtab (data->ts.u.derived);
13052	  gcc_assert (vtab);
13053	  vptr->ts.u.derived = vtab->ts.u.derived;
13054	}
13055    }
13056
13057  if (!resolve_fl_derived0 (sym))
13058    return false;
13059
13060  /* Resolve the type-bound procedures.  */
13061  if (!resolve_typebound_procedures (sym))
13062    return false;
13063
13064  return true;
13065}
13066
13067
13068static bool
13069resolve_fl_namelist (gfc_symbol *sym)
13070{
13071  gfc_namelist *nl;
13072  gfc_symbol *nlsym;
13073
13074  for (nl = sym->namelist; nl; nl = nl->next)
13075    {
13076      /* Check again, the check in match only works if NAMELIST comes
13077	 after the decl.  */
13078      if (nl->sym->as && nl->sym->as->type == AS_ASSUMED_SIZE)
13079     	{
13080	  gfc_error ("Assumed size array %qs in namelist %qs at %L is not "
13081		     "allowed", nl->sym->name, sym->name, &sym->declared_at);
13082	  return false;
13083	}
13084
13085      if (nl->sym->as && nl->sym->as->type == AS_ASSUMED_SHAPE
13086	  && !gfc_notify_std (GFC_STD_F2003, "NAMELIST array object %qs "
13087			      "with assumed shape in namelist %qs at %L",
13088			      nl->sym->name, sym->name, &sym->declared_at))
13089	return false;
13090
13091      if (is_non_constant_shape_array (nl->sym)
13092	  && !gfc_notify_std (GFC_STD_F2003, "NAMELIST array object %qs "
13093			      "with nonconstant shape in namelist %qs at %L",
13094			      nl->sym->name, sym->name, &sym->declared_at))
13095	return false;
13096
13097      if (nl->sym->ts.type == BT_CHARACTER
13098	  && (nl->sym->ts.u.cl->length == NULL
13099	      || !gfc_is_constant_expr (nl->sym->ts.u.cl->length))
13100	  && !gfc_notify_std (GFC_STD_F2003, "NAMELIST object %qs with "
13101			      "nonconstant character length in "
13102			      "namelist %qs at %L", nl->sym->name,
13103			      sym->name, &sym->declared_at))
13104	return false;
13105
13106      /* FIXME: Once UDDTIO is implemented, the following can be
13107	 removed.  */
13108      if (nl->sym->ts.type == BT_CLASS)
13109	{
13110	  gfc_error ("NAMELIST object %qs in namelist %qs at %L is "
13111		     "polymorphic and requires a defined input/output "
13112		     "procedure", nl->sym->name, sym->name, &sym->declared_at);
13113	  return false;
13114	}
13115
13116      if (nl->sym->ts.type == BT_DERIVED
13117	  && (nl->sym->ts.u.derived->attr.alloc_comp
13118	      || nl->sym->ts.u.derived->attr.pointer_comp))
13119	{
13120	  if (!gfc_notify_std (GFC_STD_F2003, "NAMELIST object %qs in "
13121			       "namelist %qs at %L with ALLOCATABLE "
13122			       "or POINTER components", nl->sym->name,
13123			       sym->name, &sym->declared_at))
13124	    return false;
13125
13126	 /* FIXME: Once UDDTIO is implemented, the following can be
13127	    removed.  */
13128	  gfc_error ("NAMELIST object %qs in namelist %qs at %L has "
13129		     "ALLOCATABLE or POINTER components and thus requires "
13130		     "a defined input/output procedure", nl->sym->name,
13131		     sym->name, &sym->declared_at);
13132	  return false;
13133	}
13134    }
13135
13136  /* Reject PRIVATE objects in a PUBLIC namelist.  */
13137  if (gfc_check_symbol_access (sym))
13138    {
13139      for (nl = sym->namelist; nl; nl = nl->next)
13140	{
13141	  if (!nl->sym->attr.use_assoc
13142	      && !is_sym_host_assoc (nl->sym, sym->ns)
13143	      && !gfc_check_symbol_access (nl->sym))
13144	    {
13145	      gfc_error ("NAMELIST object %qs was declared PRIVATE and "
13146			 "cannot be member of PUBLIC namelist %qs at %L",
13147			 nl->sym->name, sym->name, &sym->declared_at);
13148	      return false;
13149	    }
13150
13151	  /* Types with private components that came here by USE-association.  */
13152	  if (nl->sym->ts.type == BT_DERIVED
13153	      && derived_inaccessible (nl->sym->ts.u.derived))
13154	    {
13155	      gfc_error ("NAMELIST object %qs has use-associated PRIVATE "
13156			 "components and cannot be member of namelist %qs at %L",
13157			 nl->sym->name, sym->name, &sym->declared_at);
13158	      return false;
13159	    }
13160
13161	  /* Types with private components that are defined in the same module.  */
13162	  if (nl->sym->ts.type == BT_DERIVED
13163	      && !is_sym_host_assoc (nl->sym->ts.u.derived, sym->ns)
13164	      && nl->sym->ts.u.derived->attr.private_comp)
13165	    {
13166	      gfc_error ("NAMELIST object %qs has PRIVATE components and "
13167			 "cannot be a member of PUBLIC namelist %qs at %L",
13168			 nl->sym->name, sym->name, &sym->declared_at);
13169	      return false;
13170	    }
13171	}
13172    }
13173
13174
13175  /* 14.1.2 A module or internal procedure represent local entities
13176     of the same type as a namelist member and so are not allowed.  */
13177  for (nl = sym->namelist; nl; nl = nl->next)
13178    {
13179      if (nl->sym->ts.kind != 0 && nl->sym->attr.flavor == FL_VARIABLE)
13180	continue;
13181
13182      if (nl->sym->attr.function && nl->sym == nl->sym->result)
13183	if ((nl->sym == sym->ns->proc_name)
13184	       ||
13185	    (sym->ns->parent && nl->sym == sym->ns->parent->proc_name))
13186	  continue;
13187
13188      nlsym = NULL;
13189      if (nl->sym->name)
13190	gfc_find_symbol (nl->sym->name, sym->ns, 1, &nlsym);
13191      if (nlsym && nlsym->attr.flavor == FL_PROCEDURE)
13192	{
13193	  gfc_error ("PROCEDURE attribute conflicts with NAMELIST "
13194		     "attribute in %qs at %L", nlsym->name,
13195		     &sym->declared_at);
13196	  return false;
13197	}
13198    }
13199
13200  return true;
13201}
13202
13203
13204static bool
13205resolve_fl_parameter (gfc_symbol *sym)
13206{
13207  /* A parameter array's shape needs to be constant.  */
13208  if (sym->as != NULL
13209      && (sym->as->type == AS_DEFERRED
13210          || is_non_constant_shape_array (sym)))
13211    {
13212      gfc_error ("Parameter array %qs at %L cannot be automatic "
13213		 "or of deferred shape", sym->name, &sym->declared_at);
13214      return false;
13215    }
13216
13217  /* Make sure a parameter that has been implicitly typed still
13218     matches the implicit type, since PARAMETER statements can precede
13219     IMPLICIT statements.  */
13220  if (sym->attr.implicit_type
13221      && !gfc_compare_types (&sym->ts, gfc_get_default_type (sym->name,
13222							     sym->ns)))
13223    {
13224      gfc_error ("Implicitly typed PARAMETER %qs at %L doesn't match a "
13225		 "later IMPLICIT type", sym->name, &sym->declared_at);
13226      return false;
13227    }
13228
13229  /* Make sure the types of derived parameters are consistent.  This
13230     type checking is deferred until resolution because the type may
13231     refer to a derived type from the host.  */
13232  if (sym->ts.type == BT_DERIVED
13233      && !gfc_compare_types (&sym->ts, &sym->value->ts))
13234    {
13235      gfc_error ("Incompatible derived type in PARAMETER at %L",
13236		 &sym->value->where);
13237      return false;
13238    }
13239  return true;
13240}
13241
13242
13243/* Do anything necessary to resolve a symbol.  Right now, we just
13244   assume that an otherwise unknown symbol is a variable.  This sort
13245   of thing commonly happens for symbols in module.  */
13246
13247static void
13248resolve_symbol (gfc_symbol *sym)
13249{
13250  int check_constant, mp_flag;
13251  gfc_symtree *symtree;
13252  gfc_symtree *this_symtree;
13253  gfc_namespace *ns;
13254  gfc_component *c;
13255  symbol_attribute class_attr;
13256  gfc_array_spec *as;
13257  bool saved_specification_expr;
13258
13259  if (sym->resolved)
13260    return;
13261  sym->resolved = 1;
13262
13263  if (sym->attr.artificial)
13264    return;
13265
13266  if (sym->attr.unlimited_polymorphic)
13267    return;
13268
13269  if (sym->attr.flavor == FL_UNKNOWN
13270      || (sym->attr.flavor == FL_PROCEDURE && !sym->attr.intrinsic
13271	  && !sym->attr.generic && !sym->attr.external
13272	  && sym->attr.if_source == IFSRC_UNKNOWN
13273	  && sym->ts.type == BT_UNKNOWN))
13274    {
13275
13276    /* If we find that a flavorless symbol is an interface in one of the
13277       parent namespaces, find its symtree in this namespace, free the
13278       symbol and set the symtree to point to the interface symbol.  */
13279      for (ns = gfc_current_ns->parent; ns; ns = ns->parent)
13280	{
13281	  symtree = gfc_find_symtree (ns->sym_root, sym->name);
13282	  if (symtree && (symtree->n.sym->generic ||
13283			  (symtree->n.sym->attr.flavor == FL_PROCEDURE
13284			   && sym->ns->construct_entities)))
13285	    {
13286	      this_symtree = gfc_find_symtree (gfc_current_ns->sym_root,
13287					       sym->name);
13288	      if (this_symtree->n.sym == sym)
13289		{
13290		  symtree->n.sym->refs++;
13291		  gfc_release_symbol (sym);
13292		  this_symtree->n.sym = symtree->n.sym;
13293		  return;
13294		}
13295	    }
13296	}
13297
13298      /* Otherwise give it a flavor according to such attributes as
13299	 it has.  */
13300      if (sym->attr.flavor == FL_UNKNOWN && sym->attr.external == 0
13301	  && sym->attr.intrinsic == 0)
13302	sym->attr.flavor = FL_VARIABLE;
13303      else if (sym->attr.flavor == FL_UNKNOWN)
13304	{
13305	  sym->attr.flavor = FL_PROCEDURE;
13306	  if (sym->attr.dimension)
13307	    sym->attr.function = 1;
13308	}
13309    }
13310
13311  if (sym->attr.external && sym->ts.type != BT_UNKNOWN && !sym->attr.function)
13312    gfc_add_function (&sym->attr, sym->name, &sym->declared_at);
13313
13314  if (sym->attr.procedure && sym->attr.if_source != IFSRC_DECL
13315      && !resolve_procedure_interface (sym))
13316    return;
13317
13318  if (sym->attr.is_protected && !sym->attr.proc_pointer
13319      && (sym->attr.procedure || sym->attr.external))
13320    {
13321      if (sym->attr.external)
13322	gfc_error ("PROTECTED attribute conflicts with EXTERNAL attribute "
13323	           "at %L", &sym->declared_at);
13324      else
13325	gfc_error ("PROCEDURE attribute conflicts with PROTECTED attribute "
13326	           "at %L", &sym->declared_at);
13327
13328      return;
13329    }
13330
13331  if (sym->attr.flavor == FL_DERIVED && !resolve_fl_derived (sym))
13332    return;
13333
13334  /* Symbols that are module procedures with results (functions) have
13335     the types and array specification copied for type checking in
13336     procedures that call them, as well as for saving to a module
13337     file.  These symbols can't stand the scrutiny that their results
13338     can.  */
13339  mp_flag = (sym->result != NULL && sym->result != sym);
13340
13341  /* Make sure that the intrinsic is consistent with its internal
13342     representation. This needs to be done before assigning a default
13343     type to avoid spurious warnings.  */
13344  if (sym->attr.flavor != FL_MODULE && sym->attr.intrinsic
13345      && !gfc_resolve_intrinsic (sym, &sym->declared_at))
13346    return;
13347
13348  /* Resolve associate names.  */
13349  if (sym->assoc)
13350    resolve_assoc_var (sym, true);
13351
13352  /* Assign default type to symbols that need one and don't have one.  */
13353  if (sym->ts.type == BT_UNKNOWN)
13354    {
13355      if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER)
13356	{
13357	  gfc_set_default_type (sym, 1, NULL);
13358	}
13359
13360      if (sym->attr.flavor == FL_PROCEDURE && sym->attr.external
13361	  && !sym->attr.function && !sym->attr.subroutine
13362	  && gfc_get_default_type (sym->name, sym->ns)->type == BT_UNKNOWN)
13363	gfc_add_subroutine (&sym->attr, sym->name, &sym->declared_at);
13364
13365      if (sym->attr.flavor == FL_PROCEDURE && sym->attr.function)
13366	{
13367	  /* The specific case of an external procedure should emit an error
13368	     in the case that there is no implicit type.  */
13369	  if (!mp_flag)
13370	    gfc_set_default_type (sym, sym->attr.external, NULL);
13371	  else
13372	    {
13373	      /* Result may be in another namespace.  */
13374	      resolve_symbol (sym->result);
13375
13376	      if (!sym->result->attr.proc_pointer)
13377		{
13378		  sym->ts = sym->result->ts;
13379		  sym->as = gfc_copy_array_spec (sym->result->as);
13380		  sym->attr.dimension = sym->result->attr.dimension;
13381		  sym->attr.pointer = sym->result->attr.pointer;
13382		  sym->attr.allocatable = sym->result->attr.allocatable;
13383		  sym->attr.contiguous = sym->result->attr.contiguous;
13384		}
13385	    }
13386	}
13387    }
13388  else if (mp_flag && sym->attr.flavor == FL_PROCEDURE && sym->attr.function)
13389    {
13390      bool saved_specification_expr = specification_expr;
13391      specification_expr = true;
13392      gfc_resolve_array_spec (sym->result->as, false);
13393      specification_expr = saved_specification_expr;
13394    }
13395
13396  if (sym->ts.type == BT_CLASS && sym->attr.class_ok)
13397    {
13398      as = CLASS_DATA (sym)->as;
13399      class_attr = CLASS_DATA (sym)->attr;
13400      class_attr.pointer = class_attr.class_pointer;
13401    }
13402  else
13403    {
13404      class_attr = sym->attr;
13405      as = sym->as;
13406    }
13407
13408  /* F2008, C530.  */
13409  if (sym->attr.contiguous
13410      && (!class_attr.dimension
13411	  || (as->type != AS_ASSUMED_SHAPE && as->type != AS_ASSUMED_RANK
13412	      && !class_attr.pointer)))
13413    {
13414      gfc_error ("%qs at %L has the CONTIGUOUS attribute but is not an "
13415		 "array pointer or an assumed-shape or assumed-rank array",
13416		 sym->name, &sym->declared_at);
13417      return;
13418    }
13419
13420  /* Assumed size arrays and assumed shape arrays must be dummy
13421     arguments.  Array-spec's of implied-shape should have been resolved to
13422     AS_EXPLICIT already.  */
13423
13424  if (as)
13425    {
13426      gcc_assert (as->type != AS_IMPLIED_SHAPE);
13427      if (((as->type == AS_ASSUMED_SIZE && !as->cp_was_assumed)
13428	   || as->type == AS_ASSUMED_SHAPE)
13429	  && !sym->attr.dummy && !sym->attr.select_type_temporary)
13430	{
13431	  if (as->type == AS_ASSUMED_SIZE)
13432	    gfc_error ("Assumed size array at %L must be a dummy argument",
13433		       &sym->declared_at);
13434	  else
13435	    gfc_error ("Assumed shape array at %L must be a dummy argument",
13436		       &sym->declared_at);
13437	  return;
13438	}
13439      /* TS 29113, C535a.  */
13440      if (as->type == AS_ASSUMED_RANK && !sym->attr.dummy
13441	  && !sym->attr.select_type_temporary)
13442	{
13443	  gfc_error ("Assumed-rank array at %L must be a dummy argument",
13444		     &sym->declared_at);
13445	  return;
13446	}
13447      if (as->type == AS_ASSUMED_RANK
13448	  && (sym->attr.codimension || sym->attr.value))
13449	{
13450	  gfc_error ("Assumed-rank array at %L may not have the VALUE or "
13451		     "CODIMENSION attribute", &sym->declared_at);
13452	  return;
13453	}
13454    }
13455
13456  /* Make sure symbols with known intent or optional are really dummy
13457     variable.  Because of ENTRY statement, this has to be deferred
13458     until resolution time.  */
13459
13460  if (!sym->attr.dummy
13461      && (sym->attr.optional || sym->attr.intent != INTENT_UNKNOWN))
13462    {
13463      gfc_error ("Symbol at %L is not a DUMMY variable", &sym->declared_at);
13464      return;
13465    }
13466
13467  if (sym->attr.value && !sym->attr.dummy)
13468    {
13469      gfc_error ("%qs at %L cannot have the VALUE attribute because "
13470		 "it is not a dummy argument", sym->name, &sym->declared_at);
13471      return;
13472    }
13473
13474  if (sym->attr.value && sym->ts.type == BT_CHARACTER)
13475    {
13476      gfc_charlen *cl = sym->ts.u.cl;
13477      if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
13478	{
13479	  gfc_error ("Character dummy variable %qs at %L with VALUE "
13480		     "attribute must have constant length",
13481		     sym->name, &sym->declared_at);
13482	  return;
13483	}
13484
13485      if (sym->ts.is_c_interop
13486	  && mpz_cmp_si (cl->length->value.integer, 1) != 0)
13487	{
13488	  gfc_error ("C interoperable character dummy variable %qs at %L "
13489		     "with VALUE attribute must have length one",
13490		     sym->name, &sym->declared_at);
13491	  return;
13492	}
13493    }
13494
13495  if (sym->ts.type == BT_DERIVED && !sym->attr.is_iso_c
13496      && sym->ts.u.derived->attr.generic)
13497    {
13498      sym->ts.u.derived = gfc_find_dt_in_generic (sym->ts.u.derived);
13499      if (!sym->ts.u.derived)
13500	{
13501	  gfc_error ("The derived type %qs at %L is of type %qs, "
13502		     "which has not been defined", sym->name,
13503		     &sym->declared_at, sym->ts.u.derived->name);
13504	  sym->ts.type = BT_UNKNOWN;
13505	  return;
13506	}
13507    }
13508
13509    /* Use the same constraints as TYPE(*), except for the type check
13510       and that only scalars and assumed-size arrays are permitted.  */
13511    if (sym->attr.ext_attr & (1 << EXT_ATTR_NO_ARG_CHECK))
13512      {
13513	if (!sym->attr.dummy)
13514	  {
13515	    gfc_error ("Variable %s at %L with NO_ARG_CHECK attribute shall be "
13516		       "a dummy argument", sym->name, &sym->declared_at);
13517	    return;
13518	  }
13519
13520	if (sym->ts.type != BT_ASSUMED && sym->ts.type != BT_INTEGER
13521	    && sym->ts.type != BT_REAL && sym->ts.type != BT_LOGICAL
13522	    && sym->ts.type != BT_COMPLEX)
13523	  {
13524	    gfc_error ("Variable %s at %L with NO_ARG_CHECK attribute shall be "
13525		       "of type TYPE(*) or of an numeric intrinsic type",
13526		       sym->name, &sym->declared_at);
13527	    return;
13528	  }
13529
13530      if (sym->attr.allocatable || sym->attr.codimension
13531	  || sym->attr.pointer || sym->attr.value)
13532	{
13533	  gfc_error ("Variable %s at %L with NO_ARG_CHECK attribute may not "
13534		     "have the ALLOCATABLE, CODIMENSION, POINTER or VALUE "
13535		     "attribute", sym->name, &sym->declared_at);
13536	  return;
13537	}
13538
13539      if (sym->attr.intent == INTENT_OUT)
13540	{
13541	  gfc_error ("Variable %s at %L with NO_ARG_CHECK attribute may not "
13542		     "have the INTENT(OUT) attribute",
13543		     sym->name, &sym->declared_at);
13544	  return;
13545	}
13546      if (sym->attr.dimension && sym->as->type != AS_ASSUMED_SIZE)
13547	{
13548	  gfc_error ("Variable %s at %L with NO_ARG_CHECK attribute shall "
13549		     "either be a scalar or an assumed-size array",
13550		     sym->name, &sym->declared_at);
13551	  return;
13552	}
13553
13554      /* Set the type to TYPE(*) and add a dimension(*) to ensure
13555	 NO_ARG_CHECK is correctly handled in trans*.c, e.g. with
13556	 packing.  */
13557      sym->ts.type = BT_ASSUMED;
13558      sym->as = gfc_get_array_spec ();
13559      sym->as->type = AS_ASSUMED_SIZE;
13560      sym->as->rank = 1;
13561      sym->as->lower[0] = gfc_get_int_expr (gfc_default_integer_kind, NULL, 1);
13562    }
13563  else if (sym->ts.type == BT_ASSUMED)
13564    {
13565      /* TS 29113, C407a.  */
13566      if (!sym->attr.dummy)
13567	{
13568	  gfc_error ("Assumed type of variable %s at %L is only permitted "
13569		     "for dummy variables", sym->name, &sym->declared_at);
13570	  return;
13571	}
13572      if (sym->attr.allocatable || sym->attr.codimension
13573	  || sym->attr.pointer || sym->attr.value)
13574    	{
13575	  gfc_error ("Assumed-type variable %s at %L may not have the "
13576		     "ALLOCATABLE, CODIMENSION, POINTER or VALUE attribute",
13577		     sym->name, &sym->declared_at);
13578	  return;
13579	}
13580      if (sym->attr.intent == INTENT_OUT)
13581    	{
13582	  gfc_error ("Assumed-type variable %s at %L may not have the "
13583		     "INTENT(OUT) attribute",
13584		     sym->name, &sym->declared_at);
13585	  return;
13586	}
13587      if (sym->attr.dimension && sym->as->type == AS_EXPLICIT)
13588	{
13589	  gfc_error ("Assumed-type variable %s at %L shall not be an "
13590		     "explicit-shape array", sym->name, &sym->declared_at);
13591	  return;
13592	}
13593    }
13594
13595  /* If the symbol is marked as bind(c), verify it's type and kind.  Do not
13596     do this for something that was implicitly typed because that is handled
13597     in gfc_set_default_type.  Handle dummy arguments and procedure
13598     definitions separately.  Also, anything that is use associated is not
13599     handled here but instead is handled in the module it is declared in.
13600     Finally, derived type definitions are allowed to be BIND(C) since that
13601     only implies that they're interoperable, and they are checked fully for
13602     interoperability when a variable is declared of that type.  */
13603  if (sym->attr.is_bind_c && sym->attr.implicit_type == 0 &&
13604      sym->attr.use_assoc == 0 && sym->attr.dummy == 0 &&
13605      sym->attr.flavor != FL_PROCEDURE && sym->attr.flavor != FL_DERIVED)
13606    {
13607      bool t = true;
13608
13609      /* First, make sure the variable is declared at the
13610	 module-level scope (J3/04-007, Section 15.3).	*/
13611      if (sym->ns->proc_name->attr.flavor != FL_MODULE &&
13612          sym->attr.in_common == 0)
13613	{
13614	  gfc_error ("Variable %qs at %L cannot be BIND(C) because it "
13615		     "is neither a COMMON block nor declared at the "
13616		     "module level scope", sym->name, &(sym->declared_at));
13617	  t = false;
13618	}
13619      else if (sym->common_head != NULL)
13620        {
13621          t = verify_com_block_vars_c_interop (sym->common_head);
13622        }
13623      else
13624	{
13625	  /* If type() declaration, we need to verify that the components
13626	     of the given type are all C interoperable, etc.  */
13627	  if (sym->ts.type == BT_DERIVED &&
13628              sym->ts.u.derived->attr.is_c_interop != 1)
13629            {
13630              /* Make sure the user marked the derived type as BIND(C).  If
13631                 not, call the verify routine.  This could print an error
13632                 for the derived type more than once if multiple variables
13633                 of that type are declared.  */
13634              if (sym->ts.u.derived->attr.is_bind_c != 1)
13635                verify_bind_c_derived_type (sym->ts.u.derived);
13636              t = false;
13637            }
13638
13639	  /* Verify the variable itself as C interoperable if it
13640             is BIND(C).  It is not possible for this to succeed if
13641             the verify_bind_c_derived_type failed, so don't have to handle
13642             any error returned by verify_bind_c_derived_type.  */
13643          t = verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
13644                                 sym->common_block);
13645	}
13646
13647      if (!t)
13648        {
13649          /* clear the is_bind_c flag to prevent reporting errors more than
13650             once if something failed.  */
13651          sym->attr.is_bind_c = 0;
13652          return;
13653        }
13654    }
13655
13656  /* If a derived type symbol has reached this point, without its
13657     type being declared, we have an error.  Notice that most
13658     conditions that produce undefined derived types have already
13659     been dealt with.  However, the likes of:
13660     implicit type(t) (t) ..... call foo (t) will get us here if
13661     the type is not declared in the scope of the implicit
13662     statement. Change the type to BT_UNKNOWN, both because it is so
13663     and to prevent an ICE.  */
13664  if (sym->ts.type == BT_DERIVED && !sym->attr.is_iso_c
13665      && sym->ts.u.derived->components == NULL
13666      && !sym->ts.u.derived->attr.zero_comp)
13667    {
13668      gfc_error ("The derived type %qs at %L is of type %qs, "
13669		 "which has not been defined", sym->name,
13670		  &sym->declared_at, sym->ts.u.derived->name);
13671      sym->ts.type = BT_UNKNOWN;
13672      return;
13673    }
13674
13675  /* Make sure that the derived type has been resolved and that the
13676     derived type is visible in the symbol's namespace, if it is a
13677     module function and is not PRIVATE.  */
13678  if (sym->ts.type == BT_DERIVED
13679	&& sym->ts.u.derived->attr.use_assoc
13680	&& sym->ns->proc_name
13681	&& sym->ns->proc_name->attr.flavor == FL_MODULE
13682        && !resolve_fl_derived (sym->ts.u.derived))
13683    return;
13684
13685  /* Unless the derived-type declaration is use associated, Fortran 95
13686     does not allow public entries of private derived types.
13687     See 4.4.1 (F95) and 4.5.1.1 (F2003); and related interpretation
13688     161 in 95-006r3.  */
13689  if (sym->ts.type == BT_DERIVED
13690      && sym->ns->proc_name && sym->ns->proc_name->attr.flavor == FL_MODULE
13691      && !sym->ts.u.derived->attr.use_assoc
13692      && gfc_check_symbol_access (sym)
13693      && !gfc_check_symbol_access (sym->ts.u.derived)
13694      && !gfc_notify_std (GFC_STD_F2003, "PUBLIC %s %qs at %L of PRIVATE "
13695			  "derived type %qs",
13696			  (sym->attr.flavor == FL_PARAMETER)
13697			  ? "parameter" : "variable",
13698			  sym->name, &sym->declared_at,
13699			  sym->ts.u.derived->name))
13700    return;
13701
13702  /* F2008, C1302.  */
13703  if (sym->ts.type == BT_DERIVED
13704      && ((sym->ts.u.derived->from_intmod == INTMOD_ISO_FORTRAN_ENV
13705	   && sym->ts.u.derived->intmod_sym_id == ISOFORTRAN_LOCK_TYPE)
13706	  || sym->ts.u.derived->attr.lock_comp)
13707      && !sym->attr.codimension && !sym->ts.u.derived->attr.coarray_comp)
13708    {
13709      gfc_error ("Variable %s at %L of type LOCK_TYPE or with subcomponent of "
13710		 "type LOCK_TYPE must be a coarray", sym->name,
13711		 &sym->declared_at);
13712      return;
13713    }
13714
13715  /* TS18508, C702/C703.  */
13716  if (sym->ts.type == BT_DERIVED
13717      && ((sym->ts.u.derived->from_intmod == INTMOD_ISO_FORTRAN_ENV
13718	   && sym->ts.u.derived->intmod_sym_id == ISOFORTRAN_EVENT_TYPE)
13719	  || sym->ts.u.derived->attr.event_comp)
13720      && !sym->attr.codimension && !sym->ts.u.derived->attr.coarray_comp)
13721    {
13722      gfc_error ("Variable %s at %L of type EVENT_TYPE or with subcomponent of "
13723		 "type LOCK_TYPE must be a coarray", sym->name,
13724		 &sym->declared_at);
13725      return;
13726    }
13727
13728  /* An assumed-size array with INTENT(OUT) shall not be of a type for which
13729     default initialization is defined (5.1.2.4.4).  */
13730  if (sym->ts.type == BT_DERIVED
13731      && sym->attr.dummy
13732      && sym->attr.intent == INTENT_OUT
13733      && sym->as
13734      && sym->as->type == AS_ASSUMED_SIZE)
13735    {
13736      for (c = sym->ts.u.derived->components; c; c = c->next)
13737	{
13738	  if (c->initializer)
13739	    {
13740	      gfc_error ("The INTENT(OUT) dummy argument %qs at %L is "
13741			 "ASSUMED SIZE and so cannot have a default initializer",
13742			 sym->name, &sym->declared_at);
13743	      return;
13744	    }
13745	}
13746    }
13747
13748  /* F2008, C542.  */
13749  if (sym->ts.type == BT_DERIVED && sym->attr.dummy
13750      && sym->attr.intent == INTENT_OUT && sym->attr.lock_comp)
13751    {
13752      gfc_error ("Dummy argument %qs at %L of LOCK_TYPE shall not be "
13753		 "INTENT(OUT)", sym->name, &sym->declared_at);
13754      return;
13755    }
13756
13757  /* TS18508.  */
13758  if (sym->ts.type == BT_DERIVED && sym->attr.dummy
13759      && sym->attr.intent == INTENT_OUT && sym->attr.event_comp)
13760    {
13761      gfc_error ("Dummy argument %qs at %L of EVENT_TYPE shall not be "
13762		 "INTENT(OUT)", sym->name, &sym->declared_at);
13763      return;
13764    }
13765
13766  /* F2008, C525.  */
13767  if ((((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
13768	 || (sym->ts.type == BT_CLASS && sym->attr.class_ok
13769	     && CLASS_DATA (sym)->attr.coarray_comp))
13770       || class_attr.codimension)
13771      && (sym->attr.result || sym->result == sym))
13772    {
13773      gfc_error ("Function result %qs at %L shall not be a coarray or have "
13774	         "a coarray component", sym->name, &sym->declared_at);
13775      return;
13776    }
13777
13778  /* F2008, C524.  */
13779  if (sym->attr.codimension && sym->ts.type == BT_DERIVED
13780      && sym->ts.u.derived->ts.is_iso_c)
13781    {
13782      gfc_error ("Variable %qs at %L of TYPE(C_PTR) or TYPE(C_FUNPTR) "
13783		 "shall not be a coarray", sym->name, &sym->declared_at);
13784      return;
13785    }
13786
13787  /* F2008, C525.  */
13788  if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
13789	|| (sym->ts.type == BT_CLASS && sym->attr.class_ok
13790	    && CLASS_DATA (sym)->attr.coarray_comp))
13791      && (class_attr.codimension || class_attr.pointer || class_attr.dimension
13792	  || class_attr.allocatable))
13793    {
13794      gfc_error ("Variable %qs at %L with coarray component shall be a "
13795		 "nonpointer, nonallocatable scalar, which is not a coarray",
13796		 sym->name, &sym->declared_at);
13797      return;
13798    }
13799
13800  /* F2008, C526.  The function-result case was handled above.  */
13801  if (class_attr.codimension
13802      && !(class_attr.allocatable || sym->attr.dummy || sym->attr.save
13803	   || sym->attr.select_type_temporary
13804	   || sym->ns->save_all
13805	   || sym->ns->proc_name->attr.flavor == FL_MODULE
13806	   || sym->ns->proc_name->attr.is_main_program
13807	   || sym->attr.function || sym->attr.result || sym->attr.use_assoc))
13808    {
13809      gfc_error ("Variable %qs at %L is a coarray and is not ALLOCATABLE, SAVE "
13810		 "nor a dummy argument", sym->name, &sym->declared_at);
13811      return;
13812    }
13813  /* F2008, C528.  */
13814  else if (class_attr.codimension && !sym->attr.select_type_temporary
13815	   && !class_attr.allocatable && as && as->cotype == AS_DEFERRED)
13816    {
13817      gfc_error ("Coarray variable %qs at %L shall not have codimensions with "
13818		 "deferred shape", sym->name, &sym->declared_at);
13819      return;
13820    }
13821  else if (class_attr.codimension && class_attr.allocatable && as
13822	   && (as->cotype != AS_DEFERRED || as->type != AS_DEFERRED))
13823    {
13824      gfc_error ("Allocatable coarray variable %qs at %L must have "
13825		 "deferred shape", sym->name, &sym->declared_at);
13826      return;
13827    }
13828
13829  /* F2008, C541.  */
13830  if ((((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
13831	|| (sym->ts.type == BT_CLASS && sym->attr.class_ok
13832	    && CLASS_DATA (sym)->attr.coarray_comp))
13833       || (class_attr.codimension && class_attr.allocatable))
13834      && sym->attr.dummy && sym->attr.intent == INTENT_OUT)
13835    {
13836      gfc_error ("Variable %qs at %L is INTENT(OUT) and can thus not be an "
13837		 "allocatable coarray or have coarray components",
13838		 sym->name, &sym->declared_at);
13839      return;
13840    }
13841
13842  if (class_attr.codimension && sym->attr.dummy
13843      && sym->ns->proc_name && sym->ns->proc_name->attr.is_bind_c)
13844    {
13845      gfc_error ("Coarray dummy variable %qs at %L not allowed in BIND(C) "
13846		 "procedure %qs", sym->name, &sym->declared_at,
13847		 sym->ns->proc_name->name);
13848      return;
13849    }
13850
13851  if (sym->ts.type == BT_LOGICAL
13852      && ((sym->attr.function && sym->attr.is_bind_c && sym->result == sym)
13853	  || ((sym->attr.dummy || sym->attr.result) && sym->ns->proc_name
13854	      && sym->ns->proc_name->attr.is_bind_c)))
13855    {
13856      int i;
13857      for (i = 0; gfc_logical_kinds[i].kind; i++)
13858        if (gfc_logical_kinds[i].kind == sym->ts.kind)
13859          break;
13860      if (!gfc_logical_kinds[i].c_bool && sym->attr.dummy
13861	  && !gfc_notify_std (GFC_STD_GNU, "LOGICAL dummy argument %qs at "
13862			      "%L with non-C_Bool kind in BIND(C) procedure "
13863			      "%qs", sym->name, &sym->declared_at,
13864			      sym->ns->proc_name->name))
13865	return;
13866      else if (!gfc_logical_kinds[i].c_bool
13867	       && !gfc_notify_std (GFC_STD_GNU, "LOGICAL result variable "
13868				   "%qs at %L with non-C_Bool kind in "
13869				   "BIND(C) procedure %qs", sym->name,
13870				   &sym->declared_at,
13871				   sym->attr.function ? sym->name
13872				   : sym->ns->proc_name->name))
13873	return;
13874    }
13875
13876  switch (sym->attr.flavor)
13877    {
13878    case FL_VARIABLE:
13879      if (!resolve_fl_variable (sym, mp_flag))
13880	return;
13881      break;
13882
13883    case FL_PROCEDURE:
13884      if (!resolve_fl_procedure (sym, mp_flag))
13885	return;
13886      break;
13887
13888    case FL_NAMELIST:
13889      if (!resolve_fl_namelist (sym))
13890	return;
13891      break;
13892
13893    case FL_PARAMETER:
13894      if (!resolve_fl_parameter (sym))
13895	return;
13896      break;
13897
13898    default:
13899      break;
13900    }
13901
13902  /* Resolve array specifier. Check as well some constraints
13903     on COMMON blocks.  */
13904
13905  check_constant = sym->attr.in_common && !sym->attr.pointer;
13906
13907  /* Set the formal_arg_flag so that check_conflict will not throw
13908     an error for host associated variables in the specification
13909     expression for an array_valued function.  */
13910  if (sym->attr.function && sym->as)
13911    formal_arg_flag = 1;
13912
13913  saved_specification_expr = specification_expr;
13914  specification_expr = true;
13915  gfc_resolve_array_spec (sym->as, check_constant);
13916  specification_expr = saved_specification_expr;
13917
13918  formal_arg_flag = 0;
13919
13920  /* Resolve formal namespaces.  */
13921  if (sym->formal_ns && sym->formal_ns != gfc_current_ns
13922      && !sym->attr.contained && !sym->attr.intrinsic)
13923    gfc_resolve (sym->formal_ns);
13924
13925  /* Make sure the formal namespace is present.  */
13926  if (sym->formal && !sym->formal_ns)
13927    {
13928      gfc_formal_arglist *formal = sym->formal;
13929      while (formal && !formal->sym)
13930	formal = formal->next;
13931
13932      if (formal)
13933	{
13934	  sym->formal_ns = formal->sym->ns;
13935          if (sym->ns != formal->sym->ns)
13936	    sym->formal_ns->refs++;
13937	}
13938    }
13939
13940  /* Check threadprivate restrictions.  */
13941  if (sym->attr.threadprivate && !sym->attr.save && !sym->ns->save_all
13942      && (!sym->attr.in_common
13943	  && sym->module == NULL
13944	  && (sym->ns->proc_name == NULL
13945	      || sym->ns->proc_name->attr.flavor != FL_MODULE)))
13946    gfc_error ("Threadprivate at %L isn't SAVEd", &sym->declared_at);
13947
13948  /* Check omp declare target restrictions.  */
13949  if (sym->attr.omp_declare_target
13950      && sym->attr.flavor == FL_VARIABLE
13951      && !sym->attr.save
13952      && !sym->ns->save_all
13953      && (!sym->attr.in_common
13954	  && sym->module == NULL
13955	  && (sym->ns->proc_name == NULL
13956	      || sym->ns->proc_name->attr.flavor != FL_MODULE)))
13957    gfc_error ("!$OMP DECLARE TARGET variable %qs at %L isn't SAVEd",
13958	       sym->name, &sym->declared_at);
13959
13960  /* If we have come this far we can apply default-initializers, as
13961     described in 14.7.5, to those variables that have not already
13962     been assigned one.  */
13963  if (sym->ts.type == BT_DERIVED
13964      && !sym->value
13965      && !sym->attr.allocatable
13966      && !sym->attr.alloc_comp)
13967    {
13968      symbol_attribute *a = &sym->attr;
13969
13970      if ((!a->save && !a->dummy && !a->pointer
13971	   && !a->in_common && !a->use_assoc
13972	   && (a->referenced || a->result)
13973	   && !(a->function && sym != sym->result))
13974	  || (a->dummy && a->intent == INTENT_OUT && !a->pointer))
13975	apply_default_init (sym);
13976    }
13977
13978  if (sym->ts.type == BT_CLASS && sym->ns == gfc_current_ns
13979      && sym->attr.dummy && sym->attr.intent == INTENT_OUT
13980      && !CLASS_DATA (sym)->attr.class_pointer
13981      && !CLASS_DATA (sym)->attr.allocatable)
13982    apply_default_init (sym);
13983
13984  /* If this symbol has a type-spec, check it.  */
13985  if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER
13986      || (sym->attr.flavor == FL_PROCEDURE && sym->attr.function))
13987    if (!resolve_typespec_used (&sym->ts, &sym->declared_at, sym->name))
13988      return;
13989}
13990
13991
13992/************* Resolve DATA statements *************/
13993
13994static struct
13995{
13996  gfc_data_value *vnode;
13997  mpz_t left;
13998}
13999values;
14000
14001
14002/* Advance the values structure to point to the next value in the data list.  */
14003
14004static bool
14005next_data_value (void)
14006{
14007  while (mpz_cmp_ui (values.left, 0) == 0)
14008    {
14009
14010      if (values.vnode->next == NULL)
14011	return false;
14012
14013      values.vnode = values.vnode->next;
14014      mpz_set (values.left, values.vnode->repeat);
14015    }
14016
14017  return true;
14018}
14019
14020
14021static bool
14022check_data_variable (gfc_data_variable *var, locus *where)
14023{
14024  gfc_expr *e;
14025  mpz_t size;
14026  mpz_t offset;
14027  bool t;
14028  ar_type mark = AR_UNKNOWN;
14029  int i;
14030  mpz_t section_index[GFC_MAX_DIMENSIONS];
14031  gfc_ref *ref;
14032  gfc_array_ref *ar;
14033  gfc_symbol *sym;
14034  int has_pointer;
14035
14036  if (!gfc_resolve_expr (var->expr))
14037    return false;
14038
14039  ar = NULL;
14040  mpz_init_set_si (offset, 0);
14041  e = var->expr;
14042
14043  if (e->expr_type != EXPR_VARIABLE)
14044    gfc_internal_error ("check_data_variable(): Bad expression");
14045
14046  sym = e->symtree->n.sym;
14047
14048  if (sym->ns->is_block_data && !sym->attr.in_common)
14049    {
14050      gfc_error ("BLOCK DATA element %qs at %L must be in COMMON",
14051		 sym->name, &sym->declared_at);
14052    }
14053
14054  if (e->ref == NULL && sym->as)
14055    {
14056      gfc_error ("DATA array %qs at %L must be specified in a previous"
14057		 " declaration", sym->name, where);
14058      return false;
14059    }
14060
14061  has_pointer = sym->attr.pointer;
14062
14063  if (gfc_is_coindexed (e))
14064    {
14065      gfc_error ("DATA element %qs at %L cannot have a coindex", sym->name,
14066		 where);
14067      return false;
14068    }
14069
14070  for (ref = e->ref; ref; ref = ref->next)
14071    {
14072      if (ref->type == REF_COMPONENT && ref->u.c.component->attr.pointer)
14073	has_pointer = 1;
14074
14075      if (has_pointer
14076	    && ref->type == REF_ARRAY
14077	    && ref->u.ar.type != AR_FULL)
14078	  {
14079	    gfc_error ("DATA element %qs at %L is a pointer and so must "
14080			"be a full array", sym->name, where);
14081	    return false;
14082	  }
14083    }
14084
14085  if (e->rank == 0 || has_pointer)
14086    {
14087      mpz_init_set_ui (size, 1);
14088      ref = NULL;
14089    }
14090  else
14091    {
14092      ref = e->ref;
14093
14094      /* Find the array section reference.  */
14095      for (ref = e->ref; ref; ref = ref->next)
14096	{
14097	  if (ref->type != REF_ARRAY)
14098	    continue;
14099	  if (ref->u.ar.type == AR_ELEMENT)
14100	    continue;
14101	  break;
14102	}
14103      gcc_assert (ref);
14104
14105      /* Set marks according to the reference pattern.  */
14106      switch (ref->u.ar.type)
14107	{
14108	case AR_FULL:
14109	  mark = AR_FULL;
14110	  break;
14111
14112	case AR_SECTION:
14113	  ar = &ref->u.ar;
14114	  /* Get the start position of array section.  */
14115	  gfc_get_section_index (ar, section_index, &offset);
14116	  mark = AR_SECTION;
14117	  break;
14118
14119	default:
14120	  gcc_unreachable ();
14121	}
14122
14123      if (!gfc_array_size (e, &size))
14124	{
14125	  gfc_error ("Nonconstant array section at %L in DATA statement",
14126		     &e->where);
14127	  mpz_clear (offset);
14128	  return false;
14129	}
14130    }
14131
14132  t = true;
14133
14134  while (mpz_cmp_ui (size, 0) > 0)
14135    {
14136      if (!next_data_value ())
14137	{
14138	  gfc_error ("DATA statement at %L has more variables than values",
14139		     where);
14140	  t = false;
14141	  break;
14142	}
14143
14144      t = gfc_check_assign (var->expr, values.vnode->expr, 0);
14145      if (!t)
14146	break;
14147
14148      /* If we have more than one element left in the repeat count,
14149	 and we have more than one element left in the target variable,
14150	 then create a range assignment.  */
14151      /* FIXME: Only done for full arrays for now, since array sections
14152	 seem tricky.  */
14153      if (mark == AR_FULL && ref && ref->next == NULL
14154	  && mpz_cmp_ui (values.left, 1) > 0 && mpz_cmp_ui (size, 1) > 0)
14155	{
14156	  mpz_t range;
14157
14158	  if (mpz_cmp (size, values.left) >= 0)
14159	    {
14160	      mpz_init_set (range, values.left);
14161	      mpz_sub (size, size, values.left);
14162	      mpz_set_ui (values.left, 0);
14163	    }
14164	  else
14165	    {
14166	      mpz_init_set (range, size);
14167	      mpz_sub (values.left, values.left, size);
14168	      mpz_set_ui (size, 0);
14169	    }
14170
14171	  t = gfc_assign_data_value (var->expr, values.vnode->expr,
14172				     offset, &range);
14173
14174	  mpz_add (offset, offset, range);
14175	  mpz_clear (range);
14176
14177	  if (!t)
14178	    break;
14179	}
14180
14181      /* Assign initial value to symbol.  */
14182      else
14183	{
14184	  mpz_sub_ui (values.left, values.left, 1);
14185	  mpz_sub_ui (size, size, 1);
14186
14187	  t = gfc_assign_data_value (var->expr, values.vnode->expr,
14188				     offset, NULL);
14189	  if (!t)
14190	    break;
14191
14192	  if (mark == AR_FULL)
14193	    mpz_add_ui (offset, offset, 1);
14194
14195	  /* Modify the array section indexes and recalculate the offset
14196	     for next element.  */
14197	  else if (mark == AR_SECTION)
14198	    gfc_advance_section (section_index, ar, &offset);
14199	}
14200    }
14201
14202  if (mark == AR_SECTION)
14203    {
14204      for (i = 0; i < ar->dimen; i++)
14205	mpz_clear (section_index[i]);
14206    }
14207
14208  mpz_clear (size);
14209  mpz_clear (offset);
14210
14211  return t;
14212}
14213
14214
14215static bool traverse_data_var (gfc_data_variable *, locus *);
14216
14217/* Iterate over a list of elements in a DATA statement.  */
14218
14219static bool
14220traverse_data_list (gfc_data_variable *var, locus *where)
14221{
14222  mpz_t trip;
14223  iterator_stack frame;
14224  gfc_expr *e, *start, *end, *step;
14225  bool retval = true;
14226
14227  mpz_init (frame.value);
14228  mpz_init (trip);
14229
14230  start = gfc_copy_expr (var->iter.start);
14231  end = gfc_copy_expr (var->iter.end);
14232  step = gfc_copy_expr (var->iter.step);
14233
14234  if (!gfc_simplify_expr (start, 1)
14235      || start->expr_type != EXPR_CONSTANT)
14236    {
14237      gfc_error ("start of implied-do loop at %L could not be "
14238		 "simplified to a constant value", &start->where);
14239      retval = false;
14240      goto cleanup;
14241    }
14242  if (!gfc_simplify_expr (end, 1)
14243      || end->expr_type != EXPR_CONSTANT)
14244    {
14245      gfc_error ("end of implied-do loop at %L could not be "
14246		 "simplified to a constant value", &start->where);
14247      retval = false;
14248      goto cleanup;
14249    }
14250  if (!gfc_simplify_expr (step, 1)
14251      || step->expr_type != EXPR_CONSTANT)
14252    {
14253      gfc_error ("step of implied-do loop at %L could not be "
14254		 "simplified to a constant value", &start->where);
14255      retval = false;
14256      goto cleanup;
14257    }
14258
14259  mpz_set (trip, end->value.integer);
14260  mpz_sub (trip, trip, start->value.integer);
14261  mpz_add (trip, trip, step->value.integer);
14262
14263  mpz_div (trip, trip, step->value.integer);
14264
14265  mpz_set (frame.value, start->value.integer);
14266
14267  frame.prev = iter_stack;
14268  frame.variable = var->iter.var->symtree;
14269  iter_stack = &frame;
14270
14271  while (mpz_cmp_ui (trip, 0) > 0)
14272    {
14273      if (!traverse_data_var (var->list, where))
14274	{
14275	  retval = false;
14276	  goto cleanup;
14277	}
14278
14279      e = gfc_copy_expr (var->expr);
14280      if (!gfc_simplify_expr (e, 1))
14281	{
14282	  gfc_free_expr (e);
14283	  retval = false;
14284	  goto cleanup;
14285	}
14286
14287      mpz_add (frame.value, frame.value, step->value.integer);
14288
14289      mpz_sub_ui (trip, trip, 1);
14290    }
14291
14292cleanup:
14293  mpz_clear (frame.value);
14294  mpz_clear (trip);
14295
14296  gfc_free_expr (start);
14297  gfc_free_expr (end);
14298  gfc_free_expr (step);
14299
14300  iter_stack = frame.prev;
14301  return retval;
14302}
14303
14304
14305/* Type resolve variables in the variable list of a DATA statement.  */
14306
14307static bool
14308traverse_data_var (gfc_data_variable *var, locus *where)
14309{
14310  bool t;
14311
14312  for (; var; var = var->next)
14313    {
14314      if (var->expr == NULL)
14315	t = traverse_data_list (var, where);
14316      else
14317	t = check_data_variable (var, where);
14318
14319      if (!t)
14320	return false;
14321    }
14322
14323  return true;
14324}
14325
14326
14327/* Resolve the expressions and iterators associated with a data statement.
14328   This is separate from the assignment checking because data lists should
14329   only be resolved once.  */
14330
14331static bool
14332resolve_data_variables (gfc_data_variable *d)
14333{
14334  for (; d; d = d->next)
14335    {
14336      if (d->list == NULL)
14337	{
14338	  if (!gfc_resolve_expr (d->expr))
14339	    return false;
14340	}
14341      else
14342	{
14343	  if (!gfc_resolve_iterator (&d->iter, false, true))
14344	    return false;
14345
14346	  if (!resolve_data_variables (d->list))
14347	    return false;
14348	}
14349    }
14350
14351  return true;
14352}
14353
14354
14355/* Resolve a single DATA statement.  We implement this by storing a pointer to
14356   the value list into static variables, and then recursively traversing the
14357   variables list, expanding iterators and such.  */
14358
14359static void
14360resolve_data (gfc_data *d)
14361{
14362
14363  if (!resolve_data_variables (d->var))
14364    return;
14365
14366  values.vnode = d->value;
14367  if (d->value == NULL)
14368    mpz_set_ui (values.left, 0);
14369  else
14370    mpz_set (values.left, d->value->repeat);
14371
14372  if (!traverse_data_var (d->var, &d->where))
14373    return;
14374
14375  /* At this point, we better not have any values left.  */
14376
14377  if (next_data_value ())
14378    gfc_error ("DATA statement at %L has more values than variables",
14379	       &d->where);
14380}
14381
14382
14383/* 12.6 Constraint: In a pure subprogram any variable which is in common or
14384   accessed by host or use association, is a dummy argument to a pure function,
14385   is a dummy argument with INTENT (IN) to a pure subroutine, or an object that
14386   is storage associated with any such variable, shall not be used in the
14387   following contexts: (clients of this function).  */
14388
14389/* Determines if a variable is not 'pure', i.e., not assignable within a pure
14390   procedure.  Returns zero if assignment is OK, nonzero if there is a
14391   problem.  */
14392int
14393gfc_impure_variable (gfc_symbol *sym)
14394{
14395  gfc_symbol *proc;
14396  gfc_namespace *ns;
14397
14398  if (sym->attr.use_assoc || sym->attr.in_common)
14399    return 1;
14400
14401  /* Check if the symbol's ns is inside the pure procedure.  */
14402  for (ns = gfc_current_ns; ns; ns = ns->parent)
14403    {
14404      if (ns == sym->ns)
14405	break;
14406      if (ns->proc_name->attr.flavor == FL_PROCEDURE && !sym->attr.function)
14407	return 1;
14408    }
14409
14410  proc = sym->ns->proc_name;
14411  if (sym->attr.dummy
14412      && ((proc->attr.subroutine && sym->attr.intent == INTENT_IN)
14413	  || proc->attr.function))
14414    return 1;
14415
14416  /* TODO: Sort out what can be storage associated, if anything, and include
14417     it here.  In principle equivalences should be scanned but it does not
14418     seem to be possible to storage associate an impure variable this way.  */
14419  return 0;
14420}
14421
14422
14423/* Test whether a symbol is pure or not.  For a NULL pointer, checks if the
14424   current namespace is inside a pure procedure.  */
14425
14426int
14427gfc_pure (gfc_symbol *sym)
14428{
14429  symbol_attribute attr;
14430  gfc_namespace *ns;
14431
14432  if (sym == NULL)
14433    {
14434      /* Check if the current namespace or one of its parents
14435	belongs to a pure procedure.  */
14436      for (ns = gfc_current_ns; ns; ns = ns->parent)
14437	{
14438	  sym = ns->proc_name;
14439	  if (sym == NULL)
14440	    return 0;
14441	  attr = sym->attr;
14442	  if (attr.flavor == FL_PROCEDURE && attr.pure)
14443	    return 1;
14444	}
14445      return 0;
14446    }
14447
14448  attr = sym->attr;
14449
14450  return attr.flavor == FL_PROCEDURE && attr.pure;
14451}
14452
14453
14454/* Test whether a symbol is implicitly pure or not.  For a NULL pointer,
14455   checks if the current namespace is implicitly pure.  Note that this
14456   function returns false for a PURE procedure.  */
14457
14458int
14459gfc_implicit_pure (gfc_symbol *sym)
14460{
14461  gfc_namespace *ns;
14462
14463  if (sym == NULL)
14464    {
14465      /* Check if the current procedure is implicit_pure.  Walk up
14466	 the procedure list until we find a procedure.  */
14467      for (ns = gfc_current_ns; ns; ns = ns->parent)
14468	{
14469	  sym = ns->proc_name;
14470	  if (sym == NULL)
14471	    return 0;
14472
14473	  if (sym->attr.flavor == FL_PROCEDURE)
14474	    break;
14475	}
14476    }
14477
14478  return sym->attr.flavor == FL_PROCEDURE && sym->attr.implicit_pure
14479    && !sym->attr.pure;
14480}
14481
14482
14483void
14484gfc_unset_implicit_pure (gfc_symbol *sym)
14485{
14486  gfc_namespace *ns;
14487
14488  if (sym == NULL)
14489    {
14490      /* Check if the current procedure is implicit_pure.  Walk up
14491	 the procedure list until we find a procedure.  */
14492      for (ns = gfc_current_ns; ns; ns = ns->parent)
14493	{
14494	  sym = ns->proc_name;
14495	  if (sym == NULL)
14496	    return;
14497
14498	  if (sym->attr.flavor == FL_PROCEDURE)
14499	    break;
14500	}
14501    }
14502
14503  if (sym->attr.flavor == FL_PROCEDURE)
14504    sym->attr.implicit_pure = 0;
14505  else
14506    sym->attr.pure = 0;
14507}
14508
14509
14510/* Test whether the current procedure is elemental or not.  */
14511
14512int
14513gfc_elemental (gfc_symbol *sym)
14514{
14515  symbol_attribute attr;
14516
14517  if (sym == NULL)
14518    sym = gfc_current_ns->proc_name;
14519  if (sym == NULL)
14520    return 0;
14521  attr = sym->attr;
14522
14523  return attr.flavor == FL_PROCEDURE && attr.elemental;
14524}
14525
14526
14527/* Warn about unused labels.  */
14528
14529static void
14530warn_unused_fortran_label (gfc_st_label *label)
14531{
14532  if (label == NULL)
14533    return;
14534
14535  warn_unused_fortran_label (label->left);
14536
14537  if (label->defined == ST_LABEL_UNKNOWN)
14538    return;
14539
14540  switch (label->referenced)
14541    {
14542    case ST_LABEL_UNKNOWN:
14543      gfc_warning (0, "Label %d at %L defined but not used", label->value,
14544		   &label->where);
14545      break;
14546
14547    case ST_LABEL_BAD_TARGET:
14548      gfc_warning (0, "Label %d at %L defined but cannot be used",
14549		   label->value, &label->where);
14550      break;
14551
14552    default:
14553      break;
14554    }
14555
14556  warn_unused_fortran_label (label->right);
14557}
14558
14559
14560/* Returns the sequence type of a symbol or sequence.  */
14561
14562static seq_type
14563sequence_type (gfc_typespec ts)
14564{
14565  seq_type result;
14566  gfc_component *c;
14567
14568  switch (ts.type)
14569  {
14570    case BT_DERIVED:
14571
14572      if (ts.u.derived->components == NULL)
14573	return SEQ_NONDEFAULT;
14574
14575      result = sequence_type (ts.u.derived->components->ts);
14576      for (c = ts.u.derived->components->next; c; c = c->next)
14577	if (sequence_type (c->ts) != result)
14578	  return SEQ_MIXED;
14579
14580      return result;
14581
14582    case BT_CHARACTER:
14583      if (ts.kind != gfc_default_character_kind)
14584	  return SEQ_NONDEFAULT;
14585
14586      return SEQ_CHARACTER;
14587
14588    case BT_INTEGER:
14589      if (ts.kind != gfc_default_integer_kind)
14590	  return SEQ_NONDEFAULT;
14591
14592      return SEQ_NUMERIC;
14593
14594    case BT_REAL:
14595      if (!(ts.kind == gfc_default_real_kind
14596	    || ts.kind == gfc_default_double_kind))
14597	  return SEQ_NONDEFAULT;
14598
14599      return SEQ_NUMERIC;
14600
14601    case BT_COMPLEX:
14602      if (ts.kind != gfc_default_complex_kind)
14603	  return SEQ_NONDEFAULT;
14604
14605      return SEQ_NUMERIC;
14606
14607    case BT_LOGICAL:
14608      if (ts.kind != gfc_default_logical_kind)
14609	  return SEQ_NONDEFAULT;
14610
14611      return SEQ_NUMERIC;
14612
14613    default:
14614      return SEQ_NONDEFAULT;
14615  }
14616}
14617
14618
14619/* Resolve derived type EQUIVALENCE object.  */
14620
14621static bool
14622resolve_equivalence_derived (gfc_symbol *derived, gfc_symbol *sym, gfc_expr *e)
14623{
14624  gfc_component *c = derived->components;
14625
14626  if (!derived)
14627    return true;
14628
14629  /* Shall not be an object of nonsequence derived type.  */
14630  if (!derived->attr.sequence)
14631    {
14632      gfc_error ("Derived type variable %qs at %L must have SEQUENCE "
14633		 "attribute to be an EQUIVALENCE object", sym->name,
14634		 &e->where);
14635      return false;
14636    }
14637
14638  /* Shall not have allocatable components.  */
14639  if (derived->attr.alloc_comp)
14640    {
14641      gfc_error ("Derived type variable %qs at %L cannot have ALLOCATABLE "
14642		 "components to be an EQUIVALENCE object",sym->name,
14643		 &e->where);
14644      return false;
14645    }
14646
14647  if (sym->attr.in_common && gfc_has_default_initializer (sym->ts.u.derived))
14648    {
14649      gfc_error ("Derived type variable %qs at %L with default "
14650		 "initialization cannot be in EQUIVALENCE with a variable "
14651		 "in COMMON", sym->name, &e->where);
14652      return false;
14653    }
14654
14655  for (; c ; c = c->next)
14656    {
14657      if (c->ts.type == BT_DERIVED
14658	  && (!resolve_equivalence_derived(c->ts.u.derived, sym, e)))
14659	return false;
14660
14661      /* Shall not be an object of sequence derived type containing a pointer
14662	 in the structure.  */
14663      if (c->attr.pointer)
14664	{
14665	  gfc_error ("Derived type variable %qs at %L with pointer "
14666		     "component(s) cannot be an EQUIVALENCE object",
14667		     sym->name, &e->where);
14668	  return false;
14669	}
14670    }
14671  return true;
14672}
14673
14674
14675/* Resolve equivalence object.
14676   An EQUIVALENCE object shall not be a dummy argument, a pointer, a target,
14677   an allocatable array, an object of nonsequence derived type, an object of
14678   sequence derived type containing a pointer at any level of component
14679   selection, an automatic object, a function name, an entry name, a result
14680   name, a named constant, a structure component, or a subobject of any of
14681   the preceding objects.  A substring shall not have length zero.  A
14682   derived type shall not have components with default initialization nor
14683   shall two objects of an equivalence group be initialized.
14684   Either all or none of the objects shall have an protected attribute.
14685   The simple constraints are done in symbol.c(check_conflict) and the rest
14686   are implemented here.  */
14687
14688static void
14689resolve_equivalence (gfc_equiv *eq)
14690{
14691  gfc_symbol *sym;
14692  gfc_symbol *first_sym;
14693  gfc_expr *e;
14694  gfc_ref *r;
14695  locus *last_where = NULL;
14696  seq_type eq_type, last_eq_type;
14697  gfc_typespec *last_ts;
14698  int object, cnt_protected;
14699  const char *msg;
14700
14701  last_ts = &eq->expr->symtree->n.sym->ts;
14702
14703  first_sym = eq->expr->symtree->n.sym;
14704
14705  cnt_protected = 0;
14706
14707  for (object = 1; eq; eq = eq->eq, object++)
14708    {
14709      e = eq->expr;
14710
14711      e->ts = e->symtree->n.sym->ts;
14712      /* match_varspec might not know yet if it is seeing
14713	 array reference or substring reference, as it doesn't
14714	 know the types.  */
14715      if (e->ref && e->ref->type == REF_ARRAY)
14716	{
14717	  gfc_ref *ref = e->ref;
14718	  sym = e->symtree->n.sym;
14719
14720	  if (sym->attr.dimension)
14721	    {
14722	      ref->u.ar.as = sym->as;
14723	      ref = ref->next;
14724	    }
14725
14726	  /* For substrings, convert REF_ARRAY into REF_SUBSTRING.  */
14727	  if (e->ts.type == BT_CHARACTER
14728	      && ref
14729	      && ref->type == REF_ARRAY
14730	      && ref->u.ar.dimen == 1
14731	      && ref->u.ar.dimen_type[0] == DIMEN_RANGE
14732	      && ref->u.ar.stride[0] == NULL)
14733	    {
14734	      gfc_expr *start = ref->u.ar.start[0];
14735	      gfc_expr *end = ref->u.ar.end[0];
14736	      void *mem = NULL;
14737
14738	      /* Optimize away the (:) reference.  */
14739	      if (start == NULL && end == NULL)
14740		{
14741		  if (e->ref == ref)
14742		    e->ref = ref->next;
14743		  else
14744		    e->ref->next = ref->next;
14745		  mem = ref;
14746		}
14747	      else
14748		{
14749		  ref->type = REF_SUBSTRING;
14750		  if (start == NULL)
14751		    start = gfc_get_int_expr (gfc_default_integer_kind,
14752					      NULL, 1);
14753		  ref->u.ss.start = start;
14754		  if (end == NULL && e->ts.u.cl)
14755		    end = gfc_copy_expr (e->ts.u.cl->length);
14756		  ref->u.ss.end = end;
14757		  ref->u.ss.length = e->ts.u.cl;
14758		  e->ts.u.cl = NULL;
14759		}
14760	      ref = ref->next;
14761	      free (mem);
14762	    }
14763
14764	  /* Any further ref is an error.  */
14765	  if (ref)
14766	    {
14767	      gcc_assert (ref->type == REF_ARRAY);
14768	      gfc_error ("Syntax error in EQUIVALENCE statement at %L",
14769			 &ref->u.ar.where);
14770	      continue;
14771	    }
14772	}
14773
14774      if (!gfc_resolve_expr (e))
14775	continue;
14776
14777      sym = e->symtree->n.sym;
14778
14779      if (sym->attr.is_protected)
14780	cnt_protected++;
14781      if (cnt_protected > 0 && cnt_protected != object)
14782       	{
14783	      gfc_error ("Either all or none of the objects in the "
14784			 "EQUIVALENCE set at %L shall have the "
14785			 "PROTECTED attribute",
14786			 &e->where);
14787	      break;
14788	}
14789
14790      /* Shall not equivalence common block variables in a PURE procedure.  */
14791      if (sym->ns->proc_name
14792	  && sym->ns->proc_name->attr.pure
14793	  && sym->attr.in_common)
14794	{
14795	  gfc_error ("Common block member %qs at %L cannot be an EQUIVALENCE "
14796		     "object in the pure procedure %qs",
14797		     sym->name, &e->where, sym->ns->proc_name->name);
14798	  break;
14799	}
14800
14801      /* Shall not be a named constant.  */
14802      if (e->expr_type == EXPR_CONSTANT)
14803	{
14804	  gfc_error ("Named constant %qs at %L cannot be an EQUIVALENCE "
14805		     "object", sym->name, &e->where);
14806	  continue;
14807	}
14808
14809      if (e->ts.type == BT_DERIVED
14810	  && !resolve_equivalence_derived (e->ts.u.derived, sym, e))
14811	continue;
14812
14813      /* Check that the types correspond correctly:
14814	 Note 5.28:
14815	 A numeric sequence structure may be equivalenced to another sequence
14816	 structure, an object of default integer type, default real type, double
14817	 precision real type, default logical type such that components of the
14818	 structure ultimately only become associated to objects of the same
14819	 kind. A character sequence structure may be equivalenced to an object
14820	 of default character kind or another character sequence structure.
14821	 Other objects may be equivalenced only to objects of the same type and
14822	 kind parameters.  */
14823
14824      /* Identical types are unconditionally OK.  */
14825      if (object == 1 || gfc_compare_types (last_ts, &sym->ts))
14826	goto identical_types;
14827
14828      last_eq_type = sequence_type (*last_ts);
14829      eq_type = sequence_type (sym->ts);
14830
14831      /* Since the pair of objects is not of the same type, mixed or
14832	 non-default sequences can be rejected.  */
14833
14834      msg = "Sequence %s with mixed components in EQUIVALENCE "
14835	    "statement at %L with different type objects";
14836      if ((object ==2
14837	   && last_eq_type == SEQ_MIXED
14838	   && !gfc_notify_std (GFC_STD_GNU, msg, first_sym->name, last_where))
14839	  || (eq_type == SEQ_MIXED
14840	      && !gfc_notify_std (GFC_STD_GNU, msg, sym->name, &e->where)))
14841	continue;
14842
14843      msg = "Non-default type object or sequence %s in EQUIVALENCE "
14844	    "statement at %L with objects of different type";
14845      if ((object ==2
14846	   && last_eq_type == SEQ_NONDEFAULT
14847	   && !gfc_notify_std (GFC_STD_GNU, msg, first_sym->name, last_where))
14848	  || (eq_type == SEQ_NONDEFAULT
14849	      && !gfc_notify_std (GFC_STD_GNU, msg, sym->name, &e->where)))
14850	continue;
14851
14852      msg ="Non-CHARACTER object %qs in default CHARACTER "
14853	   "EQUIVALENCE statement at %L";
14854      if (last_eq_type == SEQ_CHARACTER
14855	  && eq_type != SEQ_CHARACTER
14856	  && !gfc_notify_std (GFC_STD_GNU, msg, sym->name, &e->where))
14857		continue;
14858
14859      msg ="Non-NUMERIC object %qs in default NUMERIC "
14860	   "EQUIVALENCE statement at %L";
14861      if (last_eq_type == SEQ_NUMERIC
14862	  && eq_type != SEQ_NUMERIC
14863	  && !gfc_notify_std (GFC_STD_GNU, msg, sym->name, &e->where))
14864		continue;
14865
14866  identical_types:
14867      last_ts =&sym->ts;
14868      last_where = &e->where;
14869
14870      if (!e->ref)
14871	continue;
14872
14873      /* Shall not be an automatic array.  */
14874      if (e->ref->type == REF_ARRAY
14875	  && !gfc_resolve_array_spec (e->ref->u.ar.as, 1))
14876	{
14877	  gfc_error ("Array %qs at %L with non-constant bounds cannot be "
14878		     "an EQUIVALENCE object", sym->name, &e->where);
14879	  continue;
14880	}
14881
14882      r = e->ref;
14883      while (r)
14884	{
14885	  /* Shall not be a structure component.  */
14886	  if (r->type == REF_COMPONENT)
14887	    {
14888	      gfc_error ("Structure component %qs at %L cannot be an "
14889			 "EQUIVALENCE object",
14890			 r->u.c.component->name, &e->where);
14891	      break;
14892	    }
14893
14894	  /* A substring shall not have length zero.  */
14895	  if (r->type == REF_SUBSTRING)
14896	    {
14897	      if (compare_bound (r->u.ss.start, r->u.ss.end) == CMP_GT)
14898		{
14899		  gfc_error ("Substring at %L has length zero",
14900			     &r->u.ss.start->where);
14901		  break;
14902		}
14903	    }
14904	  r = r->next;
14905	}
14906    }
14907}
14908
14909
14910/* Resolve function and ENTRY types, issue diagnostics if needed.  */
14911
14912static void
14913resolve_fntype (gfc_namespace *ns)
14914{
14915  gfc_entry_list *el;
14916  gfc_symbol *sym;
14917
14918  if (ns->proc_name == NULL || !ns->proc_name->attr.function)
14919    return;
14920
14921  /* If there are any entries, ns->proc_name is the entry master
14922     synthetic symbol and ns->entries->sym actual FUNCTION symbol.  */
14923  if (ns->entries)
14924    sym = ns->entries->sym;
14925  else
14926    sym = ns->proc_name;
14927  if (sym->result == sym
14928      && sym->ts.type == BT_UNKNOWN
14929      && !gfc_set_default_type (sym, 0, NULL)
14930      && !sym->attr.untyped)
14931    {
14932      gfc_error ("Function %qs at %L has no IMPLICIT type",
14933		 sym->name, &sym->declared_at);
14934      sym->attr.untyped = 1;
14935    }
14936
14937  if (sym->ts.type == BT_DERIVED && !sym->ts.u.derived->attr.use_assoc
14938      && !sym->attr.contained
14939      && !gfc_check_symbol_access (sym->ts.u.derived)
14940      && gfc_check_symbol_access (sym))
14941    {
14942      gfc_notify_std (GFC_STD_F2003, "PUBLIC function %qs at "
14943		      "%L of PRIVATE type %qs", sym->name,
14944		      &sym->declared_at, sym->ts.u.derived->name);
14945    }
14946
14947    if (ns->entries)
14948    for (el = ns->entries->next; el; el = el->next)
14949      {
14950	if (el->sym->result == el->sym
14951	    && el->sym->ts.type == BT_UNKNOWN
14952	    && !gfc_set_default_type (el->sym, 0, NULL)
14953	    && !el->sym->attr.untyped)
14954	  {
14955	    gfc_error ("ENTRY %qs at %L has no IMPLICIT type",
14956		       el->sym->name, &el->sym->declared_at);
14957	    el->sym->attr.untyped = 1;
14958	  }
14959      }
14960}
14961
14962
14963/* 12.3.2.1.1 Defined operators.  */
14964
14965static bool
14966check_uop_procedure (gfc_symbol *sym, locus where)
14967{
14968  gfc_formal_arglist *formal;
14969
14970  if (!sym->attr.function)
14971    {
14972      gfc_error ("User operator procedure %qs at %L must be a FUNCTION",
14973		 sym->name, &where);
14974      return false;
14975    }
14976
14977  if (sym->ts.type == BT_CHARACTER
14978      && !((sym->ts.u.cl && sym->ts.u.cl->length) || sym->ts.deferred)
14979      && !(sym->result && ((sym->result->ts.u.cl
14980	   && sym->result->ts.u.cl->length) || sym->result->ts.deferred)))
14981    {
14982      gfc_error ("User operator procedure %qs at %L cannot be assumed "
14983		 "character length", sym->name, &where);
14984      return false;
14985    }
14986
14987  formal = gfc_sym_get_dummy_args (sym);
14988  if (!formal || !formal->sym)
14989    {
14990      gfc_error ("User operator procedure %qs at %L must have at least "
14991		 "one argument", sym->name, &where);
14992      return false;
14993    }
14994
14995  if (formal->sym->attr.intent != INTENT_IN)
14996    {
14997      gfc_error ("First argument of operator interface at %L must be "
14998		 "INTENT(IN)", &where);
14999      return false;
15000    }
15001
15002  if (formal->sym->attr.optional)
15003    {
15004      gfc_error ("First argument of operator interface at %L cannot be "
15005		 "optional", &where);
15006      return false;
15007    }
15008
15009  formal = formal->next;
15010  if (!formal || !formal->sym)
15011    return true;
15012
15013  if (formal->sym->attr.intent != INTENT_IN)
15014    {
15015      gfc_error ("Second argument of operator interface at %L must be "
15016		 "INTENT(IN)", &where);
15017      return false;
15018    }
15019
15020  if (formal->sym->attr.optional)
15021    {
15022      gfc_error ("Second argument of operator interface at %L cannot be "
15023		 "optional", &where);
15024      return false;
15025    }
15026
15027  if (formal->next)
15028    {
15029      gfc_error ("Operator interface at %L must have, at most, two "
15030		 "arguments", &where);
15031      return false;
15032    }
15033
15034  return true;
15035}
15036
15037static void
15038gfc_resolve_uops (gfc_symtree *symtree)
15039{
15040  gfc_interface *itr;
15041
15042  if (symtree == NULL)
15043    return;
15044
15045  gfc_resolve_uops (symtree->left);
15046  gfc_resolve_uops (symtree->right);
15047
15048  for (itr = symtree->n.uop->op; itr; itr = itr->next)
15049    check_uop_procedure (itr->sym, itr->sym->declared_at);
15050}
15051
15052
15053/* Examine all of the expressions associated with a program unit,
15054   assign types to all intermediate expressions, make sure that all
15055   assignments are to compatible types and figure out which names
15056   refer to which functions or subroutines.  It doesn't check code
15057   block, which is handled by gfc_resolve_code.  */
15058
15059static void
15060resolve_types (gfc_namespace *ns)
15061{
15062  gfc_namespace *n;
15063  gfc_charlen *cl;
15064  gfc_data *d;
15065  gfc_equiv *eq;
15066  gfc_namespace* old_ns = gfc_current_ns;
15067
15068  if (ns->types_resolved)
15069    return;
15070
15071  /* Check that all IMPLICIT types are ok.  */
15072  if (!ns->seen_implicit_none)
15073    {
15074      unsigned letter;
15075      for (letter = 0; letter != GFC_LETTERS; ++letter)
15076	if (ns->set_flag[letter]
15077	    && !resolve_typespec_used (&ns->default_type[letter],
15078				       &ns->implicit_loc[letter], NULL))
15079	  return;
15080    }
15081
15082  gfc_current_ns = ns;
15083
15084  resolve_entries (ns);
15085
15086  resolve_common_vars (ns->blank_common.head, false);
15087  resolve_common_blocks (ns->common_root);
15088
15089  resolve_contained_functions (ns);
15090
15091  if (ns->proc_name && ns->proc_name->attr.flavor == FL_PROCEDURE
15092      && ns->proc_name->attr.if_source == IFSRC_IFBODY)
15093    resolve_formal_arglist (ns->proc_name);
15094
15095  gfc_traverse_ns (ns, resolve_bind_c_derived_types);
15096
15097  for (cl = ns->cl_list; cl; cl = cl->next)
15098    resolve_charlen (cl);
15099
15100  gfc_traverse_ns (ns, resolve_symbol);
15101
15102  resolve_fntype (ns);
15103
15104  for (n = ns->contained; n; n = n->sibling)
15105    {
15106      if (gfc_pure (ns->proc_name) && !gfc_pure (n->proc_name))
15107	gfc_error ("Contained procedure %qs at %L of a PURE procedure must "
15108		   "also be PURE", n->proc_name->name,
15109		   &n->proc_name->declared_at);
15110
15111      resolve_types (n);
15112    }
15113
15114  forall_flag = 0;
15115  gfc_do_concurrent_flag = 0;
15116  gfc_check_interfaces (ns);
15117
15118  gfc_traverse_ns (ns, resolve_values);
15119
15120  if (ns->save_all)
15121    gfc_save_all (ns);
15122
15123  iter_stack = NULL;
15124  for (d = ns->data; d; d = d->next)
15125    resolve_data (d);
15126
15127  iter_stack = NULL;
15128  gfc_traverse_ns (ns, gfc_formalize_init_value);
15129
15130  gfc_traverse_ns (ns, gfc_verify_binding_labels);
15131
15132  for (eq = ns->equiv; eq; eq = eq->next)
15133    resolve_equivalence (eq);
15134
15135  /* Warn about unused labels.  */
15136  if (warn_unused_label)
15137    warn_unused_fortran_label (ns->st_labels);
15138
15139  gfc_resolve_uops (ns->uop_root);
15140
15141  gfc_resolve_omp_declare_simd (ns);
15142
15143  gfc_resolve_omp_udrs (ns->omp_udr_root);
15144
15145  ns->types_resolved = 1;
15146
15147  gfc_current_ns = old_ns;
15148}
15149
15150
15151/* Call gfc_resolve_code recursively.  */
15152
15153static void
15154resolve_codes (gfc_namespace *ns)
15155{
15156  gfc_namespace *n;
15157  bitmap_obstack old_obstack;
15158
15159  if (ns->resolved == 1)
15160    return;
15161
15162  for (n = ns->contained; n; n = n->sibling)
15163    resolve_codes (n);
15164
15165  gfc_current_ns = ns;
15166
15167  /* Don't clear 'cs_base' if this is the namespace of a BLOCK construct.  */
15168  if (!(ns->proc_name && ns->proc_name->attr.flavor == FL_LABEL))
15169    cs_base = NULL;
15170
15171  /* Set to an out of range value.  */
15172  current_entry_id = -1;
15173
15174  old_obstack = labels_obstack;
15175  bitmap_obstack_initialize (&labels_obstack);
15176
15177  gfc_resolve_oacc_declare (ns);
15178  gfc_resolve_code (ns->code, ns);
15179
15180  bitmap_obstack_release (&labels_obstack);
15181  labels_obstack = old_obstack;
15182}
15183
15184
15185/* This function is called after a complete program unit has been compiled.
15186   Its purpose is to examine all of the expressions associated with a program
15187   unit, assign types to all intermediate expressions, make sure that all
15188   assignments are to compatible types and figure out which names refer to
15189   which functions or subroutines.  */
15190
15191void
15192gfc_resolve (gfc_namespace *ns)
15193{
15194  gfc_namespace *old_ns;
15195  code_stack *old_cs_base;
15196  struct gfc_omp_saved_state old_omp_state;
15197
15198  if (ns->resolved)
15199    return;
15200
15201  ns->resolved = -1;
15202  old_ns = gfc_current_ns;
15203  old_cs_base = cs_base;
15204
15205  /* As gfc_resolve can be called during resolution of an OpenMP construct
15206     body, we should clear any state associated to it, so that say NS's
15207     DO loops are not interpreted as OpenMP loops.  */
15208  gfc_omp_save_and_clear_state (&old_omp_state);
15209
15210  resolve_types (ns);
15211  component_assignment_level = 0;
15212  resolve_codes (ns);
15213
15214  gfc_current_ns = old_ns;
15215  cs_base = old_cs_base;
15216  ns->resolved = 1;
15217
15218  gfc_run_passes (ns);
15219
15220  gfc_omp_restore_state (&old_omp_state);
15221}
15222