6a7b6c9d894b41e872851906b88d21d0b459bd7f
[platform/upstream/gcc.git] / gcc / fortran / resolve.c
1 /* Perform type resolution on the various structures.
2    Copyright (C) 2001, 2002, 2003, 2004, 2005, 2006, 2007, 2008, 2009,
3    2010, 2011, 2012
4    Free Software Foundation, Inc.
5    Contributed by Andy Vaught
6
7 This file is part of GCC.
8
9 GCC is free software; you can redistribute it and/or modify it under
10 the terms of the GNU General Public License as published by the Free
11 Software Foundation; either version 3, or (at your option) any later
12 version.
13
14 GCC is distributed in the hope that it will be useful, but WITHOUT ANY
15 WARRANTY; without even the implied warranty of MERCHANTABILITY or
16 FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
17 for more details.
18
19 You should have received a copy of the GNU General Public License
20 along with GCC; see the file COPYING3.  If not see
21 <http://www.gnu.org/licenses/>.  */
22
23 #include "config.h"
24 #include "system.h"
25 #include "coretypes.h"
26 #include "flags.h"
27 #include "gfortran.h"
28 #include "obstack.h"
29 #include "bitmap.h"
30 #include "arith.h"  /* For gfc_compare_expr().  */
31 #include "dependency.h"
32 #include "data.h"
33 #include "target-memory.h" /* for gfc_simplify_transfer */
34 #include "constructor.h"
35
36 /* Types used in equivalence statements.  */
37
38 typedef enum seq_type
39 {
40   SEQ_NONDEFAULT, SEQ_NUMERIC, SEQ_CHARACTER, SEQ_MIXED
41 }
42 seq_type;
43
44 /* Stack to keep track of the nesting of blocks as we move through the
45    code.  See resolve_branch() and resolve_code().  */
46
47 typedef struct code_stack
48 {
49   struct gfc_code *head, *current;
50   struct code_stack *prev;
51
52   /* This bitmap keeps track of the targets valid for a branch from
53      inside this block except for END {IF|SELECT}s of enclosing
54      blocks.  */
55   bitmap reachable_labels;
56 }
57 code_stack;
58
59 static code_stack *cs_base = NULL;
60
61
62 /* Nonzero if we're inside a FORALL or DO CONCURRENT block.  */
63
64 static int forall_flag;
65 static int do_concurrent_flag;
66
67 /* True when we are resolving an expression that is an actual argument to
68    a procedure.  */
69 static bool actual_arg = false;
70 /* True when we are resolving an expression that is the first actual argument
71    to a procedure.  */
72 static bool first_actual_arg = false;
73
74
75 /* Nonzero if we're inside a OpenMP WORKSHARE or PARALLEL WORKSHARE block.  */
76
77 static int omp_workshare_flag;
78
79 /* Nonzero if we are processing a formal arglist. The corresponding function
80    resets the flag each time that it is read.  */
81 static int formal_arg_flag = 0;
82
83 /* True if we are resolving a specification expression.  */
84 static int specification_expr = 0;
85
86 /* The id of the last entry seen.  */
87 static int current_entry_id;
88
89 /* We use bitmaps to determine if a branch target is valid.  */
90 static bitmap_obstack labels_obstack;
91
92 /* True when simplifying a EXPR_VARIABLE argument to an inquiry function.  */
93 static bool inquiry_argument = false;
94
95
96 int
97 gfc_is_formal_arg (void)
98 {
99   return formal_arg_flag;
100 }
101
102 /* Is the symbol host associated?  */
103 static bool
104 is_sym_host_assoc (gfc_symbol *sym, gfc_namespace *ns)
105 {
106   for (ns = ns->parent; ns; ns = ns->parent)
107     {      
108       if (sym->ns == ns)
109         return true;
110     }
111
112   return false;
113 }
114
115 /* Ensure a typespec used is valid; for instance, TYPE(t) is invalid if t is
116    an ABSTRACT derived-type.  If where is not NULL, an error message with that
117    locus is printed, optionally using name.  */
118
119 static gfc_try
120 resolve_typespec_used (gfc_typespec* ts, locus* where, const char* name)
121 {
122   if (ts->type == BT_DERIVED && ts->u.derived->attr.abstract)
123     {
124       if (where)
125         {
126           if (name)
127             gfc_error ("'%s' at %L is of the ABSTRACT type '%s'",
128                        name, where, ts->u.derived->name);
129           else
130             gfc_error ("ABSTRACT type '%s' used at %L",
131                        ts->u.derived->name, where);
132         }
133
134       return FAILURE;
135     }
136
137   return SUCCESS;
138 }
139
140
141 static gfc_try
142 check_proc_interface (gfc_symbol *ifc, locus *where)
143 {
144   /* Several checks for F08:C1216.  */
145   if (ifc->attr.procedure)
146     {
147       gfc_error ("Interface '%s' at %L is declared "
148                  "in a later PROCEDURE statement", ifc->name, where);
149       return FAILURE;
150     }
151   if (ifc->generic)
152     {
153       /* For generic interfaces, check if there is
154          a specific procedure with the same name.  */
155       gfc_interface *gen = ifc->generic;
156       while (gen && strcmp (gen->sym->name, ifc->name) != 0)
157         gen = gen->next;
158       if (!gen)
159         {
160           gfc_error ("Interface '%s' at %L may not be generic",
161                      ifc->name, where);
162           return FAILURE;
163         }
164     }
165   if (ifc->attr.proc == PROC_ST_FUNCTION)
166     {
167       gfc_error ("Interface '%s' at %L may not be a statement function",
168                  ifc->name, where);
169       return FAILURE;
170     }
171   if (gfc_is_intrinsic (ifc, 0, ifc->declared_at)
172       || gfc_is_intrinsic (ifc, 1, ifc->declared_at))
173     ifc->attr.intrinsic = 1;
174   if (ifc->attr.intrinsic && !gfc_intrinsic_actual_ok (ifc->name, 0))
175     {
176       gfc_error ("Intrinsic procedure '%s' not allowed in "
177                  "PROCEDURE statement at %L", ifc->name, where);
178       return FAILURE;
179     }
180   if (!ifc->attr.if_source && !ifc->attr.intrinsic && ifc->name[0] != '\0')
181     {
182       gfc_error ("Interface '%s' at %L must be explicit", ifc->name, where);
183       return FAILURE;
184     }
185   return SUCCESS;
186 }
187
188
189 static void resolve_symbol (gfc_symbol *sym);
190
191
192 /* Resolve the interface for a PROCEDURE declaration or procedure pointer.  */
193
194 static gfc_try
195 resolve_procedure_interface (gfc_symbol *sym)
196 {
197   gfc_symbol *ifc = sym->ts.interface;
198
199   if (!ifc)
200     return SUCCESS;
201
202   if (ifc == sym)
203     {
204       gfc_error ("PROCEDURE '%s' at %L may not be used as its own interface",
205                  sym->name, &sym->declared_at);
206       return FAILURE;
207     }
208   if (check_proc_interface (ifc, &sym->declared_at) == FAILURE)
209     return FAILURE;
210
211   if (ifc->attr.if_source || ifc->attr.intrinsic)
212     {
213       /* Resolve interface and copy attributes.  */
214       resolve_symbol (ifc);
215       if (ifc->attr.intrinsic)
216         gfc_resolve_intrinsic (ifc, &ifc->declared_at);
217
218       if (ifc->result)
219         {
220           sym->ts = ifc->result->ts;
221           sym->result = sym;
222         }
223       else   
224         sym->ts = ifc->ts;
225       sym->ts.interface = ifc;
226       sym->attr.function = ifc->attr.function;
227       sym->attr.subroutine = ifc->attr.subroutine;
228       gfc_copy_formal_args (sym, ifc, IFSRC_DECL);
229
230       sym->attr.allocatable = ifc->attr.allocatable;
231       sym->attr.pointer = ifc->attr.pointer;
232       sym->attr.pure = ifc->attr.pure;
233       sym->attr.elemental = ifc->attr.elemental;
234       sym->attr.dimension = ifc->attr.dimension;
235       sym->attr.contiguous = ifc->attr.contiguous;
236       sym->attr.recursive = ifc->attr.recursive;
237       sym->attr.always_explicit = ifc->attr.always_explicit;
238       sym->attr.ext_attr |= ifc->attr.ext_attr;
239       sym->attr.is_bind_c = ifc->attr.is_bind_c;
240       sym->attr.class_ok = ifc->attr.class_ok;
241       /* Copy array spec.  */
242       sym->as = gfc_copy_array_spec (ifc->as);
243       if (sym->as)
244         {
245           int i;
246           for (i = 0; i < sym->as->rank; i++)
247             {
248               gfc_expr_replace_symbols (sym->as->lower[i], sym);
249               gfc_expr_replace_symbols (sym->as->upper[i], sym);
250             }
251         }
252       /* Copy char length.  */
253       if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
254         {
255           sym->ts.u.cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
256           gfc_expr_replace_symbols (sym->ts.u.cl->length, sym);
257           if (sym->ts.u.cl->length && !sym->ts.u.cl->resolved
258               && gfc_resolve_expr (sym->ts.u.cl->length) == FAILURE)
259             return FAILURE;
260         }
261     }
262
263   return SUCCESS;
264 }
265
266
267 /* Resolve types of formal argument lists.  These have to be done early so that
268    the formal argument lists of module procedures can be copied to the
269    containing module before the individual procedures are resolved
270    individually.  We also resolve argument lists of procedures in interface
271    blocks because they are self-contained scoping units.
272
273    Since a dummy argument cannot be a non-dummy procedure, the only
274    resort left for untyped names are the IMPLICIT types.  */
275
276 static void
277 resolve_formal_arglist (gfc_symbol *proc)
278 {
279   gfc_formal_arglist *f;
280   gfc_symbol *sym;
281   int i;
282
283   if (proc->result != NULL)
284     sym = proc->result;
285   else
286     sym = proc;
287
288   if (gfc_elemental (proc)
289       || sym->attr.pointer || sym->attr.allocatable
290       || (sym->as && sym->as->rank != 0))
291     {
292       proc->attr.always_explicit = 1;
293       sym->attr.always_explicit = 1;
294     }
295
296   formal_arg_flag = 1;
297
298   for (f = proc->formal; f; f = f->next)
299     {
300       gfc_array_spec *as;
301
302       sym = f->sym;
303
304       if (sym == NULL)
305         {
306           /* Alternate return placeholder.  */
307           if (gfc_elemental (proc))
308             gfc_error ("Alternate return specifier in elemental subroutine "
309                        "'%s' at %L is not allowed", proc->name,
310                        &proc->declared_at);
311           if (proc->attr.function)
312             gfc_error ("Alternate return specifier in function "
313                        "'%s' at %L is not allowed", proc->name,
314                        &proc->declared_at);
315           continue;
316         }
317       else if (sym->attr.procedure && sym->attr.if_source != IFSRC_DECL
318                && resolve_procedure_interface (sym) == FAILURE)
319         return;
320
321       if (sym->attr.if_source != IFSRC_UNKNOWN)
322         resolve_formal_arglist (sym);
323
324       if (sym->attr.subroutine || sym->attr.external)
325         {
326           if (sym->attr.flavor == FL_UNKNOWN)
327             gfc_add_flavor (&sym->attr, FL_PROCEDURE, sym->name, &sym->declared_at);
328         }
329       else
330         {
331           if (sym->ts.type == BT_UNKNOWN && !proc->attr.intrinsic
332               && (!sym->attr.function || sym->result == sym))
333             gfc_set_default_type (sym, 1, sym->ns);
334         }
335
336       as = sym->ts.type == BT_CLASS && sym->attr.class_ok
337            ? CLASS_DATA (sym)->as : sym->as;
338
339       gfc_resolve_array_spec (as, 0);
340
341       /* We can't tell if an array with dimension (:) is assumed or deferred
342          shape until we know if it has the pointer or allocatable attributes.
343       */
344       if (as && as->rank > 0 && as->type == AS_DEFERRED
345           && ((sym->ts.type != BT_CLASS
346                && !(sym->attr.pointer || sym->attr.allocatable))
347               || (sym->ts.type == BT_CLASS
348                   && !(CLASS_DATA (sym)->attr.class_pointer
349                        || CLASS_DATA (sym)->attr.allocatable)))
350           && sym->attr.flavor != FL_PROCEDURE)
351         {
352           as->type = AS_ASSUMED_SHAPE;
353           for (i = 0; i < as->rank; i++)
354             as->lower[i] = gfc_get_int_expr (gfc_default_integer_kind, NULL, 1);
355         }
356
357       if ((as && as->rank > 0 && as->type == AS_ASSUMED_SHAPE)
358           || (as && as->type == AS_ASSUMED_RANK)
359           || sym->attr.pointer || sym->attr.allocatable || sym->attr.target
360           || (sym->ts.type == BT_CLASS && sym->attr.class_ok
361               && (CLASS_DATA (sym)->attr.class_pointer
362                   || CLASS_DATA (sym)->attr.allocatable
363                   || CLASS_DATA (sym)->attr.target))
364           || sym->attr.optional)
365         {
366           proc->attr.always_explicit = 1;
367           if (proc->result)
368             proc->result->attr.always_explicit = 1;
369         }
370
371       /* If the flavor is unknown at this point, it has to be a variable.
372          A procedure specification would have already set the type.  */
373
374       if (sym->attr.flavor == FL_UNKNOWN)
375         gfc_add_flavor (&sym->attr, FL_VARIABLE, sym->name, &sym->declared_at);
376
377       if (gfc_pure (proc))
378         {
379           if (sym->attr.flavor == FL_PROCEDURE)
380             {
381               /* F08:C1279.  */
382               if (!gfc_pure (sym))
383                 {
384                   gfc_error ("Dummy procedure '%s' of PURE procedure at %L must "
385                             "also be PURE", sym->name, &sym->declared_at);
386                   continue;
387                 }
388             }
389           else if (!sym->attr.pointer)
390             {
391               if (proc->attr.function && sym->attr.intent != INTENT_IN)
392                 {
393                   if (sym->attr.value)
394                     gfc_notify_std (GFC_STD_F2008, "Argument '%s'"
395                                     " of pure function '%s' at %L with VALUE "
396                                     "attribute but without INTENT(IN)",
397                                     sym->name, proc->name, &sym->declared_at);
398                   else
399                     gfc_error ("Argument '%s' of pure function '%s' at %L must "
400                                "be INTENT(IN) or VALUE", sym->name, proc->name,
401                                &sym->declared_at);
402                 }
403
404               if (proc->attr.subroutine && sym->attr.intent == INTENT_UNKNOWN)
405                 {
406                   if (sym->attr.value)
407                     gfc_notify_std (GFC_STD_F2008, "Argument '%s'"
408                                     " of pure subroutine '%s' at %L with VALUE "
409                                     "attribute but without INTENT", sym->name,
410                                     proc->name, &sym->declared_at);
411                   else
412                     gfc_error ("Argument '%s' of pure subroutine '%s' at %L "
413                                "must have its INTENT specified or have the "
414                                "VALUE attribute", sym->name, proc->name,
415                                &sym->declared_at);
416                 }
417             }
418         }
419
420       if (proc->attr.implicit_pure)
421         {
422           if (sym->attr.flavor == FL_PROCEDURE)
423             {
424               if (!gfc_pure(sym))
425                 proc->attr.implicit_pure = 0;
426             }
427           else if (!sym->attr.pointer)
428             {
429               if (proc->attr.function && sym->attr.intent != INTENT_IN
430                   && !sym->value)
431                 proc->attr.implicit_pure = 0;
432
433               if (proc->attr.subroutine && sym->attr.intent == INTENT_UNKNOWN
434                   && !sym->value)
435                 proc->attr.implicit_pure = 0;
436             }
437         }
438
439       if (gfc_elemental (proc))
440         {
441           /* F08:C1289.  */
442           if (sym->attr.codimension
443               || (sym->ts.type == BT_CLASS && CLASS_DATA (sym)
444                   && CLASS_DATA (sym)->attr.codimension))
445             {
446               gfc_error ("Coarray dummy argument '%s' at %L to elemental "
447                          "procedure", sym->name, &sym->declared_at);
448               continue;
449             }
450
451           if (sym->as || (sym->ts.type == BT_CLASS && CLASS_DATA (sym)
452                           && CLASS_DATA (sym)->as))
453             {
454               gfc_error ("Argument '%s' of elemental procedure at %L must "
455                          "be scalar", sym->name, &sym->declared_at);
456               continue;
457             }
458
459           if (sym->attr.allocatable
460               || (sym->ts.type == BT_CLASS && CLASS_DATA (sym)
461                   && CLASS_DATA (sym)->attr.allocatable))
462             {
463               gfc_error ("Argument '%s' of elemental procedure at %L cannot "
464                          "have the ALLOCATABLE attribute", sym->name,
465                          &sym->declared_at);
466               continue;
467             }
468
469           if (sym->attr.pointer
470               || (sym->ts.type == BT_CLASS && CLASS_DATA (sym)
471                   && CLASS_DATA (sym)->attr.class_pointer))
472             {
473               gfc_error ("Argument '%s' of elemental procedure at %L cannot "
474                          "have the POINTER attribute", sym->name,
475                          &sym->declared_at);
476               continue;
477             }
478
479           if (sym->attr.flavor == FL_PROCEDURE)
480             {
481               gfc_error ("Dummy procedure '%s' not allowed in elemental "
482                          "procedure '%s' at %L", sym->name, proc->name,
483                          &sym->declared_at);
484               continue;
485             }
486
487           if (sym->attr.intent == INTENT_UNKNOWN)
488             {
489               gfc_error ("Argument '%s' of elemental procedure '%s' at %L must "
490                          "have its INTENT specified", sym->name, proc->name,
491                          &sym->declared_at);
492               continue;
493             }
494         }
495
496       /* Each dummy shall be specified to be scalar.  */
497       if (proc->attr.proc == PROC_ST_FUNCTION)
498         {
499           if (sym->as != NULL)
500             {
501               gfc_error ("Argument '%s' of statement function at %L must "
502                          "be scalar", sym->name, &sym->declared_at);
503               continue;
504             }
505
506           if (sym->ts.type == BT_CHARACTER)
507             {
508               gfc_charlen *cl = sym->ts.u.cl;
509               if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
510                 {
511                   gfc_error ("Character-valued argument '%s' of statement "
512                              "function at %L must have constant length",
513                              sym->name, &sym->declared_at);
514                   continue;
515                 }
516             }
517         }
518     }
519   formal_arg_flag = 0;
520 }
521
522
523 /* Work function called when searching for symbols that have argument lists
524    associated with them.  */
525
526 static void
527 find_arglists (gfc_symbol *sym)
528 {
529   if (sym->attr.if_source == IFSRC_UNKNOWN || sym->ns != gfc_current_ns
530       || sym->attr.flavor == FL_DERIVED)
531     return;
532
533   resolve_formal_arglist (sym);
534 }
535
536
537 /* Given a namespace, resolve all formal argument lists within the namespace.
538  */
539
540 static void
541 resolve_formal_arglists (gfc_namespace *ns)
542 {
543   if (ns == NULL)
544     return;
545
546   gfc_traverse_ns (ns, find_arglists);
547 }
548
549
550 static void
551 resolve_contained_fntype (gfc_symbol *sym, gfc_namespace *ns)
552 {
553   gfc_try t;
554
555   /* If this namespace is not a function or an entry master function,
556      ignore it.  */
557   if (! sym || !(sym->attr.function || sym->attr.flavor == FL_VARIABLE)
558       || sym->attr.entry_master)
559     return;
560
561   /* Try to find out of what the return type is.  */
562   if (sym->result->ts.type == BT_UNKNOWN && sym->result->ts.interface == NULL)
563     {
564       t = gfc_set_default_type (sym->result, 0, ns);
565
566       if (t == FAILURE && !sym->result->attr.untyped)
567         {
568           if (sym->result == sym)
569             gfc_error ("Contained function '%s' at %L has no IMPLICIT type",
570                        sym->name, &sym->declared_at);
571           else if (!sym->result->attr.proc_pointer)
572             gfc_error ("Result '%s' of contained function '%s' at %L has "
573                        "no IMPLICIT type", sym->result->name, sym->name,
574                        &sym->result->declared_at);
575           sym->result->attr.untyped = 1;
576         }
577     }
578
579   /* Fortran 95 Draft Standard, page 51, Section 5.1.1.5, on the Character 
580      type, lists the only ways a character length value of * can be used:
581      dummy arguments of procedures, named constants, and function results
582      in external functions.  Internal function results and results of module
583      procedures are not on this list, ergo, not permitted.  */
584
585   if (sym->result->ts.type == BT_CHARACTER)
586     {
587       gfc_charlen *cl = sym->result->ts.u.cl;
588       if ((!cl || !cl->length) && !sym->result->ts.deferred)
589         {
590           /* See if this is a module-procedure and adapt error message
591              accordingly.  */
592           bool module_proc;
593           gcc_assert (ns->parent && ns->parent->proc_name);
594           module_proc = (ns->parent->proc_name->attr.flavor == FL_MODULE);
595
596           gfc_error ("Character-valued %s '%s' at %L must not be"
597                      " assumed length",
598                      module_proc ? _("module procedure")
599                                  : _("internal function"),
600                      sym->name, &sym->declared_at);
601         }
602     }
603 }
604
605
606 /* Add NEW_ARGS to the formal argument list of PROC, taking care not to
607    introduce duplicates.  */
608
609 static void
610 merge_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
611 {
612   gfc_formal_arglist *f, *new_arglist;
613   gfc_symbol *new_sym;
614
615   for (; new_args != NULL; new_args = new_args->next)
616     {
617       new_sym = new_args->sym;
618       /* See if this arg is already in the formal argument list.  */
619       for (f = proc->formal; f; f = f->next)
620         {
621           if (new_sym == f->sym)
622             break;
623         }
624
625       if (f)
626         continue;
627
628       /* Add a new argument.  Argument order is not important.  */
629       new_arglist = gfc_get_formal_arglist ();
630       new_arglist->sym = new_sym;
631       new_arglist->next = proc->formal;
632       proc->formal  = new_arglist;
633     }
634 }
635
636
637 /* Flag the arguments that are not present in all entries.  */
638
639 static void
640 check_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
641 {
642   gfc_formal_arglist *f, *head;
643   head = new_args;
644
645   for (f = proc->formal; f; f = f->next)
646     {
647       if (f->sym == NULL)
648         continue;
649
650       for (new_args = head; new_args; new_args = new_args->next)
651         {
652           if (new_args->sym == f->sym)
653             break;
654         }
655
656       if (new_args)
657         continue;
658
659       f->sym->attr.not_always_present = 1;
660     }
661 }
662
663
664 /* Resolve alternate entry points.  If a symbol has multiple entry points we
665    create a new master symbol for the main routine, and turn the existing
666    symbol into an entry point.  */
667
668 static void
669 resolve_entries (gfc_namespace *ns)
670 {
671   gfc_namespace *old_ns;
672   gfc_code *c;
673   gfc_symbol *proc;
674   gfc_entry_list *el;
675   char name[GFC_MAX_SYMBOL_LEN + 1];
676   static int master_count = 0;
677
678   if (ns->proc_name == NULL)
679     return;
680
681   /* No need to do anything if this procedure doesn't have alternate entry
682      points.  */
683   if (!ns->entries)
684     return;
685
686   /* We may already have resolved alternate entry points.  */
687   if (ns->proc_name->attr.entry_master)
688     return;
689
690   /* If this isn't a procedure something has gone horribly wrong.  */
691   gcc_assert (ns->proc_name->attr.flavor == FL_PROCEDURE);
692
693   /* Remember the current namespace.  */
694   old_ns = gfc_current_ns;
695
696   gfc_current_ns = ns;
697
698   /* Add the main entry point to the list of entry points.  */
699   el = gfc_get_entry_list ();
700   el->sym = ns->proc_name;
701   el->id = 0;
702   el->next = ns->entries;
703   ns->entries = el;
704   ns->proc_name->attr.entry = 1;
705
706   /* If it is a module function, it needs to be in the right namespace
707      so that gfc_get_fake_result_decl can gather up the results. The
708      need for this arose in get_proc_name, where these beasts were
709      left in their own namespace, to keep prior references linked to
710      the entry declaration.*/
711   if (ns->proc_name->attr.function
712       && ns->parent && ns->parent->proc_name->attr.flavor == FL_MODULE)
713     el->sym->ns = ns;
714
715   /* Do the same for entries where the master is not a module
716      procedure.  These are retained in the module namespace because
717      of the module procedure declaration.  */
718   for (el = el->next; el; el = el->next)
719     if (el->sym->ns->proc_name->attr.flavor == FL_MODULE
720           && el->sym->attr.mod_proc)
721       el->sym->ns = ns;
722   el = ns->entries;
723
724   /* Add an entry statement for it.  */
725   c = gfc_get_code ();
726   c->op = EXEC_ENTRY;
727   c->ext.entry = el;
728   c->next = ns->code;
729   ns->code = c;
730
731   /* Create a new symbol for the master function.  */
732   /* Give the internal function a unique name (within this file).
733      Also include the function name so the user has some hope of figuring
734      out what is going on.  */
735   snprintf (name, GFC_MAX_SYMBOL_LEN, "master.%d.%s",
736             master_count++, ns->proc_name->name);
737   gfc_get_ha_symbol (name, &proc);
738   gcc_assert (proc != NULL);
739
740   gfc_add_procedure (&proc->attr, PROC_INTERNAL, proc->name, NULL);
741   if (ns->proc_name->attr.subroutine)
742     gfc_add_subroutine (&proc->attr, proc->name, NULL);
743   else
744     {
745       gfc_symbol *sym;
746       gfc_typespec *ts, *fts;
747       gfc_array_spec *as, *fas;
748       gfc_add_function (&proc->attr, proc->name, NULL);
749       proc->result = proc;
750       fas = ns->entries->sym->as;
751       fas = fas ? fas : ns->entries->sym->result->as;
752       fts = &ns->entries->sym->result->ts;
753       if (fts->type == BT_UNKNOWN)
754         fts = gfc_get_default_type (ns->entries->sym->result->name, NULL);
755       for (el = ns->entries->next; el; el = el->next)
756         {
757           ts = &el->sym->result->ts;
758           as = el->sym->as;
759           as = as ? as : el->sym->result->as;
760           if (ts->type == BT_UNKNOWN)
761             ts = gfc_get_default_type (el->sym->result->name, NULL);
762
763           if (! gfc_compare_types (ts, fts)
764               || (el->sym->result->attr.dimension
765                   != ns->entries->sym->result->attr.dimension)
766               || (el->sym->result->attr.pointer
767                   != ns->entries->sym->result->attr.pointer))
768             break;
769           else if (as && fas && ns->entries->sym->result != el->sym->result
770                       && gfc_compare_array_spec (as, fas) == 0)
771             gfc_error ("Function %s at %L has entries with mismatched "
772                        "array specifications", ns->entries->sym->name,
773                        &ns->entries->sym->declared_at);
774           /* The characteristics need to match and thus both need to have
775              the same string length, i.e. both len=*, or both len=4.
776              Having both len=<variable> is also possible, but difficult to
777              check at compile time.  */
778           else if (ts->type == BT_CHARACTER && ts->u.cl && fts->u.cl
779                    && (((ts->u.cl->length && !fts->u.cl->length)
780                         ||(!ts->u.cl->length && fts->u.cl->length))
781                        || (ts->u.cl->length
782                            && ts->u.cl->length->expr_type
783                               != fts->u.cl->length->expr_type)
784                        || (ts->u.cl->length
785                            && ts->u.cl->length->expr_type == EXPR_CONSTANT
786                            && mpz_cmp (ts->u.cl->length->value.integer,
787                                        fts->u.cl->length->value.integer) != 0)))
788             gfc_notify_std (GFC_STD_GNU, "Function %s at %L with "
789                             "entries returning variables of different "
790                             "string lengths", ns->entries->sym->name,
791                             &ns->entries->sym->declared_at);
792         }
793
794       if (el == NULL)
795         {
796           sym = ns->entries->sym->result;
797           /* All result types the same.  */
798           proc->ts = *fts;
799           if (sym->attr.dimension)
800             gfc_set_array_spec (proc, gfc_copy_array_spec (sym->as), NULL);
801           if (sym->attr.pointer)
802             gfc_add_pointer (&proc->attr, NULL);
803         }
804       else
805         {
806           /* Otherwise the result will be passed through a union by
807              reference.  */
808           proc->attr.mixed_entry_master = 1;
809           for (el = ns->entries; el; el = el->next)
810             {
811               sym = el->sym->result;
812               if (sym->attr.dimension)
813                 {
814                   if (el == ns->entries)
815                     gfc_error ("FUNCTION result %s can't be an array in "
816                                "FUNCTION %s at %L", sym->name,
817                                ns->entries->sym->name, &sym->declared_at);
818                   else
819                     gfc_error ("ENTRY result %s can't be an array in "
820                                "FUNCTION %s at %L", sym->name,
821                                ns->entries->sym->name, &sym->declared_at);
822                 }
823               else if (sym->attr.pointer)
824                 {
825                   if (el == ns->entries)
826                     gfc_error ("FUNCTION result %s can't be a POINTER in "
827                                "FUNCTION %s at %L", sym->name,
828                                ns->entries->sym->name, &sym->declared_at);
829                   else
830                     gfc_error ("ENTRY result %s can't be a POINTER in "
831                                "FUNCTION %s at %L", sym->name,
832                                ns->entries->sym->name, &sym->declared_at);
833                 }
834               else
835                 {
836                   ts = &sym->ts;
837                   if (ts->type == BT_UNKNOWN)
838                     ts = gfc_get_default_type (sym->name, NULL);
839                   switch (ts->type)
840                     {
841                     case BT_INTEGER:
842                       if (ts->kind == gfc_default_integer_kind)
843                         sym = NULL;
844                       break;
845                     case BT_REAL:
846                       if (ts->kind == gfc_default_real_kind
847                           || ts->kind == gfc_default_double_kind)
848                         sym = NULL;
849                       break;
850                     case BT_COMPLEX:
851                       if (ts->kind == gfc_default_complex_kind)
852                         sym = NULL;
853                       break;
854                     case BT_LOGICAL:
855                       if (ts->kind == gfc_default_logical_kind)
856                         sym = NULL;
857                       break;
858                     case BT_UNKNOWN:
859                       /* We will issue error elsewhere.  */
860                       sym = NULL;
861                       break;
862                     default:
863                       break;
864                     }
865                   if (sym)
866                     {
867                       if (el == ns->entries)
868                         gfc_error ("FUNCTION result %s can't be of type %s "
869                                    "in FUNCTION %s at %L", sym->name,
870                                    gfc_typename (ts), ns->entries->sym->name,
871                                    &sym->declared_at);
872                       else
873                         gfc_error ("ENTRY result %s can't be of type %s "
874                                    "in FUNCTION %s at %L", sym->name,
875                                    gfc_typename (ts), ns->entries->sym->name,
876                                    &sym->declared_at);
877                     }
878                 }
879             }
880         }
881     }
882   proc->attr.access = ACCESS_PRIVATE;
883   proc->attr.entry_master = 1;
884
885   /* Merge all the entry point arguments.  */
886   for (el = ns->entries; el; el = el->next)
887     merge_argument_lists (proc, el->sym->formal);
888
889   /* Check the master formal arguments for any that are not
890      present in all entry points.  */
891   for (el = ns->entries; el; el = el->next)
892     check_argument_lists (proc, el->sym->formal);
893
894   /* Use the master function for the function body.  */
895   ns->proc_name = proc;
896
897   /* Finalize the new symbols.  */
898   gfc_commit_symbols ();
899
900   /* Restore the original namespace.  */
901   gfc_current_ns = old_ns;
902 }
903
904
905 /* Resolve common variables.  */
906 static void
907 resolve_common_vars (gfc_symbol *sym, bool named_common)
908 {
909   gfc_symbol *csym = sym;
910
911   for (; csym; csym = csym->common_next)
912     {
913       if (csym->value || csym->attr.data)
914         {
915           if (!csym->ns->is_block_data)
916             gfc_notify_std (GFC_STD_GNU, "Variable '%s' at %L is in COMMON "
917                             "but only in BLOCK DATA initialization is "
918                             "allowed", csym->name, &csym->declared_at);
919           else if (!named_common)
920             gfc_notify_std (GFC_STD_GNU, "Initialized variable '%s' at %L is "
921                             "in a blank COMMON but initialization is only "
922                             "allowed in named common blocks", csym->name,
923                             &csym->declared_at);
924         }
925
926       if (csym->ts.type != BT_DERIVED)
927         continue;
928
929       if (!(csym->ts.u.derived->attr.sequence
930             || csym->ts.u.derived->attr.is_bind_c))
931         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
932                        "has neither the SEQUENCE nor the BIND(C) "
933                        "attribute", csym->name, &csym->declared_at);
934       if (csym->ts.u.derived->attr.alloc_comp)
935         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
936                        "has an ultimate component that is "
937                        "allocatable", csym->name, &csym->declared_at);
938       if (gfc_has_default_initializer (csym->ts.u.derived))
939         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
940                        "may not have default initializer", csym->name,
941                        &csym->declared_at);
942
943       if (csym->attr.flavor == FL_UNKNOWN && !csym->attr.proc_pointer)
944         gfc_add_flavor (&csym->attr, FL_VARIABLE, csym->name, &csym->declared_at);
945     }
946 }
947
948 /* Resolve common blocks.  */
949 static void
950 resolve_common_blocks (gfc_symtree *common_root)
951 {
952   gfc_symbol *sym;
953
954   if (common_root == NULL)
955     return;
956
957   if (common_root->left)
958     resolve_common_blocks (common_root->left);
959   if (common_root->right)
960     resolve_common_blocks (common_root->right);
961
962   resolve_common_vars (common_root->n.common->head, true);
963
964   gfc_find_symbol (common_root->name, gfc_current_ns, 0, &sym);
965   if (sym == NULL)
966     return;
967
968   if (sym->attr.flavor == FL_PARAMETER)
969     gfc_error ("COMMON block '%s' at %L is used as PARAMETER at %L",
970                sym->name, &common_root->n.common->where, &sym->declared_at);
971
972   if (sym->attr.external)
973     gfc_error ("COMMON block '%s' at %L can not have the EXTERNAL attribute",
974                sym->name, &common_root->n.common->where);
975
976   if (sym->attr.intrinsic)
977     gfc_error ("COMMON block '%s' at %L is also an intrinsic procedure",
978                sym->name, &common_root->n.common->where);
979   else if (sym->attr.result
980            || gfc_is_function_return_value (sym, gfc_current_ns))
981     gfc_notify_std (GFC_STD_F2003, "COMMON block '%s' at %L "
982                     "that is also a function result", sym->name,
983                     &common_root->n.common->where);
984   else if (sym->attr.flavor == FL_PROCEDURE && sym->attr.proc != PROC_INTERNAL
985            && sym->attr.proc != PROC_ST_FUNCTION)
986     gfc_notify_std (GFC_STD_F2003, "COMMON block '%s' at %L "
987                     "that is also a global procedure", sym->name,
988                     &common_root->n.common->where);
989 }
990
991
992 /* Resolve contained function types.  Because contained functions can call one
993    another, they have to be worked out before any of the contained procedures
994    can be resolved.
995
996    The good news is that if a function doesn't already have a type, the only
997    way it can get one is through an IMPLICIT type or a RESULT variable, because
998    by definition contained functions are contained namespace they're contained
999    in, not in a sibling or parent namespace.  */
1000
1001 static void
1002 resolve_contained_functions (gfc_namespace *ns)
1003 {
1004   gfc_namespace *child;
1005   gfc_entry_list *el;
1006
1007   resolve_formal_arglists (ns);
1008
1009   for (child = ns->contained; child; child = child->sibling)
1010     {
1011       /* Resolve alternate entry points first.  */
1012       resolve_entries (child);
1013
1014       /* Then check function return types.  */
1015       resolve_contained_fntype (child->proc_name, child);
1016       for (el = child->entries; el; el = el->next)
1017         resolve_contained_fntype (el->sym, child);
1018     }
1019 }
1020
1021
1022 static gfc_try resolve_fl_derived0 (gfc_symbol *sym);
1023
1024
1025 /* Resolve all of the elements of a structure constructor and make sure that
1026    the types are correct. The 'init' flag indicates that the given
1027    constructor is an initializer.  */
1028
1029 static gfc_try
1030 resolve_structure_cons (gfc_expr *expr, int init)
1031 {
1032   gfc_constructor *cons;
1033   gfc_component *comp;
1034   gfc_try t;
1035   symbol_attribute a;
1036
1037   t = SUCCESS;
1038
1039   if (expr->ts.type == BT_DERIVED)
1040     resolve_fl_derived0 (expr->ts.u.derived);
1041
1042   cons = gfc_constructor_first (expr->value.constructor);
1043
1044   /* See if the user is trying to invoke a structure constructor for one of
1045      the iso_c_binding derived types.  */
1046   if (expr->ts.type == BT_DERIVED && expr->ts.u.derived
1047       && expr->ts.u.derived->ts.is_iso_c && cons
1048       && (cons->expr == NULL || cons->expr->expr_type != EXPR_NULL))
1049     {
1050       gfc_error ("Components of structure constructor '%s' at %L are PRIVATE",
1051                  expr->ts.u.derived->name, &(expr->where));
1052       return FAILURE;
1053     }
1054
1055   /* Return if structure constructor is c_null_(fun)prt.  */
1056   if (expr->ts.type == BT_DERIVED && expr->ts.u.derived
1057       && expr->ts.u.derived->ts.is_iso_c && cons
1058       && cons->expr && cons->expr->expr_type == EXPR_NULL)
1059     return SUCCESS;
1060
1061   /* A constructor may have references if it is the result of substituting a
1062      parameter variable.  In this case we just pull out the component we
1063      want.  */
1064   if (expr->ref)
1065     comp = expr->ref->u.c.sym->components;
1066   else
1067     comp = expr->ts.u.derived->components;
1068
1069   for (; comp && cons; comp = comp->next, cons = gfc_constructor_next (cons))
1070     {
1071       int rank;
1072
1073       if (!cons->expr)
1074         continue;
1075
1076       if (gfc_resolve_expr (cons->expr) == FAILURE)
1077         {
1078           t = FAILURE;
1079           continue;
1080         }
1081
1082       rank = comp->as ? comp->as->rank : 0;
1083       if (cons->expr->expr_type != EXPR_NULL && rank != cons->expr->rank
1084           && (comp->attr.allocatable || cons->expr->rank))
1085         {
1086           gfc_error ("The rank of the element in the structure "
1087                      "constructor at %L does not match that of the "
1088                      "component (%d/%d)", &cons->expr->where,
1089                      cons->expr->rank, rank);
1090           t = FAILURE;
1091         }
1092
1093       /* If we don't have the right type, try to convert it.  */
1094
1095       if (!comp->attr.proc_pointer &&
1096           !gfc_compare_types (&cons->expr->ts, &comp->ts))
1097         {
1098           t = FAILURE;
1099           if (strcmp (comp->name, "_extends") == 0)
1100             {
1101               /* Can afford to be brutal with the _extends initializer.
1102                  The derived type can get lost because it is PRIVATE
1103                  but it is not usage constrained by the standard.  */
1104               cons->expr->ts = comp->ts;
1105               t = SUCCESS;
1106             }
1107           else if (comp->attr.pointer && cons->expr->ts.type != BT_UNKNOWN)
1108             gfc_error ("The element in the structure constructor at %L, "
1109                        "for pointer component '%s', is %s but should be %s",
1110                        &cons->expr->where, comp->name,
1111                        gfc_basic_typename (cons->expr->ts.type),
1112                        gfc_basic_typename (comp->ts.type));
1113           else
1114             t = gfc_convert_type (cons->expr, &comp->ts, 1);
1115         }
1116
1117       /* For strings, the length of the constructor should be the same as
1118          the one of the structure, ensure this if the lengths are known at
1119          compile time and when we are dealing with PARAMETER or structure
1120          constructors.  */
1121       if (cons->expr->ts.type == BT_CHARACTER && comp->ts.u.cl
1122           && comp->ts.u.cl->length
1123           && comp->ts.u.cl->length->expr_type == EXPR_CONSTANT
1124           && cons->expr->ts.u.cl && cons->expr->ts.u.cl->length
1125           && cons->expr->ts.u.cl->length->expr_type == EXPR_CONSTANT
1126           && cons->expr->rank != 0
1127           && mpz_cmp (cons->expr->ts.u.cl->length->value.integer,
1128                       comp->ts.u.cl->length->value.integer) != 0)
1129         {
1130           if (cons->expr->expr_type == EXPR_VARIABLE
1131               && cons->expr->symtree->n.sym->attr.flavor == FL_PARAMETER)
1132             {
1133               /* Wrap the parameter in an array constructor (EXPR_ARRAY)
1134                  to make use of the gfc_resolve_character_array_constructor
1135                  machinery.  The expression is later simplified away to
1136                  an array of string literals.  */
1137               gfc_expr *para = cons->expr;
1138               cons->expr = gfc_get_expr ();
1139               cons->expr->ts = para->ts;
1140               cons->expr->where = para->where;
1141               cons->expr->expr_type = EXPR_ARRAY;
1142               cons->expr->rank = para->rank;
1143               cons->expr->shape = gfc_copy_shape (para->shape, para->rank);
1144               gfc_constructor_append_expr (&cons->expr->value.constructor,
1145                                            para, &cons->expr->where);
1146             }
1147           if (cons->expr->expr_type == EXPR_ARRAY)
1148             {
1149               gfc_constructor *p;
1150               p = gfc_constructor_first (cons->expr->value.constructor);
1151               if (cons->expr->ts.u.cl != p->expr->ts.u.cl)
1152                 {
1153                   gfc_charlen *cl, *cl2;
1154
1155                   cl2 = NULL;
1156                   for (cl = gfc_current_ns->cl_list; cl; cl = cl->next)
1157                     {
1158                       if (cl == cons->expr->ts.u.cl)
1159                         break;
1160                       cl2 = cl;
1161                     }
1162
1163                   gcc_assert (cl);
1164
1165                   if (cl2)
1166                     cl2->next = cl->next;
1167
1168                   gfc_free_expr (cl->length);
1169                   free (cl);
1170                 }
1171
1172               cons->expr->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
1173               cons->expr->ts.u.cl->length_from_typespec = true;
1174               cons->expr->ts.u.cl->length = gfc_copy_expr (comp->ts.u.cl->length);
1175               gfc_resolve_character_array_constructor (cons->expr);
1176             }
1177         }
1178
1179       if (cons->expr->expr_type == EXPR_NULL
1180           && !(comp->attr.pointer || comp->attr.allocatable
1181                || comp->attr.proc_pointer
1182                || (comp->ts.type == BT_CLASS
1183                    && (CLASS_DATA (comp)->attr.class_pointer
1184                        || CLASS_DATA (comp)->attr.allocatable))))
1185         {
1186           t = FAILURE;
1187           gfc_error ("The NULL in the structure constructor at %L is "
1188                      "being applied to component '%s', which is neither "
1189                      "a POINTER nor ALLOCATABLE", &cons->expr->where,
1190                      comp->name);
1191         }
1192
1193       if (comp->attr.proc_pointer && comp->ts.interface)
1194         {
1195           /* Check procedure pointer interface.  */
1196           gfc_symbol *s2 = NULL;
1197           gfc_component *c2;
1198           const char *name;
1199           char err[200];
1200
1201           c2 = gfc_get_proc_ptr_comp (cons->expr);
1202           if (c2)
1203             {
1204               s2 = c2->ts.interface;
1205               name = c2->name;
1206             }
1207           else if (cons->expr->expr_type == EXPR_FUNCTION)
1208             {
1209               s2 = cons->expr->symtree->n.sym->result;
1210               name = cons->expr->symtree->n.sym->result->name;
1211             }
1212           else if (cons->expr->expr_type != EXPR_NULL)
1213             {
1214               s2 = cons->expr->symtree->n.sym;
1215               name = cons->expr->symtree->n.sym->name;
1216             }
1217
1218           if (s2 && !gfc_compare_interfaces (comp->ts.interface, s2, name, 0, 1,
1219                                              err, sizeof (err), NULL, NULL))
1220             {
1221               gfc_error ("Interface mismatch for procedure-pointer component "
1222                          "'%s' in structure constructor at %L: %s",
1223                          comp->name, &cons->expr->where, err);
1224               return FAILURE;
1225             }
1226         }
1227
1228       if (!comp->attr.pointer || comp->attr.proc_pointer
1229           || cons->expr->expr_type == EXPR_NULL)
1230         continue;
1231
1232       a = gfc_expr_attr (cons->expr);
1233
1234       if (!a.pointer && !a.target)
1235         {
1236           t = FAILURE;
1237           gfc_error ("The element in the structure constructor at %L, "
1238                      "for pointer component '%s' should be a POINTER or "
1239                      "a TARGET", &cons->expr->where, comp->name);
1240         }
1241
1242       if (init)
1243         {
1244           /* F08:C461. Additional checks for pointer initialization.  */
1245           if (a.allocatable)
1246             {
1247               t = FAILURE;
1248               gfc_error ("Pointer initialization target at %L "
1249                          "must not be ALLOCATABLE ", &cons->expr->where);
1250             }
1251           if (!a.save)
1252             {
1253               t = FAILURE;
1254               gfc_error ("Pointer initialization target at %L "
1255                          "must have the SAVE attribute", &cons->expr->where);
1256             }
1257         }
1258
1259       /* F2003, C1272 (3).  */
1260       if (gfc_pure (NULL) && cons->expr->expr_type == EXPR_VARIABLE
1261           && (gfc_impure_variable (cons->expr->symtree->n.sym)
1262               || gfc_is_coindexed (cons->expr)))
1263         {
1264           t = FAILURE;
1265           gfc_error ("Invalid expression in the structure constructor for "
1266                      "pointer component '%s' at %L in PURE procedure",
1267                      comp->name, &cons->expr->where);
1268         }
1269
1270       if (gfc_implicit_pure (NULL)
1271             && cons->expr->expr_type == EXPR_VARIABLE
1272             && (gfc_impure_variable (cons->expr->symtree->n.sym)
1273                 || gfc_is_coindexed (cons->expr)))
1274         gfc_current_ns->proc_name->attr.implicit_pure = 0;
1275
1276     }
1277
1278   return t;
1279 }
1280
1281
1282 /****************** Expression name resolution ******************/
1283
1284 /* Returns 0 if a symbol was not declared with a type or
1285    attribute declaration statement, nonzero otherwise.  */
1286
1287 static int
1288 was_declared (gfc_symbol *sym)
1289 {
1290   symbol_attribute a;
1291
1292   a = sym->attr;
1293
1294   if (!a.implicit_type && sym->ts.type != BT_UNKNOWN)
1295     return 1;
1296
1297   if (a.allocatable || a.dimension || a.dummy || a.external || a.intrinsic
1298       || a.optional || a.pointer || a.save || a.target || a.volatile_
1299       || a.value || a.access != ACCESS_UNKNOWN || a.intent != INTENT_UNKNOWN
1300       || a.asynchronous || a.codimension)
1301     return 1;
1302
1303   return 0;
1304 }
1305
1306
1307 /* Determine if a symbol is generic or not.  */
1308
1309 static int
1310 generic_sym (gfc_symbol *sym)
1311 {
1312   gfc_symbol *s;
1313
1314   if (sym->attr.generic ||
1315       (sym->attr.intrinsic && gfc_generic_intrinsic (sym->name)))
1316     return 1;
1317
1318   if (was_declared (sym) || sym->ns->parent == NULL)
1319     return 0;
1320
1321   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
1322   
1323   if (s != NULL)
1324     {
1325       if (s == sym)
1326         return 0;
1327       else
1328         return generic_sym (s);
1329     }
1330
1331   return 0;
1332 }
1333
1334
1335 /* Determine if a symbol is specific or not.  */
1336
1337 static int
1338 specific_sym (gfc_symbol *sym)
1339 {
1340   gfc_symbol *s;
1341
1342   if (sym->attr.if_source == IFSRC_IFBODY
1343       || sym->attr.proc == PROC_MODULE
1344       || sym->attr.proc == PROC_INTERNAL
1345       || sym->attr.proc == PROC_ST_FUNCTION
1346       || (sym->attr.intrinsic && gfc_specific_intrinsic (sym->name))
1347       || sym->attr.external)
1348     return 1;
1349
1350   if (was_declared (sym) || sym->ns->parent == NULL)
1351     return 0;
1352
1353   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
1354
1355   return (s == NULL) ? 0 : specific_sym (s);
1356 }
1357
1358
1359 /* Figure out if the procedure is specific, generic or unknown.  */
1360
1361 typedef enum
1362 { PTYPE_GENERIC = 1, PTYPE_SPECIFIC, PTYPE_UNKNOWN }
1363 proc_type;
1364
1365 static proc_type
1366 procedure_kind (gfc_symbol *sym)
1367 {
1368   if (generic_sym (sym))
1369     return PTYPE_GENERIC;
1370
1371   if (specific_sym (sym))
1372     return PTYPE_SPECIFIC;
1373
1374   return PTYPE_UNKNOWN;
1375 }
1376
1377 /* Check references to assumed size arrays.  The flag need_full_assumed_size
1378    is nonzero when matching actual arguments.  */
1379
1380 static int need_full_assumed_size = 0;
1381
1382 static bool
1383 check_assumed_size_reference (gfc_symbol *sym, gfc_expr *e)
1384 {
1385   if (need_full_assumed_size || !(sym->as && sym->as->type == AS_ASSUMED_SIZE))
1386       return false;
1387
1388   /* FIXME: The comparison "e->ref->u.ar.type == AR_FULL" is wrong.
1389      What should it be?  */
1390   if ((e->ref->u.ar.end[e->ref->u.ar.as->rank - 1] == NULL)
1391           && (e->ref->u.ar.as->type == AS_ASSUMED_SIZE)
1392                && (e->ref->u.ar.type == AR_FULL))
1393     {
1394       gfc_error ("The upper bound in the last dimension must "
1395                  "appear in the reference to the assumed size "
1396                  "array '%s' at %L", sym->name, &e->where);
1397       return true;
1398     }
1399   return false;
1400 }
1401
1402
1403 /* Look for bad assumed size array references in argument expressions
1404   of elemental and array valued intrinsic procedures.  Since this is
1405   called from procedure resolution functions, it only recurses at
1406   operators.  */
1407
1408 static bool
1409 resolve_assumed_size_actual (gfc_expr *e)
1410 {
1411   if (e == NULL)
1412    return false;
1413
1414   switch (e->expr_type)
1415     {
1416     case EXPR_VARIABLE:
1417       if (e->symtree && check_assumed_size_reference (e->symtree->n.sym, e))
1418         return true;
1419       break;
1420
1421     case EXPR_OP:
1422       if (resolve_assumed_size_actual (e->value.op.op1)
1423           || resolve_assumed_size_actual (e->value.op.op2))
1424         return true;
1425       break;
1426
1427     default:
1428       break;
1429     }
1430   return false;
1431 }
1432
1433
1434 /* Check a generic procedure, passed as an actual argument, to see if
1435    there is a matching specific name.  If none, it is an error, and if
1436    more than one, the reference is ambiguous.  */
1437 static int
1438 count_specific_procs (gfc_expr *e)
1439 {
1440   int n;
1441   gfc_interface *p;
1442   gfc_symbol *sym;
1443         
1444   n = 0;
1445   sym = e->symtree->n.sym;
1446
1447   for (p = sym->generic; p; p = p->next)
1448     if (strcmp (sym->name, p->sym->name) == 0)
1449       {
1450         e->symtree = gfc_find_symtree (p->sym->ns->sym_root,
1451                                        sym->name);
1452         n++;
1453       }
1454
1455   if (n > 1)
1456     gfc_error ("'%s' at %L is ambiguous", e->symtree->n.sym->name,
1457                &e->where);
1458
1459   if (n == 0)
1460     gfc_error ("GENERIC procedure '%s' is not allowed as an actual "
1461                "argument at %L", sym->name, &e->where);
1462
1463   return n;
1464 }
1465
1466
1467 /* See if a call to sym could possibly be a not allowed RECURSION because of
1468    a missing RECURSIVE declaration.  This means that either sym is the current
1469    context itself, or sym is the parent of a contained procedure calling its
1470    non-RECURSIVE containing procedure.
1471    This also works if sym is an ENTRY.  */
1472
1473 static bool
1474 is_illegal_recursion (gfc_symbol* sym, gfc_namespace* context)
1475 {
1476   gfc_symbol* proc_sym;
1477   gfc_symbol* context_proc;
1478   gfc_namespace* real_context;
1479
1480   if (sym->attr.flavor == FL_PROGRAM
1481       || sym->attr.flavor == FL_DERIVED)
1482     return false;
1483
1484   gcc_assert (sym->attr.flavor == FL_PROCEDURE);
1485
1486   /* If we've got an ENTRY, find real procedure.  */
1487   if (sym->attr.entry && sym->ns->entries)
1488     proc_sym = sym->ns->entries->sym;
1489   else
1490     proc_sym = sym;
1491
1492   /* If sym is RECURSIVE, all is well of course.  */
1493   if (proc_sym->attr.recursive || gfc_option.flag_recursive)
1494     return false;
1495
1496   /* Find the context procedure's "real" symbol if it has entries.
1497      We look for a procedure symbol, so recurse on the parents if we don't
1498      find one (like in case of a BLOCK construct).  */
1499   for (real_context = context; ; real_context = real_context->parent)
1500     {
1501       /* We should find something, eventually!  */
1502       gcc_assert (real_context);
1503
1504       context_proc = (real_context->entries ? real_context->entries->sym
1505                                             : real_context->proc_name);
1506
1507       /* In some special cases, there may not be a proc_name, like for this
1508          invalid code:
1509          real(bad_kind()) function foo () ...
1510          when checking the call to bad_kind ().
1511          In these cases, we simply return here and assume that the
1512          call is ok.  */
1513       if (!context_proc)
1514         return false;
1515
1516       if (context_proc->attr.flavor != FL_LABEL)
1517         break;
1518     }
1519
1520   /* A call from sym's body to itself is recursion, of course.  */
1521   if (context_proc == proc_sym)
1522     return true;
1523
1524   /* The same is true if context is a contained procedure and sym the
1525      containing one.  */
1526   if (context_proc->attr.contained)
1527     {
1528       gfc_symbol* parent_proc;
1529
1530       gcc_assert (context->parent);
1531       parent_proc = (context->parent->entries ? context->parent->entries->sym
1532                                               : context->parent->proc_name);
1533
1534       if (parent_proc == proc_sym)
1535         return true;
1536     }
1537
1538   return false;
1539 }
1540
1541
1542 /* Resolve an intrinsic procedure: Set its function/subroutine attribute,
1543    its typespec and formal argument list.  */
1544
1545 gfc_try
1546 gfc_resolve_intrinsic (gfc_symbol *sym, locus *loc)
1547 {
1548   gfc_intrinsic_sym* isym = NULL;
1549   const char* symstd;
1550
1551   if (sym->formal)
1552     return SUCCESS;
1553
1554   /* Already resolved.  */
1555   if (sym->from_intmod && sym->ts.type != BT_UNKNOWN)
1556     return SUCCESS;
1557
1558   /* We already know this one is an intrinsic, so we don't call
1559      gfc_is_intrinsic for full checking but rather use gfc_find_function and
1560      gfc_find_subroutine directly to check whether it is a function or
1561      subroutine.  */
1562
1563   if (sym->intmod_sym_id)
1564     isym = gfc_intrinsic_function_by_id ((gfc_isym_id) sym->intmod_sym_id);
1565   else if (!sym->attr.subroutine)
1566     isym = gfc_find_function (sym->name);
1567
1568   if (isym)
1569     {
1570       if (sym->ts.type != BT_UNKNOWN && gfc_option.warn_surprising
1571           && !sym->attr.implicit_type)
1572         gfc_warning ("Type specified for intrinsic function '%s' at %L is"
1573                       " ignored", sym->name, &sym->declared_at);
1574
1575       if (!sym->attr.function &&
1576           gfc_add_function (&sym->attr, sym->name, loc) == FAILURE)
1577         return FAILURE;
1578
1579       sym->ts = isym->ts;
1580     }
1581   else if ((isym = gfc_find_subroutine (sym->name)))
1582     {
1583       if (sym->ts.type != BT_UNKNOWN && !sym->attr.implicit_type)
1584         {
1585           gfc_error ("Intrinsic subroutine '%s' at %L shall not have a type"
1586                       " specifier", sym->name, &sym->declared_at);
1587           return FAILURE;
1588         }
1589
1590       if (!sym->attr.subroutine &&
1591           gfc_add_subroutine (&sym->attr, sym->name, loc) == FAILURE)
1592         return FAILURE;
1593     }
1594   else
1595     {
1596       gfc_error ("'%s' declared INTRINSIC at %L does not exist", sym->name,
1597                  &sym->declared_at);
1598       return FAILURE;
1599     }
1600
1601   gfc_copy_formal_args_intr (sym, isym);
1602
1603   /* Check it is actually available in the standard settings.  */
1604   if (gfc_check_intrinsic_standard (isym, &symstd, false, sym->declared_at)
1605       == FAILURE)
1606     {
1607       gfc_error ("The intrinsic '%s' declared INTRINSIC at %L is not"
1608                  " available in the current standard settings but %s.  Use"
1609                  " an appropriate -std=* option or enable -fall-intrinsics"
1610                  " in order to use it.",
1611                  sym->name, &sym->declared_at, symstd);
1612       return FAILURE;
1613     }
1614
1615   return SUCCESS;
1616 }
1617
1618
1619 /* Resolve a procedure expression, like passing it to a called procedure or as
1620    RHS for a procedure pointer assignment.  */
1621
1622 static gfc_try
1623 resolve_procedure_expression (gfc_expr* expr)
1624 {
1625   gfc_symbol* sym;
1626
1627   if (expr->expr_type != EXPR_VARIABLE)
1628     return SUCCESS;
1629   gcc_assert (expr->symtree);
1630
1631   sym = expr->symtree->n.sym;
1632
1633   if (sym->attr.intrinsic)
1634     gfc_resolve_intrinsic (sym, &expr->where);
1635
1636   if (sym->attr.flavor != FL_PROCEDURE
1637       || (sym->attr.function && sym->result == sym))
1638     return SUCCESS;
1639
1640   /* A non-RECURSIVE procedure that is used as procedure expression within its
1641      own body is in danger of being called recursively.  */
1642   if (is_illegal_recursion (sym, gfc_current_ns))
1643     gfc_warning ("Non-RECURSIVE procedure '%s' at %L is possibly calling"
1644                  " itself recursively.  Declare it RECURSIVE or use"
1645                  " -frecursive", sym->name, &expr->where);
1646   
1647   return SUCCESS;
1648 }
1649
1650
1651 /* Resolve an actual argument list.  Most of the time, this is just
1652    resolving the expressions in the list.
1653    The exception is that we sometimes have to decide whether arguments
1654    that look like procedure arguments are really simple variable
1655    references.  */
1656
1657 static gfc_try
1658 resolve_actual_arglist (gfc_actual_arglist *arg, procedure_type ptype,
1659                         bool no_formal_args)
1660 {
1661   gfc_symbol *sym;
1662   gfc_symtree *parent_st;
1663   gfc_expr *e;
1664   int save_need_full_assumed_size;
1665   gfc_try return_value = FAILURE;
1666   bool actual_arg_sav = actual_arg, first_actual_arg_sav = first_actual_arg;
1667
1668   actual_arg = true;
1669   first_actual_arg = true;
1670
1671   for (; arg; arg = arg->next)
1672     {
1673       e = arg->expr;
1674       if (e == NULL)
1675         {
1676           /* Check the label is a valid branching target.  */
1677           if (arg->label)
1678             {
1679               if (arg->label->defined == ST_LABEL_UNKNOWN)
1680                 {
1681                   gfc_error ("Label %d referenced at %L is never defined",
1682                              arg->label->value, &arg->label->where);
1683                   goto cleanup;
1684                 }
1685             }
1686           first_actual_arg = false;
1687           continue;
1688         }
1689
1690       if (e->expr_type == EXPR_VARIABLE
1691             && e->symtree->n.sym->attr.generic
1692             && no_formal_args
1693             && count_specific_procs (e) != 1)
1694         goto cleanup;
1695
1696       if (e->ts.type != BT_PROCEDURE)
1697         {
1698           save_need_full_assumed_size = need_full_assumed_size;
1699           if (e->expr_type != EXPR_VARIABLE)
1700             need_full_assumed_size = 0;
1701           if (gfc_resolve_expr (e) != SUCCESS)
1702             goto cleanup;
1703           need_full_assumed_size = save_need_full_assumed_size;
1704           goto argument_list;
1705         }
1706
1707       /* See if the expression node should really be a variable reference.  */
1708
1709       sym = e->symtree->n.sym;
1710
1711       if (sym->attr.flavor == FL_PROCEDURE
1712           || sym->attr.intrinsic
1713           || sym->attr.external)
1714         {
1715           int actual_ok;
1716
1717           /* If a procedure is not already determined to be something else
1718              check if it is intrinsic.  */
1719           if (gfc_is_intrinsic (sym, sym->attr.subroutine, e->where))
1720             sym->attr.intrinsic = 1;
1721
1722           if (sym->attr.proc == PROC_ST_FUNCTION)
1723             {
1724               gfc_error ("Statement function '%s' at %L is not allowed as an "
1725                          "actual argument", sym->name, &e->where);
1726             }
1727
1728           actual_ok = gfc_intrinsic_actual_ok (sym->name,
1729                                                sym->attr.subroutine);
1730           if (sym->attr.intrinsic && actual_ok == 0)
1731             {
1732               gfc_error ("Intrinsic '%s' at %L is not allowed as an "
1733                          "actual argument", sym->name, &e->where);
1734             }
1735
1736           if (sym->attr.contained && !sym->attr.use_assoc
1737               && sym->ns->proc_name->attr.flavor != FL_MODULE)
1738             {
1739               if (gfc_notify_std (GFC_STD_F2008,
1740                                   "Internal procedure '%s' is"
1741                                   " used as actual argument at %L",
1742                                   sym->name, &e->where) == FAILURE)
1743                 goto cleanup;
1744             }
1745
1746           if (sym->attr.elemental && !sym->attr.intrinsic)
1747             {
1748               gfc_error ("ELEMENTAL non-INTRINSIC procedure '%s' is not "
1749                          "allowed as an actual argument at %L", sym->name,
1750                          &e->where);
1751             }
1752
1753           /* Check if a generic interface has a specific procedure
1754             with the same name before emitting an error.  */
1755           if (sym->attr.generic && count_specific_procs (e) != 1)
1756             goto cleanup;
1757
1758           /* Just in case a specific was found for the expression.  */
1759           sym = e->symtree->n.sym;
1760
1761           /* If the symbol is the function that names the current (or
1762              parent) scope, then we really have a variable reference.  */
1763
1764           if (gfc_is_function_return_value (sym, sym->ns))
1765             goto got_variable;
1766
1767           /* If all else fails, see if we have a specific intrinsic.  */
1768           if (sym->ts.type == BT_UNKNOWN && sym->attr.intrinsic)
1769             {
1770               gfc_intrinsic_sym *isym;
1771
1772               isym = gfc_find_function (sym->name);
1773               if (isym == NULL || !isym->specific)
1774                 {
1775                   gfc_error ("Unable to find a specific INTRINSIC procedure "
1776                              "for the reference '%s' at %L", sym->name,
1777                              &e->where);
1778                   goto cleanup;
1779                 }
1780               sym->ts = isym->ts;
1781               sym->attr.intrinsic = 1;
1782               sym->attr.function = 1;
1783             }
1784
1785           if (gfc_resolve_expr (e) == FAILURE)
1786             goto cleanup;
1787           goto argument_list;
1788         }
1789
1790       /* See if the name is a module procedure in a parent unit.  */
1791
1792       if (was_declared (sym) || sym->ns->parent == NULL)
1793         goto got_variable;
1794
1795       if (gfc_find_sym_tree (sym->name, sym->ns->parent, 1, &parent_st))
1796         {
1797           gfc_error ("Symbol '%s' at %L is ambiguous", sym->name, &e->where);
1798           goto cleanup;
1799         }
1800
1801       if (parent_st == NULL)
1802         goto got_variable;
1803
1804       sym = parent_st->n.sym;
1805       e->symtree = parent_st;           /* Point to the right thing.  */
1806
1807       if (sym->attr.flavor == FL_PROCEDURE
1808           || sym->attr.intrinsic
1809           || sym->attr.external)
1810         {
1811           if (gfc_resolve_expr (e) == FAILURE)
1812             goto cleanup;
1813           goto argument_list;
1814         }
1815
1816     got_variable:
1817       e->expr_type = EXPR_VARIABLE;
1818       e->ts = sym->ts;
1819       if ((sym->as != NULL && sym->ts.type != BT_CLASS)
1820           || (sym->ts.type == BT_CLASS && sym->attr.class_ok
1821               && CLASS_DATA (sym)->as))
1822         {
1823           e->rank = sym->ts.type == BT_CLASS
1824                     ? CLASS_DATA (sym)->as->rank : sym->as->rank;
1825           e->ref = gfc_get_ref ();
1826           e->ref->type = REF_ARRAY;
1827           e->ref->u.ar.type = AR_FULL;
1828           e->ref->u.ar.as = sym->ts.type == BT_CLASS
1829                             ? CLASS_DATA (sym)->as : sym->as;
1830         }
1831
1832       /* Expressions are assigned a default ts.type of BT_PROCEDURE in
1833          primary.c (match_actual_arg). If above code determines that it
1834          is a  variable instead, it needs to be resolved as it was not
1835          done at the beginning of this function.  */
1836       save_need_full_assumed_size = need_full_assumed_size;
1837       if (e->expr_type != EXPR_VARIABLE)
1838         need_full_assumed_size = 0;
1839       if (gfc_resolve_expr (e) != SUCCESS)
1840         goto cleanup;
1841       need_full_assumed_size = save_need_full_assumed_size;
1842
1843     argument_list:
1844       /* Check argument list functions %VAL, %LOC and %REF.  There is
1845          nothing to do for %REF.  */
1846       if (arg->name && arg->name[0] == '%')
1847         {
1848           if (strncmp ("%VAL", arg->name, 4) == 0)
1849             {
1850               if (e->ts.type == BT_CHARACTER || e->ts.type == BT_DERIVED)
1851                 {
1852                   gfc_error ("By-value argument at %L is not of numeric "
1853                              "type", &e->where);
1854                   goto cleanup;
1855                 }
1856
1857               if (e->rank)
1858                 {
1859                   gfc_error ("By-value argument at %L cannot be an array or "
1860                              "an array section", &e->where);
1861                   goto cleanup;
1862                 }
1863
1864               /* Intrinsics are still PROC_UNKNOWN here.  However,
1865                  since same file external procedures are not resolvable
1866                  in gfortran, it is a good deal easier to leave them to
1867                  intrinsic.c.  */
1868               if (ptype != PROC_UNKNOWN
1869                   && ptype != PROC_DUMMY
1870                   && ptype != PROC_EXTERNAL
1871                   && ptype != PROC_MODULE)
1872                 {
1873                   gfc_error ("By-value argument at %L is not allowed "
1874                              "in this context", &e->where);
1875                   goto cleanup;
1876                 }
1877             }
1878
1879           /* Statement functions have already been excluded above.  */
1880           else if (strncmp ("%LOC", arg->name, 4) == 0
1881                    && e->ts.type == BT_PROCEDURE)
1882             {
1883               if (e->symtree->n.sym->attr.proc == PROC_INTERNAL)
1884                 {
1885                   gfc_error ("Passing internal procedure at %L by location "
1886                              "not allowed", &e->where);
1887                   goto cleanup;
1888                 }
1889             }
1890         }
1891
1892       /* Fortran 2008, C1237.  */
1893       if (e->expr_type == EXPR_VARIABLE && gfc_is_coindexed (e)
1894           && gfc_has_ultimate_pointer (e))
1895         {
1896           gfc_error ("Coindexed actual argument at %L with ultimate pointer "
1897                      "component", &e->where);
1898           goto cleanup;
1899         }
1900
1901       first_actual_arg = false;
1902     }
1903
1904   return_value = SUCCESS;
1905
1906 cleanup:
1907   actual_arg = actual_arg_sav;
1908   first_actual_arg = first_actual_arg_sav;
1909
1910   return return_value;
1911 }
1912
1913
1914 /* Do the checks of the actual argument list that are specific to elemental
1915    procedures.  If called with c == NULL, we have a function, otherwise if
1916    expr == NULL, we have a subroutine.  */
1917
1918 static gfc_try
1919 resolve_elemental_actual (gfc_expr *expr, gfc_code *c)
1920 {
1921   gfc_actual_arglist *arg0;
1922   gfc_actual_arglist *arg;
1923   gfc_symbol *esym = NULL;
1924   gfc_intrinsic_sym *isym = NULL;
1925   gfc_expr *e = NULL;
1926   gfc_intrinsic_arg *iformal = NULL;
1927   gfc_formal_arglist *eformal = NULL;
1928   bool formal_optional = false;
1929   bool set_by_optional = false;
1930   int i;
1931   int rank = 0;
1932
1933   /* Is this an elemental procedure?  */
1934   if (expr && expr->value.function.actual != NULL)
1935     {
1936       if (expr->value.function.esym != NULL
1937           && expr->value.function.esym->attr.elemental)
1938         {
1939           arg0 = expr->value.function.actual;
1940           esym = expr->value.function.esym;
1941         }
1942       else if (expr->value.function.isym != NULL
1943                && expr->value.function.isym->elemental)
1944         {
1945           arg0 = expr->value.function.actual;
1946           isym = expr->value.function.isym;
1947         }
1948       else
1949         return SUCCESS;
1950     }
1951   else if (c && c->ext.actual != NULL)
1952     {
1953       arg0 = c->ext.actual;
1954       
1955       if (c->resolved_sym)
1956         esym = c->resolved_sym;
1957       else
1958         esym = c->symtree->n.sym;
1959       gcc_assert (esym);
1960
1961       if (!esym->attr.elemental)
1962         return SUCCESS;
1963     }
1964   else
1965     return SUCCESS;
1966
1967   /* The rank of an elemental is the rank of its array argument(s).  */
1968   for (arg = arg0; arg; arg = arg->next)
1969     {
1970       if (arg->expr != NULL && arg->expr->rank != 0)
1971         {
1972           rank = arg->expr->rank;
1973           if (arg->expr->expr_type == EXPR_VARIABLE
1974               && arg->expr->symtree->n.sym->attr.optional)
1975             set_by_optional = true;
1976
1977           /* Function specific; set the result rank and shape.  */
1978           if (expr)
1979             {
1980               expr->rank = rank;
1981               if (!expr->shape && arg->expr->shape)
1982                 {
1983                   expr->shape = gfc_get_shape (rank);
1984                   for (i = 0; i < rank; i++)
1985                     mpz_init_set (expr->shape[i], arg->expr->shape[i]);
1986                 }
1987             }
1988           break;
1989         }
1990     }
1991
1992   /* If it is an array, it shall not be supplied as an actual argument
1993      to an elemental procedure unless an array of the same rank is supplied
1994      as an actual argument corresponding to a nonoptional dummy argument of
1995      that elemental procedure(12.4.1.5).  */
1996   formal_optional = false;
1997   if (isym)
1998     iformal = isym->formal;
1999   else
2000     eformal = esym->formal;
2001
2002   for (arg = arg0; arg; arg = arg->next)
2003     {
2004       if (eformal)
2005         {
2006           if (eformal->sym && eformal->sym->attr.optional)
2007             formal_optional = true;
2008           eformal = eformal->next;
2009         }
2010       else if (isym && iformal)
2011         {
2012           if (iformal->optional)
2013             formal_optional = true;
2014           iformal = iformal->next;
2015         }
2016       else if (isym)
2017         formal_optional = true;
2018
2019       if (pedantic && arg->expr != NULL
2020           && arg->expr->expr_type == EXPR_VARIABLE
2021           && arg->expr->symtree->n.sym->attr.optional
2022           && formal_optional
2023           && arg->expr->rank
2024           && (set_by_optional || arg->expr->rank != rank)
2025           && !(isym && isym->id == GFC_ISYM_CONVERSION))
2026         {
2027           gfc_warning ("'%s' at %L is an array and OPTIONAL; IF IT IS "
2028                        "MISSING, it cannot be the actual argument of an "
2029                        "ELEMENTAL procedure unless there is a non-optional "
2030                        "argument with the same rank (12.4.1.5)",
2031                        arg->expr->symtree->n.sym->name, &arg->expr->where);
2032         }
2033     }
2034
2035   for (arg = arg0; arg; arg = arg->next)
2036     {
2037       if (arg->expr == NULL || arg->expr->rank == 0)
2038         continue;
2039
2040       /* Being elemental, the last upper bound of an assumed size array
2041          argument must be present.  */
2042       if (resolve_assumed_size_actual (arg->expr))
2043         return FAILURE;
2044
2045       /* Elemental procedure's array actual arguments must conform.  */
2046       if (e != NULL)
2047         {
2048           if (gfc_check_conformance (arg->expr, e,
2049                                      "elemental procedure") == FAILURE)
2050             return FAILURE;
2051         }
2052       else
2053         e = arg->expr;
2054     }
2055
2056   /* INTENT(OUT) is only allowed for subroutines; if any actual argument
2057      is an array, the intent inout/out variable needs to be also an array.  */
2058   if (rank > 0 && esym && expr == NULL)
2059     for (eformal = esym->formal, arg = arg0; arg && eformal;
2060          arg = arg->next, eformal = eformal->next)
2061       if ((eformal->sym->attr.intent == INTENT_OUT
2062            || eformal->sym->attr.intent == INTENT_INOUT)
2063           && arg->expr && arg->expr->rank == 0)
2064         {
2065           gfc_error ("Actual argument at %L for INTENT(%s) dummy '%s' of "
2066                      "ELEMENTAL subroutine '%s' is a scalar, but another "
2067                      "actual argument is an array", &arg->expr->where,
2068                      (eformal->sym->attr.intent == INTENT_OUT) ? "OUT"
2069                      : "INOUT", eformal->sym->name, esym->name);
2070           return FAILURE;
2071         }
2072   return SUCCESS;
2073 }
2074
2075
2076 /* This function does the checking of references to global procedures
2077    as defined in sections 18.1 and 14.1, respectively, of the Fortran
2078    77 and 95 standards.  It checks for a gsymbol for the name, making
2079    one if it does not already exist.  If it already exists, then the
2080    reference being resolved must correspond to the type of gsymbol.
2081    Otherwise, the new symbol is equipped with the attributes of the
2082    reference.  The corresponding code that is called in creating
2083    global entities is parse.c.
2084
2085    In addition, for all but -std=legacy, the gsymbols are used to
2086    check the interfaces of external procedures from the same file.
2087    The namespace of the gsymbol is resolved and then, once this is
2088    done the interface is checked.  */
2089
2090
2091 static bool
2092 not_in_recursive (gfc_symbol *sym, gfc_namespace *gsym_ns)
2093 {
2094   if (!gsym_ns->proc_name->attr.recursive)
2095     return true;
2096
2097   if (sym->ns == gsym_ns)
2098     return false;
2099
2100   if (sym->ns->parent && sym->ns->parent == gsym_ns)
2101     return false;
2102
2103   return true;
2104 }
2105
2106 static bool
2107 not_entry_self_reference  (gfc_symbol *sym, gfc_namespace *gsym_ns)
2108 {
2109   if (gsym_ns->entries)
2110     {
2111       gfc_entry_list *entry = gsym_ns->entries;
2112
2113       for (; entry; entry = entry->next)
2114         {
2115           if (strcmp (sym->name, entry->sym->name) == 0)
2116             {
2117               if (strcmp (gsym_ns->proc_name->name,
2118                           sym->ns->proc_name->name) == 0)
2119                 return false;
2120
2121               if (sym->ns->parent
2122                   && strcmp (gsym_ns->proc_name->name,
2123                              sym->ns->parent->proc_name->name) == 0)
2124                 return false;
2125             }
2126         }
2127     }
2128   return true;
2129 }
2130
2131 static void
2132 resolve_global_procedure (gfc_symbol *sym, locus *where,
2133                           gfc_actual_arglist **actual, int sub)
2134 {
2135   gfc_gsymbol * gsym;
2136   gfc_namespace *ns;
2137   enum gfc_symbol_type type;
2138
2139   type = sub ? GSYM_SUBROUTINE : GSYM_FUNCTION;
2140
2141   gsym = gfc_get_gsymbol (sym->name);
2142
2143   if ((gsym->type != GSYM_UNKNOWN && gsym->type != type))
2144     gfc_global_used (gsym, where);
2145
2146   if (gfc_option.flag_whole_file
2147         && (sym->attr.if_source == IFSRC_UNKNOWN
2148             || sym->attr.if_source == IFSRC_IFBODY)
2149         && gsym->type != GSYM_UNKNOWN
2150         && gsym->ns
2151         && gsym->ns->resolved != -1
2152         && gsym->ns->proc_name
2153         && not_in_recursive (sym, gsym->ns)
2154         && not_entry_self_reference (sym, gsym->ns))
2155     {
2156       gfc_symbol *def_sym;
2157
2158       /* Resolve the gsymbol namespace if needed.  */
2159       if (!gsym->ns->resolved)
2160         {
2161           gfc_dt_list *old_dt_list;
2162           struct gfc_omp_saved_state old_omp_state;
2163
2164           /* Stash away derived types so that the backend_decls do not
2165              get mixed up.  */
2166           old_dt_list = gfc_derived_types;
2167           gfc_derived_types = NULL;
2168           /* And stash away openmp state.  */
2169           gfc_omp_save_and_clear_state (&old_omp_state);
2170
2171           gfc_resolve (gsym->ns);
2172
2173           /* Store the new derived types with the global namespace.  */
2174           if (gfc_derived_types)
2175             gsym->ns->derived_types = gfc_derived_types;
2176
2177           /* Restore the derived types of this namespace.  */
2178           gfc_derived_types = old_dt_list;
2179           /* And openmp state.  */
2180           gfc_omp_restore_state (&old_omp_state);
2181         }
2182
2183       /* Make sure that translation for the gsymbol occurs before
2184          the procedure currently being resolved.  */
2185       ns = gfc_global_ns_list;
2186       for (; ns && ns != gsym->ns; ns = ns->sibling)
2187         {
2188           if (ns->sibling == gsym->ns)
2189             {
2190               ns->sibling = gsym->ns->sibling;
2191               gsym->ns->sibling = gfc_global_ns_list;
2192               gfc_global_ns_list = gsym->ns;
2193               break;
2194             }
2195         }
2196
2197       def_sym = gsym->ns->proc_name;
2198       if (def_sym->attr.entry_master)
2199         {
2200           gfc_entry_list *entry;
2201           for (entry = gsym->ns->entries; entry; entry = entry->next)
2202             if (strcmp (entry->sym->name, sym->name) == 0)
2203               {
2204                 def_sym = entry->sym;
2205                 break;
2206               }
2207         }
2208
2209       /* Differences in constant character lengths.  */
2210       if (sym->attr.function && sym->ts.type == BT_CHARACTER)
2211         {
2212           long int l1 = 0, l2 = 0;
2213           gfc_charlen *cl1 = sym->ts.u.cl;
2214           gfc_charlen *cl2 = def_sym->ts.u.cl;
2215
2216           if (cl1 != NULL
2217               && cl1->length != NULL
2218               && cl1->length->expr_type == EXPR_CONSTANT)
2219             l1 = mpz_get_si (cl1->length->value.integer);
2220
2221           if (cl2 != NULL
2222               && cl2->length != NULL
2223               && cl2->length->expr_type == EXPR_CONSTANT)
2224             l2 = mpz_get_si (cl2->length->value.integer);
2225
2226           if (l1 && l2 && l1 != l2)
2227             gfc_error ("Character length mismatch in return type of "
2228                        "function '%s' at %L (%ld/%ld)", sym->name,
2229                        &sym->declared_at, l1, l2);
2230         }
2231
2232      /* Type mismatch of function return type and expected type.  */
2233      if (sym->attr.function
2234          && !gfc_compare_types (&sym->ts, &def_sym->ts))
2235         gfc_error ("Return type mismatch of function '%s' at %L (%s/%s)",
2236                    sym->name, &sym->declared_at, gfc_typename (&sym->ts),
2237                    gfc_typename (&def_sym->ts));
2238
2239       if (def_sym->formal && sym->attr.if_source != IFSRC_IFBODY)
2240         {
2241           gfc_formal_arglist *arg = def_sym->formal;
2242           for ( ; arg; arg = arg->next)
2243             if (!arg->sym)
2244               continue;
2245             /* F2003, 12.3.1.1 (2a); F2008, 12.4.2.2 (2a)  */
2246             else if (arg->sym->attr.allocatable
2247                      || arg->sym->attr.asynchronous
2248                      || arg->sym->attr.optional
2249                      || arg->sym->attr.pointer
2250                      || arg->sym->attr.target
2251                      || arg->sym->attr.value
2252                      || arg->sym->attr.volatile_)
2253               {
2254                 gfc_error ("Dummy argument '%s' of procedure '%s' at %L "
2255                            "has an attribute that requires an explicit "
2256                            "interface for this procedure", arg->sym->name,
2257                            sym->name, &sym->declared_at);
2258                 break;
2259               }
2260             /* F2003, 12.3.1.1 (2b); F2008, 12.4.2.2 (2b)  */
2261             else if (arg->sym && arg->sym->as
2262                      && arg->sym->as->type == AS_ASSUMED_SHAPE)
2263               {
2264                 gfc_error ("Procedure '%s' at %L with assumed-shape dummy "
2265                            "argument '%s' must have an explicit interface",
2266                            sym->name, &sym->declared_at, arg->sym->name);
2267                 break;
2268               }
2269             /* TS 29113, 6.2.  */
2270             else if (arg->sym && arg->sym->as
2271                      && arg->sym->as->type == AS_ASSUMED_RANK)
2272               {
2273                 gfc_error ("Procedure '%s' at %L with assumed-rank dummy "
2274                            "argument '%s' must have an explicit interface",
2275                            sym->name, &sym->declared_at, arg->sym->name);
2276                 break;
2277               }
2278             /* F2008, 12.4.2.2 (2c)  */
2279             else if (arg->sym->attr.codimension)
2280               {
2281                 gfc_error ("Procedure '%s' at %L with coarray dummy argument "
2282                            "'%s' must have an explicit interface",
2283                            sym->name, &sym->declared_at, arg->sym->name);
2284                 break;
2285               }
2286             /* F2003, 12.3.1.1 (2c); F2008, 12.4.2.2 (2d)   */
2287             else if (false) /* TODO: is a parametrized derived type  */
2288               {
2289                 gfc_error ("Procedure '%s' at %L with parametrized derived "
2290                            "type argument '%s' must have an explicit "
2291                            "interface", sym->name, &sym->declared_at,
2292                            arg->sym->name);
2293                 break;
2294               }
2295             /* F2003, 12.3.1.1 (2d); F2008, 12.4.2.2 (2e)   */
2296             else if (arg->sym->ts.type == BT_CLASS)
2297               {
2298                 gfc_error ("Procedure '%s' at %L with polymorphic dummy "
2299                            "argument '%s' must have an explicit interface",
2300                            sym->name, &sym->declared_at, arg->sym->name);
2301                 break;
2302               }
2303             /* As assumed-type is unlimited polymorphic (cf. above).
2304                See also  TS 29113, Note 6.1.  */
2305             else if (arg->sym->ts.type == BT_ASSUMED)
2306               {
2307                 gfc_error ("Procedure '%s' at %L with assumed-type dummy "
2308                            "argument '%s' must have an explicit interface",
2309                            sym->name, &sym->declared_at, arg->sym->name);
2310                 break;
2311               }
2312         }
2313
2314       if (def_sym->attr.function)
2315         {
2316           /* F2003, 12.3.1.1 (3a); F2008, 12.4.2.2 (3a) */
2317           if (def_sym->as && def_sym->as->rank
2318               && (!sym->as || sym->as->rank != def_sym->as->rank))
2319             gfc_error ("The reference to function '%s' at %L either needs an "
2320                        "explicit INTERFACE or the rank is incorrect", sym->name,
2321                        where);
2322
2323           /* F2003, 12.3.1.1 (3b); F2008, 12.4.2.2 (3b) */
2324           if ((def_sym->result->attr.pointer
2325                || def_sym->result->attr.allocatable)
2326                && (sym->attr.if_source != IFSRC_IFBODY
2327                    || def_sym->result->attr.pointer
2328                         != sym->result->attr.pointer
2329                    || def_sym->result->attr.allocatable
2330                         != sym->result->attr.allocatable))
2331             gfc_error ("Function '%s' at %L with a POINTER or ALLOCATABLE "
2332                        "result must have an explicit interface", sym->name,
2333                        where);
2334
2335           /* F2003, 12.3.1.1 (3c); F2008, 12.4.2.2 (3c)  */
2336           if (sym->ts.type == BT_CHARACTER && sym->attr.if_source != IFSRC_IFBODY
2337               && def_sym->ts.type == BT_CHARACTER && def_sym->ts.u.cl->length != NULL)
2338             {
2339               gfc_charlen *cl = sym->ts.u.cl;
2340
2341               if (!sym->attr.entry_master && sym->attr.if_source == IFSRC_UNKNOWN
2342                   && cl && cl->length && cl->length->expr_type != EXPR_CONSTANT)
2343                 {
2344                   gfc_error ("Nonconstant character-length function '%s' at %L "
2345                              "must have an explicit interface", sym->name,
2346                              &sym->declared_at);
2347                 }
2348             }
2349         }
2350
2351       /* F2003, 12.3.1.1 (4); F2008, 12.4.2.2 (4) */
2352       if (def_sym->attr.elemental && !sym->attr.elemental)
2353         {
2354           gfc_error ("ELEMENTAL procedure '%s' at %L must have an explicit "
2355                      "interface", sym->name, &sym->declared_at);
2356         }
2357
2358       /* F2003, 12.3.1.1 (5); F2008, 12.4.2.2 (5) */
2359       if (def_sym->attr.is_bind_c && !sym->attr.is_bind_c)
2360         {
2361           gfc_error ("Procedure '%s' at %L with BIND(C) attribute must have "
2362                      "an explicit interface", sym->name, &sym->declared_at);
2363         }
2364
2365       if (gfc_option.flag_whole_file == 1
2366           || ((gfc_option.warn_std & GFC_STD_LEGACY)
2367               && !(gfc_option.warn_std & GFC_STD_GNU)))
2368         gfc_errors_to_warnings (1);
2369
2370       if (sym->attr.if_source != IFSRC_IFBODY)  
2371         gfc_procedure_use (def_sym, actual, where);
2372
2373       gfc_errors_to_warnings (0);
2374     }
2375
2376   if (gsym->type == GSYM_UNKNOWN)
2377     {
2378       gsym->type = type;
2379       gsym->where = *where;
2380     }
2381
2382   gsym->used = 1;
2383 }
2384
2385
2386 /************* Function resolution *************/
2387
2388 /* Resolve a function call known to be generic.
2389    Section 14.1.2.4.1.  */
2390
2391 static match
2392 resolve_generic_f0 (gfc_expr *expr, gfc_symbol *sym)
2393 {
2394   gfc_symbol *s;
2395
2396   if (sym->attr.generic)
2397     {
2398       s = gfc_search_interface (sym->generic, 0, &expr->value.function.actual);
2399       if (s != NULL)
2400         {
2401           expr->value.function.name = s->name;
2402           expr->value.function.esym = s;
2403
2404           if (s->ts.type != BT_UNKNOWN)
2405             expr->ts = s->ts;
2406           else if (s->result != NULL && s->result->ts.type != BT_UNKNOWN)
2407             expr->ts = s->result->ts;
2408
2409           if (s->as != NULL)
2410             expr->rank = s->as->rank;
2411           else if (s->result != NULL && s->result->as != NULL)
2412             expr->rank = s->result->as->rank;
2413
2414           gfc_set_sym_referenced (expr->value.function.esym);
2415
2416           return MATCH_YES;
2417         }
2418
2419       /* TODO: Need to search for elemental references in generic
2420          interface.  */
2421     }
2422
2423   if (sym->attr.intrinsic)
2424     return gfc_intrinsic_func_interface (expr, 0);
2425
2426   return MATCH_NO;
2427 }
2428
2429
2430 static gfc_try
2431 resolve_generic_f (gfc_expr *expr)
2432 {
2433   gfc_symbol *sym;
2434   match m;
2435   gfc_interface *intr = NULL;
2436
2437   sym = expr->symtree->n.sym;
2438
2439   for (;;)
2440     {
2441       m = resolve_generic_f0 (expr, sym);
2442       if (m == MATCH_YES)
2443         return SUCCESS;
2444       else if (m == MATCH_ERROR)
2445         return FAILURE;
2446
2447 generic:
2448       if (!intr)
2449         for (intr = sym->generic; intr; intr = intr->next)
2450           if (intr->sym->attr.flavor == FL_DERIVED)
2451             break;
2452
2453       if (sym->ns->parent == NULL)
2454         break;
2455       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2456
2457       if (sym == NULL)
2458         break;
2459       if (!generic_sym (sym))
2460         goto generic;
2461     }
2462
2463   /* Last ditch attempt.  See if the reference is to an intrinsic
2464      that possesses a matching interface.  14.1.2.4  */
2465   if (sym  && !intr && !gfc_is_intrinsic (sym, 0, expr->where))
2466     {
2467       gfc_error ("There is no specific function for the generic '%s' "
2468                  "at %L", expr->symtree->n.sym->name, &expr->where);
2469       return FAILURE;
2470     }
2471
2472   if (intr)
2473     {
2474       if (gfc_convert_to_structure_constructor (expr, intr->sym, NULL, NULL,
2475                                                 false) != SUCCESS)
2476         return FAILURE;
2477       return resolve_structure_cons (expr, 0);
2478     }
2479
2480   m = gfc_intrinsic_func_interface (expr, 0);
2481   if (m == MATCH_YES)
2482     return SUCCESS;
2483
2484   if (m == MATCH_NO)
2485     gfc_error ("Generic function '%s' at %L is not consistent with a "
2486                "specific intrinsic interface", expr->symtree->n.sym->name,
2487                &expr->where);
2488
2489   return FAILURE;
2490 }
2491
2492
2493 /* Resolve a function call known to be specific.  */
2494
2495 static match
2496 resolve_specific_f0 (gfc_symbol *sym, gfc_expr *expr)
2497 {
2498   match m;
2499
2500   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
2501     {
2502       if (sym->attr.dummy)
2503         {
2504           sym->attr.proc = PROC_DUMMY;
2505           goto found;
2506         }
2507
2508       sym->attr.proc = PROC_EXTERNAL;
2509       goto found;
2510     }
2511
2512   if (sym->attr.proc == PROC_MODULE
2513       || sym->attr.proc == PROC_ST_FUNCTION
2514       || sym->attr.proc == PROC_INTERNAL)
2515     goto found;
2516
2517   if (sym->attr.intrinsic)
2518     {
2519       m = gfc_intrinsic_func_interface (expr, 1);
2520       if (m == MATCH_YES)
2521         return MATCH_YES;
2522       if (m == MATCH_NO)
2523         gfc_error ("Function '%s' at %L is INTRINSIC but is not compatible "
2524                    "with an intrinsic", sym->name, &expr->where);
2525
2526       return MATCH_ERROR;
2527     }
2528
2529   return MATCH_NO;
2530
2531 found:
2532   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2533
2534   if (sym->result)
2535     expr->ts = sym->result->ts;
2536   else
2537     expr->ts = sym->ts;
2538   expr->value.function.name = sym->name;
2539   expr->value.function.esym = sym;
2540   if (sym->as != NULL)
2541     expr->rank = sym->as->rank;
2542
2543   return MATCH_YES;
2544 }
2545
2546
2547 static gfc_try
2548 resolve_specific_f (gfc_expr *expr)
2549 {
2550   gfc_symbol *sym;
2551   match m;
2552
2553   sym = expr->symtree->n.sym;
2554
2555   for (;;)
2556     {
2557       m = resolve_specific_f0 (sym, expr);
2558       if (m == MATCH_YES)
2559         return SUCCESS;
2560       if (m == MATCH_ERROR)
2561         return FAILURE;
2562
2563       if (sym->ns->parent == NULL)
2564         break;
2565
2566       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2567
2568       if (sym == NULL)
2569         break;
2570     }
2571
2572   gfc_error ("Unable to resolve the specific function '%s' at %L",
2573              expr->symtree->n.sym->name, &expr->where);
2574
2575   return SUCCESS;
2576 }
2577
2578
2579 /* Resolve a procedure call not known to be generic nor specific.  */
2580
2581 static gfc_try
2582 resolve_unknown_f (gfc_expr *expr)
2583 {
2584   gfc_symbol *sym;
2585   gfc_typespec *ts;
2586
2587   sym = expr->symtree->n.sym;
2588
2589   if (sym->attr.dummy)
2590     {
2591       sym->attr.proc = PROC_DUMMY;
2592       expr->value.function.name = sym->name;
2593       goto set_type;
2594     }
2595
2596   /* See if we have an intrinsic function reference.  */
2597
2598   if (gfc_is_intrinsic (sym, 0, expr->where))
2599     {
2600       if (gfc_intrinsic_func_interface (expr, 1) == MATCH_YES)
2601         return SUCCESS;
2602       return FAILURE;
2603     }
2604
2605   /* The reference is to an external name.  */
2606
2607   sym->attr.proc = PROC_EXTERNAL;
2608   expr->value.function.name = sym->name;
2609   expr->value.function.esym = expr->symtree->n.sym;
2610
2611   if (sym->as != NULL)
2612     expr->rank = sym->as->rank;
2613
2614   /* Type of the expression is either the type of the symbol or the
2615      default type of the symbol.  */
2616
2617 set_type:
2618   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2619
2620   if (sym->ts.type != BT_UNKNOWN)
2621     expr->ts = sym->ts;
2622   else
2623     {
2624       ts = gfc_get_default_type (sym->name, sym->ns);
2625
2626       if (ts->type == BT_UNKNOWN)
2627         {
2628           gfc_error ("Function '%s' at %L has no IMPLICIT type",
2629                      sym->name, &expr->where);
2630           return FAILURE;
2631         }
2632       else
2633         expr->ts = *ts;
2634     }
2635
2636   return SUCCESS;
2637 }
2638
2639
2640 /* Return true, if the symbol is an external procedure.  */
2641 static bool
2642 is_external_proc (gfc_symbol *sym)
2643 {
2644   if (!sym->attr.dummy && !sym->attr.contained
2645         && !gfc_is_intrinsic (sym, sym->attr.subroutine, sym->declared_at)
2646         && sym->attr.proc != PROC_ST_FUNCTION
2647         && !sym->attr.proc_pointer
2648         && !sym->attr.use_assoc
2649         && sym->name)
2650     return true;
2651
2652   return false;
2653 }
2654
2655
2656 /* Figure out if a function reference is pure or not.  Also set the name
2657    of the function for a potential error message.  Return nonzero if the
2658    function is PURE, zero if not.  */
2659 static int
2660 pure_stmt_function (gfc_expr *, gfc_symbol *);
2661
2662 static int
2663 pure_function (gfc_expr *e, const char **name)
2664 {
2665   int pure;
2666
2667   *name = NULL;
2668
2669   if (e->symtree != NULL
2670         && e->symtree->n.sym != NULL
2671         && e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2672     return pure_stmt_function (e, e->symtree->n.sym);
2673
2674   if (e->value.function.esym)
2675     {
2676       pure = gfc_pure (e->value.function.esym);
2677       *name = e->value.function.esym->name;
2678     }
2679   else if (e->value.function.isym)
2680     {
2681       pure = e->value.function.isym->pure
2682              || e->value.function.isym->elemental;
2683       *name = e->value.function.isym->name;
2684     }
2685   else
2686     {
2687       /* Implicit functions are not pure.  */
2688       pure = 0;
2689       *name = e->value.function.name;
2690     }
2691
2692   return pure;
2693 }
2694
2695
2696 static bool
2697 impure_stmt_fcn (gfc_expr *e, gfc_symbol *sym,
2698                  int *f ATTRIBUTE_UNUSED)
2699 {
2700   const char *name;
2701
2702   /* Don't bother recursing into other statement functions
2703      since they will be checked individually for purity.  */
2704   if (e->expr_type != EXPR_FUNCTION
2705         || !e->symtree
2706         || e->symtree->n.sym == sym
2707         || e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2708     return false;
2709
2710   return pure_function (e, &name) ? false : true;
2711 }
2712
2713
2714 static int
2715 pure_stmt_function (gfc_expr *e, gfc_symbol *sym)
2716 {
2717   return gfc_traverse_expr (e, sym, impure_stmt_fcn, 0) ? 0 : 1;
2718 }
2719
2720
2721 static gfc_try
2722 is_scalar_expr_ptr (gfc_expr *expr)
2723 {
2724   gfc_try retval = SUCCESS;
2725   gfc_ref *ref;
2726   int start;
2727   int end;
2728
2729   /* See if we have a gfc_ref, which means we have a substring, array
2730      reference, or a component.  */
2731   if (expr->ref != NULL)
2732     {
2733       ref = expr->ref;
2734       while (ref->next != NULL)
2735         ref = ref->next;
2736
2737       switch (ref->type)
2738         {
2739         case REF_SUBSTRING:
2740           if (ref->u.ss.start == NULL || ref->u.ss.end == NULL
2741               || gfc_dep_compare_expr (ref->u.ss.start, ref->u.ss.end) != 0)
2742             retval = FAILURE;
2743           break;
2744
2745         case REF_ARRAY:
2746           if (ref->u.ar.type == AR_ELEMENT)
2747             retval = SUCCESS;
2748           else if (ref->u.ar.type == AR_FULL)
2749             {
2750               /* The user can give a full array if the array is of size 1.  */
2751               if (ref->u.ar.as != NULL
2752                   && ref->u.ar.as->rank == 1
2753                   && ref->u.ar.as->type == AS_EXPLICIT
2754                   && ref->u.ar.as->lower[0] != NULL
2755                   && ref->u.ar.as->lower[0]->expr_type == EXPR_CONSTANT
2756                   && ref->u.ar.as->upper[0] != NULL
2757                   && ref->u.ar.as->upper[0]->expr_type == EXPR_CONSTANT)
2758                 {
2759                   /* If we have a character string, we need to check if
2760                      its length is one.  */
2761                   if (expr->ts.type == BT_CHARACTER)
2762                     {
2763                       if (expr->ts.u.cl == NULL
2764                           || expr->ts.u.cl->length == NULL
2765                           || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1)
2766                           != 0)
2767                         retval = FAILURE;
2768                     }
2769                   else
2770                     {
2771                       /* We have constant lower and upper bounds.  If the
2772                          difference between is 1, it can be considered a
2773                          scalar.  
2774                          FIXME: Use gfc_dep_compare_expr instead.  */
2775                       start = (int) mpz_get_si
2776                                 (ref->u.ar.as->lower[0]->value.integer);
2777                       end = (int) mpz_get_si
2778                                 (ref->u.ar.as->upper[0]->value.integer);
2779                       if (end - start + 1 != 1)
2780                         retval = FAILURE;
2781                    }
2782                 }
2783               else
2784                 retval = FAILURE;
2785             }
2786           else
2787             retval = FAILURE;
2788           break;
2789         default:
2790           retval = SUCCESS;
2791           break;
2792         }
2793     }
2794   else if (expr->ts.type == BT_CHARACTER && expr->rank == 0)
2795     {
2796       /* Character string.  Make sure it's of length 1.  */
2797       if (expr->ts.u.cl == NULL
2798           || expr->ts.u.cl->length == NULL
2799           || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1) != 0)
2800         retval = FAILURE;
2801     }
2802   else if (expr->rank != 0)
2803     retval = FAILURE;
2804
2805   return retval;
2806 }
2807
2808
2809 /* Match one of the iso_c_binding functions (c_associated or c_loc)
2810    and, in the case of c_associated, set the binding label based on
2811    the arguments.  */
2812
2813 static gfc_try
2814 gfc_iso_c_func_interface (gfc_symbol *sym, gfc_actual_arglist *args,
2815                           gfc_symbol **new_sym)
2816 {
2817   char name[GFC_MAX_SYMBOL_LEN + 1];
2818   int optional_arg = 0;
2819   gfc_try retval = SUCCESS;
2820   gfc_symbol *args_sym;
2821   gfc_typespec *arg_ts;
2822   symbol_attribute arg_attr;
2823
2824   if (args->expr->expr_type == EXPR_CONSTANT
2825       || args->expr->expr_type == EXPR_OP
2826       || args->expr->expr_type == EXPR_NULL)
2827     {
2828       gfc_error ("Argument to '%s' at %L is not a variable",
2829                  sym->name, &(args->expr->where));
2830       return FAILURE;
2831     }
2832
2833   args_sym = args->expr->symtree->n.sym;
2834
2835   /* The typespec for the actual arg should be that stored in the expr
2836      and not necessarily that of the expr symbol (args_sym), because
2837      the actual expression could be a part-ref of the expr symbol.  */
2838   arg_ts = &(args->expr->ts);
2839   arg_attr = gfc_expr_attr (args->expr);
2840     
2841   if (sym->intmod_sym_id == ISOCBINDING_ASSOCIATED)
2842     {
2843       /* If the user gave two args then they are providing something for
2844          the optional arg (the second cptr).  Therefore, set the name and
2845          binding label to the c_associated for two cptrs.  Otherwise,
2846          set c_associated to expect one cptr.  */
2847       if (args->next)
2848         {
2849           /* two args.  */
2850           sprintf (name, "%s_2", sym->name);
2851           optional_arg = 1;
2852         }
2853       else
2854         {
2855           /* one arg.  */
2856           sprintf (name, "%s_1", sym->name);
2857           optional_arg = 0;
2858         }
2859
2860       /* Get a new symbol for the version of c_associated that
2861          will get called.  */
2862       *new_sym = get_iso_c_sym (sym, name, NULL, optional_arg);
2863     }
2864   else if (sym->intmod_sym_id == ISOCBINDING_LOC
2865            || sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2866     {
2867       sprintf (name, "%s", sym->name);
2868
2869       /* Error check the call.  */
2870       if (args->next != NULL)
2871         {
2872           gfc_error_now ("More actual than formal arguments in '%s' "
2873                          "call at %L", name, &(args->expr->where));
2874           retval = FAILURE;
2875         }
2876       else if (sym->intmod_sym_id == ISOCBINDING_LOC)
2877         {
2878           gfc_ref *ref;
2879           bool seen_section;
2880
2881           /* Make sure we have either the target or pointer attribute.  */
2882           if (!arg_attr.target && !arg_attr.pointer)
2883             {
2884               gfc_error_now ("Parameter '%s' to '%s' at %L must be either "
2885                              "a TARGET or an associated pointer",
2886                              args_sym->name,
2887                              sym->name, &(args->expr->where));
2888               retval = FAILURE;
2889             }
2890
2891           if (gfc_is_coindexed (args->expr))
2892             {
2893               gfc_error_now ("Coindexed argument not permitted"
2894                              " in '%s' call at %L", name,
2895                              &(args->expr->where));
2896               retval = FAILURE;
2897             }
2898
2899           /* Follow references to make sure there are no array
2900              sections.  */
2901           seen_section = false;
2902
2903           for (ref=args->expr->ref; ref; ref = ref->next)
2904             {
2905               if (ref->type == REF_ARRAY)
2906                 {
2907                   if (ref->u.ar.type == AR_SECTION)
2908                     seen_section = true;
2909
2910                   if (ref->u.ar.type != AR_ELEMENT)
2911                     {
2912                       gfc_ref *r;
2913                       for (r = ref->next; r; r=r->next)
2914                         if (r->type == REF_COMPONENT)
2915                           {
2916                             gfc_error_now ("Array section not permitted"
2917                                            " in '%s' call at %L", name,
2918                                            &(args->expr->where));
2919                             retval = FAILURE;
2920                             break;
2921                           }
2922                     }
2923                 }
2924             }
2925
2926           if (seen_section && retval == SUCCESS)
2927             gfc_warning ("Array section in '%s' call at %L", name,
2928                          &(args->expr->where));
2929                          
2930           /* See if we have interoperable type and type param.  */
2931           if (gfc_verify_c_interop (arg_ts) == SUCCESS
2932               || gfc_check_any_c_kind (arg_ts) == SUCCESS)
2933             {
2934               if (args_sym->attr.target == 1)
2935                 {
2936                   /* Case 1a, section 15.1.2.5, J3/04-007: variable that
2937                      has the target attribute and is interoperable.  */
2938                   /* Case 1b, section 15.1.2.5, J3/04-007: allocated
2939                      allocatable variable that has the TARGET attribute and
2940                      is not an array of zero size.  */
2941                   if (args_sym->attr.allocatable == 1)
2942                     {
2943                       if (args_sym->attr.dimension != 0 
2944                           && (args_sym->as && args_sym->as->rank == 0))
2945                         {
2946                           gfc_error_now ("Allocatable variable '%s' used as a "
2947                                          "parameter to '%s' at %L must not be "
2948                                          "an array of zero size",
2949                                          args_sym->name, sym->name,
2950                                          &(args->expr->where));
2951                           retval = FAILURE;
2952                         }
2953                     }
2954                   else
2955                     {
2956                       /* A non-allocatable target variable with C
2957                          interoperable type and type parameters must be
2958                          interoperable.  */
2959                       if (args_sym && args_sym->attr.dimension)
2960                         {
2961                           if (args_sym->as->type == AS_ASSUMED_SHAPE)
2962                             {
2963                               gfc_error ("Assumed-shape array '%s' at %L "
2964                                          "cannot be an argument to the "
2965                                          "procedure '%s' because "
2966                                          "it is not C interoperable",
2967                                          args_sym->name,
2968                                          &(args->expr->where), sym->name);
2969                               retval = FAILURE;
2970                             }
2971                           else if (args_sym->as->type == AS_DEFERRED)
2972                             {
2973                               gfc_error ("Deferred-shape array '%s' at %L "
2974                                          "cannot be an argument to the "
2975                                          "procedure '%s' because "
2976                                          "it is not C interoperable",
2977                                          args_sym->name,
2978                                          &(args->expr->where), sym->name);
2979                               retval = FAILURE;
2980                             }
2981                         }
2982                               
2983                       /* Make sure it's not a character string.  Arrays of
2984                          any type should be ok if the variable is of a C
2985                          interoperable type.  */
2986                       if (arg_ts->type == BT_CHARACTER)
2987                         if (arg_ts->u.cl != NULL
2988                             && (arg_ts->u.cl->length == NULL
2989                                 || arg_ts->u.cl->length->expr_type
2990                                    != EXPR_CONSTANT
2991                                 || mpz_cmp_si
2992                                     (arg_ts->u.cl->length->value.integer, 1)
2993                                    != 0)
2994                             && is_scalar_expr_ptr (args->expr) != SUCCESS)
2995                           {
2996                             gfc_error_now ("CHARACTER argument '%s' to '%s' "
2997                                            "at %L must have a length of 1",
2998                                            args_sym->name, sym->name,
2999                                            &(args->expr->where));
3000                             retval = FAILURE;
3001                           }
3002                     }
3003                 }
3004               else if (arg_attr.pointer
3005                        && is_scalar_expr_ptr (args->expr) != SUCCESS)
3006                 {
3007                   /* Case 1c, section 15.1.2.5, J3/04-007: an associated
3008                      scalar pointer.  */
3009                   gfc_error_now ("Argument '%s' to '%s' at %L must be an "
3010                                  "associated scalar POINTER", args_sym->name,
3011                                  sym->name, &(args->expr->where));
3012                   retval = FAILURE;
3013                 }
3014             }
3015           else
3016             {
3017               /* The parameter is not required to be C interoperable.  If it
3018                  is not C interoperable, it must be a nonpolymorphic scalar
3019                  with no length type parameters.  It still must have either
3020                  the pointer or target attribute, and it can be
3021                  allocatable (but must be allocated when c_loc is called).  */
3022               if (args->expr->rank != 0 
3023                   && is_scalar_expr_ptr (args->expr) != SUCCESS)
3024                 {
3025                   gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
3026                                  "scalar", args_sym->name, sym->name,
3027                                  &(args->expr->where));
3028                   retval = FAILURE;
3029                 }
3030               else if (arg_ts->type == BT_CHARACTER 
3031                        && is_scalar_expr_ptr (args->expr) != SUCCESS)
3032                 {
3033                   gfc_error_now ("CHARACTER argument '%s' to '%s' at "
3034                                  "%L must have a length of 1",
3035                                  args_sym->name, sym->name,
3036                                  &(args->expr->where));
3037                   retval = FAILURE;
3038                 }
3039               else if (arg_ts->type == BT_CLASS)
3040                 {
3041                   gfc_error_now ("Parameter '%s' to '%s' at %L must not be "
3042                                  "polymorphic", args_sym->name, sym->name,
3043                                  &(args->expr->where));
3044                   retval = FAILURE;
3045                 }
3046             }
3047         }
3048       else if (sym->intmod_sym_id == ISOCBINDING_FUNLOC)
3049         {
3050           if (args_sym->attr.flavor != FL_PROCEDURE)
3051             {
3052               /* TODO: Update this error message to allow for procedure
3053                  pointers once they are implemented.  */
3054               gfc_error_now ("Argument '%s' to '%s' at %L must be a "
3055                              "procedure",
3056                              args_sym->name, sym->name,
3057                              &(args->expr->where));
3058               retval = FAILURE;
3059             }
3060           else if (args_sym->attr.is_bind_c != 1
3061                    && gfc_notify_std (GFC_STD_F2008_TS, "Noninteroperable "
3062                                       "argument '%s' to '%s' at %L",
3063                                       args_sym->name, sym->name,
3064                                       &(args->expr->where)) == FAILURE)
3065             retval = FAILURE;
3066         }
3067       
3068       /* for c_loc/c_funloc, the new symbol is the same as the old one */
3069       *new_sym = sym;
3070     }
3071   else
3072     {
3073       gfc_internal_error ("gfc_iso_c_func_interface(): Unhandled "
3074                           "iso_c_binding function: '%s'!\n", sym->name);
3075     }
3076
3077   return retval;
3078 }
3079
3080
3081 /* Resolve a function call, which means resolving the arguments, then figuring
3082    out which entity the name refers to.  */
3083
3084 static gfc_try
3085 resolve_function (gfc_expr *expr)
3086 {
3087   gfc_actual_arglist *arg;
3088   gfc_symbol *sym;
3089   const char *name;
3090   gfc_try t;
3091   int temp;
3092   procedure_type p = PROC_INTRINSIC;
3093   bool no_formal_args;
3094
3095   sym = NULL;
3096   if (expr->symtree)
3097     sym = expr->symtree->n.sym;
3098
3099   /* If this is a procedure pointer component, it has already been resolved.  */
3100   if (gfc_is_proc_ptr_comp (expr))
3101     return SUCCESS;
3102
3103   if (sym && sym->attr.intrinsic
3104       && gfc_resolve_intrinsic (sym, &expr->where) == FAILURE)
3105     return FAILURE;
3106
3107   if (sym && (sym->attr.flavor == FL_VARIABLE || sym->attr.subroutine))
3108     {
3109       gfc_error ("'%s' at %L is not a function", sym->name, &expr->where);
3110       return FAILURE;
3111     }
3112
3113   /* If this ia a deferred TBP with an abstract interface (which may
3114      of course be referenced), expr->value.function.esym will be set.  */
3115   if (sym && sym->attr.abstract && !expr->value.function.esym)
3116     {
3117       gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
3118                  sym->name, &expr->where);
3119       return FAILURE;
3120     }
3121
3122   /* Switch off assumed size checking and do this again for certain kinds
3123      of procedure, once the procedure itself is resolved.  */
3124   need_full_assumed_size++;
3125
3126   if (expr->symtree && expr->symtree->n.sym)
3127     p = expr->symtree->n.sym->attr.proc;
3128
3129   if (expr->value.function.isym && expr->value.function.isym->inquiry)
3130     inquiry_argument = true;
3131   no_formal_args = sym && is_external_proc (sym) && sym->formal == NULL;
3132
3133   if (resolve_actual_arglist (expr->value.function.actual,
3134                               p, no_formal_args) == FAILURE)
3135     {
3136       inquiry_argument = false;
3137       return FAILURE;
3138     }
3139
3140   inquiry_argument = false;
3141  
3142   /* Need to setup the call to the correct c_associated, depending on
3143      the number of cptrs to user gives to compare.  */
3144   if (sym && sym->attr.is_iso_c == 1)
3145     {
3146       if (gfc_iso_c_func_interface (sym, expr->value.function.actual, &sym)
3147           == FAILURE)
3148         return FAILURE;
3149       
3150       /* Get the symtree for the new symbol (resolved func).
3151          the old one will be freed later, when it's no longer used.  */
3152       gfc_find_sym_tree (sym->name, sym->ns, 1, &(expr->symtree));
3153     }
3154   
3155   /* Resume assumed_size checking.  */
3156   need_full_assumed_size--;
3157
3158   /* If the procedure is external, check for usage.  */
3159   if (sym && is_external_proc (sym))
3160     resolve_global_procedure (sym, &expr->where,
3161                               &expr->value.function.actual, 0);
3162
3163   if (sym && sym->ts.type == BT_CHARACTER
3164       && sym->ts.u.cl
3165       && sym->ts.u.cl->length == NULL
3166       && !sym->attr.dummy
3167       && !sym->ts.deferred
3168       && expr->value.function.esym == NULL
3169       && !sym->attr.contained)
3170     {
3171       /* Internal procedures are taken care of in resolve_contained_fntype.  */
3172       gfc_error ("Function '%s' is declared CHARACTER(*) and cannot "
3173                  "be used at %L since it is not a dummy argument",
3174                  sym->name, &expr->where);
3175       return FAILURE;
3176     }
3177
3178   /* See if function is already resolved.  */
3179
3180   if (expr->value.function.name != NULL)
3181     {
3182       if (expr->ts.type == BT_UNKNOWN)
3183         expr->ts = sym->ts;
3184       t = SUCCESS;
3185     }
3186   else
3187     {
3188       /* Apply the rules of section 14.1.2.  */
3189
3190       switch (procedure_kind (sym))
3191         {
3192         case PTYPE_GENERIC:
3193           t = resolve_generic_f (expr);
3194           break;
3195
3196         case PTYPE_SPECIFIC:
3197           t = resolve_specific_f (expr);
3198           break;
3199
3200         case PTYPE_UNKNOWN:
3201           t = resolve_unknown_f (expr);
3202           break;
3203
3204         default:
3205           gfc_internal_error ("resolve_function(): bad function type");
3206         }
3207     }
3208
3209   /* If the expression is still a function (it might have simplified),
3210      then we check to see if we are calling an elemental function.  */
3211
3212   if (expr->expr_type != EXPR_FUNCTION)
3213     return t;
3214
3215   temp = need_full_assumed_size;
3216   need_full_assumed_size = 0;
3217
3218   if (resolve_elemental_actual (expr, NULL) == FAILURE)
3219     return FAILURE;
3220
3221   if (omp_workshare_flag
3222       && expr->value.function.esym
3223       && ! gfc_elemental (expr->value.function.esym))
3224     {
3225       gfc_error ("User defined non-ELEMENTAL function '%s' at %L not allowed "
3226                  "in WORKSHARE construct", expr->value.function.esym->name,
3227                  &expr->where);
3228       t = FAILURE;
3229     }
3230
3231 #define GENERIC_ID expr->value.function.isym->id
3232   else if (expr->value.function.actual != NULL
3233            && expr->value.function.isym != NULL
3234            && GENERIC_ID != GFC_ISYM_LBOUND
3235            && GENERIC_ID != GFC_ISYM_LEN
3236            && GENERIC_ID != GFC_ISYM_LOC
3237            && GENERIC_ID != GFC_ISYM_PRESENT)
3238     {
3239       /* Array intrinsics must also have the last upper bound of an
3240          assumed size array argument.  UBOUND and SIZE have to be
3241          excluded from the check if the second argument is anything
3242          than a constant.  */
3243
3244       for (arg = expr->value.function.actual; arg; arg = arg->next)
3245         {
3246           if ((GENERIC_ID == GFC_ISYM_UBOUND || GENERIC_ID == GFC_ISYM_SIZE)
3247               && arg->next != NULL && arg->next->expr)
3248             {
3249               if (arg->next->expr->expr_type != EXPR_CONSTANT)
3250                 break;
3251
3252               if (arg->next->name && strncmp(arg->next->name, "kind", 4) == 0)
3253                 break;
3254
3255               if ((int)mpz_get_si (arg->next->expr->value.integer)
3256                         < arg->expr->rank)
3257                 break;
3258             }
3259
3260           if (arg->expr != NULL
3261               && arg->expr->rank > 0
3262               && resolve_assumed_size_actual (arg->expr))
3263             return FAILURE;
3264         }
3265     }
3266 #undef GENERIC_ID
3267
3268   need_full_assumed_size = temp;
3269   name = NULL;
3270
3271   if (!pure_function (expr, &name) && name)
3272     {
3273       if (forall_flag)
3274         {
3275           gfc_error ("Reference to non-PURE function '%s' at %L inside a "
3276                      "FORALL %s", name, &expr->where,
3277                      forall_flag == 2 ? "mask" : "block");
3278           t = FAILURE;
3279         }
3280       else if (do_concurrent_flag)
3281         {
3282           gfc_error ("Reference to non-PURE function '%s' at %L inside a "
3283                      "DO CONCURRENT %s", name, &expr->where,
3284                      do_concurrent_flag == 2 ? "mask" : "block");
3285           t = FAILURE;
3286         }
3287       else if (gfc_pure (NULL))
3288         {
3289           gfc_error ("Function reference to '%s' at %L is to a non-PURE "
3290                      "procedure within a PURE procedure", name, &expr->where);
3291           t = FAILURE;
3292         }
3293
3294       if (gfc_implicit_pure (NULL))
3295         gfc_current_ns->proc_name->attr.implicit_pure = 0;
3296     }
3297
3298   /* Functions without the RECURSIVE attribution are not allowed to
3299    * call themselves.  */
3300   if (expr->value.function.esym && !expr->value.function.esym->attr.recursive)
3301     {
3302       gfc_symbol *esym;
3303       esym = expr->value.function.esym;
3304
3305       if (is_illegal_recursion (esym, gfc_current_ns))
3306       {
3307         if (esym->attr.entry && esym->ns->entries)
3308           gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
3309                      " function '%s' is not RECURSIVE",
3310                      esym->name, &expr->where, esym->ns->entries->sym->name);
3311         else
3312           gfc_error ("Function '%s' at %L cannot be called recursively, as it"
3313                      " is not RECURSIVE", esym->name, &expr->where);
3314
3315         t = FAILURE;
3316       }
3317     }
3318
3319   /* Character lengths of use associated functions may contains references to
3320      symbols not referenced from the current program unit otherwise.  Make sure
3321      those symbols are marked as referenced.  */
3322
3323   if (expr->ts.type == BT_CHARACTER && expr->value.function.esym
3324       && expr->value.function.esym->attr.use_assoc)
3325     {
3326       gfc_expr_set_symbols_referenced (expr->ts.u.cl->length);
3327     }
3328
3329   /* Make sure that the expression has a typespec that works.  */
3330   if (expr->ts.type == BT_UNKNOWN)
3331     {
3332       if (expr->symtree->n.sym->result
3333             && expr->symtree->n.sym->result->ts.type != BT_UNKNOWN
3334             && !expr->symtree->n.sym->result->attr.proc_pointer)
3335         expr->ts = expr->symtree->n.sym->result->ts;
3336     }
3337
3338   return t;
3339 }
3340
3341
3342 /************* Subroutine resolution *************/
3343
3344 static void
3345 pure_subroutine (gfc_code *c, gfc_symbol *sym)
3346 {
3347   if (gfc_pure (sym))
3348     return;
3349
3350   if (forall_flag)
3351     gfc_error ("Subroutine call to '%s' in FORALL block at %L is not PURE",
3352                sym->name, &c->loc);
3353   else if (do_concurrent_flag)
3354     gfc_error ("Subroutine call to '%s' in DO CONCURRENT block at %L is not "
3355                "PURE", sym->name, &c->loc);
3356   else if (gfc_pure (NULL))
3357     gfc_error ("Subroutine call to '%s' at %L is not PURE", sym->name,
3358                &c->loc);
3359
3360   if (gfc_implicit_pure (NULL))
3361     gfc_current_ns->proc_name->attr.implicit_pure = 0;
3362 }
3363
3364
3365 static match
3366 resolve_generic_s0 (gfc_code *c, gfc_symbol *sym)
3367 {
3368   gfc_symbol *s;
3369
3370   if (sym->attr.generic)
3371     {
3372       s = gfc_search_interface (sym->generic, 1, &c->ext.actual);
3373       if (s != NULL)
3374         {
3375           c->resolved_sym = s;
3376           pure_subroutine (c, s);
3377           return MATCH_YES;
3378         }
3379
3380       /* TODO: Need to search for elemental references in generic interface.  */
3381     }
3382
3383   if (sym->attr.intrinsic)
3384     return gfc_intrinsic_sub_interface (c, 0);
3385
3386   return MATCH_NO;
3387 }
3388
3389
3390 static gfc_try
3391 resolve_generic_s (gfc_code *c)
3392 {
3393   gfc_symbol *sym;
3394   match m;
3395
3396   sym = c->symtree->n.sym;
3397
3398   for (;;)
3399     {
3400       m = resolve_generic_s0 (c, sym);
3401       if (m == MATCH_YES)
3402         return SUCCESS;
3403       else if (m == MATCH_ERROR)
3404         return FAILURE;
3405
3406 generic:
3407       if (sym->ns->parent == NULL)
3408         break;
3409       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
3410
3411       if (sym == NULL)
3412         break;
3413       if (!generic_sym (sym))
3414         goto generic;
3415     }
3416
3417   /* Last ditch attempt.  See if the reference is to an intrinsic
3418      that possesses a matching interface.  14.1.2.4  */
3419   sym = c->symtree->n.sym;
3420
3421   if (!gfc_is_intrinsic (sym, 1, c->loc))
3422     {
3423       gfc_error ("There is no specific subroutine for the generic '%s' at %L",
3424                  sym->name, &c->loc);
3425       return FAILURE;
3426     }
3427
3428   m = gfc_intrinsic_sub_interface (c, 0);
3429   if (m == MATCH_YES)
3430     return SUCCESS;
3431   if (m == MATCH_NO)
3432     gfc_error ("Generic subroutine '%s' at %L is not consistent with an "
3433                "intrinsic subroutine interface", sym->name, &c->loc);
3434
3435   return FAILURE;
3436 }
3437
3438
3439 /* Set the name and binding label of the subroutine symbol in the call
3440    expression represented by 'c' to include the type and kind of the
3441    second parameter.  This function is for resolving the appropriate
3442    version of c_f_pointer() and c_f_procpointer().  For example, a
3443    call to c_f_pointer() for a default integer pointer could have a
3444    name of c_f_pointer_i4.  If no second arg exists, which is an error
3445    for these two functions, it defaults to the generic symbol's name
3446    and binding label.  */
3447
3448 static void
3449 set_name_and_label (gfc_code *c, gfc_symbol *sym,
3450                     char *name, const char **binding_label)
3451 {
3452   gfc_expr *arg = NULL;
3453   char type;
3454   int kind;
3455
3456   /* The second arg of c_f_pointer and c_f_procpointer determines
3457      the type and kind for the procedure name.  */
3458   arg = c->ext.actual->next->expr;
3459
3460   if (arg != NULL)
3461     {
3462       /* Set up the name to have the given symbol's name,
3463          plus the type and kind.  */
3464       /* a derived type is marked with the type letter 'u' */
3465       if (arg->ts.type == BT_DERIVED)
3466         {
3467           type = 'd';
3468           kind = 0; /* set the kind as 0 for now */
3469         }
3470       else
3471         {
3472           type = gfc_type_letter (arg->ts.type);
3473           kind = arg->ts.kind;
3474         }
3475
3476       if (arg->ts.type == BT_CHARACTER)
3477         /* Kind info for character strings not needed.  */
3478         kind = 0;
3479
3480       sprintf (name, "%s_%c%d", sym->name, type, kind);
3481       /* Set up the binding label as the given symbol's label plus
3482          the type and kind.  */
3483       *binding_label = gfc_get_string ("%s_%c%d", sym->binding_label, type, 
3484                                        kind);
3485     }
3486   else
3487     {
3488       /* If the second arg is missing, set the name and label as
3489          was, cause it should at least be found, and the missing
3490          arg error will be caught by compare_parameters().  */
3491       sprintf (name, "%s", sym->name);
3492       *binding_label = sym->binding_label;
3493     }
3494    
3495   return;
3496 }
3497
3498
3499 /* Resolve a generic version of the iso_c_binding procedure given
3500    (sym) to the specific one based on the type and kind of the
3501    argument(s).  Currently, this function resolves c_f_pointer() and
3502    c_f_procpointer based on the type and kind of the second argument
3503    (FPTR).  Other iso_c_binding procedures aren't specially handled.
3504    Upon successfully exiting, c->resolved_sym will hold the resolved
3505    symbol.  Returns MATCH_ERROR if an error occurred; MATCH_YES
3506    otherwise.  */
3507
3508 match
3509 gfc_iso_c_sub_interface (gfc_code *c, gfc_symbol *sym)
3510 {
3511   gfc_symbol *new_sym;
3512   /* this is fine, since we know the names won't use the max */
3513   char name[GFC_MAX_SYMBOL_LEN + 1];
3514   const char* binding_label;
3515   /* default to success; will override if find error */
3516   match m = MATCH_YES;
3517
3518   /* Make sure the actual arguments are in the necessary order (based on the 
3519      formal args) before resolving.  */
3520   if (gfc_procedure_use (sym, &c->ext.actual, &(c->loc)) == FAILURE)
3521     {
3522       c->resolved_sym = sym;
3523       return MATCH_ERROR;
3524     }
3525
3526   if ((sym->intmod_sym_id == ISOCBINDING_F_POINTER) ||
3527       (sym->intmod_sym_id == ISOCBINDING_F_PROCPOINTER))
3528     {
3529       set_name_and_label (c, sym, name, &binding_label);
3530       
3531       if (sym->intmod_sym_id == ISOCBINDING_F_POINTER)
3532         {
3533           if (c->ext.actual != NULL && c->ext.actual->next != NULL)
3534             {
3535               if (c->ext.actual->expr->ts.type != BT_DERIVED
3536                   || c->ext.actual->expr->ts.u.derived->intmod_sym_id
3537                      != ISOCBINDING_PTR)
3538                 {
3539                   gfc_error ("Argument at %L to C_F_POINTER shall have the type"
3540                              " C_PTR", &c->ext.actual->expr->where);
3541                   m = MATCH_ERROR;
3542                 }
3543
3544               /* Make sure we got a third arg if the second arg has non-zero
3545                  rank.  We must also check that the type and rank are
3546                  correct since we short-circuit this check in
3547                  gfc_procedure_use() (called above to sort actual args).  */
3548               if (c->ext.actual->next->expr->rank != 0)
3549                 {
3550                   if(c->ext.actual->next->next == NULL 
3551                      || c->ext.actual->next->next->expr == NULL)
3552                     {
3553                       m = MATCH_ERROR;
3554                       gfc_error ("Missing SHAPE parameter for call to %s "
3555                                  "at %L", sym->name, &(c->loc));
3556                     }
3557                   else if (c->ext.actual->next->next->expr->ts.type
3558                            != BT_INTEGER
3559                            || c->ext.actual->next->next->expr->rank != 1)
3560                     {
3561                       m = MATCH_ERROR;
3562                       gfc_error ("SHAPE parameter for call to %s at %L must "
3563                                  "be a rank 1 INTEGER array", sym->name,
3564                                  &(c->loc));
3565                     }
3566                 }
3567             }
3568         }
3569       else /* ISOCBINDING_F_PROCPOINTER.  */
3570         {
3571           if (c->ext.actual
3572               && (c->ext.actual->expr->ts.type != BT_DERIVED
3573                   || c->ext.actual->expr->ts.u.derived->intmod_sym_id
3574                      != ISOCBINDING_FUNPTR))
3575             {
3576               gfc_error ("Argument at %L to C_F_FUNPOINTER shall have the type "
3577                          "C_FUNPTR", &c->ext.actual->expr->where);
3578               m = MATCH_ERROR;
3579             }
3580           if (c->ext.actual && c->ext.actual->next
3581               && !gfc_expr_attr (c->ext.actual->next->expr).is_bind_c
3582               && gfc_notify_std (GFC_STD_F2008_TS, "Noninteroperable "
3583                                  "procedure-pointer at %L to C_F_FUNPOINTER",
3584                                  &c->ext.actual->next->expr->where)
3585                    == FAILURE)
3586             m = MATCH_ERROR;
3587         }
3588
3589       if (m != MATCH_ERROR)
3590         {
3591           /* the 1 means to add the optional arg to formal list */
3592           new_sym = get_iso_c_sym (sym, name, binding_label, 1);
3593          
3594           /* for error reporting, say it's declared where the original was */
3595           new_sym->declared_at = sym->declared_at;
3596         }
3597     }
3598   else
3599     {
3600       /* no differences for c_loc or c_funloc */
3601       new_sym = sym;
3602     }
3603
3604   /* set the resolved symbol */
3605   if (m != MATCH_ERROR)
3606     c->resolved_sym = new_sym;
3607   else
3608     c->resolved_sym = sym;
3609   
3610   return m;
3611 }
3612
3613
3614 /* Resolve a subroutine call known to be specific.  */
3615
3616 static match
3617 resolve_specific_s0 (gfc_code *c, gfc_symbol *sym)
3618 {
3619   match m;
3620
3621   if(sym->attr.is_iso_c)
3622     {
3623       m = gfc_iso_c_sub_interface (c,sym);
3624       return m;
3625     }
3626   
3627   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
3628     {
3629       if (sym->attr.dummy)
3630         {
3631           sym->attr.proc = PROC_DUMMY;
3632           goto found;
3633         }
3634
3635       sym->attr.proc = PROC_EXTERNAL;
3636       goto found;
3637     }
3638
3639   if (sym->attr.proc == PROC_MODULE || sym->attr.proc == PROC_INTERNAL)
3640     goto found;
3641
3642   if (sym->attr.intrinsic)
3643     {
3644       m = gfc_intrinsic_sub_interface (c, 1);
3645       if (m == MATCH_YES)
3646         return MATCH_YES;
3647       if (m == MATCH_NO)
3648         gfc_error ("Subroutine '%s' at %L is INTRINSIC but is not compatible "
3649                    "with an intrinsic", sym->name, &c->loc);
3650
3651       return MATCH_ERROR;
3652     }
3653
3654   return MATCH_NO;
3655
3656 found:
3657   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3658
3659   c->resolved_sym = sym;
3660   pure_subroutine (c, sym);
3661
3662   return MATCH_YES;
3663 }
3664
3665
3666 static gfc_try
3667 resolve_specific_s (gfc_code *c)
3668 {
3669   gfc_symbol *sym;
3670   match m;
3671
3672   sym = c->symtree->n.sym;
3673
3674   for (;;)
3675     {
3676       m = resolve_specific_s0 (c, sym);
3677       if (m == MATCH_YES)
3678         return SUCCESS;
3679       if (m == MATCH_ERROR)
3680         return FAILURE;
3681
3682       if (sym->ns->parent == NULL)
3683         break;
3684
3685       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
3686
3687       if (sym == NULL)
3688         break;
3689     }
3690
3691   sym = c->symtree->n.sym;
3692   gfc_error ("Unable to resolve the specific subroutine '%s' at %L",
3693              sym->name, &c->loc);
3694
3695   return FAILURE;
3696 }
3697
3698
3699 /* Resolve a subroutine call not known to be generic nor specific.  */
3700
3701 static gfc_try
3702 resolve_unknown_s (gfc_code *c)
3703 {
3704   gfc_symbol *sym;
3705
3706   sym = c->symtree->n.sym;
3707
3708   if (sym->attr.dummy)
3709     {
3710       sym->attr.proc = PROC_DUMMY;
3711       goto found;
3712     }
3713
3714   /* See if we have an intrinsic function reference.  */
3715
3716   if (gfc_is_intrinsic (sym, 1, c->loc))
3717     {
3718       if (gfc_intrinsic_sub_interface (c, 1) == MATCH_YES)
3719         return SUCCESS;
3720       return FAILURE;
3721     }
3722
3723   /* The reference is to an external name.  */
3724
3725 found:
3726   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3727
3728   c->resolved_sym = sym;
3729
3730   pure_subroutine (c, sym);
3731
3732   return SUCCESS;
3733 }
3734
3735
3736 /* Resolve a subroutine call.  Although it was tempting to use the same code
3737    for functions, subroutines and functions are stored differently and this
3738    makes things awkward.  */
3739
3740 static gfc_try
3741 resolve_call (gfc_code *c)
3742 {
3743   gfc_try t;
3744   procedure_type ptype = PROC_INTRINSIC;
3745   gfc_symbol *csym, *sym;
3746   bool no_formal_args;
3747
3748   csym = c->symtree ? c->symtree->n.sym : NULL;
3749
3750   if (csym && csym->ts.type != BT_UNKNOWN)
3751     {
3752       gfc_error ("'%s' at %L has a type, which is not consistent with "
3753                  "the CALL at %L", csym->name, &csym->declared_at, &c->loc);
3754       return FAILURE;
3755     }
3756
3757   if (csym && gfc_current_ns->parent && csym->ns != gfc_current_ns)
3758     {
3759       gfc_symtree *st;
3760       gfc_find_sym_tree (csym->name, gfc_current_ns, 1, &st);
3761       sym = st ? st->n.sym : NULL;
3762       if (sym && csym != sym
3763               && sym->ns == gfc_current_ns
3764               && sym->attr.flavor == FL_PROCEDURE
3765               && sym->attr.contained)
3766         {
3767           sym->refs++;
3768           if (csym->attr.generic)
3769             c->symtree->n.sym = sym;
3770           else
3771             c->symtree = st;
3772           csym = c->symtree->n.sym;
3773         }
3774     }
3775
3776   /* If this ia a deferred TBP with an abstract interface
3777      (which may of course be referenced), c->expr1 will be set.  */
3778   if (csym && csym->attr.abstract && !c->expr1)
3779     {
3780       gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
3781                  csym->name, &c->loc);
3782       return FAILURE;
3783     }
3784
3785   /* Subroutines without the RECURSIVE attribution are not allowed to
3786    * call themselves.  */
3787   if (csym && is_illegal_recursion (csym, gfc_current_ns))
3788     {
3789       if (csym->attr.entry && csym->ns->entries)
3790         gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
3791                    " subroutine '%s' is not RECURSIVE",
3792                    csym->name, &c->loc, csym->ns->entries->sym->name);
3793       else
3794         gfc_error ("SUBROUTINE '%s' at %L cannot be called recursively, as it"
3795                    " is not RECURSIVE", csym->name, &c->loc);
3796
3797       t = FAILURE;
3798     }
3799
3800   /* Switch off assumed size checking and do this again for certain kinds
3801      of procedure, once the procedure itself is resolved.  */
3802   need_full_assumed_size++;
3803
3804   if (csym)
3805     ptype = csym->attr.proc;
3806
3807   no_formal_args = csym && is_external_proc (csym) && csym->formal == NULL;
3808   if (resolve_actual_arglist (c->ext.actual, ptype,
3809                               no_formal_args) == FAILURE)
3810     return FAILURE;
3811
3812   /* Resume assumed_size checking.  */
3813   need_full_assumed_size--;
3814
3815   /* If external, check for usage.  */
3816   if (csym && is_external_proc (csym))
3817     resolve_global_procedure (csym, &c->loc, &c->ext.actual, 1);
3818
3819   t = SUCCESS;
3820   if (c->resolved_sym == NULL)
3821     {
3822       c->resolved_isym = NULL;
3823       switch (procedure_kind (csym))
3824         {
3825         case PTYPE_GENERIC:
3826           t = resolve_generic_s (c);
3827           break;
3828
3829         case PTYPE_SPECIFIC:
3830           t = resolve_specific_s (c);
3831           break;
3832
3833         case PTYPE_UNKNOWN:
3834           t = resolve_unknown_s (c);
3835           break;
3836
3837         default:
3838           gfc_internal_error ("resolve_subroutine(): bad function type");
3839         }
3840     }
3841
3842   /* Some checks of elemental subroutine actual arguments.  */
3843   if (resolve_elemental_actual (NULL, c) == FAILURE)
3844     return FAILURE;
3845
3846   return t;
3847 }
3848
3849
3850 /* Compare the shapes of two arrays that have non-NULL shapes.  If both
3851    op1->shape and op2->shape are non-NULL return SUCCESS if their shapes
3852    match.  If both op1->shape and op2->shape are non-NULL return FAILURE
3853    if their shapes do not match.  If either op1->shape or op2->shape is
3854    NULL, return SUCCESS.  */
3855
3856 static gfc_try
3857 compare_shapes (gfc_expr *op1, gfc_expr *op2)
3858 {
3859   gfc_try t;
3860   int i;
3861
3862   t = SUCCESS;
3863
3864   if (op1->shape != NULL && op2->shape != NULL)
3865     {
3866       for (i = 0; i < op1->rank; i++)
3867         {
3868           if (mpz_cmp (op1->shape[i], op2->shape[i]) != 0)
3869            {
3870              gfc_error ("Shapes for operands at %L and %L are not conformable",
3871                          &op1->where, &op2->where);
3872              t = FAILURE;
3873              break;
3874            }
3875         }
3876     }
3877
3878   return t;
3879 }
3880
3881
3882 /* Resolve an operator expression node.  This can involve replacing the
3883    operation with a user defined function call.  */
3884
3885 static gfc_try
3886 resolve_operator (gfc_expr *e)
3887 {
3888   gfc_expr *op1, *op2;
3889   char msg[200];
3890   bool dual_locus_error;
3891   gfc_try t;
3892
3893   /* Resolve all subnodes-- give them types.  */
3894
3895   switch (e->value.op.op)
3896     {
3897     default:
3898       if (gfc_resolve_expr (e->value.op.op2) == FAILURE)
3899         return FAILURE;
3900
3901     /* Fall through...  */
3902
3903     case INTRINSIC_NOT:
3904     case INTRINSIC_UPLUS:
3905     case INTRINSIC_UMINUS:
3906     case INTRINSIC_PARENTHESES:
3907       if (gfc_resolve_expr (e->value.op.op1) == FAILURE)
3908         return FAILURE;
3909       break;
3910     }
3911
3912   /* Typecheck the new node.  */
3913
3914   op1 = e->value.op.op1;
3915   op2 = e->value.op.op2;
3916   dual_locus_error = false;
3917
3918   if ((op1 && op1->expr_type == EXPR_NULL)
3919       || (op2 && op2->expr_type == EXPR_NULL))
3920     {
3921       sprintf (msg, _("Invalid context for NULL() pointer at %%L"));
3922       goto bad_op;
3923     }
3924
3925   switch (e->value.op.op)
3926     {
3927     case INTRINSIC_UPLUS:
3928     case INTRINSIC_UMINUS:
3929       if (op1->ts.type == BT_INTEGER
3930           || op1->ts.type == BT_REAL
3931           || op1->ts.type == BT_COMPLEX)
3932         {
3933           e->ts = op1->ts;
3934           break;
3935         }
3936
3937       sprintf (msg, _("Operand of unary numeric operator '%s' at %%L is %s"),
3938                gfc_op2string (e->value.op.op), gfc_typename (&e->ts));
3939       goto bad_op;
3940
3941     case INTRINSIC_PLUS:
3942     case INTRINSIC_MINUS:
3943     case INTRINSIC_TIMES:
3944     case INTRINSIC_DIVIDE:
3945     case INTRINSIC_POWER:
3946       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3947         {
3948           gfc_type_convert_binary (e, 1);
3949           break;
3950         }
3951
3952       sprintf (msg,
3953                _("Operands of binary numeric operator '%s' at %%L are %s/%s"),
3954                gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3955                gfc_typename (&op2->ts));
3956       goto bad_op;
3957
3958     case INTRINSIC_CONCAT:
3959       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3960           && op1->ts.kind == op2->ts.kind)
3961         {
3962           e->ts.type = BT_CHARACTER;
3963           e->ts.kind = op1->ts.kind;
3964           break;
3965         }
3966
3967       sprintf (msg,
3968                _("Operands of string concatenation operator at %%L are %s/%s"),
3969                gfc_typename (&op1->ts), gfc_typename (&op2->ts));
3970       goto bad_op;
3971
3972     case INTRINSIC_AND:
3973     case INTRINSIC_OR:
3974     case INTRINSIC_EQV:
3975     case INTRINSIC_NEQV:
3976       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3977         {
3978           e->ts.type = BT_LOGICAL;
3979           e->ts.kind = gfc_kind_max (op1, op2);
3980           if (op1->ts.kind < e->ts.kind)
3981             gfc_convert_type (op1, &e->ts, 2);
3982           else if (op2->ts.kind < e->ts.kind)
3983             gfc_convert_type (op2, &e->ts, 2);
3984           break;
3985         }
3986
3987       sprintf (msg, _("Operands of logical operator '%s' at %%L are %s/%s"),
3988                gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3989                gfc_typename (&op2->ts));
3990
3991       goto bad_op;
3992
3993     case INTRINSIC_NOT:
3994       if (op1->ts.type == BT_LOGICAL)
3995         {
3996           e->ts.type = BT_LOGICAL;
3997           e->ts.kind = op1->ts.kind;
3998           break;
3999         }
4000
4001       sprintf (msg, _("Operand of .not. operator at %%L is %s"),
4002                gfc_typename (&op1->ts));
4003       goto bad_op;
4004
4005     case INTRINSIC_GT:
4006     case INTRINSIC_GT_OS:
4007     case INTRINSIC_GE:
4008     case INTRINSIC_GE_OS:
4009     case INTRINSIC_LT:
4010     case INTRINSIC_LT_OS:
4011     case INTRINSIC_LE:
4012     case INTRINSIC_LE_OS:
4013       if (op1->ts.type == BT_COMPLEX || op2->ts.type == BT_COMPLEX)
4014         {
4015           strcpy (msg, _("COMPLEX quantities cannot be compared at %L"));
4016           goto bad_op;
4017         }
4018
4019       /* Fall through...  */
4020
4021     case INTRINSIC_EQ:
4022     case INTRINSIC_EQ_OS:
4023     case INTRINSIC_NE:
4024     case INTRINSIC_NE_OS:
4025       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
4026           && op1->ts.kind == op2->ts.kind)
4027         {
4028           e->ts.type = BT_LOGICAL;
4029           e->ts.kind = gfc_default_logical_kind;
4030           break;
4031         }
4032
4033       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
4034         {
4035           gfc_type_convert_binary (e, 1);
4036
4037           e->ts.type = BT_LOGICAL;
4038           e->ts.kind = gfc_default_logical_kind;
4039
4040           if (gfc_option.warn_compare_reals)
4041             {
4042               gfc_intrinsic_op op = e->value.op.op;
4043
4044               /* Type conversion has made sure that the types of op1 and op2
4045                  agree, so it is only necessary to check the first one.   */
4046               if ((op1->ts.type == BT_REAL || op1->ts.type == BT_COMPLEX)
4047                   && (op == INTRINSIC_EQ || op == INTRINSIC_EQ_OS
4048                       || op == INTRINSIC_NE || op == INTRINSIC_NE_OS))
4049                 {
4050                   const char *msg;
4051
4052                   if (op == INTRINSIC_EQ || op == INTRINSIC_EQ_OS)
4053                     msg = "Equality comparison for %s at %L";
4054                   else
4055                     msg = "Inequality comparison for %s at %L";
4056                   
4057                   gfc_warning (msg, gfc_typename (&op1->ts), &op1->where);
4058                 }
4059             }
4060
4061           break;
4062         }
4063
4064       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
4065         sprintf (msg,
4066                  _("Logicals at %%L must be compared with %s instead of %s"),
4067                  (e->value.op.op == INTRINSIC_EQ 
4068                   || e->value.op.op == INTRINSIC_EQ_OS)
4069                  ? ".eqv." : ".neqv.", gfc_op2string (e->value.op.op));
4070       else
4071         sprintf (msg,
4072                  _("Operands of comparison operator '%s' at %%L are %s/%s"),
4073                  gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
4074                  gfc_typename (&op2->ts));
4075
4076       goto bad_op;
4077
4078     case INTRINSIC_USER:
4079       if (e->value.op.uop->op == NULL)
4080         sprintf (msg, _("Unknown operator '%s' at %%L"), e->value.op.uop->name);
4081       else if (op2 == NULL)
4082         sprintf (msg, _("Operand of user operator '%s' at %%L is %s"),
4083                  e->value.op.uop->name, gfc_typename (&op1->ts));
4084       else
4085         {
4086           sprintf (msg, _("Operands of user operator '%s' at %%L are %s/%s"),
4087                    e->value.op.uop->name, gfc_typename (&op1->ts),
4088                    gfc_typename (&op2->ts));
4089           e->value.op.uop->op->sym->attr.referenced = 1;
4090         }
4091
4092       goto bad_op;
4093
4094     case INTRINSIC_PARENTHESES:
4095       e->ts = op1->ts;
4096       if (e->ts.type == BT_CHARACTER)
4097         e->ts.u.cl = op1->ts.u.cl;
4098       break;
4099
4100     default:
4101       gfc_internal_error ("resolve_operator(): Bad intrinsic");
4102     }
4103
4104   /* Deal with arrayness of an operand through an operator.  */
4105
4106   t = SUCCESS;
4107
4108   switch (e->value.op.op)
4109     {
4110     case INTRINSIC_PLUS:
4111     case INTRINSIC_MINUS:
4112     case INTRINSIC_TIMES:
4113     case INTRINSIC_DIVIDE:
4114     case INTRINSIC_POWER:
4115     case INTRINSIC_CONCAT:
4116     case INTRINSIC_AND:
4117     case INTRINSIC_OR:
4118     case INTRINSIC_EQV:
4119     case INTRINSIC_NEQV:
4120     case INTRINSIC_EQ:
4121     case INTRINSIC_EQ_OS:
4122     case INTRINSIC_NE:
4123     case INTRINSIC_NE_OS:
4124     case INTRINSIC_GT:
4125     case INTRINSIC_GT_OS:
4126     case INTRINSIC_GE:
4127     case INTRINSIC_GE_OS:
4128     case INTRINSIC_LT:
4129     case INTRINSIC_LT_OS:
4130     case INTRINSIC_LE:
4131     case INTRINSIC_LE_OS:
4132
4133       if (op1->rank == 0 && op2->rank == 0)
4134         e->rank = 0;
4135
4136       if (op1->rank == 0 && op2->rank != 0)
4137         {
4138           e->rank = op2->rank;
4139
4140           if (e->shape == NULL)
4141             e->shape = gfc_copy_shape (op2->shape, op2->rank);
4142         }
4143
4144       if (op1->rank != 0 && op2->rank == 0)
4145         {
4146           e->rank = op1->rank;
4147
4148           if (e->shape == NULL)
4149             e->shape = gfc_copy_shape (op1->shape, op1->rank);
4150         }
4151
4152       if (op1->rank != 0 && op2->rank != 0)
4153         {
4154           if (op1->rank == op2->rank)
4155             {
4156               e->rank = op1->rank;
4157               if (e->shape == NULL)
4158                 {
4159                   t = compare_shapes (op1, op2);
4160                   if (t == FAILURE)
4161                     e->shape = NULL;
4162                   else
4163                     e->shape = gfc_copy_shape (op1->shape, op1->rank);
4164                 }
4165             }
4166           else
4167             {
4168               /* Allow higher level expressions to work.  */
4169               e->rank = 0;
4170
4171               /* Try user-defined operators, and otherwise throw an error.  */
4172               dual_locus_error = true;
4173               sprintf (msg,
4174                        _("Inconsistent ranks for operator at %%L and %%L"));
4175               goto bad_op;
4176             }
4177         }
4178
4179       break;
4180
4181     case INTRINSIC_PARENTHESES:
4182     case INTRINSIC_NOT:
4183     case INTRINSIC_UPLUS:
4184     case INTRINSIC_UMINUS:
4185       /* Simply copy arrayness attribute */
4186       e->rank = op1->rank;
4187
4188       if (e->shape == NULL)
4189         e->shape = gfc_copy_shape (op1->shape, op1->rank);
4190
4191       break;
4192
4193     default:
4194       break;
4195     }
4196
4197   /* Attempt to simplify the expression.  */
4198   if (t == SUCCESS)
4199     {
4200       t = gfc_simplify_expr (e, 0);
4201       /* Some calls do not succeed in simplification and return FAILURE
4202          even though there is no error; e.g. variable references to
4203          PARAMETER arrays.  */
4204       if (!gfc_is_constant_expr (e))
4205         t = SUCCESS;
4206     }
4207   return t;
4208
4209 bad_op:
4210
4211   {
4212     match m = gfc_extend_expr (e);
4213     if (m == MATCH_YES)
4214       return SUCCESS;
4215     if (m == MATCH_ERROR)
4216       return FAILURE;
4217   }
4218
4219   if (dual_locus_error)
4220     gfc_error (msg, &op1->where, &op2->where);
4221   else
4222     gfc_error (msg, &e->where);
4223
4224   return FAILURE;
4225 }
4226
4227
4228 /************** Array resolution subroutines **************/
4229
4230 typedef enum
4231 { CMP_LT, CMP_EQ, CMP_GT, CMP_UNKNOWN }
4232 comparison;
4233
4234 /* Compare two integer expressions.  */
4235
4236 static comparison
4237 compare_bound (gfc_expr *a, gfc_expr *b)
4238 {
4239   int i;
4240
4241   if (a == NULL || a->expr_type != EXPR_CONSTANT
4242       || b == NULL || b->expr_type != EXPR_CONSTANT)
4243     return CMP_UNKNOWN;
4244
4245   /* If either of the types isn't INTEGER, we must have
4246      raised an error earlier.  */
4247
4248   if (a->ts.type != BT_INTEGER || b->ts.type != BT_INTEGER)
4249     return CMP_UNKNOWN;
4250
4251   i = mpz_cmp (a->value.integer, b->value.integer);
4252
4253   if (i < 0)
4254     return CMP_LT;
4255   if (i > 0)
4256     return CMP_GT;
4257   return CMP_EQ;
4258 }
4259
4260
4261 /* Compare an integer expression with an integer.  */
4262
4263 static comparison
4264 compare_bound_int (gfc_expr *a, int b)
4265 {
4266   int i;
4267
4268   if (a == NULL || a->expr_type != EXPR_CONSTANT)
4269     return CMP_UNKNOWN;
4270
4271   if (a->ts.type != BT_INTEGER)
4272     gfc_internal_error ("compare_bound_int(): Bad expression");
4273
4274   i = mpz_cmp_si (a->value.integer, b);
4275
4276   if (i < 0)
4277     return CMP_LT;
4278   if (i > 0)
4279     return CMP_GT;
4280   return CMP_EQ;
4281 }
4282
4283
4284 /* Compare an integer expression with a mpz_t.  */
4285
4286 static comparison
4287 compare_bound_mpz_t (gfc_expr *a, mpz_t b)
4288 {
4289   int i;
4290
4291   if (a == NULL || a->expr_type != EXPR_CONSTANT)
4292     return CMP_UNKNOWN;
4293
4294   if (a->ts.type != BT_INTEGER)
4295     gfc_internal_error ("compare_bound_int(): Bad expression");
4296
4297   i = mpz_cmp (a->value.integer, b);
4298
4299   if (i < 0)
4300     return CMP_LT;
4301   if (i > 0)
4302     return CMP_GT;
4303   return CMP_EQ;
4304 }
4305
4306
4307 /* Compute the last value of a sequence given by a triplet.  
4308    Return 0 if it wasn't able to compute the last value, or if the
4309    sequence if empty, and 1 otherwise.  */
4310
4311 static int
4312 compute_last_value_for_triplet (gfc_expr *start, gfc_expr *end,
4313                                 gfc_expr *stride, mpz_t last)
4314 {
4315   mpz_t rem;
4316
4317   if (start == NULL || start->expr_type != EXPR_CONSTANT
4318       || end == NULL || end->expr_type != EXPR_CONSTANT
4319       || (stride != NULL && stride->expr_type != EXPR_CONSTANT))
4320     return 0;
4321
4322   if (start->ts.type != BT_INTEGER || end->ts.type != BT_INTEGER
4323       || (stride != NULL && stride->ts.type != BT_INTEGER))
4324     return 0;
4325
4326   if (stride == NULL || compare_bound_int(stride, 1) == CMP_EQ)
4327     {
4328       if (compare_bound (start, end) == CMP_GT)
4329         return 0;
4330       mpz_set (last, end->value.integer);
4331       return 1;
4332     }
4333
4334   if (compare_bound_int (stride, 0) == CMP_GT)
4335     {
4336       /* Stride is positive */
4337       if (mpz_cmp (start->value.integer, end->value.integer) > 0)
4338         return 0;
4339     }
4340   else
4341     {
4342       /* Stride is negative */
4343       if (mpz_cmp (start->value.integer, end->value.integer) < 0)
4344         return 0;
4345     }
4346
4347   mpz_init (rem);
4348   mpz_sub (rem, end->value.integer, start->value.integer);
4349   mpz_tdiv_r (rem, rem, stride->value.integer);
4350   mpz_sub (last, end->value.integer, rem);
4351   mpz_clear (rem);
4352
4353   return 1;
4354 }
4355
4356
4357 /* Compare a single dimension of an array reference to the array
4358    specification.  */
4359
4360 static gfc_try
4361 check_dimension (int i, gfc_array_ref *ar, gfc_array_spec *as)
4362 {
4363   mpz_t last_value;
4364
4365   if (ar->dimen_type[i] == DIMEN_STAR)
4366     {
4367       gcc_assert (ar->stride[i] == NULL);
4368       /* This implies [*] as [*:] and [*:3] are not possible.  */
4369       if (ar->start[i] == NULL)
4370         {
4371           gcc_assert (ar->end[i] == NULL);
4372           return SUCCESS;
4373         }
4374     }
4375
4376 /* Given start, end and stride values, calculate the minimum and
4377    maximum referenced indexes.  */
4378
4379   switch (ar->dimen_type[i])
4380     {
4381     case DIMEN_VECTOR:
4382     case DIMEN_THIS_IMAGE:
4383       break;
4384
4385     case DIMEN_STAR:
4386     case DIMEN_ELEMENT:
4387       if (compare_bound (ar->start[i], as->lower[i]) == CMP_LT)
4388         {
4389           if (i < as->rank)
4390             gfc_warning ("Array reference at %L is out of bounds "
4391                          "(%ld < %ld) in dimension %d", &ar->c_where[i],
4392                          mpz_get_si (ar->start[i]->value.integer),
4393                          mpz_get_si (as->lower[i]->value.integer), i+1);
4394           else
4395             gfc_warning ("Array reference at %L is out of bounds "
4396                          "(%ld < %ld) in codimension %d", &ar->c_where[i],
4397                          mpz_get_si (ar->start[i]->value.integer),
4398                          mpz_get_si (as->lower[i]->value.integer),
4399                          i + 1 - as->rank);
4400           return SUCCESS;
4401         }
4402       if (compare_bound (ar->start[i], as->upper[i]) == CMP_GT)
4403         {
4404           if (i < as->rank)
4405             gfc_warning ("Array reference at %L is out of bounds "
4406                          "(%ld > %ld) in dimension %d", &ar->c_where[i],
4407                          mpz_get_si (ar->start[i]->value.integer),
4408                          mpz_get_si (as->upper[i]->value.integer), i+1);
4409           else
4410             gfc_warning ("Array reference at %L is out of bounds "
4411                          "(%ld > %ld) in codimension %d", &ar->c_where[i],
4412                          mpz_get_si (ar->start[i]->value.integer),
4413                          mpz_get_si (as->upper[i]->value.integer),
4414                          i + 1 - as->rank);
4415           return SUCCESS;
4416         }
4417
4418       break;
4419
4420     case DIMEN_RANGE:
4421       {
4422 #define AR_START (ar->start[i] ? ar->start[i] : as->lower[i])
4423 #define AR_END (ar->end[i] ? ar->end[i] : as->upper[i])
4424
4425         comparison comp_start_end = compare_bound (AR_START, AR_END);
4426
4427         /* Check for zero stride, which is not allowed.  */
4428         if (compare_bound_int (ar->stride[i], 0) == CMP_EQ)
4429           {
4430             gfc_error ("Illegal stride of zero at %L", &ar->c_where[i]);
4431             return FAILURE;
4432           }
4433
4434         /* if start == len || (stride > 0 && start < len)
4435                            || (stride < 0 && start > len),
4436            then the array section contains at least one element.  In this
4437            case, there is an out-of-bounds access if
4438            (start < lower || start > upper).  */
4439         if (compare_bound (AR_START, AR_END) == CMP_EQ
4440             || ((compare_bound_int (ar->stride[i], 0) == CMP_GT
4441                  || ar->stride[i] == NULL) && comp_start_end == CMP_LT)
4442             || (compare_bound_int (ar->stride[i], 0) == CMP_LT
4443                 && comp_start_end == CMP_GT))
4444           {
4445             if (compare_bound (AR_START, as->lower[i]) == CMP_LT)
4446               {
4447                 gfc_warning ("Lower array reference at %L is out of bounds "
4448                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
4449                        mpz_get_si (AR_START->value.integer),
4450                        mpz_get_si (as->lower[i]->value.integer), i+1);
4451                 return SUCCESS;
4452               }
4453             if (compare_bound (AR_START, as->upper[i]) == CMP_GT)
4454               {
4455                 gfc_warning ("Lower array reference at %L is out of bounds "
4456                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
4457                        mpz_get_si (AR_START->value.integer),
4458                        mpz_get_si (as->upper[i]->value.integer), i+1);
4459                 return SUCCESS;
4460               }
4461           }
4462
4463         /* If we can compute the highest index of the array section,
4464            then it also has to be between lower and upper.  */
4465         mpz_init (last_value);
4466         if (compute_last_value_for_triplet (AR_START, AR_END, ar->stride[i],
4467                                             last_value))
4468           {
4469             if (compare_bound_mpz_t (as->lower[i], last_value) == CMP_GT)
4470               {
4471                 gfc_warning ("Upper array reference at %L is out of bounds "
4472                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
4473                        mpz_get_si (last_value),
4474                        mpz_get_si (as->lower[i]->value.integer), i+1);
4475                 mpz_clear (last_value);
4476                 return SUCCESS;
4477               }
4478             if (compare_bound_mpz_t (as->upper[i], last_value) == CMP_LT)
4479               {
4480                 gfc_warning ("Upper array reference at %L is out of bounds "
4481                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
4482                        mpz_get_si (last_value),
4483                        mpz_get_si (as->upper[i]->value.integer), i+1);
4484                 mpz_clear (last_value);
4485                 return SUCCESS;
4486               }
4487           }
4488         mpz_clear (last_value);
4489
4490 #undef AR_START
4491 #undef AR_END
4492       }
4493       break;
4494
4495     default:
4496       gfc_internal_error ("check_dimension(): Bad array reference");
4497     }
4498
4499   return SUCCESS;
4500 }
4501
4502
4503 /* Compare an array reference with an array specification.  */
4504
4505 static gfc_try
4506 compare_spec_to_ref (gfc_array_ref *ar)
4507 {
4508   gfc_array_spec *as;
4509   int i;
4510
4511   as = ar->as;
4512   i = as->rank - 1;
4513   /* TODO: Full array sections are only allowed as actual parameters.  */
4514   if (as->type == AS_ASSUMED_SIZE
4515       && (/*ar->type == AR_FULL
4516           ||*/ (ar->type == AR_SECTION
4517               && ar->dimen_type[i] == DIMEN_RANGE && ar->end[i] == NULL)))
4518     {
4519       gfc_error ("Rightmost upper bound of assumed size array section "
4520                  "not specified at %L", &ar->where);
4521       return FAILURE;
4522     }
4523
4524   if (ar->type == AR_FULL)
4525     return SUCCESS;
4526
4527   if (as->rank != ar->dimen)
4528     {
4529       gfc_error ("Rank mismatch in array reference at %L (%d/%d)",
4530                  &ar->where, ar->dimen, as->rank);
4531       return FAILURE;
4532     }
4533
4534   /* ar->codimen == 0 is a local array.  */
4535   if (as->corank != ar->codimen && ar->codimen != 0)
4536     {
4537       gfc_error ("Coindex rank mismatch in array reference at %L (%d/%d)",
4538                  &ar->where, ar->codimen, as->corank);
4539       return FAILURE;
4540     }
4541
4542   for (i = 0; i < as->rank; i++)
4543     if (check_dimension (i, ar, as) == FAILURE)
4544       return FAILURE;
4545
4546   /* Local access has no coarray spec.  */
4547   if (ar->codimen != 0)
4548     for (i = as->rank; i < as->rank + as->corank; i++)
4549       {
4550         if (ar->dimen_type[i] != DIMEN_ELEMENT && !ar->in_allocate
4551             && ar->dimen_type[i] != DIMEN_THIS_IMAGE)
4552           {
4553             gfc_error ("Coindex of codimension %d must be a scalar at %L",
4554                        i + 1 - as->rank, &ar->where);
4555             return FAILURE;
4556           }
4557         if (check_dimension (i, ar, as) == FAILURE)
4558           return FAILURE;
4559       }
4560
4561   return SUCCESS;
4562 }
4563
4564
4565 /* Resolve one part of an array index.  */
4566
4567 static gfc_try
4568 gfc_resolve_index_1 (gfc_expr *index, int check_scalar,
4569                      int force_index_integer_kind)
4570 {
4571   gfc_typespec ts;
4572
4573   if (index == NULL)
4574     return SUCCESS;
4575
4576   if (gfc_resolve_expr (index) == FAILURE)
4577     return FAILURE;
4578
4579   if (check_scalar && index->rank != 0)
4580     {
4581       gfc_error ("Array index at %L must be scalar", &index->where);
4582       return FAILURE;
4583     }
4584
4585   if (index->ts.type != BT_INTEGER && index->ts.type != BT_REAL)
4586     {
4587       gfc_error ("Array index at %L must be of INTEGER type, found %s",
4588                  &index->where, gfc_basic_typename (index->ts.type));
4589       return FAILURE;
4590     }
4591
4592   if (index->ts.type == BT_REAL)
4593     if (gfc_notify_std (GFC_STD_LEGACY, "REAL array index at %L",
4594                         &index->where) == FAILURE)
4595       return FAILURE;
4596
4597   if ((index->ts.kind != gfc_index_integer_kind
4598        && force_index_integer_kind)
4599       || index->ts.type != BT_INTEGER)
4600     {
4601       gfc_clear_ts (&ts);
4602       ts.type = BT_INTEGER;
4603       ts.kind = gfc_index_integer_kind;
4604
4605       gfc_convert_type_warn (index, &ts, 2, 0);
4606     }
4607
4608   return SUCCESS;
4609 }
4610
4611 /* Resolve one part of an array index.  */
4612
4613 gfc_try
4614 gfc_resolve_index (gfc_expr *index, int check_scalar)
4615 {
4616   return gfc_resolve_index_1 (index, check_scalar, 1);
4617 }
4618
4619 /* Resolve a dim argument to an intrinsic function.  */
4620
4621 gfc_try
4622 gfc_resolve_dim_arg (gfc_expr *dim)
4623 {
4624   if (dim == NULL)
4625     return SUCCESS;
4626
4627   if (gfc_resolve_expr (dim) == FAILURE)
4628     return FAILURE;
4629
4630   if (dim->rank != 0)
4631     {
4632       gfc_error ("Argument dim at %L must be scalar", &dim->where);
4633       return FAILURE;
4634
4635     }
4636
4637   if (dim->ts.type != BT_INTEGER)
4638     {
4639       gfc_error ("Argument dim at %L must be of INTEGER type", &dim->where);
4640       return FAILURE;
4641     }
4642
4643   if (dim->ts.kind != gfc_index_integer_kind)
4644     {
4645       gfc_typespec ts;
4646
4647       gfc_clear_ts (&ts);
4648       ts.type = BT_INTEGER;
4649       ts.kind = gfc_index_integer_kind;
4650
4651       gfc_convert_type_warn (dim, &ts, 2, 0);
4652     }
4653
4654   return SUCCESS;
4655 }
4656
4657 /* Given an expression that contains array references, update those array
4658    references to point to the right array specifications.  While this is
4659    filled in during matching, this information is difficult to save and load
4660    in a module, so we take care of it here.
4661
4662    The idea here is that the original array reference comes from the
4663    base symbol.  We traverse the list of reference structures, setting
4664    the stored reference to references.  Component references can
4665    provide an additional array specification.  */
4666
4667 static void
4668 find_array_spec (gfc_expr *e)
4669 {
4670   gfc_array_spec *as;
4671   gfc_component *c;
4672   gfc_ref *ref;
4673
4674   if (e->symtree->n.sym->ts.type == BT_CLASS)
4675     as = CLASS_DATA (e->symtree->n.sym)->as;
4676   else
4677     as = e->symtree->n.sym->as;
4678
4679   for (ref = e->ref; ref; ref = ref->next)
4680     switch (ref->type)
4681       {
4682       case REF_ARRAY:
4683         if (as == NULL)
4684           gfc_internal_error ("find_array_spec(): Missing spec");
4685
4686         ref->u.ar.as = as;
4687         as = NULL;
4688         break;
4689
4690       case REF_COMPONENT:
4691         c = ref->u.c.component;
4692         if (c->attr.dimension)
4693           {
4694             if (as != NULL)
4695               gfc_internal_error ("find_array_spec(): unused as(1)");
4696             as = c->as;
4697           }
4698
4699         break;
4700
4701       case REF_SUBSTRING:
4702         break;
4703       }
4704
4705   if (as != NULL)
4706     gfc_internal_error ("find_array_spec(): unused as(2)");
4707 }
4708
4709
4710 /* Resolve an array reference.  */
4711
4712 static gfc_try
4713 resolve_array_ref (gfc_array_ref *ar)
4714 {
4715   int i, check_scalar;
4716   gfc_expr *e;
4717
4718   for (i = 0; i < ar->dimen + ar->codimen; i++)
4719     {
4720       check_scalar = ar->dimen_type[i] == DIMEN_RANGE;
4721
4722       /* Do not force gfc_index_integer_kind for the start.  We can
4723          do fine with any integer kind.  This avoids temporary arrays
4724          created for indexing with a vector.  */
4725       if (gfc_resolve_index_1 (ar->start[i], check_scalar, 0) == FAILURE)
4726         return FAILURE;
4727       if (gfc_resolve_index (ar->end[i], check_scalar) == FAILURE)
4728         return FAILURE;
4729       if (gfc_resolve_index (ar->stride[i], check_scalar) == FAILURE)
4730         return FAILURE;
4731
4732       e = ar->start[i];
4733
4734       if (ar->dimen_type[i] == DIMEN_UNKNOWN)
4735         switch (e->rank)
4736           {
4737           case 0:
4738             ar->dimen_type[i] = DIMEN_ELEMENT;
4739             break;
4740
4741           case 1:
4742             ar->dimen_type[i] = DIMEN_VECTOR;
4743             if (e->expr_type == EXPR_VARIABLE
4744                 && e->symtree->n.sym->ts.type == BT_DERIVED)
4745               ar->start[i] = gfc_get_parentheses (e);
4746             break;
4747
4748           default:
4749             gfc_error ("Array index at %L is an array of rank %d",
4750                        &ar->c_where[i], e->rank);
4751             return FAILURE;
4752           }
4753
4754       /* Fill in the upper bound, which may be lower than the
4755          specified one for something like a(2:10:5), which is
4756          identical to a(2:7:5).  Only relevant for strides not equal
4757          to one.  Don't try a division by zero.  */
4758       if (ar->dimen_type[i] == DIMEN_RANGE
4759           && ar->stride[i] != NULL && ar->stride[i]->expr_type == EXPR_CONSTANT
4760           && mpz_cmp_si (ar->stride[i]->value.integer, 1L) != 0
4761           && mpz_cmp_si (ar->stride[i]->value.integer, 0L) != 0)
4762         {
4763           mpz_t size, end;
4764
4765           if (gfc_ref_dimen_size (ar, i, &size, &end) == SUCCESS)
4766             {
4767               if (ar->end[i] == NULL)
4768                 {
4769                   ar->end[i] =
4770                     gfc_get_constant_expr (BT_INTEGER, gfc_index_integer_kind,
4771                                            &ar->where);
4772                   mpz_set (ar->end[i]->value.integer, end);
4773                 }
4774               else if (ar->end[i]->ts.type == BT_INTEGER
4775                        && ar->end[i]->expr_type == EXPR_CONSTANT)
4776                 {
4777                   mpz_set (ar->end[i]->value.integer, end);
4778                 }
4779               else
4780                 gcc_unreachable ();
4781
4782               mpz_clear (size);
4783               mpz_clear (end);
4784             }
4785         }
4786     }
4787
4788   if (ar->type == AR_FULL)
4789     {
4790       if (ar->as->rank == 0)
4791         ar->type = AR_ELEMENT;
4792
4793       /* Make sure array is the same as array(:,:), this way
4794          we don't need to special case all the time.  */
4795       ar->dimen = ar->as->rank;
4796       for (i = 0; i < ar->dimen; i++)
4797         {
4798           ar->dimen_type[i] = DIMEN_RANGE;
4799
4800           gcc_assert (ar->start[i] == NULL);
4801           gcc_assert (ar->end[i] == NULL);
4802           gcc_assert (ar->stride[i] == NULL);
4803         }
4804     }
4805
4806   /* If the reference type is unknown, figure out what kind it is.  */
4807
4808   if (ar->type == AR_UNKNOWN)
4809     {
4810       ar->type = AR_ELEMENT;
4811       for (i = 0; i < ar->dimen; i++)
4812         if (ar->dimen_type[i] == DIMEN_RANGE
4813             || ar->dimen_type[i] == DIMEN_VECTOR)
4814           {
4815             ar->type = AR_SECTION;
4816             break;
4817           }
4818     }
4819
4820   if (!ar->as->cray_pointee && compare_spec_to_ref (ar) == FAILURE)
4821     return FAILURE;
4822
4823   if (ar->as->corank && ar->codimen == 0)
4824     {
4825       int n;
4826       ar->codimen = ar->as->corank;
4827       for (n = ar->dimen; n < ar->dimen + ar->codimen; n++)
4828         ar->dimen_type[n] = DIMEN_THIS_IMAGE;
4829     }
4830
4831   return SUCCESS;
4832 }
4833
4834
4835 static gfc_try
4836 resolve_substring (gfc_ref *ref)
4837 {
4838   int k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
4839
4840   if (ref->u.ss.start != NULL)
4841     {
4842       if (gfc_resolve_expr (ref->u.ss.start) == FAILURE)
4843         return FAILURE;
4844
4845       if (ref->u.ss.start->ts.type != BT_INTEGER)
4846         {
4847           gfc_error ("Substring start index at %L must be of type INTEGER",
4848                      &ref->u.ss.start->where);
4849           return FAILURE;
4850         }
4851
4852       if (ref->u.ss.start->rank != 0)
4853         {
4854           gfc_error ("Substring start index at %L must be scalar",
4855                      &ref->u.ss.start->where);
4856           return FAILURE;
4857         }
4858
4859       if (compare_bound_int (ref->u.ss.start, 1) == CMP_LT
4860           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4861               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4862         {
4863           gfc_error ("Substring start index at %L is less than one",
4864                      &ref->u.ss.start->where);
4865           return FAILURE;
4866         }
4867     }
4868
4869   if (ref->u.ss.end != NULL)
4870     {
4871       if (gfc_resolve_expr (ref->u.ss.end) == FAILURE)
4872         return FAILURE;
4873
4874       if (ref->u.ss.end->ts.type != BT_INTEGER)
4875         {
4876           gfc_error ("Substring end index at %L must be of type INTEGER",
4877                      &ref->u.ss.end->where);
4878           return FAILURE;
4879         }
4880
4881       if (ref->u.ss.end->rank != 0)
4882         {
4883           gfc_error ("Substring end index at %L must be scalar",
4884                      &ref->u.ss.end->where);
4885           return FAILURE;
4886         }
4887
4888       if (ref->u.ss.length != NULL
4889           && compare_bound (ref->u.ss.end, ref->u.ss.length->length) == CMP_GT
4890           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4891               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4892         {
4893           gfc_error ("Substring end index at %L exceeds the string length",
4894                      &ref->u.ss.start->where);
4895           return FAILURE;
4896         }
4897
4898       if (compare_bound_mpz_t (ref->u.ss.end,
4899                                gfc_integer_kinds[k].huge) == CMP_GT
4900           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4901               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4902         {
4903           gfc_error ("Substring end index at %L is too large",
4904                      &ref->u.ss.end->where);
4905           return FAILURE;
4906         }
4907     }
4908
4909   return SUCCESS;
4910 }
4911
4912
4913 /* This function supplies missing substring charlens.  */
4914
4915 void
4916 gfc_resolve_substring_charlen (gfc_expr *e)
4917 {
4918   gfc_ref *char_ref;
4919   gfc_expr *start, *end;
4920
4921   for (char_ref = e->ref; char_ref; char_ref = char_ref->next)
4922     if (char_ref->type == REF_SUBSTRING)
4923       break;
4924
4925   if (!char_ref)
4926     return;
4927
4928   gcc_assert (char_ref->next == NULL);
4929
4930   if (e->ts.u.cl)
4931     {
4932       if (e->ts.u.cl->length)
4933         gfc_free_expr (e->ts.u.cl->length);
4934       else if (e->expr_type == EXPR_VARIABLE
4935                  && e->symtree->n.sym->attr.dummy)
4936         return;
4937     }
4938
4939   e->ts.type = BT_CHARACTER;
4940   e->ts.kind = gfc_default_character_kind;
4941
4942   if (!e->ts.u.cl)
4943     e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
4944
4945   if (char_ref->u.ss.start)
4946     start = gfc_copy_expr (char_ref->u.ss.start);
4947   else
4948     start = gfc_get_int_expr (gfc_default_integer_kind, NULL, 1);
4949
4950   if (char_ref->u.ss.end)
4951     end = gfc_copy_expr (char_ref->u.ss.end);
4952   else if (e->expr_type == EXPR_VARIABLE)
4953     end = gfc_copy_expr (e->symtree->n.sym->ts.u.cl->length);
4954   else
4955     end = NULL;
4956
4957   if (!start || !end)
4958     return;
4959
4960   /* Length = (end - start +1).  */
4961   e->ts.u.cl->length = gfc_subtract (end, start);
4962   e->ts.u.cl->length = gfc_add (e->ts.u.cl->length,
4963                                 gfc_get_int_expr (gfc_default_integer_kind,
4964                                                   NULL, 1));
4965
4966   e->ts.u.cl->length->ts.type = BT_INTEGER;
4967   e->ts.u.cl->length->ts.kind = gfc_charlen_int_kind;
4968
4969   /* Make sure that the length is simplified.  */
4970   gfc_simplify_expr (e->ts.u.cl->length, 1);
4971   gfc_resolve_expr (e->ts.u.cl->length);
4972 }
4973
4974
4975 /* Resolve subtype references.  */
4976
4977 static gfc_try
4978 resolve_ref (gfc_expr *expr)
4979 {
4980   int current_part_dimension, n_components, seen_part_dimension;
4981   gfc_ref *ref;
4982
4983   for (ref = expr->ref; ref; ref = ref->next)
4984     if (ref->type == REF_ARRAY && ref->u.ar.as == NULL)
4985       {
4986         find_array_spec (expr);
4987         break;
4988       }
4989
4990   for (ref = expr->ref; ref; ref = ref->next)
4991     switch (ref->type)
4992       {
4993       case REF_ARRAY:
4994         if (resolve_array_ref (&ref->u.ar) == FAILURE)
4995           return FAILURE;
4996         break;
4997
4998       case REF_COMPONENT:
4999         break;
5000
5001       case REF_SUBSTRING:
5002         if (resolve_substring (ref) == FAILURE)
5003           return FAILURE;
5004         break;
5005       }
5006
5007   /* Check constraints on part references.  */
5008
5009   current_part_dimension = 0;
5010   seen_part_dimension = 0;
5011   n_components = 0;
5012
5013   for (ref = expr->ref; ref; ref = ref->next)
5014     {
5015       switch (ref->type)
5016         {
5017         case REF_ARRAY:
5018           switch (ref->u.ar.type)
5019             {
5020             case AR_FULL:
5021               /* Coarray scalar.  */
5022               if (ref->u.ar.as->rank == 0)
5023                 {
5024                   current_part_dimension = 0;
5025                   break;
5026                 }
5027               /* Fall through.  */
5028             case AR_SECTION:
5029               current_part_dimension = 1;
5030               break;
5031
5032             case AR_ELEMENT:
5033               current_part_dimension = 0;
5034               break;
5035
5036             case AR_UNKNOWN:
5037               gfc_internal_error ("resolve_ref(): Bad array reference");
5038             }
5039
5040           break;
5041
5042         case REF_COMPONENT:
5043           if (current_part_dimension || seen_part_dimension)
5044             {
5045               /* F03:C614.  */
5046               if (ref->u.c.component->attr.pointer
5047                   || ref->u.c.component->attr.proc_pointer
5048                   || (ref->u.c.component->ts.type == BT_CLASS
5049                         && CLASS_DATA (ref->u.c.component)->attr.pointer))
5050                 {
5051                   gfc_error ("Component to the right of a part reference "
5052                              "with nonzero rank must not have the POINTER "
5053                              "attribute at %L", &expr->where);
5054                   return FAILURE;
5055                 }
5056               else if (ref->u.c.component->attr.allocatable
5057                         || (ref->u.c.component->ts.type == BT_CLASS
5058                             && CLASS_DATA (ref->u.c.component)->attr.allocatable))
5059
5060                 {
5061                   gfc_error ("Component to the right of a part reference "
5062                              "with nonzero rank must not have the ALLOCATABLE "
5063                              "attribute at %L", &expr->where);
5064                   return FAILURE;
5065                 }
5066             }
5067
5068           n_components++;
5069           break;
5070
5071         case REF_SUBSTRING:
5072           break;
5073         }
5074
5075       if (((ref->type == REF_COMPONENT && n_components > 1)
5076            || ref->next == NULL)
5077           && current_part_dimension
5078           && seen_part_dimension)
5079         {
5080           gfc_error ("Two or more part references with nonzero rank must "
5081                      "not be specified at %L", &expr->where);
5082           return FAILURE;
5083         }
5084
5085       if (ref->type == REF_COMPONENT)
5086         {
5087           if (current_part_dimension)
5088             seen_part_dimension = 1;
5089
5090           /* reset to make sure */
5091           current_part_dimension = 0;
5092         }
5093     }
5094
5095   return SUCCESS;
5096 }
5097
5098
5099 /* Given an expression, determine its shape.  This is easier than it sounds.
5100    Leaves the shape array NULL if it is not possible to determine the shape.  */
5101
5102 static void
5103 expression_shape (gfc_expr *e)
5104 {
5105   mpz_t array[GFC_MAX_DIMENSIONS];
5106   int i;
5107
5108   if (e->rank <= 0 || e->shape != NULL)
5109     return;
5110
5111   for (i = 0; i < e->rank; i++)
5112     if (gfc_array_dimen_size (e, i, &array[i]) == FAILURE)
5113       goto fail;
5114
5115   e->shape = gfc_get_shape (e->rank);
5116
5117   memcpy (e->shape, array, e->rank * sizeof (mpz_t));
5118
5119   return;
5120
5121 fail:
5122   for (i--; i >= 0; i--)
5123     mpz_clear (array[i]);
5124 }
5125
5126
5127 /* Given a variable expression node, compute the rank of the expression by
5128    examining the base symbol and any reference structures it may have.  */
5129
5130 static void
5131 expression_rank (gfc_expr *e)
5132 {
5133   gfc_ref *ref;
5134   int i, rank;
5135
5136   /* Just to make sure, because EXPR_COMPCALL's also have an e->ref and that
5137      could lead to serious confusion...  */
5138   gcc_assert (e->expr_type != EXPR_COMPCALL);
5139
5140   if (e->ref == NULL)
5141     {
5142       if (e->expr_type == EXPR_ARRAY)
5143         goto done;
5144       /* Constructors can have a rank different from one via RESHAPE().  */
5145
5146       if (e->symtree == NULL)
5147         {
5148           e->rank = 0;
5149           goto done;
5150         }
5151
5152       e->rank = (e->symtree->n.sym->as == NULL)
5153                 ? 0 : e->symtree->n.sym->as->rank;
5154       goto done;
5155     }
5156
5157   rank = 0;
5158
5159   for (ref = e->ref; ref; ref = ref->next)
5160     {
5161       if (ref->type == REF_COMPONENT && ref->u.c.component->attr.proc_pointer
5162           && ref->u.c.component->attr.function && !ref->next)
5163         rank = ref->u.c.component->as ? ref->u.c.component->as->rank : 0;
5164
5165       if (ref->type != REF_ARRAY)
5166         continue;
5167
5168       if (ref->u.ar.type == AR_FULL)
5169         {
5170           rank = ref->u.ar.as->rank;
5171           break;
5172         }
5173
5174       if (ref->u.ar.type == AR_SECTION)
5175         {
5176           /* Figure out the rank of the section.  */
5177           if (rank != 0)
5178             gfc_internal_error ("expression_rank(): Two array specs");
5179
5180           for (i = 0; i < ref->u.ar.dimen; i++)
5181             if (ref->u.ar.dimen_type[i] == DIMEN_RANGE
5182                 || ref->u.ar.dimen_type[i] == DIMEN_VECTOR)
5183               rank++;
5184
5185           break;
5186         }
5187     }
5188
5189   e->rank = rank;
5190
5191 done:
5192   expression_shape (e);
5193 }
5194
5195
5196 /* Resolve a variable expression.  */
5197
5198 static gfc_try
5199 resolve_variable (gfc_expr *e)
5200 {
5201   gfc_symbol *sym;
5202   gfc_try t;
5203
5204   t = SUCCESS;
5205
5206   if (e->symtree == NULL)
5207     return FAILURE;
5208   sym = e->symtree->n.sym;
5209
5210   /* TS 29113, 407b.  */
5211   if (e->ts.type == BT_ASSUMED)
5212     {
5213       if (!actual_arg)
5214         {
5215           gfc_error ("Assumed-type variable %s at %L may only be used "
5216                      "as actual argument", sym->name, &e->where);
5217           return FAILURE;
5218         }
5219       else if (inquiry_argument && !first_actual_arg)
5220         {
5221           /* FIXME: It doesn't work reliably as inquiry_argument is not set
5222              for all inquiry functions in resolve_function; the reason is
5223              that the function-name resolution happens too late in that
5224              function.  */
5225           gfc_error ("Assumed-type variable %s at %L as actual argument to "
5226                      "an inquiry function shall be the first argument",
5227                      sym->name, &e->where);
5228           return FAILURE;
5229         }
5230     }
5231
5232   /* TS 29113, C535b.  */
5233   if ((sym->ts.type == BT_CLASS && sym->attr.class_ok
5234         && CLASS_DATA (sym)->as
5235         && CLASS_DATA (sym)->as->type == AS_ASSUMED_RANK)
5236        || (sym->ts.type != BT_CLASS && sym->as
5237            && sym->as->type == AS_ASSUMED_RANK))
5238     {
5239       if (!actual_arg)
5240         {
5241           gfc_error ("Assumed-rank variable %s at %L may only be used as "
5242                      "actual argument", sym->name, &e->where);
5243           return FAILURE;
5244         }
5245       else if (inquiry_argument && !first_actual_arg)
5246         {
5247           /* FIXME: It doesn't work reliably as inquiry_argument is not set
5248              for all inquiry functions in resolve_function; the reason is
5249              that the function-name resolution happens too late in that
5250              function.  */
5251           gfc_error ("Assumed-rank variable %s at %L as actual argument "
5252                      "to an inquiry function shall be the first argument",
5253                      sym->name, &e->where);
5254           return FAILURE;
5255         }
5256     }
5257
5258   /* TS 29113, 407b.  */
5259   if (e->ts.type == BT_ASSUMED && e->ref
5260       && !(e->ref->type == REF_ARRAY && e->ref->u.ar.type == AR_FULL
5261            && e->ref->next == NULL))
5262     {
5263       gfc_error ("Assumed-type variable %s at %L shall not have a subobject "
5264                  "reference", sym->name, &e->ref->u.ar.where);
5265       return FAILURE;
5266     }
5267
5268   /* TS 29113, C535b.  */
5269   if (((sym->ts.type == BT_CLASS && sym->attr.class_ok
5270         && CLASS_DATA (sym)->as
5271         && CLASS_DATA (sym)->as->type == AS_ASSUMED_RANK)
5272        || (sym->ts.type != BT_CLASS && sym->as
5273            && sym->as->type == AS_ASSUMED_RANK))
5274       && e->ref
5275       && !(e->ref->type == REF_ARRAY && e->ref->u.ar.type == AR_FULL
5276            && e->ref->next == NULL))
5277     {
5278       gfc_error ("Assumed-rank variable %s at %L shall not have a subobject "
5279                  "reference", sym->name, &e->ref->u.ar.where);
5280       return FAILURE;
5281     }
5282
5283
5284   /* If this is an associate-name, it may be parsed with an array reference
5285      in error even though the target is scalar.  Fail directly in this case.
5286      TODO Understand why class scalar expressions must be excluded.  */
5287   if (sym->assoc && !(sym->ts.type == BT_CLASS && e->rank == 0))
5288     {
5289       if (sym->ts.type == BT_CLASS)
5290         gfc_fix_class_refs (e);
5291       if (!sym->attr.dimension && e->ref && e->ref->type == REF_ARRAY)
5292         return FAILURE;
5293     }
5294
5295   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.generic)
5296     sym->ts.u.derived = gfc_find_dt_in_generic (sym->ts.u.derived);
5297
5298   /* On the other hand, the parser may not have known this is an array;
5299      in this case, we have to add a FULL reference.  */
5300   if (sym->assoc && sym->attr.dimension && !e->ref)
5301     {
5302       e->ref = gfc_get_ref ();
5303       e->ref->type = REF_ARRAY;
5304       e->ref->u.ar.type = AR_FULL;
5305       e->ref->u.ar.dimen = 0;
5306     }
5307
5308   if (e->ref && resolve_ref (e) == FAILURE)
5309     return FAILURE;
5310
5311   if (sym->attr.flavor == FL_PROCEDURE
5312       && (!sym->attr.function
5313           || (sym->attr.function && sym->result
5314               && sym->result->attr.proc_pointer
5315               && !sym->result->attr.function)))
5316     {
5317       e->ts.type = BT_PROCEDURE;
5318       goto resolve_procedure;
5319     }
5320
5321   if (sym->ts.type != BT_UNKNOWN)
5322     gfc_variable_attr (e, &e->ts);
5323   else
5324     {
5325       /* Must be a simple variable reference.  */
5326       if (gfc_set_default_type (sym, 1, sym->ns) == FAILURE)
5327         return FAILURE;
5328       e->ts = sym->ts;
5329     }
5330
5331   if (check_assumed_size_reference (sym, e))
5332     return FAILURE;
5333
5334   /* If a PRIVATE variable is used in the specification expression of the
5335      result variable, it might be accessed from outside the module and can
5336      thus not be TREE_PUBLIC() = 0.
5337      TODO: sym->attr.public_used only has to be set for the result variable's
5338      type-parameter expression and not for dummies or automatic variables.
5339      Additionally, it only has to be set if the function is either PUBLIC or
5340      used in a generic interface or TBP; unfortunately,
5341      proc_name->attr.public_used can get set at a later stage.  */
5342   if (specification_expr && sym->attr.access == ACCESS_PRIVATE
5343       && !sym->attr.function && !sym->attr.use_assoc
5344       && gfc_current_ns->proc_name && gfc_current_ns->proc_name->attr.function)
5345     sym->attr.public_used = 1;
5346
5347   /* Deal with forward references to entries during resolve_code, to
5348      satisfy, at least partially, 12.5.2.5.  */
5349   if (gfc_current_ns->entries
5350       && current_entry_id == sym->entry_id
5351       && cs_base
5352       && cs_base->current
5353       && cs_base->current->op != EXEC_ENTRY)
5354     {
5355       gfc_entry_list *entry;
5356       gfc_formal_arglist *formal;
5357       int n;
5358       bool seen;
5359
5360       /* If the symbol is a dummy...  */
5361       if (sym->attr.dummy && sym->ns == gfc_current_ns)
5362         {
5363           entry = gfc_current_ns->entries;
5364           seen = false;
5365
5366           /* ...test if the symbol is a parameter of previous entries.  */
5367           for (; entry && entry->id <= current_entry_id; entry = entry->next)
5368             for (formal = entry->sym->formal; formal; formal = formal->next)
5369               {
5370                 if (formal->sym && sym->name == formal->sym->name)
5371                   seen = true;
5372               }
5373
5374           /*  If it has not been seen as a dummy, this is an error.  */
5375           if (!seen)
5376             {
5377               if (specification_expr)
5378                 gfc_error ("Variable '%s', used in a specification expression"
5379                            ", is referenced at %L before the ENTRY statement "
5380                            "in which it is a parameter",
5381                            sym->name, &cs_base->current->loc);
5382               else
5383                 gfc_error ("Variable '%s' is used at %L before the ENTRY "
5384                            "statement in which it is a parameter",
5385                            sym->name, &cs_base->current->loc);
5386               t = FAILURE;
5387             }
5388         }
5389
5390       /* Now do the same check on the specification expressions.  */
5391       specification_expr = 1;
5392       if (sym->ts.type == BT_CHARACTER
5393           && gfc_resolve_expr (sym->ts.u.cl->length) == FAILURE)
5394         t = FAILURE;
5395
5396       if (sym->as)
5397         for (n = 0; n < sym->as->rank; n++)
5398           {
5399              specification_expr = 1;
5400              if (gfc_resolve_expr (sym->as->lower[n]) == FAILURE)
5401                t = FAILURE;
5402              specification_expr = 1;
5403              if (gfc_resolve_expr (sym->as->upper[n]) == FAILURE)
5404                t = FAILURE;
5405           }
5406       specification_expr = 0;
5407
5408       if (t == SUCCESS)
5409         /* Update the symbol's entry level.  */
5410         sym->entry_id = current_entry_id + 1;
5411     }
5412
5413   /* If a symbol has been host_associated mark it.  This is used latter,
5414      to identify if aliasing is possible via host association.  */
5415   if (sym->attr.flavor == FL_VARIABLE
5416         && gfc_current_ns->parent
5417         && (gfc_current_ns->parent == sym->ns
5418               || (gfc_current_ns->parent->parent
5419                     && gfc_current_ns->parent->parent == sym->ns)))
5420     sym->attr.host_assoc = 1;
5421
5422 resolve_procedure:
5423   if (t == SUCCESS && resolve_procedure_expression (e) == FAILURE)
5424     t = FAILURE;
5425
5426   /* F2008, C617 and C1229.  */
5427   if (!inquiry_argument && (e->ts.type == BT_CLASS || e->ts.type == BT_DERIVED)
5428       && gfc_is_coindexed (e))
5429     {
5430       gfc_ref *ref, *ref2 = NULL;
5431
5432       for (ref = e->ref; ref; ref = ref->next)
5433         {
5434           if (ref->type == REF_COMPONENT)
5435             ref2 = ref;
5436           if (ref->type == REF_ARRAY && ref->u.ar.codimen > 0)
5437             break;
5438         }
5439
5440       for ( ; ref; ref = ref->next)
5441         if (ref->type == REF_COMPONENT)
5442           break;
5443
5444       /* Expression itself is not coindexed object.  */
5445       if (ref && e->ts.type == BT_CLASS)
5446         {
5447           gfc_error ("Polymorphic subobject of coindexed object at %L",
5448                      &e->where);
5449           t = FAILURE;
5450         }
5451
5452       /* Expression itself is coindexed object.  */
5453       if (ref == NULL)
5454         {
5455           gfc_component *c;
5456           c = ref2 ? ref2->u.c.component : e->symtree->n.sym->components;
5457           for ( ; c; c = c->next)
5458             if (c->attr.allocatable && c->ts.type == BT_CLASS)
5459               {
5460                 gfc_error ("Coindexed object with polymorphic allocatable "
5461                          "subcomponent at %L", &e->where);
5462                 t = FAILURE;
5463                 break;
5464               }
5465         }
5466     }
5467
5468   return t;
5469 }
5470
5471
5472 /* Checks to see that the correct symbol has been host associated.
5473    The only situation where this arises is that in which a twice
5474    contained function is parsed after the host association is made.
5475    Therefore, on detecting this, change the symbol in the expression
5476    and convert the array reference into an actual arglist if the old
5477    symbol is a variable.  */
5478 static bool
5479 check_host_association (gfc_expr *e)
5480 {
5481   gfc_symbol *sym, *old_sym;
5482   gfc_symtree *st;
5483   int n;
5484   gfc_ref *ref;
5485   gfc_actual_arglist *arg, *tail = NULL;
5486   bool retval = e->expr_type == EXPR_FUNCTION;
5487
5488   /*  If the expression is the result of substitution in
5489       interface.c(gfc_extend_expr) because there is no way in
5490       which the host association can be wrong.  */
5491   if (e->symtree == NULL
5492         || e->symtree->n.sym == NULL
5493         || e->user_operator)
5494     return retval;
5495
5496   old_sym = e->symtree->n.sym;
5497
5498   if (gfc_current_ns->parent
5499         && old_sym->ns != gfc_current_ns)
5500     {
5501       /* Use the 'USE' name so that renamed module symbols are
5502          correctly handled.  */
5503       gfc_find_symbol (e->symtree->name, gfc_current_ns, 1, &sym);
5504
5505       if (sym && old_sym != sym
5506               && sym->ts.type == old_sym->ts.type
5507               && sym->attr.flavor == FL_PROCEDURE
5508               && sym->attr.contained)
5509         {
5510           /* Clear the shape, since it might not be valid.  */
5511           gfc_free_shape (&e->shape, e->rank);
5512
5513           /* Give the expression the right symtree!  */
5514           gfc_find_sym_tree (e->symtree->name, NULL, 1, &st);
5515           gcc_assert (st != NULL);
5516
5517           if (old_sym->attr.flavor == FL_PROCEDURE
5518                 || e->expr_type == EXPR_FUNCTION)
5519             {
5520               /* Original was function so point to the new symbol, since
5521                  the actual argument list is already attached to the
5522                  expression. */
5523               e->value.function.esym = NULL;
5524               e->symtree = st;
5525             }
5526           else
5527             {
5528               /* Original was variable so convert array references into
5529                  an actual arglist. This does not need any checking now
5530                  since resolve_function will take care of it.  */
5531               e->value.function.actual = NULL;
5532               e->expr_type = EXPR_FUNCTION;
5533               e->symtree = st;
5534
5535               /* Ambiguity will not arise if the array reference is not
5536                  the last reference.  */
5537               for (ref = e->ref; ref; ref = ref->next)
5538                 if (ref->type == REF_ARRAY && ref->next == NULL)
5539                   break;
5540
5541               gcc_assert (ref->type == REF_ARRAY);
5542
5543               /* Grab the start expressions from the array ref and
5544                  copy them into actual arguments.  */
5545               for (n = 0; n < ref->u.ar.dimen; n++)
5546                 {
5547                   arg = gfc_get_actual_arglist ();
5548                   arg->expr = gfc_copy_expr (ref->u.ar.start[n]);
5549                   if (e->value.function.actual == NULL)
5550                     tail = e->value.function.actual = arg;
5551                   else
5552                     {
5553                       tail->next = arg;
5554                       tail = arg;
5555                     }
5556                 }
5557
5558               /* Dump the reference list and set the rank.  */
5559               gfc_free_ref_list (e->ref);
5560               e->ref = NULL;
5561               e->rank = sym->as ? sym->as->rank : 0;
5562             }
5563
5564           gfc_resolve_expr (e);
5565           sym->refs++;
5566         }
5567     }
5568   /* This might have changed!  */
5569   return e->expr_type == EXPR_FUNCTION;
5570 }
5571
5572
5573 static void
5574 gfc_resolve_character_operator (gfc_expr *e)
5575 {
5576   gfc_expr *op1 = e->value.op.op1;
5577   gfc_expr *op2 = e->value.op.op2;
5578   gfc_expr *e1 = NULL;
5579   gfc_expr *e2 = NULL;
5580
5581   gcc_assert (e->value.op.op == INTRINSIC_CONCAT);
5582
5583   if (op1->ts.u.cl && op1->ts.u.cl->length)
5584     e1 = gfc_copy_expr (op1->ts.u.cl->length);
5585   else if (op1->expr_type == EXPR_CONSTANT)
5586     e1 = gfc_get_int_expr (gfc_default_integer_kind, NULL,
5587                            op1->value.character.length);
5588
5589   if (op2->ts.u.cl && op2->ts.u.cl->length)
5590     e2 = gfc_copy_expr (op2->ts.u.cl->length);
5591   else if (op2->expr_type == EXPR_CONSTANT)
5592     e2 = gfc_get_int_expr (gfc_default_integer_kind, NULL,
5593                            op2->value.character.length);
5594
5595   e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
5596
5597   if (!e1 || !e2)
5598     {
5599       gfc_free_expr (e1);
5600       gfc_free_expr (e2);
5601       
5602       return;
5603     }
5604
5605   e->ts.u.cl->length = gfc_add (e1, e2);
5606   e->ts.u.cl->length->ts.type = BT_INTEGER;
5607   e->ts.u.cl->length->ts.kind = gfc_charlen_int_kind;
5608   gfc_simplify_expr (e->ts.u.cl->length, 0);
5609   gfc_resolve_expr (e->ts.u.cl->length);
5610
5611   return;
5612 }
5613
5614
5615 /*  Ensure that an character expression has a charlen and, if possible, a
5616     length expression.  */
5617
5618 static void
5619 fixup_charlen (gfc_expr *e)
5620 {
5621   /* The cases fall through so that changes in expression type and the need
5622      for multiple fixes are picked up.  In all circumstances, a charlen should
5623      be available for the middle end to hang a backend_decl on.  */
5624   switch (e->expr_type)
5625     {
5626     case EXPR_OP:
5627       gfc_resolve_character_operator (e);
5628
5629     case EXPR_ARRAY:
5630       if (e->expr_type == EXPR_ARRAY)
5631         gfc_resolve_character_array_constructor (e);
5632
5633     case EXPR_SUBSTRING:
5634       if (!e->ts.u.cl && e->ref)
5635         gfc_resolve_substring_charlen (e);
5636
5637     default:
5638       if (!e->ts.u.cl)
5639         e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
5640
5641       break;
5642     }
5643 }
5644
5645
5646 /* Update an actual argument to include the passed-object for type-bound
5647    procedures at the right position.  */
5648
5649 static gfc_actual_arglist*
5650 update_arglist_pass (gfc_actual_arglist* lst, gfc_expr* po, unsigned argpos,
5651                      const char *name)
5652 {
5653   gcc_assert (argpos > 0);
5654
5655   if (argpos == 1)
5656     {
5657       gfc_actual_arglist* result;
5658
5659       result = gfc_get_actual_arglist ();
5660       result->expr = po;
5661       result->next = lst;
5662       if (name)
5663         result->name = name;
5664
5665       return result;
5666     }
5667
5668   if (lst)
5669     lst->next = update_arglist_pass (lst->next, po, argpos - 1, name);
5670   else
5671     lst = update_arglist_pass (NULL, po, argpos - 1, name);
5672   return lst;
5673 }
5674
5675
5676 /* Extract the passed-object from an EXPR_COMPCALL (a copy of it).  */
5677
5678 static gfc_expr*
5679 extract_compcall_passed_object (gfc_expr* e)
5680 {
5681   gfc_expr* po;
5682
5683   gcc_assert (e->expr_type == EXPR_COMPCALL);
5684
5685   if (e->value.compcall.base_object)
5686     po = gfc_copy_expr (e->value.compcall.base_object);
5687   else
5688     {
5689       po = gfc_get_expr ();
5690       po->expr_type = EXPR_VARIABLE;
5691       po->symtree = e->symtree;
5692       po->ref = gfc_copy_ref (e->ref);
5693       po->where = e->where;
5694     }
5695
5696   if (gfc_resolve_expr (po) == FAILURE)
5697     return NULL;
5698
5699   return po;
5700 }
5701
5702
5703 /* Update the arglist of an EXPR_COMPCALL expression to include the
5704    passed-object.  */
5705
5706 static gfc_try
5707 update_compcall_arglist (gfc_expr* e)
5708 {
5709   gfc_expr* po;
5710   gfc_typebound_proc* tbp;
5711
5712   tbp = e->value.compcall.tbp;
5713
5714   if (tbp->error)
5715     return FAILURE;
5716
5717   po = extract_compcall_passed_object (e);
5718   if (!po)
5719     return FAILURE;
5720
5721   if (tbp->nopass || e->value.compcall.ignore_pass)
5722     {
5723       gfc_free_expr (po);
5724       return SUCCESS;
5725     }
5726
5727   gcc_assert (tbp->pass_arg_num > 0);
5728   e->value.compcall.actual = update_arglist_pass (e->value.compcall.actual, po,
5729                                                   tbp->pass_arg_num,
5730                                                   tbp->pass_arg);
5731
5732   return SUCCESS;
5733 }
5734
5735
5736 /* Extract the passed object from a PPC call (a copy of it).  */
5737
5738 static gfc_expr*
5739 extract_ppc_passed_object (gfc_expr *e)
5740 {
5741   gfc_expr *po;
5742   gfc_ref **ref;
5743
5744   po = gfc_get_expr ();
5745   po->expr_type = EXPR_VARIABLE;
5746   po->symtree = e->symtree;
5747   po->ref = gfc_copy_ref (e->ref);
5748   po->where = e->where;
5749
5750   /* Remove PPC reference.  */
5751   ref = &po->ref;
5752   while ((*ref)->next)
5753     ref = &(*ref)->next;
5754   gfc_free_ref_list (*ref);
5755   *ref = NULL;
5756
5757   if (gfc_resolve_expr (po) == FAILURE)
5758     return NULL;
5759
5760   return po;
5761 }
5762
5763
5764 /* Update the actual arglist of a procedure pointer component to include the
5765    passed-object.  */
5766
5767 static gfc_try
5768 update_ppc_arglist (gfc_expr* e)
5769 {
5770   gfc_expr* po;
5771   gfc_component *ppc;
5772   gfc_typebound_proc* tb;
5773
5774   ppc = gfc_get_proc_ptr_comp (e);
5775   if (!ppc)
5776     return FAILURE;
5777
5778   tb = ppc->tb;
5779
5780   if (tb->error)
5781     return FAILURE;
5782   else if (tb->nopass)
5783     return SUCCESS;
5784
5785   po = extract_ppc_passed_object (e);
5786   if (!po)
5787     return FAILURE;
5788
5789   /* F08:R739.  */
5790   if (po->rank != 0)
5791     {
5792       gfc_error ("Passed-object at %L must be scalar", &e->where);
5793       return FAILURE;
5794     }
5795
5796   /* F08:C611.  */
5797   if (po->ts.type == BT_DERIVED && po->ts.u.derived->attr.abstract)
5798     {
5799       gfc_error ("Base object for procedure-pointer component call at %L is of"
5800                  " ABSTRACT type '%s'", &e->where, po->ts.u.derived->name);
5801       return FAILURE;
5802     }
5803
5804   gcc_assert (tb->pass_arg_num > 0);
5805   e->value.compcall.actual = update_arglist_pass (e->value.compcall.actual, po,
5806                                                   tb->pass_arg_num,
5807                                                   tb->pass_arg);
5808
5809   return SUCCESS;
5810 }
5811
5812
5813 /* Check that the object a TBP is called on is valid, i.e. it must not be
5814    of ABSTRACT type (as in subobject%abstract_parent%tbp()).  */
5815
5816 static gfc_try
5817 check_typebound_baseobject (gfc_expr* e)
5818 {
5819   gfc_expr* base;
5820   gfc_try return_value = FAILURE;
5821
5822   base = extract_compcall_passed_object (e);
5823   if (!base)
5824     return FAILURE;
5825
5826   gcc_assert (base->ts.type == BT_DERIVED || base->ts.type == BT_CLASS);
5827
5828   if (base->ts.type == BT_CLASS && !gfc_expr_attr (base).class_ok)
5829     return FAILURE;
5830
5831   /* F08:C611.  */
5832   if (base->ts.type == BT_DERIVED && base->ts.u.derived->attr.abstract)
5833     {
5834       gfc_error ("Base object for type-bound procedure call at %L is of"
5835                  " ABSTRACT type '%s'", &e->where, base->ts.u.derived->name);
5836       goto cleanup;
5837     }
5838
5839   /* F08:C1230. If the procedure called is NOPASS,
5840      the base object must be scalar.  */
5841   if (e->value.compcall.tbp->nopass && base->rank != 0)
5842     {
5843       gfc_error ("Base object for NOPASS type-bound procedure call at %L must"
5844                  " be scalar", &e->where);
5845       goto cleanup;
5846     }
5847
5848   return_value = SUCCESS;
5849
5850 cleanup:
5851   gfc_free_expr (base);
5852   return return_value;
5853 }
5854
5855
5856 /* Resolve a call to a type-bound procedure, either function or subroutine,
5857    statically from the data in an EXPR_COMPCALL expression.  The adapted
5858    arglist and the target-procedure symtree are returned.  */
5859
5860 static gfc_try
5861 resolve_typebound_static (gfc_expr* e, gfc_symtree** target,
5862                           gfc_actual_arglist** actual)
5863 {
5864   gcc_assert (e->expr_type == EXPR_COMPCALL);
5865   gcc_assert (!e->value.compcall.tbp->is_generic);
5866
5867   /* Update the actual arglist for PASS.  */
5868   if (update_compcall_arglist (e) == FAILURE)
5869     return FAILURE;
5870
5871   *actual = e->value.compcall.actual;
5872   *target = e->value.compcall.tbp->u.specific;
5873
5874   gfc_free_ref_list (e->ref);
5875   e->ref = NULL;
5876   e->value.compcall.actual = NULL;
5877
5878   /* If we find a deferred typebound procedure, check for derived types
5879      that an overriding typebound procedure has not been missed.  */
5880   if (e->value.compcall.name
5881       && !e->value.compcall.tbp->non_overridable
5882       && e->value.compcall.base_object
5883       && e->value.compcall.base_object->ts.type == BT_DERIVED)
5884     {
5885       gfc_symtree *st;
5886       gfc_symbol *derived;
5887
5888       /* Use the derived type of the base_object.  */
5889       derived = e->value.compcall.base_object->ts.u.derived;
5890       st = NULL;
5891
5892       /* If necessary, go through the inheritance chain.  */
5893       while (!st && derived)
5894         {
5895           /* Look for the typebound procedure 'name'.  */
5896           if (derived->f2k_derived && derived->f2k_derived->tb_sym_root)
5897             st = gfc_find_symtree (derived->f2k_derived->tb_sym_root,
5898                                    e->value.compcall.name);
5899           if (!st)
5900             derived = gfc_get_derived_super_type (derived);
5901         }
5902
5903       /* Now find the specific name in the derived type namespace.  */
5904       if (st && st->n.tb && st->n.tb->u.specific)
5905         gfc_find_sym_tree (st->n.tb->u.specific->name,
5906                            derived->ns, 1, &st);
5907       if (st)
5908         *target = st;
5909     }
5910   return SUCCESS;
5911 }
5912
5913
5914 /* Get the ultimate declared type from an expression.  In addition,
5915    return the last class/derived type reference and the copy of the
5916    reference list.  If check_types is set true, derived types are
5917    identified as well as class references.  */
5918 static gfc_symbol*
5919 get_declared_from_expr (gfc_ref **class_ref, gfc_ref **new_ref,
5920                         gfc_expr *e, bool check_types)
5921 {
5922   gfc_symbol *declared;
5923   gfc_ref *ref;
5924
5925   declared = NULL;
5926   if (class_ref)
5927     *class_ref = NULL;
5928   if (new_ref)
5929     *new_ref = gfc_copy_ref (e->ref);
5930
5931   for (ref = e->ref; ref; ref = ref->next)
5932     {
5933       if (ref->type != REF_COMPONENT)
5934         continue;
5935
5936       if ((ref->u.c.component->ts.type == BT_CLASS
5937              || (check_types && ref->u.c.component->ts.type == BT_DERIVED))
5938           && ref->u.c.component->attr.flavor != FL_PROCEDURE)
5939         {
5940           declared = ref->u.c.component->ts.u.derived;
5941           if (class_ref)
5942             *class_ref = ref;
5943         }
5944     }
5945
5946   if (declared == NULL)
5947     declared = e->symtree->n.sym->ts.u.derived;
5948
5949   return declared;
5950 }
5951
5952
5953 /* Given an EXPR_COMPCALL calling a GENERIC typebound procedure, figure out
5954    which of the specific bindings (if any) matches the arglist and transform
5955    the expression into a call of that binding.  */
5956
5957 static gfc_try
5958 resolve_typebound_generic_call (gfc_expr* e, const char **name)
5959 {
5960   gfc_typebound_proc* genproc;
5961   const char* genname;
5962   gfc_symtree *st;
5963   gfc_symbol *derived;
5964
5965   gcc_assert (e->expr_type == EXPR_COMPCALL);
5966   genname = e->value.compcall.name;
5967   genproc = e->value.compcall.tbp;
5968
5969   if (!genproc->is_generic)
5970     return SUCCESS;
5971
5972   /* Try the bindings on this type and in the inheritance hierarchy.  */
5973   for (; genproc; genproc = genproc->overridden)
5974     {
5975       gfc_tbp_generic* g;
5976
5977       gcc_assert (genproc->is_generic);
5978       for (g = genproc->u.generic; g; g = g->next)
5979         {
5980           gfc_symbol* target;
5981           gfc_actual_arglist* args;
5982           bool matches;
5983
5984           gcc_assert (g->specific);
5985
5986           if (g->specific->error)
5987             continue;
5988
5989           target = g->specific->u.specific->n.sym;
5990
5991           /* Get the right arglist by handling PASS/NOPASS.  */
5992           args = gfc_copy_actual_arglist (e->value.compcall.actual);
5993           if (!g->specific->nopass)
5994             {
5995               gfc_expr* po;
5996               po = extract_compcall_passed_object (e);
5997               if (!po)
5998                 return FAILURE;
5999
6000               gcc_assert (g->specific->pass_arg_num > 0);
6001               gcc_assert (!g->specific->error);
6002               args = update_arglist_pass (args, po, g->specific->pass_arg_num,
6003                                           g->specific->pass_arg);
6004             }
6005           resolve_actual_arglist (args, target->attr.proc,
6006                                   is_external_proc (target) && !target->formal);
6007
6008           /* Check if this arglist matches the formal.  */
6009           matches = gfc_arglist_matches_symbol (&args, target);
6010
6011           /* Clean up and break out of the loop if we've found it.  */
6012           gfc_free_actual_arglist (args);
6013           if (matches)
6014             {
6015               e->value.compcall.tbp = g->specific;
6016               genname = g->specific_st->name;
6017               /* Pass along the name for CLASS methods, where the vtab
6018                  procedure pointer component has to be referenced.  */
6019               if (name)
6020                 *name = genname;
6021               goto success;
6022             }
6023         }
6024     }
6025
6026   /* Nothing matching found!  */
6027   gfc_error ("Found no matching specific binding for the call to the GENERIC"
6028              " '%s' at %L", genname, &e->where);
6029   return FAILURE;
6030
6031 success:
6032   /* Make sure that we have the right specific instance for the name.  */
6033   derived = get_declared_from_expr (NULL, NULL, e, true);
6034
6035   st = gfc_find_typebound_proc (derived, NULL, genname, true, &e->where);
6036   if (st)
6037     e->value.compcall.tbp = st->n.tb;
6038
6039   return SUCCESS;
6040 }
6041
6042
6043 /* Resolve a call to a type-bound subroutine.  */
6044
6045 static gfc_try
6046 resolve_typebound_call (gfc_code* c, const char **name)
6047 {
6048   gfc_actual_arglist* newactual;
6049   gfc_symtree* target;
6050
6051   /* Check that's really a SUBROUTINE.  */
6052   if (!c->expr1->value.compcall.tbp->subroutine)
6053     {
6054       gfc_error ("'%s' at %L should be a SUBROUTINE",
6055                  c->expr1->value.compcall.name, &c->loc);
6056       return FAILURE;
6057     }
6058
6059   if (check_typebound_baseobject (c->expr1) == FAILURE)
6060     return FAILURE;
6061
6062   /* Pass along the name for CLASS methods, where the vtab
6063      procedure pointer component has to be referenced.  */
6064   if (name)
6065     *name = c->expr1->value.compcall.name;
6066
6067   if (resolve_typebound_generic_call (c->expr1, name) == FAILURE)
6068     return FAILURE;
6069
6070   /* Transform into an ordinary EXEC_CALL for now.  */
6071
6072   if (resolve_typebound_static (c->expr1, &target, &newactual) == FAILURE)
6073     return FAILURE;
6074
6075   c->ext.actual = newactual;
6076   c->symtree = target;
6077   c->op = (c->expr1->value.compcall.assign ? EXEC_ASSIGN_CALL : EXEC_CALL);
6078
6079   gcc_assert (!c->expr1->ref && !c->expr1->value.compcall.actual);
6080
6081   gfc_free_expr (c->expr1);
6082   c->expr1 = gfc_get_expr ();
6083   c->expr1->expr_type = EXPR_FUNCTION;
6084   c->expr1->symtree = target;
6085   c->expr1->where = c->loc;
6086
6087   return resolve_call (c);
6088 }
6089
6090
6091 /* Resolve a component-call expression.  */
6092 static gfc_try
6093 resolve_compcall (gfc_expr* e, const char **name)
6094 {
6095   gfc_actual_arglist* newactual;
6096   gfc_symtree* target;
6097
6098   /* Check that's really a FUNCTION.  */
6099   if (!e->value.compcall.tbp->function)
6100     {
6101       gfc_error ("'%s' at %L should be a FUNCTION",
6102                  e->value.compcall.name, &e->where);
6103       return FAILURE;
6104     }
6105
6106   /* These must not be assign-calls!  */
6107   gcc_assert (!e->value.compcall.assign);
6108
6109   if (check_typebound_baseobject (e) == FAILURE)
6110     return FAILURE;
6111
6112   /* Pass along the name for CLASS methods, where the vtab
6113      procedure pointer component has to be referenced.  */
6114   if (name)
6115     *name = e->value.compcall.name;
6116
6117   if (resolve_typebound_generic_call (e, name) == FAILURE)
6118     return FAILURE;
6119   gcc_assert (!e->value.compcall.tbp->is_generic);
6120
6121   /* Take the rank from the function's symbol.  */
6122   if (e->value.compcall.tbp->u.specific->n.sym->as)
6123     e->rank = e->value.compcall.tbp->u.specific->n.sym->as->rank;
6124
6125   /* For now, we simply transform it into an EXPR_FUNCTION call with the same
6126      arglist to the TBP's binding target.  */
6127
6128   if (resolve_typebound_static (e, &target, &newactual) == FAILURE)
6129     return FAILURE;
6130
6131   e->value.function.actual = newactual;
6132   e->value.function.name = NULL;
6133   e->value.function.esym = target->n.sym;
6134   e->value.function.isym = NULL;
6135   e->symtree = target;
6136   e->ts = target->n.sym->ts;
6137   e->expr_type = EXPR_FUNCTION;
6138
6139   /* Resolution is not necessary if this is a class subroutine; this
6140      function only has to identify the specific proc. Resolution of
6141      the call will be done next in resolve_typebound_call.  */
6142   return gfc_resolve_expr (e);
6143 }
6144
6145
6146
6147 /* Resolve a typebound function, or 'method'. First separate all
6148    the non-CLASS references by calling resolve_compcall directly.  */
6149
6150 static gfc_try
6151 resolve_typebound_function (gfc_expr* e)
6152 {
6153   gfc_symbol *declared;
6154   gfc_component *c;
6155   gfc_ref *new_ref;
6156   gfc_ref *class_ref;
6157   gfc_symtree *st;
6158   const char *name;
6159   gfc_typespec ts;
6160   gfc_expr *expr;
6161   bool overridable;
6162
6163   st = e->symtree;
6164
6165   /* Deal with typebound operators for CLASS objects.  */
6166   expr = e->value.compcall.base_object;
6167   overridable = !e->value.compcall.tbp->non_overridable;
6168   if (expr && expr->ts.type == BT_CLASS && e->value.compcall.name)
6169     {
6170       /* If the base_object is not a variable, the corresponding actual
6171          argument expression must be stored in e->base_expression so
6172          that the corresponding tree temporary can be used as the base
6173          object in gfc_conv_procedure_call.  */
6174       if (expr->expr_type != EXPR_VARIABLE)
6175         {
6176           gfc_actual_arglist *args;
6177
6178           for (args= e->value.function.actual; args; args = args->next)
6179             {
6180               if (expr == args->expr)
6181                 expr = args->expr;
6182             }
6183         }
6184
6185       /* Since the typebound operators are generic, we have to ensure
6186          that any delays in resolution are corrected and that the vtab
6187          is present.  */
6188       ts = expr->ts;
6189       declared = ts.u.derived;
6190       c = gfc_find_component (declared, "_vptr", true, true);
6191       if (c->ts.u.derived == NULL)
6192         c->ts.u.derived = gfc_find_derived_vtab (declared);
6193
6194       if (resolve_compcall (e, &name) == FAILURE)
6195         return FAILURE;
6196
6197       /* Use the generic name if it is there.  */
6198       name = name ? name : e->value.function.esym->name;
6199       e->symtree = expr->symtree;
6200       e->ref = gfc_copy_ref (expr->ref);
6201       get_declared_from_expr (&class_ref, NULL, e, false);
6202
6203       /* Trim away the extraneous references that emerge from nested
6204          use of interface.c (extend_expr).  */
6205       if (class_ref && class_ref->next)
6206         {
6207           gfc_free_ref_list (class_ref->next);
6208           class_ref->next = NULL;
6209         }
6210       else if (e->ref && !class_ref)
6211         {
6212           gfc_free_ref_list (e->ref);
6213           e->ref = NULL;
6214         }
6215
6216       gfc_add_vptr_component (e);
6217       gfc_add_component_ref (e, name);
6218       e->value.function.esym = NULL;
6219       if (expr->expr_type != EXPR_VARIABLE)
6220         e->base_expr = expr;
6221       return SUCCESS;
6222     }
6223
6224   if (st == NULL)
6225     return resolve_compcall (e, NULL);
6226
6227   if (resolve_ref (e) == FAILURE)
6228     return FAILURE;
6229
6230   /* Get the CLASS declared type.  */
6231   declared = get_declared_from_expr (&class_ref, &new_ref, e, true);
6232
6233   /* Weed out cases of the ultimate component being a derived type.  */
6234   if ((class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
6235          || (!class_ref && st->n.sym->ts.type != BT_CLASS))
6236     {
6237       gfc_free_ref_list (new_ref);
6238       return resolve_compcall (e, NULL);
6239     }
6240
6241   c = gfc_find_component (declared, "_data", true, true);
6242   declared = c->ts.u.derived;
6243
6244   /* Treat the call as if it is a typebound procedure, in order to roll
6245      out the correct name for the specific function.  */
6246   if (resolve_compcall (e, &name) == FAILURE)
6247     return FAILURE;
6248   ts = e->ts;
6249
6250   if (overridable)
6251     {
6252       /* Convert the expression to a procedure pointer component call.  */
6253       e->value.function.esym = NULL;
6254       e->symtree = st;
6255
6256       if (new_ref)  
6257         e->ref = new_ref;
6258
6259       /* '_vptr' points to the vtab, which contains the procedure pointers.  */
6260       gfc_add_vptr_component (e);
6261       gfc_add_component_ref (e, name);
6262
6263       /* Recover the typespec for the expression.  This is really only
6264         necessary for generic procedures, where the additional call
6265         to gfc_add_component_ref seems to throw the collection of the
6266         correct typespec.  */
6267       e->ts = ts;
6268     }
6269
6270   return SUCCESS;
6271 }
6272
6273 /* Resolve a typebound subroutine, or 'method'. First separate all
6274    the non-CLASS references by calling resolve_typebound_call
6275    directly.  */
6276
6277 static gfc_try
6278 resolve_typebound_subroutine (gfc_code *code)
6279 {
6280   gfc_symbol *declared;
6281   gfc_component *c;
6282   gfc_ref *new_ref;
6283   gfc_ref *class_ref;
6284   gfc_symtree *st;
6285   const char *name;
6286   gfc_typespec ts;
6287   gfc_expr *expr;
6288   bool overridable;
6289
6290   st = code->expr1->symtree;
6291
6292   /* Deal with typebound operators for CLASS objects.  */
6293   expr = code->expr1->value.compcall.base_object;
6294   overridable = !code->expr1->value.compcall.tbp->non_overridable;
6295   if (expr && expr->ts.type == BT_CLASS && code->expr1->value.compcall.name)
6296     {
6297       /* If the base_object is not a variable, the corresponding actual
6298          argument expression must be stored in e->base_expression so
6299          that the corresponding tree temporary can be used as the base
6300          object in gfc_conv_procedure_call.  */
6301       if (expr->expr_type != EXPR_VARIABLE)
6302         {
6303           gfc_actual_arglist *args;
6304
6305           args= code->expr1->value.function.actual;
6306           for (; args; args = args->next)
6307             if (expr == args->expr)
6308               expr = args->expr;
6309         }
6310
6311       /* Since the typebound operators are generic, we have to ensure
6312          that any delays in resolution are corrected and that the vtab
6313          is present.  */
6314       declared = expr->ts.u.derived;
6315       c = gfc_find_component (declared, "_vptr", true, true);
6316       if (c->ts.u.derived == NULL)
6317         c->ts.u.derived = gfc_find_derived_vtab (declared);
6318
6319       if (resolve_typebound_call (code, &name) == FAILURE)
6320         return FAILURE;
6321
6322       /* Use the generic name if it is there.  */
6323       name = name ? name : code->expr1->value.function.esym->name;
6324       code->expr1->symtree = expr->symtree;
6325       code->expr1->ref = gfc_copy_ref (expr->ref);
6326
6327       /* Trim away the extraneous references that emerge from nested
6328          use of interface.c (extend_expr).  */
6329       get_declared_from_expr (&class_ref, NULL, code->expr1, false);
6330       if (class_ref && class_ref->next)
6331         {
6332           gfc_free_ref_list (class_ref->next);
6333           class_ref->next = NULL;
6334         }
6335       else if (code->expr1->ref && !class_ref)
6336         {
6337           gfc_free_ref_list (code->expr1->ref);
6338           code->expr1->ref = NULL;
6339         }
6340
6341       /* Now use the procedure in the vtable.  */
6342       gfc_add_vptr_component (code->expr1);
6343       gfc_add_component_ref (code->expr1, name);
6344       code->expr1->value.function.esym = NULL;
6345       if (expr->expr_type != EXPR_VARIABLE)
6346         code->expr1->base_expr = expr;
6347       return SUCCESS;
6348     }
6349
6350   if (st == NULL)
6351     return resolve_typebound_call (code, NULL);
6352
6353   if (resolve_ref (code->expr1) == FAILURE)
6354     return FAILURE;
6355
6356   /* Get the CLASS declared type.  */
6357   get_declared_from_expr (&class_ref, &new_ref, code->expr1, true);
6358
6359   /* Weed out cases of the ultimate component being a derived type.  */
6360   if ((class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
6361          || (!class_ref && st->n.sym->ts.type != BT_CLASS))
6362     {
6363       gfc_free_ref_list (new_ref);
6364       return resolve_typebound_call (code, NULL);
6365     }
6366
6367   if (resolve_typebound_call (code, &name) == FAILURE)
6368     return FAILURE;
6369   ts = code->expr1->ts;
6370
6371   if (overridable)
6372     {
6373       /* Convert the expression to a procedure pointer component call.  */
6374       code->expr1->value.function.esym = NULL;
6375       code->expr1->symtree = st;
6376
6377       if (new_ref)
6378         code->expr1->ref = new_ref;
6379
6380       /* '_vptr' points to the vtab, which contains the procedure pointers.  */
6381       gfc_add_vptr_component (code->expr1);
6382       gfc_add_component_ref (code->expr1, name);
6383
6384       /* Recover the typespec for the expression.  This is really only
6385         necessary for generic procedures, where the additional call
6386         to gfc_add_component_ref seems to throw the collection of the
6387         correct typespec.  */
6388       code->expr1->ts = ts;
6389     }
6390
6391   return SUCCESS;
6392 }
6393
6394
6395 /* Resolve a CALL to a Procedure Pointer Component (Subroutine).  */
6396
6397 static gfc_try
6398 resolve_ppc_call (gfc_code* c)
6399 {
6400   gfc_component *comp;
6401
6402   comp = gfc_get_proc_ptr_comp (c->expr1);
6403   gcc_assert (comp != NULL);
6404
6405   c->resolved_sym = c->expr1->symtree->n.sym;
6406   c->expr1->expr_type = EXPR_VARIABLE;
6407
6408   if (!comp->attr.subroutine)
6409     gfc_add_subroutine (&comp->attr, comp->name, &c->expr1->where);
6410
6411   if (resolve_ref (c->expr1) == FAILURE)
6412     return FAILURE;
6413
6414   if (update_ppc_arglist (c->expr1) == FAILURE)
6415     return FAILURE;
6416
6417   c->ext.actual = c->expr1->value.compcall.actual;
6418
6419   if (resolve_actual_arglist (c->ext.actual, comp->attr.proc,
6420                               comp->formal == NULL) == FAILURE)
6421     return FAILURE;
6422
6423   gfc_ppc_use (comp, &c->expr1->value.compcall.actual, &c->expr1->where);
6424
6425   return SUCCESS;
6426 }
6427
6428
6429 /* Resolve a Function Call to a Procedure Pointer Component (Function).  */
6430
6431 static gfc_try
6432 resolve_expr_ppc (gfc_expr* e)
6433 {
6434   gfc_component *comp;
6435
6436   comp = gfc_get_proc_ptr_comp (e);
6437   gcc_assert (comp != NULL);
6438
6439   /* Convert to EXPR_FUNCTION.  */
6440   e->expr_type = EXPR_FUNCTION;
6441   e->value.function.isym = NULL;
6442   e->value.function.actual = e->value.compcall.actual;
6443   e->ts = comp->ts;
6444   if (comp->as != NULL)
6445     e->rank = comp->as->rank;
6446
6447   if (!comp->attr.function)
6448     gfc_add_function (&comp->attr, comp->name, &e->where);
6449
6450   if (resolve_ref (e) == FAILURE)
6451     return FAILURE;
6452
6453   if (resolve_actual_arglist (e->value.function.actual, comp->attr.proc,
6454                               comp->formal == NULL) == FAILURE)
6455     return FAILURE;
6456
6457   if (update_ppc_arglist (e) == FAILURE)
6458     return FAILURE;
6459
6460   gfc_ppc_use (comp, &e->value.compcall.actual, &e->where);
6461
6462   return SUCCESS;
6463 }
6464
6465
6466 static bool
6467 gfc_is_expandable_expr (gfc_expr *e)
6468 {
6469   gfc_constructor *con;
6470
6471   if (e->expr_type == EXPR_ARRAY)
6472     {
6473       /* Traverse the constructor looking for variables that are flavor
6474          parameter.  Parameters must be expanded since they are fully used at
6475          compile time.  */
6476       con = gfc_constructor_first (e->value.constructor);
6477       for (; con; con = gfc_constructor_next (con))
6478         {
6479           if (con->expr->expr_type == EXPR_VARIABLE
6480               && con->expr->symtree
6481               && (con->expr->symtree->n.sym->attr.flavor == FL_PARAMETER
6482               || con->expr->symtree->n.sym->attr.flavor == FL_VARIABLE))
6483             return true;
6484           if (con->expr->expr_type == EXPR_ARRAY
6485               && gfc_is_expandable_expr (con->expr))
6486             return true;
6487         }
6488     }
6489
6490   return false;
6491 }
6492
6493 /* Resolve an expression.  That is, make sure that types of operands agree
6494    with their operators, intrinsic operators are converted to function calls
6495    for overloaded types and unresolved function references are resolved.  */
6496
6497 gfc_try
6498 gfc_resolve_expr (gfc_expr *e)
6499 {
6500   gfc_try t;
6501   bool inquiry_save, actual_arg_save, first_actual_arg_save;
6502
6503   if (e == NULL)
6504     return SUCCESS;
6505
6506   /* inquiry_argument only applies to variables.  */
6507   inquiry_save = inquiry_argument;
6508   actual_arg_save = actual_arg;
6509   first_actual_arg_save = first_actual_arg;
6510
6511   if (e->expr_type != EXPR_VARIABLE)
6512     {
6513       inquiry_argument = false;
6514       actual_arg = false;
6515       first_actual_arg = false;
6516     }
6517
6518   switch (e->expr_type)
6519     {
6520     case EXPR_OP:
6521       t = resolve_operator (e);
6522       break;
6523
6524     case EXPR_FUNCTION:
6525     case EXPR_VARIABLE:
6526
6527       if (check_host_association (e))
6528         t = resolve_function (e);
6529       else
6530         {
6531           t = resolve_variable (e);
6532           if (t == SUCCESS)
6533             expression_rank (e);
6534         }
6535
6536       if (e->ts.type == BT_CHARACTER && e->ts.u.cl == NULL && e->ref
6537           && e->ref->type != REF_SUBSTRING)
6538         gfc_resolve_substring_charlen (e);
6539
6540       break;
6541
6542     case EXPR_COMPCALL:
6543       t = resolve_typebound_function (e);
6544       break;
6545
6546     case EXPR_SUBSTRING:
6547       t = resolve_ref (e);
6548       break;
6549
6550     case EXPR_CONSTANT:
6551     case EXPR_NULL:
6552       t = SUCCESS;
6553       break;
6554
6555     case EXPR_PPC:
6556       t = resolve_expr_ppc (e);
6557       break;
6558
6559     case EXPR_ARRAY:
6560       t = FAILURE;
6561       if (resolve_ref (e) == FAILURE)
6562         break;
6563
6564       t = gfc_resolve_array_constructor (e);
6565       /* Also try to expand a constructor.  */
6566       if (t == SUCCESS)
6567         {
6568           expression_rank (e);
6569           if (gfc_is_constant_expr (e) || gfc_is_expandable_expr (e))
6570             gfc_expand_constructor (e, false);
6571         }
6572
6573       /* This provides the opportunity for the length of constructors with
6574          character valued function elements to propagate the string length
6575          to the expression.  */
6576       if (t == SUCCESS && e->ts.type == BT_CHARACTER)
6577         {
6578           /* For efficiency, we call gfc_expand_constructor for BT_CHARACTER
6579              here rather then add a duplicate test for it above.  */ 
6580           gfc_expand_constructor (e, false);
6581           t = gfc_resolve_character_array_constructor (e);
6582         }
6583
6584       break;
6585
6586     case EXPR_STRUCTURE:
6587       t = resolve_ref (e);
6588       if (t == FAILURE)
6589         break;
6590
6591       t = resolve_structure_cons (e, 0);
6592       if (t == FAILURE)
6593         break;
6594
6595       t = gfc_simplify_expr (e, 0);
6596       break;
6597
6598     default:
6599       gfc_internal_error ("gfc_resolve_expr(): Bad expression type");
6600     }
6601
6602   if (e->ts.type == BT_CHARACTER && t == SUCCESS && !e->ts.u.cl)
6603     fixup_charlen (e);
6604
6605   inquiry_argument = inquiry_save;
6606   actual_arg = actual_arg_save;
6607   first_actual_arg = first_actual_arg_save;
6608
6609   return t;
6610 }
6611
6612
6613 /* Resolve an expression from an iterator.  They must be scalar and have
6614    INTEGER or (optionally) REAL type.  */
6615
6616 static gfc_try
6617 gfc_resolve_iterator_expr (gfc_expr *expr, bool real_ok,
6618                            const char *name_msgid)
6619 {
6620   if (gfc_resolve_expr (expr) == FAILURE)
6621     return FAILURE;
6622
6623   if (expr->rank != 0)
6624     {
6625       gfc_error ("%s at %L must be a scalar", _(name_msgid), &expr->where);
6626       return FAILURE;
6627     }
6628
6629   if (expr->ts.type != BT_INTEGER)
6630     {
6631       if (expr->ts.type == BT_REAL)
6632         {
6633           if (real_ok)
6634             return gfc_notify_std (GFC_STD_F95_DEL,
6635                                    "%s at %L must be integer",
6636                                    _(name_msgid), &expr->where);
6637           else
6638             {
6639               gfc_error ("%s at %L must be INTEGER", _(name_msgid),
6640                          &expr->where);
6641               return FAILURE;
6642             }
6643         }
6644       else
6645         {
6646           gfc_error ("%s at %L must be INTEGER", _(name_msgid), &expr->where);
6647           return FAILURE;
6648         }
6649     }
6650   return SUCCESS;
6651 }
6652
6653
6654 /* Resolve the expressions in an iterator structure.  If REAL_OK is
6655    false allow only INTEGER type iterators, otherwise allow REAL types.  */
6656
6657 gfc_try
6658 gfc_resolve_iterator (gfc_iterator *iter, bool real_ok)
6659 {
6660   if (gfc_resolve_iterator_expr (iter->var, real_ok, "Loop variable")
6661       == FAILURE)
6662     return FAILURE;
6663
6664   if (gfc_check_vardef_context (iter->var, false, false, _("iterator variable"))
6665       == FAILURE)
6666     return FAILURE;
6667
6668   if (gfc_resolve_iterator_expr (iter->start, real_ok,
6669                                  "Start expression in DO loop") == FAILURE)
6670     return FAILURE;
6671
6672   if (gfc_resolve_iterator_expr (iter->end, real_ok,
6673                                  "End expression in DO loop") == FAILURE)
6674     return FAILURE;
6675
6676   if (gfc_resolve_iterator_expr (iter->step, real_ok,
6677                                  "Step expression in DO loop") == FAILURE)
6678     return FAILURE;
6679
6680   if (iter->step->expr_type == EXPR_CONSTANT)
6681     {
6682       if ((iter->step->ts.type == BT_INTEGER
6683            && mpz_cmp_ui (iter->step->value.integer, 0) == 0)
6684           || (iter->step->ts.type == BT_REAL
6685               && mpfr_sgn (iter->step->value.real) == 0))
6686         {
6687           gfc_error ("Step expression in DO loop at %L cannot be zero",
6688                      &iter->step->where);
6689           return FAILURE;
6690         }
6691     }
6692
6693   /* Convert start, end, and step to the same type as var.  */
6694   if (iter->start->ts.kind != iter->var->ts.kind
6695       || iter->start->ts.type != iter->var->ts.type)
6696     gfc_convert_type (iter->start, &iter->var->ts, 2);
6697
6698   if (iter->end->ts.kind != iter->var->ts.kind
6699       || iter->end->ts.type != iter->var->ts.type)
6700     gfc_convert_type (iter->end, &iter->var->ts, 2);
6701
6702   if (iter->step->ts.kind != iter->var->ts.kind
6703       || iter->step->ts.type != iter->var->ts.type)
6704     gfc_convert_type (iter->step, &iter->var->ts, 2);
6705
6706   if (iter->start->expr_type == EXPR_CONSTANT
6707       && iter->end->expr_type == EXPR_CONSTANT
6708       && iter->step->expr_type == EXPR_CONSTANT)
6709     {
6710       int sgn, cmp;
6711       if (iter->start->ts.type == BT_INTEGER)
6712         {
6713           sgn = mpz_cmp_ui (iter->step->value.integer, 0);
6714           cmp = mpz_cmp (iter->end->value.integer, iter->start->value.integer);
6715         }
6716       else
6717         {
6718           sgn = mpfr_sgn (iter->step->value.real);
6719           cmp = mpfr_cmp (iter->end->value.real, iter->start->value.real);
6720         }
6721       if ((sgn > 0 && cmp < 0) || (sgn < 0 && cmp > 0))
6722         gfc_warning ("DO loop at %L will be executed zero times",
6723                      &iter->step->where);
6724     }
6725
6726   return SUCCESS;
6727 }
6728
6729
6730 /* Traversal function for find_forall_index.  f == 2 signals that
6731    that variable itself is not to be checked - only the references.  */
6732
6733 static bool
6734 forall_index (gfc_expr *expr, gfc_symbol *sym, int *f)
6735 {
6736   if (expr->expr_type != EXPR_VARIABLE)
6737     return false;
6738   
6739   /* A scalar assignment  */
6740   if (!expr->ref || *f == 1)
6741     {
6742       if (expr->symtree->n.sym == sym)
6743         return true;
6744       else
6745         return false;
6746     }
6747
6748   if (*f == 2)
6749     *f = 1;
6750   return false;
6751 }
6752
6753
6754 /* Check whether the FORALL index appears in the expression or not.
6755    Returns SUCCESS if SYM is found in EXPR.  */
6756
6757 gfc_try
6758 find_forall_index (gfc_expr *expr, gfc_symbol *sym, int f)
6759 {
6760   if (gfc_traverse_expr (expr, sym, forall_index, f))
6761     return SUCCESS;
6762   else
6763     return FAILURE;
6764 }
6765
6766
6767 /* Resolve a list of FORALL iterators.  The FORALL index-name is constrained
6768    to be a scalar INTEGER variable.  The subscripts and stride are scalar
6769    INTEGERs, and if stride is a constant it must be nonzero.
6770    Furthermore "A subscript or stride in a forall-triplet-spec shall
6771    not contain a reference to any index-name in the
6772    forall-triplet-spec-list in which it appears." (7.5.4.1)  */
6773
6774 static void
6775 resolve_forall_iterators (gfc_forall_iterator *it)
6776 {
6777   gfc_forall_iterator *iter, *iter2;
6778
6779   for (iter = it; iter; iter = iter->next)
6780     {
6781       if (gfc_resolve_expr (iter->var) == SUCCESS
6782           && (iter->var->ts.type != BT_INTEGER || iter->var->rank != 0))
6783         gfc_error ("FORALL index-name at %L must be a scalar INTEGER",
6784                    &iter->var->where);
6785
6786       if (gfc_resolve_expr (iter->start) == SUCCESS
6787           && (iter->start->ts.type != BT_INTEGER || iter->start->rank != 0))
6788         gfc_error ("FORALL start expression at %L must be a scalar INTEGER",
6789                    &iter->start->where);
6790       if (iter->var->ts.kind != iter->start->ts.kind)
6791         gfc_convert_type (iter->start, &iter->var->ts, 1);
6792
6793       if (gfc_resolve_expr (iter->end) == SUCCESS
6794           && (iter->end->ts.type != BT_INTEGER || iter->end->rank != 0))
6795         gfc_error ("FORALL end expression at %L must be a scalar INTEGER",
6796                    &iter->end->where);
6797       if (iter->var->ts.kind != iter->end->ts.kind)
6798         gfc_convert_type (iter->end, &iter->var->ts, 1);
6799
6800       if (gfc_resolve_expr (iter->stride) == SUCCESS)
6801         {
6802           if (iter->stride->ts.type != BT_INTEGER || iter->stride->rank != 0)
6803             gfc_error ("FORALL stride expression at %L must be a scalar %s",
6804                        &iter->stride->where, "INTEGER");
6805
6806           if (iter->stride->expr_type == EXPR_CONSTANT
6807               && mpz_cmp_ui(iter->stride->value.integer, 0) == 0)
6808             gfc_error ("FORALL stride expression at %L cannot be zero",
6809                        &iter->stride->where);
6810         }
6811       if (iter->var->ts.kind != iter->stride->ts.kind)
6812         gfc_convert_type (iter->stride, &iter->var->ts, 1);
6813     }
6814
6815   for (iter = it; iter; iter = iter->next)
6816     for (iter2 = iter; iter2; iter2 = iter2->next)
6817       {
6818         if (find_forall_index (iter2->start,
6819                                iter->var->symtree->n.sym, 0) == SUCCESS
6820             || find_forall_index (iter2->end,
6821                                   iter->var->symtree->n.sym, 0) == SUCCESS
6822             || find_forall_index (iter2->stride,
6823                                   iter->var->symtree->n.sym, 0) == SUCCESS)
6824           gfc_error ("FORALL index '%s' may not appear in triplet "
6825                      "specification at %L", iter->var->symtree->name,
6826                      &iter2->start->where);
6827       }
6828 }
6829
6830
6831 /* Given a pointer to a symbol that is a derived type, see if it's
6832    inaccessible, i.e. if it's defined in another module and the components are
6833    PRIVATE.  The search is recursive if necessary.  Returns zero if no
6834    inaccessible components are found, nonzero otherwise.  */
6835
6836 static int
6837 derived_inaccessible (gfc_symbol *sym)
6838 {
6839   gfc_component *c;
6840
6841   if (sym->attr.use_assoc && sym->attr.private_comp)
6842     return 1;
6843
6844   for (c = sym->components; c; c = c->next)
6845     {
6846         if (c->ts.type == BT_DERIVED && derived_inaccessible (c->ts.u.derived))
6847           return 1;
6848     }
6849
6850   return 0;
6851 }
6852
6853
6854 /* Resolve the argument of a deallocate expression.  The expression must be
6855    a pointer or a full array.  */
6856
6857 static gfc_try
6858 resolve_deallocate_expr (gfc_expr *e)
6859 {
6860   symbol_attribute attr;
6861   int allocatable, pointer;
6862   gfc_ref *ref;
6863   gfc_symbol *sym;
6864   gfc_component *c;
6865
6866   if (gfc_resolve_expr (e) == FAILURE)
6867     return FAILURE;
6868
6869   if (e->expr_type != EXPR_VARIABLE)
6870     goto bad;
6871
6872   sym = e->symtree->n.sym;
6873
6874   if (sym->ts.type == BT_CLASS)
6875     {
6876       allocatable = CLASS_DATA (sym)->attr.allocatable;
6877       pointer = CLASS_DATA (sym)->attr.class_pointer;
6878     }
6879   else
6880     {
6881       allocatable = sym->attr.allocatable;
6882       pointer = sym->attr.pointer;
6883     }
6884   for (ref = e->ref; ref; ref = ref->next)
6885     {
6886       switch (ref->type)
6887         {
6888         case REF_ARRAY:
6889           if (ref->u.ar.type != AR_FULL
6890               && !(ref->u.ar.type == AR_ELEMENT && ref->u.ar.as->rank == 0
6891                    && ref->u.ar.codimen && gfc_ref_this_image (ref)))
6892             allocatable = 0;
6893           break;
6894
6895         case REF_COMPONENT:
6896           c = ref->u.c.component;
6897           if (c->ts.type == BT_CLASS)
6898             {
6899               allocatable = CLASS_DATA (c)->attr.allocatable;
6900               pointer = CLASS_DATA (c)->attr.class_pointer;
6901             }
6902           else
6903             {
6904               allocatable = c->attr.allocatable;
6905               pointer = c->attr.pointer;
6906             }
6907           break;
6908
6909         case REF_SUBSTRING:
6910           allocatable = 0;
6911           break;
6912         }
6913     }
6914
6915   attr = gfc_expr_attr (e);
6916
6917   if (allocatable == 0 && attr.pointer == 0)
6918     {
6919     bad:
6920       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
6921                  &e->where);
6922       return FAILURE;
6923     }
6924
6925   /* F2008, C644.  */
6926   if (gfc_is_coindexed (e))
6927     {
6928       gfc_error ("Coindexed allocatable object at %L", &e->where);
6929       return FAILURE;
6930     }
6931
6932   if (pointer
6933       && gfc_check_vardef_context (e, true, true, _("DEALLOCATE object"))
6934          == FAILURE)
6935     return FAILURE;
6936   if (gfc_check_vardef_context (e, false, true, _("DEALLOCATE object"))
6937       == FAILURE)
6938     return FAILURE;
6939
6940   return SUCCESS;
6941 }
6942
6943
6944 /* Returns true if the expression e contains a reference to the symbol sym.  */
6945 static bool
6946 sym_in_expr (gfc_expr *e, gfc_symbol *sym, int *f ATTRIBUTE_UNUSED)
6947 {
6948   if (e->expr_type == EXPR_VARIABLE && e->symtree->n.sym == sym)
6949     return true;
6950
6951   return false;
6952 }
6953
6954 bool
6955 gfc_find_sym_in_expr (gfc_symbol *sym, gfc_expr *e)
6956 {
6957   return gfc_traverse_expr (e, sym, sym_in_expr, 0);
6958 }
6959
6960
6961 /* Given the expression node e for an allocatable/pointer of derived type to be
6962    allocated, get the expression node to be initialized afterwards (needed for
6963    derived types with default initializers, and derived types with allocatable
6964    components that need nullification.)  */
6965
6966 gfc_expr *
6967 gfc_expr_to_initialize (gfc_expr *e)
6968 {
6969   gfc_expr *result;
6970   gfc_ref *ref;
6971   int i;
6972
6973   result = gfc_copy_expr (e);
6974
6975   /* Change the last array reference from AR_ELEMENT to AR_FULL.  */
6976   for (ref = result->ref; ref; ref = ref->next)
6977     if (ref->type == REF_ARRAY && ref->next == NULL)
6978       {
6979         ref->u.ar.type = AR_FULL;
6980
6981         for (i = 0; i < ref->u.ar.dimen; i++)
6982           ref->u.ar.start[i] = ref->u.ar.end[i] = ref->u.ar.stride[i] = NULL;
6983
6984         break;
6985       }
6986
6987   gfc_free_shape (&result->shape, result->rank);
6988
6989   /* Recalculate rank, shape, etc.  */
6990   gfc_resolve_expr (result);
6991   return result;
6992 }
6993
6994
6995 /* If the last ref of an expression is an array ref, return a copy of the
6996    expression with that one removed.  Otherwise, a copy of the original
6997    expression.  This is used for allocate-expressions and pointer assignment
6998    LHS, where there may be an array specification that needs to be stripped
6999    off when using gfc_check_vardef_context.  */
7000
7001 static gfc_expr*
7002 remove_last_array_ref (gfc_expr* e)
7003 {
7004   gfc_expr* e2;
7005   gfc_ref** r;
7006
7007   e2 = gfc_copy_expr (e);
7008   for (r = &e2->ref; *r; r = &(*r)->next)
7009     if ((*r)->type == REF_ARRAY && !(*r)->next)
7010       {
7011         gfc_free_ref_list (*r);
7012         *r = NULL;
7013         break;
7014       }
7015
7016   return e2;
7017 }
7018
7019
7020 /* Used in resolve_allocate_expr to check that a allocation-object and
7021    a source-expr are conformable.  This does not catch all possible 
7022    cases; in particular a runtime checking is needed.  */
7023
7024 static gfc_try
7025 conformable_arrays (gfc_expr *e1, gfc_expr *e2)
7026 {
7027   gfc_ref *tail;
7028   for (tail = e2->ref; tail && tail->next; tail = tail->next);
7029   
7030   /* First compare rank.  */
7031   if (tail && e1->rank != tail->u.ar.as->rank)
7032     {
7033       gfc_error ("Source-expr at %L must be scalar or have the "
7034                  "same rank as the allocate-object at %L",
7035                  &e1->where, &e2->where);
7036       return FAILURE;
7037     }
7038
7039   if (e1->shape)
7040     {
7041       int i;
7042       mpz_t s;
7043
7044       mpz_init (s);
7045
7046       for (i = 0; i < e1->rank; i++)
7047         {
7048           if (tail->u.ar.end[i])
7049             {
7050               mpz_set (s, tail->u.ar.end[i]->value.integer);
7051               mpz_sub (s, s, tail->u.ar.start[i]->value.integer);
7052               mpz_add_ui (s, s, 1);
7053             }
7054           else
7055             {
7056               mpz_set (s, tail->u.ar.start[i]->value.integer);
7057             }
7058
7059           if (mpz_cmp (e1->shape[i], s) != 0)
7060             {
7061               gfc_error ("Source-expr at %L and allocate-object at %L must "
7062                          "have the same shape", &e1->where, &e2->where);
7063               mpz_clear (s);
7064               return FAILURE;
7065             }
7066         }
7067
7068       mpz_clear (s);
7069     }
7070
7071   return SUCCESS;
7072 }
7073
7074
7075 /* Resolve the expression in an ALLOCATE statement, doing the additional
7076    checks to see whether the expression is OK or not.  The expression must
7077    have a trailing array reference that gives the size of the array.  */
7078
7079 static gfc_try
7080 resolve_allocate_expr (gfc_expr *e, gfc_code *code)
7081 {
7082   int i, pointer, allocatable, dimension, is_abstract;
7083   int codimension;
7084   bool coindexed;
7085   symbol_attribute attr;
7086   gfc_ref *ref, *ref2;
7087   gfc_expr *e2;
7088   gfc_array_ref *ar;
7089   gfc_symbol *sym = NULL;
7090   gfc_alloc *a;
7091   gfc_component *c;
7092   gfc_try t;
7093
7094   /* Mark the utmost array component as being in allocate to allow DIMEN_STAR
7095      checking of coarrays.  */
7096   for (ref = e->ref; ref; ref = ref->next)
7097     if (ref->next == NULL)
7098       break;
7099
7100   if (ref && ref->type == REF_ARRAY)
7101     ref->u.ar.in_allocate = true;
7102
7103   if (gfc_resolve_expr (e) == FAILURE)
7104     goto failure;
7105
7106   /* Make sure the expression is allocatable or a pointer.  If it is
7107      pointer, the next-to-last reference must be a pointer.  */
7108
7109   ref2 = NULL;
7110   if (e->symtree)
7111     sym = e->symtree->n.sym;
7112
7113   /* Check whether ultimate component is abstract and CLASS.  */
7114   is_abstract = 0;
7115
7116   if (e->expr_type != EXPR_VARIABLE)
7117     {
7118       allocatable = 0;
7119       attr = gfc_expr_attr (e);
7120       pointer = attr.pointer;
7121       dimension = attr.dimension;
7122       codimension = attr.codimension;
7123     }
7124   else
7125     {
7126       if (sym->ts.type == BT_CLASS && CLASS_DATA (sym))
7127         {
7128           allocatable = CLASS_DATA (sym)->attr.allocatable;
7129           pointer = CLASS_DATA (sym)->attr.class_pointer;
7130           dimension = CLASS_DATA (sym)->attr.dimension;
7131           codimension = CLASS_DATA (sym)->attr.codimension;
7132           is_abstract = CLASS_DATA (sym)->attr.abstract;
7133         }
7134       else
7135         {
7136           allocatable = sym->attr.allocatable;
7137           pointer = sym->attr.pointer;
7138           dimension = sym->attr.dimension;
7139           codimension = sym->attr.codimension;
7140         }
7141
7142       coindexed = false;
7143
7144       for (ref = e->ref; ref; ref2 = ref, ref = ref->next)
7145         {
7146           switch (ref->type)
7147             {
7148               case REF_ARRAY:
7149                 if (ref->u.ar.codimen > 0)
7150                   {
7151                     int n;
7152                     for (n = ref->u.ar.dimen;
7153                          n < ref->u.ar.dimen + ref->u.ar.codimen; n++)
7154                       if (ref->u.ar.dimen_type[n] != DIMEN_THIS_IMAGE)
7155                         {
7156                           coindexed = true;
7157                           break;
7158                         }
7159                    }
7160
7161                 if (ref->next != NULL)
7162                   pointer = 0;
7163                 break;
7164
7165               case REF_COMPONENT:
7166                 /* F2008, C644.  */
7167                 if (coindexed)
7168                   {
7169                     gfc_error ("Coindexed allocatable object at %L",
7170                                &e->where);
7171                     goto failure;
7172                   }
7173
7174                 c = ref->u.c.component;
7175                 if (c->ts.type == BT_CLASS)
7176                   {
7177                     allocatable = CLASS_DATA (c)->attr.allocatable;
7178                     pointer = CLASS_DATA (c)->attr.class_pointer;
7179                     dimension = CLASS_DATA (c)->attr.dimension;
7180                     codimension = CLASS_DATA (c)->attr.codimension;
7181                     is_abstract = CLASS_DATA (c)->attr.abstract;
7182                   }
7183                 else
7184                   {
7185                     allocatable = c->attr.allocatable;
7186                     pointer = c->attr.pointer;
7187                     dimension = c->attr.dimension;
7188                     codimension = c->attr.codimension;
7189                     is_abstract = c->attr.abstract;
7190                   }
7191                 break;
7192
7193               case REF_SUBSTRING:
7194                 allocatable = 0;
7195                 pointer = 0;
7196                 break;
7197             }
7198         }
7199     }
7200
7201   /* Check for F08:C628.  */
7202   if (allocatable == 0 && pointer == 0)
7203     {
7204       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
7205                  &e->where);
7206       goto failure;
7207     }
7208
7209   /* Some checks for the SOURCE tag.  */
7210   if (code->expr3)
7211     {
7212       /* Check F03:C631.  */
7213       if (!gfc_type_compatible (&e->ts, &code->expr3->ts))
7214         {
7215           gfc_error ("Type of entity at %L is type incompatible with "
7216                       "source-expr at %L", &e->where, &code->expr3->where);
7217           goto failure;
7218         }
7219
7220       /* Check F03:C632 and restriction following Note 6.18.  */
7221       if (code->expr3->rank > 0
7222           && conformable_arrays (code->expr3, e) == FAILURE)
7223         goto failure;
7224
7225       /* Check F03:C633.  */
7226       if (code->expr3->ts.kind != e->ts.kind)
7227         {
7228           gfc_error ("The allocate-object at %L and the source-expr at %L "
7229                       "shall have the same kind type parameter",
7230                       &e->where, &code->expr3->where);
7231           goto failure;
7232         }
7233
7234       /* Check F2008, C642.  */
7235       if (code->expr3->ts.type == BT_DERIVED
7236           && ((codimension && gfc_expr_attr (code->expr3).lock_comp)
7237               || (code->expr3->ts.u.derived->from_intmod
7238                      == INTMOD_ISO_FORTRAN_ENV
7239                   && code->expr3->ts.u.derived->intmod_sym_id
7240                      == ISOFORTRAN_LOCK_TYPE)))
7241         {
7242           gfc_error ("The source-expr at %L shall neither be of type "
7243                      "LOCK_TYPE nor have a LOCK_TYPE component if "
7244                       "allocate-object at %L is a coarray",
7245                       &code->expr3->where, &e->where);
7246           goto failure;
7247         }
7248     }
7249
7250   /* Check F08:C629.  */
7251   if (is_abstract && code->ext.alloc.ts.type == BT_UNKNOWN
7252       && !code->expr3)
7253     {
7254       gcc_assert (e->ts.type == BT_CLASS);
7255       gfc_error ("Allocating %s of ABSTRACT base type at %L requires a "
7256                  "type-spec or source-expr", sym->name, &e->where);
7257       goto failure;
7258     }
7259
7260   if (code->ext.alloc.ts.type == BT_CHARACTER && !e->ts.deferred)
7261     {
7262       int cmp = gfc_dep_compare_expr (e->ts.u.cl->length,
7263                                       code->ext.alloc.ts.u.cl->length);
7264       if (cmp == 1 || cmp == -1 || cmp == -3)
7265         {
7266           gfc_error ("Allocating %s at %L with type-spec requires the same "
7267                      "character-length parameter as in the declaration",
7268                      sym->name, &e->where);
7269           goto failure;
7270         }
7271     }
7272
7273   /* In the variable definition context checks, gfc_expr_attr is used
7274      on the expression.  This is fooled by the array specification
7275      present in e, thus we have to eliminate that one temporarily.  */
7276   e2 = remove_last_array_ref (e);
7277   t = SUCCESS;
7278   if (t == SUCCESS && pointer)
7279     t = gfc_check_vardef_context (e2, true, true, _("ALLOCATE object"));
7280   if (t == SUCCESS)
7281     t = gfc_check_vardef_context (e2, false, true, _("ALLOCATE object"));
7282   gfc_free_expr (e2);
7283   if (t == FAILURE)
7284     goto failure;
7285
7286   if (e->ts.type == BT_CLASS && CLASS_DATA (e)->attr.dimension
7287         && !code->expr3 && code->ext.alloc.ts.type == BT_DERIVED)
7288     {
7289       /* For class arrays, the initialization with SOURCE is done
7290          using _copy and trans_call. It is convenient to exploit that
7291          when the allocated type is different from the declared type but
7292          no SOURCE exists by setting expr3.  */
7293       code->expr3 = gfc_default_initializer (&code->ext.alloc.ts); 
7294     }
7295   else if (!code->expr3)
7296     {
7297       /* Set up default initializer if needed.  */
7298       gfc_typespec ts;
7299       gfc_expr *init_e;
7300
7301       if (code->ext.alloc.ts.type == BT_DERIVED)
7302         ts = code->ext.alloc.ts;
7303       else
7304         ts = e->ts;
7305
7306       if (ts.type == BT_CLASS)
7307         ts = ts.u.derived->components->ts;
7308
7309       if (ts.type == BT_DERIVED && (init_e = gfc_default_initializer (&ts)))
7310         {
7311           gfc_code *init_st = gfc_get_code ();
7312           init_st->loc = code->loc;
7313           init_st->op = EXEC_INIT_ASSIGN;
7314           init_st->expr1 = gfc_expr_to_initialize (e);
7315           init_st->expr2 = init_e;
7316           init_st->next = code->next;
7317           code->next = init_st;
7318         }
7319     }
7320   else if (code->expr3->mold && code->expr3->ts.type == BT_DERIVED)
7321     {
7322       /* Default initialization via MOLD (non-polymorphic).  */
7323       gfc_expr *rhs = gfc_default_initializer (&code->expr3->ts);
7324       gfc_resolve_expr (rhs);
7325       gfc_free_expr (code->expr3);
7326       code->expr3 = rhs;
7327     }
7328
7329   if (e->ts.type == BT_CLASS)
7330     {
7331       /* Make sure the vtab symbol is present when
7332          the module variables are generated.  */
7333       gfc_typespec ts = e->ts;
7334       if (code->expr3)
7335         ts = code->expr3->ts;
7336       else if (code->ext.alloc.ts.type == BT_DERIVED)
7337         ts = code->ext.alloc.ts;
7338       gfc_find_derived_vtab (ts.u.derived);
7339       if (dimension)
7340         e = gfc_expr_to_initialize (e);
7341     }
7342
7343   if (dimension == 0 && codimension == 0)
7344     goto success;
7345
7346   /* Make sure the last reference node is an array specification.  */
7347
7348   if (!ref2 || ref2->type != REF_ARRAY || ref2->u.ar.type == AR_FULL
7349       || (dimension && ref2->u.ar.dimen == 0))
7350     {
7351       gfc_error ("Array specification required in ALLOCATE statement "
7352                  "at %L", &e->where);
7353       goto failure;
7354     }
7355
7356   /* Make sure that the array section reference makes sense in the
7357     context of an ALLOCATE specification.  */
7358
7359   ar = &ref2->u.ar;
7360
7361   if (codimension)
7362     for (i = ar->dimen; i < ar->dimen + ar->codimen; i++)
7363       if (ar->dimen_type[i] == DIMEN_THIS_IMAGE)
7364         {
7365           gfc_error ("Coarray specification required in ALLOCATE statement "
7366                      "at %L", &e->where);
7367           goto failure;
7368         }
7369
7370   for (i = 0; i < ar->dimen; i++)
7371     {
7372       if (ref2->u.ar.type == AR_ELEMENT)
7373         goto check_symbols;
7374
7375       switch (ar->dimen_type[i])
7376         {
7377         case DIMEN_ELEMENT:
7378           break;
7379
7380         case DIMEN_RANGE:
7381           if (ar->start[i] != NULL
7382               && ar->end[i] != NULL
7383               && ar->stride[i] == NULL)
7384             break;
7385
7386           /* Fall Through...  */
7387
7388         case DIMEN_UNKNOWN:
7389         case DIMEN_VECTOR:
7390         case DIMEN_STAR:
7391         case DIMEN_THIS_IMAGE:
7392           gfc_error ("Bad array specification in ALLOCATE statement at %L",
7393                      &e->where);
7394           goto failure;
7395         }
7396
7397 check_symbols:
7398       for (a = code->ext.alloc.list; a; a = a->next)
7399         {
7400           sym = a->expr->symtree->n.sym;
7401
7402           /* TODO - check derived type components.  */
7403           if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
7404             continue;
7405
7406           if ((ar->start[i] != NULL
7407                && gfc_find_sym_in_expr (sym, ar->start[i]))
7408               || (ar->end[i] != NULL
7409                   && gfc_find_sym_in_expr (sym, ar->end[i])))
7410             {
7411               gfc_error ("'%s' must not appear in the array specification at "
7412                          "%L in the same ALLOCATE statement where it is "
7413                          "itself allocated", sym->name, &ar->where);
7414               goto failure;
7415             }
7416         }
7417     }
7418
7419   for (i = ar->dimen; i < ar->codimen + ar->dimen; i++)
7420     {
7421       if (ar->dimen_type[i] == DIMEN_ELEMENT
7422           || ar->dimen_type[i] == DIMEN_RANGE)
7423         {
7424           if (i == (ar->dimen + ar->codimen - 1))
7425             {
7426               gfc_error ("Expected '*' in coindex specification in ALLOCATE "
7427                          "statement at %L", &e->where);
7428               goto failure;
7429             }
7430           break;
7431         }
7432
7433       if (ar->dimen_type[i] == DIMEN_STAR && i == (ar->dimen + ar->codimen - 1)
7434           && ar->stride[i] == NULL)
7435         break;
7436
7437       gfc_error ("Bad coarray specification in ALLOCATE statement at %L",
7438                  &e->where);
7439       goto failure;
7440     }
7441
7442 success:
7443   return SUCCESS;
7444
7445 failure:
7446   return FAILURE;
7447 }
7448
7449 static void
7450 resolve_allocate_deallocate (gfc_code *code, const char *fcn)
7451 {
7452   gfc_expr *stat, *errmsg, *pe, *qe;
7453   gfc_alloc *a, *p, *q;
7454
7455   stat = code->expr1;
7456   errmsg = code->expr2;
7457
7458   /* Check the stat variable.  */
7459   if (stat)
7460     {
7461       gfc_check_vardef_context (stat, false, false, _("STAT variable"));
7462
7463       if ((stat->ts.type != BT_INTEGER
7464            && !(stat->ref && (stat->ref->type == REF_ARRAY
7465                               || stat->ref->type == REF_COMPONENT)))
7466           || stat->rank > 0)
7467         gfc_error ("Stat-variable at %L must be a scalar INTEGER "
7468                    "variable", &stat->where);
7469
7470       for (p = code->ext.alloc.list; p; p = p->next)
7471         if (p->expr->symtree->n.sym->name == stat->symtree->n.sym->name)
7472           {
7473             gfc_ref *ref1, *ref2;
7474             bool found = true;
7475
7476             for (ref1 = p->expr->ref, ref2 = stat->ref; ref1 && ref2;
7477                  ref1 = ref1->next, ref2 = ref2->next)
7478               {
7479                 if (ref1->type != REF_COMPONENT || ref2->type != REF_COMPONENT)
7480                   continue;
7481                 if (ref1->u.c.component->name != ref2->u.c.component->name)
7482                   {
7483                     found = false;
7484                     break;
7485                   }
7486               }
7487
7488             if (found)
7489               {
7490                 gfc_error ("Stat-variable at %L shall not be %sd within "
7491                            "the same %s statement", &stat->where, fcn, fcn);
7492                 break;
7493               }
7494           }
7495     }
7496
7497   /* Check the errmsg variable.  */
7498   if (errmsg)
7499     {
7500       if (!stat)
7501         gfc_warning ("ERRMSG at %L is useless without a STAT tag",
7502                      &errmsg->where);
7503
7504       gfc_check_vardef_context (errmsg, false, false, _("ERRMSG variable"));
7505
7506       if ((errmsg->ts.type != BT_CHARACTER
7507            && !(errmsg->ref
7508                 && (errmsg->ref->type == REF_ARRAY
7509                     || errmsg->ref->type == REF_COMPONENT)))
7510           || errmsg->rank > 0 )
7511         gfc_error ("Errmsg-variable at %L must be a scalar CHARACTER "
7512                    "variable", &errmsg->where);
7513
7514       for (p = code->ext.alloc.list; p; p = p->next)
7515         if (p->expr->symtree->n.sym->name == errmsg->symtree->n.sym->name)
7516           {
7517             gfc_ref *ref1, *ref2;
7518             bool found = true;
7519
7520             for (ref1 = p->expr->ref, ref2 = errmsg->ref; ref1 && ref2;
7521                  ref1 = ref1->next, ref2 = ref2->next)
7522               {
7523                 if (ref1->type != REF_COMPONENT || ref2->type != REF_COMPONENT)
7524                   continue;
7525                 if (ref1->u.c.component->name != ref2->u.c.component->name)
7526                   {
7527                     found = false;
7528                     break;
7529                   }
7530               }
7531
7532             if (found)
7533               {
7534                 gfc_error ("Errmsg-variable at %L shall not be %sd within "
7535                            "the same %s statement", &errmsg->where, fcn, fcn);
7536                 break;
7537               }
7538           }
7539     }
7540
7541   /* Check that an allocate-object appears only once in the statement.  */
7542
7543   for (p = code->ext.alloc.list; p; p = p->next)
7544     {
7545       pe = p->expr;
7546       for (q = p->next; q; q = q->next)
7547         {
7548           qe = q->expr;
7549           if (pe->symtree->n.sym->name == qe->symtree->n.sym->name)
7550             {
7551               /* This is a potential collision.  */
7552               gfc_ref *pr = pe->ref;
7553               gfc_ref *qr = qe->ref;
7554               
7555               /* Follow the references  until
7556                  a) They start to differ, in which case there is no error;
7557                  you can deallocate a%b and a%c in a single statement
7558                  b) Both of them stop, which is an error
7559                  c) One of them stops, which is also an error.  */
7560               while (1)
7561                 {
7562                   if (pr == NULL && qr == NULL)
7563                     {
7564                       gfc_error ("Allocate-object at %L also appears at %L",
7565                                  &pe->where, &qe->where);
7566                       break;
7567                     }
7568                   else if (pr != NULL && qr == NULL)
7569                     {
7570                       gfc_error ("Allocate-object at %L is subobject of"
7571                                  " object at %L", &pe->where, &qe->where);
7572                       break;
7573                     }
7574                   else if (pr == NULL && qr != NULL)
7575                     {
7576                       gfc_error ("Allocate-object at %L is subobject of"
7577                                  " object at %L", &qe->where, &pe->where);
7578                       break;
7579                     }
7580                   /* Here, pr != NULL && qr != NULL  */
7581                   gcc_assert(pr->type == qr->type);
7582                   if (pr->type == REF_ARRAY)
7583                     {
7584                       /* Handle cases like allocate(v(3)%x(3), v(2)%x(3)),
7585                          which are legal.  */
7586                       gcc_assert (qr->type == REF_ARRAY);
7587
7588                       if (pr->next && qr->next)
7589                         {
7590                           gfc_array_ref *par = &(pr->u.ar);
7591                           gfc_array_ref *qar = &(qr->u.ar);
7592                           if ((par->start[0] != NULL || qar->start[0] != NULL)
7593                               && gfc_dep_compare_expr (par->start[0],
7594                                                        qar->start[0]) != 0)
7595                             break;
7596                         }
7597                     }
7598                   else
7599                     {
7600                       if (pr->u.c.component->name != qr->u.c.component->name)
7601                         break;
7602                     }
7603                   
7604                   pr = pr->next;
7605                   qr = qr->next;
7606                 }
7607             }
7608         }
7609     }
7610
7611   if (strcmp (fcn, "ALLOCATE") == 0)
7612     {
7613       for (a = code->ext.alloc.list; a; a = a->next)
7614         resolve_allocate_expr (a->expr, code);
7615     }
7616   else
7617     {
7618       for (a = code->ext.alloc.list; a; a = a->next)
7619         resolve_deallocate_expr (a->expr);
7620     }
7621 }
7622
7623
7624 /************ SELECT CASE resolution subroutines ************/
7625
7626 /* Callback function for our mergesort variant.  Determines interval
7627    overlaps for CASEs. Return <0 if op1 < op2, 0 for overlap, >0 for
7628    op1 > op2.  Assumes we're not dealing with the default case.  
7629    We have op1 = (:L), (K:L) or (K:) and op2 = (:N), (M:N) or (M:).
7630    There are nine situations to check.  */
7631
7632 static int
7633 compare_cases (const gfc_case *op1, const gfc_case *op2)
7634 {
7635   int retval;
7636
7637   if (op1->low == NULL) /* op1 = (:L)  */
7638     {
7639       /* op2 = (:N), so overlap.  */
7640       retval = 0;
7641       /* op2 = (M:) or (M:N),  L < M  */
7642       if (op2->low != NULL
7643           && gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
7644         retval = -1;
7645     }
7646   else if (op1->high == NULL) /* op1 = (K:)  */
7647     {
7648       /* op2 = (M:), so overlap.  */
7649       retval = 0;
7650       /* op2 = (:N) or (M:N), K > N  */
7651       if (op2->high != NULL
7652           && gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
7653         retval = 1;
7654     }
7655   else /* op1 = (K:L)  */
7656     {
7657       if (op2->low == NULL)       /* op2 = (:N), K > N  */
7658         retval = (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
7659                  ? 1 : 0;
7660       else if (op2->high == NULL) /* op2 = (M:), L < M  */
7661         retval = (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
7662                  ? -1 : 0;
7663       else                      /* op2 = (M:N)  */
7664         {
7665           retval =  0;
7666           /* L < M  */
7667           if (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
7668             retval =  -1;
7669           /* K > N  */
7670           else if (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
7671             retval =  1;
7672         }
7673     }
7674
7675   return retval;
7676 }
7677
7678
7679 /* Merge-sort a double linked case list, detecting overlap in the
7680    process.  LIST is the head of the double linked case list before it
7681    is sorted.  Returns the head of the sorted list if we don't see any
7682    overlap, or NULL otherwise.  */
7683
7684 static gfc_case *
7685 check_case_overlap (gfc_case *list)
7686 {
7687   gfc_case *p, *q, *e, *tail;
7688   int insize, nmerges, psize, qsize, cmp, overlap_seen;
7689
7690   /* If the passed list was empty, return immediately.  */
7691   if (!list)
7692     return NULL;
7693
7694   overlap_seen = 0;
7695   insize = 1;
7696
7697   /* Loop unconditionally.  The only exit from this loop is a return
7698      statement, when we've finished sorting the case list.  */
7699   for (;;)
7700     {
7701       p = list;
7702       list = NULL;
7703       tail = NULL;
7704
7705       /* Count the number of merges we do in this pass.  */
7706       nmerges = 0;
7707
7708       /* Loop while there exists a merge to be done.  */
7709       while (p)
7710         {
7711           int i;
7712
7713           /* Count this merge.  */
7714           nmerges++;
7715
7716           /* Cut the list in two pieces by stepping INSIZE places
7717              forward in the list, starting from P.  */
7718           psize = 0;
7719           q = p;
7720           for (i = 0; i < insize; i++)
7721             {
7722               psize++;
7723               q = q->right;
7724               if (!q)
7725                 break;
7726             }
7727           qsize = insize;
7728
7729           /* Now we have two lists.  Merge them!  */
7730           while (psize > 0 || (qsize > 0 && q != NULL))
7731             {
7732               /* See from which the next case to merge comes from.  */
7733               if (psize == 0)
7734                 {
7735                   /* P is empty so the next case must come from Q.  */
7736                   e = q;
7737                   q = q->right;
7738                   qsize--;
7739                 }
7740               else if (qsize == 0 || q == NULL)
7741                 {
7742                   /* Q is empty.  */
7743                   e = p;
7744                   p = p->right;
7745                   psize--;
7746                 }
7747               else
7748                 {
7749                   cmp = compare_cases (p, q);
7750                   if (cmp < 0)
7751                     {
7752                       /* The whole case range for P is less than the
7753                          one for Q.  */
7754                       e = p;
7755                       p = p->right;
7756                       psize--;
7757                     }
7758                   else if (cmp > 0)
7759                     {
7760                       /* The whole case range for Q is greater than
7761                          the case range for P.  */
7762                       e = q;
7763                       q = q->right;
7764                       qsize--;
7765                     }
7766                   else
7767                     {
7768                       /* The cases overlap, or they are the same
7769                          element in the list.  Either way, we must
7770                          issue an error and get the next case from P.  */
7771                       /* FIXME: Sort P and Q by line number.  */
7772                       gfc_error ("CASE label at %L overlaps with CASE "
7773                                  "label at %L", &p->where, &q->where);
7774                       overlap_seen = 1;
7775                       e = p;
7776                       p = p->right;
7777                       psize--;
7778                     }
7779                 }
7780
7781                 /* Add the next element to the merged list.  */
7782               if (tail)
7783                 tail->right = e;
7784               else
7785                 list = e;
7786               e->left = tail;
7787               tail = e;
7788             }
7789
7790           /* P has now stepped INSIZE places along, and so has Q.  So
7791              they're the same.  */
7792           p = q;
7793         }
7794       tail->right = NULL;
7795
7796       /* If we have done only one merge or none at all, we've
7797          finished sorting the cases.  */
7798       if (nmerges <= 1)
7799         {
7800           if (!overlap_seen)
7801             return list;
7802           else
7803             return NULL;
7804         }
7805
7806       /* Otherwise repeat, merging lists twice the size.  */
7807       insize *= 2;
7808     }
7809 }
7810
7811
7812 /* Check to see if an expression is suitable for use in a CASE statement.
7813    Makes sure that all case expressions are scalar constants of the same
7814    type.  Return FAILURE if anything is wrong.  */
7815
7816 static gfc_try
7817 validate_case_label_expr (gfc_expr *e, gfc_expr *case_expr)
7818 {
7819   if (e == NULL) return SUCCESS;
7820
7821   if (e->ts.type != case_expr->ts.type)
7822     {
7823       gfc_error ("Expression in CASE statement at %L must be of type %s",
7824                  &e->where, gfc_basic_typename (case_expr->ts.type));
7825       return FAILURE;
7826     }
7827
7828   /* C805 (R808) For a given case-construct, each case-value shall be of
7829      the same type as case-expr.  For character type, length differences
7830      are allowed, but the kind type parameters shall be the same.  */
7831
7832   if (case_expr->ts.type == BT_CHARACTER && e->ts.kind != case_expr->ts.kind)
7833     {
7834       gfc_error ("Expression in CASE statement at %L must be of kind %d",
7835                  &e->where, case_expr->ts.kind);
7836       return FAILURE;
7837     }
7838
7839   /* Convert the case value kind to that of case expression kind,
7840      if needed */
7841
7842   if (e->ts.kind != case_expr->ts.kind)
7843     gfc_convert_type_warn (e, &case_expr->ts, 2, 0);
7844
7845   if (e->rank != 0)
7846     {
7847       gfc_error ("Expression in CASE statement at %L must be scalar",
7848                  &e->where);
7849       return FAILURE;
7850     }
7851
7852   return SUCCESS;
7853 }
7854
7855
7856 /* Given a completely parsed select statement, we:
7857
7858      - Validate all expressions and code within the SELECT.
7859      - Make sure that the selection expression is not of the wrong type.
7860      - Make sure that no case ranges overlap.
7861      - Eliminate unreachable cases and unreachable code resulting from
7862        removing case labels.
7863
7864    The standard does allow unreachable cases, e.g. CASE (5:3).  But
7865    they are a hassle for code generation, and to prevent that, we just
7866    cut them out here.  This is not necessary for overlapping cases
7867    because they are illegal and we never even try to generate code.
7868
7869    We have the additional caveat that a SELECT construct could have
7870    been a computed GOTO in the source code. Fortunately we can fairly
7871    easily work around that here: The case_expr for a "real" SELECT CASE
7872    is in code->expr1, but for a computed GOTO it is in code->expr2. All
7873    we have to do is make sure that the case_expr is a scalar integer
7874    expression.  */
7875
7876 static void
7877 resolve_select (gfc_code *code)
7878 {
7879   gfc_code *body;
7880   gfc_expr *case_expr;
7881   gfc_case *cp, *default_case, *tail, *head;
7882   int seen_unreachable;
7883   int seen_logical;
7884   int ncases;
7885   bt type;
7886   gfc_try t;
7887
7888   if (code->expr1 == NULL)
7889     {
7890       /* This was actually a computed GOTO statement.  */
7891       case_expr = code->expr2;
7892       if (case_expr->ts.type != BT_INTEGER|| case_expr->rank != 0)
7893         gfc_error ("Selection expression in computed GOTO statement "
7894                    "at %L must be a scalar integer expression",
7895                    &case_expr->where);
7896
7897       /* Further checking is not necessary because this SELECT was built
7898          by the compiler, so it should always be OK.  Just move the
7899          case_expr from expr2 to expr so that we can handle computed
7900          GOTOs as normal SELECTs from here on.  */
7901       code->expr1 = code->expr2;
7902       code->expr2 = NULL;
7903       return;
7904     }
7905
7906   case_expr = code->expr1;
7907
7908   type = case_expr->ts.type;
7909   if (type != BT_LOGICAL && type != BT_INTEGER && type != BT_CHARACTER)
7910     {
7911       gfc_error ("Argument of SELECT statement at %L cannot be %s",
7912                  &case_expr->where, gfc_typename (&case_expr->ts));
7913
7914       /* Punt. Going on here just produce more garbage error messages.  */
7915       return;
7916     }
7917
7918   /* Raise a warning if an INTEGER case value exceeds the range of
7919      the case-expr. Later, all expressions will be promoted to the
7920      largest kind of all case-labels.  */
7921
7922   if (type == BT_INTEGER)
7923     for (body = code->block; body; body = body->block)
7924       for (cp = body->ext.block.case_list; cp; cp = cp->next)
7925         {
7926           if (cp->low
7927               && gfc_check_integer_range (cp->low->value.integer,
7928                                           case_expr->ts.kind) != ARITH_OK)
7929             gfc_warning ("Expression in CASE statement at %L is "
7930                          "not in the range of %s", &cp->low->where,
7931                          gfc_typename (&case_expr->ts));
7932
7933           if (cp->high
7934               && cp->low != cp->high
7935               && gfc_check_integer_range (cp->high->value.integer,
7936                                           case_expr->ts.kind) != ARITH_OK)
7937             gfc_warning ("Expression in CASE statement at %L is "
7938                          "not in the range of %s", &cp->high->where,
7939                          gfc_typename (&case_expr->ts));
7940         }
7941
7942   /* PR 19168 has a long discussion concerning a mismatch of the kinds
7943      of the SELECT CASE expression and its CASE values.  Walk the lists
7944      of case values, and if we find a mismatch, promote case_expr to
7945      the appropriate kind.  */
7946
7947   if (type == BT_LOGICAL || type == BT_INTEGER)
7948     {
7949       for (body = code->block; body; body = body->block)
7950         {
7951           /* Walk the case label list.  */
7952           for (cp = body->ext.block.case_list; cp; cp = cp->next)
7953             {
7954               /* Intercept the DEFAULT case.  It does not have a kind.  */
7955               if (cp->low == NULL && cp->high == NULL)
7956                 continue;
7957
7958               /* Unreachable case ranges are discarded, so ignore.  */
7959               if (cp->low != NULL && cp->high != NULL
7960                   && cp->low != cp->high
7961                   && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
7962                 continue;
7963
7964               if (cp->low != NULL
7965                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->low))
7966                 gfc_convert_type_warn (case_expr, &cp->low->ts, 2, 0);
7967
7968               if (cp->high != NULL
7969                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->high))
7970                 gfc_convert_type_warn (case_expr, &cp->high->ts, 2, 0);
7971             }
7972          }
7973     }
7974
7975   /* Assume there is no DEFAULT case.  */
7976   default_case = NULL;
7977   head = tail = NULL;
7978   ncases = 0;
7979   seen_logical = 0;
7980
7981   for (body = code->block; body; body = body->block)
7982     {
7983       /* Assume the CASE list is OK, and all CASE labels can be matched.  */
7984       t = SUCCESS;
7985       seen_unreachable = 0;
7986
7987       /* Walk the case label list, making sure that all case labels
7988          are legal.  */
7989       for (cp = body->ext.block.case_list; cp; cp = cp->next)
7990         {
7991           /* Count the number of cases in the whole construct.  */
7992           ncases++;
7993
7994           /* Intercept the DEFAULT case.  */
7995           if (cp->low == NULL && cp->high == NULL)
7996             {
7997               if (default_case != NULL)
7998                 {
7999                   gfc_error ("The DEFAULT CASE at %L cannot be followed "
8000                              "by a second DEFAULT CASE at %L",
8001                              &default_case->where, &cp->where);
8002                   t = FAILURE;
8003                   break;
8004                 }
8005               else
8006                 {
8007                   default_case = cp;
8008                   continue;
8009                 }
8010             }
8011
8012           /* Deal with single value cases and case ranges.  Errors are
8013              issued from the validation function.  */
8014           if (validate_case_label_expr (cp->low, case_expr) != SUCCESS
8015               || validate_case_label_expr (cp->high, case_expr) != SUCCESS)
8016             {
8017               t = FAILURE;
8018               break;
8019             }
8020
8021           if (type == BT_LOGICAL
8022               && ((cp->low == NULL || cp->high == NULL)
8023                   || cp->low != cp->high))
8024             {
8025               gfc_error ("Logical range in CASE statement at %L is not "
8026                          "allowed", &cp->low->where);
8027               t = FAILURE;
8028               break;
8029             }
8030
8031           if (type == BT_LOGICAL && cp->low->expr_type == EXPR_CONSTANT)
8032             {
8033               int value;
8034               value = cp->low->value.logical == 0 ? 2 : 1;
8035               if (value & seen_logical)
8036                 {
8037                   gfc_error ("Constant logical value in CASE statement "
8038                              "is repeated at %L",
8039                              &cp->low->where);
8040                   t = FAILURE;
8041                   break;
8042                 }
8043               seen_logical |= value;
8044             }
8045
8046           if (cp->low != NULL && cp->high != NULL
8047               && cp->low != cp->high
8048               && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
8049             {
8050               if (gfc_option.warn_surprising)
8051                 gfc_warning ("Range specification at %L can never "
8052                              "be matched", &cp->where);
8053
8054               cp->unreachable = 1;
8055               seen_unreachable = 1;
8056             }
8057           else
8058             {
8059               /* If the case range can be matched, it can also overlap with
8060                  other cases.  To make sure it does not, we put it in a
8061                  double linked list here.  We sort that with a merge sort
8062                  later on to detect any overlapping cases.  */
8063               if (!head)
8064                 {
8065                   head = tail = cp;
8066                   head->right = head->left = NULL;
8067                 }
8068               else
8069                 {
8070                   tail->right = cp;
8071                   tail->right->left = tail;
8072                   tail = tail->right;
8073                   tail->right = NULL;
8074                 }
8075             }
8076         }
8077
8078       /* It there was a failure in the previous case label, give up
8079          for this case label list.  Continue with the next block.  */
8080       if (t == FAILURE)
8081         continue;
8082
8083       /* See if any case labels that are unreachable have been seen.
8084          If so, we eliminate them.  This is a bit of a kludge because
8085          the case lists for a single case statement (label) is a
8086          single forward linked lists.  */
8087       if (seen_unreachable)
8088       {
8089         /* Advance until the first case in the list is reachable.  */
8090         while (body->ext.block.case_list != NULL
8091                && body->ext.block.case_list->unreachable)
8092           {
8093             gfc_case *n = body->ext.block.case_list;
8094             body->ext.block.case_list = body->ext.block.case_list->next;
8095             n->next = NULL;
8096             gfc_free_case_list (n);
8097           }
8098
8099         /* Strip all other unreachable cases.  */
8100         if (body->ext.block.case_list)
8101           {
8102             for (cp = body->ext.block.case_list; cp->next; cp = cp->next)
8103               {
8104                 if (cp->next->unreachable)
8105                   {
8106                     gfc_case *n = cp->next;
8107                     cp->next = cp->next->next;
8108                     n->next = NULL;
8109                     gfc_free_case_list (n);
8110                   }
8111               }
8112           }
8113       }
8114     }
8115
8116   /* See if there were overlapping cases.  If the check returns NULL,
8117      there was overlap.  In that case we don't do anything.  If head
8118      is non-NULL, we prepend the DEFAULT case.  The sorted list can
8119      then used during code generation for SELECT CASE constructs with
8120      a case expression of a CHARACTER type.  */
8121   if (head)
8122     {
8123       head = check_case_overlap (head);
8124
8125       /* Prepend the default_case if it is there.  */
8126       if (head != NULL && default_case)
8127         {
8128           default_case->left = NULL;
8129           default_case->right = head;
8130           head->left = default_case;
8131         }
8132     }
8133
8134   /* Eliminate dead blocks that may be the result if we've seen
8135      unreachable case labels for a block.  */
8136   for (body = code; body && body->block; body = body->block)
8137     {
8138       if (body->block->ext.block.case_list == NULL)
8139         {
8140           /* Cut the unreachable block from the code chain.  */
8141           gfc_code *c = body->block;
8142           body->block = c->block;
8143
8144           /* Kill the dead block, but not the blocks below it.  */
8145           c->block = NULL;
8146           gfc_free_statements (c);
8147         }
8148     }
8149
8150   /* More than two cases is legal but insane for logical selects.
8151      Issue a warning for it.  */
8152   if (gfc_option.warn_surprising && type == BT_LOGICAL
8153       && ncases > 2)
8154     gfc_warning ("Logical SELECT CASE block at %L has more that two cases",
8155                  &code->loc);
8156 }
8157
8158
8159 /* Check if a derived type is extensible.  */
8160
8161 bool
8162 gfc_type_is_extensible (gfc_symbol *sym)
8163 {
8164   return !(sym->attr.is_bind_c || sym->attr.sequence);
8165 }
8166
8167
8168 /* Resolve an associate-name:  Resolve target and ensure the type-spec is
8169    correct as well as possibly the array-spec.  */
8170
8171 static void
8172 resolve_assoc_var (gfc_symbol* sym, bool resolve_target)
8173 {
8174   gfc_expr* target;
8175
8176   gcc_assert (sym->assoc);
8177   gcc_assert (sym->attr.flavor == FL_VARIABLE);
8178
8179   /* If this is for SELECT TYPE, the target may not yet be set.  In that
8180      case, return.  Resolution will be called later manually again when
8181      this is done.  */
8182   target = sym->assoc->target;
8183   if (!target)
8184     return;
8185   gcc_assert (!sym->assoc->dangling);
8186
8187   if (resolve_target && gfc_resolve_expr (target) != SUCCESS)
8188     return;
8189
8190   /* For variable targets, we get some attributes from the target.  */
8191   if (target->expr_type == EXPR_VARIABLE)
8192     {
8193       gfc_symbol* tsym;
8194
8195       gcc_assert (target->symtree);
8196       tsym = target->symtree->n.sym;
8197
8198       sym->attr.asynchronous = tsym->attr.asynchronous;
8199       sym->attr.volatile_ = tsym->attr.volatile_;
8200
8201       sym->attr.target = tsym->attr.target
8202                          || gfc_expr_attr (target).pointer;
8203     }
8204
8205   /* Get type if this was not already set.  Note that it can be
8206      some other type than the target in case this is a SELECT TYPE
8207      selector!  So we must not update when the type is already there.  */
8208   if (sym->ts.type == BT_UNKNOWN)
8209     sym->ts = target->ts;
8210   gcc_assert (sym->ts.type != BT_UNKNOWN);
8211
8212   /* See if this is a valid association-to-variable.  */
8213   sym->assoc->variable = (target->expr_type == EXPR_VARIABLE
8214                           && !gfc_has_vector_subscript (target));
8215
8216   /* Finally resolve if this is an array or not.  */
8217   if (sym->attr.dimension && target->rank == 0)
8218     {
8219       gfc_error ("Associate-name '%s' at %L is used as array",
8220                  sym->name, &sym->declared_at);
8221       sym->attr.dimension = 0;
8222       return;
8223     }
8224
8225   /* We cannot deal with class selectors that need temporaries.  */
8226   if (target->ts.type == BT_CLASS
8227         && gfc_ref_needs_temporary_p (target->ref))
8228     {
8229       gfc_error ("CLASS selector at %L needs a temporary which is not "
8230                  "yet implemented", &target->where);
8231       return;
8232     }
8233
8234   if (target->ts.type != BT_CLASS && target->rank > 0)
8235     sym->attr.dimension = 1;
8236   else if (target->ts.type == BT_CLASS)
8237     gfc_fix_class_refs (target);
8238
8239   /* The associate-name will have a correct type by now. Make absolutely
8240      sure that it has not picked up a dimension attribute.  */
8241   if (sym->ts.type == BT_CLASS)
8242     sym->attr.dimension = 0;
8243
8244   if (sym->attr.dimension)
8245     {
8246       sym->as = gfc_get_array_spec ();
8247       sym->as->rank = target->rank;
8248       sym->as->type = AS_DEFERRED;
8249
8250       /* Target must not be coindexed, thus the associate-variable
8251          has no corank.  */
8252       sym->as->corank = 0;
8253     }
8254 }
8255
8256
8257 /* Resolve a SELECT TYPE statement.  */
8258
8259 static void
8260 resolve_select_type (gfc_code *code, gfc_namespace *old_ns)
8261 {
8262   gfc_symbol *selector_type;
8263   gfc_code *body, *new_st, *if_st, *tail;
8264   gfc_code *class_is = NULL, *default_case = NULL;
8265   gfc_case *c;
8266   gfc_symtree *st;
8267   char name[GFC_MAX_SYMBOL_LEN];
8268   gfc_namespace *ns;
8269   int error = 0;
8270
8271   ns = code->ext.block.ns;
8272   gfc_resolve (ns);
8273
8274   /* Check for F03:C813.  */
8275   if (code->expr1->ts.type != BT_CLASS
8276       && !(code->expr2 && code->expr2->ts.type == BT_CLASS))
8277     {
8278       gfc_error ("Selector shall be polymorphic in SELECT TYPE statement "
8279                  "at %L", &code->loc);
8280       return;
8281     }
8282
8283   if (!code->expr1->symtree->n.sym->attr.class_ok)
8284     return;
8285
8286   if (code->expr2)
8287     {
8288       if (code->expr1->symtree->n.sym->attr.untyped)
8289         code->expr1->symtree->n.sym->ts = code->expr2->ts;
8290       selector_type = CLASS_DATA (code->expr2)->ts.u.derived;
8291     }
8292   else
8293     selector_type = CLASS_DATA (code->expr1)->ts.u.derived;
8294
8295   /* Loop over TYPE IS / CLASS IS cases.  */
8296   for (body = code->block; body; body = body->block)
8297     {
8298       c = body->ext.block.case_list;
8299
8300       /* Check F03:C815.  */
8301       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
8302           && !gfc_type_is_extensible (c->ts.u.derived))
8303         {
8304           gfc_error ("Derived type '%s' at %L must be extensible",
8305                      c->ts.u.derived->name, &c->where);
8306           error++;
8307           continue;
8308         }
8309
8310       /* Check F03:C816.  */
8311       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
8312           && !gfc_type_is_extension_of (selector_type, c->ts.u.derived))
8313         {
8314           gfc_error ("Derived type '%s' at %L must be an extension of '%s'",
8315                      c->ts.u.derived->name, &c->where, selector_type->name);
8316           error++;
8317           continue;
8318         }
8319
8320       /* Intercept the DEFAULT case.  */
8321       if (c->ts.type == BT_UNKNOWN)
8322         {
8323           /* Check F03:C818.  */
8324           if (default_case)
8325             {
8326               gfc_error ("The DEFAULT CASE at %L cannot be followed "
8327                          "by a second DEFAULT CASE at %L",
8328                          &default_case->ext.block.case_list->where, &c->where);
8329               error++;
8330               continue;
8331             }
8332
8333           default_case = body;
8334         }
8335     }
8336     
8337   if (error > 0)
8338     return;
8339
8340   /* Transform SELECT TYPE statement to BLOCK and associate selector to
8341      target if present.  If there are any EXIT statements referring to the
8342      SELECT TYPE construct, this is no problem because the gfc_code
8343      reference stays the same and EXIT is equally possible from the BLOCK
8344      it is changed to.  */
8345   code->op = EXEC_BLOCK;
8346   if (code->expr2)
8347     {
8348       gfc_association_list* assoc;
8349
8350       assoc = gfc_get_association_list ();
8351       assoc->st = code->expr1->symtree;
8352       assoc->target = gfc_copy_expr (code->expr2);
8353       assoc->target->where = code->expr2->where;
8354       /* assoc->variable will be set by resolve_assoc_var.  */
8355       
8356       code->ext.block.assoc = assoc;
8357       code->expr1->symtree->n.sym->assoc = assoc;
8358
8359       resolve_assoc_var (code->expr1->symtree->n.sym, false);
8360     }
8361   else
8362     code->ext.block.assoc = NULL;
8363
8364   /* Add EXEC_SELECT to switch on type.  */
8365   new_st = gfc_get_code ();
8366   new_st->op = code->op;
8367   new_st->expr1 = code->expr1;
8368   new_st->expr2 = code->expr2;
8369   new_st->block = code->block;
8370   code->expr1 = code->expr2 =  NULL;
8371   code->block = NULL;
8372   if (!ns->code)
8373     ns->code = new_st;
8374   else
8375     ns->code->next = new_st;
8376   code = new_st;
8377   code->op = EXEC_SELECT;
8378   gfc_add_vptr_component (code->expr1);
8379   gfc_add_hash_component (code->expr1);
8380
8381   /* Loop over TYPE IS / CLASS IS cases.  */
8382   for (body = code->block; body; body = body->block)
8383     {
8384       c = body->ext.block.case_list;
8385
8386       if (c->ts.type == BT_DERIVED)
8387         c->low = c->high = gfc_get_int_expr (gfc_default_integer_kind, NULL,
8388                                              c->ts.u.derived->hash_value);
8389
8390       else if (c->ts.type == BT_UNKNOWN)
8391         continue;
8392
8393       /* Associate temporary to selector.  This should only be done
8394          when this case is actually true, so build a new ASSOCIATE
8395          that does precisely this here (instead of using the
8396          'global' one).  */
8397
8398       if (c->ts.type == BT_CLASS)
8399         sprintf (name, "__tmp_class_%s", c->ts.u.derived->name);
8400       else
8401         sprintf (name, "__tmp_type_%s", c->ts.u.derived->name);
8402       st = gfc_find_symtree (ns->sym_root, name);
8403       gcc_assert (st->n.sym->assoc);
8404       st->n.sym->assoc->target = gfc_get_variable_expr (code->expr1->symtree);
8405       st->n.sym->assoc->target->where = code->expr1->where;
8406       if (c->ts.type == BT_DERIVED)
8407         gfc_add_data_component (st->n.sym->assoc->target);
8408
8409       new_st = gfc_get_code ();
8410       new_st->op = EXEC_BLOCK;
8411       new_st->ext.block.ns = gfc_build_block_ns (ns);
8412       new_st->ext.block.ns->code = body->next;
8413       body->next = new_st;
8414
8415       /* Chain in the new list only if it is marked as dangling.  Otherwise
8416          there is a CASE label overlap and this is already used.  Just ignore,
8417          the error is diagnosed elsewhere.  */
8418       if (st->n.sym->assoc->dangling)
8419         {
8420           new_st->ext.block.assoc = st->n.sym->assoc;
8421           st->n.sym->assoc->dangling = 0;
8422         }
8423
8424       resolve_assoc_var (st->n.sym, false);
8425     }
8426     
8427   /* Take out CLASS IS cases for separate treatment.  */
8428   body = code;
8429   while (body && body->block)
8430     {
8431       if (body->block->ext.block.case_list->ts.type == BT_CLASS)
8432         {
8433           /* Add to class_is list.  */
8434           if (class_is == NULL)
8435             { 
8436               class_is = body->block;
8437               tail = class_is;
8438             }
8439           else
8440             {
8441               for (tail = class_is; tail->block; tail = tail->block) ;
8442               tail->block = body->block;
8443               tail = tail->block;
8444             }
8445           /* Remove from EXEC_SELECT list.  */
8446           body->block = body->block->block;
8447           tail->block = NULL;
8448         }
8449       else
8450         body = body->block;
8451     }
8452
8453   if (class_is)
8454     {
8455       gfc_symbol *vtab;
8456       
8457       if (!default_case)
8458         {
8459           /* Add a default case to hold the CLASS IS cases.  */
8460           for (tail = code; tail->block; tail = tail->block) ;
8461           tail->block = gfc_get_code ();
8462           tail = tail->block;
8463           tail->op = EXEC_SELECT_TYPE;
8464           tail->ext.block.case_list = gfc_get_case ();
8465           tail->ext.block.case_list->ts.type = BT_UNKNOWN;
8466           tail->next = NULL;
8467           default_case = tail;
8468         }
8469
8470       /* More than one CLASS IS block?  */
8471       if (class_is->block)
8472         {
8473           gfc_code **c1,*c2;
8474           bool swapped;
8475           /* Sort CLASS IS blocks by extension level.  */
8476           do
8477             {
8478               swapped = false;
8479               for (c1 = &class_is; (*c1) && (*c1)->block; c1 = &((*c1)->block))
8480                 {
8481                   c2 = (*c1)->block;
8482                   /* F03:C817 (check for doubles).  */
8483                   if ((*c1)->ext.block.case_list->ts.u.derived->hash_value
8484                       == c2->ext.block.case_list->ts.u.derived->hash_value)
8485                     {
8486                       gfc_error ("Double CLASS IS block in SELECT TYPE "
8487                                  "statement at %L",
8488                                  &c2->ext.block.case_list->where);
8489                       return;
8490                     }
8491                   if ((*c1)->ext.block.case_list->ts.u.derived->attr.extension
8492                       < c2->ext.block.case_list->ts.u.derived->attr.extension)
8493                     {
8494                       /* Swap.  */
8495                       (*c1)->block = c2->block;
8496                       c2->block = *c1;
8497                       *c1 = c2;
8498                       swapped = true;
8499                     }
8500                 }
8501             }
8502           while (swapped);
8503         }
8504         
8505       /* Generate IF chain.  */
8506       if_st = gfc_get_code ();
8507       if_st->op = EXEC_IF;
8508       new_st = if_st;
8509       for (body = class_is; body; body = body->block)
8510         {
8511           new_st->block = gfc_get_code ();
8512           new_st = new_st->block;
8513           new_st->op = EXEC_IF;
8514           /* Set up IF condition: Call _gfortran_is_extension_of.  */
8515           new_st->expr1 = gfc_get_expr ();
8516           new_st->expr1->expr_type = EXPR_FUNCTION;
8517           new_st->expr1->ts.type = BT_LOGICAL;
8518           new_st->expr1->ts.kind = 4;
8519           new_st->expr1->value.function.name = gfc_get_string (PREFIX ("is_extension_of"));
8520           new_st->expr1->value.function.isym = XCNEW (gfc_intrinsic_sym);
8521           new_st->expr1->value.function.isym->id = GFC_ISYM_EXTENDS_TYPE_OF;
8522           /* Set up arguments.  */
8523           new_st->expr1->value.function.actual = gfc_get_actual_arglist ();
8524           new_st->expr1->value.function.actual->expr = gfc_get_variable_expr (code->expr1->symtree);
8525           new_st->expr1->value.function.actual->expr->where = code->loc;
8526           gfc_add_vptr_component (new_st->expr1->value.function.actual->expr);
8527           vtab = gfc_find_derived_vtab (body->ext.block.case_list->ts.u.derived);
8528           st = gfc_find_symtree (vtab->ns->sym_root, vtab->name);
8529           new_st->expr1->value.function.actual->next = gfc_get_actual_arglist ();
8530           new_st->expr1->value.function.actual->next->expr = gfc_get_variable_expr (st);
8531           new_st->next = body->next;
8532         }
8533         if (default_case->next)
8534           {
8535             new_st->block = gfc_get_code ();
8536             new_st = new_st->block;
8537             new_st->op = EXEC_IF;
8538             new_st->next = default_case->next;
8539           }
8540           
8541         /* Replace CLASS DEFAULT code by the IF chain.  */
8542         default_case->next = if_st;
8543     }
8544
8545   /* Resolve the internal code.  This can not be done earlier because
8546      it requires that the sym->assoc of selectors is set already.  */
8547   gfc_current_ns = ns;
8548   gfc_resolve_blocks (code->block, gfc_current_ns);
8549   gfc_current_ns = old_ns;
8550
8551   resolve_select (code);
8552 }
8553
8554
8555 /* Resolve a transfer statement. This is making sure that:
8556    -- a derived type being transferred has only non-pointer components
8557    -- a derived type being transferred doesn't have private components, unless 
8558       it's being transferred from the module where the type was defined
8559    -- we're not trying to transfer a whole assumed size array.  */
8560
8561 static void
8562 resolve_transfer (gfc_code *code)
8563 {
8564   gfc_typespec *ts;
8565   gfc_symbol *sym;
8566   gfc_ref *ref;
8567   gfc_expr *exp;
8568
8569   exp = code->expr1;
8570
8571   while (exp != NULL && exp->expr_type == EXPR_OP
8572          && exp->value.op.op == INTRINSIC_PARENTHESES)
8573     exp = exp->value.op.op1;
8574
8575   if (exp && exp->expr_type == EXPR_NULL && exp->ts.type == BT_UNKNOWN)
8576     {
8577       gfc_error ("NULL intrinsic at %L in data transfer statement requires "
8578                  "MOLD=", &exp->where);
8579       return;
8580     }
8581
8582   if (exp == NULL || (exp->expr_type != EXPR_VARIABLE
8583                       && exp->expr_type != EXPR_FUNCTION))
8584     return;
8585
8586   /* If we are reading, the variable will be changed.  Note that
8587      code->ext.dt may be NULL if the TRANSFER is related to
8588      an INQUIRE statement -- but in this case, we are not reading, either.  */
8589   if (code->ext.dt && code->ext.dt->dt_io_kind->value.iokind == M_READ
8590       && gfc_check_vardef_context (exp, false, false, _("item in READ"))
8591          == FAILURE)
8592     return;
8593
8594   sym = exp->symtree->n.sym;
8595   ts = &sym->ts;
8596
8597   /* Go to actual component transferred.  */
8598   for (ref = exp->ref; ref; ref = ref->next)
8599     if (ref->type == REF_COMPONENT)
8600       ts = &ref->u.c.component->ts;
8601
8602   if (ts->type == BT_CLASS)
8603     {
8604       /* FIXME: Test for defined input/output.  */
8605       gfc_error ("Data transfer element at %L cannot be polymorphic unless "
8606                 "it is processed by a defined input/output procedure",
8607                 &code->loc);
8608       return;
8609     }
8610
8611   if (ts->type == BT_DERIVED)
8612     {
8613       /* Check that transferred derived type doesn't contain POINTER
8614          components.  */
8615       if (ts->u.derived->attr.pointer_comp)
8616         {
8617           gfc_error ("Data transfer element at %L cannot have POINTER "
8618                      "components unless it is processed by a defined "
8619                      "input/output procedure", &code->loc);
8620           return;
8621         }
8622
8623       /* F08:C935.  */
8624       if (ts->u.derived->attr.proc_pointer_comp)
8625         {
8626           gfc_error ("Data transfer element at %L cannot have "
8627                      "procedure pointer components", &code->loc);
8628           return;
8629         }
8630
8631       if (ts->u.derived->attr.alloc_comp)
8632         {
8633           gfc_error ("Data transfer element at %L cannot have ALLOCATABLE "
8634                      "components unless it is processed by a defined "
8635                      "input/output procedure", &code->loc);
8636           return;
8637         }
8638
8639       if (derived_inaccessible (ts->u.derived))
8640         {
8641           gfc_error ("Data transfer element at %L cannot have "
8642                      "PRIVATE components",&code->loc);
8643           return;
8644         }
8645     }
8646
8647   if (sym->as != NULL && sym->as->type == AS_ASSUMED_SIZE && exp->ref
8648       && exp->ref->type == REF_ARRAY && exp->ref->u.ar.type == AR_FULL)
8649     {
8650       gfc_error ("Data transfer element at %L cannot be a full reference to "
8651                  "an assumed-size array", &code->loc);
8652       return;
8653     }
8654 }
8655
8656
8657 /*********** Toplevel code resolution subroutines ***********/
8658
8659 /* Find the set of labels that are reachable from this block.  We also
8660    record the last statement in each block.  */
8661      
8662 static void
8663 find_reachable_labels (gfc_code *block)
8664 {
8665   gfc_code *c;
8666
8667   if (!block)
8668     return;
8669
8670   cs_base->reachable_labels = bitmap_obstack_alloc (&labels_obstack);
8671
8672   /* Collect labels in this block.  We don't keep those corresponding
8673      to END {IF|SELECT}, these are checked in resolve_branch by going
8674      up through the code_stack.  */
8675   for (c = block; c; c = c->next)
8676     {
8677       if (c->here && c->op != EXEC_END_NESTED_BLOCK)
8678         bitmap_set_bit (cs_base->reachable_labels, c->here->value);
8679     }
8680
8681   /* Merge with labels from parent block.  */
8682   if (cs_base->prev)
8683     {
8684       gcc_assert (cs_base->prev->reachable_labels);
8685       bitmap_ior_into (cs_base->reachable_labels,
8686                        cs_base->prev->reachable_labels);
8687     }
8688 }
8689
8690
8691 static void
8692 resolve_lock_unlock (gfc_code *code)
8693 {
8694   if (code->expr1->ts.type != BT_DERIVED
8695       || code->expr1->expr_type != EXPR_VARIABLE
8696       || code->expr1->ts.u.derived->from_intmod != INTMOD_ISO_FORTRAN_ENV
8697       || code->expr1->ts.u.derived->intmod_sym_id != ISOFORTRAN_LOCK_TYPE
8698       || code->expr1->rank != 0
8699       || (!gfc_is_coarray (code->expr1) && !gfc_is_coindexed (code->expr1)))
8700     gfc_error ("Lock variable at %L must be a scalar of type LOCK_TYPE",
8701                &code->expr1->where);
8702
8703   /* Check STAT.  */
8704   if (code->expr2
8705       && (code->expr2->ts.type != BT_INTEGER || code->expr2->rank != 0
8706           || code->expr2->expr_type != EXPR_VARIABLE))
8707     gfc_error ("STAT= argument at %L must be a scalar INTEGER variable",
8708                &code->expr2->where);
8709
8710   if (code->expr2
8711       && gfc_check_vardef_context (code->expr2, false, false,
8712                                    _("STAT variable")) == FAILURE)
8713     return;
8714
8715   /* Check ERRMSG.  */
8716   if (code->expr3
8717       && (code->expr3->ts.type != BT_CHARACTER || code->expr3->rank != 0
8718           || code->expr3->expr_type != EXPR_VARIABLE))
8719     gfc_error ("ERRMSG= argument at %L must be a scalar CHARACTER variable",
8720                &code->expr3->where);
8721
8722   if (code->expr3
8723       && gfc_check_vardef_context (code->expr3, false, false,
8724                                    _("ERRMSG variable")) == FAILURE)
8725     return;
8726
8727   /* Check ACQUIRED_LOCK.  */
8728   if (code->expr4
8729       && (code->expr4->ts.type != BT_LOGICAL || code->expr4->rank != 0
8730           || code->expr4->expr_type != EXPR_VARIABLE))
8731     gfc_error ("ACQUIRED_LOCK= argument at %L must be a scalar LOGICAL "
8732                "variable", &code->expr4->where);
8733
8734   if (code->expr4
8735       && gfc_check_vardef_context (code->expr4, false, false,
8736                                    _("ACQUIRED_LOCK variable")) == FAILURE)
8737     return;
8738 }
8739
8740
8741 static void
8742 resolve_sync (gfc_code *code)
8743 {
8744   /* Check imageset. The * case matches expr1 == NULL.  */
8745   if (code->expr1)
8746     {
8747       if (code->expr1->ts.type != BT_INTEGER || code->expr1->rank > 1)
8748         gfc_error ("Imageset argument at %L must be a scalar or rank-1 "
8749                    "INTEGER expression", &code->expr1->where);
8750       if (code->expr1->expr_type == EXPR_CONSTANT && code->expr1->rank == 0
8751           && mpz_cmp_si (code->expr1->value.integer, 1) < 0)
8752         gfc_error ("Imageset argument at %L must between 1 and num_images()",
8753                    &code->expr1->where);
8754       else if (code->expr1->expr_type == EXPR_ARRAY
8755                && gfc_simplify_expr (code->expr1, 0) == SUCCESS)
8756         {
8757            gfc_constructor *cons;
8758            cons = gfc_constructor_first (code->expr1->value.constructor);
8759            for (; cons; cons = gfc_constructor_next (cons))
8760              if (cons->expr->expr_type == EXPR_CONSTANT
8761                  &&  mpz_cmp_si (cons->expr->value.integer, 1) < 0)
8762                gfc_error ("Imageset argument at %L must between 1 and "
8763                           "num_images()", &cons->expr->where);
8764         }
8765     }
8766
8767   /* Check STAT.  */
8768   if (code->expr2
8769       && (code->expr2->ts.type != BT_INTEGER || code->expr2->rank != 0
8770           || code->expr2->expr_type != EXPR_VARIABLE))
8771     gfc_error ("STAT= argument at %L must be a scalar INTEGER variable",
8772                &code->expr2->where);
8773
8774   /* Check ERRMSG.  */
8775   if (code->expr3
8776       && (code->expr3->ts.type != BT_CHARACTER || code->expr3->rank != 0
8777           || code->expr3->expr_type != EXPR_VARIABLE))
8778     gfc_error ("ERRMSG= argument at %L must be a scalar CHARACTER variable",
8779                &code->expr3->where);
8780 }
8781
8782
8783 /* Given a branch to a label, see if the branch is conforming.
8784    The code node describes where the branch is located.  */
8785
8786 static void
8787 resolve_branch (gfc_st_label *label, gfc_code *code)
8788 {
8789   code_stack *stack;
8790
8791   if (label == NULL)
8792     return;
8793
8794   /* Step one: is this a valid branching target?  */
8795
8796   if (label->defined == ST_LABEL_UNKNOWN)
8797     {
8798       gfc_error ("Label %d referenced at %L is never defined", label->value,
8799                  &label->where);
8800       return;
8801     }
8802
8803   if (label->defined != ST_LABEL_TARGET && label->defined != ST_LABEL_DO_TARGET)
8804     {
8805       gfc_error ("Statement at %L is not a valid branch target statement "
8806                  "for the branch statement at %L", &label->where, &code->loc);
8807       return;
8808     }
8809
8810   /* Step two: make sure this branch is not a branch to itself ;-)  */
8811
8812   if (code->here == label)
8813     {
8814       gfc_warning ("Branch at %L may result in an infinite loop", &code->loc);
8815       return;
8816     }
8817
8818   /* Step three:  See if the label is in the same block as the
8819      branching statement.  The hard work has been done by setting up
8820      the bitmap reachable_labels.  */
8821
8822   if (bitmap_bit_p (cs_base->reachable_labels, label->value))
8823     {
8824       /* Check now whether there is a CRITICAL construct; if so, check
8825          whether the label is still visible outside of the CRITICAL block,
8826          which is invalid.  */
8827       for (stack = cs_base; stack; stack = stack->prev)
8828         {
8829           if (stack->current->op == EXEC_CRITICAL
8830               && bitmap_bit_p (stack->reachable_labels, label->value))
8831             gfc_error ("GOTO statement at %L leaves CRITICAL construct for "
8832                       "label at %L", &code->loc, &label->where);
8833           else if (stack->current->op == EXEC_DO_CONCURRENT
8834                    && bitmap_bit_p (stack->reachable_labels, label->value))
8835             gfc_error ("GOTO statement at %L leaves DO CONCURRENT construct "
8836                       "for label at %L", &code->loc, &label->where);
8837         }
8838
8839       return;
8840     }
8841
8842   /* Step four:  If we haven't found the label in the bitmap, it may
8843     still be the label of the END of the enclosing block, in which
8844     case we find it by going up the code_stack.  */
8845
8846   for (stack = cs_base; stack; stack = stack->prev)
8847     {
8848       if (stack->current->next && stack->current->next->here == label)
8849         break;
8850       if (stack->current->op == EXEC_CRITICAL)
8851         {
8852           /* Note: A label at END CRITICAL does not leave the CRITICAL
8853              construct as END CRITICAL is still part of it.  */
8854           gfc_error ("GOTO statement at %L leaves CRITICAL construct for label"
8855                       " at %L", &code->loc, &label->where);
8856           return;
8857         }
8858       else if (stack->current->op == EXEC_DO_CONCURRENT)
8859         {
8860           gfc_error ("GOTO statement at %L leaves DO CONCURRENT construct for "
8861                      "label at %L", &code->loc, &label->where);
8862           return;
8863         }
8864     }
8865
8866   if (stack)
8867     {
8868       gcc_assert (stack->current->next->op == EXEC_END_NESTED_BLOCK);
8869       return;
8870     }
8871
8872   /* The label is not in an enclosing block, so illegal.  This was
8873      allowed in Fortran 66, so we allow it as extension.  No
8874      further checks are necessary in this case.  */
8875   gfc_notify_std (GFC_STD_LEGACY, "Label at %L is not in the same block "
8876                   "as the GOTO statement at %L", &label->where,
8877                   &code->loc);
8878   return;
8879 }
8880
8881
8882 /* Check whether EXPR1 has the same shape as EXPR2.  */
8883
8884 static gfc_try
8885 resolve_where_shape (gfc_expr *expr1, gfc_expr *expr2)
8886 {
8887   mpz_t shape[GFC_MAX_DIMENSIONS];
8888   mpz_t shape2[GFC_MAX_DIMENSIONS];
8889   gfc_try result = FAILURE;
8890   int i;
8891
8892   /* Compare the rank.  */
8893   if (expr1->rank != expr2->rank)
8894     return result;
8895
8896   /* Compare the size of each dimension.  */
8897   for (i=0; i<expr1->rank; i++)
8898     {
8899       if (gfc_array_dimen_size (expr1, i, &shape[i]) == FAILURE)
8900         goto ignore;
8901
8902       if (gfc_array_dimen_size (expr2, i, &shape2[i]) == FAILURE)
8903         goto ignore;
8904
8905       if (mpz_cmp (shape[i], shape2[i]))
8906         goto over;
8907     }
8908
8909   /* When either of the two expression is an assumed size array, we
8910      ignore the comparison of dimension sizes.  */
8911 ignore:
8912   result = SUCCESS;
8913
8914 over:
8915   gfc_clear_shape (shape, i);
8916   gfc_clear_shape (shape2, i);
8917   return result;
8918 }
8919
8920
8921 /* Check whether a WHERE assignment target or a WHERE mask expression
8922    has the same shape as the outmost WHERE mask expression.  */
8923
8924 static void
8925 resolve_where (gfc_code *code, gfc_expr *mask)
8926 {
8927   gfc_code *cblock;
8928   gfc_code *cnext;
8929   gfc_expr *e = NULL;
8930
8931   cblock = code->block;
8932
8933   /* Store the first WHERE mask-expr of the WHERE statement or construct.
8934      In case of nested WHERE, only the outmost one is stored.  */
8935   if (mask == NULL) /* outmost WHERE */
8936     e = cblock->expr1;
8937   else /* inner WHERE */
8938     e = mask;
8939
8940   while (cblock)
8941     {
8942       if (cblock->expr1)
8943         {
8944           /* Check if the mask-expr has a consistent shape with the
8945              outmost WHERE mask-expr.  */
8946           if (resolve_where_shape (cblock->expr1, e) == FAILURE)
8947             gfc_error ("WHERE mask at %L has inconsistent shape",
8948                        &cblock->expr1->where);
8949          }
8950
8951       /* the assignment statement of a WHERE statement, or the first
8952          statement in where-body-construct of a WHERE construct */
8953       cnext = cblock->next;
8954       while (cnext)
8955         {
8956           switch (cnext->op)
8957             {
8958             /* WHERE assignment statement */
8959             case EXEC_ASSIGN:
8960
8961               /* Check shape consistent for WHERE assignment target.  */
8962               if (e && resolve_where_shape (cnext->expr1, e) == FAILURE)
8963                gfc_error ("WHERE assignment target at %L has "
8964                           "inconsistent shape", &cnext->expr1->where);
8965               break;
8966
8967   
8968             case EXEC_ASSIGN_CALL:
8969               resolve_call (cnext);
8970               if (!cnext->resolved_sym->attr.elemental)
8971                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
8972                           &cnext->ext.actual->expr->where);
8973               break;
8974
8975             /* WHERE or WHERE construct is part of a where-body-construct */
8976             case EXEC_WHERE:
8977               resolve_where (cnext, e);
8978               break;
8979
8980             default:
8981               gfc_error ("Unsupported statement inside WHERE at %L",
8982                          &cnext->loc);
8983             }
8984          /* the next statement within the same where-body-construct */
8985          cnext = cnext->next;
8986        }
8987     /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
8988     cblock = cblock->block;
8989   }
8990 }
8991
8992
8993 /* Resolve assignment in FORALL construct.
8994    NVAR is the number of FORALL index variables, and VAR_EXPR records the
8995    FORALL index variables.  */
8996
8997 static void
8998 gfc_resolve_assign_in_forall (gfc_code *code, int nvar, gfc_expr **var_expr)
8999 {
9000   int n;
9001
9002   for (n = 0; n < nvar; n++)
9003     {
9004       gfc_symbol *forall_index;
9005
9006       forall_index = var_expr[n]->symtree->n.sym;
9007
9008       /* Check whether the assignment target is one of the FORALL index
9009          variable.  */
9010       if ((code->expr1->expr_type == EXPR_VARIABLE)
9011           && (code->expr1->symtree->n.sym == forall_index))
9012         gfc_error ("Assignment to a FORALL index variable at %L",
9013                    &code->expr1->where);
9014       else
9015         {
9016           /* If one of the FORALL index variables doesn't appear in the
9017              assignment variable, then there could be a many-to-one
9018              assignment.  Emit a warning rather than an error because the
9019              mask could be resolving this problem.  */
9020           if (find_forall_index (code->expr1, forall_index, 0) == FAILURE)
9021             gfc_warning ("The FORALL with index '%s' is not used on the "
9022                          "left side of the assignment at %L and so might "
9023                          "cause multiple assignment to this object",
9024                          var_expr[n]->symtree->name, &code->expr1->where);
9025         }
9026     }
9027 }
9028
9029
9030 /* Resolve WHERE statement in FORALL construct.  */
9031
9032 static void
9033 gfc_resolve_where_code_in_forall (gfc_code *code, int nvar,
9034                                   gfc_expr **var_expr)
9035 {
9036   gfc_code *cblock;
9037   gfc_code *cnext;
9038
9039   cblock = code->block;
9040   while (cblock)
9041     {
9042       /* the assignment statement of a WHERE statement, or the first
9043          statement in where-body-construct of a WHERE construct */
9044       cnext = cblock->next;
9045       while (cnext)
9046         {
9047           switch (cnext->op)
9048             {
9049             /* WHERE assignment statement */
9050             case EXEC_ASSIGN:
9051               gfc_resolve_assign_in_forall (cnext, nvar, var_expr);
9052               break;
9053   
9054             /* WHERE operator assignment statement */
9055             case EXEC_ASSIGN_CALL:
9056               resolve_call (cnext);
9057               if (!cnext->resolved_sym->attr.elemental)
9058                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
9059                           &cnext->ext.actual->expr->where);
9060               break;
9061
9062             /* WHERE or WHERE construct is part of a where-body-construct */
9063             case EXEC_WHERE:
9064               gfc_resolve_where_code_in_forall (cnext, nvar, var_expr);
9065               break;
9066
9067             default:
9068               gfc_error ("Unsupported statement inside WHERE at %L",
9069                          &cnext->loc);
9070             }
9071           /* the next statement within the same where-body-construct */
9072           cnext = cnext->next;
9073         }
9074       /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
9075       cblock = cblock->block;
9076     }
9077 }
9078
9079
9080 /* Traverse the FORALL body to check whether the following errors exist:
9081    1. For assignment, check if a many-to-one assignment happens.
9082    2. For WHERE statement, check the WHERE body to see if there is any
9083       many-to-one assignment.  */
9084
9085 static void
9086 gfc_resolve_forall_body (gfc_code *code, int nvar, gfc_expr **var_expr)
9087 {
9088   gfc_code *c;
9089
9090   c = code->block->next;
9091   while (c)
9092     {
9093       switch (c->op)
9094         {
9095         case EXEC_ASSIGN:
9096         case EXEC_POINTER_ASSIGN:
9097           gfc_resolve_assign_in_forall (c, nvar, var_expr);
9098           break;
9099
9100         case EXEC_ASSIGN_CALL:
9101           resolve_call (c);
9102           break;
9103
9104         /* Because the gfc_resolve_blocks() will handle the nested FORALL,
9105            there is no need to handle it here.  */
9106         case EXEC_FORALL:
9107           break;
9108         case EXEC_WHERE:
9109           gfc_resolve_where_code_in_forall(c, nvar, var_expr);
9110           break;
9111         default:
9112           break;
9113         }
9114       /* The next statement in the FORALL body.  */
9115       c = c->next;
9116     }
9117 }
9118
9119
9120 /* Counts the number of iterators needed inside a forall construct, including
9121    nested forall constructs. This is used to allocate the needed memory 
9122    in gfc_resolve_forall.  */
9123
9124 static int 
9125 gfc_count_forall_iterators (gfc_code *code)
9126 {
9127   int max_iters, sub_iters, current_iters;
9128   gfc_forall_iterator *fa;
9129
9130   gcc_assert(code->op == EXEC_FORALL);
9131   max_iters = 0;
9132   current_iters = 0;
9133
9134   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
9135     current_iters ++;
9136   
9137   code = code->block->next;
9138
9139   while (code)
9140     {          
9141       if (code->op == EXEC_FORALL)
9142         {
9143           sub_iters = gfc_count_forall_iterators (code);
9144           if (sub_iters > max_iters)
9145             max_iters = sub_iters;
9146         }
9147       code = code->next;
9148     }
9149
9150   return current_iters + max_iters;
9151 }
9152
9153
9154 /* Given a FORALL construct, first resolve the FORALL iterator, then call
9155    gfc_resolve_forall_body to resolve the FORALL body.  */
9156
9157 static void
9158 gfc_resolve_forall (gfc_code *code, gfc_namespace *ns, int forall_save)
9159 {
9160   static gfc_expr **var_expr;
9161   static int total_var = 0;
9162   static int nvar = 0;
9163   int old_nvar, tmp;
9164   gfc_forall_iterator *fa;
9165   int i;
9166
9167   old_nvar = nvar;
9168
9169   /* Start to resolve a FORALL construct   */
9170   if (forall_save == 0)
9171     {
9172       /* Count the total number of FORALL index in the nested FORALL
9173          construct in order to allocate the VAR_EXPR with proper size.  */
9174       total_var = gfc_count_forall_iterators (code);
9175
9176       /* Allocate VAR_EXPR with NUMBER_OF_FORALL_INDEX elements.  */
9177       var_expr = XCNEWVEC (gfc_expr *, total_var);
9178     }
9179
9180   /* The information about FORALL iterator, including FORALL index start, end
9181      and stride. The FORALL index can not appear in start, end or stride.  */
9182   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
9183     {
9184       /* Check if any outer FORALL index name is the same as the current
9185          one.  */
9186       for (i = 0; i < nvar; i++)
9187         {
9188           if (fa->var->symtree->n.sym == var_expr[i]->symtree->n.sym)
9189             {
9190               gfc_error ("An outer FORALL construct already has an index "
9191                          "with this name %L", &fa->var->where);
9192             }
9193         }
9194
9195       /* Record the current FORALL index.  */
9196       var_expr[nvar] = gfc_copy_expr (fa->var);
9197
9198       nvar++;
9199
9200       /* No memory leak.  */
9201       gcc_assert (nvar <= total_var);
9202     }
9203
9204   /* Resolve the FORALL body.  */
9205   gfc_resolve_forall_body (code, nvar, var_expr);
9206
9207   /* May call gfc_resolve_forall to resolve the inner FORALL loop.  */
9208   gfc_resolve_blocks (code->block, ns);
9209
9210   tmp = nvar;
9211   nvar = old_nvar;
9212   /* Free only the VAR_EXPRs allocated in this frame.  */
9213   for (i = nvar; i < tmp; i++)
9214      gfc_free_expr (var_expr[i]);
9215
9216   if (nvar == 0)
9217     {
9218       /* We are in the outermost FORALL construct.  */
9219       gcc_assert (forall_save == 0);
9220
9221       /* VAR_EXPR is not needed any more.  */
9222       free (var_expr);
9223       total_var = 0;
9224     }
9225 }
9226
9227
9228 /* Resolve a BLOCK construct statement.  */
9229
9230 static void
9231 resolve_block_construct (gfc_code* code)
9232 {
9233   /* Resolve the BLOCK's namespace.  */
9234   gfc_resolve (code->ext.block.ns);
9235
9236   /* For an ASSOCIATE block, the associations (and their targets) are already
9237      resolved during resolve_symbol.  */
9238 }
9239
9240
9241 /* Resolve lists of blocks found in IF, SELECT CASE, WHERE, FORALL, GOTO and
9242    DO code nodes.  */
9243
9244 static void resolve_code (gfc_code *, gfc_namespace *);
9245
9246 void
9247 gfc_resolve_blocks (gfc_code *b, gfc_namespace *ns)
9248 {
9249   gfc_try t;
9250
9251   for (; b; b = b->block)
9252     {
9253       t = gfc_resolve_expr (b->expr1);
9254       if (gfc_resolve_expr (b->expr2) == FAILURE)
9255         t = FAILURE;
9256
9257       switch (b->op)
9258         {
9259         case EXEC_IF:
9260           if (t == SUCCESS && b->expr1 != NULL
9261               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank != 0))
9262             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
9263                        &b->expr1->where);
9264           break;
9265
9266         case EXEC_WHERE:
9267           if (t == SUCCESS
9268               && b->expr1 != NULL
9269               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank == 0))
9270             gfc_error ("WHERE/ELSEWHERE clause at %L requires a LOGICAL array",
9271                        &b->expr1->where);
9272           break;
9273
9274         case EXEC_GOTO:
9275           resolve_branch (b->label1, b);
9276           break;
9277
9278         case EXEC_BLOCK:
9279           resolve_block_construct (b);
9280           break;
9281
9282         case EXEC_SELECT:
9283         case EXEC_SELECT_TYPE:
9284         case EXEC_FORALL:
9285         case EXEC_DO:
9286         case EXEC_DO_WHILE:
9287         case EXEC_DO_CONCURRENT:
9288         case EXEC_CRITICAL:
9289         case EXEC_READ:
9290         case EXEC_WRITE:
9291         case EXEC_IOLENGTH:
9292         case EXEC_WAIT:
9293           break;
9294
9295         case EXEC_OMP_ATOMIC:
9296         case EXEC_OMP_CRITICAL:
9297         case EXEC_OMP_DO:
9298         case EXEC_OMP_MASTER:
9299         case EXEC_OMP_ORDERED:
9300         case EXEC_OMP_PARALLEL:
9301         case EXEC_OMP_PARALLEL_DO:
9302         case EXEC_OMP_PARALLEL_SECTIONS:
9303         case EXEC_OMP_PARALLEL_WORKSHARE:
9304         case EXEC_OMP_SECTIONS:
9305         case EXEC_OMP_SINGLE:
9306         case EXEC_OMP_TASK:
9307         case EXEC_OMP_TASKWAIT:
9308         case EXEC_OMP_TASKYIELD:
9309         case EXEC_OMP_WORKSHARE:
9310           break;
9311
9312         default:
9313           gfc_internal_error ("gfc_resolve_blocks(): Bad block type");
9314         }
9315
9316       resolve_code (b->next, ns);
9317     }
9318 }
9319
9320
9321 /* Does everything to resolve an ordinary assignment.  Returns true
9322    if this is an interface assignment.  */
9323 static bool
9324 resolve_ordinary_assign (gfc_code *code, gfc_namespace *ns)
9325 {
9326   bool rval = false;
9327   gfc_expr *lhs;
9328   gfc_expr *rhs;
9329   int llen = 0;
9330   int rlen = 0;
9331   int n;
9332   gfc_ref *ref;
9333
9334   if (gfc_extend_assign (code, ns) == SUCCESS)
9335     {
9336       gfc_expr** rhsptr;
9337
9338       if (code->op == EXEC_ASSIGN_CALL)
9339         {
9340           lhs = code->ext.actual->expr;
9341           rhsptr = &code->ext.actual->next->expr;
9342         }
9343       else
9344         {
9345           gfc_actual_arglist* args;
9346           gfc_typebound_proc* tbp;
9347
9348           gcc_assert (code->op == EXEC_COMPCALL);
9349
9350           args = code->expr1->value.compcall.actual;
9351           lhs = args->expr;
9352           rhsptr = &args->next->expr;
9353
9354           tbp = code->expr1->value.compcall.tbp;
9355           gcc_assert (!tbp->is_generic);
9356         }
9357
9358       /* Make a temporary rhs when there is a default initializer
9359          and rhs is the same symbol as the lhs.  */
9360       if ((*rhsptr)->expr_type == EXPR_VARIABLE
9361             && (*rhsptr)->symtree->n.sym->ts.type == BT_DERIVED
9362             && gfc_has_default_initializer ((*rhsptr)->symtree->n.sym->ts.u.derived)
9363             && (lhs->symtree->n.sym == (*rhsptr)->symtree->n.sym))
9364         *rhsptr = gfc_get_parentheses (*rhsptr);
9365
9366       return true;
9367     }
9368
9369   lhs = code->expr1;
9370   rhs = code->expr2;
9371
9372   if (rhs->is_boz
9373       && gfc_notify_std (GFC_STD_GNU, "BOZ literal at %L outside "
9374                          "a DATA statement and outside INT/REAL/DBLE/CMPLX",
9375                          &code->loc) == FAILURE)
9376     return false;
9377
9378   /* Handle the case of a BOZ literal on the RHS.  */
9379   if (rhs->is_boz && lhs->ts.type != BT_INTEGER)
9380     {
9381       int rc;
9382       if (gfc_option.warn_surprising)
9383         gfc_warning ("BOZ literal at %L is bitwise transferred "
9384                      "non-integer symbol '%s'", &code->loc,
9385                      lhs->symtree->n.sym->name);
9386
9387       if (!gfc_convert_boz (rhs, &lhs->ts))
9388         return false;
9389       if ((rc = gfc_range_check (rhs)) != ARITH_OK)
9390         {
9391           if (rc == ARITH_UNDERFLOW)
9392             gfc_error ("Arithmetic underflow of bit-wise transferred BOZ at %L"
9393                        ". This check can be disabled with the option "
9394                        "-fno-range-check", &rhs->where);
9395           else if (rc == ARITH_OVERFLOW)
9396             gfc_error ("Arithmetic overflow of bit-wise transferred BOZ at %L"
9397                        ". This check can be disabled with the option "
9398                        "-fno-range-check", &rhs->where);
9399           else if (rc == ARITH_NAN)
9400             gfc_error ("Arithmetic NaN of bit-wise transferred BOZ at %L"
9401                        ". This check can be disabled with the option "
9402                        "-fno-range-check", &rhs->where);
9403           return false;
9404         }
9405     }
9406
9407   if (lhs->ts.type == BT_CHARACTER
9408         && gfc_option.warn_character_truncation)
9409     {
9410       if (lhs->ts.u.cl != NULL
9411             && lhs->ts.u.cl->length != NULL
9412             && lhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
9413         llen = mpz_get_si (lhs->ts.u.cl->length->value.integer);
9414
9415       if (rhs->expr_type == EXPR_CONSTANT)
9416         rlen = rhs->value.character.length;
9417
9418       else if (rhs->ts.u.cl != NULL
9419                  && rhs->ts.u.cl->length != NULL
9420                  && rhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
9421         rlen = mpz_get_si (rhs->ts.u.cl->length->value.integer);
9422
9423       if (rlen && llen && rlen > llen)
9424         gfc_warning_now ("CHARACTER expression will be truncated "
9425                          "in assignment (%d/%d) at %L",
9426                          llen, rlen, &code->loc);
9427     }
9428
9429   /* Ensure that a vector index expression for the lvalue is evaluated
9430      to a temporary if the lvalue symbol is referenced in it.  */
9431   if (lhs->rank)
9432     {
9433       for (ref = lhs->ref; ref; ref= ref->next)
9434         if (ref->type == REF_ARRAY)
9435           {
9436             for (n = 0; n < ref->u.ar.dimen; n++)
9437               if (ref->u.ar.dimen_type[n] == DIMEN_VECTOR
9438                   && gfc_find_sym_in_expr (lhs->symtree->n.sym,
9439                                            ref->u.ar.start[n]))
9440                 ref->u.ar.start[n]
9441                         = gfc_get_parentheses (ref->u.ar.start[n]);
9442           }
9443     }
9444
9445   if (gfc_pure (NULL))
9446     {
9447       if (lhs->ts.type == BT_DERIVED
9448             && lhs->expr_type == EXPR_VARIABLE
9449             && lhs->ts.u.derived->attr.pointer_comp
9450             && rhs->expr_type == EXPR_VARIABLE
9451             && (gfc_impure_variable (rhs->symtree->n.sym)
9452                 || gfc_is_coindexed (rhs)))
9453         {
9454           /* F2008, C1283.  */
9455           if (gfc_is_coindexed (rhs))
9456             gfc_error ("Coindexed expression at %L is assigned to "
9457                         "a derived type variable with a POINTER "
9458                         "component in a PURE procedure",
9459                         &rhs->where);
9460           else
9461             gfc_error ("The impure variable at %L is assigned to "
9462                         "a derived type variable with a POINTER "
9463                         "component in a PURE procedure (12.6)",
9464                         &rhs->where);
9465           return rval;
9466         }
9467
9468       /* Fortran 2008, C1283.  */
9469       if (gfc_is_coindexed (lhs))
9470         {
9471           gfc_error ("Assignment to coindexed variable at %L in a PURE "
9472                      "procedure", &rhs->where);
9473           return rval;
9474         }
9475     }
9476
9477   if (gfc_implicit_pure (NULL))
9478     {
9479       if (lhs->expr_type == EXPR_VARIABLE
9480             && lhs->symtree->n.sym != gfc_current_ns->proc_name
9481             && lhs->symtree->n.sym->ns != gfc_current_ns)
9482         gfc_current_ns->proc_name->attr.implicit_pure = 0;
9483
9484       if (lhs->ts.type == BT_DERIVED
9485             && lhs->expr_type == EXPR_VARIABLE
9486             && lhs->ts.u.derived->attr.pointer_comp
9487             && rhs->expr_type == EXPR_VARIABLE
9488             && (gfc_impure_variable (rhs->symtree->n.sym)
9489                 || gfc_is_coindexed (rhs)))
9490         gfc_current_ns->proc_name->attr.implicit_pure = 0;
9491
9492       /* Fortran 2008, C1283.  */
9493       if (gfc_is_coindexed (lhs))
9494         gfc_current_ns->proc_name->attr.implicit_pure = 0;
9495     }
9496
9497   /* F03:7.4.1.2.  */
9498   /* FIXME: Valid in Fortran 2008, unless the LHS is both polymorphic
9499      and coindexed; cf. F2008, 7.2.1.2 and PR 43366.  */
9500   if (lhs->ts.type == BT_CLASS)
9501     {
9502       gfc_error ("Variable must not be polymorphic in intrinsic assignment at "
9503                  "%L - check that there is a matching specific subroutine "
9504                  "for '=' operator", &lhs->where);
9505       return false;
9506     }
9507
9508   /* F2008, Section 7.2.1.2.  */
9509   if (gfc_is_coindexed (lhs) && gfc_has_ultimate_allocatable (lhs))
9510     {
9511       gfc_error ("Coindexed variable must not be have an allocatable ultimate "
9512                  "component in assignment at %L", &lhs->where);
9513       return false;
9514     }
9515
9516   gfc_check_assign (lhs, rhs, 1);
9517   return false;
9518 }
9519
9520
9521 /* Given a block of code, recursively resolve everything pointed to by this
9522    code block.  */
9523
9524 static void
9525 resolve_code (gfc_code *code, gfc_namespace *ns)
9526 {
9527   int omp_workshare_save;
9528   int forall_save, do_concurrent_save;
9529   code_stack frame;
9530   gfc_try t;
9531
9532   frame.prev = cs_base;
9533   frame.head = code;
9534   cs_base = &frame;
9535
9536   find_reachable_labels (code);
9537
9538   for (; code; code = code->next)
9539     {
9540       frame.current = code;
9541       forall_save = forall_flag;
9542       do_concurrent_save = do_concurrent_flag;
9543
9544       if (code->op == EXEC_FORALL)
9545         {
9546           forall_flag = 1;
9547           gfc_resolve_forall (code, ns, forall_save);
9548           forall_flag = 2;
9549         }
9550       else if (code->block)
9551         {
9552           omp_workshare_save = -1;
9553           switch (code->op)
9554             {
9555             case EXEC_OMP_PARALLEL_WORKSHARE:
9556               omp_workshare_save = omp_workshare_flag;
9557               omp_workshare_flag = 1;
9558               gfc_resolve_omp_parallel_blocks (code, ns);
9559               break;
9560             case EXEC_OMP_PARALLEL:
9561             case EXEC_OMP_PARALLEL_DO:
9562             case EXEC_OMP_PARALLEL_SECTIONS:
9563             case EXEC_OMP_TASK:
9564               omp_workshare_save = omp_workshare_flag;
9565               omp_workshare_flag = 0;
9566               gfc_resolve_omp_parallel_blocks (code, ns);
9567               break;
9568             case EXEC_OMP_DO:
9569               gfc_resolve_omp_do_blocks (code, ns);
9570               break;
9571             case EXEC_SELECT_TYPE:
9572               /* Blocks are handled in resolve_select_type because we have
9573                  to transform the SELECT TYPE into ASSOCIATE first.  */
9574               break;
9575             case EXEC_DO_CONCURRENT:
9576               do_concurrent_flag = 1;
9577               gfc_resolve_blocks (code->block, ns);
9578               do_concurrent_flag = 2;
9579               break;
9580             case EXEC_OMP_WORKSHARE:
9581               omp_workshare_save = omp_workshare_flag;
9582               omp_workshare_flag = 1;
9583               /* FALL THROUGH */
9584             default:
9585               gfc_resolve_blocks (code->block, ns);
9586               break;
9587             }
9588
9589           if (omp_workshare_save != -1)
9590             omp_workshare_flag = omp_workshare_save;
9591         }
9592
9593       t = SUCCESS;
9594       if (code->op != EXEC_COMPCALL && code->op != EXEC_CALL_PPC)
9595         t = gfc_resolve_expr (code->expr1);
9596       forall_flag = forall_save;
9597       do_concurrent_flag = do_concurrent_save;
9598
9599       if (gfc_resolve_expr (code->expr2) == FAILURE)
9600         t = FAILURE;
9601
9602       if (code->op == EXEC_ALLOCATE
9603           && gfc_resolve_expr (code->expr3) == FAILURE)
9604         t = FAILURE;
9605
9606       switch (code->op)
9607         {
9608         case EXEC_NOP:
9609         case EXEC_END_BLOCK:
9610         case EXEC_END_NESTED_BLOCK:
9611         case EXEC_CYCLE:
9612         case EXEC_PAUSE:
9613         case EXEC_STOP:
9614         case EXEC_ERROR_STOP:
9615         case EXEC_EXIT:
9616         case EXEC_CONTINUE:
9617         case EXEC_DT_END:
9618         case EXEC_ASSIGN_CALL:
9619         case EXEC_CRITICAL:
9620           break;
9621
9622         case EXEC_SYNC_ALL:
9623         case EXEC_SYNC_IMAGES:
9624         case EXEC_SYNC_MEMORY:
9625           resolve_sync (code);
9626           break;
9627
9628         case EXEC_LOCK:
9629         case EXEC_UNLOCK:
9630           resolve_lock_unlock (code);
9631           break;
9632
9633         case EXEC_ENTRY:
9634           /* Keep track of which entry we are up to.  */
9635           current_entry_id = code->ext.entry->id;
9636           break;
9637
9638         case EXEC_WHERE:
9639           resolve_where (code, NULL);
9640           break;
9641
9642         case EXEC_GOTO:
9643           if (code->expr1 != NULL)
9644             {
9645               if (code->expr1->ts.type != BT_INTEGER)
9646                 gfc_error ("ASSIGNED GOTO statement at %L requires an "
9647                            "INTEGER variable", &code->expr1->where);
9648               else if (code->expr1->symtree->n.sym->attr.assign != 1)
9649                 gfc_error ("Variable '%s' has not been assigned a target "
9650                            "label at %L", code->expr1->symtree->n.sym->name,
9651                            &code->expr1->where);
9652             }
9653           else
9654             resolve_branch (code->label1, code);
9655           break;
9656
9657         case EXEC_RETURN:
9658           if (code->expr1 != NULL
9659                 && (code->expr1->ts.type != BT_INTEGER || code->expr1->rank))
9660             gfc_error ("Alternate RETURN statement at %L requires a SCALAR-"
9661                        "INTEGER return specifier", &code->expr1->where);
9662           break;
9663
9664         case EXEC_INIT_ASSIGN:
9665         case EXEC_END_PROCEDURE:
9666           break;
9667
9668         case EXEC_ASSIGN:
9669           if (t == FAILURE)
9670             break;
9671
9672           if (gfc_check_vardef_context (code->expr1, false, false,
9673                                         _("assignment")) == FAILURE)
9674             break;
9675
9676           if (resolve_ordinary_assign (code, ns))
9677             {
9678               if (code->op == EXEC_COMPCALL)
9679                 goto compcall;
9680               else
9681                 goto call;
9682             }
9683           break;
9684
9685         case EXEC_LABEL_ASSIGN:
9686           if (code->label1->defined == ST_LABEL_UNKNOWN)
9687             gfc_error ("Label %d referenced at %L is never defined",
9688                        code->label1->value, &code->label1->where);
9689           if (t == SUCCESS
9690               && (code->expr1->expr_type != EXPR_VARIABLE
9691                   || code->expr1->symtree->n.sym->ts.type != BT_INTEGER
9692                   || code->expr1->symtree->n.sym->ts.kind
9693                      != gfc_default_integer_kind
9694                   || code->expr1->symtree->n.sym->as != NULL))
9695             gfc_error ("ASSIGN statement at %L requires a scalar "
9696                        "default INTEGER variable", &code->expr1->where);
9697           break;
9698
9699         case EXEC_POINTER_ASSIGN:
9700           {
9701             gfc_expr* e;
9702
9703             if (t == FAILURE)
9704               break;
9705
9706             /* This is both a variable definition and pointer assignment
9707                context, so check both of them.  For rank remapping, a final
9708                array ref may be present on the LHS and fool gfc_expr_attr
9709                used in gfc_check_vardef_context.  Remove it.  */
9710             e = remove_last_array_ref (code->expr1);
9711             t = gfc_check_vardef_context (e, true, false,
9712                                           _("pointer assignment"));
9713             if (t == SUCCESS)
9714               t = gfc_check_vardef_context (e, false, false,
9715                                             _("pointer assignment"));
9716             gfc_free_expr (e);
9717             if (t == FAILURE)
9718               break;
9719
9720             gfc_check_pointer_assign (code->expr1, code->expr2);
9721             break;
9722           }
9723
9724         case EXEC_ARITHMETIC_IF:
9725           if (t == SUCCESS
9726               && code->expr1->ts.type != BT_INTEGER
9727               && code->expr1->ts.type != BT_REAL)
9728             gfc_error ("Arithmetic IF statement at %L requires a numeric "
9729                        "expression", &code->expr1->where);
9730
9731           resolve_branch (code->label1, code);
9732           resolve_branch (code->label2, code);
9733           resolve_branch (code->label3, code);
9734           break;
9735
9736         case EXEC_IF:
9737           if (t == SUCCESS && code->expr1 != NULL
9738               && (code->expr1->ts.type != BT_LOGICAL
9739                   || code->expr1->rank != 0))
9740             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
9741                        &code->expr1->where);
9742           break;
9743
9744         case EXEC_CALL:
9745         call:
9746           resolve_call (code);
9747           break;
9748
9749         case EXEC_COMPCALL:
9750         compcall:
9751           resolve_typebound_subroutine (code);
9752           break;
9753
9754         case EXEC_CALL_PPC:
9755           resolve_ppc_call (code);
9756           break;
9757
9758         case EXEC_SELECT:
9759           /* Select is complicated. Also, a SELECT construct could be
9760              a transformed computed GOTO.  */
9761           resolve_select (code);
9762           break;
9763
9764         case EXEC_SELECT_TYPE:
9765           resolve_select_type (code, ns);
9766           break;
9767
9768         case EXEC_BLOCK:
9769           resolve_block_construct (code);
9770           break;
9771
9772         case EXEC_DO:
9773           if (code->ext.iterator != NULL)
9774             {
9775               gfc_iterator *iter = code->ext.iterator;
9776               if (gfc_resolve_iterator (iter, true) != FAILURE)
9777                 gfc_resolve_do_iterator (code, iter->var->symtree->n.sym);
9778             }
9779           break;
9780
9781         case EXEC_DO_WHILE:
9782           if (code->expr1 == NULL)
9783             gfc_internal_error ("resolve_code(): No expression on DO WHILE");
9784           if (t == SUCCESS
9785               && (code->expr1->rank != 0
9786                   || code->expr1->ts.type != BT_LOGICAL))
9787             gfc_error ("Exit condition of DO WHILE loop at %L must be "
9788                        "a scalar LOGICAL expression", &code->expr1->where);
9789           break;
9790
9791         case EXEC_ALLOCATE:
9792           if (t == SUCCESS)
9793             resolve_allocate_deallocate (code, "ALLOCATE");
9794
9795           break;
9796
9797         case EXEC_DEALLOCATE:
9798           if (t == SUCCESS)
9799             resolve_allocate_deallocate (code, "DEALLOCATE");
9800
9801           break;
9802
9803         case EXEC_OPEN:
9804           if (gfc_resolve_open (code->ext.open) == FAILURE)
9805             break;
9806
9807           resolve_branch (code->ext.open->err, code);
9808           break;
9809
9810         case EXEC_CLOSE:
9811           if (gfc_resolve_close (code->ext.close) == FAILURE)
9812             break;
9813
9814           resolve_branch (code->ext.close->err, code);
9815           break;
9816
9817         case EXEC_BACKSPACE:
9818         case EXEC_ENDFILE:
9819         case EXEC_REWIND:
9820         case EXEC_FLUSH:
9821           if (gfc_resolve_filepos (code->ext.filepos) == FAILURE)
9822             break;
9823
9824           resolve_branch (code->ext.filepos->err, code);
9825           break;
9826
9827         case EXEC_INQUIRE:
9828           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
9829               break;
9830
9831           resolve_branch (code->ext.inquire->err, code);
9832           break;
9833
9834         case EXEC_IOLENGTH:
9835           gcc_assert (code->ext.inquire != NULL);
9836           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
9837             break;
9838
9839           resolve_branch (code->ext.inquire->err, code);
9840           break;
9841
9842         case EXEC_WAIT:
9843           if (gfc_resolve_wait (code->ext.wait) == FAILURE)
9844             break;
9845
9846           resolve_branch (code->ext.wait->err, code);
9847           resolve_branch (code->ext.wait->end, code);
9848           resolve_branch (code->ext.wait->eor, code);
9849           break;
9850
9851         case EXEC_READ:
9852         case EXEC_WRITE:
9853           if (gfc_resolve_dt (code->ext.dt, &code->loc) == FAILURE)
9854             break;
9855
9856           resolve_branch (code->ext.dt->err, code);
9857           resolve_branch (code->ext.dt->end, code);
9858           resolve_branch (code->ext.dt->eor, code);
9859           break;
9860
9861         case EXEC_TRANSFER:
9862           resolve_transfer (code);
9863           break;
9864
9865         case EXEC_DO_CONCURRENT:
9866         case EXEC_FORALL:
9867           resolve_forall_iterators (code->ext.forall_iterator);
9868
9869           if (code->expr1 != NULL
9870               && (code->expr1->ts.type != BT_LOGICAL || code->expr1->rank))
9871             gfc_error ("FORALL mask clause at %L requires a scalar LOGICAL "
9872                        "expression", &code->expr1->where);
9873           break;
9874
9875         case EXEC_OMP_ATOMIC:
9876         case EXEC_OMP_BARRIER:
9877         case EXEC_OMP_CRITICAL:
9878         case EXEC_OMP_FLUSH:
9879         case EXEC_OMP_DO:
9880         case EXEC_OMP_MASTER:
9881         case EXEC_OMP_ORDERED:
9882         case EXEC_OMP_SECTIONS:
9883         case EXEC_OMP_SINGLE:
9884         case EXEC_OMP_TASKWAIT:
9885         case EXEC_OMP_TASKYIELD:
9886         case EXEC_OMP_WORKSHARE:
9887           gfc_resolve_omp_directive (code, ns);
9888           break;
9889
9890         case EXEC_OMP_PARALLEL:
9891         case EXEC_OMP_PARALLEL_DO:
9892         case EXEC_OMP_PARALLEL_SECTIONS:
9893         case EXEC_OMP_PARALLEL_WORKSHARE:
9894         case EXEC_OMP_TASK:
9895           omp_workshare_save = omp_workshare_flag;
9896           omp_workshare_flag = 0;
9897           gfc_resolve_omp_directive (code, ns);
9898           omp_workshare_flag = omp_workshare_save;
9899           break;
9900
9901         default:
9902           gfc_internal_error ("resolve_code(): Bad statement code");
9903         }
9904     }
9905
9906   cs_base = frame.prev;
9907 }
9908
9909
9910 /* Resolve initial values and make sure they are compatible with
9911    the variable.  */
9912
9913 static void
9914 resolve_values (gfc_symbol *sym)
9915 {
9916   gfc_try t;
9917
9918   if (sym->value == NULL)
9919     return;
9920
9921   if (sym->value->expr_type == EXPR_STRUCTURE)
9922     t= resolve_structure_cons (sym->value, 1);
9923   else 
9924     t = gfc_resolve_expr (sym->value);
9925
9926   if (t == FAILURE)
9927     return;
9928
9929   gfc_check_assign_symbol (sym, sym->value);
9930 }
9931
9932
9933 /* Verify the binding labels for common blocks that are BIND(C).  The label
9934    for a BIND(C) common block must be identical in all scoping units in which
9935    the common block is declared.  Further, the binding label can not collide
9936    with any other global entity in the program.  */
9937
9938 static void
9939 resolve_bind_c_comms (gfc_symtree *comm_block_tree)
9940 {
9941   if (comm_block_tree->n.common->is_bind_c == 1)
9942     {
9943       gfc_gsymbol *binding_label_gsym;
9944       gfc_gsymbol *comm_name_gsym;
9945       const char * bind_label = comm_block_tree->n.common->binding_label 
9946         ? comm_block_tree->n.common->binding_label : "";
9947
9948       /* See if a global symbol exists by the common block's name.  It may
9949          be NULL if the common block is use-associated.  */
9950       comm_name_gsym = gfc_find_gsymbol (gfc_gsym_root,
9951                                          comm_block_tree->n.common->name);
9952       if (comm_name_gsym != NULL && comm_name_gsym->type != GSYM_COMMON)
9953         gfc_error ("Binding label '%s' for common block '%s' at %L collides "
9954                    "with the global entity '%s' at %L",
9955                    bind_label,
9956                    comm_block_tree->n.common->name,
9957                    &(comm_block_tree->n.common->where),
9958                    comm_name_gsym->name, &(comm_name_gsym->where));
9959       else if (comm_name_gsym != NULL
9960                && strcmp (comm_name_gsym->name,
9961                           comm_block_tree->n.common->name) == 0)
9962         {
9963           /* TODO: Need to make sure the fields of gfc_gsymbol are initialized
9964              as expected.  */
9965           if (comm_name_gsym->binding_label == NULL)
9966             /* No binding label for common block stored yet; save this one.  */
9967             comm_name_gsym->binding_label = bind_label;
9968           else if (strcmp (comm_name_gsym->binding_label, bind_label) != 0)
9969               {
9970                 /* Common block names match but binding labels do not.  */
9971                 gfc_error ("Binding label '%s' for common block '%s' at %L "
9972                            "does not match the binding label '%s' for common "
9973                            "block '%s' at %L",
9974                            bind_label,
9975                            comm_block_tree->n.common->name,
9976                            &(comm_block_tree->n.common->where),
9977                            comm_name_gsym->binding_label,
9978                            comm_name_gsym->name,
9979                            &(comm_name_gsym->where));
9980                 return;
9981               }
9982         }
9983
9984       /* There is no binding label (NAME="") so we have nothing further to
9985          check and nothing to add as a global symbol for the label.  */
9986       if (!comm_block_tree->n.common->binding_label)
9987         return;
9988       
9989       binding_label_gsym =
9990         gfc_find_gsymbol (gfc_gsym_root,
9991                           comm_block_tree->n.common->binding_label);
9992       if (binding_label_gsym == NULL)
9993         {
9994           /* Need to make a global symbol for the binding label to prevent
9995              it from colliding with another.  */
9996           binding_label_gsym =
9997             gfc_get_gsymbol (comm_block_tree->n.common->binding_label);
9998           binding_label_gsym->sym_name = comm_block_tree->n.common->name;
9999           binding_label_gsym->type = GSYM_COMMON;
10000         }
10001       else
10002         {
10003           /* If comm_name_gsym is NULL, the name common block is use
10004              associated and the name could be colliding.  */
10005           if (binding_label_gsym->type != GSYM_COMMON)
10006             gfc_error ("Binding label '%s' for common block '%s' at %L "
10007                        "collides with the global entity '%s' at %L",
10008                        comm_block_tree->n.common->binding_label,
10009                        comm_block_tree->n.common->name,
10010                        &(comm_block_tree->n.common->where),
10011                        binding_label_gsym->name,
10012                        &(binding_label_gsym->where));
10013           else if (comm_name_gsym != NULL
10014                    && (strcmp (binding_label_gsym->name,
10015                                comm_name_gsym->binding_label) != 0)
10016                    && (strcmp (binding_label_gsym->sym_name,
10017                                comm_name_gsym->name) != 0))
10018             gfc_error ("Binding label '%s' for common block '%s' at %L "
10019                        "collides with global entity '%s' at %L",
10020                        binding_label_gsym->name, binding_label_gsym->sym_name,
10021                        &(comm_block_tree->n.common->where),
10022                        comm_name_gsym->name, &(comm_name_gsym->where));
10023         }
10024     }
10025   
10026   return;
10027 }
10028
10029
10030 /* Verify any BIND(C) derived types in the namespace so we can report errors
10031    for them once, rather than for each variable declared of that type.  */
10032
10033 static void
10034 resolve_bind_c_derived_types (gfc_symbol *derived_sym)
10035 {
10036   if (derived_sym != NULL && derived_sym->attr.flavor == FL_DERIVED
10037       && derived_sym->attr.is_bind_c == 1)
10038     verify_bind_c_derived_type (derived_sym);
10039   
10040   return;
10041 }
10042
10043
10044 /* Verify that any binding labels used in a given namespace do not collide 
10045    with the names or binding labels of any global symbols.  */
10046
10047 static void
10048 gfc_verify_binding_labels (gfc_symbol *sym)
10049 {
10050   int has_error = 0;
10051   
10052   if (sym != NULL && sym->attr.is_bind_c && sym->attr.is_iso_c == 0 
10053       && sym->attr.flavor != FL_DERIVED && sym->binding_label)
10054     {
10055       gfc_gsymbol *bind_c_sym;
10056
10057       bind_c_sym = gfc_find_gsymbol (gfc_gsym_root, sym->binding_label);
10058       if (bind_c_sym != NULL 
10059           && strcmp (bind_c_sym->name, sym->binding_label) == 0)
10060         {
10061           if (sym->attr.if_source == IFSRC_DECL 
10062               && (bind_c_sym->type != GSYM_SUBROUTINE 
10063                   && bind_c_sym->type != GSYM_FUNCTION) 
10064               && ((sym->attr.contained == 1 
10065                    && strcmp (bind_c_sym->sym_name, sym->name) != 0) 
10066                   || (sym->attr.use_assoc == 1 
10067                       && (strcmp (bind_c_sym->mod_name, sym->module) != 0))))
10068             {
10069               /* Make sure global procedures don't collide with anything.  */
10070               gfc_error ("Binding label '%s' at %L collides with the global "
10071                          "entity '%s' at %L", sym->binding_label,
10072                          &(sym->declared_at), bind_c_sym->name,
10073                          &(bind_c_sym->where));
10074               has_error = 1;
10075             }
10076           else if (sym->attr.contained == 0 
10077                    && (sym->attr.if_source == IFSRC_IFBODY 
10078                        && sym->attr.flavor == FL_PROCEDURE) 
10079                    && (bind_c_sym->sym_name != NULL 
10080                        && strcmp (bind_c_sym->sym_name, sym->name) != 0))
10081             {
10082               /* Make sure procedures in interface bodies don't collide.  */
10083               gfc_error ("Binding label '%s' in interface body at %L collides "
10084                          "with the global entity '%s' at %L",
10085                          sym->binding_label,
10086                          &(sym->declared_at), bind_c_sym->name,
10087                          &(bind_c_sym->where));
10088               has_error = 1;
10089             }
10090           else if (sym->attr.contained == 0 
10091                    && sym->attr.if_source == IFSRC_UNKNOWN)
10092             if ((sym->attr.use_assoc && bind_c_sym->mod_name
10093                  && strcmp (bind_c_sym->mod_name, sym->module) != 0) 
10094                 || sym->attr.use_assoc == 0)
10095               {
10096                 gfc_error ("Binding label '%s' at %L collides with global "
10097                            "entity '%s' at %L", sym->binding_label,
10098                            &(sym->declared_at), bind_c_sym->name,
10099                            &(bind_c_sym->where));
10100                 has_error = 1;
10101               }
10102
10103           if (has_error != 0)
10104             /* Clear the binding label to prevent checking multiple times.  */
10105             sym->binding_label = NULL;
10106         }
10107       else if (bind_c_sym == NULL)
10108         {
10109           bind_c_sym = gfc_get_gsymbol (sym->binding_label);
10110           bind_c_sym->where = sym->declared_at;
10111           bind_c_sym->sym_name = sym->name;
10112
10113           if (sym->attr.use_assoc == 1)
10114             bind_c_sym->mod_name = sym->module;
10115           else
10116             if (sym->ns->proc_name != NULL)
10117               bind_c_sym->mod_name = sym->ns->proc_name->name;
10118
10119           if (sym->attr.contained == 0)
10120             {
10121               if (sym->attr.subroutine)
10122                 bind_c_sym->type = GSYM_SUBROUTINE;
10123               else if (sym->attr.function)
10124                 bind_c_sym->type = GSYM_FUNCTION;
10125             }
10126         }
10127     }
10128   return;
10129 }
10130
10131
10132 /* Resolve an index expression.  */
10133
10134 static gfc_try
10135 resolve_index_expr (gfc_expr *e)
10136 {
10137   if (gfc_resolve_expr (e) == FAILURE)
10138     return FAILURE;
10139
10140   if (gfc_simplify_expr (e, 0) == FAILURE)
10141     return FAILURE;
10142
10143   if (gfc_specification_expr (e) == FAILURE)
10144     return FAILURE;
10145
10146   return SUCCESS;
10147 }
10148
10149
10150 /* Resolve a charlen structure.  */
10151
10152 static gfc_try
10153 resolve_charlen (gfc_charlen *cl)
10154 {
10155   int i, k;
10156
10157   if (cl->resolved)
10158     return SUCCESS;
10159
10160   cl->resolved = 1;
10161
10162
10163   if (cl->length_from_typespec)
10164     {
10165       if (gfc_resolve_expr (cl->length) == FAILURE)
10166         return FAILURE;
10167
10168       if (gfc_simplify_expr (cl->length, 0) == FAILURE)
10169         return FAILURE;
10170     }
10171   else
10172     {
10173       specification_expr = 1;
10174
10175       if (resolve_index_expr (cl->length) == FAILURE)
10176         {
10177           specification_expr = 0;
10178           return FAILURE;
10179         }
10180     }
10181
10182   /* "If the character length parameter value evaluates to a negative
10183      value, the length of character entities declared is zero."  */
10184   if (cl->length && !gfc_extract_int (cl->length, &i) && i < 0)
10185     {
10186       if (gfc_option.warn_surprising)
10187         gfc_warning_now ("CHARACTER variable at %L has negative length %d,"
10188                          " the length has been set to zero",
10189                          &cl->length->where, i);
10190       gfc_replace_expr (cl->length,
10191                         gfc_get_int_expr (gfc_default_integer_kind, NULL, 0));
10192     }
10193
10194   /* Check that the character length is not too large.  */
10195   k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
10196   if (cl->length && cl->length->expr_type == EXPR_CONSTANT
10197       && cl->length->ts.type == BT_INTEGER
10198       && mpz_cmp (cl->length->value.integer, gfc_integer_kinds[k].huge) > 0)
10199     {
10200       gfc_error ("String length at %L is too large", &cl->length->where);
10201       return FAILURE;
10202     }
10203
10204   return SUCCESS;
10205 }
10206
10207
10208 /* Test for non-constant shape arrays.  */
10209
10210 static bool
10211 is_non_constant_shape_array (gfc_symbol *sym)
10212 {
10213   gfc_expr *e;
10214   int i;
10215   bool not_constant;
10216
10217   not_constant = false;
10218   if (sym->as != NULL)
10219     {
10220       /* Unfortunately, !gfc_is_compile_time_shape hits a legal case that
10221          has not been simplified; parameter array references.  Do the
10222          simplification now.  */
10223       for (i = 0; i < sym->as->rank + sym->as->corank; i++)
10224         {
10225           e = sym->as->lower[i];
10226           if (e && (resolve_index_expr (e) == FAILURE
10227                     || !gfc_is_constant_expr (e)))
10228             not_constant = true;
10229           e = sym->as->upper[i];
10230           if (e && (resolve_index_expr (e) == FAILURE
10231                     || !gfc_is_constant_expr (e)))
10232             not_constant = true;
10233         }
10234     }
10235   return not_constant;
10236 }
10237
10238 /* Given a symbol and an initialization expression, add code to initialize
10239    the symbol to the function entry.  */
10240 static void
10241 build_init_assign (gfc_symbol *sym, gfc_expr *init)
10242 {
10243   gfc_expr *lval;
10244   gfc_code *init_st;
10245   gfc_namespace *ns = sym->ns;
10246
10247   /* Search for the function namespace if this is a contained
10248      function without an explicit result.  */
10249   if (sym->attr.function && sym == sym->result
10250       && sym->name != sym->ns->proc_name->name)
10251     {
10252       ns = ns->contained;
10253       for (;ns; ns = ns->sibling)
10254         if (strcmp (ns->proc_name->name, sym->name) == 0)
10255           break;
10256     }
10257
10258   if (ns == NULL)
10259     {
10260       gfc_free_expr (init);
10261       return;
10262     }
10263
10264   /* Build an l-value expression for the result.  */
10265   lval = gfc_lval_expr_from_sym (sym);
10266
10267   /* Add the code at scope entry.  */
10268   init_st = gfc_get_code ();
10269   init_st->next = ns->code;
10270   ns->code = init_st;
10271
10272   /* Assign the default initializer to the l-value.  */
10273   init_st->loc = sym->declared_at;
10274   init_st->op = EXEC_INIT_ASSIGN;
10275   init_st->expr1 = lval;
10276   init_st->expr2 = init;
10277 }
10278
10279 /* Assign the default initializer to a derived type variable or result.  */
10280
10281 static void
10282 apply_default_init (gfc_symbol *sym)
10283 {
10284   gfc_expr *init = NULL;
10285
10286   if (sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
10287     return;
10288
10289   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived)
10290     init = gfc_default_initializer (&sym->ts);
10291
10292   if (init == NULL && sym->ts.type != BT_CLASS)
10293     return;
10294
10295   build_init_assign (sym, init);
10296   sym->attr.referenced = 1;
10297 }
10298
10299 /* Build an initializer for a local integer, real, complex, logical, or
10300    character variable, based on the command line flags finit-local-zero,
10301    finit-integer=, finit-real=, finit-logical=, and finit-runtime.  Returns 
10302    null if the symbol should not have a default initialization.  */
10303 static gfc_expr *
10304 build_default_init_expr (gfc_symbol *sym)
10305 {
10306   int char_len;
10307   gfc_expr *init_expr;
10308   int i;
10309
10310   /* These symbols should never have a default initialization.  */
10311   if (sym->attr.allocatable
10312       || sym->attr.external
10313       || sym->attr.dummy
10314       || sym->attr.pointer
10315       || sym->attr.in_equivalence
10316       || sym->attr.in_common
10317       || sym->attr.data
10318       || sym->module
10319       || sym->attr.cray_pointee
10320       || sym->attr.cray_pointer
10321       || sym->assoc)
10322     return NULL;
10323
10324   /* Now we'll try to build an initializer expression.  */
10325   init_expr = gfc_get_constant_expr (sym->ts.type, sym->ts.kind,
10326                                      &sym->declared_at);
10327
10328   /* We will only initialize integers, reals, complex, logicals, and
10329      characters, and only if the corresponding command-line flags
10330      were set.  Otherwise, we free init_expr and return null.  */
10331   switch (sym->ts.type)
10332     {    
10333     case BT_INTEGER:
10334       if (gfc_option.flag_init_integer != GFC_INIT_INTEGER_OFF)
10335         mpz_set_si (init_expr->value.integer, 
10336                          gfc_option.flag_init_integer_value);
10337       else
10338         {
10339           gfc_free_expr (init_expr);
10340           init_expr = NULL;
10341         }
10342       break;
10343
10344     case BT_REAL:
10345       switch (gfc_option.flag_init_real)
10346         {
10347         case GFC_INIT_REAL_SNAN:
10348           init_expr->is_snan = 1;
10349           /* Fall through.  */
10350         case GFC_INIT_REAL_NAN:
10351           mpfr_set_nan (init_expr->value.real);
10352           break;
10353
10354         case GFC_INIT_REAL_INF:
10355           mpfr_set_inf (init_expr->value.real, 1);
10356           break;
10357
10358         case GFC_INIT_REAL_NEG_INF:
10359           mpfr_set_inf (init_expr->value.real, -1);
10360           break;
10361
10362         case GFC_INIT_REAL_ZERO:
10363           mpfr_set_ui (init_expr->value.real, 0.0, GFC_RND_MODE);
10364           break;
10365
10366         default:
10367           gfc_free_expr (init_expr);
10368           init_expr = NULL;
10369           break;
10370         }
10371       break;
10372           
10373     case BT_COMPLEX:
10374       switch (gfc_option.flag_init_real)
10375         {
10376         case GFC_INIT_REAL_SNAN:
10377           init_expr->is_snan = 1;
10378           /* Fall through.  */
10379         case GFC_INIT_REAL_NAN:
10380           mpfr_set_nan (mpc_realref (init_expr->value.complex));
10381           mpfr_set_nan (mpc_imagref (init_expr->value.complex));
10382           break;
10383
10384         case GFC_INIT_REAL_INF:
10385           mpfr_set_inf (mpc_realref (init_expr->value.complex), 1);
10386           mpfr_set_inf (mpc_imagref (init_expr->value.complex), 1);
10387           break;
10388
10389         case GFC_INIT_REAL_NEG_INF:
10390           mpfr_set_inf (mpc_realref (init_expr->value.complex), -1);
10391           mpfr_set_inf (mpc_imagref (init_expr->value.complex), -1);
10392           break;
10393
10394         case GFC_INIT_REAL_ZERO:
10395           mpc_set_ui (init_expr->value.complex, 0, GFC_MPC_RND_MODE);
10396           break;
10397
10398         default:
10399           gfc_free_expr (init_expr);
10400           init_expr = NULL;
10401           break;
10402         }
10403       break;
10404           
10405     case BT_LOGICAL:
10406       if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_FALSE)
10407         init_expr->value.logical = 0;
10408       else if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_TRUE)
10409         init_expr->value.logical = 1;
10410       else
10411         {
10412           gfc_free_expr (init_expr);
10413           init_expr = NULL;
10414         }
10415       break;
10416           
10417     case BT_CHARACTER:
10418       /* For characters, the length must be constant in order to 
10419          create a default initializer.  */
10420       if (gfc_option.flag_init_character == GFC_INIT_CHARACTER_ON
10421           && sym->ts.u.cl->length
10422           && sym->ts.u.cl->length->expr_type == EXPR_CONSTANT)
10423         {
10424           char_len = mpz_get_si (sym->ts.u.cl->length->value.integer);
10425           init_expr->value.character.length = char_len;
10426           init_expr->value.character.string = gfc_get_wide_string (char_len+1);
10427           for (i = 0; i < char_len; i++)
10428             init_expr->value.character.string[i]
10429               = (unsigned char) gfc_option.flag_init_character_value;
10430         }
10431       else
10432         {
10433           gfc_free_expr (init_expr);
10434           init_expr = NULL;
10435         }
10436       if (!init_expr && gfc_option.flag_init_character == GFC_INIT_CHARACTER_ON
10437           && sym->ts.u.cl->length)
10438         {
10439           gfc_actual_arglist *arg;
10440           init_expr = gfc_get_expr ();
10441           init_expr->where = sym->declared_at;
10442           init_expr->ts = sym->ts;
10443           init_expr->expr_type = EXPR_FUNCTION;
10444           init_expr->value.function.isym =
10445                 gfc_intrinsic_function_by_id (GFC_ISYM_REPEAT);
10446           init_expr->value.function.name = "repeat";
10447           arg = gfc_get_actual_arglist ();
10448           arg->expr = gfc_get_character_expr (sym->ts.kind, &sym->declared_at,
10449                                               NULL, 1);
10450           arg->expr->value.character.string[0]
10451                 = gfc_option.flag_init_character_value;
10452           arg->next = gfc_get_actual_arglist ();
10453           arg->next->expr = gfc_copy_expr (sym->ts.u.cl->length);
10454           init_expr->value.function.actual = arg;
10455         }
10456       break;
10457           
10458     default:
10459      gfc_free_expr (init_expr);
10460      init_expr = NULL;
10461     }
10462   return init_expr;
10463 }
10464
10465 /* Add an initialization expression to a local variable.  */
10466 static void
10467 apply_default_init_local (gfc_symbol *sym)
10468 {
10469   gfc_expr *init = NULL;
10470
10471   /* The symbol should be a variable or a function return value.  */
10472   if ((sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
10473       || (sym->attr.function && sym->result != sym))
10474     return;
10475
10476   /* Try to build the initializer expression.  If we can't initialize
10477      this symbol, then init will be NULL.  */
10478   init = build_default_init_expr (sym);
10479   if (init == NULL)
10480     return;
10481
10482   /* For saved variables, we don't want to add an initializer at function
10483      entry, so we just add a static initializer. Note that automatic variables
10484      are stack allocated even with -fno-automatic.  */
10485   if (sym->attr.save || sym->ns->save_all 
10486       || (gfc_option.flag_max_stack_var_size == 0
10487           && (!sym->attr.dimension || !is_non_constant_shape_array (sym))))
10488     {
10489       /* Don't clobber an existing initializer!  */
10490       gcc_assert (sym->value == NULL);
10491       sym->value = init;
10492       return;
10493     }
10494
10495   build_init_assign (sym, init);
10496 }
10497
10498
10499 /* Resolution of common features of flavors variable and procedure.  */
10500
10501 static gfc_try
10502 resolve_fl_var_and_proc (gfc_symbol *sym, int mp_flag)
10503 {
10504   gfc_array_spec *as;
10505
10506   /* Avoid double diagnostics for function result symbols.  */
10507   if ((sym->result || sym->attr.result) && !sym->attr.dummy
10508       && (sym->ns != gfc_current_ns))
10509     return SUCCESS;
10510
10511   if (sym->ts.type == BT_CLASS && sym->attr.class_ok)
10512     as = CLASS_DATA (sym)->as;
10513   else
10514     as = sym->as;
10515
10516   /* Constraints on deferred shape variable.  */
10517   if (as == NULL || as->type != AS_DEFERRED)
10518     {
10519       bool pointer, allocatable, dimension;
10520
10521       if (sym->ts.type == BT_CLASS && sym->attr.class_ok)
10522         {
10523           pointer = CLASS_DATA (sym)->attr.class_pointer;
10524           allocatable = CLASS_DATA (sym)->attr.allocatable;
10525           dimension = CLASS_DATA (sym)->attr.dimension;
10526         }
10527       else
10528         {
10529           pointer = sym->attr.pointer;
10530           allocatable = sym->attr.allocatable;
10531           dimension = sym->attr.dimension;
10532         }
10533
10534       if (allocatable)
10535         {
10536           if (dimension && as->type != AS_ASSUMED_RANK)
10537             {
10538               gfc_error ("Allocatable array '%s' at %L must have a deferred "
10539                          "shape or assumed rank", sym->name, &sym->declared_at);
10540               return FAILURE;
10541             }
10542           else if (gfc_notify_std (GFC_STD_F2003, "Scalar object "
10543                                    "'%s' at %L may not be ALLOCATABLE",
10544                                    sym->name, &sym->declared_at) == FAILURE)
10545             return FAILURE;
10546         }
10547
10548       if (pointer && dimension && as->type != AS_ASSUMED_RANK)
10549         {
10550           gfc_error ("Array pointer '%s' at %L must have a deferred shape or "
10551                      "assumed rank", sym->name, &sym->declared_at);
10552           return FAILURE;
10553         }
10554     }
10555   else
10556     {
10557       if (!mp_flag && !sym->attr.allocatable && !sym->attr.pointer
10558           && sym->ts.type != BT_CLASS && !sym->assoc)
10559         {
10560           gfc_error ("Array '%s' at %L cannot have a deferred shape",
10561                      sym->name, &sym->declared_at);
10562           return FAILURE;
10563          }
10564     }
10565
10566   /* Constraints on polymorphic variables.  */
10567   if (sym->ts.type == BT_CLASS && !(sym->result && sym->result != sym))
10568     {
10569       /* F03:C502.  */
10570       if (sym->attr.class_ok
10571           && !gfc_type_is_extensible (CLASS_DATA (sym)->ts.u.derived))
10572         {
10573           gfc_error ("Type '%s' of CLASS variable '%s' at %L is not extensible",
10574                      CLASS_DATA (sym)->ts.u.derived->name, sym->name,
10575                      &sym->declared_at);
10576           return FAILURE;
10577         }
10578
10579       /* F03:C509.  */
10580       /* Assume that use associated symbols were checked in the module ns.
10581          Class-variables that are associate-names are also something special
10582          and excepted from the test.  */
10583       if (!sym->attr.class_ok && !sym->attr.use_assoc && !sym->assoc)
10584         {
10585           gfc_error ("CLASS variable '%s' at %L must be dummy, allocatable "
10586                      "or pointer", sym->name, &sym->declared_at);
10587           return FAILURE;
10588         }
10589     }
10590     
10591   return SUCCESS;
10592 }
10593
10594
10595 /* Additional checks for symbols with flavor variable and derived
10596    type.  To be called from resolve_fl_variable.  */
10597
10598 static gfc_try
10599 resolve_fl_variable_derived (gfc_symbol *sym, int no_init_flag)
10600 {
10601   gcc_assert (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS);
10602
10603   /* Check to see if a derived type is blocked from being host
10604      associated by the presence of another class I symbol in the same
10605      namespace.  14.6.1.3 of the standard and the discussion on
10606      comp.lang.fortran.  */
10607   if (sym->ns != sym->ts.u.derived->ns
10608       && sym->ns->proc_name->attr.if_source != IFSRC_IFBODY)
10609     {
10610       gfc_symbol *s;
10611       gfc_find_symbol (sym->ts.u.derived->name, sym->ns, 0, &s);
10612       if (s && s->attr.generic)
10613         s = gfc_find_dt_in_generic (s);
10614       if (s && s->attr.flavor != FL_DERIVED)
10615         {
10616           gfc_error ("The type '%s' cannot be host associated at %L "
10617                      "because it is blocked by an incompatible object "
10618                      "of the same name declared at %L",
10619                      sym->ts.u.derived->name, &sym->declared_at,
10620                      &s->declared_at);
10621           return FAILURE;
10622         }
10623     }
10624
10625   /* 4th constraint in section 11.3: "If an object of a type for which
10626      component-initialization is specified (R429) appears in the
10627      specification-part of a module and does not have the ALLOCATABLE
10628      or POINTER attribute, the object shall have the SAVE attribute."
10629
10630      The check for initializers is performed with
10631      gfc_has_default_initializer because gfc_default_initializer generates
10632      a hidden default for allocatable components.  */
10633   if (!(sym->value || no_init_flag) && sym->ns->proc_name
10634       && sym->ns->proc_name->attr.flavor == FL_MODULE
10635       && !sym->ns->save_all && !sym->attr.save
10636       && !sym->attr.pointer && !sym->attr.allocatable
10637       && gfc_has_default_initializer (sym->ts.u.derived)
10638       && gfc_notify_std (GFC_STD_F2008, "Implied SAVE for "
10639                          "module variable '%s' at %L, needed due to "
10640                          "the default initialization", sym->name,
10641                          &sym->declared_at) == FAILURE)
10642     return FAILURE;
10643
10644   /* Assign default initializer.  */
10645   if (!(sym->value || sym->attr.pointer || sym->attr.allocatable)
10646       && (!no_init_flag || sym->attr.intent == INTENT_OUT))
10647     {
10648       sym->value = gfc_default_initializer (&sym->ts);
10649     }
10650
10651   return SUCCESS;
10652 }
10653
10654
10655 /* Resolve symbols with flavor variable.  */
10656
10657 static gfc_try
10658 resolve_fl_variable (gfc_symbol *sym, int mp_flag)
10659 {
10660   int no_init_flag, automatic_flag;
10661   gfc_expr *e;
10662   const char *auto_save_msg;
10663
10664   auto_save_msg = "Automatic object '%s' at %L cannot have the "
10665                   "SAVE attribute";
10666
10667   if (resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
10668     return FAILURE;
10669
10670   /* Set this flag to check that variables are parameters of all entries.
10671      This check is effected by the call to gfc_resolve_expr through
10672      is_non_constant_shape_array.  */
10673   specification_expr = 1;
10674
10675   if (sym->ns->proc_name
10676       && (sym->ns->proc_name->attr.flavor == FL_MODULE
10677           || sym->ns->proc_name->attr.is_main_program)
10678       && !sym->attr.use_assoc
10679       && !sym->attr.allocatable
10680       && !sym->attr.pointer
10681       && is_non_constant_shape_array (sym))
10682     {
10683       /* The shape of a main program or module array needs to be
10684          constant.  */
10685       gfc_error ("The module or main program array '%s' at %L must "
10686                  "have constant shape", sym->name, &sym->declared_at);
10687       specification_expr = 0;
10688       return FAILURE;
10689     }
10690
10691   /* Constraints on deferred type parameter.  */
10692   if (sym->ts.deferred && !(sym->attr.pointer || sym->attr.allocatable))
10693     {
10694       gfc_error ("Entity '%s' at %L has a deferred type parameter and "
10695                  "requires either the pointer or allocatable attribute",
10696                      sym->name, &sym->declared_at);
10697       return FAILURE;
10698     }
10699
10700   if (sym->ts.type == BT_CHARACTER)
10701     {
10702       /* Make sure that character string variables with assumed length are
10703          dummy arguments.  */
10704       e = sym->ts.u.cl->length;
10705       if (e == NULL && !sym->attr.dummy && !sym->attr.result
10706           && !sym->ts.deferred)
10707         {
10708           gfc_error ("Entity with assumed character length at %L must be a "
10709                      "dummy argument or a PARAMETER", &sym->declared_at);
10710           return FAILURE;
10711         }
10712
10713       if (e && sym->attr.save == SAVE_EXPLICIT && !gfc_is_constant_expr (e))
10714         {
10715           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
10716           return FAILURE;
10717         }
10718
10719       if (!gfc_is_constant_expr (e)
10720           && !(e->expr_type == EXPR_VARIABLE
10721                && e->symtree->n.sym->attr.flavor == FL_PARAMETER))
10722         {
10723           if (!sym->attr.use_assoc && sym->ns->proc_name
10724               && (sym->ns->proc_name->attr.flavor == FL_MODULE
10725                   || sym->ns->proc_name->attr.is_main_program))
10726             {
10727               gfc_error ("'%s' at %L must have constant character length "
10728                         "in this context", sym->name, &sym->declared_at);
10729               return FAILURE;
10730             }
10731           if (sym->attr.in_common)
10732             {
10733               gfc_error ("COMMON variable '%s' at %L must have constant "
10734                          "character length", sym->name, &sym->declared_at);
10735               return FAILURE;
10736             }
10737         }
10738     }
10739
10740   if (sym->value == NULL && sym->attr.referenced)
10741     apply_default_init_local (sym); /* Try to apply a default initialization.  */
10742
10743   /* Determine if the symbol may not have an initializer.  */
10744   no_init_flag = automatic_flag = 0;
10745   if (sym->attr.allocatable || sym->attr.external || sym->attr.dummy
10746       || sym->attr.intrinsic || sym->attr.result)
10747     no_init_flag = 1;
10748   else if ((sym->attr.dimension || sym->attr.codimension) && !sym->attr.pointer
10749            && is_non_constant_shape_array (sym))
10750     {
10751       no_init_flag = automatic_flag = 1;
10752
10753       /* Also, they must not have the SAVE attribute.
10754          SAVE_IMPLICIT is checked below.  */
10755       if (sym->as && sym->attr.codimension)
10756         {
10757           int corank = sym->as->corank;
10758           sym->as->corank = 0;
10759           no_init_flag = automatic_flag = is_non_constant_shape_array (sym);
10760           sym->as->corank = corank;
10761         }
10762       if (automatic_flag && sym->attr.save == SAVE_EXPLICIT)
10763         {
10764           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
10765           return FAILURE;
10766         }
10767     }
10768
10769   /* Ensure that any initializer is simplified.  */
10770   if (sym->value)
10771     gfc_simplify_expr (sym->value, 1);
10772
10773   /* Reject illegal initializers.  */
10774   if (!sym->mark && sym->value)
10775     {
10776       if (sym->attr.allocatable || (sym->ts.type == BT_CLASS
10777                                     && CLASS_DATA (sym)->attr.allocatable))
10778         gfc_error ("Allocatable '%s' at %L cannot have an initializer",
10779                    sym->name, &sym->declared_at);
10780       else if (sym->attr.external)
10781         gfc_error ("External '%s' at %L cannot have an initializer",
10782                    sym->name, &sym->declared_at);
10783       else if (sym->attr.dummy
10784         && !(sym->ts.type == BT_DERIVED && sym->attr.intent == INTENT_OUT))
10785         gfc_error ("Dummy '%s' at %L cannot have an initializer",
10786                    sym->name, &sym->declared_at);
10787       else if (sym->attr.intrinsic)
10788         gfc_error ("Intrinsic '%s' at %L cannot have an initializer",
10789                    sym->name, &sym->declared_at);
10790       else if (sym->attr.result)
10791         gfc_error ("Function result '%s' at %L cannot have an initializer",
10792                    sym->name, &sym->declared_at);
10793       else if (automatic_flag)
10794         gfc_error ("Automatic array '%s' at %L cannot have an initializer",
10795                    sym->name, &sym->declared_at);
10796       else
10797         goto no_init_error;
10798       return FAILURE;
10799     }
10800
10801 no_init_error:
10802   if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
10803     return resolve_fl_variable_derived (sym, no_init_flag);
10804
10805   return SUCCESS;
10806 }
10807
10808
10809 /* Resolve a procedure.  */
10810
10811 static gfc_try
10812 resolve_fl_procedure (gfc_symbol *sym, int mp_flag)
10813 {
10814   gfc_formal_arglist *arg;
10815
10816   if (sym->attr.function
10817       && resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
10818     return FAILURE;
10819
10820   if (sym->ts.type == BT_CHARACTER)
10821     {
10822       gfc_charlen *cl = sym->ts.u.cl;
10823
10824       if (cl && cl->length && gfc_is_constant_expr (cl->length)
10825              && resolve_charlen (cl) == FAILURE)
10826         return FAILURE;
10827
10828       if ((!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
10829           && sym->attr.proc == PROC_ST_FUNCTION)
10830         {
10831           gfc_error ("Character-valued statement function '%s' at %L must "
10832                      "have constant length", sym->name, &sym->declared_at);
10833           return FAILURE;
10834         }
10835     }
10836
10837   /* Ensure that derived type for are not of a private type.  Internal
10838      module procedures are excluded by 2.2.3.3 - i.e., they are not
10839      externally accessible and can access all the objects accessible in
10840      the host.  */
10841   if (!(sym->ns->parent
10842         && sym->ns->parent->proc_name->attr.flavor == FL_MODULE)
10843       && gfc_check_symbol_access (sym))
10844     {
10845       gfc_interface *iface;
10846
10847       for (arg = sym->formal; arg; arg = arg->next)
10848         {
10849           if (arg->sym
10850               && arg->sym->ts.type == BT_DERIVED
10851               && !arg->sym->ts.u.derived->attr.use_assoc
10852               && !gfc_check_symbol_access (arg->sym->ts.u.derived)
10853               && gfc_notify_std (GFC_STD_F2003, "'%s' is of a "
10854                                  "PRIVATE type and cannot be a dummy argument"
10855                                  " of '%s', which is PUBLIC at %L",
10856                                  arg->sym->name, sym->name, &sym->declared_at)
10857                  == FAILURE)
10858             {
10859               /* Stop this message from recurring.  */
10860               arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
10861               return FAILURE;
10862             }
10863         }
10864
10865       /* PUBLIC interfaces may expose PRIVATE procedures that take types
10866          PRIVATE to the containing module.  */
10867       for (iface = sym->generic; iface; iface = iface->next)
10868         {
10869           for (arg = iface->sym->formal; arg; arg = arg->next)
10870             {
10871               if (arg->sym
10872                   && arg->sym->ts.type == BT_DERIVED
10873                   && !arg->sym->ts.u.derived->attr.use_assoc
10874                   && !gfc_check_symbol_access (arg->sym->ts.u.derived)
10875                   && gfc_notify_std (GFC_STD_F2003, "Procedure "
10876                                      "'%s' in PUBLIC interface '%s' at %L "
10877                                      "takes dummy arguments of '%s' which is "
10878                                      "PRIVATE", iface->sym->name, sym->name,
10879                                      &iface->sym->declared_at,
10880                                      gfc_typename (&arg->sym->ts)) == FAILURE)
10881                 {
10882                   /* Stop this message from recurring.  */
10883                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
10884                   return FAILURE;
10885                 }
10886              }
10887         }
10888
10889       /* PUBLIC interfaces may expose PRIVATE procedures that take types
10890          PRIVATE to the containing module.  */
10891       for (iface = sym->generic; iface; iface = iface->next)
10892         {
10893           for (arg = iface->sym->formal; arg; arg = arg->next)
10894             {
10895               if (arg->sym
10896                   && arg->sym->ts.type == BT_DERIVED
10897                   && !arg->sym->ts.u.derived->attr.use_assoc
10898                   && !gfc_check_symbol_access (arg->sym->ts.u.derived)
10899                   && gfc_notify_std (GFC_STD_F2003, "Procedure "
10900                                      "'%s' in PUBLIC interface '%s' at %L "
10901                                      "takes dummy arguments of '%s' which is "
10902                                      "PRIVATE", iface->sym->name, sym->name,
10903                                      &iface->sym->declared_at,
10904                                      gfc_typename (&arg->sym->ts)) == FAILURE)
10905                 {
10906                   /* Stop this message from recurring.  */
10907                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
10908                   return FAILURE;
10909                 }
10910              }
10911         }
10912     }
10913
10914   if (sym->attr.function && sym->value && sym->attr.proc != PROC_ST_FUNCTION
10915       && !sym->attr.proc_pointer)
10916     {
10917       gfc_error ("Function '%s' at %L cannot have an initializer",
10918                  sym->name, &sym->declared_at);
10919       return FAILURE;
10920     }
10921
10922   /* An external symbol may not have an initializer because it is taken to be
10923      a procedure. Exception: Procedure Pointers.  */
10924   if (sym->attr.external && sym->value && !sym->attr.proc_pointer)
10925     {
10926       gfc_error ("External object '%s' at %L may not have an initializer",
10927                  sym->name, &sym->declared_at);
10928       return FAILURE;
10929     }
10930
10931   /* An elemental function is required to return a scalar 12.7.1  */
10932   if (sym->attr.elemental && sym->attr.function && sym->as)
10933     {
10934       gfc_error ("ELEMENTAL function '%s' at %L must have a scalar "
10935                  "result", sym->name, &sym->declared_at);
10936       /* Reset so that the error only occurs once.  */
10937       sym->attr.elemental = 0;
10938       return FAILURE;
10939     }
10940
10941   if (sym->attr.proc == PROC_ST_FUNCTION
10942       && (sym->attr.allocatable || sym->attr.pointer))
10943     {
10944       gfc_error ("Statement function '%s' at %L may not have pointer or "
10945                  "allocatable attribute", sym->name, &sym->declared_at);
10946       return FAILURE;
10947     }
10948
10949   /* 5.1.1.5 of the Standard: A function name declared with an asterisk
10950      char-len-param shall not be array-valued, pointer-valued, recursive
10951      or pure.  ....snip... A character value of * may only be used in the
10952      following ways: (i) Dummy arg of procedure - dummy associates with
10953      actual length; (ii) To declare a named constant; or (iii) External
10954      function - but length must be declared in calling scoping unit.  */
10955   if (sym->attr.function
10956       && sym->ts.type == BT_CHARACTER && !sym->ts.deferred
10957       && sym->ts.u.cl && sym->ts.u.cl->length == NULL)
10958     {
10959       if ((sym->as && sym->as->rank) || (sym->attr.pointer)
10960           || (sym->attr.recursive) || (sym->attr.pure))
10961         {
10962           if (sym->as && sym->as->rank)
10963             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10964                        "array-valued", sym->name, &sym->declared_at);
10965
10966           if (sym->attr.pointer)
10967             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10968                        "pointer-valued", sym->name, &sym->declared_at);
10969
10970           if (sym->attr.pure)
10971             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10972                        "pure", sym->name, &sym->declared_at);
10973
10974           if (sym->attr.recursive)
10975             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10976                        "recursive", sym->name, &sym->declared_at);
10977
10978           return FAILURE;
10979         }
10980
10981       /* Appendix B.2 of the standard.  Contained functions give an
10982          error anyway.  Fixed-form is likely to be F77/legacy. Deferred
10983          character length is an F2003 feature.  */
10984       if (!sym->attr.contained
10985             && gfc_current_form != FORM_FIXED
10986             && !sym->ts.deferred)
10987         gfc_notify_std (GFC_STD_F95_OBS,
10988                         "CHARACTER(*) function '%s' at %L",
10989                         sym->name, &sym->declared_at);
10990     }
10991
10992   if (sym->attr.is_bind_c && sym->attr.is_c_interop != 1)
10993     {
10994       gfc_formal_arglist *curr_arg;
10995       int has_non_interop_arg = 0;
10996
10997       if (verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
10998                              sym->common_block) == FAILURE)
10999         {
11000           /* Clear these to prevent looking at them again if there was an
11001              error.  */
11002           sym->attr.is_bind_c = 0;
11003           sym->attr.is_c_interop = 0;
11004           sym->ts.is_c_interop = 0;
11005         }
11006       else
11007         {
11008           /* So far, no errors have been found.  */
11009           sym->attr.is_c_interop = 1;
11010           sym->ts.is_c_interop = 1;
11011         }
11012       
11013       curr_arg = sym->formal;
11014       while (curr_arg != NULL)
11015         {
11016           /* Skip implicitly typed dummy args here.  */
11017           if (curr_arg->sym->attr.implicit_type == 0)
11018             if (gfc_verify_c_interop_param (curr_arg->sym) == FAILURE)
11019               /* If something is found to fail, record the fact so we
11020                  can mark the symbol for the procedure as not being
11021                  BIND(C) to try and prevent multiple errors being
11022                  reported.  */
11023               has_non_interop_arg = 1;
11024           
11025           curr_arg = curr_arg->next;
11026         }
11027
11028       /* See if any of the arguments were not interoperable and if so, clear
11029          the procedure symbol to prevent duplicate error messages.  */
11030       if (has_non_interop_arg != 0)
11031         {
11032           sym->attr.is_c_interop = 0;
11033           sym->ts.is_c_interop = 0;
11034           sym->attr.is_bind_c = 0;
11035         }
11036     }
11037   
11038   if (!sym->attr.proc_pointer)
11039     {
11040       if (sym->attr.save == SAVE_EXPLICIT)
11041         {
11042           gfc_error ("PROCEDURE attribute conflicts with SAVE attribute "
11043                      "in '%s' at %L", sym->name, &sym->declared_at);
11044           return FAILURE;
11045         }
11046       if (sym->attr.intent)
11047         {
11048           gfc_error ("PROCEDURE attribute conflicts with INTENT attribute "
11049                      "in '%s' at %L", sym->name, &sym->declared_at);
11050           return FAILURE;
11051         }
11052       if (sym->attr.subroutine && sym->attr.result)
11053         {
11054           gfc_error ("PROCEDURE attribute conflicts with RESULT attribute "
11055                      "in '%s' at %L", sym->name, &sym->declared_at);
11056           return FAILURE;
11057         }
11058       if (sym->attr.external && sym->attr.function
11059           && ((sym->attr.if_source == IFSRC_DECL && !sym->attr.procedure)
11060               || sym->attr.contained))
11061         {
11062           gfc_error ("EXTERNAL attribute conflicts with FUNCTION attribute "
11063                      "in '%s' at %L", sym->name, &sym->declared_at);
11064           return FAILURE;
11065         }
11066       if (strcmp ("ppr@", sym->name) == 0)
11067         {
11068           gfc_error ("Procedure pointer result '%s' at %L "
11069                      "is missing the pointer attribute",
11070                      sym->ns->proc_name->name, &sym->declared_at);
11071           return FAILURE;
11072         }
11073     }
11074
11075   return SUCCESS;
11076 }
11077
11078
11079 /* Resolve a list of finalizer procedures.  That is, after they have hopefully
11080    been defined and we now know their defined arguments, check that they fulfill
11081    the requirements of the standard for procedures used as finalizers.  */
11082
11083 static gfc_try
11084 gfc_resolve_finalizers (gfc_symbol* derived)
11085 {
11086   gfc_finalizer* list;
11087   gfc_finalizer** prev_link; /* For removing wrong entries from the list.  */
11088   gfc_try result = SUCCESS;
11089   bool seen_scalar = false;
11090
11091   if (!derived->f2k_derived || !derived->f2k_derived->finalizers)
11092     return SUCCESS;
11093
11094   /* Walk over the list of finalizer-procedures, check them, and if any one
11095      does not fit in with the standard's definition, print an error and remove
11096      it from the list.  */
11097   prev_link = &derived->f2k_derived->finalizers;
11098   for (list = derived->f2k_derived->finalizers; list; list = *prev_link)
11099     {
11100       gfc_symbol* arg;
11101       gfc_finalizer* i;
11102       int my_rank;
11103
11104       /* Skip this finalizer if we already resolved it.  */
11105       if (list->proc_tree)
11106         {
11107           prev_link = &(list->next);
11108           continue;
11109         }
11110
11111       /* Check this exists and is a SUBROUTINE.  */
11112       if (!list->proc_sym->attr.subroutine)
11113         {
11114           gfc_error ("FINAL procedure '%s' at %L is not a SUBROUTINE",
11115                      list->proc_sym->name, &list->where);
11116           goto error;
11117         }
11118
11119       /* We should have exactly one argument.  */
11120       if (!list->proc_sym->formal || list->proc_sym->formal->next)
11121         {
11122           gfc_error ("FINAL procedure at %L must have exactly one argument",
11123                      &list->where);
11124           goto error;
11125         }
11126       arg = list->proc_sym->formal->sym;
11127
11128       /* This argument must be of our type.  */
11129       if (arg->ts.type != BT_DERIVED || arg->ts.u.derived != derived)
11130         {
11131           gfc_error ("Argument of FINAL procedure at %L must be of type '%s'",
11132                      &arg->declared_at, derived->name);
11133           goto error;
11134         }
11135
11136       /* It must neither be a pointer nor allocatable nor optional.  */
11137       if (arg->attr.pointer)
11138         {
11139           gfc_error ("Argument of FINAL procedure at %L must not be a POINTER",
11140                      &arg->declared_at);
11141           goto error;
11142         }
11143       if (arg->attr.allocatable)
11144         {
11145           gfc_error ("Argument of FINAL procedure at %L must not be"
11146                      " ALLOCATABLE", &arg->declared_at);
11147           goto error;
11148         }
11149       if (arg->attr.optional)
11150         {
11151           gfc_error ("Argument of FINAL procedure at %L must not be OPTIONAL",
11152                      &arg->declared_at);
11153           goto error;
11154         }
11155
11156       /* It must not be INTENT(OUT).  */
11157       if (arg->attr.intent == INTENT_OUT)
11158         {
11159           gfc_error ("Argument of FINAL procedure at %L must not be"
11160                      " INTENT(OUT)", &arg->declared_at);
11161           goto error;
11162         }
11163
11164       /* Warn if the procedure is non-scalar and not assumed shape.  */
11165       if (gfc_option.warn_surprising && arg->as && arg->as->rank != 0
11166           && arg->as->type != AS_ASSUMED_SHAPE)
11167         gfc_warning ("Non-scalar FINAL procedure at %L should have assumed"
11168                      " shape argument", &arg->declared_at);
11169
11170       /* Check that it does not match in kind and rank with a FINAL procedure
11171          defined earlier.  To really loop over the *earlier* declarations,
11172          we need to walk the tail of the list as new ones were pushed at the
11173          front.  */
11174       /* TODO: Handle kind parameters once they are implemented.  */
11175       my_rank = (arg->as ? arg->as->rank : 0);
11176       for (i = list->next; i; i = i->next)
11177         {
11178           /* Argument list might be empty; that is an error signalled earlier,
11179              but we nevertheless continued resolving.  */
11180           if (i->proc_sym->formal)
11181             {
11182               gfc_symbol* i_arg = i->proc_sym->formal->sym;
11183               const int i_rank = (i_arg->as ? i_arg->as->rank : 0);
11184               if (i_rank == my_rank)
11185                 {
11186                   gfc_error ("FINAL procedure '%s' declared at %L has the same"
11187                              " rank (%d) as '%s'",
11188                              list->proc_sym->name, &list->where, my_rank, 
11189                              i->proc_sym->name);
11190                   goto error;
11191                 }
11192             }
11193         }
11194
11195         /* Is this the/a scalar finalizer procedure?  */
11196         if (!arg->as || arg->as->rank == 0)
11197           seen_scalar = true;
11198
11199         /* Find the symtree for this procedure.  */
11200         gcc_assert (!list->proc_tree);
11201         list->proc_tree = gfc_find_sym_in_symtree (list->proc_sym);
11202
11203         prev_link = &list->next;
11204         continue;
11205
11206         /* Remove wrong nodes immediately from the list so we don't risk any
11207            troubles in the future when they might fail later expectations.  */
11208 error:
11209         result = FAILURE;
11210         i = list;
11211         *prev_link = list->next;
11212         gfc_free_finalizer (i);
11213     }
11214
11215   /* Warn if we haven't seen a scalar finalizer procedure (but we know there
11216      were nodes in the list, must have been for arrays.  It is surely a good
11217      idea to have a scalar version there if there's something to finalize.  */
11218   if (gfc_option.warn_surprising && result == SUCCESS && !seen_scalar)
11219     gfc_warning ("Only array FINAL procedures declared for derived type '%s'"
11220                  " defined at %L, suggest also scalar one",
11221                  derived->name, &derived->declared_at);
11222
11223   /* TODO:  Remove this error when finalization is finished.  */
11224   gfc_error ("Finalization at %L is not yet implemented",
11225              &derived->declared_at);
11226
11227   gfc_find_derived_vtab (derived);
11228   return result;
11229 }
11230
11231
11232 /* Check if two GENERIC targets are ambiguous and emit an error is they are.  */
11233
11234 static gfc_try
11235 check_generic_tbp_ambiguity (gfc_tbp_generic* t1, gfc_tbp_generic* t2,
11236                              const char* generic_name, locus where)
11237 {
11238   gfc_symbol *sym1, *sym2;
11239   const char *pass1, *pass2;
11240
11241   gcc_assert (t1->specific && t2->specific);
11242   gcc_assert (!t1->specific->is_generic);
11243   gcc_assert (!t2->specific->is_generic);
11244   gcc_assert (t1->is_operator == t2->is_operator);
11245
11246   sym1 = t1->specific->u.specific->n.sym;
11247   sym2 = t2->specific->u.specific->n.sym;
11248
11249   if (sym1 == sym2)
11250     return SUCCESS;
11251
11252   /* Both must be SUBROUTINEs or both must be FUNCTIONs.  */
11253   if (sym1->attr.subroutine != sym2->attr.subroutine
11254       || sym1->attr.function != sym2->attr.function)
11255     {
11256       gfc_error ("'%s' and '%s' can't be mixed FUNCTION/SUBROUTINE for"
11257                  " GENERIC '%s' at %L",
11258                  sym1->name, sym2->name, generic_name, &where);
11259       return FAILURE;
11260     }
11261
11262   /* Compare the interfaces.  */
11263   if (t1->specific->nopass)
11264     pass1 = NULL;
11265   else if (t1->specific->pass_arg)
11266     pass1 = t1->specific->pass_arg;
11267   else
11268     pass1 = t1->specific->u.specific->n.sym->formal->sym->name;
11269   if (t2->specific->nopass)
11270     pass2 = NULL;
11271   else if (t2->specific->pass_arg)
11272     pass2 = t2->specific->pass_arg;
11273   else
11274     pass2 = t2->specific->u.specific->n.sym->formal->sym->name;  
11275   if (gfc_compare_interfaces (sym1, sym2, sym2->name, !t1->is_operator, 0,
11276                               NULL, 0, pass1, pass2))
11277     {
11278       gfc_error ("'%s' and '%s' for GENERIC '%s' at %L are ambiguous",
11279                  sym1->name, sym2->name, generic_name, &where);
11280       return FAILURE;
11281     }
11282
11283   return SUCCESS;
11284 }
11285
11286
11287 /* Worker function for resolving a generic procedure binding; this is used to
11288    resolve GENERIC as well as user and intrinsic OPERATOR typebound procedures.
11289
11290    The difference between those cases is finding possible inherited bindings
11291    that are overridden, as one has to look for them in tb_sym_root,
11292    tb_uop_root or tb_op, respectively.  Thus the caller must already find
11293    the super-type and set p->overridden correctly.  */
11294
11295 static gfc_try
11296 resolve_tb_generic_targets (gfc_symbol* super_type,
11297                             gfc_typebound_proc* p, const char* name)
11298 {
11299   gfc_tbp_generic* target;
11300   gfc_symtree* first_target;
11301   gfc_symtree* inherited;
11302
11303   gcc_assert (p && p->is_generic);
11304
11305   /* Try to find the specific bindings for the symtrees in our target-list.  */
11306   gcc_assert (p->u.generic);
11307   for (target = p->u.generic; target; target = target->next)
11308     if (!target->specific)
11309       {
11310         gfc_typebound_proc* overridden_tbp;
11311         gfc_tbp_generic* g;
11312         const char* target_name;
11313
11314         target_name = target->specific_st->name;
11315
11316         /* Defined for this type directly.  */
11317         if (target->specific_st->n.tb && !target->specific_st->n.tb->error)
11318           {
11319             target->specific = target->specific_st->n.tb;
11320             goto specific_found;
11321           }
11322
11323         /* Look for an inherited specific binding.  */
11324         if (super_type)
11325           {
11326             inherited = gfc_find_typebound_proc (super_type, NULL, target_name,
11327                                                  true, NULL);
11328
11329             if (inherited)
11330               {
11331                 gcc_assert (inherited->n.tb);
11332                 target->specific = inherited->n.tb;
11333                 goto specific_found;
11334               }
11335           }
11336
11337         gfc_error ("Undefined specific binding '%s' as target of GENERIC '%s'"
11338                    " at %L", target_name, name, &p->where);
11339         return FAILURE;
11340
11341         /* Once we've found the specific binding, check it is not ambiguous with
11342            other specifics already found or inherited for the same GENERIC.  */
11343 specific_found:
11344         gcc_assert (target->specific);
11345
11346         /* This must really be a specific binding!  */
11347         if (target->specific->is_generic)
11348           {
11349             gfc_error ("GENERIC '%s' at %L must target a specific binding,"
11350                        " '%s' is GENERIC, too", name, &p->where, target_name);
11351             return FAILURE;
11352           }
11353
11354         /* Check those already resolved on this type directly.  */
11355         for (g = p->u.generic; g; g = g->next)
11356           if (g != target && g->specific
11357               && check_generic_tbp_ambiguity (target, g, name, p->where)
11358                   == FAILURE)
11359             return FAILURE;
11360
11361         /* Check for ambiguity with inherited specific targets.  */
11362         for (overridden_tbp = p->overridden; overridden_tbp;
11363              overridden_tbp = overridden_tbp->overridden)
11364           if (overridden_tbp->is_generic)
11365             {
11366               for (g = overridden_tbp->u.generic; g; g = g->next)
11367                 {
11368                   gcc_assert (g->specific);
11369                   if (check_generic_tbp_ambiguity (target, g,
11370                                                    name, p->where) == FAILURE)
11371                     return FAILURE;
11372                 }
11373             }
11374       }
11375
11376   /* If we attempt to "overwrite" a specific binding, this is an error.  */
11377   if (p->overridden && !p->overridden->is_generic)
11378     {
11379       gfc_error ("GENERIC '%s' at %L can't overwrite specific binding with"
11380                  " the same name", name, &p->where);
11381       return FAILURE;
11382     }
11383
11384   /* Take the SUBROUTINE/FUNCTION attributes of the first specific target, as
11385      all must have the same attributes here.  */
11386   first_target = p->u.generic->specific->u.specific;
11387   gcc_assert (first_target);
11388   p->subroutine = first_target->n.sym->attr.subroutine;
11389   p->function = first_target->n.sym->attr.function;
11390
11391   return SUCCESS;
11392 }
11393
11394
11395 /* Resolve a GENERIC procedure binding for a derived type.  */
11396
11397 static gfc_try
11398 resolve_typebound_generic (gfc_symbol* derived, gfc_symtree* st)
11399 {
11400   gfc_symbol* super_type;
11401
11402   /* Find the overridden binding if any.  */
11403   st->n.tb->overridden = NULL;
11404   super_type = gfc_get_derived_super_type (derived);
11405   if (super_type)
11406     {
11407       gfc_symtree* overridden;
11408       overridden = gfc_find_typebound_proc (super_type, NULL, st->name,
11409                                             true, NULL);
11410
11411       if (overridden && overridden->n.tb)
11412         st->n.tb->overridden = overridden->n.tb;
11413     }
11414
11415   /* Resolve using worker function.  */
11416   return resolve_tb_generic_targets (super_type, st->n.tb, st->name);
11417 }
11418
11419
11420 /* Retrieve the target-procedure of an operator binding and do some checks in
11421    common for intrinsic and user-defined type-bound operators.  */
11422
11423 static gfc_symbol*
11424 get_checked_tb_operator_target (gfc_tbp_generic* target, locus where)
11425 {
11426   gfc_symbol* target_proc;
11427
11428   gcc_assert (target->specific && !target->specific->is_generic);
11429   target_proc = target->specific->u.specific->n.sym;
11430   gcc_assert (target_proc);
11431
11432   /* F08:C468. All operator bindings must have a passed-object dummy argument.  */
11433   if (target->specific->nopass)
11434     {
11435       gfc_error ("Type-bound operator at %L can't be NOPASS", &where);
11436       return NULL;
11437     }
11438
11439   return target_proc;
11440 }
11441
11442
11443 /* Resolve a type-bound intrinsic operator.  */
11444
11445 static gfc_try
11446 resolve_typebound_intrinsic_op (gfc_symbol* derived, gfc_intrinsic_op op,
11447                                 gfc_typebound_proc* p)
11448 {
11449   gfc_symbol* super_type;
11450   gfc_tbp_generic* target;
11451   
11452   /* If there's already an error here, do nothing (but don't fail again).  */
11453   if (p->error)
11454     return SUCCESS;
11455
11456   /* Operators should always be GENERIC bindings.  */
11457   gcc_assert (p->is_generic);
11458
11459   /* Look for an overridden binding.  */
11460   super_type = gfc_get_derived_super_type (derived);
11461   if (super_type && super_type->f2k_derived)
11462     p->overridden = gfc_find_typebound_intrinsic_op (super_type, NULL,
11463                                                      op, true, NULL);
11464   else
11465     p->overridden = NULL;
11466
11467   /* Resolve general GENERIC properties using worker function.  */
11468   if (resolve_tb_generic_targets (super_type, p, gfc_op2string (op)) == FAILURE)
11469     goto error;
11470
11471   /* Check the targets to be procedures of correct interface.  */
11472   for (target = p->u.generic; target; target = target->next)
11473     {
11474       gfc_symbol* target_proc;
11475
11476       target_proc = get_checked_tb_operator_target (target, p->where);
11477       if (!target_proc)
11478         goto error;
11479
11480       if (!gfc_check_operator_interface (target_proc, op, p->where))
11481         goto error;
11482
11483       /* Add target to non-typebound operator list.  */
11484       if (!target->specific->deferred && !derived->attr.use_assoc
11485           && p->access != ACCESS_PRIVATE)
11486         {
11487           gfc_interface *head, *intr;
11488           if (gfc_check_new_interface (derived->ns->op[op], target_proc,
11489                                        p->where) == FAILURE)
11490             return FAILURE;
11491           head = derived->ns->op[op];
11492           intr = gfc_get_interface ();
11493           intr->sym = target_proc;
11494           intr->where = p->where;
11495           intr->next = head;
11496           derived->ns->op[op] = intr;
11497         }
11498     }
11499
11500   return SUCCESS;
11501
11502 error:
11503   p->error = 1;
11504   return FAILURE;
11505 }
11506
11507
11508 /* Resolve a type-bound user operator (tree-walker callback).  */
11509
11510 static gfc_symbol* resolve_bindings_derived;
11511 static gfc_try resolve_bindings_result;
11512
11513 static gfc_try check_uop_procedure (gfc_symbol* sym, locus where);
11514
11515 static void
11516 resolve_typebound_user_op (gfc_symtree* stree)
11517 {
11518   gfc_symbol* super_type;
11519   gfc_tbp_generic* target;
11520
11521   gcc_assert (stree && stree->n.tb);
11522
11523   if (stree->n.tb->error)
11524     return;
11525
11526   /* Operators should always be GENERIC bindings.  */
11527   gcc_assert (stree->n.tb->is_generic);
11528
11529   /* Find overridden procedure, if any.  */
11530   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
11531   if (super_type && super_type->f2k_derived)
11532     {
11533       gfc_symtree* overridden;
11534       overridden = gfc_find_typebound_user_op (super_type, NULL,
11535                                                stree->name, true, NULL);
11536
11537       if (overridden && overridden->n.tb)
11538         stree->n.tb->overridden = overridden->n.tb;
11539     }
11540   else
11541     stree->n.tb->overridden = NULL;
11542
11543   /* Resolve basically using worker function.  */
11544   if (resolve_tb_generic_targets (super_type, stree->n.tb, stree->name)
11545         == FAILURE)
11546     goto error;
11547
11548   /* Check the targets to be functions of correct interface.  */
11549   for (target = stree->n.tb->u.generic; target; target = target->next)
11550     {
11551       gfc_symbol* target_proc;
11552
11553       target_proc = get_checked_tb_operator_target (target, stree->n.tb->where);
11554       if (!target_proc)
11555         goto error;
11556
11557       if (check_uop_procedure (target_proc, stree->n.tb->where) == FAILURE)
11558         goto error;
11559     }
11560
11561   return;
11562
11563 error:
11564   resolve_bindings_result = FAILURE;
11565   stree->n.tb->error = 1;
11566 }
11567
11568
11569 /* Resolve the type-bound procedures for a derived type.  */
11570
11571 static void
11572 resolve_typebound_procedure (gfc_symtree* stree)
11573 {
11574   gfc_symbol* proc;
11575   locus where;
11576   gfc_symbol* me_arg;
11577   gfc_symbol* super_type;
11578   gfc_component* comp;
11579
11580   gcc_assert (stree);
11581
11582   /* Undefined specific symbol from GENERIC target definition.  */
11583   if (!stree->n.tb)
11584     return;
11585
11586   if (stree->n.tb->error)
11587     return;
11588
11589   /* If this is a GENERIC binding, use that routine.  */
11590   if (stree->n.tb->is_generic)
11591     {
11592       if (resolve_typebound_generic (resolve_bindings_derived, stree)
11593             == FAILURE)
11594         goto error;
11595       return;
11596     }
11597
11598   /* Get the target-procedure to check it.  */
11599   gcc_assert (!stree->n.tb->is_generic);
11600   gcc_assert (stree->n.tb->u.specific);
11601   proc = stree->n.tb->u.specific->n.sym;
11602   where = stree->n.tb->where;
11603   proc->attr.public_used = 1;
11604
11605   /* Default access should already be resolved from the parser.  */
11606   gcc_assert (stree->n.tb->access != ACCESS_UNKNOWN);
11607
11608   if (stree->n.tb->deferred)
11609     {
11610       if (check_proc_interface (proc, &where) == FAILURE)
11611         goto error;
11612     }
11613   else
11614     {
11615       /* Check for F08:C465.  */
11616       if ((!proc->attr.subroutine && !proc->attr.function)
11617           || (proc->attr.proc != PROC_MODULE
11618               && proc->attr.if_source != IFSRC_IFBODY)
11619           || proc->attr.abstract)
11620         {
11621           gfc_error ("'%s' must be a module procedure or an external procedure with"
11622                     " an explicit interface at %L", proc->name, &where);
11623           goto error;
11624         }
11625     }
11626
11627   stree->n.tb->subroutine = proc->attr.subroutine;
11628   stree->n.tb->function = proc->attr.function;
11629
11630   /* Find the super-type of the current derived type.  We could do this once and
11631      store in a global if speed is needed, but as long as not I believe this is
11632      more readable and clearer.  */
11633   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
11634
11635   /* If PASS, resolve and check arguments if not already resolved / loaded
11636      from a .mod file.  */
11637   if (!stree->n.tb->nopass && stree->n.tb->pass_arg_num == 0)
11638     {
11639       if (stree->n.tb->pass_arg)
11640         {
11641           gfc_formal_arglist* i;
11642
11643           /* If an explicit passing argument name is given, walk the arg-list
11644              and look for it.  */
11645
11646           me_arg = NULL;
11647           stree->n.tb->pass_arg_num = 1;
11648           for (i = proc->formal; i; i = i->next)
11649             {
11650               if (!strcmp (i->sym->name, stree->n.tb->pass_arg))
11651                 {
11652                   me_arg = i->sym;
11653                   break;
11654                 }
11655               ++stree->n.tb->pass_arg_num;
11656             }
11657
11658           if (!me_arg)
11659             {
11660               gfc_error ("Procedure '%s' with PASS(%s) at %L has no"
11661                          " argument '%s'",
11662                          proc->name, stree->n.tb->pass_arg, &where,
11663                          stree->n.tb->pass_arg);
11664               goto error;
11665             }
11666         }
11667       else
11668         {
11669           /* Otherwise, take the first one; there should in fact be at least
11670              one.  */
11671           stree->n.tb->pass_arg_num = 1;
11672           if (!proc->formal)
11673             {
11674               gfc_error ("Procedure '%s' with PASS at %L must have at"
11675                          " least one argument", proc->name, &where);
11676               goto error;
11677             }
11678           me_arg = proc->formal->sym;
11679         }
11680
11681       /* Now check that the argument-type matches and the passed-object
11682          dummy argument is generally fine.  */
11683
11684       gcc_assert (me_arg);
11685
11686       if (me_arg->ts.type != BT_CLASS)
11687         {
11688           gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
11689                      " at %L", proc->name, &where);
11690           goto error;
11691         }
11692
11693       if (CLASS_DATA (me_arg)->ts.u.derived
11694           != resolve_bindings_derived)
11695         {
11696           gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
11697                      " the derived-type '%s'", me_arg->name, proc->name,
11698                      me_arg->name, &where, resolve_bindings_derived->name);
11699           goto error;
11700         }
11701   
11702       gcc_assert (me_arg->ts.type == BT_CLASS);
11703       if (CLASS_DATA (me_arg)->as && CLASS_DATA (me_arg)->as->rank != 0)
11704         {
11705           gfc_error ("Passed-object dummy argument of '%s' at %L must be"
11706                      " scalar", proc->name, &where);
11707           goto error;
11708         }
11709       if (CLASS_DATA (me_arg)->attr.allocatable)
11710         {
11711           gfc_error ("Passed-object dummy argument of '%s' at %L must not"
11712                      " be ALLOCATABLE", proc->name, &where);
11713           goto error;
11714         }
11715       if (CLASS_DATA (me_arg)->attr.class_pointer)
11716         {
11717           gfc_error ("Passed-object dummy argument of '%s' at %L must not"
11718                      " be POINTER", proc->name, &where);
11719           goto error;
11720         }
11721     }
11722
11723   /* If we are extending some type, check that we don't override a procedure
11724      flagged NON_OVERRIDABLE.  */
11725   stree->n.tb->overridden = NULL;
11726   if (super_type)
11727     {
11728       gfc_symtree* overridden;
11729       overridden = gfc_find_typebound_proc (super_type, NULL,
11730                                             stree->name, true, NULL);
11731
11732       if (overridden)
11733         {
11734           if (overridden->n.tb)
11735             stree->n.tb->overridden = overridden->n.tb;
11736
11737           if (gfc_check_typebound_override (stree, overridden) == FAILURE)
11738             goto error;
11739         }
11740     }
11741
11742   /* See if there's a name collision with a component directly in this type.  */
11743   for (comp = resolve_bindings_derived->components; comp; comp = comp->next)
11744     if (!strcmp (comp->name, stree->name))
11745       {
11746         gfc_error ("Procedure '%s' at %L has the same name as a component of"
11747                    " '%s'",
11748                    stree->name, &where, resolve_bindings_derived->name);
11749         goto error;
11750       }
11751
11752   /* Try to find a name collision with an inherited component.  */
11753   if (super_type && gfc_find_component (super_type, stree->name, true, true))
11754     {
11755       gfc_error ("Procedure '%s' at %L has the same name as an inherited"
11756                  " component of '%s'",
11757                  stree->name, &where, resolve_bindings_derived->name);
11758       goto error;
11759     }
11760
11761   stree->n.tb->error = 0;
11762   return;
11763
11764 error:
11765   resolve_bindings_result = FAILURE;
11766   stree->n.tb->error = 1;
11767 }
11768
11769
11770 static gfc_try
11771 resolve_typebound_procedures (gfc_symbol* derived)
11772 {
11773   int op;
11774   gfc_symbol* super_type;
11775
11776   if (!derived->f2k_derived || !derived->f2k_derived->tb_sym_root)
11777     return SUCCESS;
11778   
11779   super_type = gfc_get_derived_super_type (derived);
11780   if (super_type)
11781     resolve_typebound_procedures (super_type);
11782
11783   resolve_bindings_derived = derived;
11784   resolve_bindings_result = SUCCESS;
11785
11786   /* Make sure the vtab has been generated.  */
11787   gfc_find_derived_vtab (derived);
11788
11789   if (derived->f2k_derived->tb_sym_root)
11790     gfc_traverse_symtree (derived->f2k_derived->tb_sym_root,
11791                           &resolve_typebound_procedure);
11792
11793   if (derived->f2k_derived->tb_uop_root)
11794     gfc_traverse_symtree (derived->f2k_derived->tb_uop_root,
11795                           &resolve_typebound_user_op);
11796
11797   for (op = 0; op != GFC_INTRINSIC_OPS; ++op)
11798     {
11799       gfc_typebound_proc* p = derived->f2k_derived->tb_op[op];
11800       if (p && resolve_typebound_intrinsic_op (derived, (gfc_intrinsic_op) op,
11801                                                p) == FAILURE)
11802         resolve_bindings_result = FAILURE;
11803     }
11804
11805   return resolve_bindings_result;
11806 }
11807
11808
11809 /* Add a derived type to the dt_list.  The dt_list is used in trans-types.c
11810    to give all identical derived types the same backend_decl.  */
11811 static void
11812 add_dt_to_dt_list (gfc_symbol *derived)
11813 {
11814   gfc_dt_list *dt_list;
11815
11816   for (dt_list = gfc_derived_types; dt_list; dt_list = dt_list->next)
11817     if (derived == dt_list->derived)
11818       return;
11819
11820   dt_list = gfc_get_dt_list ();
11821   dt_list->next = gfc_derived_types;
11822   dt_list->derived = derived;
11823   gfc_derived_types = dt_list;
11824 }
11825
11826
11827 /* Ensure that a derived-type is really not abstract, meaning that every
11828    inherited DEFERRED binding is overridden by a non-DEFERRED one.  */
11829
11830 static gfc_try
11831 ensure_not_abstract_walker (gfc_symbol* sub, gfc_symtree* st)
11832 {
11833   if (!st)
11834     return SUCCESS;
11835
11836   if (ensure_not_abstract_walker (sub, st->left) == FAILURE)
11837     return FAILURE;
11838   if (ensure_not_abstract_walker (sub, st->right) == FAILURE)
11839     return FAILURE;
11840
11841   if (st->n.tb && st->n.tb->deferred)
11842     {
11843       gfc_symtree* overriding;
11844       overriding = gfc_find_typebound_proc (sub, NULL, st->name, true, NULL);
11845       if (!overriding)
11846         return FAILURE;
11847       gcc_assert (overriding->n.tb);
11848       if (overriding->n.tb->deferred)
11849         {
11850           gfc_error ("Derived-type '%s' declared at %L must be ABSTRACT because"
11851                      " '%s' is DEFERRED and not overridden",
11852                      sub->name, &sub->declared_at, st->name);
11853           return FAILURE;
11854         }
11855     }
11856
11857   return SUCCESS;
11858 }
11859
11860 static gfc_try
11861 ensure_not_abstract (gfc_symbol* sub, gfc_symbol* ancestor)
11862 {
11863   /* The algorithm used here is to recursively travel up the ancestry of sub
11864      and for each ancestor-type, check all bindings.  If any of them is
11865      DEFERRED, look it up starting from sub and see if the found (overriding)
11866      binding is not DEFERRED.
11867      This is not the most efficient way to do this, but it should be ok and is
11868      clearer than something sophisticated.  */
11869
11870   gcc_assert (ancestor && !sub->attr.abstract);
11871   
11872   if (!ancestor->attr.abstract)
11873     return SUCCESS;
11874
11875   /* Walk bindings of this ancestor.  */
11876   if (ancestor->f2k_derived)
11877     {
11878       gfc_try t;
11879       t = ensure_not_abstract_walker (sub, ancestor->f2k_derived->tb_sym_root);
11880       if (t == FAILURE)
11881         return FAILURE;
11882     }
11883
11884   /* Find next ancestor type and recurse on it.  */
11885   ancestor = gfc_get_derived_super_type (ancestor);
11886   if (ancestor)
11887     return ensure_not_abstract (sub, ancestor);
11888
11889   return SUCCESS;
11890 }
11891
11892
11893 /* Resolve the components of a derived type. This does not have to wait until
11894    resolution stage, but can be done as soon as the dt declaration has been
11895    parsed.  */
11896
11897 static gfc_try
11898 resolve_fl_derived0 (gfc_symbol *sym)
11899 {
11900   gfc_symbol* super_type;
11901   gfc_component *c;
11902
11903   super_type = gfc_get_derived_super_type (sym);
11904
11905   /* F2008, C432. */
11906   if (super_type && sym->attr.coarray_comp && !super_type->attr.coarray_comp)
11907     {
11908       gfc_error ("As extending type '%s' at %L has a coarray component, "
11909                  "parent type '%s' shall also have one", sym->name,
11910                  &sym->declared_at, super_type->name);
11911       return FAILURE;
11912     }
11913
11914   /* Ensure the extended type gets resolved before we do.  */
11915   if (super_type && resolve_fl_derived0 (super_type) == FAILURE)
11916     return FAILURE;
11917
11918   /* An ABSTRACT type must be extensible.  */
11919   if (sym->attr.abstract && !gfc_type_is_extensible (sym))
11920     {
11921       gfc_error ("Non-extensible derived-type '%s' at %L must not be ABSTRACT",
11922                  sym->name, &sym->declared_at);
11923       return FAILURE;
11924     }
11925
11926   c = (sym->attr.is_class) ? sym->components->ts.u.derived->components
11927                            : sym->components;
11928
11929   for ( ; c != NULL; c = c->next)
11930     {
11931       if (c->attr.artificial)
11932         continue;
11933
11934       /* See PRs 51550, 47545, 48654, 49050, 51075 - and 45170.  */
11935       if (c->ts.type == BT_CHARACTER && c->ts.deferred && !c->attr.function)
11936         {
11937           gfc_error ("Deferred-length character component '%s' at %L is not "
11938                      "yet supported", c->name, &c->loc);
11939           return FAILURE;
11940         }
11941
11942       /* F2008, C442.  */
11943       if ((!sym->attr.is_class || c != sym->components)
11944           && c->attr.codimension
11945           && (!c->attr.allocatable || (c->as && c->as->type != AS_DEFERRED)))
11946         {
11947           gfc_error ("Coarray component '%s' at %L must be allocatable with "
11948                      "deferred shape", c->name, &c->loc);
11949           return FAILURE;
11950         }
11951
11952       /* F2008, C443.  */
11953       if (c->attr.codimension && c->ts.type == BT_DERIVED
11954           && c->ts.u.derived->ts.is_iso_c)
11955         {
11956           gfc_error ("Component '%s' at %L of TYPE(C_PTR) or TYPE(C_FUNPTR) "
11957                      "shall not be a coarray", c->name, &c->loc);
11958           return FAILURE;
11959         }
11960
11961       /* F2008, C444.  */
11962       if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.coarray_comp
11963           && (c->attr.codimension || c->attr.pointer || c->attr.dimension
11964               || c->attr.allocatable))
11965         {
11966           gfc_error ("Component '%s' at %L with coarray component "
11967                      "shall be a nonpointer, nonallocatable scalar",
11968                      c->name, &c->loc);
11969           return FAILURE;
11970         }
11971
11972       /* F2008, C448.  */
11973       if (c->attr.contiguous && (!c->attr.dimension || !c->attr.pointer))
11974         {
11975           gfc_error ("Component '%s' at %L has the CONTIGUOUS attribute but "
11976                      "is not an array pointer", c->name, &c->loc);
11977           return FAILURE;
11978         }
11979
11980       if (c->attr.proc_pointer && c->ts.interface)
11981         {
11982           gfc_symbol *ifc = c->ts.interface;
11983
11984           if (!sym->attr.vtype
11985               && check_proc_interface (ifc, &c->loc) == FAILURE)
11986             return FAILURE;
11987
11988           if (ifc->attr.if_source || ifc->attr.intrinsic)
11989             {
11990               /* Resolve interface and copy attributes.  */
11991               if (ifc->formal && !ifc->formal_ns)
11992                 resolve_symbol (ifc);
11993               if (ifc->attr.intrinsic)
11994                 gfc_resolve_intrinsic (ifc, &ifc->declared_at);
11995
11996               if (ifc->result)
11997                 {
11998                   c->ts = ifc->result->ts;
11999                   c->attr.allocatable = ifc->result->attr.allocatable;
12000                   c->attr.pointer = ifc->result->attr.pointer;
12001                   c->attr.dimension = ifc->result->attr.dimension;
12002                   c->as = gfc_copy_array_spec (ifc->result->as);
12003                 }
12004               else
12005                 {   
12006                   c->ts = ifc->ts;
12007                   c->attr.allocatable = ifc->attr.allocatable;
12008                   c->attr.pointer = ifc->attr.pointer;
12009                   c->attr.dimension = ifc->attr.dimension;
12010                   c->as = gfc_copy_array_spec (ifc->as);
12011                 }
12012               c->ts.interface = ifc;
12013               c->attr.function = ifc->attr.function;
12014               c->attr.subroutine = ifc->attr.subroutine;
12015               gfc_copy_formal_args_ppc (c, ifc, IFSRC_DECL);
12016
12017               c->attr.pure = ifc->attr.pure;
12018               c->attr.elemental = ifc->attr.elemental;
12019               c->attr.recursive = ifc->attr.recursive;
12020               c->attr.always_explicit = ifc->attr.always_explicit;
12021               c->attr.ext_attr |= ifc->attr.ext_attr;
12022               c->attr.class_ok = ifc->attr.class_ok;
12023               /* Replace symbols in array spec.  */
12024               if (c->as)
12025                 {
12026                   int i;
12027                   for (i = 0; i < c->as->rank; i++)
12028                     {
12029                       gfc_expr_replace_comp (c->as->lower[i], c);
12030                       gfc_expr_replace_comp (c->as->upper[i], c);
12031                     }
12032                 }
12033               /* Copy char length.  */
12034               if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
12035                 {
12036                   gfc_charlen *cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
12037                   gfc_expr_replace_comp (cl->length, c);
12038                   if (cl->length && !cl->resolved
12039                         && gfc_resolve_expr (cl->length) == FAILURE)
12040                     return FAILURE;
12041                   c->ts.u.cl = cl;
12042                 }
12043             }
12044         }
12045       else if (c->attr.proc_pointer && c->ts.type == BT_UNKNOWN)
12046         {
12047           /* Since PPCs are not implicitly typed, a PPC without an explicit
12048              interface must be a subroutine.  */
12049           gfc_add_subroutine (&c->attr, c->name, &c->loc);
12050         }
12051
12052       /* Procedure pointer components: Check PASS arg.  */
12053       if (c->attr.proc_pointer && !c->tb->nopass && c->tb->pass_arg_num == 0
12054           && !sym->attr.vtype)
12055         {
12056           gfc_symbol* me_arg;
12057
12058           if (c->tb->pass_arg)
12059             {
12060               gfc_formal_arglist* i;
12061
12062               /* If an explicit passing argument name is given, walk the arg-list
12063                 and look for it.  */
12064
12065               me_arg = NULL;
12066               c->tb->pass_arg_num = 1;
12067               for (i = c->formal; i; i = i->next)
12068                 {
12069                   if (!strcmp (i->sym->name, c->tb->pass_arg))
12070                     {
12071                       me_arg = i->sym;
12072                       break;
12073                     }
12074                   c->tb->pass_arg_num++;
12075                 }
12076
12077               if (!me_arg)
12078                 {
12079                   gfc_error ("Procedure pointer component '%s' with PASS(%s) "
12080                              "at %L has no argument '%s'", c->name,
12081                              c->tb->pass_arg, &c->loc, c->tb->pass_arg);
12082                   c->tb->error = 1;
12083                   return FAILURE;
12084                 }
12085             }
12086           else
12087             {
12088               /* Otherwise, take the first one; there should in fact be at least
12089                 one.  */
12090               c->tb->pass_arg_num = 1;
12091               if (!c->formal)
12092                 {
12093                   gfc_error ("Procedure pointer component '%s' with PASS at %L "
12094                              "must have at least one argument",
12095                              c->name, &c->loc);
12096                   c->tb->error = 1;
12097                   return FAILURE;
12098                 }
12099               me_arg = c->formal->sym;
12100             }
12101
12102           /* Now check that the argument-type matches.  */
12103           gcc_assert (me_arg);
12104           if ((me_arg->ts.type != BT_DERIVED && me_arg->ts.type != BT_CLASS)
12105               || (me_arg->ts.type == BT_DERIVED && me_arg->ts.u.derived != sym)
12106               || (me_arg->ts.type == BT_CLASS
12107                   && CLASS_DATA (me_arg)->ts.u.derived != sym))
12108             {
12109               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
12110                          " the derived type '%s'", me_arg->name, c->name,
12111                          me_arg->name, &c->loc, sym->name);
12112               c->tb->error = 1;
12113               return FAILURE;
12114             }
12115
12116           /* Check for C453.  */
12117           if (me_arg->attr.dimension)
12118             {
12119               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
12120                          "must be scalar", me_arg->name, c->name, me_arg->name,
12121                          &c->loc);
12122               c->tb->error = 1;
12123               return FAILURE;
12124             }
12125
12126           if (me_arg->attr.pointer)
12127             {
12128               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
12129                          "may not have the POINTER attribute", me_arg->name,
12130                          c->name, me_arg->name, &c->loc);
12131               c->tb->error = 1;
12132               return FAILURE;
12133             }
12134
12135           if (me_arg->attr.allocatable)
12136             {
12137               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
12138                          "may not be ALLOCATABLE", me_arg->name, c->name,
12139                          me_arg->name, &c->loc);
12140               c->tb->error = 1;
12141               return FAILURE;
12142             }
12143
12144           if (gfc_type_is_extensible (sym) && me_arg->ts.type != BT_CLASS)
12145             gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
12146                        " at %L", c->name, &c->loc);
12147
12148         }
12149
12150       /* Check type-spec if this is not the parent-type component.  */
12151       if (((sym->attr.is_class
12152             && (!sym->components->ts.u.derived->attr.extension
12153                 || c != sym->components->ts.u.derived->components))
12154            || (!sym->attr.is_class
12155                && (!sym->attr.extension || c != sym->components)))
12156           && !sym->attr.vtype
12157           && resolve_typespec_used (&c->ts, &c->loc, c->name) == FAILURE)
12158         return FAILURE;
12159
12160       /* If this type is an extension, set the accessibility of the parent
12161          component.  */
12162       if (super_type
12163           && ((sym->attr.is_class
12164                && c == sym->components->ts.u.derived->components)
12165               || (!sym->attr.is_class && c == sym->components))
12166           && strcmp (super_type->name, c->name) == 0)
12167         c->attr.access = super_type->attr.access;
12168       
12169       /* If this type is an extension, see if this component has the same name
12170          as an inherited type-bound procedure.  */
12171       if (super_type && !sym->attr.is_class
12172           && gfc_find_typebound_proc (super_type, NULL, c->name, true, NULL))
12173         {
12174           gfc_error ("Component '%s' of '%s' at %L has the same name as an"
12175                      " inherited type-bound procedure",
12176                      c->name, sym->name, &c->loc);
12177           return FAILURE;
12178         }
12179
12180       if (c->ts.type == BT_CHARACTER && !c->attr.proc_pointer
12181             && !c->ts.deferred)
12182         {
12183          if (c->ts.u.cl->length == NULL
12184              || (resolve_charlen (c->ts.u.cl) == FAILURE)
12185              || !gfc_is_constant_expr (c->ts.u.cl->length))
12186            {
12187              gfc_error ("Character length of component '%s' needs to "
12188                         "be a constant specification expression at %L",
12189                         c->name,
12190                         c->ts.u.cl->length ? &c->ts.u.cl->length->where : &c->loc);
12191              return FAILURE;
12192            }
12193         }
12194
12195       if (c->ts.type == BT_CHARACTER && c->ts.deferred
12196           && !c->attr.pointer && !c->attr.allocatable)
12197         {
12198           gfc_error ("Character component '%s' of '%s' at %L with deferred "
12199                      "length must be a POINTER or ALLOCATABLE",
12200                      c->name, sym->name, &c->loc);
12201           return FAILURE;
12202         }
12203
12204       if (c->ts.type == BT_DERIVED
12205           && sym->component_access != ACCESS_PRIVATE
12206           && gfc_check_symbol_access (sym)
12207           && !is_sym_host_assoc (c->ts.u.derived, sym->ns)
12208           && !c->ts.u.derived->attr.use_assoc
12209           && !gfc_check_symbol_access (c->ts.u.derived)
12210           && gfc_notify_std (GFC_STD_F2003, "the component '%s' "
12211                              "is a PRIVATE type and cannot be a component of "
12212                              "'%s', which is PUBLIC at %L", c->name,
12213                              sym->name, &sym->declared_at) == FAILURE)
12214         return FAILURE;
12215
12216       if ((sym->attr.sequence || sym->attr.is_bind_c) && c->ts.type == BT_CLASS)
12217         {
12218           gfc_error ("Polymorphic component %s at %L in SEQUENCE or BIND(C) "
12219                      "type %s", c->name, &c->loc, sym->name);
12220           return FAILURE;
12221         }
12222
12223       if (sym->attr.sequence)
12224         {
12225           if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.sequence == 0)
12226             {
12227               gfc_error ("Component %s of SEQUENCE type declared at %L does "
12228                          "not have the SEQUENCE attribute",
12229                          c->ts.u.derived->name, &sym->declared_at);
12230               return FAILURE;
12231             }
12232         }
12233
12234       if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.generic)
12235         c->ts.u.derived = gfc_find_dt_in_generic (c->ts.u.derived);
12236       else if (c->ts.type == BT_CLASS && c->attr.class_ok
12237                && CLASS_DATA (c)->ts.u.derived->attr.generic)
12238         CLASS_DATA (c)->ts.u.derived
12239                         = gfc_find_dt_in_generic (CLASS_DATA (c)->ts.u.derived);
12240
12241       if (!sym->attr.is_class && c->ts.type == BT_DERIVED && !sym->attr.vtype
12242           && c->attr.pointer && c->ts.u.derived->components == NULL
12243           && !c->ts.u.derived->attr.zero_comp)
12244         {
12245           gfc_error ("The pointer component '%s' of '%s' at %L is a type "
12246                      "that has not been declared", c->name, sym->name,
12247                      &c->loc);
12248           return FAILURE;
12249         }
12250
12251       if (c->ts.type == BT_CLASS && c->attr.class_ok
12252           && CLASS_DATA (c)->attr.class_pointer
12253           && CLASS_DATA (c)->ts.u.derived->components == NULL
12254           && !CLASS_DATA (c)->ts.u.derived->attr.zero_comp)
12255         {
12256           gfc_error ("The pointer component '%s' of '%s' at %L is a type "
12257                      "that has not been declared", c->name, sym->name,
12258                      &c->loc);
12259           return FAILURE;
12260         }
12261
12262       /* C437.  */
12263       if (c->ts.type == BT_CLASS && c->attr.flavor != FL_PROCEDURE
12264           && (!c->attr.class_ok
12265               || !(CLASS_DATA (c)->attr.class_pointer
12266                    || CLASS_DATA (c)->attr.allocatable)))
12267         {
12268           gfc_error ("Component '%s' with CLASS at %L must be allocatable "
12269                      "or pointer", c->name, &c->loc);
12270           return FAILURE;
12271         }
12272
12273       /* Ensure that all the derived type components are put on the
12274          derived type list; even in formal namespaces, where derived type
12275          pointer components might not have been declared.  */
12276       if (c->ts.type == BT_DERIVED
12277             && c->ts.u.derived
12278             && c->ts.u.derived->components
12279             && c->attr.pointer
12280             && sym != c->ts.u.derived)
12281         add_dt_to_dt_list (c->ts.u.derived);
12282
12283       if (gfc_resolve_array_spec (c->as, !(c->attr.pointer
12284                                            || c->attr.proc_pointer
12285                                            || c->attr.allocatable)) == FAILURE)
12286         return FAILURE;
12287     }
12288
12289   /* If this is a non-ABSTRACT type extending an ABSTRACT one, ensure that
12290      all DEFERRED bindings are overridden.  */
12291   if (super_type && super_type->attr.abstract && !sym->attr.abstract
12292       && !sym->attr.is_class
12293       && ensure_not_abstract (sym, super_type) == FAILURE)
12294     return FAILURE;
12295
12296   /* Add derived type to the derived type list.  */
12297   add_dt_to_dt_list (sym);
12298
12299   return SUCCESS;
12300 }
12301
12302
12303 /* The following procedure does the full resolution of a derived type,
12304    including resolution of all type-bound procedures (if present). In contrast
12305    to 'resolve_fl_derived0' this can only be done after the module has been
12306    parsed completely.  */
12307
12308 static gfc_try
12309 resolve_fl_derived (gfc_symbol *sym)
12310 {
12311   gfc_symbol *gen_dt = NULL;
12312
12313   if (!sym->attr.is_class)
12314     gfc_find_symbol (sym->name, sym->ns, 0, &gen_dt);
12315   if (gen_dt && gen_dt->generic && gen_dt->generic->next
12316       && (!gen_dt->generic->sym->attr.use_assoc
12317           || gen_dt->generic->sym->module != gen_dt->generic->next->sym->module)
12318       && gfc_notify_std (GFC_STD_F2003, "Generic name '%s' of "
12319                          "function '%s' at %L being the same name as derived "
12320                          "type at %L", sym->name,
12321                          gen_dt->generic->sym == sym
12322                            ? gen_dt->generic->next->sym->name
12323                            : gen_dt->generic->sym->name,
12324                          gen_dt->generic->sym == sym
12325                            ? &gen_dt->generic->next->sym->declared_at
12326                            : &gen_dt->generic->sym->declared_at,
12327                          &sym->declared_at) == FAILURE)
12328     return FAILURE;
12329
12330   /* Resolve the finalizer procedures.  */
12331   if (gfc_resolve_finalizers (sym) == FAILURE)
12332     return FAILURE;
12333   
12334   if (sym->attr.is_class && sym->ts.u.derived == NULL)
12335     {
12336       /* Fix up incomplete CLASS symbols.  */
12337       gfc_component *data = gfc_find_component (sym, "_data", true, true);
12338       gfc_component *vptr = gfc_find_component (sym, "_vptr", true, true);
12339       if (vptr->ts.u.derived == NULL)
12340         {
12341           gfc_symbol *vtab = gfc_find_derived_vtab (data->ts.u.derived);
12342           gcc_assert (vtab);
12343           vptr->ts.u.derived = vtab->ts.u.derived;
12344         }
12345     }
12346   
12347   if (resolve_fl_derived0 (sym) == FAILURE)
12348     return FAILURE;
12349   
12350   /* Resolve the type-bound procedures.  */
12351   if (resolve_typebound_procedures (sym) == FAILURE)
12352     return FAILURE;
12353
12354   return SUCCESS;
12355 }
12356
12357
12358 static gfc_try
12359 resolve_fl_namelist (gfc_symbol *sym)
12360 {
12361   gfc_namelist *nl;
12362   gfc_symbol *nlsym;
12363
12364   for (nl = sym->namelist; nl; nl = nl->next)
12365     {
12366       /* Check again, the check in match only works if NAMELIST comes
12367          after the decl.  */
12368       if (nl->sym->as && nl->sym->as->type == AS_ASSUMED_SIZE)
12369         {
12370           gfc_error ("Assumed size array '%s' in namelist '%s' at %L is not "
12371                      "allowed", nl->sym->name, sym->name, &sym->declared_at);
12372           return FAILURE;
12373         }
12374
12375       if (nl->sym->as && nl->sym->as->type == AS_ASSUMED_SHAPE
12376           && gfc_notify_std (GFC_STD_F2003, "NAMELIST array "
12377                              "object '%s' with assumed shape in namelist "
12378                              "'%s' at %L", nl->sym->name, sym->name,
12379                              &sym->declared_at) == FAILURE)
12380         return FAILURE;
12381
12382       if (is_non_constant_shape_array (nl->sym)
12383           && gfc_notify_std (GFC_STD_F2003, "NAMELIST array "
12384                              "object '%s' with nonconstant shape in namelist "
12385                              "'%s' at %L", nl->sym->name, sym->name,
12386                              &sym->declared_at) == FAILURE)
12387         return FAILURE;
12388
12389       if (nl->sym->ts.type == BT_CHARACTER
12390           && (nl->sym->ts.u.cl->length == NULL
12391               || !gfc_is_constant_expr (nl->sym->ts.u.cl->length))
12392           && gfc_notify_std (GFC_STD_F2003, "NAMELIST object "
12393                              "'%s' with nonconstant character length in "
12394                              "namelist '%s' at %L", nl->sym->name, sym->name,
12395                              &sym->declared_at) == FAILURE)
12396         return FAILURE;
12397
12398       /* FIXME: Once UDDTIO is implemented, the following can be
12399          removed.  */
12400       if (nl->sym->ts.type == BT_CLASS)
12401         {
12402           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L is "
12403                      "polymorphic and requires a defined input/output "
12404                      "procedure", nl->sym->name, sym->name, &sym->declared_at);
12405           return FAILURE;
12406         }
12407
12408       if (nl->sym->ts.type == BT_DERIVED
12409           && (nl->sym->ts.u.derived->attr.alloc_comp
12410               || nl->sym->ts.u.derived->attr.pointer_comp))
12411         {
12412           if (gfc_notify_std (GFC_STD_F2003, "NAMELIST object "
12413                               "'%s' in namelist '%s' at %L with ALLOCATABLE "
12414                               "or POINTER components", nl->sym->name,
12415                               sym->name, &sym->declared_at) == FAILURE)
12416             return FAILURE;
12417
12418          /* FIXME: Once UDDTIO is implemented, the following can be
12419             removed.  */
12420           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L has "
12421                      "ALLOCATABLE or POINTER components and thus requires "
12422                      "a defined input/output procedure", nl->sym->name,
12423                      sym->name, &sym->declared_at);
12424           return FAILURE;
12425         }
12426     }
12427
12428   /* Reject PRIVATE objects in a PUBLIC namelist.  */
12429   if (gfc_check_symbol_access (sym))
12430     {
12431       for (nl = sym->namelist; nl; nl = nl->next)
12432         {
12433           if (!nl->sym->attr.use_assoc
12434               && !is_sym_host_assoc (nl->sym, sym->ns)
12435               && !gfc_check_symbol_access (nl->sym))
12436             {
12437               gfc_error ("NAMELIST object '%s' was declared PRIVATE and "
12438                          "cannot be member of PUBLIC namelist '%s' at %L",
12439                          nl->sym->name, sym->name, &sym->declared_at);
12440               return FAILURE;
12441             }
12442
12443           /* Types with private components that came here by USE-association.  */
12444           if (nl->sym->ts.type == BT_DERIVED
12445               && derived_inaccessible (nl->sym->ts.u.derived))
12446             {
12447               gfc_error ("NAMELIST object '%s' has use-associated PRIVATE "
12448                          "components and cannot be member of namelist '%s' at %L",
12449                          nl->sym->name, sym->name, &sym->declared_at);
12450               return FAILURE;
12451             }
12452
12453           /* Types with private components that are defined in the same module.  */
12454           if (nl->sym->ts.type == BT_DERIVED
12455               && !is_sym_host_assoc (nl->sym->ts.u.derived, sym->ns)
12456               && nl->sym->ts.u.derived->attr.private_comp)
12457             {
12458               gfc_error ("NAMELIST object '%s' has PRIVATE components and "
12459                          "cannot be a member of PUBLIC namelist '%s' at %L",
12460                          nl->sym->name, sym->name, &sym->declared_at);
12461               return FAILURE;
12462             }
12463         }
12464     }
12465
12466
12467   /* 14.1.2 A module or internal procedure represent local entities
12468      of the same type as a namelist member and so are not allowed.  */
12469   for (nl = sym->namelist; nl; nl = nl->next)
12470     {
12471       if (nl->sym->ts.kind != 0 && nl->sym->attr.flavor == FL_VARIABLE)
12472         continue;
12473
12474       if (nl->sym->attr.function && nl->sym == nl->sym->result)
12475         if ((nl->sym == sym->ns->proc_name)
12476                ||
12477             (sym->ns->parent && nl->sym == sym->ns->parent->proc_name))
12478           continue;
12479
12480       nlsym = NULL;
12481       if (nl->sym && nl->sym->name)
12482         gfc_find_symbol (nl->sym->name, sym->ns, 1, &nlsym);
12483       if (nlsym && nlsym->attr.flavor == FL_PROCEDURE)
12484         {
12485           gfc_error ("PROCEDURE attribute conflicts with NAMELIST "
12486                      "attribute in '%s' at %L", nlsym->name,
12487                      &sym->declared_at);
12488           return FAILURE;
12489         }
12490     }
12491
12492   return SUCCESS;
12493 }
12494
12495
12496 static gfc_try
12497 resolve_fl_parameter (gfc_symbol *sym)
12498 {
12499   /* A parameter array's shape needs to be constant.  */
12500   if (sym->as != NULL 
12501       && (sym->as->type == AS_DEFERRED
12502           || is_non_constant_shape_array (sym)))
12503     {
12504       gfc_error ("Parameter array '%s' at %L cannot be automatic "
12505                  "or of deferred shape", sym->name, &sym->declared_at);
12506       return FAILURE;
12507     }
12508
12509   /* Make sure a parameter that has been implicitly typed still
12510      matches the implicit type, since PARAMETER statements can precede
12511      IMPLICIT statements.  */
12512   if (sym->attr.implicit_type
12513       && !gfc_compare_types (&sym->ts, gfc_get_default_type (sym->name,
12514                                                              sym->ns)))
12515     {
12516       gfc_error ("Implicitly typed PARAMETER '%s' at %L doesn't match a "
12517                  "later IMPLICIT type", sym->name, &sym->declared_at);
12518       return FAILURE;
12519     }
12520
12521   /* Make sure the types of derived parameters are consistent.  This
12522      type checking is deferred until resolution because the type may
12523      refer to a derived type from the host.  */
12524   if (sym->ts.type == BT_DERIVED
12525       && !gfc_compare_types (&sym->ts, &sym->value->ts))
12526     {
12527       gfc_error ("Incompatible derived type in PARAMETER at %L",
12528                  &sym->value->where);
12529       return FAILURE;
12530     }
12531   return SUCCESS;
12532 }
12533
12534
12535 /* Do anything necessary to resolve a symbol.  Right now, we just
12536    assume that an otherwise unknown symbol is a variable.  This sort
12537    of thing commonly happens for symbols in module.  */
12538
12539 static void
12540 resolve_symbol (gfc_symbol *sym)
12541 {
12542   int check_constant, mp_flag;
12543   gfc_symtree *symtree;
12544   gfc_symtree *this_symtree;
12545   gfc_namespace *ns;
12546   gfc_component *c;
12547   symbol_attribute class_attr;
12548   gfc_array_spec *as;
12549
12550   if (sym->attr.artificial)
12551     return;
12552
12553   if (sym->attr.flavor == FL_UNKNOWN
12554       || (sym->attr.flavor == FL_PROCEDURE && !sym->attr.intrinsic
12555           && !sym->attr.generic && !sym->attr.external
12556           && sym->attr.if_source == IFSRC_UNKNOWN))
12557     {
12558
12559     /* If we find that a flavorless symbol is an interface in one of the
12560        parent namespaces, find its symtree in this namespace, free the
12561        symbol and set the symtree to point to the interface symbol.  */
12562       for (ns = gfc_current_ns->parent; ns; ns = ns->parent)
12563         {
12564           symtree = gfc_find_symtree (ns->sym_root, sym->name);
12565           if (symtree && (symtree->n.sym->generic ||
12566                           (symtree->n.sym->attr.flavor == FL_PROCEDURE
12567                            && sym->ns->construct_entities)))
12568             {
12569               this_symtree = gfc_find_symtree (gfc_current_ns->sym_root,
12570                                                sym->name);
12571               gfc_release_symbol (sym);
12572               symtree->n.sym->refs++;
12573               this_symtree->n.sym = symtree->n.sym;
12574               return;
12575             }
12576         }
12577
12578       /* Otherwise give it a flavor according to such attributes as
12579          it has.  */
12580       if (sym->attr.flavor == FL_UNKNOWN && sym->attr.external == 0
12581           && sym->attr.intrinsic == 0)
12582         sym->attr.flavor = FL_VARIABLE;
12583       else if (sym->attr.flavor == FL_UNKNOWN)
12584         {
12585           sym->attr.flavor = FL_PROCEDURE;
12586           if (sym->attr.dimension)
12587             sym->attr.function = 1;
12588         }
12589     }
12590
12591   if (sym->attr.external && sym->ts.type != BT_UNKNOWN && !sym->attr.function)
12592     gfc_add_function (&sym->attr, sym->name, &sym->declared_at);
12593
12594   if (sym->attr.procedure && sym->attr.if_source != IFSRC_DECL
12595       && resolve_procedure_interface (sym) == FAILURE)
12596     return;
12597
12598   if (sym->attr.is_protected && !sym->attr.proc_pointer
12599       && (sym->attr.procedure || sym->attr.external))
12600     {
12601       if (sym->attr.external)
12602         gfc_error ("PROTECTED attribute conflicts with EXTERNAL attribute "
12603                    "at %L", &sym->declared_at);
12604       else
12605         gfc_error ("PROCEDURE attribute conflicts with PROTECTED attribute "
12606                    "at %L", &sym->declared_at);
12607
12608       return;
12609     }
12610
12611   if (sym->attr.flavor == FL_DERIVED && resolve_fl_derived (sym) == FAILURE)
12612     return;
12613
12614   /* Symbols that are module procedures with results (functions) have
12615      the types and array specification copied for type checking in
12616      procedures that call them, as well as for saving to a module
12617      file.  These symbols can't stand the scrutiny that their results
12618      can.  */
12619   mp_flag = (sym->result != NULL && sym->result != sym);
12620
12621   /* Make sure that the intrinsic is consistent with its internal 
12622      representation. This needs to be done before assigning a default 
12623      type to avoid spurious warnings.  */
12624   if (sym->attr.flavor != FL_MODULE && sym->attr.intrinsic
12625       && gfc_resolve_intrinsic (sym, &sym->declared_at) == FAILURE)
12626     return;
12627
12628   /* Resolve associate names.  */
12629   if (sym->assoc)
12630     resolve_assoc_var (sym, true);
12631
12632   /* Assign default type to symbols that need one and don't have one.  */
12633   if (sym->ts.type == BT_UNKNOWN)
12634     {
12635       if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER)
12636         {
12637           gfc_set_default_type (sym, 1, NULL);
12638         }
12639
12640       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.external
12641           && !sym->attr.function && !sym->attr.subroutine
12642           && gfc_get_default_type (sym->name, sym->ns)->type == BT_UNKNOWN)
12643         gfc_add_subroutine (&sym->attr, sym->name, &sym->declared_at);
12644
12645       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.function)
12646         {
12647           /* The specific case of an external procedure should emit an error
12648              in the case that there is no implicit type.  */
12649           if (!mp_flag)
12650             gfc_set_default_type (sym, sym->attr.external, NULL);
12651           else
12652             {
12653               /* Result may be in another namespace.  */
12654               resolve_symbol (sym->result);
12655
12656               if (!sym->result->attr.proc_pointer)
12657                 {
12658                   sym->ts = sym->result->ts;
12659                   sym->as = gfc_copy_array_spec (sym->result->as);
12660                   sym->attr.dimension = sym->result->attr.dimension;
12661                   sym->attr.pointer = sym->result->attr.pointer;
12662                   sym->attr.allocatable = sym->result->attr.allocatable;
12663                   sym->attr.contiguous = sym->result->attr.contiguous;
12664                 }
12665             }
12666         }
12667     }
12668   else if (mp_flag && sym->attr.flavor == FL_PROCEDURE && sym->attr.function)
12669     gfc_resolve_array_spec (sym->result->as, false);
12670
12671   if (sym->ts.type == BT_CLASS && sym->attr.class_ok)
12672     {
12673       as = CLASS_DATA (sym)->as;
12674       class_attr = CLASS_DATA (sym)->attr;
12675       class_attr.pointer = class_attr.class_pointer;
12676     }
12677   else
12678     {
12679       class_attr = sym->attr;
12680       as = sym->as;
12681     }
12682
12683   /* F2008, C530. */
12684   if (sym->attr.contiguous
12685       && (!class_attr.dimension
12686           || (as->type != AS_ASSUMED_SHAPE && as->type != AS_ASSUMED_RANK
12687               && !class_attr.pointer)))
12688     {
12689       gfc_error ("'%s' at %L has the CONTIGUOUS attribute but is not an "
12690                  "array pointer or an assumed-shape or assumed-rank array",
12691                  sym->name, &sym->declared_at);
12692       return;
12693     }
12694
12695   /* Assumed size arrays and assumed shape arrays must be dummy
12696      arguments.  Array-spec's of implied-shape should have been resolved to
12697      AS_EXPLICIT already.  */
12698
12699   if (as)
12700     {
12701       gcc_assert (as->type != AS_IMPLIED_SHAPE);
12702       if (((as->type == AS_ASSUMED_SIZE && !as->cp_was_assumed)
12703            || as->type == AS_ASSUMED_SHAPE)
12704           && sym->attr.dummy == 0)
12705         {
12706           if (as->type == AS_ASSUMED_SIZE)
12707             gfc_error ("Assumed size array at %L must be a dummy argument",
12708                        &sym->declared_at);
12709           else
12710             gfc_error ("Assumed shape array at %L must be a dummy argument",
12711                        &sym->declared_at);
12712           return;
12713         }
12714       /* TS 29113, C535a.  */
12715       if (as->type == AS_ASSUMED_RANK && !sym->attr.dummy)
12716         {
12717           gfc_error ("Assumed-rank array at %L must be a dummy argument",
12718                      &sym->declared_at);
12719           return;
12720         }
12721       if (as->type == AS_ASSUMED_RANK
12722           && (sym->attr.codimension || sym->attr.value))
12723         {
12724           gfc_error ("Assumed-rank array at %L may not have the VALUE or "
12725                      "CODIMENSION attribute", &sym->declared_at);
12726           return;
12727         }
12728     }
12729
12730   /* Make sure symbols with known intent or optional are really dummy
12731      variable.  Because of ENTRY statement, this has to be deferred
12732      until resolution time.  */
12733
12734   if (!sym->attr.dummy
12735       && (sym->attr.optional || sym->attr.intent != INTENT_UNKNOWN))
12736     {
12737       gfc_error ("Symbol at %L is not a DUMMY variable", &sym->declared_at);
12738       return;
12739     }
12740
12741   if (sym->attr.value && !sym->attr.dummy)
12742     {
12743       gfc_error ("'%s' at %L cannot have the VALUE attribute because "
12744                  "it is not a dummy argument", sym->name, &sym->declared_at);
12745       return;
12746     }
12747
12748   if (sym->attr.value && sym->ts.type == BT_CHARACTER)
12749     {
12750       gfc_charlen *cl = sym->ts.u.cl;
12751       if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
12752         {
12753           gfc_error ("Character dummy variable '%s' at %L with VALUE "
12754                      "attribute must have constant length",
12755                      sym->name, &sym->declared_at);
12756           return;
12757         }
12758
12759       if (sym->ts.is_c_interop
12760           && mpz_cmp_si (cl->length->value.integer, 1) != 0)
12761         {
12762           gfc_error ("C interoperable character dummy variable '%s' at %L "
12763                      "with VALUE attribute must have length one",
12764                      sym->name, &sym->declared_at);
12765           return;
12766         }
12767     }
12768
12769   if (sym->ts.type == BT_DERIVED && !sym->attr.is_iso_c
12770       && sym->ts.u.derived->attr.generic)
12771     {
12772       sym->ts.u.derived = gfc_find_dt_in_generic (sym->ts.u.derived);
12773       if (!sym->ts.u.derived)
12774         {
12775           gfc_error ("The derived type '%s' at %L is of type '%s', "
12776                      "which has not been defined", sym->name,
12777                      &sym->declared_at, sym->ts.u.derived->name);
12778           sym->ts.type = BT_UNKNOWN;
12779           return;
12780         }
12781     }
12782
12783   if (sym->ts.type == BT_ASSUMED)
12784     { 
12785       /* TS 29113, C407a.  */
12786       if (!sym->attr.dummy)
12787         {
12788           gfc_error ("Assumed type of variable %s at %L is only permitted "
12789                      "for dummy variables", sym->name, &sym->declared_at);
12790           return;
12791         }
12792       if (sym->attr.allocatable || sym->attr.codimension
12793           || sym->attr.pointer || sym->attr.value)
12794         {
12795           gfc_error ("Assumed-type variable %s at %L may not have the "
12796                      "ALLOCATABLE, CODIMENSION, POINTER or VALUE attribute",
12797                      sym->name, &sym->declared_at);
12798           return;
12799         }
12800       if (sym->attr.intent == INTENT_OUT)
12801         {
12802           gfc_error ("Assumed-type variable %s at %L may not have the "
12803                      "INTENT(OUT) attribute",
12804                      sym->name, &sym->declared_at);
12805           return;
12806         }
12807       if (sym->attr.dimension && sym->as->type == AS_EXPLICIT)
12808         {
12809           gfc_error ("Assumed-type variable %s at %L shall not be an "
12810                      "explicit-shape array", sym->name, &sym->declared_at);
12811           return;
12812         }
12813     }
12814
12815   /* If the symbol is marked as bind(c), verify it's type and kind.  Do not
12816      do this for something that was implicitly typed because that is handled
12817      in gfc_set_default_type.  Handle dummy arguments and procedure
12818      definitions separately.  Also, anything that is use associated is not
12819      handled here but instead is handled in the module it is declared in.
12820      Finally, derived type definitions are allowed to be BIND(C) since that
12821      only implies that they're interoperable, and they are checked fully for
12822      interoperability when a variable is declared of that type.  */
12823   if (sym->attr.is_bind_c && sym->attr.implicit_type == 0 &&
12824       sym->attr.use_assoc == 0 && sym->attr.dummy == 0 &&
12825       sym->attr.flavor != FL_PROCEDURE && sym->attr.flavor != FL_DERIVED)
12826     {
12827       gfc_try t = SUCCESS;
12828       
12829       /* First, make sure the variable is declared at the
12830          module-level scope (J3/04-007, Section 15.3).  */
12831       if (sym->ns->proc_name->attr.flavor != FL_MODULE &&
12832           sym->attr.in_common == 0)
12833         {
12834           gfc_error ("Variable '%s' at %L cannot be BIND(C) because it "
12835                      "is neither a COMMON block nor declared at the "
12836                      "module level scope", sym->name, &(sym->declared_at));
12837           t = FAILURE;
12838         }
12839       else if (sym->common_head != NULL)
12840         {
12841           t = verify_com_block_vars_c_interop (sym->common_head);
12842         }
12843       else
12844         {
12845           /* If type() declaration, we need to verify that the components
12846              of the given type are all C interoperable, etc.  */
12847           if (sym->ts.type == BT_DERIVED &&
12848               sym->ts.u.derived->attr.is_c_interop != 1)
12849             {
12850               /* Make sure the user marked the derived type as BIND(C).  If
12851                  not, call the verify routine.  This could print an error
12852                  for the derived type more than once if multiple variables
12853                  of that type are declared.  */
12854               if (sym->ts.u.derived->attr.is_bind_c != 1)
12855                 verify_bind_c_derived_type (sym->ts.u.derived);
12856               t = FAILURE;
12857             }
12858           
12859           /* Verify the variable itself as C interoperable if it
12860              is BIND(C).  It is not possible for this to succeed if
12861              the verify_bind_c_derived_type failed, so don't have to handle
12862              any error returned by verify_bind_c_derived_type.  */
12863           t = verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
12864                                  sym->common_block);
12865         }
12866
12867       if (t == FAILURE)
12868         {
12869           /* clear the is_bind_c flag to prevent reporting errors more than
12870              once if something failed.  */
12871           sym->attr.is_bind_c = 0;
12872           return;
12873         }
12874     }
12875
12876   /* If a derived type symbol has reached this point, without its
12877      type being declared, we have an error.  Notice that most
12878      conditions that produce undefined derived types have already
12879      been dealt with.  However, the likes of:
12880      implicit type(t) (t) ..... call foo (t) will get us here if
12881      the type is not declared in the scope of the implicit
12882      statement. Change the type to BT_UNKNOWN, both because it is so
12883      and to prevent an ICE.  */
12884   if (sym->ts.type == BT_DERIVED && !sym->attr.is_iso_c
12885       && sym->ts.u.derived->components == NULL
12886       && !sym->ts.u.derived->attr.zero_comp)
12887     {
12888       gfc_error ("The derived type '%s' at %L is of type '%s', "
12889                  "which has not been defined", sym->name,
12890                   &sym->declared_at, sym->ts.u.derived->name);
12891       sym->ts.type = BT_UNKNOWN;
12892       return;
12893     }
12894
12895   /* Make sure that the derived type has been resolved and that the
12896      derived type is visible in the symbol's namespace, if it is a
12897      module function and is not PRIVATE.  */
12898   if (sym->ts.type == BT_DERIVED
12899         && sym->ts.u.derived->attr.use_assoc
12900         && sym->ns->proc_name
12901         && sym->ns->proc_name->attr.flavor == FL_MODULE
12902         && resolve_fl_derived (sym->ts.u.derived) == FAILURE)
12903     return;
12904
12905   /* Unless the derived-type declaration is use associated, Fortran 95
12906      does not allow public entries of private derived types.
12907      See 4.4.1 (F95) and 4.5.1.1 (F2003); and related interpretation
12908      161 in 95-006r3.  */
12909   if (sym->ts.type == BT_DERIVED
12910       && sym->ns->proc_name && sym->ns->proc_name->attr.flavor == FL_MODULE
12911       && !sym->ts.u.derived->attr.use_assoc
12912       && gfc_check_symbol_access (sym)
12913       && !gfc_check_symbol_access (sym->ts.u.derived)
12914       && gfc_notify_std (GFC_STD_F2003, "PUBLIC %s '%s' at %L "
12915                          "of PRIVATE derived type '%s'",
12916                          (sym->attr.flavor == FL_PARAMETER) ? "parameter"
12917                          : "variable", sym->name, &sym->declared_at,
12918                          sym->ts.u.derived->name) == FAILURE)
12919     return;
12920
12921   /* F2008, C1302.  */
12922   if (sym->ts.type == BT_DERIVED
12923       && ((sym->ts.u.derived->from_intmod == INTMOD_ISO_FORTRAN_ENV
12924            && sym->ts.u.derived->intmod_sym_id == ISOFORTRAN_LOCK_TYPE)
12925           || sym->ts.u.derived->attr.lock_comp)
12926       && !sym->attr.codimension && !sym->ts.u.derived->attr.coarray_comp)
12927     {
12928       gfc_error ("Variable %s at %L of type LOCK_TYPE or with subcomponent of "
12929                  "type LOCK_TYPE must be a coarray", sym->name,
12930                  &sym->declared_at);
12931       return;
12932     }
12933
12934   /* An assumed-size array with INTENT(OUT) shall not be of a type for which
12935      default initialization is defined (5.1.2.4.4).  */
12936   if (sym->ts.type == BT_DERIVED
12937       && sym->attr.dummy
12938       && sym->attr.intent == INTENT_OUT
12939       && sym->as
12940       && sym->as->type == AS_ASSUMED_SIZE)
12941     {
12942       for (c = sym->ts.u.derived->components; c; c = c->next)
12943         {
12944           if (c->initializer)
12945             {
12946               gfc_error ("The INTENT(OUT) dummy argument '%s' at %L is "
12947                          "ASSUMED SIZE and so cannot have a default initializer",
12948                          sym->name, &sym->declared_at);
12949               return;
12950             }
12951         }
12952     }
12953
12954   /* F2008, C542.  */
12955   if (sym->ts.type == BT_DERIVED && sym->attr.dummy
12956       && sym->attr.intent == INTENT_OUT && sym->attr.lock_comp)
12957     {
12958       gfc_error ("Dummy argument '%s' at %L of LOCK_TYPE shall not be "
12959                  "INTENT(OUT)", sym->name, &sym->declared_at);
12960       return;
12961     }
12962
12963   /* F2008, C525.  */
12964   if ((((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
12965          || (sym->ts.type == BT_CLASS && sym->attr.class_ok
12966              && CLASS_DATA (sym)->attr.coarray_comp))
12967        || class_attr.codimension)
12968       && (sym->attr.result || sym->result == sym))
12969     {
12970       gfc_error ("Function result '%s' at %L shall not be a coarray or have "
12971                  "a coarray component", sym->name, &sym->declared_at);
12972       return;
12973     }
12974
12975   /* F2008, C524.  */
12976   if (sym->attr.codimension && sym->ts.type == BT_DERIVED
12977       && sym->ts.u.derived->ts.is_iso_c)
12978     {
12979       gfc_error ("Variable '%s' at %L of TYPE(C_PTR) or TYPE(C_FUNPTR) "
12980                  "shall not be a coarray", sym->name, &sym->declared_at);
12981       return;
12982     }
12983
12984   /* F2008, C525.  */
12985   if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
12986         || (sym->ts.type == BT_CLASS && sym->attr.class_ok
12987             && CLASS_DATA (sym)->attr.coarray_comp))
12988       && (class_attr.codimension || class_attr.pointer || class_attr.dimension
12989           || class_attr.allocatable))
12990     {
12991       gfc_error ("Variable '%s' at %L with coarray component "
12992                  "shall be a nonpointer, nonallocatable scalar",
12993                  sym->name, &sym->declared_at);
12994       return;
12995     }
12996
12997   /* F2008, C526.  The function-result case was handled above.  */
12998   if (class_attr.codimension
12999       && !(class_attr.allocatable || sym->attr.dummy || sym->attr.save
13000            || sym->attr.select_type_temporary
13001            || sym->ns->save_all
13002            || sym->ns->proc_name->attr.flavor == FL_MODULE
13003            || sym->ns->proc_name->attr.is_main_program
13004            || sym->attr.function || sym->attr.result || sym->attr.use_assoc))
13005     {
13006       gfc_error ("Variable '%s' at %L is a coarray and is not ALLOCATABLE, SAVE "
13007                  "nor a dummy argument", sym->name, &sym->declared_at);
13008       return;
13009     }
13010   /* F2008, C528.  */
13011   else if (class_attr.codimension && !sym->attr.select_type_temporary
13012            && !class_attr.allocatable && as && as->cotype == AS_DEFERRED)
13013     {
13014       gfc_error ("Coarray variable '%s' at %L shall not have codimensions with "
13015                  "deferred shape", sym->name, &sym->declared_at);
13016       return;
13017     }
13018   else if (class_attr.codimension && class_attr.allocatable && as
13019            && (as->cotype != AS_DEFERRED || as->type != AS_DEFERRED))
13020     {
13021       gfc_error ("Allocatable coarray variable '%s' at %L must have "
13022                  "deferred shape", sym->name, &sym->declared_at);
13023       return;
13024     }
13025
13026   /* F2008, C541.  */
13027   if ((((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
13028         || (sym->ts.type == BT_CLASS && sym->attr.class_ok
13029             && CLASS_DATA (sym)->attr.coarray_comp))
13030        || (class_attr.codimension && class_attr.allocatable))
13031       && sym->attr.dummy && sym->attr.intent == INTENT_OUT)
13032     {
13033       gfc_error ("Variable '%s' at %L is INTENT(OUT) and can thus not be an "
13034                  "allocatable coarray or have coarray components",
13035                  sym->name, &sym->declared_at);
13036       return;
13037     }
13038
13039   if (class_attr.codimension && sym->attr.dummy
13040       && sym->ns->proc_name && sym->ns->proc_name->attr.is_bind_c)
13041     {
13042       gfc_error ("Coarray dummy variable '%s' at %L not allowed in BIND(C) "
13043                  "procedure '%s'", sym->name, &sym->declared_at,
13044                  sym->ns->proc_name->name);
13045       return;
13046     }
13047
13048   switch (sym->attr.flavor)
13049     {
13050     case FL_VARIABLE:
13051       if (resolve_fl_variable (sym, mp_flag) == FAILURE)
13052         return;
13053       break;
13054
13055     case FL_PROCEDURE:
13056       if (resolve_fl_procedure (sym, mp_flag) == FAILURE)
13057         return;
13058       break;
13059
13060     case FL_NAMELIST:
13061       if (resolve_fl_namelist (sym) == FAILURE)
13062         return;
13063       break;
13064
13065     case FL_PARAMETER:
13066       if (resolve_fl_parameter (sym) == FAILURE)
13067         return;
13068       break;
13069
13070     default:
13071       break;
13072     }
13073
13074   /* Resolve array specifier. Check as well some constraints
13075      on COMMON blocks.  */
13076
13077   check_constant = sym->attr.in_common && !sym->attr.pointer;
13078
13079   /* Set the formal_arg_flag so that check_conflict will not throw
13080      an error for host associated variables in the specification
13081      expression for an array_valued function.  */
13082   if (sym->attr.function && sym->as)
13083     formal_arg_flag = 1;
13084
13085   gfc_resolve_array_spec (sym->as, check_constant);
13086
13087   formal_arg_flag = 0;
13088
13089   /* Resolve formal namespaces.  */
13090   if (sym->formal_ns && sym->formal_ns != gfc_current_ns
13091       && !sym->attr.contained && !sym->attr.intrinsic)
13092     gfc_resolve (sym->formal_ns);
13093
13094   /* Make sure the formal namespace is present.  */
13095   if (sym->formal && !sym->formal_ns)
13096     {
13097       gfc_formal_arglist *formal = sym->formal;
13098       while (formal && !formal->sym)
13099         formal = formal->next;
13100
13101       if (formal)
13102         {
13103           sym->formal_ns = formal->sym->ns;
13104           if (sym->ns != formal->sym->ns)
13105             sym->formal_ns->refs++;
13106         }
13107     }
13108
13109   /* Check threadprivate restrictions.  */
13110   if (sym->attr.threadprivate && !sym->attr.save && !sym->ns->save_all
13111       && (!sym->attr.in_common
13112           && sym->module == NULL
13113           && (sym->ns->proc_name == NULL
13114               || sym->ns->proc_name->attr.flavor != FL_MODULE)))
13115     gfc_error ("Threadprivate at %L isn't SAVEd", &sym->declared_at);
13116
13117   /* If we have come this far we can apply default-initializers, as
13118      described in 14.7.5, to those variables that have not already
13119      been assigned one.  */
13120   if (sym->ts.type == BT_DERIVED
13121       && sym->ns == gfc_current_ns
13122       && !sym->value
13123       && !sym->attr.allocatable
13124       && !sym->attr.alloc_comp)
13125     {
13126       symbol_attribute *a = &sym->attr;
13127
13128       if ((!a->save && !a->dummy && !a->pointer
13129            && !a->in_common && !a->use_assoc
13130            && (a->referenced || a->result)
13131            && !(a->function && sym != sym->result))
13132           || (a->dummy && a->intent == INTENT_OUT && !a->pointer))
13133         apply_default_init (sym);
13134     }
13135
13136   if (sym->ts.type == BT_CLASS && sym->ns == gfc_current_ns
13137       && sym->attr.dummy && sym->attr.intent == INTENT_OUT
13138       && !CLASS_DATA (sym)->attr.class_pointer
13139       && !CLASS_DATA (sym)->attr.allocatable)
13140     apply_default_init (sym);
13141
13142   /* If this symbol has a type-spec, check it.  */
13143   if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER
13144       || (sym->attr.flavor == FL_PROCEDURE && sym->attr.function))
13145     if (resolve_typespec_used (&sym->ts, &sym->declared_at, sym->name)
13146           == FAILURE)
13147       return;
13148 }
13149
13150
13151 /************* Resolve DATA statements *************/
13152
13153 static struct
13154 {
13155   gfc_data_value *vnode;
13156   mpz_t left;
13157 }
13158 values;
13159
13160
13161 /* Advance the values structure to point to the next value in the data list.  */
13162
13163 static gfc_try
13164 next_data_value (void)
13165 {
13166   while (mpz_cmp_ui (values.left, 0) == 0)
13167     {
13168
13169       if (values.vnode->next == NULL)
13170         return FAILURE;
13171
13172       values.vnode = values.vnode->next;
13173       mpz_set (values.left, values.vnode->repeat);
13174     }
13175
13176   return SUCCESS;
13177 }
13178
13179
13180 static gfc_try
13181 check_data_variable (gfc_data_variable *var, locus *where)
13182 {
13183   gfc_expr *e;
13184   mpz_t size;
13185   mpz_t offset;
13186   gfc_try t;
13187   ar_type mark = AR_UNKNOWN;
13188   int i;
13189   mpz_t section_index[GFC_MAX_DIMENSIONS];
13190   gfc_ref *ref;
13191   gfc_array_ref *ar;
13192   gfc_symbol *sym;
13193   int has_pointer;
13194
13195   if (gfc_resolve_expr (var->expr) == FAILURE)
13196     return FAILURE;
13197
13198   ar = NULL;
13199   mpz_init_set_si (offset, 0);
13200   e = var->expr;
13201
13202   if (e->expr_type != EXPR_VARIABLE)
13203     gfc_internal_error ("check_data_variable(): Bad expression");
13204
13205   sym = e->symtree->n.sym;
13206
13207   if (sym->ns->is_block_data && !sym->attr.in_common)
13208     {
13209       gfc_error ("BLOCK DATA element '%s' at %L must be in COMMON",
13210                  sym->name, &sym->declared_at);
13211     }
13212
13213   if (e->ref == NULL && sym->as)
13214     {
13215       gfc_error ("DATA array '%s' at %L must be specified in a previous"
13216                  " declaration", sym->name, where);
13217       return FAILURE;
13218     }
13219
13220   has_pointer = sym->attr.pointer;
13221
13222   if (gfc_is_coindexed (e))
13223     {
13224       gfc_error ("DATA element '%s' at %L cannot have a coindex", sym->name,
13225                  where);
13226       return FAILURE;
13227     }
13228
13229   for (ref = e->ref; ref; ref = ref->next)
13230     {
13231       if (ref->type == REF_COMPONENT && ref->u.c.component->attr.pointer)
13232         has_pointer = 1;
13233
13234       if (has_pointer
13235             && ref->type == REF_ARRAY
13236             && ref->u.ar.type != AR_FULL)
13237           {
13238             gfc_error ("DATA element '%s' at %L is a pointer and so must "
13239                         "be a full array", sym->name, where);
13240             return FAILURE;
13241           }
13242     }
13243
13244   if (e->rank == 0 || has_pointer)
13245     {
13246       mpz_init_set_ui (size, 1);
13247       ref = NULL;
13248     }
13249   else
13250     {
13251       ref = e->ref;
13252
13253       /* Find the array section reference.  */
13254       for (ref = e->ref; ref; ref = ref->next)
13255         {
13256           if (ref->type != REF_ARRAY)
13257             continue;
13258           if (ref->u.ar.type == AR_ELEMENT)
13259             continue;
13260           break;
13261         }
13262       gcc_assert (ref);
13263
13264       /* Set marks according to the reference pattern.  */
13265       switch (ref->u.ar.type)
13266         {
13267         case AR_FULL:
13268           mark = AR_FULL;
13269           break;
13270
13271         case AR_SECTION:
13272           ar = &ref->u.ar;
13273           /* Get the start position of array section.  */
13274           gfc_get_section_index (ar, section_index, &offset);
13275           mark = AR_SECTION;
13276           break;
13277
13278         default:
13279           gcc_unreachable ();
13280         }
13281
13282       if (gfc_array_size (e, &size) == FAILURE)
13283         {
13284           gfc_error ("Nonconstant array section at %L in DATA statement",
13285                      &e->where);
13286           mpz_clear (offset);
13287           return FAILURE;
13288         }
13289     }
13290
13291   t = SUCCESS;
13292
13293   while (mpz_cmp_ui (size, 0) > 0)
13294     {
13295       if (next_data_value () == FAILURE)
13296         {
13297           gfc_error ("DATA statement at %L has more variables than values",
13298                      where);
13299           t = FAILURE;
13300           break;
13301         }
13302
13303       t = gfc_check_assign (var->expr, values.vnode->expr, 0);
13304       if (t == FAILURE)
13305         break;
13306
13307       /* If we have more than one element left in the repeat count,
13308          and we have more than one element left in the target variable,
13309          then create a range assignment.  */
13310       /* FIXME: Only done for full arrays for now, since array sections
13311          seem tricky.  */
13312       if (mark == AR_FULL && ref && ref->next == NULL
13313           && mpz_cmp_ui (values.left, 1) > 0 && mpz_cmp_ui (size, 1) > 0)
13314         {
13315           mpz_t range;
13316
13317           if (mpz_cmp (size, values.left) >= 0)
13318             {
13319               mpz_init_set (range, values.left);
13320               mpz_sub (size, size, values.left);
13321               mpz_set_ui (values.left, 0);
13322             }
13323           else
13324             {
13325               mpz_init_set (range, size);
13326               mpz_sub (values.left, values.left, size);
13327               mpz_set_ui (size, 0);
13328             }
13329
13330           t = gfc_assign_data_value (var->expr, values.vnode->expr,
13331                                      offset, &range);
13332
13333           mpz_add (offset, offset, range);
13334           mpz_clear (range);
13335
13336           if (t == FAILURE)
13337             break;
13338         }
13339
13340       /* Assign initial value to symbol.  */
13341       else
13342         {
13343           mpz_sub_ui (values.left, values.left, 1);
13344           mpz_sub_ui (size, size, 1);
13345
13346           t = gfc_assign_data_value (var->expr, values.vnode->expr,
13347                                      offset, NULL);
13348           if (t == FAILURE)
13349             break;
13350
13351           if (mark == AR_FULL)
13352             mpz_add_ui (offset, offset, 1);
13353
13354           /* Modify the array section indexes and recalculate the offset
13355              for next element.  */
13356           else if (mark == AR_SECTION)
13357             gfc_advance_section (section_index, ar, &offset);
13358         }
13359     }
13360
13361   if (mark == AR_SECTION)
13362     {
13363       for (i = 0; i < ar->dimen; i++)
13364         mpz_clear (section_index[i]);
13365     }
13366
13367   mpz_clear (size);
13368   mpz_clear (offset);
13369
13370   return t;
13371 }
13372
13373
13374 static gfc_try traverse_data_var (gfc_data_variable *, locus *);
13375
13376 /* Iterate over a list of elements in a DATA statement.  */
13377
13378 static gfc_try
13379 traverse_data_list (gfc_data_variable *var, locus *where)
13380 {
13381   mpz_t trip;
13382   iterator_stack frame;
13383   gfc_expr *e, *start, *end, *step;
13384   gfc_try retval = SUCCESS;
13385
13386   mpz_init (frame.value);
13387   mpz_init (trip);
13388
13389   start = gfc_copy_expr (var->iter.start);
13390   end = gfc_copy_expr (var->iter.end);
13391   step = gfc_copy_expr (var->iter.step);
13392
13393   if (gfc_simplify_expr (start, 1) == FAILURE
13394       || start->expr_type != EXPR_CONSTANT)
13395     {
13396       gfc_error ("start of implied-do loop at %L could not be "
13397                  "simplified to a constant value", &start->where);
13398       retval = FAILURE;
13399       goto cleanup;
13400     }
13401   if (gfc_simplify_expr (end, 1) == FAILURE
13402       || end->expr_type != EXPR_CONSTANT)
13403     {
13404       gfc_error ("end of implied-do loop at %L could not be "
13405                  "simplified to a constant value", &start->where);
13406       retval = FAILURE;
13407       goto cleanup;
13408     }
13409   if (gfc_simplify_expr (step, 1) == FAILURE
13410       || step->expr_type != EXPR_CONSTANT)
13411     {
13412       gfc_error ("step of implied-do loop at %L could not be "
13413                  "simplified to a constant value", &start->where);
13414       retval = FAILURE;
13415       goto cleanup;
13416     }
13417
13418   mpz_set (trip, end->value.integer);
13419   mpz_sub (trip, trip, start->value.integer);
13420   mpz_add (trip, trip, step->value.integer);
13421
13422   mpz_div (trip, trip, step->value.integer);
13423
13424   mpz_set (frame.value, start->value.integer);
13425
13426   frame.prev = iter_stack;
13427   frame.variable = var->iter.var->symtree;
13428   iter_stack = &frame;
13429
13430   while (mpz_cmp_ui (trip, 0) > 0)
13431     {
13432       if (traverse_data_var (var->list, where) == FAILURE)
13433         {
13434           retval = FAILURE;
13435           goto cleanup;
13436         }
13437
13438       e = gfc_copy_expr (var->expr);
13439       if (gfc_simplify_expr (e, 1) == FAILURE)
13440         {
13441           gfc_free_expr (e);
13442           retval = FAILURE;
13443           goto cleanup;
13444         }
13445
13446       mpz_add (frame.value, frame.value, step->value.integer);
13447
13448       mpz_sub_ui (trip, trip, 1);
13449     }
13450
13451 cleanup:
13452   mpz_clear (frame.value);
13453   mpz_clear (trip);
13454
13455   gfc_free_expr (start);
13456   gfc_free_expr (end);
13457   gfc_free_expr (step);
13458
13459   iter_stack = frame.prev;
13460   return retval;
13461 }
13462
13463
13464 /* Type resolve variables in the variable list of a DATA statement.  */
13465
13466 static gfc_try
13467 traverse_data_var (gfc_data_variable *var, locus *where)
13468 {
13469   gfc_try t;
13470
13471   for (; var; var = var->next)
13472     {
13473       if (var->expr == NULL)
13474         t = traverse_data_list (var, where);
13475       else
13476         t = check_data_variable (var, where);
13477
13478       if (t == FAILURE)
13479         return FAILURE;
13480     }
13481
13482   return SUCCESS;
13483 }
13484
13485
13486 /* Resolve the expressions and iterators associated with a data statement.
13487    This is separate from the assignment checking because data lists should
13488    only be resolved once.  */
13489
13490 static gfc_try
13491 resolve_data_variables (gfc_data_variable *d)
13492 {
13493   for (; d; d = d->next)
13494     {
13495       if (d->list == NULL)
13496         {
13497           if (gfc_resolve_expr (d->expr) == FAILURE)
13498             return FAILURE;
13499         }
13500       else
13501         {
13502           if (gfc_resolve_iterator (&d->iter, false) == FAILURE)
13503             return FAILURE;
13504
13505           if (resolve_data_variables (d->list) == FAILURE)
13506             return FAILURE;
13507         }
13508     }
13509
13510   return SUCCESS;
13511 }
13512
13513
13514 /* Resolve a single DATA statement.  We implement this by storing a pointer to
13515    the value list into static variables, and then recursively traversing the
13516    variables list, expanding iterators and such.  */
13517
13518 static void
13519 resolve_data (gfc_data *d)
13520 {
13521
13522   if (resolve_data_variables (d->var) == FAILURE)
13523     return;
13524
13525   values.vnode = d->value;
13526   if (d->value == NULL)
13527     mpz_set_ui (values.left, 0);
13528   else
13529     mpz_set (values.left, d->value->repeat);
13530
13531   if (traverse_data_var (d->var, &d->where) == FAILURE)
13532     return;
13533
13534   /* At this point, we better not have any values left.  */
13535
13536   if (next_data_value () == SUCCESS)
13537     gfc_error ("DATA statement at %L has more values than variables",
13538                &d->where);
13539 }
13540
13541
13542 /* 12.6 Constraint: In a pure subprogram any variable which is in common or
13543    accessed by host or use association, is a dummy argument to a pure function,
13544    is a dummy argument with INTENT (IN) to a pure subroutine, or an object that
13545    is storage associated with any such variable, shall not be used in the
13546    following contexts: (clients of this function).  */
13547
13548 /* Determines if a variable is not 'pure', i.e., not assignable within a pure
13549    procedure.  Returns zero if assignment is OK, nonzero if there is a
13550    problem.  */
13551 int
13552 gfc_impure_variable (gfc_symbol *sym)
13553 {
13554   gfc_symbol *proc;
13555   gfc_namespace *ns;
13556
13557   if (sym->attr.use_assoc || sym->attr.in_common)
13558     return 1;
13559
13560   /* Check if the symbol's ns is inside the pure procedure.  */
13561   for (ns = gfc_current_ns; ns; ns = ns->parent)
13562     {
13563       if (ns == sym->ns)
13564         break;
13565       if (ns->proc_name->attr.flavor == FL_PROCEDURE && !sym->attr.function)
13566         return 1;
13567     }
13568
13569   proc = sym->ns->proc_name;
13570   if (sym->attr.dummy
13571       && ((proc->attr.subroutine && sym->attr.intent == INTENT_IN)
13572           || proc->attr.function))
13573     return 1;
13574
13575   /* TODO: Sort out what can be storage associated, if anything, and include
13576      it here.  In principle equivalences should be scanned but it does not
13577      seem to be possible to storage associate an impure variable this way.  */
13578   return 0;
13579 }
13580
13581
13582 /* Test whether a symbol is pure or not.  For a NULL pointer, checks if the
13583    current namespace is inside a pure procedure.  */
13584
13585 int
13586 gfc_pure (gfc_symbol *sym)
13587 {
13588   symbol_attribute attr;
13589   gfc_namespace *ns;
13590
13591   if (sym == NULL)
13592     {
13593       /* Check if the current namespace or one of its parents
13594         belongs to a pure procedure.  */
13595       for (ns = gfc_current_ns; ns; ns = ns->parent)
13596         {
13597           sym = ns->proc_name;
13598           if (sym == NULL)
13599             return 0;
13600           attr = sym->attr;
13601           if (attr.flavor == FL_PROCEDURE && attr.pure)
13602             return 1;
13603         }
13604       return 0;
13605     }
13606
13607   attr = sym->attr;
13608
13609   return attr.flavor == FL_PROCEDURE && attr.pure;
13610 }
13611
13612
13613 /* Test whether a symbol is implicitly pure or not.  For a NULL pointer,
13614    checks if the current namespace is implicitly pure.  Note that this
13615    function returns false for a PURE procedure.  */
13616
13617 int
13618 gfc_implicit_pure (gfc_symbol *sym)
13619 {
13620   gfc_namespace *ns;
13621
13622   if (sym == NULL)
13623     {
13624       /* Check if the current procedure is implicit_pure.  Walk up
13625          the procedure list until we find a procedure.  */
13626       for (ns = gfc_current_ns; ns; ns = ns->parent)
13627         {
13628           sym = ns->proc_name;
13629           if (sym == NULL)
13630             return 0;
13631           
13632           if (sym->attr.flavor == FL_PROCEDURE)
13633             break;
13634         }
13635     }
13636   
13637   return sym->attr.flavor == FL_PROCEDURE && sym->attr.implicit_pure
13638     && !sym->attr.pure;
13639 }
13640
13641
13642 /* Test whether the current procedure is elemental or not.  */
13643
13644 int
13645 gfc_elemental (gfc_symbol *sym)
13646 {
13647   symbol_attribute attr;
13648
13649   if (sym == NULL)
13650     sym = gfc_current_ns->proc_name;
13651   if (sym == NULL)
13652     return 0;
13653   attr = sym->attr;
13654
13655   return attr.flavor == FL_PROCEDURE && attr.elemental;
13656 }
13657
13658
13659 /* Warn about unused labels.  */
13660
13661 static void
13662 warn_unused_fortran_label (gfc_st_label *label)
13663 {
13664   if (label == NULL)
13665     return;
13666
13667   warn_unused_fortran_label (label->left);
13668
13669   if (label->defined == ST_LABEL_UNKNOWN)
13670     return;
13671
13672   switch (label->referenced)
13673     {
13674     case ST_LABEL_UNKNOWN:
13675       gfc_warning ("Label %d at %L defined but not used", label->value,
13676                    &label->where);
13677       break;
13678
13679     case ST_LABEL_BAD_TARGET:
13680       gfc_warning ("Label %d at %L defined but cannot be used",
13681                    label->value, &label->where);
13682       break;
13683
13684     default:
13685       break;
13686     }
13687
13688   warn_unused_fortran_label (label->right);
13689 }
13690
13691
13692 /* Returns the sequence type of a symbol or sequence.  */
13693
13694 static seq_type
13695 sequence_type (gfc_typespec ts)
13696 {
13697   seq_type result;
13698   gfc_component *c;
13699
13700   switch (ts.type)
13701   {
13702     case BT_DERIVED:
13703
13704       if (ts.u.derived->components == NULL)
13705         return SEQ_NONDEFAULT;
13706
13707       result = sequence_type (ts.u.derived->components->ts);
13708       for (c = ts.u.derived->components->next; c; c = c->next)
13709         if (sequence_type (c->ts) != result)
13710           return SEQ_MIXED;
13711
13712       return result;
13713
13714     case BT_CHARACTER:
13715       if (ts.kind != gfc_default_character_kind)
13716           return SEQ_NONDEFAULT;
13717
13718       return SEQ_CHARACTER;
13719
13720     case BT_INTEGER:
13721       if (ts.kind != gfc_default_integer_kind)
13722           return SEQ_NONDEFAULT;
13723
13724       return SEQ_NUMERIC;
13725
13726     case BT_REAL:
13727       if (!(ts.kind == gfc_default_real_kind
13728             || ts.kind == gfc_default_double_kind))
13729           return SEQ_NONDEFAULT;
13730
13731       return SEQ_NUMERIC;
13732
13733     case BT_COMPLEX:
13734       if (ts.kind != gfc_default_complex_kind)
13735           return SEQ_NONDEFAULT;
13736
13737       return SEQ_NUMERIC;
13738
13739     case BT_LOGICAL:
13740       if (ts.kind != gfc_default_logical_kind)
13741           return SEQ_NONDEFAULT;
13742
13743       return SEQ_NUMERIC;
13744
13745     default:
13746       return SEQ_NONDEFAULT;
13747   }
13748 }
13749
13750
13751 /* Resolve derived type EQUIVALENCE object.  */
13752
13753 static gfc_try
13754 resolve_equivalence_derived (gfc_symbol *derived, gfc_symbol *sym, gfc_expr *e)
13755 {
13756   gfc_component *c = derived->components;
13757
13758   if (!derived)
13759     return SUCCESS;
13760
13761   /* Shall not be an object of nonsequence derived type.  */
13762   if (!derived->attr.sequence)
13763     {
13764       gfc_error ("Derived type variable '%s' at %L must have SEQUENCE "
13765                  "attribute to be an EQUIVALENCE object", sym->name,
13766                  &e->where);
13767       return FAILURE;
13768     }
13769
13770   /* Shall not have allocatable components.  */
13771   if (derived->attr.alloc_comp)
13772     {
13773       gfc_error ("Derived type variable '%s' at %L cannot have ALLOCATABLE "
13774                  "components to be an EQUIVALENCE object",sym->name,
13775                  &e->where);
13776       return FAILURE;
13777     }
13778
13779   if (sym->attr.in_common && gfc_has_default_initializer (sym->ts.u.derived))
13780     {
13781       gfc_error ("Derived type variable '%s' at %L with default "
13782                  "initialization cannot be in EQUIVALENCE with a variable "
13783                  "in COMMON", sym->name, &e->where);
13784       return FAILURE;
13785     }
13786
13787   for (; c ; c = c->next)
13788     {
13789       if (c->ts.type == BT_DERIVED
13790           && (resolve_equivalence_derived (c->ts.u.derived, sym, e) == FAILURE))
13791         return FAILURE;
13792
13793       /* Shall not be an object of sequence derived type containing a pointer
13794          in the structure.  */
13795       if (c->attr.pointer)
13796         {
13797           gfc_error ("Derived type variable '%s' at %L with pointer "
13798                      "component(s) cannot be an EQUIVALENCE object",
13799                      sym->name, &e->where);
13800           return FAILURE;
13801         }
13802     }
13803   return SUCCESS;
13804 }
13805
13806
13807 /* Resolve equivalence object. 
13808    An EQUIVALENCE object shall not be a dummy argument, a pointer, a target,
13809    an allocatable array, an object of nonsequence derived type, an object of
13810    sequence derived type containing a pointer at any level of component
13811    selection, an automatic object, a function name, an entry name, a result
13812    name, a named constant, a structure component, or a subobject of any of
13813    the preceding objects.  A substring shall not have length zero.  A
13814    derived type shall not have components with default initialization nor
13815    shall two objects of an equivalence group be initialized.
13816    Either all or none of the objects shall have an protected attribute.
13817    The simple constraints are done in symbol.c(check_conflict) and the rest
13818    are implemented here.  */
13819
13820 static void
13821 resolve_equivalence (gfc_equiv *eq)
13822 {
13823   gfc_symbol *sym;
13824   gfc_symbol *first_sym;
13825   gfc_expr *e;
13826   gfc_ref *r;
13827   locus *last_where = NULL;
13828   seq_type eq_type, last_eq_type;
13829   gfc_typespec *last_ts;
13830   int object, cnt_protected;
13831   const char *msg;
13832
13833   last_ts = &eq->expr->symtree->n.sym->ts;
13834
13835   first_sym = eq->expr->symtree->n.sym;
13836
13837   cnt_protected = 0;
13838
13839   for (object = 1; eq; eq = eq->eq, object++)
13840     {
13841       e = eq->expr;
13842
13843       e->ts = e->symtree->n.sym->ts;
13844       /* match_varspec might not know yet if it is seeing
13845          array reference or substring reference, as it doesn't
13846          know the types.  */
13847       if (e->ref && e->ref->type == REF_ARRAY)
13848         {
13849           gfc_ref *ref = e->ref;
13850           sym = e->symtree->n.sym;
13851
13852           if (sym->attr.dimension)
13853             {
13854               ref->u.ar.as = sym->as;
13855               ref = ref->next;
13856             }
13857
13858           /* For substrings, convert REF_ARRAY into REF_SUBSTRING.  */
13859           if (e->ts.type == BT_CHARACTER
13860               && ref
13861               && ref->type == REF_ARRAY
13862               && ref->u.ar.dimen == 1
13863               && ref->u.ar.dimen_type[0] == DIMEN_RANGE
13864               && ref->u.ar.stride[0] == NULL)
13865             {
13866               gfc_expr *start = ref->u.ar.start[0];
13867               gfc_expr *end = ref->u.ar.end[0];
13868               void *mem = NULL;
13869
13870               /* Optimize away the (:) reference.  */
13871               if (start == NULL && end == NULL)
13872                 {
13873                   if (e->ref == ref)
13874                     e->ref = ref->next;
13875                   else
13876                     e->ref->next = ref->next;
13877                   mem = ref;
13878                 }
13879               else
13880                 {
13881                   ref->type = REF_SUBSTRING;
13882                   if (start == NULL)
13883                     start = gfc_get_int_expr (gfc_default_integer_kind,
13884                                               NULL, 1);
13885                   ref->u.ss.start = start;
13886                   if (end == NULL && e->ts.u.cl)
13887                     end = gfc_copy_expr (e->ts.u.cl->length);
13888                   ref->u.ss.end = end;
13889                   ref->u.ss.length = e->ts.u.cl;
13890                   e->ts.u.cl = NULL;
13891                 }
13892               ref = ref->next;
13893               free (mem);
13894             }
13895
13896           /* Any further ref is an error.  */
13897           if (ref)
13898             {
13899               gcc_assert (ref->type == REF_ARRAY);
13900               gfc_error ("Syntax error in EQUIVALENCE statement at %L",
13901                          &ref->u.ar.where);
13902               continue;
13903             }
13904         }
13905
13906       if (gfc_resolve_expr (e) == FAILURE)
13907         continue;
13908
13909       sym = e->symtree->n.sym;
13910
13911       if (sym->attr.is_protected)
13912         cnt_protected++;
13913       if (cnt_protected > 0 && cnt_protected != object)
13914         {
13915               gfc_error ("Either all or none of the objects in the "
13916                          "EQUIVALENCE set at %L shall have the "
13917                          "PROTECTED attribute",
13918                          &e->where);
13919               break;
13920         }
13921
13922       /* Shall not equivalence common block variables in a PURE procedure.  */
13923       if (sym->ns->proc_name
13924           && sym->ns->proc_name->attr.pure
13925           && sym->attr.in_common)
13926         {
13927           gfc_error ("Common block member '%s' at %L cannot be an EQUIVALENCE "
13928                      "object in the pure procedure '%s'",
13929                      sym->name, &e->where, sym->ns->proc_name->name);
13930           break;
13931         }
13932
13933       /* Shall not be a named constant.  */
13934       if (e->expr_type == EXPR_CONSTANT)
13935         {
13936           gfc_error ("Named constant '%s' at %L cannot be an EQUIVALENCE "
13937                      "object", sym->name, &e->where);
13938           continue;
13939         }
13940
13941       if (e->ts.type == BT_DERIVED
13942           && resolve_equivalence_derived (e->ts.u.derived, sym, e) == FAILURE)
13943         continue;
13944
13945       /* Check that the types correspond correctly:
13946          Note 5.28:
13947          A numeric sequence structure may be equivalenced to another sequence
13948          structure, an object of default integer type, default real type, double
13949          precision real type, default logical type such that components of the
13950          structure ultimately only become associated to objects of the same
13951          kind. A character sequence structure may be equivalenced to an object
13952          of default character kind or another character sequence structure.
13953          Other objects may be equivalenced only to objects of the same type and
13954          kind parameters.  */
13955
13956       /* Identical types are unconditionally OK.  */
13957       if (object == 1 || gfc_compare_types (last_ts, &sym->ts))
13958         goto identical_types;
13959
13960       last_eq_type = sequence_type (*last_ts);
13961       eq_type = sequence_type (sym->ts);
13962
13963       /* Since the pair of objects is not of the same type, mixed or
13964          non-default sequences can be rejected.  */
13965
13966       msg = "Sequence %s with mixed components in EQUIVALENCE "
13967             "statement at %L with different type objects";
13968       if ((object ==2
13969            && last_eq_type == SEQ_MIXED
13970            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name, last_where)
13971               == FAILURE)
13972           || (eq_type == SEQ_MIXED
13973               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13974                                  &e->where) == FAILURE))
13975         continue;
13976
13977       msg = "Non-default type object or sequence %s in EQUIVALENCE "
13978             "statement at %L with objects of different type";
13979       if ((object ==2
13980            && last_eq_type == SEQ_NONDEFAULT
13981            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name,
13982                               last_where) == FAILURE)
13983           || (eq_type == SEQ_NONDEFAULT
13984               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13985                                  &e->where) == FAILURE))
13986         continue;
13987
13988       msg ="Non-CHARACTER object '%s' in default CHARACTER "
13989            "EQUIVALENCE statement at %L";
13990       if (last_eq_type == SEQ_CHARACTER
13991           && eq_type != SEQ_CHARACTER
13992           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13993                              &e->where) == FAILURE)
13994                 continue;
13995
13996       msg ="Non-NUMERIC object '%s' in default NUMERIC "
13997            "EQUIVALENCE statement at %L";
13998       if (last_eq_type == SEQ_NUMERIC
13999           && eq_type != SEQ_NUMERIC
14000           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
14001                              &e->where) == FAILURE)
14002                 continue;
14003
14004   identical_types:
14005       last_ts =&sym->ts;
14006       last_where = &e->where;
14007
14008       if (!e->ref)
14009         continue;
14010
14011       /* Shall not be an automatic array.  */
14012       if (e->ref->type == REF_ARRAY
14013           && gfc_resolve_array_spec (e->ref->u.ar.as, 1) == FAILURE)
14014         {
14015           gfc_error ("Array '%s' at %L with non-constant bounds cannot be "
14016                      "an EQUIVALENCE object", sym->name, &e->where);
14017           continue;
14018         }
14019
14020       r = e->ref;
14021       while (r)
14022         {
14023           /* Shall not be a structure component.  */
14024           if (r->type == REF_COMPONENT)
14025             {
14026               gfc_error ("Structure component '%s' at %L cannot be an "
14027                          "EQUIVALENCE object",
14028                          r->u.c.component->name, &e->where);
14029               break;
14030             }
14031
14032           /* A substring shall not have length zero.  */
14033           if (r->type == REF_SUBSTRING)
14034             {
14035               if (compare_bound (r->u.ss.start, r->u.ss.end) == CMP_GT)
14036                 {
14037                   gfc_error ("Substring at %L has length zero",
14038                              &r->u.ss.start->where);
14039                   break;
14040                 }
14041             }
14042           r = r->next;
14043         }
14044     }
14045 }
14046
14047
14048 /* Resolve function and ENTRY types, issue diagnostics if needed.  */
14049
14050 static void
14051 resolve_fntype (gfc_namespace *ns)
14052 {
14053   gfc_entry_list *el;
14054   gfc_symbol *sym;
14055
14056   if (ns->proc_name == NULL || !ns->proc_name->attr.function)
14057     return;
14058
14059   /* If there are any entries, ns->proc_name is the entry master
14060      synthetic symbol and ns->entries->sym actual FUNCTION symbol.  */
14061   if (ns->entries)
14062     sym = ns->entries->sym;
14063   else
14064     sym = ns->proc_name;
14065   if (sym->result == sym
14066       && sym->ts.type == BT_UNKNOWN
14067       && gfc_set_default_type (sym, 0, NULL) == FAILURE
14068       && !sym->attr.untyped)
14069     {
14070       gfc_error ("Function '%s' at %L has no IMPLICIT type",
14071                  sym->name, &sym->declared_at);
14072       sym->attr.untyped = 1;
14073     }
14074
14075   if (sym->ts.type == BT_DERIVED && !sym->ts.u.derived->attr.use_assoc
14076       && !sym->attr.contained
14077       && !gfc_check_symbol_access (sym->ts.u.derived)
14078       && gfc_check_symbol_access (sym))
14079     {
14080       gfc_notify_std (GFC_STD_F2003, "PUBLIC function '%s' at "
14081                       "%L of PRIVATE type '%s'", sym->name,
14082                       &sym->declared_at, sym->ts.u.derived->name);
14083     }
14084
14085     if (ns->entries)
14086     for (el = ns->entries->next; el; el = el->next)
14087       {
14088         if (el->sym->result == el->sym
14089             && el->sym->ts.type == BT_UNKNOWN
14090             && gfc_set_default_type (el->sym, 0, NULL) == FAILURE
14091             && !el->sym->attr.untyped)
14092           {
14093             gfc_error ("ENTRY '%s' at %L has no IMPLICIT type",
14094                        el->sym->name, &el->sym->declared_at);
14095             el->sym->attr.untyped = 1;
14096           }
14097       }
14098 }
14099
14100
14101 /* 12.3.2.1.1 Defined operators.  */
14102
14103 static gfc_try
14104 check_uop_procedure (gfc_symbol *sym, locus where)
14105 {
14106   gfc_formal_arglist *formal;
14107
14108   if (!sym->attr.function)
14109     {
14110       gfc_error ("User operator procedure '%s' at %L must be a FUNCTION",
14111                  sym->name, &where);
14112       return FAILURE;
14113     }
14114
14115   if (sym->ts.type == BT_CHARACTER
14116       && !(sym->ts.u.cl && sym->ts.u.cl->length)
14117       && !(sym->result && sym->result->ts.u.cl
14118            && sym->result->ts.u.cl->length))
14119     {
14120       gfc_error ("User operator procedure '%s' at %L cannot be assumed "
14121                  "character length", sym->name, &where);
14122       return FAILURE;
14123     }
14124
14125   formal = sym->formal;
14126   if (!formal || !formal->sym)
14127     {
14128       gfc_error ("User operator procedure '%s' at %L must have at least "
14129                  "one argument", sym->name, &where);
14130       return FAILURE;
14131     }
14132
14133   if (formal->sym->attr.intent != INTENT_IN)
14134     {
14135       gfc_error ("First argument of operator interface at %L must be "
14136                  "INTENT(IN)", &where);
14137       return FAILURE;
14138     }
14139
14140   if (formal->sym->attr.optional)
14141     {
14142       gfc_error ("First argument of operator interface at %L cannot be "
14143                  "optional", &where);
14144       return FAILURE;
14145     }
14146
14147   formal = formal->next;
14148   if (!formal || !formal->sym)
14149     return SUCCESS;
14150
14151   if (formal->sym->attr.intent != INTENT_IN)
14152     {
14153       gfc_error ("Second argument of operator interface at %L must be "
14154                  "INTENT(IN)", &where);
14155       return FAILURE;
14156     }
14157
14158   if (formal->sym->attr.optional)
14159     {
14160       gfc_error ("Second argument of operator interface at %L cannot be "
14161                  "optional", &where);
14162       return FAILURE;
14163     }
14164
14165   if (formal->next)
14166     {
14167       gfc_error ("Operator interface at %L must have, at most, two "
14168                  "arguments", &where);
14169       return FAILURE;
14170     }
14171
14172   return SUCCESS;
14173 }
14174
14175 static void
14176 gfc_resolve_uops (gfc_symtree *symtree)
14177 {
14178   gfc_interface *itr;
14179
14180   if (symtree == NULL)
14181     return;
14182
14183   gfc_resolve_uops (symtree->left);
14184   gfc_resolve_uops (symtree->right);
14185
14186   for (itr = symtree->n.uop->op; itr; itr = itr->next)
14187     check_uop_procedure (itr->sym, itr->sym->declared_at);
14188 }
14189
14190
14191 /* Examine all of the expressions associated with a program unit,
14192    assign types to all intermediate expressions, make sure that all
14193    assignments are to compatible types and figure out which names
14194    refer to which functions or subroutines.  It doesn't check code
14195    block, which is handled by resolve_code.  */
14196
14197 static void
14198 resolve_types (gfc_namespace *ns)
14199 {
14200   gfc_namespace *n;
14201   gfc_charlen *cl;
14202   gfc_data *d;
14203   gfc_equiv *eq;
14204   gfc_namespace* old_ns = gfc_current_ns;
14205
14206   /* Check that all IMPLICIT types are ok.  */
14207   if (!ns->seen_implicit_none)
14208     {
14209       unsigned letter;
14210       for (letter = 0; letter != GFC_LETTERS; ++letter)
14211         if (ns->set_flag[letter]
14212             && resolve_typespec_used (&ns->default_type[letter],
14213                                       &ns->implicit_loc[letter],
14214                                       NULL) == FAILURE)
14215           return;
14216     }
14217
14218   gfc_current_ns = ns;
14219
14220   resolve_entries (ns);
14221
14222   resolve_common_vars (ns->blank_common.head, false);
14223   resolve_common_blocks (ns->common_root);
14224
14225   resolve_contained_functions (ns);
14226
14227   if (ns->proc_name && ns->proc_name->attr.flavor == FL_PROCEDURE
14228       && ns->proc_name->attr.if_source == IFSRC_IFBODY)
14229     resolve_formal_arglist (ns->proc_name);
14230
14231   gfc_traverse_ns (ns, resolve_bind_c_derived_types);
14232
14233   for (cl = ns->cl_list; cl; cl = cl->next)
14234     resolve_charlen (cl);
14235
14236   gfc_traverse_ns (ns, resolve_symbol);
14237
14238   resolve_fntype (ns);
14239
14240   for (n = ns->contained; n; n = n->sibling)
14241     {
14242       if (gfc_pure (ns->proc_name) && !gfc_pure (n->proc_name))
14243         gfc_error ("Contained procedure '%s' at %L of a PURE procedure must "
14244                    "also be PURE", n->proc_name->name,
14245                    &n->proc_name->declared_at);
14246
14247       resolve_types (n);
14248     }
14249
14250   forall_flag = 0;
14251   do_concurrent_flag = 0;
14252   gfc_check_interfaces (ns);
14253
14254   gfc_traverse_ns (ns, resolve_values);
14255
14256   if (ns->save_all)
14257     gfc_save_all (ns);
14258
14259   iter_stack = NULL;
14260   for (d = ns->data; d; d = d->next)
14261     resolve_data (d);
14262
14263   iter_stack = NULL;
14264   gfc_traverse_ns (ns, gfc_formalize_init_value);
14265
14266   gfc_traverse_ns (ns, gfc_verify_binding_labels);
14267
14268   if (ns->common_root != NULL)
14269     gfc_traverse_symtree (ns->common_root, resolve_bind_c_comms);
14270
14271   for (eq = ns->equiv; eq; eq = eq->next)
14272     resolve_equivalence (eq);
14273
14274   /* Warn about unused labels.  */
14275   if (warn_unused_label)
14276     warn_unused_fortran_label (ns->st_labels);
14277
14278   gfc_resolve_uops (ns->uop_root);
14279
14280   gfc_current_ns = old_ns;
14281 }
14282
14283
14284 /* Call resolve_code recursively.  */
14285
14286 static void
14287 resolve_codes (gfc_namespace *ns)
14288 {
14289   gfc_namespace *n;
14290   bitmap_obstack old_obstack;
14291
14292   if (ns->resolved == 1)
14293     return;
14294
14295   for (n = ns->contained; n; n = n->sibling)
14296     resolve_codes (n);
14297
14298   gfc_current_ns = ns;
14299
14300   /* Don't clear 'cs_base' if this is the namespace of a BLOCK construct.  */
14301   if (!(ns->proc_name && ns->proc_name->attr.flavor == FL_LABEL))
14302     cs_base = NULL;
14303
14304   /* Set to an out of range value.  */
14305   current_entry_id = -1;
14306
14307   old_obstack = labels_obstack;
14308   bitmap_obstack_initialize (&labels_obstack);
14309
14310   resolve_code (ns->code, ns);
14311
14312   bitmap_obstack_release (&labels_obstack);
14313   labels_obstack = old_obstack;
14314 }
14315
14316
14317 /* This function is called after a complete program unit has been compiled.
14318    Its purpose is to examine all of the expressions associated with a program
14319    unit, assign types to all intermediate expressions, make sure that all
14320    assignments are to compatible types and figure out which names refer to
14321    which functions or subroutines.  */
14322
14323 void
14324 gfc_resolve (gfc_namespace *ns)
14325 {
14326   gfc_namespace *old_ns;
14327   code_stack *old_cs_base;
14328
14329   if (ns->resolved)
14330     return;
14331
14332   ns->resolved = -1;
14333   old_ns = gfc_current_ns;
14334   old_cs_base = cs_base;
14335
14336   resolve_types (ns);
14337   resolve_codes (ns);
14338
14339   gfc_current_ns = old_ns;
14340   cs_base = old_cs_base;
14341   ns->resolved = 1;
14342
14343   gfc_run_passes (ns);
14344 }