OSDN Git Service

2012-06-04 Tobias Burnus <burnus@net-b.de>
[pf3gnuchains/gcc-fork.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 "flags.h"
26 #include "gfortran.h"
27 #include "obstack.h"
28 #include "bitmap.h"
29 #include "arith.h"  /* For gfc_compare_expr().  */
30 #include "dependency.h"
31 #include "data.h"
32 #include "target-memory.h" /* for gfc_simplify_transfer */
33 #include "constructor.h"
34
35 /* Types used in equivalence statements.  */
36
37 typedef enum seq_type
38 {
39   SEQ_NONDEFAULT, SEQ_NUMERIC, SEQ_CHARACTER, SEQ_MIXED
40 }
41 seq_type;
42
43 /* Stack to keep track of the nesting of blocks as we move through the
44    code.  See resolve_branch() and resolve_code().  */
45
46 typedef struct code_stack
47 {
48   struct gfc_code *head, *current;
49   struct code_stack *prev;
50
51   /* This bitmap keeps track of the targets valid for a branch from
52      inside this block except for END {IF|SELECT}s of enclosing
53      blocks.  */
54   bitmap reachable_labels;
55 }
56 code_stack;
57
58 static code_stack *cs_base = NULL;
59
60
61 /* Nonzero if we're inside a FORALL or DO CONCURRENT block.  */
62
63 static int forall_flag;
64 static int do_concurrent_flag;
65
66 static bool assumed_type_expr_allowed = false;
67
68 /* Nonzero if we're inside a OpenMP WORKSHARE or PARALLEL WORKSHARE block.  */
69
70 static int omp_workshare_flag;
71
72 /* Nonzero if we are processing a formal arglist. The corresponding function
73    resets the flag each time that it is read.  */
74 static int formal_arg_flag = 0;
75
76 /* True if we are resolving a specification expression.  */
77 static int specification_expr = 0;
78
79 /* The id of the last entry seen.  */
80 static int current_entry_id;
81
82 /* We use bitmaps to determine if a branch target is valid.  */
83 static bitmap_obstack labels_obstack;
84
85 /* True when simplifying a EXPR_VARIABLE argument to an inquiry function.  */
86 static bool inquiry_argument = false;
87
88 int
89 gfc_is_formal_arg (void)
90 {
91   return formal_arg_flag;
92 }
93
94 /* Is the symbol host associated?  */
95 static bool
96 is_sym_host_assoc (gfc_symbol *sym, gfc_namespace *ns)
97 {
98   for (ns = ns->parent; ns; ns = ns->parent)
99     {      
100       if (sym->ns == ns)
101         return true;
102     }
103
104   return false;
105 }
106
107 /* Ensure a typespec used is valid; for instance, TYPE(t) is invalid if t is
108    an ABSTRACT derived-type.  If where is not NULL, an error message with that
109    locus is printed, optionally using name.  */
110
111 static gfc_try
112 resolve_typespec_used (gfc_typespec* ts, locus* where, const char* name)
113 {
114   if (ts->type == BT_DERIVED && ts->u.derived->attr.abstract)
115     {
116       if (where)
117         {
118           if (name)
119             gfc_error ("'%s' at %L is of the ABSTRACT type '%s'",
120                        name, where, ts->u.derived->name);
121           else
122             gfc_error ("ABSTRACT type '%s' used at %L",
123                        ts->u.derived->name, where);
124         }
125
126       return FAILURE;
127     }
128
129   return SUCCESS;
130 }
131
132
133 static void resolve_symbol (gfc_symbol *sym);
134 static gfc_try resolve_intrinsic (gfc_symbol *sym, locus *loc);
135
136
137 /* Resolve the interface for a PROCEDURE declaration or procedure pointer.  */
138
139 static gfc_try
140 resolve_procedure_interface (gfc_symbol *sym)
141 {
142   if (sym->ts.interface == sym)
143     {
144       gfc_error ("PROCEDURE '%s' at %L may not be used as its own interface",
145                  sym->name, &sym->declared_at);
146       return FAILURE;
147     }
148   if (sym->ts.interface->attr.procedure)
149     {
150       gfc_error ("Interface '%s', used by procedure '%s' at %L, is declared "
151                  "in a later PROCEDURE statement", sym->ts.interface->name,
152                  sym->name, &sym->declared_at);
153       return FAILURE;
154     }
155
156   /* Get the attributes from the interface (now resolved).  */
157   if (sym->ts.interface->attr.if_source || sym->ts.interface->attr.intrinsic)
158     {
159       gfc_symbol *ifc = sym->ts.interface;
160       resolve_symbol (ifc);
161
162       if (ifc->attr.intrinsic)
163         resolve_intrinsic (ifc, &ifc->declared_at);
164
165       if (ifc->result)
166         {
167           sym->ts = ifc->result->ts;
168           sym->result = sym;
169         }
170       else   
171         sym->ts = ifc->ts;
172       sym->ts.interface = ifc;
173       sym->attr.function = ifc->attr.function;
174       sym->attr.subroutine = ifc->attr.subroutine;
175       gfc_copy_formal_args (sym, ifc);
176
177       sym->attr.allocatable = ifc->attr.allocatable;
178       sym->attr.pointer = ifc->attr.pointer;
179       sym->attr.pure = ifc->attr.pure;
180       sym->attr.elemental = ifc->attr.elemental;
181       sym->attr.dimension = ifc->attr.dimension;
182       sym->attr.contiguous = ifc->attr.contiguous;
183       sym->attr.recursive = ifc->attr.recursive;
184       sym->attr.always_explicit = ifc->attr.always_explicit;
185       sym->attr.ext_attr |= ifc->attr.ext_attr;
186       sym->attr.is_bind_c = ifc->attr.is_bind_c;
187       /* Copy array spec.  */
188       sym->as = gfc_copy_array_spec (ifc->as);
189       if (sym->as)
190         {
191           int i;
192           for (i = 0; i < sym->as->rank; i++)
193             {
194               gfc_expr_replace_symbols (sym->as->lower[i], sym);
195               gfc_expr_replace_symbols (sym->as->upper[i], sym);
196             }
197         }
198       /* Copy char length.  */
199       if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
200         {
201           sym->ts.u.cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
202           gfc_expr_replace_symbols (sym->ts.u.cl->length, sym);
203           if (sym->ts.u.cl->length && !sym->ts.u.cl->resolved
204               && gfc_resolve_expr (sym->ts.u.cl->length) == FAILURE)
205             return FAILURE;
206         }
207     }
208   else if (sym->ts.interface->name[0] != '\0')
209     {
210       gfc_error ("Interface '%s' of procedure '%s' at %L must be explicit",
211                  sym->ts.interface->name, sym->name, &sym->declared_at);
212       return FAILURE;
213     }
214
215   return SUCCESS;
216 }
217
218
219 /* Resolve types of formal argument lists.  These have to be done early so that
220    the formal argument lists of module procedures can be copied to the
221    containing module before the individual procedures are resolved
222    individually.  We also resolve argument lists of procedures in interface
223    blocks because they are self-contained scoping units.
224
225    Since a dummy argument cannot be a non-dummy procedure, the only
226    resort left for untyped names are the IMPLICIT types.  */
227
228 static void
229 resolve_formal_arglist (gfc_symbol *proc)
230 {
231   gfc_formal_arglist *f;
232   gfc_symbol *sym;
233   int i;
234
235   if (proc->result != NULL)
236     sym = proc->result;
237   else
238     sym = proc;
239
240   if (gfc_elemental (proc)
241       || sym->attr.pointer || sym->attr.allocatable
242       || (sym->as && sym->as->rank > 0))
243     {
244       proc->attr.always_explicit = 1;
245       sym->attr.always_explicit = 1;
246     }
247
248   formal_arg_flag = 1;
249
250   for (f = proc->formal; f; f = f->next)
251     {
252       sym = f->sym;
253
254       if (sym == NULL)
255         {
256           /* Alternate return placeholder.  */
257           if (gfc_elemental (proc))
258             gfc_error ("Alternate return specifier in elemental subroutine "
259                        "'%s' at %L is not allowed", proc->name,
260                        &proc->declared_at);
261           if (proc->attr.function)
262             gfc_error ("Alternate return specifier in function "
263                        "'%s' at %L is not allowed", proc->name,
264                        &proc->declared_at);
265           continue;
266         }
267       else if (sym->attr.procedure && sym->ts.interface
268                && sym->attr.if_source != IFSRC_DECL)
269         resolve_procedure_interface (sym);
270
271       if (sym->attr.if_source != IFSRC_UNKNOWN)
272         resolve_formal_arglist (sym);
273
274       if (sym->attr.subroutine || sym->attr.external)
275         {
276           if (sym->attr.flavor == FL_UNKNOWN)
277             gfc_add_flavor (&sym->attr, FL_PROCEDURE, sym->name, &sym->declared_at);
278         }
279       else
280         {
281           if (sym->ts.type == BT_UNKNOWN && !proc->attr.intrinsic
282               && (!sym->attr.function || sym->result == sym))
283             gfc_set_default_type (sym, 1, sym->ns);
284         }
285
286       gfc_resolve_array_spec (sym->as, 0);
287
288       /* We can't tell if an array with dimension (:) is assumed or deferred
289          shape until we know if it has the pointer or allocatable attributes.
290       */
291       if (sym->as && sym->as->rank > 0 && sym->as->type == AS_DEFERRED
292           && !(sym->attr.pointer || sym->attr.allocatable)
293           && sym->attr.flavor != FL_PROCEDURE)
294         {
295           sym->as->type = AS_ASSUMED_SHAPE;
296           for (i = 0; i < sym->as->rank; i++)
297             sym->as->lower[i] = gfc_get_int_expr (gfc_default_integer_kind,
298                                                   NULL, 1);
299         }
300
301       if ((sym->as && sym->as->rank > 0 && sym->as->type == AS_ASSUMED_SHAPE)
302           || sym->attr.pointer || sym->attr.allocatable || sym->attr.target
303           || sym->attr.optional)
304         {
305           proc->attr.always_explicit = 1;
306           if (proc->result)
307             proc->result->attr.always_explicit = 1;
308         }
309
310       /* If the flavor is unknown at this point, it has to be a variable.
311          A procedure specification would have already set the type.  */
312
313       if (sym->attr.flavor == FL_UNKNOWN)
314         gfc_add_flavor (&sym->attr, FL_VARIABLE, sym->name, &sym->declared_at);
315
316       if (gfc_pure (proc))
317         {
318           if (sym->attr.flavor == FL_PROCEDURE)
319             {
320               /* F08:C1279.  */
321               if (!gfc_pure (sym))
322                 {
323                   gfc_error ("Dummy procedure '%s' of PURE procedure at %L must "
324                             "also be PURE", sym->name, &sym->declared_at);
325                   continue;
326                 }
327             }
328           else if (!sym->attr.pointer)
329             {
330               if (proc->attr.function && sym->attr.intent != INTENT_IN)
331                 {
332                   if (sym->attr.value)
333                     gfc_notify_std (GFC_STD_F2008, "Fortran 2008: Argument '%s'"
334                                     " of pure function '%s' at %L with VALUE "
335                                     "attribute but without INTENT(IN)",
336                                     sym->name, proc->name, &sym->declared_at);
337                   else
338                     gfc_error ("Argument '%s' of pure function '%s' at %L must "
339                                "be INTENT(IN) or VALUE", sym->name, proc->name,
340                                &sym->declared_at);
341                 }
342
343               if (proc->attr.subroutine && sym->attr.intent == INTENT_UNKNOWN)
344                 {
345                   if (sym->attr.value)
346                     gfc_notify_std (GFC_STD_F2008, "Fortran 2008: Argument '%s'"
347                                     " of pure subroutine '%s' at %L with VALUE "
348                                     "attribute but without INTENT", sym->name,
349                                     proc->name, &sym->declared_at);
350                   else
351                     gfc_error ("Argument '%s' of pure subroutine '%s' at %L "
352                                "must have its INTENT specified or have the "
353                                "VALUE attribute", sym->name, proc->name,
354                                &sym->declared_at);
355                 }
356             }
357         }
358
359       if (proc->attr.implicit_pure)
360         {
361           if (sym->attr.flavor == FL_PROCEDURE)
362             {
363               if (!gfc_pure(sym))
364                 proc->attr.implicit_pure = 0;
365             }
366           else if (!sym->attr.pointer)
367             {
368               if (proc->attr.function && sym->attr.intent != INTENT_IN)
369                 proc->attr.implicit_pure = 0;
370
371               if (proc->attr.subroutine && sym->attr.intent == INTENT_UNKNOWN)
372                 proc->attr.implicit_pure = 0;
373             }
374         }
375
376       if (gfc_elemental (proc))
377         {
378           /* F08:C1289.  */
379           if (sym->attr.codimension
380               || (sym->ts.type == BT_CLASS && CLASS_DATA (sym)
381                   && CLASS_DATA (sym)->attr.codimension))
382             {
383               gfc_error ("Coarray dummy argument '%s' at %L to elemental "
384                          "procedure", sym->name, &sym->declared_at);
385               continue;
386             }
387
388           if (sym->as || (sym->ts.type == BT_CLASS && CLASS_DATA (sym)
389                           && CLASS_DATA (sym)->as))
390             {
391               gfc_error ("Argument '%s' of elemental procedure at %L must "
392                          "be scalar", sym->name, &sym->declared_at);
393               continue;
394             }
395
396           if (sym->attr.allocatable
397               || (sym->ts.type == BT_CLASS && CLASS_DATA (sym)
398                   && CLASS_DATA (sym)->attr.allocatable))
399             {
400               gfc_error ("Argument '%s' of elemental procedure at %L cannot "
401                          "have the ALLOCATABLE attribute", sym->name,
402                          &sym->declared_at);
403               continue;
404             }
405
406           if (sym->attr.pointer
407               || (sym->ts.type == BT_CLASS && CLASS_DATA (sym)
408                   && CLASS_DATA (sym)->attr.class_pointer))
409             {
410               gfc_error ("Argument '%s' of elemental procedure at %L cannot "
411                          "have the POINTER attribute", sym->name,
412                          &sym->declared_at);
413               continue;
414             }
415
416           if (sym->attr.flavor == FL_PROCEDURE)
417             {
418               gfc_error ("Dummy procedure '%s' not allowed in elemental "
419                          "procedure '%s' at %L", sym->name, proc->name,
420                          &sym->declared_at);
421               continue;
422             }
423
424           if (sym->attr.intent == INTENT_UNKNOWN)
425             {
426               gfc_error ("Argument '%s' of elemental procedure '%s' at %L must "
427                          "have its INTENT specified", sym->name, proc->name,
428                          &sym->declared_at);
429               continue;
430             }
431         }
432
433       /* Each dummy shall be specified to be scalar.  */
434       if (proc->attr.proc == PROC_ST_FUNCTION)
435         {
436           if (sym->as != NULL)
437             {
438               gfc_error ("Argument '%s' of statement function at %L must "
439                          "be scalar", sym->name, &sym->declared_at);
440               continue;
441             }
442
443           if (sym->ts.type == BT_CHARACTER)
444             {
445               gfc_charlen *cl = sym->ts.u.cl;
446               if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
447                 {
448                   gfc_error ("Character-valued argument '%s' of statement "
449                              "function at %L must have constant length",
450                              sym->name, &sym->declared_at);
451                   continue;
452                 }
453             }
454         }
455     }
456   formal_arg_flag = 0;
457 }
458
459
460 /* Work function called when searching for symbols that have argument lists
461    associated with them.  */
462
463 static void
464 find_arglists (gfc_symbol *sym)
465 {
466   if (sym->attr.if_source == IFSRC_UNKNOWN || sym->ns != gfc_current_ns
467       || sym->attr.flavor == FL_DERIVED)
468     return;
469
470   resolve_formal_arglist (sym);
471 }
472
473
474 /* Given a namespace, resolve all formal argument lists within the namespace.
475  */
476
477 static void
478 resolve_formal_arglists (gfc_namespace *ns)
479 {
480   if (ns == NULL)
481     return;
482
483   gfc_traverse_ns (ns, find_arglists);
484 }
485
486
487 static void
488 resolve_contained_fntype (gfc_symbol *sym, gfc_namespace *ns)
489 {
490   gfc_try t;
491
492   /* If this namespace is not a function or an entry master function,
493      ignore it.  */
494   if (! sym || !(sym->attr.function || sym->attr.flavor == FL_VARIABLE)
495       || sym->attr.entry_master)
496     return;
497
498   /* Try to find out of what the return type is.  */
499   if (sym->result->ts.type == BT_UNKNOWN && sym->result->ts.interface == NULL)
500     {
501       t = gfc_set_default_type (sym->result, 0, ns);
502
503       if (t == FAILURE && !sym->result->attr.untyped)
504         {
505           if (sym->result == sym)
506             gfc_error ("Contained function '%s' at %L has no IMPLICIT type",
507                        sym->name, &sym->declared_at);
508           else if (!sym->result->attr.proc_pointer)
509             gfc_error ("Result '%s' of contained function '%s' at %L has "
510                        "no IMPLICIT type", sym->result->name, sym->name,
511                        &sym->result->declared_at);
512           sym->result->attr.untyped = 1;
513         }
514     }
515
516   /* Fortran 95 Draft Standard, page 51, Section 5.1.1.5, on the Character 
517      type, lists the only ways a character length value of * can be used:
518      dummy arguments of procedures, named constants, and function results
519      in external functions.  Internal function results and results of module
520      procedures are not on this list, ergo, not permitted.  */
521
522   if (sym->result->ts.type == BT_CHARACTER)
523     {
524       gfc_charlen *cl = sym->result->ts.u.cl;
525       if ((!cl || !cl->length) && !sym->result->ts.deferred)
526         {
527           /* See if this is a module-procedure and adapt error message
528              accordingly.  */
529           bool module_proc;
530           gcc_assert (ns->parent && ns->parent->proc_name);
531           module_proc = (ns->parent->proc_name->attr.flavor == FL_MODULE);
532
533           gfc_error ("Character-valued %s '%s' at %L must not be"
534                      " assumed length",
535                      module_proc ? _("module procedure")
536                                  : _("internal function"),
537                      sym->name, &sym->declared_at);
538         }
539     }
540 }
541
542
543 /* Add NEW_ARGS to the formal argument list of PROC, taking care not to
544    introduce duplicates.  */
545
546 static void
547 merge_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
548 {
549   gfc_formal_arglist *f, *new_arglist;
550   gfc_symbol *new_sym;
551
552   for (; new_args != NULL; new_args = new_args->next)
553     {
554       new_sym = new_args->sym;
555       /* See if this arg is already in the formal argument list.  */
556       for (f = proc->formal; f; f = f->next)
557         {
558           if (new_sym == f->sym)
559             break;
560         }
561
562       if (f)
563         continue;
564
565       /* Add a new argument.  Argument order is not important.  */
566       new_arglist = gfc_get_formal_arglist ();
567       new_arglist->sym = new_sym;
568       new_arglist->next = proc->formal;
569       proc->formal  = new_arglist;
570     }
571 }
572
573
574 /* Flag the arguments that are not present in all entries.  */
575
576 static void
577 check_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
578 {
579   gfc_formal_arglist *f, *head;
580   head = new_args;
581
582   for (f = proc->formal; f; f = f->next)
583     {
584       if (f->sym == NULL)
585         continue;
586
587       for (new_args = head; new_args; new_args = new_args->next)
588         {
589           if (new_args->sym == f->sym)
590             break;
591         }
592
593       if (new_args)
594         continue;
595
596       f->sym->attr.not_always_present = 1;
597     }
598 }
599
600
601 /* Resolve alternate entry points.  If a symbol has multiple entry points we
602    create a new master symbol for the main routine, and turn the existing
603    symbol into an entry point.  */
604
605 static void
606 resolve_entries (gfc_namespace *ns)
607 {
608   gfc_namespace *old_ns;
609   gfc_code *c;
610   gfc_symbol *proc;
611   gfc_entry_list *el;
612   char name[GFC_MAX_SYMBOL_LEN + 1];
613   static int master_count = 0;
614
615   if (ns->proc_name == NULL)
616     return;
617
618   /* No need to do anything if this procedure doesn't have alternate entry
619      points.  */
620   if (!ns->entries)
621     return;
622
623   /* We may already have resolved alternate entry points.  */
624   if (ns->proc_name->attr.entry_master)
625     return;
626
627   /* If this isn't a procedure something has gone horribly wrong.  */
628   gcc_assert (ns->proc_name->attr.flavor == FL_PROCEDURE);
629
630   /* Remember the current namespace.  */
631   old_ns = gfc_current_ns;
632
633   gfc_current_ns = ns;
634
635   /* Add the main entry point to the list of entry points.  */
636   el = gfc_get_entry_list ();
637   el->sym = ns->proc_name;
638   el->id = 0;
639   el->next = ns->entries;
640   ns->entries = el;
641   ns->proc_name->attr.entry = 1;
642
643   /* If it is a module function, it needs to be in the right namespace
644      so that gfc_get_fake_result_decl can gather up the results. The
645      need for this arose in get_proc_name, where these beasts were
646      left in their own namespace, to keep prior references linked to
647      the entry declaration.*/
648   if (ns->proc_name->attr.function
649       && ns->parent && ns->parent->proc_name->attr.flavor == FL_MODULE)
650     el->sym->ns = ns;
651
652   /* Do the same for entries where the master is not a module
653      procedure.  These are retained in the module namespace because
654      of the module procedure declaration.  */
655   for (el = el->next; el; el = el->next)
656     if (el->sym->ns->proc_name->attr.flavor == FL_MODULE
657           && el->sym->attr.mod_proc)
658       el->sym->ns = ns;
659   el = ns->entries;
660
661   /* Add an entry statement for it.  */
662   c = gfc_get_code ();
663   c->op = EXEC_ENTRY;
664   c->ext.entry = el;
665   c->next = ns->code;
666   ns->code = c;
667
668   /* Create a new symbol for the master function.  */
669   /* Give the internal function a unique name (within this file).
670      Also include the function name so the user has some hope of figuring
671      out what is going on.  */
672   snprintf (name, GFC_MAX_SYMBOL_LEN, "master.%d.%s",
673             master_count++, ns->proc_name->name);
674   gfc_get_ha_symbol (name, &proc);
675   gcc_assert (proc != NULL);
676
677   gfc_add_procedure (&proc->attr, PROC_INTERNAL, proc->name, NULL);
678   if (ns->proc_name->attr.subroutine)
679     gfc_add_subroutine (&proc->attr, proc->name, NULL);
680   else
681     {
682       gfc_symbol *sym;
683       gfc_typespec *ts, *fts;
684       gfc_array_spec *as, *fas;
685       gfc_add_function (&proc->attr, proc->name, NULL);
686       proc->result = proc;
687       fas = ns->entries->sym->as;
688       fas = fas ? fas : ns->entries->sym->result->as;
689       fts = &ns->entries->sym->result->ts;
690       if (fts->type == BT_UNKNOWN)
691         fts = gfc_get_default_type (ns->entries->sym->result->name, NULL);
692       for (el = ns->entries->next; el; el = el->next)
693         {
694           ts = &el->sym->result->ts;
695           as = el->sym->as;
696           as = as ? as : el->sym->result->as;
697           if (ts->type == BT_UNKNOWN)
698             ts = gfc_get_default_type (el->sym->result->name, NULL);
699
700           if (! gfc_compare_types (ts, fts)
701               || (el->sym->result->attr.dimension
702                   != ns->entries->sym->result->attr.dimension)
703               || (el->sym->result->attr.pointer
704                   != ns->entries->sym->result->attr.pointer))
705             break;
706           else if (as && fas && ns->entries->sym->result != el->sym->result
707                       && gfc_compare_array_spec (as, fas) == 0)
708             gfc_error ("Function %s at %L has entries with mismatched "
709                        "array specifications", ns->entries->sym->name,
710                        &ns->entries->sym->declared_at);
711           /* The characteristics need to match and thus both need to have
712              the same string length, i.e. both len=*, or both len=4.
713              Having both len=<variable> is also possible, but difficult to
714              check at compile time.  */
715           else if (ts->type == BT_CHARACTER && ts->u.cl && fts->u.cl
716                    && (((ts->u.cl->length && !fts->u.cl->length)
717                         ||(!ts->u.cl->length && fts->u.cl->length))
718                        || (ts->u.cl->length
719                            && ts->u.cl->length->expr_type
720                               != fts->u.cl->length->expr_type)
721                        || (ts->u.cl->length
722                            && ts->u.cl->length->expr_type == EXPR_CONSTANT
723                            && mpz_cmp (ts->u.cl->length->value.integer,
724                                        fts->u.cl->length->value.integer) != 0)))
725             gfc_notify_std (GFC_STD_GNU, "Extension: Function %s at %L with "
726                             "entries returning variables of different "
727                             "string lengths", ns->entries->sym->name,
728                             &ns->entries->sym->declared_at);
729         }
730
731       if (el == NULL)
732         {
733           sym = ns->entries->sym->result;
734           /* All result types the same.  */
735           proc->ts = *fts;
736           if (sym->attr.dimension)
737             gfc_set_array_spec (proc, gfc_copy_array_spec (sym->as), NULL);
738           if (sym->attr.pointer)
739             gfc_add_pointer (&proc->attr, NULL);
740         }
741       else
742         {
743           /* Otherwise the result will be passed through a union by
744              reference.  */
745           proc->attr.mixed_entry_master = 1;
746           for (el = ns->entries; el; el = el->next)
747             {
748               sym = el->sym->result;
749               if (sym->attr.dimension)
750                 {
751                   if (el == ns->entries)
752                     gfc_error ("FUNCTION result %s can't be an array in "
753                                "FUNCTION %s at %L", sym->name,
754                                ns->entries->sym->name, &sym->declared_at);
755                   else
756                     gfc_error ("ENTRY result %s can't be an array in "
757                                "FUNCTION %s at %L", sym->name,
758                                ns->entries->sym->name, &sym->declared_at);
759                 }
760               else if (sym->attr.pointer)
761                 {
762                   if (el == ns->entries)
763                     gfc_error ("FUNCTION result %s can't be a POINTER in "
764                                "FUNCTION %s at %L", sym->name,
765                                ns->entries->sym->name, &sym->declared_at);
766                   else
767                     gfc_error ("ENTRY result %s can't be a POINTER in "
768                                "FUNCTION %s at %L", sym->name,
769                                ns->entries->sym->name, &sym->declared_at);
770                 }
771               else
772                 {
773                   ts = &sym->ts;
774                   if (ts->type == BT_UNKNOWN)
775                     ts = gfc_get_default_type (sym->name, NULL);
776                   switch (ts->type)
777                     {
778                     case BT_INTEGER:
779                       if (ts->kind == gfc_default_integer_kind)
780                         sym = NULL;
781                       break;
782                     case BT_REAL:
783                       if (ts->kind == gfc_default_real_kind
784                           || ts->kind == gfc_default_double_kind)
785                         sym = NULL;
786                       break;
787                     case BT_COMPLEX:
788                       if (ts->kind == gfc_default_complex_kind)
789                         sym = NULL;
790                       break;
791                     case BT_LOGICAL:
792                       if (ts->kind == gfc_default_logical_kind)
793                         sym = NULL;
794                       break;
795                     case BT_UNKNOWN:
796                       /* We will issue error elsewhere.  */
797                       sym = NULL;
798                       break;
799                     default:
800                       break;
801                     }
802                   if (sym)
803                     {
804                       if (el == ns->entries)
805                         gfc_error ("FUNCTION result %s can't be of type %s "
806                                    "in FUNCTION %s at %L", sym->name,
807                                    gfc_typename (ts), ns->entries->sym->name,
808                                    &sym->declared_at);
809                       else
810                         gfc_error ("ENTRY result %s can't be of type %s "
811                                    "in FUNCTION %s at %L", sym->name,
812                                    gfc_typename (ts), ns->entries->sym->name,
813                                    &sym->declared_at);
814                     }
815                 }
816             }
817         }
818     }
819   proc->attr.access = ACCESS_PRIVATE;
820   proc->attr.entry_master = 1;
821
822   /* Merge all the entry point arguments.  */
823   for (el = ns->entries; el; el = el->next)
824     merge_argument_lists (proc, el->sym->formal);
825
826   /* Check the master formal arguments for any that are not
827      present in all entry points.  */
828   for (el = ns->entries; el; el = el->next)
829     check_argument_lists (proc, el->sym->formal);
830
831   /* Use the master function for the function body.  */
832   ns->proc_name = proc;
833
834   /* Finalize the new symbols.  */
835   gfc_commit_symbols ();
836
837   /* Restore the original namespace.  */
838   gfc_current_ns = old_ns;
839 }
840
841
842 /* Resolve common variables.  */
843 static void
844 resolve_common_vars (gfc_symbol *sym, bool named_common)
845 {
846   gfc_symbol *csym = sym;
847
848   for (; csym; csym = csym->common_next)
849     {
850       if (csym->value || csym->attr.data)
851         {
852           if (!csym->ns->is_block_data)
853             gfc_notify_std (GFC_STD_GNU, "Variable '%s' at %L is in COMMON "
854                             "but only in BLOCK DATA initialization is "
855                             "allowed", csym->name, &csym->declared_at);
856           else if (!named_common)
857             gfc_notify_std (GFC_STD_GNU, "Initialized variable '%s' at %L is "
858                             "in a blank COMMON but initialization is only "
859                             "allowed in named common blocks", csym->name,
860                             &csym->declared_at);
861         }
862
863       if (csym->ts.type != BT_DERIVED)
864         continue;
865
866       if (!(csym->ts.u.derived->attr.sequence
867             || csym->ts.u.derived->attr.is_bind_c))
868         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
869                        "has neither the SEQUENCE nor the BIND(C) "
870                        "attribute", csym->name, &csym->declared_at);
871       if (csym->ts.u.derived->attr.alloc_comp)
872         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
873                        "has an ultimate component that is "
874                        "allocatable", csym->name, &csym->declared_at);
875       if (gfc_has_default_initializer (csym->ts.u.derived))
876         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
877                        "may not have default initializer", csym->name,
878                        &csym->declared_at);
879
880       if (csym->attr.flavor == FL_UNKNOWN && !csym->attr.proc_pointer)
881         gfc_add_flavor (&csym->attr, FL_VARIABLE, csym->name, &csym->declared_at);
882     }
883 }
884
885 /* Resolve common blocks.  */
886 static void
887 resolve_common_blocks (gfc_symtree *common_root)
888 {
889   gfc_symbol *sym;
890
891   if (common_root == NULL)
892     return;
893
894   if (common_root->left)
895     resolve_common_blocks (common_root->left);
896   if (common_root->right)
897     resolve_common_blocks (common_root->right);
898
899   resolve_common_vars (common_root->n.common->head, true);
900
901   gfc_find_symbol (common_root->name, gfc_current_ns, 0, &sym);
902   if (sym == NULL)
903     return;
904
905   if (sym->attr.flavor == FL_PARAMETER)
906     gfc_error ("COMMON block '%s' at %L is used as PARAMETER at %L",
907                sym->name, &common_root->n.common->where, &sym->declared_at);
908
909   if (sym->attr.external)
910     gfc_error ("COMMON block '%s' at %L can not have the EXTERNAL attribute",
911                sym->name, &common_root->n.common->where);
912
913   if (sym->attr.intrinsic)
914     gfc_error ("COMMON block '%s' at %L is also an intrinsic procedure",
915                sym->name, &common_root->n.common->where);
916   else if (sym->attr.result
917            || gfc_is_function_return_value (sym, gfc_current_ns))
918     gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
919                     "that is also a function result", sym->name,
920                     &common_root->n.common->where);
921   else if (sym->attr.flavor == FL_PROCEDURE && sym->attr.proc != PROC_INTERNAL
922            && sym->attr.proc != PROC_ST_FUNCTION)
923     gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
924                     "that is also a global procedure", sym->name,
925                     &common_root->n.common->where);
926 }
927
928
929 /* Resolve contained function types.  Because contained functions can call one
930    another, they have to be worked out before any of the contained procedures
931    can be resolved.
932
933    The good news is that if a function doesn't already have a type, the only
934    way it can get one is through an IMPLICIT type or a RESULT variable, because
935    by definition contained functions are contained namespace they're contained
936    in, not in a sibling or parent namespace.  */
937
938 static void
939 resolve_contained_functions (gfc_namespace *ns)
940 {
941   gfc_namespace *child;
942   gfc_entry_list *el;
943
944   resolve_formal_arglists (ns);
945
946   for (child = ns->contained; child; child = child->sibling)
947     {
948       /* Resolve alternate entry points first.  */
949       resolve_entries (child);
950
951       /* Then check function return types.  */
952       resolve_contained_fntype (child->proc_name, child);
953       for (el = child->entries; el; el = el->next)
954         resolve_contained_fntype (el->sym, child);
955     }
956 }
957
958
959 static gfc_try resolve_fl_derived0 (gfc_symbol *sym);
960
961
962 /* Resolve all of the elements of a structure constructor and make sure that
963    the types are correct. The 'init' flag indicates that the given
964    constructor is an initializer.  */
965
966 static gfc_try
967 resolve_structure_cons (gfc_expr *expr, int init)
968 {
969   gfc_constructor *cons;
970   gfc_component *comp;
971   gfc_try t;
972   symbol_attribute a;
973
974   t = SUCCESS;
975
976   if (expr->ts.type == BT_DERIVED)
977     resolve_fl_derived0 (expr->ts.u.derived);
978
979   cons = gfc_constructor_first (expr->value.constructor);
980
981   /* See if the user is trying to invoke a structure constructor for one of
982      the iso_c_binding derived types.  */
983   if (expr->ts.type == BT_DERIVED && expr->ts.u.derived
984       && expr->ts.u.derived->ts.is_iso_c && cons
985       && (cons->expr == NULL || cons->expr->expr_type != EXPR_NULL))
986     {
987       gfc_error ("Components of structure constructor '%s' at %L are PRIVATE",
988                  expr->ts.u.derived->name, &(expr->where));
989       return FAILURE;
990     }
991
992   /* Return if structure constructor is c_null_(fun)prt.  */
993   if (expr->ts.type == BT_DERIVED && expr->ts.u.derived
994       && expr->ts.u.derived->ts.is_iso_c && cons
995       && cons->expr && cons->expr->expr_type == EXPR_NULL)
996     return SUCCESS;
997
998   /* A constructor may have references if it is the result of substituting a
999      parameter variable.  In this case we just pull out the component we
1000      want.  */
1001   if (expr->ref)
1002     comp = expr->ref->u.c.sym->components;
1003   else
1004     comp = expr->ts.u.derived->components;
1005
1006   for (; comp && cons; comp = comp->next, cons = gfc_constructor_next (cons))
1007     {
1008       int rank;
1009
1010       if (!cons->expr)
1011         continue;
1012
1013       if (gfc_resolve_expr (cons->expr) == FAILURE)
1014         {
1015           t = FAILURE;
1016           continue;
1017         }
1018
1019       rank = comp->as ? comp->as->rank : 0;
1020       if (cons->expr->expr_type != EXPR_NULL && rank != cons->expr->rank
1021           && (comp->attr.allocatable || cons->expr->rank))
1022         {
1023           gfc_error ("The rank of the element in the structure "
1024                      "constructor at %L does not match that of the "
1025                      "component (%d/%d)", &cons->expr->where,
1026                      cons->expr->rank, rank);
1027           t = FAILURE;
1028         }
1029
1030       /* If we don't have the right type, try to convert it.  */
1031
1032       if (!comp->attr.proc_pointer &&
1033           !gfc_compare_types (&cons->expr->ts, &comp->ts))
1034         {
1035           t = FAILURE;
1036           if (strcmp (comp->name, "_extends") == 0)
1037             {
1038               /* Can afford to be brutal with the _extends initializer.
1039                  The derived type can get lost because it is PRIVATE
1040                  but it is not usage constrained by the standard.  */
1041               cons->expr->ts = comp->ts;
1042               t = SUCCESS;
1043             }
1044           else if (comp->attr.pointer && cons->expr->ts.type != BT_UNKNOWN)
1045             gfc_error ("The element in the structure constructor at %L, "
1046                        "for pointer component '%s', is %s but should be %s",
1047                        &cons->expr->where, comp->name,
1048                        gfc_basic_typename (cons->expr->ts.type),
1049                        gfc_basic_typename (comp->ts.type));
1050           else
1051             t = gfc_convert_type (cons->expr, &comp->ts, 1);
1052         }
1053
1054       /* For strings, the length of the constructor should be the same as
1055          the one of the structure, ensure this if the lengths are known at
1056          compile time and when we are dealing with PARAMETER or structure
1057          constructors.  */
1058       if (cons->expr->ts.type == BT_CHARACTER && comp->ts.u.cl
1059           && comp->ts.u.cl->length
1060           && comp->ts.u.cl->length->expr_type == EXPR_CONSTANT
1061           && cons->expr->ts.u.cl && cons->expr->ts.u.cl->length
1062           && cons->expr->ts.u.cl->length->expr_type == EXPR_CONSTANT
1063           && cons->expr->rank != 0
1064           && mpz_cmp (cons->expr->ts.u.cl->length->value.integer,
1065                       comp->ts.u.cl->length->value.integer) != 0)
1066         {
1067           if (cons->expr->expr_type == EXPR_VARIABLE
1068               && cons->expr->symtree->n.sym->attr.flavor == FL_PARAMETER)
1069             {
1070               /* Wrap the parameter in an array constructor (EXPR_ARRAY)
1071                  to make use of the gfc_resolve_character_array_constructor
1072                  machinery.  The expression is later simplified away to
1073                  an array of string literals.  */
1074               gfc_expr *para = cons->expr;
1075               cons->expr = gfc_get_expr ();
1076               cons->expr->ts = para->ts;
1077               cons->expr->where = para->where;
1078               cons->expr->expr_type = EXPR_ARRAY;
1079               cons->expr->rank = para->rank;
1080               cons->expr->shape = gfc_copy_shape (para->shape, para->rank);
1081               gfc_constructor_append_expr (&cons->expr->value.constructor,
1082                                            para, &cons->expr->where);
1083             }
1084           if (cons->expr->expr_type == EXPR_ARRAY)
1085             {
1086               gfc_constructor *p;
1087               p = gfc_constructor_first (cons->expr->value.constructor);
1088               if (cons->expr->ts.u.cl != p->expr->ts.u.cl)
1089                 {
1090                   gfc_charlen *cl, *cl2;
1091
1092                   cl2 = NULL;
1093                   for (cl = gfc_current_ns->cl_list; cl; cl = cl->next)
1094                     {
1095                       if (cl == cons->expr->ts.u.cl)
1096                         break;
1097                       cl2 = cl;
1098                     }
1099
1100                   gcc_assert (cl);
1101
1102                   if (cl2)
1103                     cl2->next = cl->next;
1104
1105                   gfc_free_expr (cl->length);
1106                   free (cl);
1107                 }
1108
1109               cons->expr->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
1110               cons->expr->ts.u.cl->length_from_typespec = true;
1111               cons->expr->ts.u.cl->length = gfc_copy_expr (comp->ts.u.cl->length);
1112               gfc_resolve_character_array_constructor (cons->expr);
1113             }
1114         }
1115
1116       if (cons->expr->expr_type == EXPR_NULL
1117           && !(comp->attr.pointer || comp->attr.allocatable
1118                || comp->attr.proc_pointer
1119                || (comp->ts.type == BT_CLASS
1120                    && (CLASS_DATA (comp)->attr.class_pointer
1121                        || CLASS_DATA (comp)->attr.allocatable))))
1122         {
1123           t = FAILURE;
1124           gfc_error ("The NULL in the structure constructor at %L is "
1125                      "being applied to component '%s', which is neither "
1126                      "a POINTER nor ALLOCATABLE", &cons->expr->where,
1127                      comp->name);
1128         }
1129
1130       if (comp->attr.proc_pointer && comp->ts.interface)
1131         {
1132           /* Check procedure pointer interface.  */
1133           gfc_symbol *s2 = NULL;
1134           gfc_component *c2;
1135           const char *name;
1136           char err[200];
1137
1138           if (gfc_is_proc_ptr_comp (cons->expr, &c2))
1139             {
1140               s2 = c2->ts.interface;
1141               name = c2->name;
1142             }
1143           else if (cons->expr->expr_type == EXPR_FUNCTION)
1144             {
1145               s2 = cons->expr->symtree->n.sym->result;
1146               name = cons->expr->symtree->n.sym->result->name;
1147             }
1148           else if (cons->expr->expr_type != EXPR_NULL)
1149             {
1150               s2 = cons->expr->symtree->n.sym;
1151               name = cons->expr->symtree->n.sym->name;
1152             }
1153
1154           if (s2 && !gfc_compare_interfaces (comp->ts.interface, s2, name, 0, 1,
1155                                              err, sizeof (err)))
1156             {
1157               gfc_error ("Interface mismatch for procedure-pointer component "
1158                          "'%s' in structure constructor at %L: %s",
1159                          comp->name, &cons->expr->where, err);
1160               return FAILURE;
1161             }
1162         }
1163
1164       if (!comp->attr.pointer || comp->attr.proc_pointer
1165           || cons->expr->expr_type == EXPR_NULL)
1166         continue;
1167
1168       a = gfc_expr_attr (cons->expr);
1169
1170       if (!a.pointer && !a.target)
1171         {
1172           t = FAILURE;
1173           gfc_error ("The element in the structure constructor at %L, "
1174                      "for pointer component '%s' should be a POINTER or "
1175                      "a TARGET", &cons->expr->where, comp->name);
1176         }
1177
1178       if (init)
1179         {
1180           /* F08:C461. Additional checks for pointer initialization.  */
1181           if (a.allocatable)
1182             {
1183               t = FAILURE;
1184               gfc_error ("Pointer initialization target at %L "
1185                          "must not be ALLOCATABLE ", &cons->expr->where);
1186             }
1187           if (!a.save)
1188             {
1189               t = FAILURE;
1190               gfc_error ("Pointer initialization target at %L "
1191                          "must have the SAVE attribute", &cons->expr->where);
1192             }
1193         }
1194
1195       /* F2003, C1272 (3).  */
1196       if (gfc_pure (NULL) && cons->expr->expr_type == EXPR_VARIABLE
1197           && (gfc_impure_variable (cons->expr->symtree->n.sym)
1198               || gfc_is_coindexed (cons->expr)))
1199         {
1200           t = FAILURE;
1201           gfc_error ("Invalid expression in the structure constructor for "
1202                      "pointer component '%s' at %L in PURE procedure",
1203                      comp->name, &cons->expr->where);
1204         }
1205
1206       if (gfc_implicit_pure (NULL)
1207             && cons->expr->expr_type == EXPR_VARIABLE
1208             && (gfc_impure_variable (cons->expr->symtree->n.sym)
1209                 || gfc_is_coindexed (cons->expr)))
1210         gfc_current_ns->proc_name->attr.implicit_pure = 0;
1211
1212     }
1213
1214   return t;
1215 }
1216
1217
1218 /****************** Expression name resolution ******************/
1219
1220 /* Returns 0 if a symbol was not declared with a type or
1221    attribute declaration statement, nonzero otherwise.  */
1222
1223 static int
1224 was_declared (gfc_symbol *sym)
1225 {
1226   symbol_attribute a;
1227
1228   a = sym->attr;
1229
1230   if (!a.implicit_type && sym->ts.type != BT_UNKNOWN)
1231     return 1;
1232
1233   if (a.allocatable || a.dimension || a.dummy || a.external || a.intrinsic
1234       || a.optional || a.pointer || a.save || a.target || a.volatile_
1235       || a.value || a.access != ACCESS_UNKNOWN || a.intent != INTENT_UNKNOWN
1236       || a.asynchronous || a.codimension)
1237     return 1;
1238
1239   return 0;
1240 }
1241
1242
1243 /* Determine if a symbol is generic or not.  */
1244
1245 static int
1246 generic_sym (gfc_symbol *sym)
1247 {
1248   gfc_symbol *s;
1249
1250   if (sym->attr.generic ||
1251       (sym->attr.intrinsic && gfc_generic_intrinsic (sym->name)))
1252     return 1;
1253
1254   if (was_declared (sym) || sym->ns->parent == NULL)
1255     return 0;
1256
1257   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
1258   
1259   if (s != NULL)
1260     {
1261       if (s == sym)
1262         return 0;
1263       else
1264         return generic_sym (s);
1265     }
1266
1267   return 0;
1268 }
1269
1270
1271 /* Determine if a symbol is specific or not.  */
1272
1273 static int
1274 specific_sym (gfc_symbol *sym)
1275 {
1276   gfc_symbol *s;
1277
1278   if (sym->attr.if_source == IFSRC_IFBODY
1279       || sym->attr.proc == PROC_MODULE
1280       || sym->attr.proc == PROC_INTERNAL
1281       || sym->attr.proc == PROC_ST_FUNCTION
1282       || (sym->attr.intrinsic && gfc_specific_intrinsic (sym->name))
1283       || sym->attr.external)
1284     return 1;
1285
1286   if (was_declared (sym) || sym->ns->parent == NULL)
1287     return 0;
1288
1289   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
1290
1291   return (s == NULL) ? 0 : specific_sym (s);
1292 }
1293
1294
1295 /* Figure out if the procedure is specific, generic or unknown.  */
1296
1297 typedef enum
1298 { PTYPE_GENERIC = 1, PTYPE_SPECIFIC, PTYPE_UNKNOWN }
1299 proc_type;
1300
1301 static proc_type
1302 procedure_kind (gfc_symbol *sym)
1303 {
1304   if (generic_sym (sym))
1305     return PTYPE_GENERIC;
1306
1307   if (specific_sym (sym))
1308     return PTYPE_SPECIFIC;
1309
1310   return PTYPE_UNKNOWN;
1311 }
1312
1313 /* Check references to assumed size arrays.  The flag need_full_assumed_size
1314    is nonzero when matching actual arguments.  */
1315
1316 static int need_full_assumed_size = 0;
1317
1318 static bool
1319 check_assumed_size_reference (gfc_symbol *sym, gfc_expr *e)
1320 {
1321   if (need_full_assumed_size || !(sym->as && sym->as->type == AS_ASSUMED_SIZE))
1322       return false;
1323
1324   /* FIXME: The comparison "e->ref->u.ar.type == AR_FULL" is wrong.
1325      What should it be?  */
1326   if ((e->ref->u.ar.end[e->ref->u.ar.as->rank - 1] == NULL)
1327           && (e->ref->u.ar.as->type == AS_ASSUMED_SIZE)
1328                && (e->ref->u.ar.type == AR_FULL))
1329     {
1330       gfc_error ("The upper bound in the last dimension must "
1331                  "appear in the reference to the assumed size "
1332                  "array '%s' at %L", sym->name, &e->where);
1333       return true;
1334     }
1335   return false;
1336 }
1337
1338
1339 /* Look for bad assumed size array references in argument expressions
1340   of elemental and array valued intrinsic procedures.  Since this is
1341   called from procedure resolution functions, it only recurses at
1342   operators.  */
1343
1344 static bool
1345 resolve_assumed_size_actual (gfc_expr *e)
1346 {
1347   if (e == NULL)
1348    return false;
1349
1350   switch (e->expr_type)
1351     {
1352     case EXPR_VARIABLE:
1353       if (e->symtree && check_assumed_size_reference (e->symtree->n.sym, e))
1354         return true;
1355       break;
1356
1357     case EXPR_OP:
1358       if (resolve_assumed_size_actual (e->value.op.op1)
1359           || resolve_assumed_size_actual (e->value.op.op2))
1360         return true;
1361       break;
1362
1363     default:
1364       break;
1365     }
1366   return false;
1367 }
1368
1369
1370 /* Check a generic procedure, passed as an actual argument, to see if
1371    there is a matching specific name.  If none, it is an error, and if
1372    more than one, the reference is ambiguous.  */
1373 static int
1374 count_specific_procs (gfc_expr *e)
1375 {
1376   int n;
1377   gfc_interface *p;
1378   gfc_symbol *sym;
1379         
1380   n = 0;
1381   sym = e->symtree->n.sym;
1382
1383   for (p = sym->generic; p; p = p->next)
1384     if (strcmp (sym->name, p->sym->name) == 0)
1385       {
1386         e->symtree = gfc_find_symtree (p->sym->ns->sym_root,
1387                                        sym->name);
1388         n++;
1389       }
1390
1391   if (n > 1)
1392     gfc_error ("'%s' at %L is ambiguous", e->symtree->n.sym->name,
1393                &e->where);
1394
1395   if (n == 0)
1396     gfc_error ("GENERIC procedure '%s' is not allowed as an actual "
1397                "argument at %L", sym->name, &e->where);
1398
1399   return n;
1400 }
1401
1402
1403 /* See if a call to sym could possibly be a not allowed RECURSION because of
1404    a missing RECURSIVE declaration.  This means that either sym is the current
1405    context itself, or sym is the parent of a contained procedure calling its
1406    non-RECURSIVE containing procedure.
1407    This also works if sym is an ENTRY.  */
1408
1409 static bool
1410 is_illegal_recursion (gfc_symbol* sym, gfc_namespace* context)
1411 {
1412   gfc_symbol* proc_sym;
1413   gfc_symbol* context_proc;
1414   gfc_namespace* real_context;
1415
1416   if (sym->attr.flavor == FL_PROGRAM
1417       || sym->attr.flavor == FL_DERIVED)
1418     return false;
1419
1420   gcc_assert (sym->attr.flavor == FL_PROCEDURE);
1421
1422   /* If we've got an ENTRY, find real procedure.  */
1423   if (sym->attr.entry && sym->ns->entries)
1424     proc_sym = sym->ns->entries->sym;
1425   else
1426     proc_sym = sym;
1427
1428   /* If sym is RECURSIVE, all is well of course.  */
1429   if (proc_sym->attr.recursive || gfc_option.flag_recursive)
1430     return false;
1431
1432   /* Find the context procedure's "real" symbol if it has entries.
1433      We look for a procedure symbol, so recurse on the parents if we don't
1434      find one (like in case of a BLOCK construct).  */
1435   for (real_context = context; ; real_context = real_context->parent)
1436     {
1437       /* We should find something, eventually!  */
1438       gcc_assert (real_context);
1439
1440       context_proc = (real_context->entries ? real_context->entries->sym
1441                                             : real_context->proc_name);
1442
1443       /* In some special cases, there may not be a proc_name, like for this
1444          invalid code:
1445          real(bad_kind()) function foo () ...
1446          when checking the call to bad_kind ().
1447          In these cases, we simply return here and assume that the
1448          call is ok.  */
1449       if (!context_proc)
1450         return false;
1451
1452       if (context_proc->attr.flavor != FL_LABEL)
1453         break;
1454     }
1455
1456   /* A call from sym's body to itself is recursion, of course.  */
1457   if (context_proc == proc_sym)
1458     return true;
1459
1460   /* The same is true if context is a contained procedure and sym the
1461      containing one.  */
1462   if (context_proc->attr.contained)
1463     {
1464       gfc_symbol* parent_proc;
1465
1466       gcc_assert (context->parent);
1467       parent_proc = (context->parent->entries ? context->parent->entries->sym
1468                                               : context->parent->proc_name);
1469
1470       if (parent_proc == proc_sym)
1471         return true;
1472     }
1473
1474   return false;
1475 }
1476
1477
1478 /* Resolve an intrinsic procedure: Set its function/subroutine attribute,
1479    its typespec and formal argument list.  */
1480
1481 static gfc_try
1482 resolve_intrinsic (gfc_symbol *sym, locus *loc)
1483 {
1484   gfc_intrinsic_sym* isym = NULL;
1485   const char* symstd;
1486
1487   if (sym->formal)
1488     return SUCCESS;
1489
1490   /* Already resolved.  */
1491   if (sym->from_intmod && sym->ts.type != BT_UNKNOWN)
1492     return SUCCESS;
1493
1494   /* We already know this one is an intrinsic, so we don't call
1495      gfc_is_intrinsic for full checking but rather use gfc_find_function and
1496      gfc_find_subroutine directly to check whether it is a function or
1497      subroutine.  */
1498
1499   if (sym->intmod_sym_id)
1500     isym = gfc_intrinsic_function_by_id ((gfc_isym_id) sym->intmod_sym_id);
1501   else if (!sym->attr.subroutine)
1502     isym = gfc_find_function (sym->name);
1503
1504   if (isym)
1505     {
1506       if (sym->ts.type != BT_UNKNOWN && gfc_option.warn_surprising
1507           && !sym->attr.implicit_type)
1508         gfc_warning ("Type specified for intrinsic function '%s' at %L is"
1509                       " ignored", sym->name, &sym->declared_at);
1510
1511       if (!sym->attr.function &&
1512           gfc_add_function (&sym->attr, sym->name, loc) == FAILURE)
1513         return FAILURE;
1514
1515       sym->ts = isym->ts;
1516     }
1517   else if ((isym = gfc_find_subroutine (sym->name)))
1518     {
1519       if (sym->ts.type != BT_UNKNOWN && !sym->attr.implicit_type)
1520         {
1521           gfc_error ("Intrinsic subroutine '%s' at %L shall not have a type"
1522                       " specifier", sym->name, &sym->declared_at);
1523           return FAILURE;
1524         }
1525
1526       if (!sym->attr.subroutine &&
1527           gfc_add_subroutine (&sym->attr, sym->name, loc) == FAILURE)
1528         return FAILURE;
1529     }
1530   else
1531     {
1532       gfc_error ("'%s' declared INTRINSIC at %L does not exist", sym->name,
1533                  &sym->declared_at);
1534       return FAILURE;
1535     }
1536
1537   gfc_copy_formal_args_intr (sym, isym);
1538
1539   /* Check it is actually available in the standard settings.  */
1540   if (gfc_check_intrinsic_standard (isym, &symstd, false, sym->declared_at)
1541       == FAILURE)
1542     {
1543       gfc_error ("The intrinsic '%s' declared INTRINSIC at %L is not"
1544                  " available in the current standard settings but %s.  Use"
1545                  " an appropriate -std=* option or enable -fall-intrinsics"
1546                  " in order to use it.",
1547                  sym->name, &sym->declared_at, symstd);
1548       return FAILURE;
1549     }
1550
1551   return SUCCESS;
1552 }
1553
1554
1555 /* Resolve a procedure expression, like passing it to a called procedure or as
1556    RHS for a procedure pointer assignment.  */
1557
1558 static gfc_try
1559 resolve_procedure_expression (gfc_expr* expr)
1560 {
1561   gfc_symbol* sym;
1562
1563   if (expr->expr_type != EXPR_VARIABLE)
1564     return SUCCESS;
1565   gcc_assert (expr->symtree);
1566
1567   sym = expr->symtree->n.sym;
1568
1569   if (sym->attr.intrinsic)
1570     resolve_intrinsic (sym, &expr->where);
1571
1572   if (sym->attr.flavor != FL_PROCEDURE
1573       || (sym->attr.function && sym->result == sym))
1574     return SUCCESS;
1575
1576   /* A non-RECURSIVE procedure that is used as procedure expression within its
1577      own body is in danger of being called recursively.  */
1578   if (is_illegal_recursion (sym, gfc_current_ns))
1579     gfc_warning ("Non-RECURSIVE procedure '%s' at %L is possibly calling"
1580                  " itself recursively.  Declare it RECURSIVE or use"
1581                  " -frecursive", sym->name, &expr->where);
1582   
1583   return SUCCESS;
1584 }
1585
1586
1587 /* Resolve an actual argument list.  Most of the time, this is just
1588    resolving the expressions in the list.
1589    The exception is that we sometimes have to decide whether arguments
1590    that look like procedure arguments are really simple variable
1591    references.  */
1592
1593 static gfc_try
1594 resolve_actual_arglist (gfc_actual_arglist *arg, procedure_type ptype,
1595                         bool no_formal_args)
1596 {
1597   gfc_symbol *sym;
1598   gfc_symtree *parent_st;
1599   gfc_expr *e;
1600   int save_need_full_assumed_size;
1601
1602   assumed_type_expr_allowed = true;
1603
1604   for (; arg; arg = arg->next)
1605     {
1606       e = arg->expr;
1607       if (e == NULL)
1608         {
1609           /* Check the label is a valid branching target.  */
1610           if (arg->label)
1611             {
1612               if (arg->label->defined == ST_LABEL_UNKNOWN)
1613                 {
1614                   gfc_error ("Label %d referenced at %L is never defined",
1615                              arg->label->value, &arg->label->where);
1616                   return FAILURE;
1617                 }
1618             }
1619           continue;
1620         }
1621
1622       if (e->expr_type == EXPR_VARIABLE
1623             && e->symtree->n.sym->attr.generic
1624             && no_formal_args
1625             && count_specific_procs (e) != 1)
1626         return FAILURE;
1627
1628       if (e->ts.type != BT_PROCEDURE)
1629         {
1630           save_need_full_assumed_size = need_full_assumed_size;
1631           if (e->expr_type != EXPR_VARIABLE)
1632             need_full_assumed_size = 0;
1633           if (gfc_resolve_expr (e) != SUCCESS)
1634             return FAILURE;
1635           need_full_assumed_size = save_need_full_assumed_size;
1636           goto argument_list;
1637         }
1638
1639       /* See if the expression node should really be a variable reference.  */
1640
1641       sym = e->symtree->n.sym;
1642
1643       if (sym->attr.flavor == FL_PROCEDURE
1644           || sym->attr.intrinsic
1645           || sym->attr.external)
1646         {
1647           int actual_ok;
1648
1649           /* If a procedure is not already determined to be something else
1650              check if it is intrinsic.  */
1651           if (!sym->attr.intrinsic
1652               && !(sym->attr.external || sym->attr.use_assoc
1653                    || sym->attr.if_source == IFSRC_IFBODY)
1654               && gfc_is_intrinsic (sym, sym->attr.subroutine, e->where))
1655             sym->attr.intrinsic = 1;
1656
1657           if (sym->attr.proc == PROC_ST_FUNCTION)
1658             {
1659               gfc_error ("Statement function '%s' at %L is not allowed as an "
1660                          "actual argument", sym->name, &e->where);
1661             }
1662
1663           actual_ok = gfc_intrinsic_actual_ok (sym->name,
1664                                                sym->attr.subroutine);
1665           if (sym->attr.intrinsic && actual_ok == 0)
1666             {
1667               gfc_error ("Intrinsic '%s' at %L is not allowed as an "
1668                          "actual argument", sym->name, &e->where);
1669             }
1670
1671           if (sym->attr.contained && !sym->attr.use_assoc
1672               && sym->ns->proc_name->attr.flavor != FL_MODULE)
1673             {
1674               if (gfc_notify_std (GFC_STD_F2008,
1675                                   "Fortran 2008: Internal procedure '%s' is"
1676                                   " used as actual argument at %L",
1677                                   sym->name, &e->where) == FAILURE)
1678                 return FAILURE;
1679             }
1680
1681           if (sym->attr.elemental && !sym->attr.intrinsic)
1682             {
1683               gfc_error ("ELEMENTAL non-INTRINSIC procedure '%s' is not "
1684                          "allowed as an actual argument at %L", sym->name,
1685                          &e->where);
1686             }
1687
1688           /* Check if a generic interface has a specific procedure
1689             with the same name before emitting an error.  */
1690           if (sym->attr.generic && count_specific_procs (e) != 1)
1691             return FAILURE;
1692           
1693           /* Just in case a specific was found for the expression.  */
1694           sym = e->symtree->n.sym;
1695
1696           /* If the symbol is the function that names the current (or
1697              parent) scope, then we really have a variable reference.  */
1698
1699           if (gfc_is_function_return_value (sym, sym->ns))
1700             goto got_variable;
1701
1702           /* If all else fails, see if we have a specific intrinsic.  */
1703           if (sym->ts.type == BT_UNKNOWN && sym->attr.intrinsic)
1704             {
1705               gfc_intrinsic_sym *isym;
1706
1707               isym = gfc_find_function (sym->name);
1708               if (isym == NULL || !isym->specific)
1709                 {
1710                   gfc_error ("Unable to find a specific INTRINSIC procedure "
1711                              "for the reference '%s' at %L", sym->name,
1712                              &e->where);
1713                   return FAILURE;
1714                 }
1715               sym->ts = isym->ts;
1716               sym->attr.intrinsic = 1;
1717               sym->attr.function = 1;
1718             }
1719
1720           if (gfc_resolve_expr (e) == FAILURE)
1721             return FAILURE;
1722           goto argument_list;
1723         }
1724
1725       /* See if the name is a module procedure in a parent unit.  */
1726
1727       if (was_declared (sym) || sym->ns->parent == NULL)
1728         goto got_variable;
1729
1730       if (gfc_find_sym_tree (sym->name, sym->ns->parent, 1, &parent_st))
1731         {
1732           gfc_error ("Symbol '%s' at %L is ambiguous", sym->name, &e->where);
1733           return FAILURE;
1734         }
1735
1736       if (parent_st == NULL)
1737         goto got_variable;
1738
1739       sym = parent_st->n.sym;
1740       e->symtree = parent_st;           /* Point to the right thing.  */
1741
1742       if (sym->attr.flavor == FL_PROCEDURE
1743           || sym->attr.intrinsic
1744           || sym->attr.external)
1745         {
1746           if (gfc_resolve_expr (e) == FAILURE)
1747             return FAILURE;
1748           goto argument_list;
1749         }
1750
1751     got_variable:
1752       e->expr_type = EXPR_VARIABLE;
1753       e->ts = sym->ts;
1754       if ((sym->as != NULL && sym->ts.type != BT_CLASS)
1755           || (sym->ts.type == BT_CLASS && sym->attr.class_ok
1756               && CLASS_DATA (sym)->as))
1757         {
1758           e->rank = sym->ts.type == BT_CLASS
1759                     ? CLASS_DATA (sym)->as->rank : sym->as->rank;
1760           e->ref = gfc_get_ref ();
1761           e->ref->type = REF_ARRAY;
1762           e->ref->u.ar.type = AR_FULL;
1763           e->ref->u.ar.as = sym->ts.type == BT_CLASS
1764                             ? CLASS_DATA (sym)->as : sym->as;
1765         }
1766
1767       /* Expressions are assigned a default ts.type of BT_PROCEDURE in
1768          primary.c (match_actual_arg). If above code determines that it
1769          is a  variable instead, it needs to be resolved as it was not
1770          done at the beginning of this function.  */
1771       save_need_full_assumed_size = need_full_assumed_size;
1772       if (e->expr_type != EXPR_VARIABLE)
1773         need_full_assumed_size = 0;
1774       if (gfc_resolve_expr (e) != SUCCESS)
1775         return FAILURE;
1776       need_full_assumed_size = save_need_full_assumed_size;
1777
1778     argument_list:
1779       /* Check argument list functions %VAL, %LOC and %REF.  There is
1780          nothing to do for %REF.  */
1781       if (arg->name && arg->name[0] == '%')
1782         {
1783           if (strncmp ("%VAL", arg->name, 4) == 0)
1784             {
1785               if (e->ts.type == BT_CHARACTER || e->ts.type == BT_DERIVED)
1786                 {
1787                   gfc_error ("By-value argument at %L is not of numeric "
1788                              "type", &e->where);
1789                   return FAILURE;
1790                 }
1791
1792               if (e->rank)
1793                 {
1794                   gfc_error ("By-value argument at %L cannot be an array or "
1795                              "an array section", &e->where);
1796                 return FAILURE;
1797                 }
1798
1799               /* Intrinsics are still PROC_UNKNOWN here.  However,
1800                  since same file external procedures are not resolvable
1801                  in gfortran, it is a good deal easier to leave them to
1802                  intrinsic.c.  */
1803               if (ptype != PROC_UNKNOWN
1804                   && ptype != PROC_DUMMY
1805                   && ptype != PROC_EXTERNAL
1806                   && ptype != PROC_MODULE)
1807                 {
1808                   gfc_error ("By-value argument at %L is not allowed "
1809                              "in this context", &e->where);
1810                   return FAILURE;
1811                 }
1812             }
1813
1814           /* Statement functions have already been excluded above.  */
1815           else if (strncmp ("%LOC", arg->name, 4) == 0
1816                    && e->ts.type == BT_PROCEDURE)
1817             {
1818               if (e->symtree->n.sym->attr.proc == PROC_INTERNAL)
1819                 {
1820                   gfc_error ("Passing internal procedure at %L by location "
1821                              "not allowed", &e->where);
1822                   return FAILURE;
1823                 }
1824             }
1825         }
1826
1827       /* Fortran 2008, C1237.  */
1828       if (e->expr_type == EXPR_VARIABLE && gfc_is_coindexed (e)
1829           && gfc_has_ultimate_pointer (e))
1830         {
1831           gfc_error ("Coindexed actual argument at %L with ultimate pointer "
1832                      "component", &e->where);
1833           return FAILURE;
1834         }
1835     }
1836   assumed_type_expr_allowed = false;
1837
1838   return SUCCESS;
1839 }
1840
1841
1842 /* Do the checks of the actual argument list that are specific to elemental
1843    procedures.  If called with c == NULL, we have a function, otherwise if
1844    expr == NULL, we have a subroutine.  */
1845
1846 static gfc_try
1847 resolve_elemental_actual (gfc_expr *expr, gfc_code *c)
1848 {
1849   gfc_actual_arglist *arg0;
1850   gfc_actual_arglist *arg;
1851   gfc_symbol *esym = NULL;
1852   gfc_intrinsic_sym *isym = NULL;
1853   gfc_expr *e = NULL;
1854   gfc_intrinsic_arg *iformal = NULL;
1855   gfc_formal_arglist *eformal = NULL;
1856   bool formal_optional = false;
1857   bool set_by_optional = false;
1858   int i;
1859   int rank = 0;
1860
1861   /* Is this an elemental procedure?  */
1862   if (expr && expr->value.function.actual != NULL)
1863     {
1864       if (expr->value.function.esym != NULL
1865           && expr->value.function.esym->attr.elemental)
1866         {
1867           arg0 = expr->value.function.actual;
1868           esym = expr->value.function.esym;
1869         }
1870       else if (expr->value.function.isym != NULL
1871                && expr->value.function.isym->elemental)
1872         {
1873           arg0 = expr->value.function.actual;
1874           isym = expr->value.function.isym;
1875         }
1876       else
1877         return SUCCESS;
1878     }
1879   else if (c && c->ext.actual != NULL)
1880     {
1881       arg0 = c->ext.actual;
1882       
1883       if (c->resolved_sym)
1884         esym = c->resolved_sym;
1885       else
1886         esym = c->symtree->n.sym;
1887       gcc_assert (esym);
1888
1889       if (!esym->attr.elemental)
1890         return SUCCESS;
1891     }
1892   else
1893     return SUCCESS;
1894
1895   /* The rank of an elemental is the rank of its array argument(s).  */
1896   for (arg = arg0; arg; arg = arg->next)
1897     {
1898       if (arg->expr != NULL && arg->expr->rank > 0)
1899         {
1900           rank = arg->expr->rank;
1901           if (arg->expr->expr_type == EXPR_VARIABLE
1902               && arg->expr->symtree->n.sym->attr.optional)
1903             set_by_optional = true;
1904
1905           /* Function specific; set the result rank and shape.  */
1906           if (expr)
1907             {
1908               expr->rank = rank;
1909               if (!expr->shape && arg->expr->shape)
1910                 {
1911                   expr->shape = gfc_get_shape (rank);
1912                   for (i = 0; i < rank; i++)
1913                     mpz_init_set (expr->shape[i], arg->expr->shape[i]);
1914                 }
1915             }
1916           break;
1917         }
1918     }
1919
1920   /* If it is an array, it shall not be supplied as an actual argument
1921      to an elemental procedure unless an array of the same rank is supplied
1922      as an actual argument corresponding to a nonoptional dummy argument of
1923      that elemental procedure(12.4.1.5).  */
1924   formal_optional = false;
1925   if (isym)
1926     iformal = isym->formal;
1927   else
1928     eformal = esym->formal;
1929
1930   for (arg = arg0; arg; arg = arg->next)
1931     {
1932       if (eformal)
1933         {
1934           if (eformal->sym && eformal->sym->attr.optional)
1935             formal_optional = true;
1936           eformal = eformal->next;
1937         }
1938       else if (isym && iformal)
1939         {
1940           if (iformal->optional)
1941             formal_optional = true;
1942           iformal = iformal->next;
1943         }
1944       else if (isym)
1945         formal_optional = true;
1946
1947       if (pedantic && arg->expr != NULL
1948           && arg->expr->expr_type == EXPR_VARIABLE
1949           && arg->expr->symtree->n.sym->attr.optional
1950           && formal_optional
1951           && arg->expr->rank
1952           && (set_by_optional || arg->expr->rank != rank)
1953           && !(isym && isym->id == GFC_ISYM_CONVERSION))
1954         {
1955           gfc_warning ("'%s' at %L is an array and OPTIONAL; IF IT IS "
1956                        "MISSING, it cannot be the actual argument of an "
1957                        "ELEMENTAL procedure unless there is a non-optional "
1958                        "argument with the same rank (12.4.1.5)",
1959                        arg->expr->symtree->n.sym->name, &arg->expr->where);
1960           return FAILURE;
1961         }
1962     }
1963
1964   for (arg = arg0; arg; arg = arg->next)
1965     {
1966       if (arg->expr == NULL || arg->expr->rank == 0)
1967         continue;
1968
1969       /* Being elemental, the last upper bound of an assumed size array
1970          argument must be present.  */
1971       if (resolve_assumed_size_actual (arg->expr))
1972         return FAILURE;
1973
1974       /* Elemental procedure's array actual arguments must conform.  */
1975       if (e != NULL)
1976         {
1977           if (gfc_check_conformance (arg->expr, e,
1978                                      "elemental procedure") == FAILURE)
1979             return FAILURE;
1980         }
1981       else
1982         e = arg->expr;
1983     }
1984
1985   /* INTENT(OUT) is only allowed for subroutines; if any actual argument
1986      is an array, the intent inout/out variable needs to be also an array.  */
1987   if (rank > 0 && esym && expr == NULL)
1988     for (eformal = esym->formal, arg = arg0; arg && eformal;
1989          arg = arg->next, eformal = eformal->next)
1990       if ((eformal->sym->attr.intent == INTENT_OUT
1991            || eformal->sym->attr.intent == INTENT_INOUT)
1992           && arg->expr && arg->expr->rank == 0)
1993         {
1994           gfc_error ("Actual argument at %L for INTENT(%s) dummy '%s' of "
1995                      "ELEMENTAL subroutine '%s' is a scalar, but another "
1996                      "actual argument is an array", &arg->expr->where,
1997                      (eformal->sym->attr.intent == INTENT_OUT) ? "OUT"
1998                      : "INOUT", eformal->sym->name, esym->name);
1999           return FAILURE;
2000         }
2001   return SUCCESS;
2002 }
2003
2004
2005 /* This function does the checking of references to global procedures
2006    as defined in sections 18.1 and 14.1, respectively, of the Fortran
2007    77 and 95 standards.  It checks for a gsymbol for the name, making
2008    one if it does not already exist.  If it already exists, then the
2009    reference being resolved must correspond to the type of gsymbol.
2010    Otherwise, the new symbol is equipped with the attributes of the
2011    reference.  The corresponding code that is called in creating
2012    global entities is parse.c.
2013
2014    In addition, for all but -std=legacy, the gsymbols are used to
2015    check the interfaces of external procedures from the same file.
2016    The namespace of the gsymbol is resolved and then, once this is
2017    done the interface is checked.  */
2018
2019
2020 static bool
2021 not_in_recursive (gfc_symbol *sym, gfc_namespace *gsym_ns)
2022 {
2023   if (!gsym_ns->proc_name->attr.recursive)
2024     return true;
2025
2026   if (sym->ns == gsym_ns)
2027     return false;
2028
2029   if (sym->ns->parent && sym->ns->parent == gsym_ns)
2030     return false;
2031
2032   return true;
2033 }
2034
2035 static bool
2036 not_entry_self_reference  (gfc_symbol *sym, gfc_namespace *gsym_ns)
2037 {
2038   if (gsym_ns->entries)
2039     {
2040       gfc_entry_list *entry = gsym_ns->entries;
2041
2042       for (; entry; entry = entry->next)
2043         {
2044           if (strcmp (sym->name, entry->sym->name) == 0)
2045             {
2046               if (strcmp (gsym_ns->proc_name->name,
2047                           sym->ns->proc_name->name) == 0)
2048                 return false;
2049
2050               if (sym->ns->parent
2051                   && strcmp (gsym_ns->proc_name->name,
2052                              sym->ns->parent->proc_name->name) == 0)
2053                 return false;
2054             }
2055         }
2056     }
2057   return true;
2058 }
2059
2060 static void
2061 resolve_global_procedure (gfc_symbol *sym, locus *where,
2062                           gfc_actual_arglist **actual, int sub)
2063 {
2064   gfc_gsymbol * gsym;
2065   gfc_namespace *ns;
2066   enum gfc_symbol_type type;
2067
2068   type = sub ? GSYM_SUBROUTINE : GSYM_FUNCTION;
2069
2070   gsym = gfc_get_gsymbol (sym->name);
2071
2072   if ((gsym->type != GSYM_UNKNOWN && gsym->type != type))
2073     gfc_global_used (gsym, where);
2074
2075   if (gfc_option.flag_whole_file
2076         && (sym->attr.if_source == IFSRC_UNKNOWN
2077             || sym->attr.if_source == IFSRC_IFBODY)
2078         && gsym->type != GSYM_UNKNOWN
2079         && gsym->ns
2080         && gsym->ns->resolved != -1
2081         && gsym->ns->proc_name
2082         && not_in_recursive (sym, gsym->ns)
2083         && not_entry_self_reference (sym, gsym->ns))
2084     {
2085       gfc_symbol *def_sym;
2086
2087       /* Resolve the gsymbol namespace if needed.  */
2088       if (!gsym->ns->resolved)
2089         {
2090           gfc_dt_list *old_dt_list;
2091           struct gfc_omp_saved_state old_omp_state;
2092
2093           /* Stash away derived types so that the backend_decls do not
2094              get mixed up.  */
2095           old_dt_list = gfc_derived_types;
2096           gfc_derived_types = NULL;
2097           /* And stash away openmp state.  */
2098           gfc_omp_save_and_clear_state (&old_omp_state);
2099
2100           gfc_resolve (gsym->ns);
2101
2102           /* Store the new derived types with the global namespace.  */
2103           if (gfc_derived_types)
2104             gsym->ns->derived_types = gfc_derived_types;
2105
2106           /* Restore the derived types of this namespace.  */
2107           gfc_derived_types = old_dt_list;
2108           /* And openmp state.  */
2109           gfc_omp_restore_state (&old_omp_state);
2110         }
2111
2112       /* Make sure that translation for the gsymbol occurs before
2113          the procedure currently being resolved.  */
2114       ns = gfc_global_ns_list;
2115       for (; ns && ns != gsym->ns; ns = ns->sibling)
2116         {
2117           if (ns->sibling == gsym->ns)
2118             {
2119               ns->sibling = gsym->ns->sibling;
2120               gsym->ns->sibling = gfc_global_ns_list;
2121               gfc_global_ns_list = gsym->ns;
2122               break;
2123             }
2124         }
2125
2126       def_sym = gsym->ns->proc_name;
2127       if (def_sym->attr.entry_master)
2128         {
2129           gfc_entry_list *entry;
2130           for (entry = gsym->ns->entries; entry; entry = entry->next)
2131             if (strcmp (entry->sym->name, sym->name) == 0)
2132               {
2133                 def_sym = entry->sym;
2134                 break;
2135               }
2136         }
2137
2138       /* Differences in constant character lengths.  */
2139       if (sym->attr.function && sym->ts.type == BT_CHARACTER)
2140         {
2141           long int l1 = 0, l2 = 0;
2142           gfc_charlen *cl1 = sym->ts.u.cl;
2143           gfc_charlen *cl2 = def_sym->ts.u.cl;
2144
2145           if (cl1 != NULL
2146               && cl1->length != NULL
2147               && cl1->length->expr_type == EXPR_CONSTANT)
2148             l1 = mpz_get_si (cl1->length->value.integer);
2149
2150           if (cl2 != NULL
2151               && cl2->length != NULL
2152               && cl2->length->expr_type == EXPR_CONSTANT)
2153             l2 = mpz_get_si (cl2->length->value.integer);
2154
2155           if (l1 && l2 && l1 != l2)
2156             gfc_error ("Character length mismatch in return type of "
2157                        "function '%s' at %L (%ld/%ld)", sym->name,
2158                        &sym->declared_at, l1, l2);
2159         }
2160
2161      /* Type mismatch of function return type and expected type.  */
2162      if (sym->attr.function
2163          && !gfc_compare_types (&sym->ts, &def_sym->ts))
2164         gfc_error ("Return type mismatch of function '%s' at %L (%s/%s)",
2165                    sym->name, &sym->declared_at, gfc_typename (&sym->ts),
2166                    gfc_typename (&def_sym->ts));
2167
2168       if (def_sym->formal && sym->attr.if_source != IFSRC_IFBODY)
2169         {
2170           gfc_formal_arglist *arg = def_sym->formal;
2171           for ( ; arg; arg = arg->next)
2172             if (!arg->sym)
2173               continue;
2174             /* F2003, 12.3.1.1 (2a); F2008, 12.4.2.2 (2a)  */
2175             else if (arg->sym->attr.allocatable
2176                      || arg->sym->attr.asynchronous
2177                      || arg->sym->attr.optional
2178                      || arg->sym->attr.pointer
2179                      || arg->sym->attr.target
2180                      || arg->sym->attr.value
2181                      || arg->sym->attr.volatile_)
2182               {
2183                 gfc_error ("Dummy argument '%s' of procedure '%s' at %L "
2184                            "has an attribute that requires an explicit "
2185                            "interface for this procedure", arg->sym->name,
2186                            sym->name, &sym->declared_at);
2187                 break;
2188               }
2189             /* F2003, 12.3.1.1 (2b); F2008, 12.4.2.2 (2b)  */
2190             else if (arg->sym && arg->sym->as
2191                      && arg->sym->as->type == AS_ASSUMED_SHAPE)
2192               {
2193                 gfc_error ("Procedure '%s' at %L with assumed-shape dummy "
2194                            "argument '%s' must have an explicit interface",
2195                            sym->name, &sym->declared_at, arg->sym->name);
2196                 break;
2197               }
2198             /* F2008, 12.4.2.2 (2c)  */
2199             else if (arg->sym->attr.codimension)
2200               {
2201                 gfc_error ("Procedure '%s' at %L with coarray dummy argument "
2202                            "'%s' must have an explicit interface",
2203                            sym->name, &sym->declared_at, arg->sym->name);
2204                 break;
2205               }
2206             /* F2003, 12.3.1.1 (2c); F2008, 12.4.2.2 (2d)   */
2207             else if (false) /* TODO: is a parametrized derived type  */
2208               {
2209                 gfc_error ("Procedure '%s' at %L with parametrized derived "
2210                            "type argument '%s' must have an explicit "
2211                            "interface", sym->name, &sym->declared_at,
2212                            arg->sym->name);
2213                 break;
2214               }
2215             /* F2003, 12.3.1.1 (2d); F2008, 12.4.2.2 (2e)   */
2216             else if (arg->sym->ts.type == BT_CLASS)
2217               {
2218                 gfc_error ("Procedure '%s' at %L with polymorphic dummy "
2219                            "argument '%s' must have an explicit interface",
2220                            sym->name, &sym->declared_at, arg->sym->name);
2221                 break;
2222               }
2223         }
2224
2225       if (def_sym->attr.function)
2226         {
2227           /* F2003, 12.3.1.1 (3a); F2008, 12.4.2.2 (3a) */
2228           if (def_sym->as && def_sym->as->rank
2229               && (!sym->as || sym->as->rank != def_sym->as->rank))
2230             gfc_error ("The reference to function '%s' at %L either needs an "
2231                        "explicit INTERFACE or the rank is incorrect", sym->name,
2232                        where);
2233
2234           /* F2003, 12.3.1.1 (3b); F2008, 12.4.2.2 (3b) */
2235           if ((def_sym->result->attr.pointer
2236                || def_sym->result->attr.allocatable)
2237                && (sym->attr.if_source != IFSRC_IFBODY
2238                    || def_sym->result->attr.pointer
2239                         != sym->result->attr.pointer
2240                    || def_sym->result->attr.allocatable
2241                         != sym->result->attr.allocatable))
2242             gfc_error ("Function '%s' at %L with a POINTER or ALLOCATABLE "
2243                        "result must have an explicit interface", sym->name,
2244                        where);
2245
2246           /* F2003, 12.3.1.1 (3c); F2008, 12.4.2.2 (3c)  */
2247           if (sym->ts.type == BT_CHARACTER && sym->attr.if_source != IFSRC_IFBODY
2248               && def_sym->ts.type == BT_CHARACTER && def_sym->ts.u.cl->length != NULL)
2249             {
2250               gfc_charlen *cl = sym->ts.u.cl;
2251
2252               if (!sym->attr.entry_master && sym->attr.if_source == IFSRC_UNKNOWN
2253                   && cl && cl->length && cl->length->expr_type != EXPR_CONSTANT)
2254                 {
2255                   gfc_error ("Nonconstant character-length function '%s' at %L "
2256                              "must have an explicit interface", sym->name,
2257                              &sym->declared_at);
2258                 }
2259             }
2260         }
2261
2262       /* F2003, 12.3.1.1 (4); F2008, 12.4.2.2 (4) */
2263       if (def_sym->attr.elemental && !sym->attr.elemental)
2264         {
2265           gfc_error ("ELEMENTAL procedure '%s' at %L must have an explicit "
2266                      "interface", sym->name, &sym->declared_at);
2267         }
2268
2269       /* F2003, 12.3.1.1 (5); F2008, 12.4.2.2 (5) */
2270       if (def_sym->attr.is_bind_c && !sym->attr.is_bind_c)
2271         {
2272           gfc_error ("Procedure '%s' at %L with BIND(C) attribute must have "
2273                      "an explicit interface", sym->name, &sym->declared_at);
2274         }
2275
2276       if (gfc_option.flag_whole_file == 1
2277           || ((gfc_option.warn_std & GFC_STD_LEGACY)
2278               && !(gfc_option.warn_std & GFC_STD_GNU)))
2279         gfc_errors_to_warnings (1);
2280
2281       if (sym->attr.if_source != IFSRC_IFBODY)  
2282         gfc_procedure_use (def_sym, actual, where);
2283
2284       gfc_errors_to_warnings (0);
2285     }
2286
2287   if (gsym->type == GSYM_UNKNOWN)
2288     {
2289       gsym->type = type;
2290       gsym->where = *where;
2291     }
2292
2293   gsym->used = 1;
2294 }
2295
2296
2297 /************* Function resolution *************/
2298
2299 /* Resolve a function call known to be generic.
2300    Section 14.1.2.4.1.  */
2301
2302 static match
2303 resolve_generic_f0 (gfc_expr *expr, gfc_symbol *sym)
2304 {
2305   gfc_symbol *s;
2306
2307   if (sym->attr.generic)
2308     {
2309       s = gfc_search_interface (sym->generic, 0, &expr->value.function.actual);
2310       if (s != NULL)
2311         {
2312           expr->value.function.name = s->name;
2313           expr->value.function.esym = s;
2314
2315           if (s->ts.type != BT_UNKNOWN)
2316             expr->ts = s->ts;
2317           else if (s->result != NULL && s->result->ts.type != BT_UNKNOWN)
2318             expr->ts = s->result->ts;
2319
2320           if (s->as != NULL)
2321             expr->rank = s->as->rank;
2322           else if (s->result != NULL && s->result->as != NULL)
2323             expr->rank = s->result->as->rank;
2324
2325           gfc_set_sym_referenced (expr->value.function.esym);
2326
2327           return MATCH_YES;
2328         }
2329
2330       /* TODO: Need to search for elemental references in generic
2331          interface.  */
2332     }
2333
2334   if (sym->attr.intrinsic)
2335     return gfc_intrinsic_func_interface (expr, 0);
2336
2337   return MATCH_NO;
2338 }
2339
2340
2341 static gfc_try
2342 resolve_generic_f (gfc_expr *expr)
2343 {
2344   gfc_symbol *sym;
2345   match m;
2346   gfc_interface *intr = NULL;
2347
2348   sym = expr->symtree->n.sym;
2349
2350   for (;;)
2351     {
2352       m = resolve_generic_f0 (expr, sym);
2353       if (m == MATCH_YES)
2354         return SUCCESS;
2355       else if (m == MATCH_ERROR)
2356         return FAILURE;
2357
2358 generic:
2359       if (!intr)
2360         for (intr = sym->generic; intr; intr = intr->next)
2361           if (intr->sym->attr.flavor == FL_DERIVED)
2362             break;
2363
2364       if (sym->ns->parent == NULL)
2365         break;
2366       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2367
2368       if (sym == NULL)
2369         break;
2370       if (!generic_sym (sym))
2371         goto generic;
2372     }
2373
2374   /* Last ditch attempt.  See if the reference is to an intrinsic
2375      that possesses a matching interface.  14.1.2.4  */
2376   if (sym  && !intr && !gfc_is_intrinsic (sym, 0, expr->where))
2377     {
2378       gfc_error ("There is no specific function for the generic '%s' "
2379                  "at %L", expr->symtree->n.sym->name, &expr->where);
2380       return FAILURE;
2381     }
2382
2383   if (intr)
2384     {
2385       if (gfc_convert_to_structure_constructor (expr, intr->sym, NULL, NULL,
2386                                                 false) != SUCCESS)
2387         return FAILURE;
2388       return resolve_structure_cons (expr, 0);
2389     }
2390
2391   m = gfc_intrinsic_func_interface (expr, 0);
2392   if (m == MATCH_YES)
2393     return SUCCESS;
2394
2395   if (m == MATCH_NO)
2396     gfc_error ("Generic function '%s' at %L is not consistent with a "
2397                "specific intrinsic interface", expr->symtree->n.sym->name,
2398                &expr->where);
2399
2400   return FAILURE;
2401 }
2402
2403
2404 /* Resolve a function call known to be specific.  */
2405
2406 static match
2407 resolve_specific_f0 (gfc_symbol *sym, gfc_expr *expr)
2408 {
2409   match m;
2410
2411   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
2412     {
2413       if (sym->attr.dummy)
2414         {
2415           sym->attr.proc = PROC_DUMMY;
2416           goto found;
2417         }
2418
2419       sym->attr.proc = PROC_EXTERNAL;
2420       goto found;
2421     }
2422
2423   if (sym->attr.proc == PROC_MODULE
2424       || sym->attr.proc == PROC_ST_FUNCTION
2425       || sym->attr.proc == PROC_INTERNAL)
2426     goto found;
2427
2428   if (sym->attr.intrinsic)
2429     {
2430       m = gfc_intrinsic_func_interface (expr, 1);
2431       if (m == MATCH_YES)
2432         return MATCH_YES;
2433       if (m == MATCH_NO)
2434         gfc_error ("Function '%s' at %L is INTRINSIC but is not compatible "
2435                    "with an intrinsic", sym->name, &expr->where);
2436
2437       return MATCH_ERROR;
2438     }
2439
2440   return MATCH_NO;
2441
2442 found:
2443   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2444
2445   if (sym->result)
2446     expr->ts = sym->result->ts;
2447   else
2448     expr->ts = sym->ts;
2449   expr->value.function.name = sym->name;
2450   expr->value.function.esym = sym;
2451   if (sym->as != NULL)
2452     expr->rank = sym->as->rank;
2453
2454   return MATCH_YES;
2455 }
2456
2457
2458 static gfc_try
2459 resolve_specific_f (gfc_expr *expr)
2460 {
2461   gfc_symbol *sym;
2462   match m;
2463
2464   sym = expr->symtree->n.sym;
2465
2466   for (;;)
2467     {
2468       m = resolve_specific_f0 (sym, expr);
2469       if (m == MATCH_YES)
2470         return SUCCESS;
2471       if (m == MATCH_ERROR)
2472         return FAILURE;
2473
2474       if (sym->ns->parent == NULL)
2475         break;
2476
2477       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2478
2479       if (sym == NULL)
2480         break;
2481     }
2482
2483   gfc_error ("Unable to resolve the specific function '%s' at %L",
2484              expr->symtree->n.sym->name, &expr->where);
2485
2486   return SUCCESS;
2487 }
2488
2489
2490 /* Resolve a procedure call not known to be generic nor specific.  */
2491
2492 static gfc_try
2493 resolve_unknown_f (gfc_expr *expr)
2494 {
2495   gfc_symbol *sym;
2496   gfc_typespec *ts;
2497
2498   sym = expr->symtree->n.sym;
2499
2500   if (sym->attr.dummy)
2501     {
2502       sym->attr.proc = PROC_DUMMY;
2503       expr->value.function.name = sym->name;
2504       goto set_type;
2505     }
2506
2507   /* See if we have an intrinsic function reference.  */
2508
2509   if (gfc_is_intrinsic (sym, 0, expr->where))
2510     {
2511       if (gfc_intrinsic_func_interface (expr, 1) == MATCH_YES)
2512         return SUCCESS;
2513       return FAILURE;
2514     }
2515
2516   /* The reference is to an external name.  */
2517
2518   sym->attr.proc = PROC_EXTERNAL;
2519   expr->value.function.name = sym->name;
2520   expr->value.function.esym = expr->symtree->n.sym;
2521
2522   if (sym->as != NULL)
2523     expr->rank = sym->as->rank;
2524
2525   /* Type of the expression is either the type of the symbol or the
2526      default type of the symbol.  */
2527
2528 set_type:
2529   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2530
2531   if (sym->ts.type != BT_UNKNOWN)
2532     expr->ts = sym->ts;
2533   else
2534     {
2535       ts = gfc_get_default_type (sym->name, sym->ns);
2536
2537       if (ts->type == BT_UNKNOWN)
2538         {
2539           gfc_error ("Function '%s' at %L has no IMPLICIT type",
2540                      sym->name, &expr->where);
2541           return FAILURE;
2542         }
2543       else
2544         expr->ts = *ts;
2545     }
2546
2547   return SUCCESS;
2548 }
2549
2550
2551 /* Return true, if the symbol is an external procedure.  */
2552 static bool
2553 is_external_proc (gfc_symbol *sym)
2554 {
2555   if (!sym->attr.dummy && !sym->attr.contained
2556         && !(sym->attr.intrinsic
2557               || gfc_is_intrinsic (sym, sym->attr.subroutine, sym->declared_at))
2558         && sym->attr.proc != PROC_ST_FUNCTION
2559         && !sym->attr.proc_pointer
2560         && !sym->attr.use_assoc
2561         && sym->name)
2562     return true;
2563
2564   return false;
2565 }
2566
2567
2568 /* Figure out if a function reference is pure or not.  Also set the name
2569    of the function for a potential error message.  Return nonzero if the
2570    function is PURE, zero if not.  */
2571 static int
2572 pure_stmt_function (gfc_expr *, gfc_symbol *);
2573
2574 static int
2575 pure_function (gfc_expr *e, const char **name)
2576 {
2577   int pure;
2578
2579   *name = NULL;
2580
2581   if (e->symtree != NULL
2582         && e->symtree->n.sym != NULL
2583         && e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2584     return pure_stmt_function (e, e->symtree->n.sym);
2585
2586   if (e->value.function.esym)
2587     {
2588       pure = gfc_pure (e->value.function.esym);
2589       *name = e->value.function.esym->name;
2590     }
2591   else if (e->value.function.isym)
2592     {
2593       pure = e->value.function.isym->pure
2594              || e->value.function.isym->elemental;
2595       *name = e->value.function.isym->name;
2596     }
2597   else
2598     {
2599       /* Implicit functions are not pure.  */
2600       pure = 0;
2601       *name = e->value.function.name;
2602     }
2603
2604   return pure;
2605 }
2606
2607
2608 static bool
2609 impure_stmt_fcn (gfc_expr *e, gfc_symbol *sym,
2610                  int *f ATTRIBUTE_UNUSED)
2611 {
2612   const char *name;
2613
2614   /* Don't bother recursing into other statement functions
2615      since they will be checked individually for purity.  */
2616   if (e->expr_type != EXPR_FUNCTION
2617         || !e->symtree
2618         || e->symtree->n.sym == sym
2619         || e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2620     return false;
2621
2622   return pure_function (e, &name) ? false : true;
2623 }
2624
2625
2626 static int
2627 pure_stmt_function (gfc_expr *e, gfc_symbol *sym)
2628 {
2629   return gfc_traverse_expr (e, sym, impure_stmt_fcn, 0) ? 0 : 1;
2630 }
2631
2632
2633 static gfc_try
2634 is_scalar_expr_ptr (gfc_expr *expr)
2635 {
2636   gfc_try retval = SUCCESS;
2637   gfc_ref *ref;
2638   int start;
2639   int end;
2640
2641   /* See if we have a gfc_ref, which means we have a substring, array
2642      reference, or a component.  */
2643   if (expr->ref != NULL)
2644     {
2645       ref = expr->ref;
2646       while (ref->next != NULL)
2647         ref = ref->next;
2648
2649       switch (ref->type)
2650         {
2651         case REF_SUBSTRING:
2652           if (ref->u.ss.start == NULL || ref->u.ss.end == NULL
2653               || gfc_dep_compare_expr (ref->u.ss.start, ref->u.ss.end) != 0)
2654             retval = FAILURE;
2655           break;
2656
2657         case REF_ARRAY:
2658           if (ref->u.ar.type == AR_ELEMENT)
2659             retval = SUCCESS;
2660           else if (ref->u.ar.type == AR_FULL)
2661             {
2662               /* The user can give a full array if the array is of size 1.  */
2663               if (ref->u.ar.as != NULL
2664                   && ref->u.ar.as->rank == 1
2665                   && ref->u.ar.as->type == AS_EXPLICIT
2666                   && ref->u.ar.as->lower[0] != NULL
2667                   && ref->u.ar.as->lower[0]->expr_type == EXPR_CONSTANT
2668                   && ref->u.ar.as->upper[0] != NULL
2669                   && ref->u.ar.as->upper[0]->expr_type == EXPR_CONSTANT)
2670                 {
2671                   /* If we have a character string, we need to check if
2672                      its length is one.  */
2673                   if (expr->ts.type == BT_CHARACTER)
2674                     {
2675                       if (expr->ts.u.cl == NULL
2676                           || expr->ts.u.cl->length == NULL
2677                           || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1)
2678                           != 0)
2679                         retval = FAILURE;
2680                     }
2681                   else
2682                     {
2683                       /* We have constant lower and upper bounds.  If the
2684                          difference between is 1, it can be considered a
2685                          scalar.  
2686                          FIXME: Use gfc_dep_compare_expr instead.  */
2687                       start = (int) mpz_get_si
2688                                 (ref->u.ar.as->lower[0]->value.integer);
2689                       end = (int) mpz_get_si
2690                                 (ref->u.ar.as->upper[0]->value.integer);
2691                       if (end - start + 1 != 1)
2692                         retval = FAILURE;
2693                    }
2694                 }
2695               else
2696                 retval = FAILURE;
2697             }
2698           else
2699             retval = FAILURE;
2700           break;
2701         default:
2702           retval = SUCCESS;
2703           break;
2704         }
2705     }
2706   else if (expr->ts.type == BT_CHARACTER && expr->rank == 0)
2707     {
2708       /* Character string.  Make sure it's of length 1.  */
2709       if (expr->ts.u.cl == NULL
2710           || expr->ts.u.cl->length == NULL
2711           || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1) != 0)
2712         retval = FAILURE;
2713     }
2714   else if (expr->rank != 0)
2715     retval = FAILURE;
2716
2717   return retval;
2718 }
2719
2720
2721 /* Match one of the iso_c_binding functions (c_associated or c_loc)
2722    and, in the case of c_associated, set the binding label based on
2723    the arguments.  */
2724
2725 static gfc_try
2726 gfc_iso_c_func_interface (gfc_symbol *sym, gfc_actual_arglist *args,
2727                           gfc_symbol **new_sym)
2728 {
2729   char name[GFC_MAX_SYMBOL_LEN + 1];
2730   int optional_arg = 0;
2731   gfc_try retval = SUCCESS;
2732   gfc_symbol *args_sym;
2733   gfc_typespec *arg_ts;
2734   symbol_attribute arg_attr;
2735
2736   if (args->expr->expr_type == EXPR_CONSTANT
2737       || args->expr->expr_type == EXPR_OP
2738       || args->expr->expr_type == EXPR_NULL)
2739     {
2740       gfc_error ("Argument to '%s' at %L is not a variable",
2741                  sym->name, &(args->expr->where));
2742       return FAILURE;
2743     }
2744
2745   args_sym = args->expr->symtree->n.sym;
2746
2747   /* The typespec for the actual arg should be that stored in the expr
2748      and not necessarily that of the expr symbol (args_sym), because
2749      the actual expression could be a part-ref of the expr symbol.  */
2750   arg_ts = &(args->expr->ts);
2751   arg_attr = gfc_expr_attr (args->expr);
2752     
2753   if (sym->intmod_sym_id == ISOCBINDING_ASSOCIATED)
2754     {
2755       /* If the user gave two args then they are providing something for
2756          the optional arg (the second cptr).  Therefore, set the name and
2757          binding label to the c_associated for two cptrs.  Otherwise,
2758          set c_associated to expect one cptr.  */
2759       if (args->next)
2760         {
2761           /* two args.  */
2762           sprintf (name, "%s_2", sym->name);
2763           optional_arg = 1;
2764         }
2765       else
2766         {
2767           /* one arg.  */
2768           sprintf (name, "%s_1", sym->name);
2769           optional_arg = 0;
2770         }
2771
2772       /* Get a new symbol for the version of c_associated that
2773          will get called.  */
2774       *new_sym = get_iso_c_sym (sym, name, NULL, optional_arg);
2775     }
2776   else if (sym->intmod_sym_id == ISOCBINDING_LOC
2777            || sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2778     {
2779       sprintf (name, "%s", sym->name);
2780
2781       /* Error check the call.  */
2782       if (args->next != NULL)
2783         {
2784           gfc_error_now ("More actual than formal arguments in '%s' "
2785                          "call at %L", name, &(args->expr->where));
2786           retval = FAILURE;
2787         }
2788       else if (sym->intmod_sym_id == ISOCBINDING_LOC)
2789         {
2790           gfc_ref *ref;
2791           bool seen_section;
2792
2793           /* Make sure we have either the target or pointer attribute.  */
2794           if (!arg_attr.target && !arg_attr.pointer)
2795             {
2796               gfc_error_now ("Parameter '%s' to '%s' at %L must be either "
2797                              "a TARGET or an associated pointer",
2798                              args_sym->name,
2799                              sym->name, &(args->expr->where));
2800               retval = FAILURE;
2801             }
2802
2803           if (gfc_is_coindexed (args->expr))
2804             {
2805               gfc_error_now ("Coindexed argument not permitted"
2806                              " in '%s' call at %L", name,
2807                              &(args->expr->where));
2808               retval = FAILURE;
2809             }
2810
2811           /* Follow references to make sure there are no array
2812              sections.  */
2813           seen_section = false;
2814
2815           for (ref=args->expr->ref; ref; ref = ref->next)
2816             {
2817               if (ref->type == REF_ARRAY)
2818                 {
2819                   if (ref->u.ar.type == AR_SECTION)
2820                     seen_section = true;
2821
2822                   if (ref->u.ar.type != AR_ELEMENT)
2823                     {
2824                       gfc_ref *r;
2825                       for (r = ref->next; r; r=r->next)
2826                         if (r->type == REF_COMPONENT)
2827                           {
2828                             gfc_error_now ("Array section not permitted"
2829                                            " in '%s' call at %L", name,
2830                                            &(args->expr->where));
2831                             retval = FAILURE;
2832                             break;
2833                           }
2834                     }
2835                 }
2836             }
2837
2838           if (seen_section && retval == SUCCESS)
2839             gfc_warning ("Array section in '%s' call at %L", name,
2840                          &(args->expr->where));
2841                          
2842           /* See if we have interoperable type and type param.  */
2843           if (gfc_verify_c_interop (arg_ts) == SUCCESS
2844               || gfc_check_any_c_kind (arg_ts) == SUCCESS)
2845             {
2846               if (args_sym->attr.target == 1)
2847                 {
2848                   /* Case 1a, section 15.1.2.5, J3/04-007: variable that
2849                      has the target attribute and is interoperable.  */
2850                   /* Case 1b, section 15.1.2.5, J3/04-007: allocated
2851                      allocatable variable that has the TARGET attribute and
2852                      is not an array of zero size.  */
2853                   if (args_sym->attr.allocatable == 1)
2854                     {
2855                       if (args_sym->attr.dimension != 0 
2856                           && (args_sym->as && args_sym->as->rank == 0))
2857                         {
2858                           gfc_error_now ("Allocatable variable '%s' used as a "
2859                                          "parameter to '%s' at %L must not be "
2860                                          "an array of zero size",
2861                                          args_sym->name, sym->name,
2862                                          &(args->expr->where));
2863                           retval = FAILURE;
2864                         }
2865                     }
2866                   else
2867                     {
2868                       /* A non-allocatable target variable with C
2869                          interoperable type and type parameters must be
2870                          interoperable.  */
2871                       if (args_sym && args_sym->attr.dimension)
2872                         {
2873                           if (args_sym->as->type == AS_ASSUMED_SHAPE)
2874                             {
2875                               gfc_error ("Assumed-shape array '%s' at %L "
2876                                          "cannot be an argument to the "
2877                                          "procedure '%s' because "
2878                                          "it is not C interoperable",
2879                                          args_sym->name,
2880                                          &(args->expr->where), sym->name);
2881                               retval = FAILURE;
2882                             }
2883                           else if (args_sym->as->type == AS_DEFERRED)
2884                             {
2885                               gfc_error ("Deferred-shape array '%s' at %L "
2886                                          "cannot be an argument to the "
2887                                          "procedure '%s' because "
2888                                          "it is not C interoperable",
2889                                          args_sym->name,
2890                                          &(args->expr->where), sym->name);
2891                               retval = FAILURE;
2892                             }
2893                         }
2894                               
2895                       /* Make sure it's not a character string.  Arrays of
2896                          any type should be ok if the variable is of a C
2897                          interoperable type.  */
2898                       if (arg_ts->type == BT_CHARACTER)
2899                         if (arg_ts->u.cl != NULL
2900                             && (arg_ts->u.cl->length == NULL
2901                                 || arg_ts->u.cl->length->expr_type
2902                                    != EXPR_CONSTANT
2903                                 || mpz_cmp_si
2904                                     (arg_ts->u.cl->length->value.integer, 1)
2905                                    != 0)
2906                             && is_scalar_expr_ptr (args->expr) != SUCCESS)
2907                           {
2908                             gfc_error_now ("CHARACTER argument '%s' to '%s' "
2909                                            "at %L must have a length of 1",
2910                                            args_sym->name, sym->name,
2911                                            &(args->expr->where));
2912                             retval = FAILURE;
2913                           }
2914                     }
2915                 }
2916               else if (arg_attr.pointer
2917                        && is_scalar_expr_ptr (args->expr) != SUCCESS)
2918                 {
2919                   /* Case 1c, section 15.1.2.5, J3/04-007: an associated
2920                      scalar pointer.  */
2921                   gfc_error_now ("Argument '%s' to '%s' at %L must be an "
2922                                  "associated scalar POINTER", args_sym->name,
2923                                  sym->name, &(args->expr->where));
2924                   retval = FAILURE;
2925                 }
2926             }
2927           else
2928             {
2929               /* The parameter is not required to be C interoperable.  If it
2930                  is not C interoperable, it must be a nonpolymorphic scalar
2931                  with no length type parameters.  It still must have either
2932                  the pointer or target attribute, and it can be
2933                  allocatable (but must be allocated when c_loc is called).  */
2934               if (args->expr->rank != 0 
2935                   && is_scalar_expr_ptr (args->expr) != SUCCESS)
2936                 {
2937                   gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2938                                  "scalar", args_sym->name, sym->name,
2939                                  &(args->expr->where));
2940                   retval = FAILURE;
2941                 }
2942               else if (arg_ts->type == BT_CHARACTER 
2943                        && is_scalar_expr_ptr (args->expr) != SUCCESS)
2944                 {
2945                   gfc_error_now ("CHARACTER argument '%s' to '%s' at "
2946                                  "%L must have a length of 1",
2947                                  args_sym->name, sym->name,
2948                                  &(args->expr->where));
2949                   retval = FAILURE;
2950                 }
2951               else if (arg_ts->type == BT_CLASS)
2952                 {
2953                   gfc_error_now ("Parameter '%s' to '%s' at %L must not be "
2954                                  "polymorphic", args_sym->name, sym->name,
2955                                  &(args->expr->where));
2956                   retval = FAILURE;
2957                 }
2958             }
2959         }
2960       else if (sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2961         {
2962           if (args_sym->attr.flavor != FL_PROCEDURE)
2963             {
2964               /* TODO: Update this error message to allow for procedure
2965                  pointers once they are implemented.  */
2966               gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2967                              "procedure",
2968                              args_sym->name, sym->name,
2969                              &(args->expr->where));
2970               retval = FAILURE;
2971             }
2972           else if (args_sym->attr.is_bind_c != 1)
2973             {
2974               gfc_error_now ("Parameter '%s' to '%s' at %L must be "
2975                              "BIND(C)",
2976                              args_sym->name, sym->name,
2977                              &(args->expr->where));
2978               retval = FAILURE;
2979             }
2980         }
2981       
2982       /* for c_loc/c_funloc, the new symbol is the same as the old one */
2983       *new_sym = sym;
2984     }
2985   else
2986     {
2987       gfc_internal_error ("gfc_iso_c_func_interface(): Unhandled "
2988                           "iso_c_binding function: '%s'!\n", sym->name);
2989     }
2990
2991   return retval;
2992 }
2993
2994
2995 /* Resolve a function call, which means resolving the arguments, then figuring
2996    out which entity the name refers to.  */
2997
2998 static gfc_try
2999 resolve_function (gfc_expr *expr)
3000 {
3001   gfc_actual_arglist *arg;
3002   gfc_symbol *sym;
3003   const char *name;
3004   gfc_try t;
3005   int temp;
3006   procedure_type p = PROC_INTRINSIC;
3007   bool no_formal_args;
3008
3009   sym = NULL;
3010   if (expr->symtree)
3011     sym = expr->symtree->n.sym;
3012
3013   /* If this is a procedure pointer component, it has already been resolved.  */
3014   if (gfc_is_proc_ptr_comp (expr, NULL))
3015     return SUCCESS;
3016   
3017   if (sym && sym->attr.intrinsic
3018       && resolve_intrinsic (sym, &expr->where) == FAILURE)
3019     return FAILURE;
3020
3021   if (sym && (sym->attr.flavor == FL_VARIABLE || sym->attr.subroutine))
3022     {
3023       gfc_error ("'%s' at %L is not a function", sym->name, &expr->where);
3024       return FAILURE;
3025     }
3026
3027   /* If this ia a deferred TBP with an abstract interface (which may
3028      of course be referenced), expr->value.function.esym will be set.  */
3029   if (sym && sym->attr.abstract && !expr->value.function.esym)
3030     {
3031       gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
3032                  sym->name, &expr->where);
3033       return FAILURE;
3034     }
3035
3036   /* Switch off assumed size checking and do this again for certain kinds
3037      of procedure, once the procedure itself is resolved.  */
3038   need_full_assumed_size++;
3039
3040   if (expr->symtree && expr->symtree->n.sym)
3041     p = expr->symtree->n.sym->attr.proc;
3042
3043   if (expr->value.function.isym && expr->value.function.isym->inquiry)
3044     inquiry_argument = true;
3045   no_formal_args = sym && is_external_proc (sym) && sym->formal == NULL;
3046
3047   if (resolve_actual_arglist (expr->value.function.actual,
3048                               p, no_formal_args) == FAILURE)
3049     {
3050       inquiry_argument = false;
3051       return FAILURE;
3052     }
3053
3054   inquiry_argument = false;
3055  
3056   /* Need to setup the call to the correct c_associated, depending on
3057      the number of cptrs to user gives to compare.  */
3058   if (sym && sym->attr.is_iso_c == 1)
3059     {
3060       if (gfc_iso_c_func_interface (sym, expr->value.function.actual, &sym)
3061           == FAILURE)
3062         return FAILURE;
3063       
3064       /* Get the symtree for the new symbol (resolved func).
3065          the old one will be freed later, when it's no longer used.  */
3066       gfc_find_sym_tree (sym->name, sym->ns, 1, &(expr->symtree));
3067     }
3068   
3069   /* Resume assumed_size checking.  */
3070   need_full_assumed_size--;
3071
3072   /* If the procedure is external, check for usage.  */
3073   if (sym && is_external_proc (sym))
3074     resolve_global_procedure (sym, &expr->where,
3075                               &expr->value.function.actual, 0);
3076
3077   if (sym && sym->ts.type == BT_CHARACTER
3078       && sym->ts.u.cl
3079       && sym->ts.u.cl->length == NULL
3080       && !sym->attr.dummy
3081       && !sym->ts.deferred
3082       && expr->value.function.esym == NULL
3083       && !sym->attr.contained)
3084     {
3085       /* Internal procedures are taken care of in resolve_contained_fntype.  */
3086       gfc_error ("Function '%s' is declared CHARACTER(*) and cannot "
3087                  "be used at %L since it is not a dummy argument",
3088                  sym->name, &expr->where);
3089       return FAILURE;
3090     }
3091
3092   /* See if function is already resolved.  */
3093
3094   if (expr->value.function.name != NULL)
3095     {
3096       if (expr->ts.type == BT_UNKNOWN)
3097         expr->ts = sym->ts;
3098       t = SUCCESS;
3099     }
3100   else
3101     {
3102       /* Apply the rules of section 14.1.2.  */
3103
3104       switch (procedure_kind (sym))
3105         {
3106         case PTYPE_GENERIC:
3107           t = resolve_generic_f (expr);
3108           break;
3109
3110         case PTYPE_SPECIFIC:
3111           t = resolve_specific_f (expr);
3112           break;
3113
3114         case PTYPE_UNKNOWN:
3115           t = resolve_unknown_f (expr);
3116           break;
3117
3118         default:
3119           gfc_internal_error ("resolve_function(): bad function type");
3120         }
3121     }
3122
3123   /* If the expression is still a function (it might have simplified),
3124      then we check to see if we are calling an elemental function.  */
3125
3126   if (expr->expr_type != EXPR_FUNCTION)
3127     return t;
3128
3129   temp = need_full_assumed_size;
3130   need_full_assumed_size = 0;
3131
3132   if (resolve_elemental_actual (expr, NULL) == FAILURE)
3133     return FAILURE;
3134
3135   if (omp_workshare_flag
3136       && expr->value.function.esym
3137       && ! gfc_elemental (expr->value.function.esym))
3138     {
3139       gfc_error ("User defined non-ELEMENTAL function '%s' at %L not allowed "
3140                  "in WORKSHARE construct", expr->value.function.esym->name,
3141                  &expr->where);
3142       t = FAILURE;
3143     }
3144
3145 #define GENERIC_ID expr->value.function.isym->id
3146   else if (expr->value.function.actual != NULL
3147            && expr->value.function.isym != NULL
3148            && GENERIC_ID != GFC_ISYM_LBOUND
3149            && GENERIC_ID != GFC_ISYM_LEN
3150            && GENERIC_ID != GFC_ISYM_LOC
3151            && GENERIC_ID != GFC_ISYM_PRESENT)
3152     {
3153       /* Array intrinsics must also have the last upper bound of an
3154          assumed size array argument.  UBOUND and SIZE have to be
3155          excluded from the check if the second argument is anything
3156          than a constant.  */
3157
3158       for (arg = expr->value.function.actual; arg; arg = arg->next)
3159         {
3160           if ((GENERIC_ID == GFC_ISYM_UBOUND || GENERIC_ID == GFC_ISYM_SIZE)
3161               && arg->next != NULL && arg->next->expr)
3162             {
3163               if (arg->next->expr->expr_type != EXPR_CONSTANT)
3164                 break;
3165
3166               if (arg->next->name && strncmp(arg->next->name, "kind", 4) == 0)
3167                 break;
3168
3169               if ((int)mpz_get_si (arg->next->expr->value.integer)
3170                         < arg->expr->rank)
3171                 break;
3172             }
3173
3174           if (arg->expr != NULL
3175               && arg->expr->rank > 0
3176               && resolve_assumed_size_actual (arg->expr))
3177             return FAILURE;
3178         }
3179     }
3180 #undef GENERIC_ID
3181
3182   need_full_assumed_size = temp;
3183   name = NULL;
3184
3185   if (!pure_function (expr, &name) && name)
3186     {
3187       if (forall_flag)
3188         {
3189           gfc_error ("Reference to non-PURE function '%s' at %L inside a "
3190                      "FORALL %s", name, &expr->where,
3191                      forall_flag == 2 ? "mask" : "block");
3192           t = FAILURE;
3193         }
3194       else if (do_concurrent_flag)
3195         {
3196           gfc_error ("Reference to non-PURE function '%s' at %L inside a "
3197                      "DO CONCURRENT %s", name, &expr->where,
3198                      do_concurrent_flag == 2 ? "mask" : "block");
3199           t = FAILURE;
3200         }
3201       else if (gfc_pure (NULL))
3202         {
3203           gfc_error ("Function reference to '%s' at %L is to a non-PURE "
3204                      "procedure within a PURE procedure", name, &expr->where);
3205           t = FAILURE;
3206         }
3207
3208       if (gfc_implicit_pure (NULL))
3209         gfc_current_ns->proc_name->attr.implicit_pure = 0;
3210     }
3211
3212   /* Functions without the RECURSIVE attribution are not allowed to
3213    * call themselves.  */
3214   if (expr->value.function.esym && !expr->value.function.esym->attr.recursive)
3215     {
3216       gfc_symbol *esym;
3217       esym = expr->value.function.esym;
3218
3219       if (is_illegal_recursion (esym, gfc_current_ns))
3220       {
3221         if (esym->attr.entry && esym->ns->entries)
3222           gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
3223                      " function '%s' is not RECURSIVE",
3224                      esym->name, &expr->where, esym->ns->entries->sym->name);
3225         else
3226           gfc_error ("Function '%s' at %L cannot be called recursively, as it"
3227                      " is not RECURSIVE", esym->name, &expr->where);
3228
3229         t = FAILURE;
3230       }
3231     }
3232
3233   /* Character lengths of use associated functions may contains references to
3234      symbols not referenced from the current program unit otherwise.  Make sure
3235      those symbols are marked as referenced.  */
3236
3237   if (expr->ts.type == BT_CHARACTER && expr->value.function.esym
3238       && expr->value.function.esym->attr.use_assoc)
3239     {
3240       gfc_expr_set_symbols_referenced (expr->ts.u.cl->length);
3241     }
3242
3243   /* Make sure that the expression has a typespec that works.  */
3244   if (expr->ts.type == BT_UNKNOWN)
3245     {
3246       if (expr->symtree->n.sym->result
3247             && expr->symtree->n.sym->result->ts.type != BT_UNKNOWN
3248             && !expr->symtree->n.sym->result->attr.proc_pointer)
3249         expr->ts = expr->symtree->n.sym->result->ts;
3250     }
3251
3252   return t;
3253 }
3254
3255
3256 /************* Subroutine resolution *************/
3257
3258 static void
3259 pure_subroutine (gfc_code *c, gfc_symbol *sym)
3260 {
3261   if (gfc_pure (sym))
3262     return;
3263
3264   if (forall_flag)
3265     gfc_error ("Subroutine call to '%s' in FORALL block at %L is not PURE",
3266                sym->name, &c->loc);
3267   else if (do_concurrent_flag)
3268     gfc_error ("Subroutine call to '%s' in DO CONCURRENT block at %L is not "
3269                "PURE", sym->name, &c->loc);
3270   else if (gfc_pure (NULL))
3271     gfc_error ("Subroutine call to '%s' at %L is not PURE", sym->name,
3272                &c->loc);
3273
3274   if (gfc_implicit_pure (NULL))
3275     gfc_current_ns->proc_name->attr.implicit_pure = 0;
3276 }
3277
3278
3279 static match
3280 resolve_generic_s0 (gfc_code *c, gfc_symbol *sym)
3281 {
3282   gfc_symbol *s;
3283
3284   if (sym->attr.generic)
3285     {
3286       s = gfc_search_interface (sym->generic, 1, &c->ext.actual);
3287       if (s != NULL)
3288         {
3289           c->resolved_sym = s;
3290           pure_subroutine (c, s);
3291           return MATCH_YES;
3292         }
3293
3294       /* TODO: Need to search for elemental references in generic interface.  */
3295     }
3296
3297   if (sym->attr.intrinsic)
3298     return gfc_intrinsic_sub_interface (c, 0);
3299
3300   return MATCH_NO;
3301 }
3302
3303
3304 static gfc_try
3305 resolve_generic_s (gfc_code *c)
3306 {
3307   gfc_symbol *sym;
3308   match m;
3309
3310   sym = c->symtree->n.sym;
3311
3312   for (;;)
3313     {
3314       m = resolve_generic_s0 (c, sym);
3315       if (m == MATCH_YES)
3316         return SUCCESS;
3317       else if (m == MATCH_ERROR)
3318         return FAILURE;
3319
3320 generic:
3321       if (sym->ns->parent == NULL)
3322         break;
3323       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
3324
3325       if (sym == NULL)
3326         break;
3327       if (!generic_sym (sym))
3328         goto generic;
3329     }
3330
3331   /* Last ditch attempt.  See if the reference is to an intrinsic
3332      that possesses a matching interface.  14.1.2.4  */
3333   sym = c->symtree->n.sym;
3334
3335   if (!gfc_is_intrinsic (sym, 1, c->loc))
3336     {
3337       gfc_error ("There is no specific subroutine for the generic '%s' at %L",
3338                  sym->name, &c->loc);
3339       return FAILURE;
3340     }
3341
3342   m = gfc_intrinsic_sub_interface (c, 0);
3343   if (m == MATCH_YES)
3344     return SUCCESS;
3345   if (m == MATCH_NO)
3346     gfc_error ("Generic subroutine '%s' at %L is not consistent with an "
3347                "intrinsic subroutine interface", sym->name, &c->loc);
3348
3349   return FAILURE;
3350 }
3351
3352
3353 /* Set the name and binding label of the subroutine symbol in the call
3354    expression represented by 'c' to include the type and kind of the
3355    second parameter.  This function is for resolving the appropriate
3356    version of c_f_pointer() and c_f_procpointer().  For example, a
3357    call to c_f_pointer() for a default integer pointer could have a
3358    name of c_f_pointer_i4.  If no second arg exists, which is an error
3359    for these two functions, it defaults to the generic symbol's name
3360    and binding label.  */
3361
3362 static void
3363 set_name_and_label (gfc_code *c, gfc_symbol *sym,
3364                     char *name, const char **binding_label)
3365 {
3366   gfc_expr *arg = NULL;
3367   char type;
3368   int kind;
3369
3370   /* The second arg of c_f_pointer and c_f_procpointer determines
3371      the type and kind for the procedure name.  */
3372   arg = c->ext.actual->next->expr;
3373
3374   if (arg != NULL)
3375     {
3376       /* Set up the name to have the given symbol's name,
3377          plus the type and kind.  */
3378       /* a derived type is marked with the type letter 'u' */
3379       if (arg->ts.type == BT_DERIVED)
3380         {
3381           type = 'd';
3382           kind = 0; /* set the kind as 0 for now */
3383         }
3384       else
3385         {
3386           type = gfc_type_letter (arg->ts.type);
3387           kind = arg->ts.kind;
3388         }
3389
3390       if (arg->ts.type == BT_CHARACTER)
3391         /* Kind info for character strings not needed.  */
3392         kind = 0;
3393
3394       sprintf (name, "%s_%c%d", sym->name, type, kind);
3395       /* Set up the binding label as the given symbol's label plus
3396          the type and kind.  */
3397       *binding_label = gfc_get_string ("%s_%c%d", sym->binding_label, type, 
3398                                        kind);
3399     }
3400   else
3401     {
3402       /* If the second arg is missing, set the name and label as
3403          was, cause it should at least be found, and the missing
3404          arg error will be caught by compare_parameters().  */
3405       sprintf (name, "%s", sym->name);
3406       *binding_label = sym->binding_label;
3407     }
3408    
3409   return;
3410 }
3411
3412
3413 /* Resolve a generic version of the iso_c_binding procedure given
3414    (sym) to the specific one based on the type and kind of the
3415    argument(s).  Currently, this function resolves c_f_pointer() and
3416    c_f_procpointer based on the type and kind of the second argument
3417    (FPTR).  Other iso_c_binding procedures aren't specially handled.
3418    Upon successfully exiting, c->resolved_sym will hold the resolved
3419    symbol.  Returns MATCH_ERROR if an error occurred; MATCH_YES
3420    otherwise.  */
3421
3422 match
3423 gfc_iso_c_sub_interface (gfc_code *c, gfc_symbol *sym)
3424 {
3425   gfc_symbol *new_sym;
3426   /* this is fine, since we know the names won't use the max */
3427   char name[GFC_MAX_SYMBOL_LEN + 1];
3428   const char* binding_label;
3429   /* default to success; will override if find error */
3430   match m = MATCH_YES;
3431
3432   /* Make sure the actual arguments are in the necessary order (based on the 
3433      formal args) before resolving.  */
3434   gfc_procedure_use (sym, &c->ext.actual, &(c->loc));
3435
3436   if ((sym->intmod_sym_id == ISOCBINDING_F_POINTER) ||
3437       (sym->intmod_sym_id == ISOCBINDING_F_PROCPOINTER))
3438     {
3439       set_name_and_label (c, sym, name, &binding_label);
3440       
3441       if (sym->intmod_sym_id == ISOCBINDING_F_POINTER)
3442         {
3443           if (c->ext.actual != NULL && c->ext.actual->next != NULL)
3444             {
3445               /* Make sure we got a third arg if the second arg has non-zero
3446                  rank.  We must also check that the type and rank are
3447                  correct since we short-circuit this check in
3448                  gfc_procedure_use() (called above to sort actual args).  */
3449               if (c->ext.actual->next->expr->rank != 0)
3450                 {
3451                   if(c->ext.actual->next->next == NULL 
3452                      || c->ext.actual->next->next->expr == NULL)
3453                     {
3454                       m = MATCH_ERROR;
3455                       gfc_error ("Missing SHAPE parameter for call to %s "
3456                                  "at %L", sym->name, &(c->loc));
3457                     }
3458                   else if (c->ext.actual->next->next->expr->ts.type
3459                            != BT_INTEGER
3460                            || c->ext.actual->next->next->expr->rank != 1)
3461                     {
3462                       m = MATCH_ERROR;
3463                       gfc_error ("SHAPE parameter for call to %s at %L must "
3464                                  "be a rank 1 INTEGER array", sym->name,
3465                                  &(c->loc));
3466                     }
3467                 }
3468             }
3469         }
3470       
3471       if (m != MATCH_ERROR)
3472         {
3473           /* the 1 means to add the optional arg to formal list */
3474           new_sym = get_iso_c_sym (sym, name, binding_label, 1);
3475          
3476           /* for error reporting, say it's declared where the original was */
3477           new_sym->declared_at = sym->declared_at;
3478         }
3479     }
3480   else
3481     {
3482       /* no differences for c_loc or c_funloc */
3483       new_sym = sym;
3484     }
3485
3486   /* set the resolved symbol */
3487   if (m != MATCH_ERROR)
3488     c->resolved_sym = new_sym;
3489   else
3490     c->resolved_sym = sym;
3491   
3492   return m;
3493 }
3494
3495
3496 /* Resolve a subroutine call known to be specific.  */
3497
3498 static match
3499 resolve_specific_s0 (gfc_code *c, gfc_symbol *sym)
3500 {
3501   match m;
3502
3503   if(sym->attr.is_iso_c)
3504     {
3505       m = gfc_iso_c_sub_interface (c,sym);
3506       return m;
3507     }
3508   
3509   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
3510     {
3511       if (sym->attr.dummy)
3512         {
3513           sym->attr.proc = PROC_DUMMY;
3514           goto found;
3515         }
3516
3517       sym->attr.proc = PROC_EXTERNAL;
3518       goto found;
3519     }
3520
3521   if (sym->attr.proc == PROC_MODULE || sym->attr.proc == PROC_INTERNAL)
3522     goto found;
3523
3524   if (sym->attr.intrinsic)
3525     {
3526       m = gfc_intrinsic_sub_interface (c, 1);
3527       if (m == MATCH_YES)
3528         return MATCH_YES;
3529       if (m == MATCH_NO)
3530         gfc_error ("Subroutine '%s' at %L is INTRINSIC but is not compatible "
3531                    "with an intrinsic", sym->name, &c->loc);
3532
3533       return MATCH_ERROR;
3534     }
3535
3536   return MATCH_NO;
3537
3538 found:
3539   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3540
3541   c->resolved_sym = sym;
3542   pure_subroutine (c, sym);
3543
3544   return MATCH_YES;
3545 }
3546
3547
3548 static gfc_try
3549 resolve_specific_s (gfc_code *c)
3550 {
3551   gfc_symbol *sym;
3552   match m;
3553
3554   sym = c->symtree->n.sym;
3555
3556   for (;;)
3557     {
3558       m = resolve_specific_s0 (c, sym);
3559       if (m == MATCH_YES)
3560         return SUCCESS;
3561       if (m == MATCH_ERROR)
3562         return FAILURE;
3563
3564       if (sym->ns->parent == NULL)
3565         break;
3566
3567       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
3568
3569       if (sym == NULL)
3570         break;
3571     }
3572
3573   sym = c->symtree->n.sym;
3574   gfc_error ("Unable to resolve the specific subroutine '%s' at %L",
3575              sym->name, &c->loc);
3576
3577   return FAILURE;
3578 }
3579
3580
3581 /* Resolve a subroutine call not known to be generic nor specific.  */
3582
3583 static gfc_try
3584 resolve_unknown_s (gfc_code *c)
3585 {
3586   gfc_symbol *sym;
3587
3588   sym = c->symtree->n.sym;
3589
3590   if (sym->attr.dummy)
3591     {
3592       sym->attr.proc = PROC_DUMMY;
3593       goto found;
3594     }
3595
3596   /* See if we have an intrinsic function reference.  */
3597
3598   if (gfc_is_intrinsic (sym, 1, c->loc))
3599     {
3600       if (gfc_intrinsic_sub_interface (c, 1) == MATCH_YES)
3601         return SUCCESS;
3602       return FAILURE;
3603     }
3604
3605   /* The reference is to an external name.  */
3606
3607 found:
3608   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3609
3610   c->resolved_sym = sym;
3611
3612   pure_subroutine (c, sym);
3613
3614   return SUCCESS;
3615 }
3616
3617
3618 /* Resolve a subroutine call.  Although it was tempting to use the same code
3619    for functions, subroutines and functions are stored differently and this
3620    makes things awkward.  */
3621
3622 static gfc_try
3623 resolve_call (gfc_code *c)
3624 {
3625   gfc_try t;
3626   procedure_type ptype = PROC_INTRINSIC;
3627   gfc_symbol *csym, *sym;
3628   bool no_formal_args;
3629
3630   csym = c->symtree ? c->symtree->n.sym : NULL;
3631
3632   if (csym && csym->ts.type != BT_UNKNOWN)
3633     {
3634       gfc_error ("'%s' at %L has a type, which is not consistent with "
3635                  "the CALL at %L", csym->name, &csym->declared_at, &c->loc);
3636       return FAILURE;
3637     }
3638
3639   if (csym && gfc_current_ns->parent && csym->ns != gfc_current_ns)
3640     {
3641       gfc_symtree *st;
3642       gfc_find_sym_tree (csym->name, gfc_current_ns, 1, &st);
3643       sym = st ? st->n.sym : NULL;
3644       if (sym && csym != sym
3645               && sym->ns == gfc_current_ns
3646               && sym->attr.flavor == FL_PROCEDURE
3647               && sym->attr.contained)
3648         {
3649           sym->refs++;
3650           if (csym->attr.generic)
3651             c->symtree->n.sym = sym;
3652           else
3653             c->symtree = st;
3654           csym = c->symtree->n.sym;
3655         }
3656     }
3657
3658   /* If this ia a deferred TBP with an abstract interface
3659      (which may of course be referenced), c->expr1 will be set.  */
3660   if (csym && csym->attr.abstract && !c->expr1)
3661     {
3662       gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
3663                  csym->name, &c->loc);
3664       return FAILURE;
3665     }
3666
3667   /* Subroutines without the RECURSIVE attribution are not allowed to
3668    * call themselves.  */
3669   if (csym && is_illegal_recursion (csym, gfc_current_ns))
3670     {
3671       if (csym->attr.entry && csym->ns->entries)
3672         gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
3673                    " subroutine '%s' is not RECURSIVE",
3674                    csym->name, &c->loc, csym->ns->entries->sym->name);
3675       else
3676         gfc_error ("SUBROUTINE '%s' at %L cannot be called recursively, as it"
3677                    " is not RECURSIVE", csym->name, &c->loc);
3678
3679       t = FAILURE;
3680     }
3681
3682   /* Switch off assumed size checking and do this again for certain kinds
3683      of procedure, once the procedure itself is resolved.  */
3684   need_full_assumed_size++;
3685
3686   if (csym)
3687     ptype = csym->attr.proc;
3688
3689   no_formal_args = csym && is_external_proc (csym) && csym->formal == NULL;
3690   if (resolve_actual_arglist (c->ext.actual, ptype,
3691                               no_formal_args) == FAILURE)
3692     return FAILURE;
3693
3694   /* Resume assumed_size checking.  */
3695   need_full_assumed_size--;
3696
3697   /* If external, check for usage.  */
3698   if (csym && is_external_proc (csym))
3699     resolve_global_procedure (csym, &c->loc, &c->ext.actual, 1);
3700
3701   t = SUCCESS;
3702   if (c->resolved_sym == NULL)
3703     {
3704       c->resolved_isym = NULL;
3705       switch (procedure_kind (csym))
3706         {
3707         case PTYPE_GENERIC:
3708           t = resolve_generic_s (c);
3709           break;
3710
3711         case PTYPE_SPECIFIC:
3712           t = resolve_specific_s (c);
3713           break;
3714
3715         case PTYPE_UNKNOWN:
3716           t = resolve_unknown_s (c);
3717           break;
3718
3719         default:
3720           gfc_internal_error ("resolve_subroutine(): bad function type");
3721         }
3722     }
3723
3724   /* Some checks of elemental subroutine actual arguments.  */
3725   if (resolve_elemental_actual (NULL, c) == FAILURE)
3726     return FAILURE;
3727
3728   return t;
3729 }
3730
3731
3732 /* Compare the shapes of two arrays that have non-NULL shapes.  If both
3733    op1->shape and op2->shape are non-NULL return SUCCESS if their shapes
3734    match.  If both op1->shape and op2->shape are non-NULL return FAILURE
3735    if their shapes do not match.  If either op1->shape or op2->shape is
3736    NULL, return SUCCESS.  */
3737
3738 static gfc_try
3739 compare_shapes (gfc_expr *op1, gfc_expr *op2)
3740 {
3741   gfc_try t;
3742   int i;
3743
3744   t = SUCCESS;
3745
3746   if (op1->shape != NULL && op2->shape != NULL)
3747     {
3748       for (i = 0; i < op1->rank; i++)
3749         {
3750           if (mpz_cmp (op1->shape[i], op2->shape[i]) != 0)
3751            {
3752              gfc_error ("Shapes for operands at %L and %L are not conformable",
3753                          &op1->where, &op2->where);
3754              t = FAILURE;
3755              break;
3756            }
3757         }
3758     }
3759
3760   return t;
3761 }
3762
3763
3764 /* Resolve an operator expression node.  This can involve replacing the
3765    operation with a user defined function call.  */
3766
3767 static gfc_try
3768 resolve_operator (gfc_expr *e)
3769 {
3770   gfc_expr *op1, *op2;
3771   char msg[200];
3772   bool dual_locus_error;
3773   gfc_try t;
3774
3775   /* Resolve all subnodes-- give them types.  */
3776
3777   switch (e->value.op.op)
3778     {
3779     default:
3780       if (gfc_resolve_expr (e->value.op.op2) == FAILURE)
3781         return FAILURE;
3782
3783     /* Fall through...  */
3784
3785     case INTRINSIC_NOT:
3786     case INTRINSIC_UPLUS:
3787     case INTRINSIC_UMINUS:
3788     case INTRINSIC_PARENTHESES:
3789       if (gfc_resolve_expr (e->value.op.op1) == FAILURE)
3790         return FAILURE;
3791       break;
3792     }
3793
3794   /* Typecheck the new node.  */
3795
3796   op1 = e->value.op.op1;
3797   op2 = e->value.op.op2;
3798   dual_locus_error = false;
3799
3800   if ((op1 && op1->expr_type == EXPR_NULL)
3801       || (op2 && op2->expr_type == EXPR_NULL))
3802     {
3803       sprintf (msg, _("Invalid context for NULL() pointer at %%L"));
3804       goto bad_op;
3805     }
3806
3807   switch (e->value.op.op)
3808     {
3809     case INTRINSIC_UPLUS:
3810     case INTRINSIC_UMINUS:
3811       if (op1->ts.type == BT_INTEGER
3812           || op1->ts.type == BT_REAL
3813           || op1->ts.type == BT_COMPLEX)
3814         {
3815           e->ts = op1->ts;
3816           break;
3817         }
3818
3819       sprintf (msg, _("Operand of unary numeric operator '%s' at %%L is %s"),
3820                gfc_op2string (e->value.op.op), gfc_typename (&e->ts));
3821       goto bad_op;
3822
3823     case INTRINSIC_PLUS:
3824     case INTRINSIC_MINUS:
3825     case INTRINSIC_TIMES:
3826     case INTRINSIC_DIVIDE:
3827     case INTRINSIC_POWER:
3828       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3829         {
3830           gfc_type_convert_binary (e, 1);
3831           break;
3832         }
3833
3834       sprintf (msg,
3835                _("Operands of binary numeric operator '%s' at %%L are %s/%s"),
3836                gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3837                gfc_typename (&op2->ts));
3838       goto bad_op;
3839
3840     case INTRINSIC_CONCAT:
3841       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3842           && op1->ts.kind == op2->ts.kind)
3843         {
3844           e->ts.type = BT_CHARACTER;
3845           e->ts.kind = op1->ts.kind;
3846           break;
3847         }
3848
3849       sprintf (msg,
3850                _("Operands of string concatenation operator at %%L are %s/%s"),
3851                gfc_typename (&op1->ts), gfc_typename (&op2->ts));
3852       goto bad_op;
3853
3854     case INTRINSIC_AND:
3855     case INTRINSIC_OR:
3856     case INTRINSIC_EQV:
3857     case INTRINSIC_NEQV:
3858       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3859         {
3860           e->ts.type = BT_LOGICAL;
3861           e->ts.kind = gfc_kind_max (op1, op2);
3862           if (op1->ts.kind < e->ts.kind)
3863             gfc_convert_type (op1, &e->ts, 2);
3864           else if (op2->ts.kind < e->ts.kind)
3865             gfc_convert_type (op2, &e->ts, 2);
3866           break;
3867         }
3868
3869       sprintf (msg, _("Operands of logical operator '%s' at %%L are %s/%s"),
3870                gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3871                gfc_typename (&op2->ts));
3872
3873       goto bad_op;
3874
3875     case INTRINSIC_NOT:
3876       if (op1->ts.type == BT_LOGICAL)
3877         {
3878           e->ts.type = BT_LOGICAL;
3879           e->ts.kind = op1->ts.kind;
3880           break;
3881         }
3882
3883       sprintf (msg, _("Operand of .not. operator at %%L is %s"),
3884                gfc_typename (&op1->ts));
3885       goto bad_op;
3886
3887     case INTRINSIC_GT:
3888     case INTRINSIC_GT_OS:
3889     case INTRINSIC_GE:
3890     case INTRINSIC_GE_OS:
3891     case INTRINSIC_LT:
3892     case INTRINSIC_LT_OS:
3893     case INTRINSIC_LE:
3894     case INTRINSIC_LE_OS:
3895       if (op1->ts.type == BT_COMPLEX || op2->ts.type == BT_COMPLEX)
3896         {
3897           strcpy (msg, _("COMPLEX quantities cannot be compared at %L"));
3898           goto bad_op;
3899         }
3900
3901       /* Fall through...  */
3902
3903     case INTRINSIC_EQ:
3904     case INTRINSIC_EQ_OS:
3905     case INTRINSIC_NE:
3906     case INTRINSIC_NE_OS:
3907       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3908           && op1->ts.kind == op2->ts.kind)
3909         {
3910           e->ts.type = BT_LOGICAL;
3911           e->ts.kind = gfc_default_logical_kind;
3912           break;
3913         }
3914
3915       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3916         {
3917           gfc_type_convert_binary (e, 1);
3918
3919           e->ts.type = BT_LOGICAL;
3920           e->ts.kind = gfc_default_logical_kind;
3921           break;
3922         }
3923
3924       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3925         sprintf (msg,
3926                  _("Logicals at %%L must be compared with %s instead of %s"),
3927                  (e->value.op.op == INTRINSIC_EQ 
3928                   || e->value.op.op == INTRINSIC_EQ_OS)
3929                  ? ".eqv." : ".neqv.", gfc_op2string (e->value.op.op));
3930       else
3931         sprintf (msg,
3932                  _("Operands of comparison operator '%s' at %%L are %s/%s"),
3933                  gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3934                  gfc_typename (&op2->ts));
3935
3936       goto bad_op;
3937
3938     case INTRINSIC_USER:
3939       if (e->value.op.uop->op == NULL)
3940         sprintf (msg, _("Unknown operator '%s' at %%L"), e->value.op.uop->name);
3941       else if (op2 == NULL)
3942         sprintf (msg, _("Operand of user operator '%s' at %%L is %s"),
3943                  e->value.op.uop->name, gfc_typename (&op1->ts));
3944       else
3945         {
3946           sprintf (msg, _("Operands of user operator '%s' at %%L are %s/%s"),
3947                    e->value.op.uop->name, gfc_typename (&op1->ts),
3948                    gfc_typename (&op2->ts));
3949           e->value.op.uop->op->sym->attr.referenced = 1;
3950         }
3951
3952       goto bad_op;
3953
3954     case INTRINSIC_PARENTHESES:
3955       e->ts = op1->ts;
3956       if (e->ts.type == BT_CHARACTER)
3957         e->ts.u.cl = op1->ts.u.cl;
3958       break;
3959
3960     default:
3961       gfc_internal_error ("resolve_operator(): Bad intrinsic");
3962     }
3963
3964   /* Deal with arrayness of an operand through an operator.  */
3965
3966   t = SUCCESS;
3967
3968   switch (e->value.op.op)
3969     {
3970     case INTRINSIC_PLUS:
3971     case INTRINSIC_MINUS:
3972     case INTRINSIC_TIMES:
3973     case INTRINSIC_DIVIDE:
3974     case INTRINSIC_POWER:
3975     case INTRINSIC_CONCAT:
3976     case INTRINSIC_AND:
3977     case INTRINSIC_OR:
3978     case INTRINSIC_EQV:
3979     case INTRINSIC_NEQV:
3980     case INTRINSIC_EQ:
3981     case INTRINSIC_EQ_OS:
3982     case INTRINSIC_NE:
3983     case INTRINSIC_NE_OS:
3984     case INTRINSIC_GT:
3985     case INTRINSIC_GT_OS:
3986     case INTRINSIC_GE:
3987     case INTRINSIC_GE_OS:
3988     case INTRINSIC_LT:
3989     case INTRINSIC_LT_OS:
3990     case INTRINSIC_LE:
3991     case INTRINSIC_LE_OS:
3992
3993       if (op1->rank == 0 && op2->rank == 0)
3994         e->rank = 0;
3995
3996       if (op1->rank == 0 && op2->rank != 0)
3997         {
3998           e->rank = op2->rank;
3999
4000           if (e->shape == NULL)
4001             e->shape = gfc_copy_shape (op2->shape, op2->rank);
4002         }
4003
4004       if (op1->rank != 0 && op2->rank == 0)
4005         {
4006           e->rank = op1->rank;
4007
4008           if (e->shape == NULL)
4009             e->shape = gfc_copy_shape (op1->shape, op1->rank);
4010         }
4011
4012       if (op1->rank != 0 && op2->rank != 0)
4013         {
4014           if (op1->rank == op2->rank)
4015             {
4016               e->rank = op1->rank;
4017               if (e->shape == NULL)
4018                 {
4019                   t = compare_shapes (op1, op2);
4020                   if (t == FAILURE)
4021                     e->shape = NULL;
4022                   else
4023                     e->shape = gfc_copy_shape (op1->shape, op1->rank);
4024                 }
4025             }
4026           else
4027             {
4028               /* Allow higher level expressions to work.  */
4029               e->rank = 0;
4030
4031               /* Try user-defined operators, and otherwise throw an error.  */
4032               dual_locus_error = true;
4033               sprintf (msg,
4034                        _("Inconsistent ranks for operator at %%L and %%L"));
4035               goto bad_op;
4036             }
4037         }
4038
4039       break;
4040
4041     case INTRINSIC_PARENTHESES:
4042     case INTRINSIC_NOT:
4043     case INTRINSIC_UPLUS:
4044     case INTRINSIC_UMINUS:
4045       /* Simply copy arrayness attribute */
4046       e->rank = op1->rank;
4047
4048       if (e->shape == NULL)
4049         e->shape = gfc_copy_shape (op1->shape, op1->rank);
4050
4051       break;
4052
4053     default:
4054       break;
4055     }
4056
4057   /* Attempt to simplify the expression.  */
4058   if (t == SUCCESS)
4059     {
4060       t = gfc_simplify_expr (e, 0);
4061       /* Some calls do not succeed in simplification and return FAILURE
4062          even though there is no error; e.g. variable references to
4063          PARAMETER arrays.  */
4064       if (!gfc_is_constant_expr (e))
4065         t = SUCCESS;
4066     }
4067   return t;
4068
4069 bad_op:
4070
4071   {
4072     match m = gfc_extend_expr (e);
4073     if (m == MATCH_YES)
4074       return SUCCESS;
4075     if (m == MATCH_ERROR)
4076       return FAILURE;
4077   }
4078
4079   if (dual_locus_error)
4080     gfc_error (msg, &op1->where, &op2->where);
4081   else
4082     gfc_error (msg, &e->where);
4083
4084   return FAILURE;
4085 }
4086
4087
4088 /************** Array resolution subroutines **************/
4089
4090 typedef enum
4091 { CMP_LT, CMP_EQ, CMP_GT, CMP_UNKNOWN }
4092 comparison;
4093
4094 /* Compare two integer expressions.  */
4095
4096 static comparison
4097 compare_bound (gfc_expr *a, gfc_expr *b)
4098 {
4099   int i;
4100
4101   if (a == NULL || a->expr_type != EXPR_CONSTANT
4102       || b == NULL || b->expr_type != EXPR_CONSTANT)
4103     return CMP_UNKNOWN;
4104
4105   /* If either of the types isn't INTEGER, we must have
4106      raised an error earlier.  */
4107
4108   if (a->ts.type != BT_INTEGER || b->ts.type != BT_INTEGER)
4109     return CMP_UNKNOWN;
4110
4111   i = mpz_cmp (a->value.integer, b->value.integer);
4112
4113   if (i < 0)
4114     return CMP_LT;
4115   if (i > 0)
4116     return CMP_GT;
4117   return CMP_EQ;
4118 }
4119
4120
4121 /* Compare an integer expression with an integer.  */
4122
4123 static comparison
4124 compare_bound_int (gfc_expr *a, int b)
4125 {
4126   int i;
4127
4128   if (a == NULL || a->expr_type != EXPR_CONSTANT)
4129     return CMP_UNKNOWN;
4130
4131   if (a->ts.type != BT_INTEGER)
4132     gfc_internal_error ("compare_bound_int(): Bad expression");
4133
4134   i = mpz_cmp_si (a->value.integer, b);
4135
4136   if (i < 0)
4137     return CMP_LT;
4138   if (i > 0)
4139     return CMP_GT;
4140   return CMP_EQ;
4141 }
4142
4143
4144 /* Compare an integer expression with a mpz_t.  */
4145
4146 static comparison
4147 compare_bound_mpz_t (gfc_expr *a, mpz_t b)
4148 {
4149   int i;
4150
4151   if (a == NULL || a->expr_type != EXPR_CONSTANT)
4152     return CMP_UNKNOWN;
4153
4154   if (a->ts.type != BT_INTEGER)
4155     gfc_internal_error ("compare_bound_int(): Bad expression");
4156
4157   i = mpz_cmp (a->value.integer, b);
4158
4159   if (i < 0)
4160     return CMP_LT;
4161   if (i > 0)
4162     return CMP_GT;
4163   return CMP_EQ;
4164 }
4165
4166
4167 /* Compute the last value of a sequence given by a triplet.  
4168    Return 0 if it wasn't able to compute the last value, or if the
4169    sequence if empty, and 1 otherwise.  */
4170
4171 static int
4172 compute_last_value_for_triplet (gfc_expr *start, gfc_expr *end,
4173                                 gfc_expr *stride, mpz_t last)
4174 {
4175   mpz_t rem;
4176
4177   if (start == NULL || start->expr_type != EXPR_CONSTANT
4178       || end == NULL || end->expr_type != EXPR_CONSTANT
4179       || (stride != NULL && stride->expr_type != EXPR_CONSTANT))
4180     return 0;
4181
4182   if (start->ts.type != BT_INTEGER || end->ts.type != BT_INTEGER
4183       || (stride != NULL && stride->ts.type != BT_INTEGER))
4184     return 0;
4185
4186   if (stride == NULL || compare_bound_int(stride, 1) == CMP_EQ)
4187     {
4188       if (compare_bound (start, end) == CMP_GT)
4189         return 0;
4190       mpz_set (last, end->value.integer);
4191       return 1;
4192     }
4193
4194   if (compare_bound_int (stride, 0) == CMP_GT)
4195     {
4196       /* Stride is positive */
4197       if (mpz_cmp (start->value.integer, end->value.integer) > 0)
4198         return 0;
4199     }
4200   else
4201     {
4202       /* Stride is negative */
4203       if (mpz_cmp (start->value.integer, end->value.integer) < 0)
4204         return 0;
4205     }
4206
4207   mpz_init (rem);
4208   mpz_sub (rem, end->value.integer, start->value.integer);
4209   mpz_tdiv_r (rem, rem, stride->value.integer);
4210   mpz_sub (last, end->value.integer, rem);
4211   mpz_clear (rem);
4212
4213   return 1;
4214 }
4215
4216
4217 /* Compare a single dimension of an array reference to the array
4218    specification.  */
4219
4220 static gfc_try
4221 check_dimension (int i, gfc_array_ref *ar, gfc_array_spec *as)
4222 {
4223   mpz_t last_value;
4224
4225   if (ar->dimen_type[i] == DIMEN_STAR)
4226     {
4227       gcc_assert (ar->stride[i] == NULL);
4228       /* This implies [*] as [*:] and [*:3] are not possible.  */
4229       if (ar->start[i] == NULL)
4230         {
4231           gcc_assert (ar->end[i] == NULL);
4232           return SUCCESS;
4233         }
4234     }
4235
4236 /* Given start, end and stride values, calculate the minimum and
4237    maximum referenced indexes.  */
4238
4239   switch (ar->dimen_type[i])
4240     {
4241     case DIMEN_VECTOR:
4242     case DIMEN_THIS_IMAGE:
4243       break;
4244
4245     case DIMEN_STAR:
4246     case DIMEN_ELEMENT:
4247       if (compare_bound (ar->start[i], as->lower[i]) == CMP_LT)
4248         {
4249           if (i < as->rank)
4250             gfc_warning ("Array reference at %L is out of bounds "
4251                          "(%ld < %ld) in dimension %d", &ar->c_where[i],
4252                          mpz_get_si (ar->start[i]->value.integer),
4253                          mpz_get_si (as->lower[i]->value.integer), i+1);
4254           else
4255             gfc_warning ("Array reference at %L is out of bounds "
4256                          "(%ld < %ld) in codimension %d", &ar->c_where[i],
4257                          mpz_get_si (ar->start[i]->value.integer),
4258                          mpz_get_si (as->lower[i]->value.integer),
4259                          i + 1 - as->rank);
4260           return SUCCESS;
4261         }
4262       if (compare_bound (ar->start[i], as->upper[i]) == CMP_GT)
4263         {
4264           if (i < as->rank)
4265             gfc_warning ("Array reference at %L is out of bounds "
4266                          "(%ld > %ld) in dimension %d", &ar->c_where[i],
4267                          mpz_get_si (ar->start[i]->value.integer),
4268                          mpz_get_si (as->upper[i]->value.integer), i+1);
4269           else
4270             gfc_warning ("Array reference at %L is out of bounds "
4271                          "(%ld > %ld) in codimension %d", &ar->c_where[i],
4272                          mpz_get_si (ar->start[i]->value.integer),
4273                          mpz_get_si (as->upper[i]->value.integer),
4274                          i + 1 - as->rank);
4275           return SUCCESS;
4276         }
4277
4278       break;
4279
4280     case DIMEN_RANGE:
4281       {
4282 #define AR_START (ar->start[i] ? ar->start[i] : as->lower[i])
4283 #define AR_END (ar->end[i] ? ar->end[i] : as->upper[i])
4284
4285         comparison comp_start_end = compare_bound (AR_START, AR_END);
4286
4287         /* Check for zero stride, which is not allowed.  */
4288         if (compare_bound_int (ar->stride[i], 0) == CMP_EQ)
4289           {
4290             gfc_error ("Illegal stride of zero at %L", &ar->c_where[i]);
4291             return FAILURE;
4292           }
4293
4294         /* if start == len || (stride > 0 && start < len)
4295                            || (stride < 0 && start > len),
4296            then the array section contains at least one element.  In this
4297            case, there is an out-of-bounds access if
4298            (start < lower || start > upper).  */
4299         if (compare_bound (AR_START, AR_END) == CMP_EQ
4300             || ((compare_bound_int (ar->stride[i], 0) == CMP_GT
4301                  || ar->stride[i] == NULL) && comp_start_end == CMP_LT)
4302             || (compare_bound_int (ar->stride[i], 0) == CMP_LT
4303                 && comp_start_end == CMP_GT))
4304           {
4305             if (compare_bound (AR_START, as->lower[i]) == CMP_LT)
4306               {
4307                 gfc_warning ("Lower array reference at %L is out of bounds "
4308                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
4309                        mpz_get_si (AR_START->value.integer),
4310                        mpz_get_si (as->lower[i]->value.integer), i+1);
4311                 return SUCCESS;
4312               }
4313             if (compare_bound (AR_START, as->upper[i]) == CMP_GT)
4314               {
4315                 gfc_warning ("Lower array reference at %L is out of bounds "
4316                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
4317                        mpz_get_si (AR_START->value.integer),
4318                        mpz_get_si (as->upper[i]->value.integer), i+1);
4319                 return SUCCESS;
4320               }
4321           }
4322
4323         /* If we can compute the highest index of the array section,
4324            then it also has to be between lower and upper.  */
4325         mpz_init (last_value);
4326         if (compute_last_value_for_triplet (AR_START, AR_END, ar->stride[i],
4327                                             last_value))
4328           {
4329             if (compare_bound_mpz_t (as->lower[i], last_value) == CMP_GT)
4330               {
4331                 gfc_warning ("Upper array reference at %L is out of bounds "
4332                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
4333                        mpz_get_si (last_value),
4334                        mpz_get_si (as->lower[i]->value.integer), i+1);
4335                 mpz_clear (last_value);
4336                 return SUCCESS;
4337               }
4338             if (compare_bound_mpz_t (as->upper[i], last_value) == CMP_LT)
4339               {
4340                 gfc_warning ("Upper array reference at %L is out of bounds "
4341                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
4342                        mpz_get_si (last_value),
4343                        mpz_get_si (as->upper[i]->value.integer), i+1);
4344                 mpz_clear (last_value);
4345                 return SUCCESS;
4346               }
4347           }
4348         mpz_clear (last_value);
4349
4350 #undef AR_START
4351 #undef AR_END
4352       }
4353       break;
4354
4355     default:
4356       gfc_internal_error ("check_dimension(): Bad array reference");
4357     }
4358
4359   return SUCCESS;
4360 }
4361
4362
4363 /* Compare an array reference with an array specification.  */
4364
4365 static gfc_try
4366 compare_spec_to_ref (gfc_array_ref *ar)
4367 {
4368   gfc_array_spec *as;
4369   int i;
4370
4371   as = ar->as;
4372   i = as->rank - 1;
4373   /* TODO: Full array sections are only allowed as actual parameters.  */
4374   if (as->type == AS_ASSUMED_SIZE
4375       && (/*ar->type == AR_FULL
4376           ||*/ (ar->type == AR_SECTION
4377               && ar->dimen_type[i] == DIMEN_RANGE && ar->end[i] == NULL)))
4378     {
4379       gfc_error ("Rightmost upper bound of assumed size array section "
4380                  "not specified at %L", &ar->where);
4381       return FAILURE;
4382     }
4383
4384   if (ar->type == AR_FULL)
4385     return SUCCESS;
4386
4387   if (as->rank != ar->dimen)
4388     {
4389       gfc_error ("Rank mismatch in array reference at %L (%d/%d)",
4390                  &ar->where, ar->dimen, as->rank);
4391       return FAILURE;
4392     }
4393
4394   /* ar->codimen == 0 is a local array.  */
4395   if (as->corank != ar->codimen && ar->codimen != 0)
4396     {
4397       gfc_error ("Coindex rank mismatch in array reference at %L (%d/%d)",
4398                  &ar->where, ar->codimen, as->corank);
4399       return FAILURE;
4400     }
4401
4402   for (i = 0; i < as->rank; i++)
4403     if (check_dimension (i, ar, as) == FAILURE)
4404       return FAILURE;
4405
4406   /* Local access has no coarray spec.  */
4407   if (ar->codimen != 0)
4408     for (i = as->rank; i < as->rank + as->corank; i++)
4409       {
4410         if (ar->dimen_type[i] != DIMEN_ELEMENT && !ar->in_allocate
4411             && ar->dimen_type[i] != DIMEN_THIS_IMAGE)
4412           {
4413             gfc_error ("Coindex of codimension %d must be a scalar at %L",
4414                        i + 1 - as->rank, &ar->where);
4415             return FAILURE;
4416           }
4417         if (check_dimension (i, ar, as) == FAILURE)
4418           return FAILURE;
4419       }
4420
4421   return SUCCESS;
4422 }
4423
4424
4425 /* Resolve one part of an array index.  */
4426
4427 static gfc_try
4428 gfc_resolve_index_1 (gfc_expr *index, int check_scalar,
4429                      int force_index_integer_kind)
4430 {
4431   gfc_typespec ts;
4432
4433   if (index == NULL)
4434     return SUCCESS;
4435
4436   if (gfc_resolve_expr (index) == FAILURE)
4437     return FAILURE;
4438
4439   if (check_scalar && index->rank != 0)
4440     {
4441       gfc_error ("Array index at %L must be scalar", &index->where);
4442       return FAILURE;
4443     }
4444
4445   if (index->ts.type != BT_INTEGER && index->ts.type != BT_REAL)
4446     {
4447       gfc_error ("Array index at %L must be of INTEGER type, found %s",
4448                  &index->where, gfc_basic_typename (index->ts.type));
4449       return FAILURE;
4450     }
4451
4452   if (index->ts.type == BT_REAL)
4453     if (gfc_notify_std (GFC_STD_LEGACY, "Extension: REAL array index at %L",
4454                         &index->where) == FAILURE)
4455       return FAILURE;
4456
4457   if ((index->ts.kind != gfc_index_integer_kind
4458        && force_index_integer_kind)
4459       || index->ts.type != BT_INTEGER)
4460     {
4461       gfc_clear_ts (&ts);
4462       ts.type = BT_INTEGER;
4463       ts.kind = gfc_index_integer_kind;
4464
4465       gfc_convert_type_warn (index, &ts, 2, 0);
4466     }
4467
4468   return SUCCESS;
4469 }
4470
4471 /* Resolve one part of an array index.  */
4472
4473 gfc_try
4474 gfc_resolve_index (gfc_expr *index, int check_scalar)
4475 {
4476   return gfc_resolve_index_1 (index, check_scalar, 1);
4477 }
4478
4479 /* Resolve a dim argument to an intrinsic function.  */
4480
4481 gfc_try
4482 gfc_resolve_dim_arg (gfc_expr *dim)
4483 {
4484   if (dim == NULL)
4485     return SUCCESS;
4486
4487   if (gfc_resolve_expr (dim) == FAILURE)
4488     return FAILURE;
4489
4490   if (dim->rank != 0)
4491     {
4492       gfc_error ("Argument dim at %L must be scalar", &dim->where);
4493       return FAILURE;
4494
4495     }
4496
4497   if (dim->ts.type != BT_INTEGER)
4498     {
4499       gfc_error ("Argument dim at %L must be of INTEGER type", &dim->where);
4500       return FAILURE;
4501     }
4502
4503   if (dim->ts.kind != gfc_index_integer_kind)
4504     {
4505       gfc_typespec ts;
4506
4507       gfc_clear_ts (&ts);
4508       ts.type = BT_INTEGER;
4509       ts.kind = gfc_index_integer_kind;
4510
4511       gfc_convert_type_warn (dim, &ts, 2, 0);
4512     }
4513
4514   return SUCCESS;
4515 }
4516
4517 /* Given an expression that contains array references, update those array
4518    references to point to the right array specifications.  While this is
4519    filled in during matching, this information is difficult to save and load
4520    in a module, so we take care of it here.
4521
4522    The idea here is that the original array reference comes from the
4523    base symbol.  We traverse the list of reference structures, setting
4524    the stored reference to references.  Component references can
4525    provide an additional array specification.  */
4526
4527 static void
4528 find_array_spec (gfc_expr *e)
4529 {
4530   gfc_array_spec *as;
4531   gfc_component *c;
4532   gfc_ref *ref;
4533
4534   if (e->symtree->n.sym->ts.type == BT_CLASS)
4535     as = CLASS_DATA (e->symtree->n.sym)->as;
4536   else
4537     as = e->symtree->n.sym->as;
4538
4539   for (ref = e->ref; ref; ref = ref->next)
4540     switch (ref->type)
4541       {
4542       case REF_ARRAY:
4543         if (as == NULL)
4544           gfc_internal_error ("find_array_spec(): Missing spec");
4545
4546         ref->u.ar.as = as;
4547         as = NULL;
4548         break;
4549
4550       case REF_COMPONENT:
4551         c = ref->u.c.component;
4552         if (c->attr.dimension)
4553           {
4554             if (as != NULL)
4555               gfc_internal_error ("find_array_spec(): unused as(1)");
4556             as = c->as;
4557           }
4558
4559         break;
4560
4561       case REF_SUBSTRING:
4562         break;
4563       }
4564
4565   if (as != NULL)
4566     gfc_internal_error ("find_array_spec(): unused as(2)");
4567 }
4568
4569
4570 /* Resolve an array reference.  */
4571
4572 static gfc_try
4573 resolve_array_ref (gfc_array_ref *ar)
4574 {
4575   int i, check_scalar;
4576   gfc_expr *e;
4577
4578   for (i = 0; i < ar->dimen + ar->codimen; i++)
4579     {
4580       check_scalar = ar->dimen_type[i] == DIMEN_RANGE;
4581
4582       /* Do not force gfc_index_integer_kind for the start.  We can
4583          do fine with any integer kind.  This avoids temporary arrays
4584          created for indexing with a vector.  */
4585       if (gfc_resolve_index_1 (ar->start[i], check_scalar, 0) == FAILURE)
4586         return FAILURE;
4587       if (gfc_resolve_index (ar->end[i], check_scalar) == FAILURE)
4588         return FAILURE;
4589       if (gfc_resolve_index (ar->stride[i], check_scalar) == FAILURE)
4590         return FAILURE;
4591
4592       e = ar->start[i];
4593
4594       if (ar->dimen_type[i] == DIMEN_UNKNOWN)
4595         switch (e->rank)
4596           {
4597           case 0:
4598             ar->dimen_type[i] = DIMEN_ELEMENT;
4599             break;
4600
4601           case 1:
4602             ar->dimen_type[i] = DIMEN_VECTOR;
4603             if (e->expr_type == EXPR_VARIABLE
4604                 && e->symtree->n.sym->ts.type == BT_DERIVED)
4605               ar->start[i] = gfc_get_parentheses (e);
4606             break;
4607
4608           default:
4609             gfc_error ("Array index at %L is an array of rank %d",
4610                        &ar->c_where[i], e->rank);
4611             return FAILURE;
4612           }
4613
4614       /* Fill in the upper bound, which may be lower than the
4615          specified one for something like a(2:10:5), which is
4616          identical to a(2:7:5).  Only relevant for strides not equal
4617          to one.  Don't try a division by zero.  */
4618       if (ar->dimen_type[i] == DIMEN_RANGE
4619           && ar->stride[i] != NULL && ar->stride[i]->expr_type == EXPR_CONSTANT
4620           && mpz_cmp_si (ar->stride[i]->value.integer, 1L) != 0
4621           && mpz_cmp_si (ar->stride[i]->value.integer, 0L) != 0)
4622         {
4623           mpz_t size, end;
4624
4625           if (gfc_ref_dimen_size (ar, i, &size, &end) == SUCCESS)
4626             {
4627               if (ar->end[i] == NULL)
4628                 {
4629                   ar->end[i] =
4630                     gfc_get_constant_expr (BT_INTEGER, gfc_index_integer_kind,
4631                                            &ar->where);
4632                   mpz_set (ar->end[i]->value.integer, end);
4633                 }
4634               else if (ar->end[i]->ts.type == BT_INTEGER
4635                        && ar->end[i]->expr_type == EXPR_CONSTANT)
4636                 {
4637                   mpz_set (ar->end[i]->value.integer, end);
4638                 }
4639               else
4640                 gcc_unreachable ();
4641
4642               mpz_clear (size);
4643               mpz_clear (end);
4644             }
4645         }
4646     }
4647
4648   if (ar->type == AR_FULL)
4649     {
4650       if (ar->as->rank == 0)
4651         ar->type = AR_ELEMENT;
4652
4653       /* Make sure array is the same as array(:,:), this way
4654          we don't need to special case all the time.  */
4655       ar->dimen = ar->as->rank;
4656       for (i = 0; i < ar->dimen; i++)
4657         {
4658           ar->dimen_type[i] = DIMEN_RANGE;
4659
4660           gcc_assert (ar->start[i] == NULL);
4661           gcc_assert (ar->end[i] == NULL);
4662           gcc_assert (ar->stride[i] == NULL);
4663         }
4664     }
4665
4666   /* If the reference type is unknown, figure out what kind it is.  */
4667
4668   if (ar->type == AR_UNKNOWN)
4669     {
4670       ar->type = AR_ELEMENT;
4671       for (i = 0; i < ar->dimen; i++)
4672         if (ar->dimen_type[i] == DIMEN_RANGE
4673             || ar->dimen_type[i] == DIMEN_VECTOR)
4674           {
4675             ar->type = AR_SECTION;
4676             break;
4677           }
4678     }
4679
4680   if (!ar->as->cray_pointee && compare_spec_to_ref (ar) == FAILURE)
4681     return FAILURE;
4682
4683   if (ar->as->corank && ar->codimen == 0)
4684     {
4685       int n;
4686       ar->codimen = ar->as->corank;
4687       for (n = ar->dimen; n < ar->dimen + ar->codimen; n++)
4688         ar->dimen_type[n] = DIMEN_THIS_IMAGE;
4689     }
4690
4691   return SUCCESS;
4692 }
4693
4694
4695 static gfc_try
4696 resolve_substring (gfc_ref *ref)
4697 {
4698   int k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
4699
4700   if (ref->u.ss.start != NULL)
4701     {
4702       if (gfc_resolve_expr (ref->u.ss.start) == FAILURE)
4703         return FAILURE;
4704
4705       if (ref->u.ss.start->ts.type != BT_INTEGER)
4706         {
4707           gfc_error ("Substring start index at %L must be of type INTEGER",
4708                      &ref->u.ss.start->where);
4709           return FAILURE;
4710         }
4711
4712       if (ref->u.ss.start->rank != 0)
4713         {
4714           gfc_error ("Substring start index at %L must be scalar",
4715                      &ref->u.ss.start->where);
4716           return FAILURE;
4717         }
4718
4719       if (compare_bound_int (ref->u.ss.start, 1) == CMP_LT
4720           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4721               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4722         {
4723           gfc_error ("Substring start index at %L is less than one",
4724                      &ref->u.ss.start->where);
4725           return FAILURE;
4726         }
4727     }
4728
4729   if (ref->u.ss.end != NULL)
4730     {
4731       if (gfc_resolve_expr (ref->u.ss.end) == FAILURE)
4732         return FAILURE;
4733
4734       if (ref->u.ss.end->ts.type != BT_INTEGER)
4735         {
4736           gfc_error ("Substring end index at %L must be of type INTEGER",
4737                      &ref->u.ss.end->where);
4738           return FAILURE;
4739         }
4740
4741       if (ref->u.ss.end->rank != 0)
4742         {
4743           gfc_error ("Substring end index at %L must be scalar",
4744                      &ref->u.ss.end->where);
4745           return FAILURE;
4746         }
4747
4748       if (ref->u.ss.length != NULL
4749           && compare_bound (ref->u.ss.end, ref->u.ss.length->length) == CMP_GT
4750           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4751               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4752         {
4753           gfc_error ("Substring end index at %L exceeds the string length",
4754                      &ref->u.ss.start->where);
4755           return FAILURE;
4756         }
4757
4758       if (compare_bound_mpz_t (ref->u.ss.end,
4759                                gfc_integer_kinds[k].huge) == CMP_GT
4760           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4761               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4762         {
4763           gfc_error ("Substring end index at %L is too large",
4764                      &ref->u.ss.end->where);
4765           return FAILURE;
4766         }
4767     }
4768
4769   return SUCCESS;
4770 }
4771
4772
4773 /* This function supplies missing substring charlens.  */
4774
4775 void
4776 gfc_resolve_substring_charlen (gfc_expr *e)
4777 {
4778   gfc_ref *char_ref;
4779   gfc_expr *start, *end;
4780
4781   for (char_ref = e->ref; char_ref; char_ref = char_ref->next)
4782     if (char_ref->type == REF_SUBSTRING)
4783       break;
4784
4785   if (!char_ref)
4786     return;
4787
4788   gcc_assert (char_ref->next == NULL);
4789
4790   if (e->ts.u.cl)
4791     {
4792       if (e->ts.u.cl->length)
4793         gfc_free_expr (e->ts.u.cl->length);
4794       else if (e->expr_type == EXPR_VARIABLE
4795                  && e->symtree->n.sym->attr.dummy)
4796         return;
4797     }
4798
4799   e->ts.type = BT_CHARACTER;
4800   e->ts.kind = gfc_default_character_kind;
4801
4802   if (!e->ts.u.cl)
4803     e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
4804
4805   if (char_ref->u.ss.start)
4806     start = gfc_copy_expr (char_ref->u.ss.start);
4807   else
4808     start = gfc_get_int_expr (gfc_default_integer_kind, NULL, 1);
4809
4810   if (char_ref->u.ss.end)
4811     end = gfc_copy_expr (char_ref->u.ss.end);
4812   else if (e->expr_type == EXPR_VARIABLE)
4813     end = gfc_copy_expr (e->symtree->n.sym->ts.u.cl->length);
4814   else
4815     end = NULL;
4816
4817   if (!start || !end)
4818     return;
4819
4820   /* Length = (end - start +1).  */
4821   e->ts.u.cl->length = gfc_subtract (end, start);
4822   e->ts.u.cl->length = gfc_add (e->ts.u.cl->length,
4823                                 gfc_get_int_expr (gfc_default_integer_kind,
4824                                                   NULL, 1));
4825
4826   e->ts.u.cl->length->ts.type = BT_INTEGER;
4827   e->ts.u.cl->length->ts.kind = gfc_charlen_int_kind;
4828
4829   /* Make sure that the length is simplified.  */
4830   gfc_simplify_expr (e->ts.u.cl->length, 1);
4831   gfc_resolve_expr (e->ts.u.cl->length);
4832 }
4833
4834
4835 /* Resolve subtype references.  */
4836
4837 static gfc_try
4838 resolve_ref (gfc_expr *expr)
4839 {
4840   int current_part_dimension, n_components, seen_part_dimension;
4841   gfc_ref *ref;
4842
4843   for (ref = expr->ref; ref; ref = ref->next)
4844     if (ref->type == REF_ARRAY && ref->u.ar.as == NULL)
4845       {
4846         find_array_spec (expr);
4847         break;
4848       }
4849
4850   for (ref = expr->ref; ref; ref = ref->next)
4851     switch (ref->type)
4852       {
4853       case REF_ARRAY:
4854         if (resolve_array_ref (&ref->u.ar) == FAILURE)
4855           return FAILURE;
4856         break;
4857
4858       case REF_COMPONENT:
4859         break;
4860
4861       case REF_SUBSTRING:
4862         if (resolve_substring (ref) == FAILURE)
4863           return FAILURE;
4864         break;
4865       }
4866
4867   /* Check constraints on part references.  */
4868
4869   current_part_dimension = 0;
4870   seen_part_dimension = 0;
4871   n_components = 0;
4872
4873   for (ref = expr->ref; ref; ref = ref->next)
4874     {
4875       switch (ref->type)
4876         {
4877         case REF_ARRAY:
4878           switch (ref->u.ar.type)
4879             {
4880             case AR_FULL:
4881               /* Coarray scalar.  */
4882               if (ref->u.ar.as->rank == 0)
4883                 {
4884                   current_part_dimension = 0;
4885                   break;
4886                 }
4887               /* Fall through.  */
4888             case AR_SECTION:
4889               current_part_dimension = 1;
4890               break;
4891
4892             case AR_ELEMENT:
4893               current_part_dimension = 0;
4894               break;
4895
4896             case AR_UNKNOWN:
4897               gfc_internal_error ("resolve_ref(): Bad array reference");
4898             }
4899
4900           break;
4901
4902         case REF_COMPONENT:
4903           if (current_part_dimension || seen_part_dimension)
4904             {
4905               /* F03:C614.  */
4906               if (ref->u.c.component->attr.pointer
4907                   || ref->u.c.component->attr.proc_pointer
4908                   || (ref->u.c.component->ts.type == BT_CLASS
4909                         && CLASS_DATA (ref->u.c.component)->attr.pointer))
4910                 {
4911                   gfc_error ("Component to the right of a part reference "
4912                              "with nonzero rank must not have the POINTER "
4913                              "attribute at %L", &expr->where);
4914                   return FAILURE;
4915                 }
4916               else if (ref->u.c.component->attr.allocatable
4917                         || (ref->u.c.component->ts.type == BT_CLASS
4918                             && CLASS_DATA (ref->u.c.component)->attr.allocatable))
4919
4920                 {
4921                   gfc_error ("Component to the right of a part reference "
4922                              "with nonzero rank must not have the ALLOCATABLE "
4923                              "attribute at %L", &expr->where);
4924                   return FAILURE;
4925                 }
4926             }
4927
4928           n_components++;
4929           break;
4930
4931         case REF_SUBSTRING:
4932           break;
4933         }
4934
4935       if (((ref->type == REF_COMPONENT && n_components > 1)
4936            || ref->next == NULL)
4937           && current_part_dimension
4938           && seen_part_dimension)
4939         {
4940           gfc_error ("Two or more part references with nonzero rank must "
4941                      "not be specified at %L", &expr->where);
4942           return FAILURE;
4943         }
4944
4945       if (ref->type == REF_COMPONENT)
4946         {
4947           if (current_part_dimension)
4948             seen_part_dimension = 1;
4949
4950           /* reset to make sure */
4951           current_part_dimension = 0;
4952         }
4953     }
4954
4955   return SUCCESS;
4956 }
4957
4958
4959 /* Given an expression, determine its shape.  This is easier than it sounds.
4960    Leaves the shape array NULL if it is not possible to determine the shape.  */
4961
4962 static void
4963 expression_shape (gfc_expr *e)
4964 {
4965   mpz_t array[GFC_MAX_DIMENSIONS];
4966   int i;
4967
4968   if (e->rank == 0 || e->shape != NULL)
4969     return;
4970
4971   for (i = 0; i < e->rank; i++)
4972     if (gfc_array_dimen_size (e, i, &array[i]) == FAILURE)
4973       goto fail;
4974
4975   e->shape = gfc_get_shape (e->rank);
4976
4977   memcpy (e->shape, array, e->rank * sizeof (mpz_t));
4978
4979   return;
4980
4981 fail:
4982   for (i--; i >= 0; i--)
4983     mpz_clear (array[i]);
4984 }
4985
4986
4987 /* Given a variable expression node, compute the rank of the expression by
4988    examining the base symbol and any reference structures it may have.  */
4989
4990 static void
4991 expression_rank (gfc_expr *e)
4992 {
4993   gfc_ref *ref;
4994   int i, rank;
4995
4996   /* Just to make sure, because EXPR_COMPCALL's also have an e->ref and that
4997      could lead to serious confusion...  */
4998   gcc_assert (e->expr_type != EXPR_COMPCALL);
4999
5000   if (e->ref == NULL)
5001     {
5002       if (e->expr_type == EXPR_ARRAY)
5003         goto done;
5004       /* Constructors can have a rank different from one via RESHAPE().  */
5005
5006       if (e->symtree == NULL)
5007         {
5008           e->rank = 0;
5009           goto done;
5010         }
5011
5012       e->rank = (e->symtree->n.sym->as == NULL)
5013                 ? 0 : e->symtree->n.sym->as->rank;
5014       goto done;
5015     }
5016
5017   rank = 0;
5018
5019   for (ref = e->ref; ref; ref = ref->next)
5020     {
5021       if (ref->type == REF_COMPONENT && ref->u.c.component->attr.proc_pointer
5022           && ref->u.c.component->attr.function && !ref->next)
5023         rank = ref->u.c.component->as ? ref->u.c.component->as->rank : 0;
5024
5025       if (ref->type != REF_ARRAY)
5026         continue;
5027
5028       if (ref->u.ar.type == AR_FULL)
5029         {
5030           rank = ref->u.ar.as->rank;
5031           break;
5032         }
5033
5034       if (ref->u.ar.type == AR_SECTION)
5035         {
5036           /* Figure out the rank of the section.  */
5037           if (rank != 0)
5038             gfc_internal_error ("expression_rank(): Two array specs");
5039
5040           for (i = 0; i < ref->u.ar.dimen; i++)
5041             if (ref->u.ar.dimen_type[i] == DIMEN_RANGE
5042                 || ref->u.ar.dimen_type[i] == DIMEN_VECTOR)
5043               rank++;
5044
5045           break;
5046         }
5047     }
5048
5049   e->rank = rank;
5050
5051 done:
5052   expression_shape (e);
5053 }
5054
5055
5056 /* Resolve a variable expression.  */
5057
5058 static gfc_try
5059 resolve_variable (gfc_expr *e)
5060 {
5061   gfc_symbol *sym;
5062   gfc_try t;
5063
5064   t = SUCCESS;
5065
5066   if (e->symtree == NULL)
5067     return FAILURE;
5068   sym = e->symtree->n.sym;
5069
5070   /* TS 29113, 407b.  */
5071   if (e->ts.type == BT_ASSUMED && !assumed_type_expr_allowed)
5072     {
5073       gfc_error ("Invalid expression with assumed-type variable %s at %L",
5074                  sym->name, &e->where);
5075       return FAILURE;
5076     }
5077
5078   /* TS 29113, 407b.  */
5079   if (e->ts.type == BT_ASSUMED && e->ref
5080       && !(e->ref->type == REF_ARRAY && e->ref->u.ar.type == AR_FULL
5081            && e->ref->next == NULL))
5082     {
5083       gfc_error ("Assumed-type variable %s with designator at %L",
5084                  sym->name, &e->ref->u.ar.where);
5085       return FAILURE;
5086     }
5087
5088   /* If this is an associate-name, it may be parsed with an array reference
5089      in error even though the target is scalar.  Fail directly in this case.
5090      TODO Understand why class scalar expressions must be excluded.  */
5091   if (sym->assoc && !(sym->ts.type == BT_CLASS && e->rank == 0))
5092     {
5093       if (sym->ts.type == BT_CLASS)
5094         gfc_fix_class_refs (e);
5095       if (!sym->attr.dimension && e->ref && e->ref->type == REF_ARRAY)
5096         return FAILURE;
5097     }
5098
5099   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.generic)
5100     sym->ts.u.derived = gfc_find_dt_in_generic (sym->ts.u.derived);
5101
5102   /* On the other hand, the parser may not have known this is an array;
5103      in this case, we have to add a FULL reference.  */
5104   if (sym->assoc && sym->attr.dimension && !e->ref)
5105     {
5106       e->ref = gfc_get_ref ();
5107       e->ref->type = REF_ARRAY;
5108       e->ref->u.ar.type = AR_FULL;
5109       e->ref->u.ar.dimen = 0;
5110     }
5111
5112   if (e->ref && resolve_ref (e) == FAILURE)
5113     return FAILURE;
5114
5115   if (sym->attr.flavor == FL_PROCEDURE
5116       && (!sym->attr.function
5117           || (sym->attr.function && sym->result
5118               && sym->result->attr.proc_pointer
5119               && !sym->result->attr.function)))
5120     {
5121       e->ts.type = BT_PROCEDURE;
5122       goto resolve_procedure;
5123     }
5124
5125   if (sym->ts.type != BT_UNKNOWN)
5126     gfc_variable_attr (e, &e->ts);
5127   else
5128     {
5129       /* Must be a simple variable reference.  */
5130       if (gfc_set_default_type (sym, 1, sym->ns) == FAILURE)
5131         return FAILURE;
5132       e->ts = sym->ts;
5133     }
5134
5135   if (check_assumed_size_reference (sym, e))
5136     return FAILURE;
5137
5138   /* If a PRIVATE variable is used in the specification expression of the
5139      result variable, it might be accessed from outside the module and can
5140      thus not be TREE_PUBLIC() = 0.
5141      TODO: sym->attr.public_used only has to be set for the result variable's
5142      type-parameter expression and not for dummies or automatic variables.
5143      Additionally, it only has to be set if the function is either PUBLIC or
5144      used in a generic interface or TBP; unfortunately,
5145      proc_name->attr.public_used can get set at a later stage.  */
5146   if (specification_expr && sym->attr.access == ACCESS_PRIVATE
5147       && !sym->attr.function && !sym->attr.use_assoc
5148       && gfc_current_ns->proc_name && gfc_current_ns->proc_name->attr.function)
5149     sym->attr.public_used = 1;
5150
5151   /* Deal with forward references to entries during resolve_code, to
5152      satisfy, at least partially, 12.5.2.5.  */
5153   if (gfc_current_ns->entries
5154       && current_entry_id == sym->entry_id
5155       && cs_base
5156       && cs_base->current
5157       && cs_base->current->op != EXEC_ENTRY)
5158     {
5159       gfc_entry_list *entry;
5160       gfc_formal_arglist *formal;
5161       int n;
5162       bool seen;
5163
5164       /* If the symbol is a dummy...  */
5165       if (sym->attr.dummy && sym->ns == gfc_current_ns)
5166         {
5167           entry = gfc_current_ns->entries;
5168           seen = false;
5169
5170           /* ...test if the symbol is a parameter of previous entries.  */
5171           for (; entry && entry->id <= current_entry_id; entry = entry->next)
5172             for (formal = entry->sym->formal; formal; formal = formal->next)
5173               {
5174                 if (formal->sym && sym->name == formal->sym->name)
5175                   seen = true;
5176               }
5177
5178           /*  If it has not been seen as a dummy, this is an error.  */
5179           if (!seen)
5180             {
5181               if (specification_expr)
5182                 gfc_error ("Variable '%s', used in a specification expression"
5183                            ", is referenced at %L before the ENTRY statement "
5184                            "in which it is a parameter",
5185                            sym->name, &cs_base->current->loc);
5186               else
5187                 gfc_error ("Variable '%s' is used at %L before the ENTRY "
5188                            "statement in which it is a parameter",
5189                            sym->name, &cs_base->current->loc);
5190               t = FAILURE;
5191             }
5192         }
5193
5194       /* Now do the same check on the specification expressions.  */
5195       specification_expr = 1;
5196       if (sym->ts.type == BT_CHARACTER
5197           && gfc_resolve_expr (sym->ts.u.cl->length) == FAILURE)
5198         t = FAILURE;
5199
5200       if (sym->as)
5201         for (n = 0; n < sym->as->rank; n++)
5202           {
5203              specification_expr = 1;
5204              if (gfc_resolve_expr (sym->as->lower[n]) == FAILURE)
5205                t = FAILURE;
5206              specification_expr = 1;
5207              if (gfc_resolve_expr (sym->as->upper[n]) == FAILURE)
5208                t = FAILURE;
5209           }
5210       specification_expr = 0;
5211
5212       if (t == SUCCESS)
5213         /* Update the symbol's entry level.  */
5214         sym->entry_id = current_entry_id + 1;
5215     }
5216
5217   /* If a symbol has been host_associated mark it.  This is used latter,
5218      to identify if aliasing is possible via host association.  */
5219   if (sym->attr.flavor == FL_VARIABLE
5220         && gfc_current_ns->parent
5221         && (gfc_current_ns->parent == sym->ns
5222               || (gfc_current_ns->parent->parent
5223                     && gfc_current_ns->parent->parent == sym->ns)))
5224     sym->attr.host_assoc = 1;
5225
5226 resolve_procedure:
5227   if (t == SUCCESS && resolve_procedure_expression (e) == FAILURE)
5228     t = FAILURE;
5229
5230   /* F2008, C617 and C1229.  */
5231   if (!inquiry_argument && (e->ts.type == BT_CLASS || e->ts.type == BT_DERIVED)
5232       && gfc_is_coindexed (e))
5233     {
5234       gfc_ref *ref, *ref2 = NULL;
5235
5236       for (ref = e->ref; ref; ref = ref->next)
5237         {
5238           if (ref->type == REF_COMPONENT)
5239             ref2 = ref;
5240           if (ref->type == REF_ARRAY && ref->u.ar.codimen > 0)
5241             break;
5242         }
5243
5244       for ( ; ref; ref = ref->next)
5245         if (ref->type == REF_COMPONENT)
5246           break;
5247
5248       /* Expression itself is not coindexed object.  */
5249       if (ref && e->ts.type == BT_CLASS)
5250         {
5251           gfc_error ("Polymorphic subobject of coindexed object at %L",
5252                      &e->where);
5253           t = FAILURE;
5254         }
5255
5256       /* Expression itself is coindexed object.  */
5257       if (ref == NULL)
5258         {
5259           gfc_component *c;
5260           c = ref2 ? ref2->u.c.component : e->symtree->n.sym->components;
5261           for ( ; c; c = c->next)
5262             if (c->attr.allocatable && c->ts.type == BT_CLASS)
5263               {
5264                 gfc_error ("Coindexed object with polymorphic allocatable "
5265                          "subcomponent at %L", &e->where);
5266                 t = FAILURE;
5267                 break;
5268               }
5269         }
5270     }
5271
5272   return t;
5273 }
5274
5275
5276 /* Checks to see that the correct symbol has been host associated.
5277    The only situation where this arises is that in which a twice
5278    contained function is parsed after the host association is made.
5279    Therefore, on detecting this, change the symbol in the expression
5280    and convert the array reference into an actual arglist if the old
5281    symbol is a variable.  */
5282 static bool
5283 check_host_association (gfc_expr *e)
5284 {
5285   gfc_symbol *sym, *old_sym;
5286   gfc_symtree *st;
5287   int n;
5288   gfc_ref *ref;
5289   gfc_actual_arglist *arg, *tail = NULL;
5290   bool retval = e->expr_type == EXPR_FUNCTION;
5291
5292   /*  If the expression is the result of substitution in
5293       interface.c(gfc_extend_expr) because there is no way in
5294       which the host association can be wrong.  */
5295   if (e->symtree == NULL
5296         || e->symtree->n.sym == NULL
5297         || e->user_operator)
5298     return retval;
5299
5300   old_sym = e->symtree->n.sym;
5301
5302   if (gfc_current_ns->parent
5303         && old_sym->ns != gfc_current_ns)
5304     {
5305       /* Use the 'USE' name so that renamed module symbols are
5306          correctly handled.  */
5307       gfc_find_symbol (e->symtree->name, gfc_current_ns, 1, &sym);
5308
5309       if (sym && old_sym != sym
5310               && sym->ts.type == old_sym->ts.type
5311               && sym->attr.flavor == FL_PROCEDURE
5312               && sym->attr.contained)
5313         {
5314           /* Clear the shape, since it might not be valid.  */
5315           gfc_free_shape (&e->shape, e->rank);
5316
5317           /* Give the expression the right symtree!  */
5318           gfc_find_sym_tree (e->symtree->name, NULL, 1, &st);
5319           gcc_assert (st != NULL);
5320
5321           if (old_sym->attr.flavor == FL_PROCEDURE
5322                 || e->expr_type == EXPR_FUNCTION)
5323             {
5324               /* Original was function so point to the new symbol, since
5325                  the actual argument list is already attached to the
5326                  expression. */
5327               e->value.function.esym = NULL;
5328               e->symtree = st;
5329             }
5330           else
5331             {
5332               /* Original was variable so convert array references into
5333                  an actual arglist. This does not need any checking now
5334                  since resolve_function will take care of it.  */
5335               e->value.function.actual = NULL;
5336               e->expr_type = EXPR_FUNCTION;
5337               e->symtree = st;
5338
5339               /* Ambiguity will not arise if the array reference is not
5340                  the last reference.  */
5341               for (ref = e->ref; ref; ref = ref->next)
5342                 if (ref->type == REF_ARRAY && ref->next == NULL)
5343                   break;
5344
5345               gcc_assert (ref->type == REF_ARRAY);
5346
5347               /* Grab the start expressions from the array ref and
5348                  copy them into actual arguments.  */
5349               for (n = 0; n < ref->u.ar.dimen; n++)
5350                 {
5351                   arg = gfc_get_actual_arglist ();
5352                   arg->expr = gfc_copy_expr (ref->u.ar.start[n]);
5353                   if (e->value.function.actual == NULL)
5354                     tail = e->value.function.actual = arg;
5355                   else
5356                     {
5357                       tail->next = arg;
5358                       tail = arg;
5359                     }
5360                 }
5361
5362               /* Dump the reference list and set the rank.  */
5363               gfc_free_ref_list (e->ref);
5364               e->ref = NULL;
5365               e->rank = sym->as ? sym->as->rank : 0;
5366             }
5367
5368           gfc_resolve_expr (e);
5369           sym->refs++;
5370         }
5371     }
5372   /* This might have changed!  */
5373   return e->expr_type == EXPR_FUNCTION;
5374 }
5375
5376
5377 static void
5378 gfc_resolve_character_operator (gfc_expr *e)
5379 {
5380   gfc_expr *op1 = e->value.op.op1;
5381   gfc_expr *op2 = e->value.op.op2;
5382   gfc_expr *e1 = NULL;
5383   gfc_expr *e2 = NULL;
5384
5385   gcc_assert (e->value.op.op == INTRINSIC_CONCAT);
5386
5387   if (op1->ts.u.cl && op1->ts.u.cl->length)
5388     e1 = gfc_copy_expr (op1->ts.u.cl->length);
5389   else if (op1->expr_type == EXPR_CONSTANT)
5390     e1 = gfc_get_int_expr (gfc_default_integer_kind, NULL,
5391                            op1->value.character.length);
5392
5393   if (op2->ts.u.cl && op2->ts.u.cl->length)
5394     e2 = gfc_copy_expr (op2->ts.u.cl->length);
5395   else if (op2->expr_type == EXPR_CONSTANT)
5396     e2 = gfc_get_int_expr (gfc_default_integer_kind, NULL,
5397                            op2->value.character.length);
5398
5399   e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
5400
5401   if (!e1 || !e2)
5402     return;
5403
5404   e->ts.u.cl->length = gfc_add (e1, e2);
5405   e->ts.u.cl->length->ts.type = BT_INTEGER;
5406   e->ts.u.cl->length->ts.kind = gfc_charlen_int_kind;
5407   gfc_simplify_expr (e->ts.u.cl->length, 0);
5408   gfc_resolve_expr (e->ts.u.cl->length);
5409
5410   return;
5411 }
5412
5413
5414 /*  Ensure that an character expression has a charlen and, if possible, a
5415     length expression.  */
5416
5417 static void
5418 fixup_charlen (gfc_expr *e)
5419 {
5420   /* The cases fall through so that changes in expression type and the need
5421      for multiple fixes are picked up.  In all circumstances, a charlen should
5422      be available for the middle end to hang a backend_decl on.  */
5423   switch (e->expr_type)
5424     {
5425     case EXPR_OP:
5426       gfc_resolve_character_operator (e);
5427
5428     case EXPR_ARRAY:
5429       if (e->expr_type == EXPR_ARRAY)
5430         gfc_resolve_character_array_constructor (e);
5431
5432     case EXPR_SUBSTRING:
5433       if (!e->ts.u.cl && e->ref)
5434         gfc_resolve_substring_charlen (e);
5435
5436     default:
5437       if (!e->ts.u.cl)
5438         e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
5439
5440       break;
5441     }
5442 }
5443
5444
5445 /* Update an actual argument to include the passed-object for type-bound
5446    procedures at the right position.  */
5447
5448 static gfc_actual_arglist*
5449 update_arglist_pass (gfc_actual_arglist* lst, gfc_expr* po, unsigned argpos,
5450                      const char *name)
5451 {
5452   gcc_assert (argpos > 0);
5453
5454   if (argpos == 1)
5455     {
5456       gfc_actual_arglist* result;
5457
5458       result = gfc_get_actual_arglist ();
5459       result->expr = po;
5460       result->next = lst;
5461       if (name)
5462         result->name = name;
5463
5464       return result;
5465     }
5466
5467   if (lst)
5468     lst->next = update_arglist_pass (lst->next, po, argpos - 1, name);
5469   else
5470     lst = update_arglist_pass (NULL, po, argpos - 1, name);
5471   return lst;
5472 }
5473
5474
5475 /* Extract the passed-object from an EXPR_COMPCALL (a copy of it).  */
5476
5477 static gfc_expr*
5478 extract_compcall_passed_object (gfc_expr* e)
5479 {
5480   gfc_expr* po;
5481
5482   gcc_assert (e->expr_type == EXPR_COMPCALL);
5483
5484   if (e->value.compcall.base_object)
5485     po = gfc_copy_expr (e->value.compcall.base_object);
5486   else
5487     {
5488       po = gfc_get_expr ();
5489       po->expr_type = EXPR_VARIABLE;
5490       po->symtree = e->symtree;
5491       po->ref = gfc_copy_ref (e->ref);
5492       po->where = e->where;
5493     }
5494
5495   if (gfc_resolve_expr (po) == FAILURE)
5496     return NULL;
5497
5498   return po;
5499 }
5500
5501
5502 /* Update the arglist of an EXPR_COMPCALL expression to include the
5503    passed-object.  */
5504
5505 static gfc_try
5506 update_compcall_arglist (gfc_expr* e)
5507 {
5508   gfc_expr* po;
5509   gfc_typebound_proc* tbp;
5510
5511   tbp = e->value.compcall.tbp;
5512
5513   if (tbp->error)
5514     return FAILURE;
5515
5516   po = extract_compcall_passed_object (e);
5517   if (!po)
5518     return FAILURE;
5519
5520   if (tbp->nopass || e->value.compcall.ignore_pass)
5521     {
5522       gfc_free_expr (po);
5523       return SUCCESS;
5524     }
5525
5526   gcc_assert (tbp->pass_arg_num > 0);
5527   e->value.compcall.actual = update_arglist_pass (e->value.compcall.actual, po,
5528                                                   tbp->pass_arg_num,
5529                                                   tbp->pass_arg);
5530
5531   return SUCCESS;
5532 }
5533
5534
5535 /* Extract the passed object from a PPC call (a copy of it).  */
5536
5537 static gfc_expr*
5538 extract_ppc_passed_object (gfc_expr *e)
5539 {
5540   gfc_expr *po;
5541   gfc_ref **ref;
5542
5543   po = gfc_get_expr ();
5544   po->expr_type = EXPR_VARIABLE;
5545   po->symtree = e->symtree;
5546   po->ref = gfc_copy_ref (e->ref);
5547   po->where = e->where;
5548
5549   /* Remove PPC reference.  */
5550   ref = &po->ref;
5551   while ((*ref)->next)
5552     ref = &(*ref)->next;
5553   gfc_free_ref_list (*ref);
5554   *ref = NULL;
5555
5556   if (gfc_resolve_expr (po) == FAILURE)
5557     return NULL;
5558
5559   return po;
5560 }
5561
5562
5563 /* Update the actual arglist of a procedure pointer component to include the
5564    passed-object.  */
5565
5566 static gfc_try
5567 update_ppc_arglist (gfc_expr* e)
5568 {
5569   gfc_expr* po;
5570   gfc_component *ppc;
5571   gfc_typebound_proc* tb;
5572
5573   if (!gfc_is_proc_ptr_comp (e, &ppc))
5574     return FAILURE;
5575
5576   tb = ppc->tb;
5577
5578   if (tb->error)
5579     return FAILURE;
5580   else if (tb->nopass)
5581     return SUCCESS;
5582
5583   po = extract_ppc_passed_object (e);
5584   if (!po)
5585     return FAILURE;
5586
5587   /* F08:R739.  */
5588   if (po->rank > 0)
5589     {
5590       gfc_error ("Passed-object at %L must be scalar", &e->where);
5591       return FAILURE;
5592     }
5593
5594   /* F08:C611.  */
5595   if (po->ts.type == BT_DERIVED && po->ts.u.derived->attr.abstract)
5596     {
5597       gfc_error ("Base object for procedure-pointer component call at %L is of"
5598                  " ABSTRACT type '%s'", &e->where, po->ts.u.derived->name);
5599       return FAILURE;
5600     }
5601
5602   gcc_assert (tb->pass_arg_num > 0);
5603   e->value.compcall.actual = update_arglist_pass (e->value.compcall.actual, po,
5604                                                   tb->pass_arg_num,
5605                                                   tb->pass_arg);
5606
5607   return SUCCESS;
5608 }
5609
5610
5611 /* Check that the object a TBP is called on is valid, i.e. it must not be
5612    of ABSTRACT type (as in subobject%abstract_parent%tbp()).  */
5613
5614 static gfc_try
5615 check_typebound_baseobject (gfc_expr* e)
5616 {
5617   gfc_expr* base;
5618   gfc_try return_value = FAILURE;
5619
5620   base = extract_compcall_passed_object (e);
5621   if (!base)
5622     return FAILURE;
5623
5624   gcc_assert (base->ts.type == BT_DERIVED || base->ts.type == BT_CLASS);
5625
5626   /* F08:C611.  */
5627   if (base->ts.type == BT_DERIVED && base->ts.u.derived->attr.abstract)
5628     {
5629       gfc_error ("Base object for type-bound procedure call at %L is of"
5630                  " ABSTRACT type '%s'", &e->where, base->ts.u.derived->name);
5631       goto cleanup;
5632     }
5633
5634   /* F08:C1230. If the procedure called is NOPASS,
5635      the base object must be scalar.  */
5636   if (e->value.compcall.tbp->nopass && base->rank > 0)
5637     {
5638       gfc_error ("Base object for NOPASS type-bound procedure call at %L must"
5639                  " be scalar", &e->where);
5640       goto cleanup;
5641     }
5642
5643   return_value = SUCCESS;
5644
5645 cleanup:
5646   gfc_free_expr (base);
5647   return return_value;
5648 }
5649
5650
5651 /* Resolve a call to a type-bound procedure, either function or subroutine,
5652    statically from the data in an EXPR_COMPCALL expression.  The adapted
5653    arglist and the target-procedure symtree are returned.  */
5654
5655 static gfc_try
5656 resolve_typebound_static (gfc_expr* e, gfc_symtree** target,
5657                           gfc_actual_arglist** actual)
5658 {
5659   gcc_assert (e->expr_type == EXPR_COMPCALL);
5660   gcc_assert (!e->value.compcall.tbp->is_generic);
5661
5662   /* Update the actual arglist for PASS.  */
5663   if (update_compcall_arglist (e) == FAILURE)
5664     return FAILURE;
5665
5666   *actual = e->value.compcall.actual;
5667   *target = e->value.compcall.tbp->u.specific;
5668
5669   gfc_free_ref_list (e->ref);
5670   e->ref = NULL;
5671   e->value.compcall.actual = NULL;
5672
5673   /* If we find a deferred typebound procedure, check for derived types
5674      that an overriding typebound procedure has not been missed.  */
5675   if (e->value.compcall.name
5676       && !e->value.compcall.tbp->non_overridable
5677       && e->value.compcall.base_object
5678       && e->value.compcall.base_object->ts.type == BT_DERIVED)
5679     {
5680       gfc_symtree *st;
5681       gfc_symbol *derived;
5682
5683       /* Use the derived type of the base_object.  */
5684       derived = e->value.compcall.base_object->ts.u.derived;
5685       st = NULL;
5686
5687       /* If necessary, go through the inheritance chain.  */
5688       while (!st && derived)
5689         {
5690           /* Look for the typebound procedure 'name'.  */
5691           if (derived->f2k_derived && derived->f2k_derived->tb_sym_root)
5692             st = gfc_find_symtree (derived->f2k_derived->tb_sym_root,
5693                                    e->value.compcall.name);
5694           if (!st)
5695             derived = gfc_get_derived_super_type (derived);
5696         }
5697
5698       /* Now find the specific name in the derived type namespace.  */
5699       if (st && st->n.tb && st->n.tb->u.specific)
5700         gfc_find_sym_tree (st->n.tb->u.specific->name,
5701                            derived->ns, 1, &st);
5702       if (st)
5703         *target = st;
5704     }
5705   return SUCCESS;
5706 }
5707
5708
5709 /* Get the ultimate declared type from an expression.  In addition,
5710    return the last class/derived type reference and the copy of the
5711    reference list.  If check_types is set true, derived types are
5712    identified as well as class references.  */
5713 static gfc_symbol*
5714 get_declared_from_expr (gfc_ref **class_ref, gfc_ref **new_ref,
5715                         gfc_expr *e, bool check_types)
5716 {
5717   gfc_symbol *declared;
5718   gfc_ref *ref;
5719
5720   declared = NULL;
5721   if (class_ref)
5722     *class_ref = NULL;
5723   if (new_ref)
5724     *new_ref = gfc_copy_ref (e->ref);
5725
5726   for (ref = e->ref; ref; ref = ref->next)
5727     {
5728       if (ref->type != REF_COMPONENT)
5729         continue;
5730
5731       if ((ref->u.c.component->ts.type == BT_CLASS
5732              || (check_types && ref->u.c.component->ts.type == BT_DERIVED))
5733           && ref->u.c.component->attr.flavor != FL_PROCEDURE)
5734         {
5735           declared = ref->u.c.component->ts.u.derived;
5736           if (class_ref)
5737             *class_ref = ref;
5738         }
5739     }
5740
5741   if (declared == NULL)
5742     declared = e->symtree->n.sym->ts.u.derived;
5743
5744   return declared;
5745 }
5746
5747
5748 /* Given an EXPR_COMPCALL calling a GENERIC typebound procedure, figure out
5749    which of the specific bindings (if any) matches the arglist and transform
5750    the expression into a call of that binding.  */
5751
5752 static gfc_try
5753 resolve_typebound_generic_call (gfc_expr* e, const char **name)
5754 {
5755   gfc_typebound_proc* genproc;
5756   const char* genname;
5757   gfc_symtree *st;
5758   gfc_symbol *derived;
5759
5760   gcc_assert (e->expr_type == EXPR_COMPCALL);
5761   genname = e->value.compcall.name;
5762   genproc = e->value.compcall.tbp;
5763
5764   if (!genproc->is_generic)
5765     return SUCCESS;
5766
5767   /* Try the bindings on this type and in the inheritance hierarchy.  */
5768   for (; genproc; genproc = genproc->overridden)
5769     {
5770       gfc_tbp_generic* g;
5771
5772       gcc_assert (genproc->is_generic);
5773       for (g = genproc->u.generic; g; g = g->next)
5774         {
5775           gfc_symbol* target;
5776           gfc_actual_arglist* args;
5777           bool matches;
5778
5779           gcc_assert (g->specific);
5780
5781           if (g->specific->error)
5782             continue;
5783
5784           target = g->specific->u.specific->n.sym;
5785
5786           /* Get the right arglist by handling PASS/NOPASS.  */
5787           args = gfc_copy_actual_arglist (e->value.compcall.actual);
5788           if (!g->specific->nopass)
5789             {
5790               gfc_expr* po;
5791               po = extract_compcall_passed_object (e);
5792               if (!po)
5793                 return FAILURE;
5794
5795               gcc_assert (g->specific->pass_arg_num > 0);
5796               gcc_assert (!g->specific->error);
5797               args = update_arglist_pass (args, po, g->specific->pass_arg_num,
5798                                           g->specific->pass_arg);
5799             }
5800           resolve_actual_arglist (args, target->attr.proc,
5801                                   is_external_proc (target) && !target->formal);
5802
5803           /* Check if this arglist matches the formal.  */
5804           matches = gfc_arglist_matches_symbol (&args, target);
5805
5806           /* Clean up and break out of the loop if we've found it.  */
5807           gfc_free_actual_arglist (args);
5808           if (matches)
5809             {
5810               e->value.compcall.tbp = g->specific;
5811               genname = g->specific_st->name;
5812               /* Pass along the name for CLASS methods, where the vtab
5813                  procedure pointer component has to be referenced.  */
5814               if (name)
5815                 *name = genname;
5816               goto success;
5817             }
5818         }
5819     }
5820
5821   /* Nothing matching found!  */
5822   gfc_error ("Found no matching specific binding for the call to the GENERIC"
5823              " '%s' at %L", genname, &e->where);
5824   return FAILURE;
5825
5826 success:
5827   /* Make sure that we have the right specific instance for the name.  */
5828   derived = get_declared_from_expr (NULL, NULL, e, true);
5829
5830   st = gfc_find_typebound_proc (derived, NULL, genname, true, &e->where);
5831   if (st)
5832     e->value.compcall.tbp = st->n.tb;
5833
5834   return SUCCESS;
5835 }
5836
5837
5838 /* Resolve a call to a type-bound subroutine.  */
5839
5840 static gfc_try
5841 resolve_typebound_call (gfc_code* c, const char **name)
5842 {
5843   gfc_actual_arglist* newactual;
5844   gfc_symtree* target;
5845
5846   /* Check that's really a SUBROUTINE.  */
5847   if (!c->expr1->value.compcall.tbp->subroutine)
5848     {
5849       gfc_error ("'%s' at %L should be a SUBROUTINE",
5850                  c->expr1->value.compcall.name, &c->loc);
5851       return FAILURE;
5852     }
5853
5854   if (check_typebound_baseobject (c->expr1) == FAILURE)
5855     return FAILURE;
5856
5857   /* Pass along the name for CLASS methods, where the vtab
5858      procedure pointer component has to be referenced.  */
5859   if (name)
5860     *name = c->expr1->value.compcall.name;
5861
5862   if (resolve_typebound_generic_call (c->expr1, name) == FAILURE)
5863     return FAILURE;
5864
5865   /* Transform into an ordinary EXEC_CALL for now.  */
5866
5867   if (resolve_typebound_static (c->expr1, &target, &newactual) == FAILURE)
5868     return FAILURE;
5869
5870   c->ext.actual = newactual;
5871   c->symtree = target;
5872   c->op = (c->expr1->value.compcall.assign ? EXEC_ASSIGN_CALL : EXEC_CALL);
5873
5874   gcc_assert (!c->expr1->ref && !c->expr1->value.compcall.actual);
5875
5876   gfc_free_expr (c->expr1);
5877   c->expr1 = gfc_get_expr ();
5878   c->expr1->expr_type = EXPR_FUNCTION;
5879   c->expr1->symtree = target;
5880   c->expr1->where = c->loc;
5881
5882   return resolve_call (c);
5883 }
5884
5885
5886 /* Resolve a component-call expression.  */
5887 static gfc_try
5888 resolve_compcall (gfc_expr* e, const char **name)
5889 {
5890   gfc_actual_arglist* newactual;
5891   gfc_symtree* target;
5892
5893   /* Check that's really a FUNCTION.  */
5894   if (!e->value.compcall.tbp->function)
5895     {
5896       gfc_error ("'%s' at %L should be a FUNCTION",
5897                  e->value.compcall.name, &e->where);
5898       return FAILURE;
5899     }
5900
5901   /* These must not be assign-calls!  */
5902   gcc_assert (!e->value.compcall.assign);
5903
5904   if (check_typebound_baseobject (e) == FAILURE)
5905     return FAILURE;
5906
5907   /* Pass along the name for CLASS methods, where the vtab
5908      procedure pointer component has to be referenced.  */
5909   if (name)
5910     *name = e->value.compcall.name;
5911
5912   if (resolve_typebound_generic_call (e, name) == FAILURE)
5913     return FAILURE;
5914   gcc_assert (!e->value.compcall.tbp->is_generic);
5915
5916   /* Take the rank from the function's symbol.  */
5917   if (e->value.compcall.tbp->u.specific->n.sym->as)
5918     e->rank = e->value.compcall.tbp->u.specific->n.sym->as->rank;
5919
5920   /* For now, we simply transform it into an EXPR_FUNCTION call with the same
5921      arglist to the TBP's binding target.  */
5922
5923   if (resolve_typebound_static (e, &target, &newactual) == FAILURE)
5924     return FAILURE;
5925
5926   e->value.function.actual = newactual;
5927   e->value.function.name = NULL;
5928   e->value.function.esym = target->n.sym;
5929   e->value.function.isym = NULL;
5930   e->symtree = target;
5931   e->ts = target->n.sym->ts;
5932   e->expr_type = EXPR_FUNCTION;
5933
5934   /* Resolution is not necessary if this is a class subroutine; this
5935      function only has to identify the specific proc. Resolution of
5936      the call will be done next in resolve_typebound_call.  */
5937   return gfc_resolve_expr (e);
5938 }
5939
5940
5941
5942 /* Resolve a typebound function, or 'method'. First separate all
5943    the non-CLASS references by calling resolve_compcall directly.  */
5944
5945 static gfc_try
5946 resolve_typebound_function (gfc_expr* e)
5947 {
5948   gfc_symbol *declared;
5949   gfc_component *c;
5950   gfc_ref *new_ref;
5951   gfc_ref *class_ref;
5952   gfc_symtree *st;
5953   const char *name;
5954   gfc_typespec ts;
5955   gfc_expr *expr;
5956   bool overridable;
5957
5958   st = e->symtree;
5959
5960   /* Deal with typebound operators for CLASS objects.  */
5961   expr = e->value.compcall.base_object;
5962   overridable = !e->value.compcall.tbp->non_overridable;
5963   if (expr && expr->ts.type == BT_CLASS && e->value.compcall.name)
5964     {
5965       /* If the base_object is not a variable, the corresponding actual
5966          argument expression must be stored in e->base_expression so
5967          that the corresponding tree temporary can be used as the base
5968          object in gfc_conv_procedure_call.  */
5969       if (expr->expr_type != EXPR_VARIABLE)
5970         {
5971           gfc_actual_arglist *args;
5972
5973           for (args= e->value.function.actual; args; args = args->next)
5974             {
5975               if (expr == args->expr)
5976                 expr = args->expr;
5977             }
5978         }
5979
5980       /* Since the typebound operators are generic, we have to ensure
5981          that any delays in resolution are corrected and that the vtab
5982          is present.  */
5983       ts = expr->ts;
5984       declared = ts.u.derived;
5985       c = gfc_find_component (declared, "_vptr", true, true);
5986       if (c->ts.u.derived == NULL)
5987         c->ts.u.derived = gfc_find_derived_vtab (declared);
5988
5989       if (resolve_compcall (e, &name) == FAILURE)
5990         return FAILURE;
5991
5992       /* Use the generic name if it is there.  */
5993       name = name ? name : e->value.function.esym->name;
5994       e->symtree = expr->symtree;
5995       e->ref = gfc_copy_ref (expr->ref);
5996       get_declared_from_expr (&class_ref, NULL, e, false);
5997
5998       /* Trim away the extraneous references that emerge from nested
5999          use of interface.c (extend_expr).  */
6000       if (class_ref && class_ref->next)
6001         {
6002           gfc_free_ref_list (class_ref->next);
6003           class_ref->next = NULL;
6004         }
6005       else if (e->ref && !class_ref)
6006         {
6007           gfc_free_ref_list (e->ref);
6008           e->ref = NULL;
6009         }
6010
6011       gfc_add_vptr_component (e);
6012       gfc_add_component_ref (e, name);
6013       e->value.function.esym = NULL;
6014       if (expr->expr_type != EXPR_VARIABLE)
6015         e->base_expr = expr;
6016       return SUCCESS;
6017     }
6018
6019   if (st == NULL)
6020     return resolve_compcall (e, NULL);
6021
6022   if (resolve_ref (e) == FAILURE)
6023     return FAILURE;
6024
6025   /* Get the CLASS declared type.  */
6026   declared = get_declared_from_expr (&class_ref, &new_ref, e, true);
6027
6028   /* Weed out cases of the ultimate component being a derived type.  */
6029   if ((class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
6030          || (!class_ref && st->n.sym->ts.type != BT_CLASS))
6031     {
6032       gfc_free_ref_list (new_ref);
6033       return resolve_compcall (e, NULL);
6034     }
6035
6036   c = gfc_find_component (declared, "_data", true, true);
6037   declared = c->ts.u.derived;
6038
6039   /* Treat the call as if it is a typebound procedure, in order to roll
6040      out the correct name for the specific function.  */
6041   if (resolve_compcall (e, &name) == FAILURE)
6042     return FAILURE;
6043   ts = e->ts;
6044
6045   if (overridable)
6046     {
6047       /* Convert the expression to a procedure pointer component call.  */
6048       e->value.function.esym = NULL;
6049       e->symtree = st;
6050
6051       if (new_ref)  
6052         e->ref = new_ref;
6053
6054       /* '_vptr' points to the vtab, which contains the procedure pointers.  */
6055       gfc_add_vptr_component (e);
6056       gfc_add_component_ref (e, name);
6057
6058       /* Recover the typespec for the expression.  This is really only
6059         necessary for generic procedures, where the additional call
6060         to gfc_add_component_ref seems to throw the collection of the
6061         correct typespec.  */
6062       e->ts = ts;
6063     }
6064
6065   return SUCCESS;
6066 }
6067
6068 /* Resolve a typebound subroutine, or 'method'. First separate all
6069    the non-CLASS references by calling resolve_typebound_call
6070    directly.  */
6071
6072 static gfc_try
6073 resolve_typebound_subroutine (gfc_code *code)
6074 {
6075   gfc_symbol *declared;
6076   gfc_component *c;
6077   gfc_ref *new_ref;
6078   gfc_ref *class_ref;
6079   gfc_symtree *st;
6080   const char *name;
6081   gfc_typespec ts;
6082   gfc_expr *expr;
6083   bool overridable;
6084
6085   st = code->expr1->symtree;
6086
6087   /* Deal with typebound operators for CLASS objects.  */
6088   expr = code->expr1->value.compcall.base_object;
6089   overridable = !code->expr1->value.compcall.tbp->non_overridable;
6090   if (expr && expr->ts.type == BT_CLASS && code->expr1->value.compcall.name)
6091     {
6092       /* If the base_object is not a variable, the corresponding actual
6093          argument expression must be stored in e->base_expression so
6094          that the corresponding tree temporary can be used as the base
6095          object in gfc_conv_procedure_call.  */
6096       if (expr->expr_type != EXPR_VARIABLE)
6097         {
6098           gfc_actual_arglist *args;
6099
6100           args= code->expr1->value.function.actual;
6101           for (; args; args = args->next)
6102             if (expr == args->expr)
6103               expr = args->expr;
6104         }
6105
6106       /* Since the typebound operators are generic, we have to ensure
6107          that any delays in resolution are corrected and that the vtab
6108          is present.  */
6109       declared = expr->ts.u.derived;
6110       c = gfc_find_component (declared, "_vptr", true, true);
6111       if (c->ts.u.derived == NULL)
6112         c->ts.u.derived = gfc_find_derived_vtab (declared);
6113
6114       if (resolve_typebound_call (code, &name) == FAILURE)
6115         return FAILURE;
6116
6117       /* Use the generic name if it is there.  */
6118       name = name ? name : code->expr1->value.function.esym->name;
6119       code->expr1->symtree = expr->symtree;
6120       code->expr1->ref = gfc_copy_ref (expr->ref);
6121
6122       /* Trim away the extraneous references that emerge from nested
6123          use of interface.c (extend_expr).  */
6124       get_declared_from_expr (&class_ref, NULL, code->expr1, false);
6125       if (class_ref && class_ref->next)
6126         {
6127           gfc_free_ref_list (class_ref->next);
6128           class_ref->next = NULL;
6129         }
6130       else if (code->expr1->ref && !class_ref)
6131         {
6132           gfc_free_ref_list (code->expr1->ref);
6133           code->expr1->ref = NULL;
6134         }
6135
6136       /* Now use the procedure in the vtable.  */
6137       gfc_add_vptr_component (code->expr1);
6138       gfc_add_component_ref (code->expr1, name);
6139       code->expr1->value.function.esym = NULL;
6140       if (expr->expr_type != EXPR_VARIABLE)
6141         code->expr1->base_expr = expr;
6142       return SUCCESS;
6143     }
6144
6145   if (st == NULL)
6146     return resolve_typebound_call (code, NULL);
6147
6148   if (resolve_ref (code->expr1) == FAILURE)
6149     return FAILURE;
6150
6151   /* Get the CLASS declared type.  */
6152   get_declared_from_expr (&class_ref, &new_ref, code->expr1, true);
6153
6154   /* Weed out cases of the ultimate component being a derived type.  */
6155   if ((class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
6156          || (!class_ref && st->n.sym->ts.type != BT_CLASS))
6157     {
6158       gfc_free_ref_list (new_ref);
6159       return resolve_typebound_call (code, NULL);
6160     }
6161
6162   if (resolve_typebound_call (code, &name) == FAILURE)
6163     return FAILURE;
6164   ts = code->expr1->ts;
6165
6166   if (overridable)
6167     {
6168       /* Convert the expression to a procedure pointer component call.  */
6169       code->expr1->value.function.esym = NULL;
6170       code->expr1->symtree = st;
6171
6172       if (new_ref)
6173         code->expr1->ref = new_ref;
6174
6175       /* '_vptr' points to the vtab, which contains the procedure pointers.  */
6176       gfc_add_vptr_component (code->expr1);
6177       gfc_add_component_ref (code->expr1, name);
6178
6179       /* Recover the typespec for the expression.  This is really only
6180         necessary for generic procedures, where the additional call
6181         to gfc_add_component_ref seems to throw the collection of the
6182         correct typespec.  */
6183       code->expr1->ts = ts;
6184     }
6185
6186   return SUCCESS;
6187 }
6188
6189
6190 /* Resolve a CALL to a Procedure Pointer Component (Subroutine).  */
6191
6192 static gfc_try
6193 resolve_ppc_call (gfc_code* c)
6194 {
6195   gfc_component *comp;
6196   bool b;
6197
6198   b = gfc_is_proc_ptr_comp (c->expr1, &comp);
6199   gcc_assert (b);
6200
6201   c->resolved_sym = c->expr1->symtree->n.sym;
6202   c->expr1->expr_type = EXPR_VARIABLE;
6203
6204   if (!comp->attr.subroutine)
6205     gfc_add_subroutine (&comp->attr, comp->name, &c->expr1->where);
6206
6207   if (resolve_ref (c->expr1) == FAILURE)
6208     return FAILURE;
6209
6210   if (update_ppc_arglist (c->expr1) == FAILURE)
6211     return FAILURE;
6212
6213   c->ext.actual = c->expr1->value.compcall.actual;
6214
6215   if (resolve_actual_arglist (c->ext.actual, comp->attr.proc,
6216                               comp->formal == NULL) == FAILURE)
6217     return FAILURE;
6218
6219   gfc_ppc_use (comp, &c->expr1->value.compcall.actual, &c->expr1->where);
6220
6221   return SUCCESS;
6222 }
6223
6224
6225 /* Resolve a Function Call to a Procedure Pointer Component (Function).  */
6226
6227 static gfc_try
6228 resolve_expr_ppc (gfc_expr* e)
6229 {
6230   gfc_component *comp;
6231   bool b;
6232
6233   b = gfc_is_proc_ptr_comp (e, &comp);
6234   gcc_assert (b);
6235
6236   /* Convert to EXPR_FUNCTION.  */
6237   e->expr_type = EXPR_FUNCTION;
6238   e->value.function.isym = NULL;
6239   e->value.function.actual = e->value.compcall.actual;
6240   e->ts = comp->ts;
6241   if (comp->as != NULL)
6242     e->rank = comp->as->rank;
6243
6244   if (!comp->attr.function)
6245     gfc_add_function (&comp->attr, comp->name, &e->where);
6246
6247   if (resolve_ref (e) == FAILURE)
6248     return FAILURE;
6249
6250   if (resolve_actual_arglist (e->value.function.actual, comp->attr.proc,
6251                               comp->formal == NULL) == FAILURE)
6252     return FAILURE;
6253
6254   if (update_ppc_arglist (e) == FAILURE)
6255     return FAILURE;
6256
6257   gfc_ppc_use (comp, &e->value.compcall.actual, &e->where);
6258
6259   return SUCCESS;
6260 }
6261
6262
6263 static bool
6264 gfc_is_expandable_expr (gfc_expr *e)
6265 {
6266   gfc_constructor *con;
6267
6268   if (e->expr_type == EXPR_ARRAY)
6269     {
6270       /* Traverse the constructor looking for variables that are flavor
6271          parameter.  Parameters must be expanded since they are fully used at
6272          compile time.  */
6273       con = gfc_constructor_first (e->value.constructor);
6274       for (; con; con = gfc_constructor_next (con))
6275         {
6276           if (con->expr->expr_type == EXPR_VARIABLE
6277               && con->expr->symtree
6278               && (con->expr->symtree->n.sym->attr.flavor == FL_PARAMETER
6279               || con->expr->symtree->n.sym->attr.flavor == FL_VARIABLE))
6280             return true;
6281           if (con->expr->expr_type == EXPR_ARRAY
6282               && gfc_is_expandable_expr (con->expr))
6283             return true;
6284         }
6285     }
6286
6287   return false;
6288 }
6289
6290 /* Resolve an expression.  That is, make sure that types of operands agree
6291    with their operators, intrinsic operators are converted to function calls
6292    for overloaded types and unresolved function references are resolved.  */
6293
6294 gfc_try
6295 gfc_resolve_expr (gfc_expr *e)
6296 {
6297   gfc_try t;
6298   bool inquiry_save;
6299
6300   if (e == NULL)
6301     return SUCCESS;
6302
6303   /* inquiry_argument only applies to variables.  */
6304   inquiry_save = inquiry_argument;
6305   if (e->expr_type != EXPR_VARIABLE)
6306     inquiry_argument = false;
6307
6308   switch (e->expr_type)
6309     {
6310     case EXPR_OP:
6311       t = resolve_operator (e);
6312       break;
6313
6314     case EXPR_FUNCTION:
6315     case EXPR_VARIABLE:
6316
6317       if (check_host_association (e))
6318         t = resolve_function (e);
6319       else
6320         {
6321           t = resolve_variable (e);
6322           if (t == SUCCESS)
6323             expression_rank (e);
6324         }
6325
6326       if (e->ts.type == BT_CHARACTER && e->ts.u.cl == NULL && e->ref
6327           && e->ref->type != REF_SUBSTRING)
6328         gfc_resolve_substring_charlen (e);
6329
6330       break;
6331
6332     case EXPR_COMPCALL:
6333       t = resolve_typebound_function (e);
6334       break;
6335
6336     case EXPR_SUBSTRING:
6337       t = resolve_ref (e);
6338       break;
6339
6340     case EXPR_CONSTANT:
6341     case EXPR_NULL:
6342       t = SUCCESS;
6343       break;
6344
6345     case EXPR_PPC:
6346       t = resolve_expr_ppc (e);
6347       break;
6348
6349     case EXPR_ARRAY:
6350       t = FAILURE;
6351       if (resolve_ref (e) == FAILURE)
6352         break;
6353
6354       t = gfc_resolve_array_constructor (e);
6355       /* Also try to expand a constructor.  */
6356       if (t == SUCCESS)
6357         {
6358           expression_rank (e);
6359           if (gfc_is_constant_expr (e) || gfc_is_expandable_expr (e))
6360             gfc_expand_constructor (e, false);
6361         }
6362
6363       /* This provides the opportunity for the length of constructors with
6364          character valued function elements to propagate the string length
6365          to the expression.  */
6366       if (t == SUCCESS && e->ts.type == BT_CHARACTER)
6367         {
6368           /* For efficiency, we call gfc_expand_constructor for BT_CHARACTER
6369              here rather then add a duplicate test for it above.  */ 
6370           gfc_expand_constructor (e, false);
6371           t = gfc_resolve_character_array_constructor (e);
6372         }
6373
6374       break;
6375
6376     case EXPR_STRUCTURE:
6377       t = resolve_ref (e);
6378       if (t == FAILURE)
6379         break;
6380
6381       t = resolve_structure_cons (e, 0);
6382       if (t == FAILURE)
6383         break;
6384
6385       t = gfc_simplify_expr (e, 0);
6386       break;
6387
6388     default:
6389       gfc_internal_error ("gfc_resolve_expr(): Bad expression type");
6390     }
6391
6392   if (e->ts.type == BT_CHARACTER && t == SUCCESS && !e->ts.u.cl)
6393     fixup_charlen (e);
6394
6395   inquiry_argument = inquiry_save;
6396
6397   return t;
6398 }
6399
6400
6401 /* Resolve an expression from an iterator.  They must be scalar and have
6402    INTEGER or (optionally) REAL type.  */
6403
6404 static gfc_try
6405 gfc_resolve_iterator_expr (gfc_expr *expr, bool real_ok,
6406                            const char *name_msgid)
6407 {
6408   if (gfc_resolve_expr (expr) == FAILURE)
6409     return FAILURE;
6410
6411   if (expr->rank != 0)
6412     {
6413       gfc_error ("%s at %L must be a scalar", _(name_msgid), &expr->where);
6414       return FAILURE;
6415     }
6416
6417   if (expr->ts.type != BT_INTEGER)
6418     {
6419       if (expr->ts.type == BT_REAL)
6420         {
6421           if (real_ok)
6422             return gfc_notify_std (GFC_STD_F95_DEL,
6423                                    "Deleted feature: %s at %L must be integer",
6424                                    _(name_msgid), &expr->where);
6425           else
6426             {
6427               gfc_error ("%s at %L must be INTEGER", _(name_msgid),
6428                          &expr->where);
6429               return FAILURE;
6430             }
6431         }
6432       else
6433         {
6434           gfc_error ("%s at %L must be INTEGER", _(name_msgid), &expr->where);
6435           return FAILURE;
6436         }
6437     }
6438   return SUCCESS;
6439 }
6440
6441
6442 /* Resolve the expressions in an iterator structure.  If REAL_OK is
6443    false allow only INTEGER type iterators, otherwise allow REAL types.  */
6444
6445 gfc_try
6446 gfc_resolve_iterator (gfc_iterator *iter, bool real_ok)
6447 {
6448   if (gfc_resolve_iterator_expr (iter->var, real_ok, "Loop variable")
6449       == FAILURE)
6450     return FAILURE;
6451
6452   if (gfc_check_vardef_context (iter->var, false, false, _("iterator variable"))
6453       == FAILURE)
6454     return FAILURE;
6455
6456   if (gfc_resolve_iterator_expr (iter->start, real_ok,
6457                                  "Start expression in DO loop") == FAILURE)
6458     return FAILURE;
6459
6460   if (gfc_resolve_iterator_expr (iter->end, real_ok,
6461                                  "End expression in DO loop") == FAILURE)
6462     return FAILURE;
6463
6464   if (gfc_resolve_iterator_expr (iter->step, real_ok,
6465                                  "Step expression in DO loop") == FAILURE)
6466     return FAILURE;
6467
6468   if (iter->step->expr_type == EXPR_CONSTANT)
6469     {
6470       if ((iter->step->ts.type == BT_INTEGER
6471            && mpz_cmp_ui (iter->step->value.integer, 0) == 0)
6472           || (iter->step->ts.type == BT_REAL
6473               && mpfr_sgn (iter->step->value.real) == 0))
6474         {
6475           gfc_error ("Step expression in DO loop at %L cannot be zero",
6476                      &iter->step->where);
6477           return FAILURE;
6478         }
6479     }
6480
6481   /* Convert start, end, and step to the same type as var.  */
6482   if (iter->start->ts.kind != iter->var->ts.kind
6483       || iter->start->ts.type != iter->var->ts.type)
6484     gfc_convert_type (iter->start, &iter->var->ts, 2);
6485
6486   if (iter->end->ts.kind != iter->var->ts.kind
6487       || iter->end->ts.type != iter->var->ts.type)
6488     gfc_convert_type (iter->end, &iter->var->ts, 2);
6489
6490   if (iter->step->ts.kind != iter->var->ts.kind
6491       || iter->step->ts.type != iter->var->ts.type)
6492     gfc_convert_type (iter->step, &iter->var->ts, 2);
6493
6494   if (iter->start->expr_type == EXPR_CONSTANT
6495       && iter->end->expr_type == EXPR_CONSTANT
6496       && iter->step->expr_type == EXPR_CONSTANT)
6497     {
6498       int sgn, cmp;
6499       if (iter->start->ts.type == BT_INTEGER)
6500         {
6501           sgn = mpz_cmp_ui (iter->step->value.integer, 0);
6502           cmp = mpz_cmp (iter->end->value.integer, iter->start->value.integer);
6503         }
6504       else
6505         {
6506           sgn = mpfr_sgn (iter->step->value.real);
6507           cmp = mpfr_cmp (iter->end->value.real, iter->start->value.real);
6508         }
6509       if ((sgn > 0 && cmp < 0) || (sgn < 0 && cmp > 0))
6510         gfc_warning ("DO loop at %L will be executed zero times",
6511                      &iter->step->where);
6512     }
6513
6514   return SUCCESS;
6515 }
6516
6517
6518 /* Traversal function for find_forall_index.  f == 2 signals that
6519    that variable itself is not to be checked - only the references.  */
6520
6521 static bool
6522 forall_index (gfc_expr *expr, gfc_symbol *sym, int *f)
6523 {
6524   if (expr->expr_type != EXPR_VARIABLE)
6525     return false;
6526   
6527   /* A scalar assignment  */
6528   if (!expr->ref || *f == 1)
6529     {
6530       if (expr->symtree->n.sym == sym)
6531         return true;
6532       else
6533         return false;
6534     }
6535
6536   if (*f == 2)
6537     *f = 1;
6538   return false;
6539 }
6540
6541
6542 /* Check whether the FORALL index appears in the expression or not.
6543    Returns SUCCESS if SYM is found in EXPR.  */
6544
6545 gfc_try
6546 find_forall_index (gfc_expr *expr, gfc_symbol *sym, int f)
6547 {
6548   if (gfc_traverse_expr (expr, sym, forall_index, f))
6549     return SUCCESS;
6550   else
6551     return FAILURE;
6552 }
6553
6554
6555 /* Resolve a list of FORALL iterators.  The FORALL index-name is constrained
6556    to be a scalar INTEGER variable.  The subscripts and stride are scalar
6557    INTEGERs, and if stride is a constant it must be nonzero.
6558    Furthermore "A subscript or stride in a forall-triplet-spec shall
6559    not contain a reference to any index-name in the
6560    forall-triplet-spec-list in which it appears." (7.5.4.1)  */
6561
6562 static void
6563 resolve_forall_iterators (gfc_forall_iterator *it)
6564 {
6565   gfc_forall_iterator *iter, *iter2;
6566
6567   for (iter = it; iter; iter = iter->next)
6568     {
6569       if (gfc_resolve_expr (iter->var) == SUCCESS
6570           && (iter->var->ts.type != BT_INTEGER || iter->var->rank != 0))
6571         gfc_error ("FORALL index-name at %L must be a scalar INTEGER",
6572                    &iter->var->where);
6573
6574       if (gfc_resolve_expr (iter->start) == SUCCESS
6575           && (iter->start->ts.type != BT_INTEGER || iter->start->rank != 0))
6576         gfc_error ("FORALL start expression at %L must be a scalar INTEGER",
6577                    &iter->start->where);
6578       if (iter->var->ts.kind != iter->start->ts.kind)
6579         gfc_convert_type (iter->start, &iter->var->ts, 1);
6580
6581       if (gfc_resolve_expr (iter->end) == SUCCESS
6582           && (iter->end->ts.type != BT_INTEGER || iter->end->rank != 0))
6583         gfc_error ("FORALL end expression at %L must be a scalar INTEGER",
6584                    &iter->end->where);
6585       if (iter->var->ts.kind != iter->end->ts.kind)
6586         gfc_convert_type (iter->end, &iter->var->ts, 1);
6587
6588       if (gfc_resolve_expr (iter->stride) == SUCCESS)
6589         {
6590           if (iter->stride->ts.type != BT_INTEGER || iter->stride->rank != 0)
6591             gfc_error ("FORALL stride expression at %L must be a scalar %s",
6592                        &iter->stride->where, "INTEGER");
6593
6594           if (iter->stride->expr_type == EXPR_CONSTANT
6595               && mpz_cmp_ui(iter->stride->value.integer, 0) == 0)
6596             gfc_error ("FORALL stride expression at %L cannot be zero",
6597                        &iter->stride->where);
6598         }
6599       if (iter->var->ts.kind != iter->stride->ts.kind)
6600         gfc_convert_type (iter->stride, &iter->var->ts, 1);
6601     }
6602
6603   for (iter = it; iter; iter = iter->next)
6604     for (iter2 = iter; iter2; iter2 = iter2->next)
6605       {
6606         if (find_forall_index (iter2->start,
6607                                iter->var->symtree->n.sym, 0) == SUCCESS
6608             || find_forall_index (iter2->end,
6609                                   iter->var->symtree->n.sym, 0) == SUCCESS
6610             || find_forall_index (iter2->stride,
6611                                   iter->var->symtree->n.sym, 0) == SUCCESS)
6612           gfc_error ("FORALL index '%s' may not appear in triplet "
6613                      "specification at %L", iter->var->symtree->name,
6614                      &iter2->start->where);
6615       }
6616 }
6617
6618
6619 /* Given a pointer to a symbol that is a derived type, see if it's
6620    inaccessible, i.e. if it's defined in another module and the components are
6621    PRIVATE.  The search is recursive if necessary.  Returns zero if no
6622    inaccessible components are found, nonzero otherwise.  */
6623
6624 static int
6625 derived_inaccessible (gfc_symbol *sym)
6626 {
6627   gfc_component *c;
6628
6629   if (sym->attr.use_assoc && sym->attr.private_comp)
6630     return 1;
6631
6632   for (c = sym->components; c; c = c->next)
6633     {
6634         if (c->ts.type == BT_DERIVED && derived_inaccessible (c->ts.u.derived))
6635           return 1;
6636     }
6637
6638   return 0;
6639 }
6640
6641
6642 /* Resolve the argument of a deallocate expression.  The expression must be
6643    a pointer or a full array.  */
6644
6645 static gfc_try
6646 resolve_deallocate_expr (gfc_expr *e)
6647 {
6648   symbol_attribute attr;
6649   int allocatable, pointer;
6650   gfc_ref *ref;
6651   gfc_symbol *sym;
6652   gfc_component *c;
6653
6654   if (gfc_resolve_expr (e) == FAILURE)
6655     return FAILURE;
6656
6657   if (e->expr_type != EXPR_VARIABLE)
6658     goto bad;
6659
6660   sym = e->symtree->n.sym;
6661
6662   if (sym->ts.type == BT_CLASS)
6663     {
6664       allocatable = CLASS_DATA (sym)->attr.allocatable;
6665       pointer = CLASS_DATA (sym)->attr.class_pointer;
6666     }
6667   else
6668     {
6669       allocatable = sym->attr.allocatable;
6670       pointer = sym->attr.pointer;
6671     }
6672   for (ref = e->ref; ref; ref = ref->next)
6673     {
6674       switch (ref->type)
6675         {
6676         case REF_ARRAY:
6677           if (ref->u.ar.type != AR_FULL
6678               && !(ref->u.ar.type == AR_ELEMENT && ref->u.ar.as->rank == 0
6679                    && ref->u.ar.codimen && gfc_ref_this_image (ref)))
6680             allocatable = 0;
6681           break;
6682
6683         case REF_COMPONENT:
6684           c = ref->u.c.component;
6685           if (c->ts.type == BT_CLASS)
6686             {
6687               allocatable = CLASS_DATA (c)->attr.allocatable;
6688               pointer = CLASS_DATA (c)->attr.class_pointer;
6689             }
6690           else
6691             {
6692               allocatable = c->attr.allocatable;
6693               pointer = c->attr.pointer;
6694             }
6695           break;
6696
6697         case REF_SUBSTRING:
6698           allocatable = 0;
6699           break;
6700         }
6701     }
6702
6703   attr = gfc_expr_attr (e);
6704
6705   if (allocatable == 0 && attr.pointer == 0)
6706     {
6707     bad:
6708       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
6709                  &e->where);
6710       return FAILURE;
6711     }
6712
6713   /* F2008, C644.  */
6714   if (gfc_is_coindexed (e))
6715     {
6716       gfc_error ("Coindexed allocatable object at %L", &e->where);
6717       return FAILURE;
6718     }
6719
6720   if (pointer
6721       && gfc_check_vardef_context (e, true, true, _("DEALLOCATE object"))
6722          == FAILURE)
6723     return FAILURE;
6724   if (gfc_check_vardef_context (e, false, true, _("DEALLOCATE object"))
6725       == FAILURE)
6726     return FAILURE;
6727
6728   return SUCCESS;
6729 }
6730
6731
6732 /* Returns true if the expression e contains a reference to the symbol sym.  */
6733 static bool
6734 sym_in_expr (gfc_expr *e, gfc_symbol *sym, int *f ATTRIBUTE_UNUSED)
6735 {
6736   if (e->expr_type == EXPR_VARIABLE && e->symtree->n.sym == sym)
6737     return true;
6738
6739   return false;
6740 }
6741
6742 bool
6743 gfc_find_sym_in_expr (gfc_symbol *sym, gfc_expr *e)
6744 {
6745   return gfc_traverse_expr (e, sym, sym_in_expr, 0);
6746 }
6747
6748
6749 /* Given the expression node e for an allocatable/pointer of derived type to be
6750    allocated, get the expression node to be initialized afterwards (needed for
6751    derived types with default initializers, and derived types with allocatable
6752    components that need nullification.)  */
6753
6754 gfc_expr *
6755 gfc_expr_to_initialize (gfc_expr *e)
6756 {
6757   gfc_expr *result;
6758   gfc_ref *ref;
6759   int i;
6760
6761   result = gfc_copy_expr (e);
6762
6763   /* Change the last array reference from AR_ELEMENT to AR_FULL.  */
6764   for (ref = result->ref; ref; ref = ref->next)
6765     if (ref->type == REF_ARRAY && ref->next == NULL)
6766       {
6767         ref->u.ar.type = AR_FULL;
6768
6769         for (i = 0; i < ref->u.ar.dimen; i++)
6770           ref->u.ar.start[i] = ref->u.ar.end[i] = ref->u.ar.stride[i] = NULL;
6771
6772         break;
6773       }
6774
6775   gfc_free_shape (&result->shape, result->rank);
6776
6777   /* Recalculate rank, shape, etc.  */
6778   gfc_resolve_expr (result);
6779   return result;
6780 }
6781
6782
6783 /* If the last ref of an expression is an array ref, return a copy of the
6784    expression with that one removed.  Otherwise, a copy of the original
6785    expression.  This is used for allocate-expressions and pointer assignment
6786    LHS, where there may be an array specification that needs to be stripped
6787    off when using gfc_check_vardef_context.  */
6788
6789 static gfc_expr*
6790 remove_last_array_ref (gfc_expr* e)
6791 {
6792   gfc_expr* e2;
6793   gfc_ref** r;
6794
6795   e2 = gfc_copy_expr (e);
6796   for (r = &e2->ref; *r; r = &(*r)->next)
6797     if ((*r)->type == REF_ARRAY && !(*r)->next)
6798       {
6799         gfc_free_ref_list (*r);
6800         *r = NULL;
6801         break;
6802       }
6803
6804   return e2;
6805 }
6806
6807
6808 /* Used in resolve_allocate_expr to check that a allocation-object and
6809    a source-expr are conformable.  This does not catch all possible 
6810    cases; in particular a runtime checking is needed.  */
6811
6812 static gfc_try
6813 conformable_arrays (gfc_expr *e1, gfc_expr *e2)
6814 {
6815   gfc_ref *tail;
6816   for (tail = e2->ref; tail && tail->next; tail = tail->next);
6817   
6818   /* First compare rank.  */
6819   if (tail && e1->rank != tail->u.ar.as->rank)
6820     {
6821       gfc_error ("Source-expr at %L must be scalar or have the "
6822                  "same rank as the allocate-object at %L",
6823                  &e1->where, &e2->where);
6824       return FAILURE;
6825     }
6826
6827   if (e1->shape)
6828     {
6829       int i;
6830       mpz_t s;
6831
6832       mpz_init (s);
6833
6834       for (i = 0; i < e1->rank; i++)
6835         {
6836           if (tail->u.ar.end[i])
6837             {
6838               mpz_set (s, tail->u.ar.end[i]->value.integer);
6839               mpz_sub (s, s, tail->u.ar.start[i]->value.integer);
6840               mpz_add_ui (s, s, 1);
6841             }
6842           else
6843             {
6844               mpz_set (s, tail->u.ar.start[i]->value.integer);
6845             }
6846
6847           if (mpz_cmp (e1->shape[i], s) != 0)
6848             {
6849               gfc_error ("Source-expr at %L and allocate-object at %L must "
6850                          "have the same shape", &e1->where, &e2->where);
6851               mpz_clear (s);
6852               return FAILURE;
6853             }
6854         }
6855
6856       mpz_clear (s);
6857     }
6858
6859   return SUCCESS;
6860 }
6861
6862
6863 /* Resolve the expression in an ALLOCATE statement, doing the additional
6864    checks to see whether the expression is OK or not.  The expression must
6865    have a trailing array reference that gives the size of the array.  */
6866
6867 static gfc_try
6868 resolve_allocate_expr (gfc_expr *e, gfc_code *code)
6869 {
6870   int i, pointer, allocatable, dimension, is_abstract;
6871   int codimension;
6872   bool coindexed;
6873   symbol_attribute attr;
6874   gfc_ref *ref, *ref2;
6875   gfc_expr *e2;
6876   gfc_array_ref *ar;
6877   gfc_symbol *sym = NULL;
6878   gfc_alloc *a;
6879   gfc_component *c;
6880   gfc_try t;
6881
6882   /* Mark the utmost array component as being in allocate to allow DIMEN_STAR
6883      checking of coarrays.  */
6884   for (ref = e->ref; ref; ref = ref->next)
6885     if (ref->next == NULL)
6886       break;
6887
6888   if (ref && ref->type == REF_ARRAY)
6889     ref->u.ar.in_allocate = true;
6890
6891   if (gfc_resolve_expr (e) == FAILURE)
6892     goto failure;
6893
6894   /* Make sure the expression is allocatable or a pointer.  If it is
6895      pointer, the next-to-last reference must be a pointer.  */
6896
6897   ref2 = NULL;
6898   if (e->symtree)
6899     sym = e->symtree->n.sym;
6900
6901   /* Check whether ultimate component is abstract and CLASS.  */
6902   is_abstract = 0;
6903
6904   if (e->expr_type != EXPR_VARIABLE)
6905     {
6906       allocatable = 0;
6907       attr = gfc_expr_attr (e);
6908       pointer = attr.pointer;
6909       dimension = attr.dimension;
6910       codimension = attr.codimension;
6911     }
6912   else
6913     {
6914       if (sym->ts.type == BT_CLASS && CLASS_DATA (sym))
6915         {
6916           allocatable = CLASS_DATA (sym)->attr.allocatable;
6917           pointer = CLASS_DATA (sym)->attr.class_pointer;
6918           dimension = CLASS_DATA (sym)->attr.dimension;
6919           codimension = CLASS_DATA (sym)->attr.codimension;
6920           is_abstract = CLASS_DATA (sym)->attr.abstract;
6921         }
6922       else
6923         {
6924           allocatable = sym->attr.allocatable;
6925           pointer = sym->attr.pointer;
6926           dimension = sym->attr.dimension;
6927           codimension = sym->attr.codimension;
6928         }
6929
6930       coindexed = false;
6931
6932       for (ref = e->ref; ref; ref2 = ref, ref = ref->next)
6933         {
6934           switch (ref->type)
6935             {
6936               case REF_ARRAY:
6937                 if (ref->u.ar.codimen > 0)
6938                   {
6939                     int n;
6940                     for (n = ref->u.ar.dimen;
6941                          n < ref->u.ar.dimen + ref->u.ar.codimen; n++)
6942                       if (ref->u.ar.dimen_type[n] != DIMEN_THIS_IMAGE)
6943                         {
6944                           coindexed = true;
6945                           break;
6946                         }
6947                    }
6948
6949                 if (ref->next != NULL)
6950                   pointer = 0;
6951                 break;
6952
6953               case REF_COMPONENT:
6954                 /* F2008, C644.  */
6955                 if (coindexed)
6956                   {
6957                     gfc_error ("Coindexed allocatable object at %L",
6958                                &e->where);
6959                     goto failure;
6960                   }
6961
6962                 c = ref->u.c.component;
6963                 if (c->ts.type == BT_CLASS)
6964                   {
6965                     allocatable = CLASS_DATA (c)->attr.allocatable;
6966                     pointer = CLASS_DATA (c)->attr.class_pointer;
6967                     dimension = CLASS_DATA (c)->attr.dimension;
6968                     codimension = CLASS_DATA (c)->attr.codimension;
6969                     is_abstract = CLASS_DATA (c)->attr.abstract;
6970                   }
6971                 else
6972                   {
6973                     allocatable = c->attr.allocatable;
6974                     pointer = c->attr.pointer;
6975                     dimension = c->attr.dimension;
6976                     codimension = c->attr.codimension;
6977                     is_abstract = c->attr.abstract;
6978                   }
6979                 break;
6980
6981               case REF_SUBSTRING:
6982                 allocatable = 0;
6983                 pointer = 0;
6984                 break;
6985             }
6986         }
6987     }
6988
6989   if (allocatable == 0 && pointer == 0)
6990     {
6991       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
6992                  &e->where);
6993       goto failure;
6994     }
6995
6996   /* Some checks for the SOURCE tag.  */
6997   if (code->expr3)
6998     {
6999       /* Check F03:C631.  */
7000       if (!gfc_type_compatible (&e->ts, &code->expr3->ts))
7001         {
7002           gfc_error ("Type of entity at %L is type incompatible with "
7003                       "source-expr at %L", &e->where, &code->expr3->where);
7004           goto failure;
7005         }
7006
7007       /* Check F03:C632 and restriction following Note 6.18.  */
7008       if (code->expr3->rank > 0
7009           && conformable_arrays (code->expr3, e) == FAILURE)
7010         goto failure;
7011
7012       /* Check F03:C633.  */
7013       if (code->expr3->ts.kind != e->ts.kind)
7014         {
7015           gfc_error ("The allocate-object at %L and the source-expr at %L "
7016                       "shall have the same kind type parameter",
7017                       &e->where, &code->expr3->where);
7018           goto failure;
7019         }
7020
7021       /* Check F2008, C642.  */
7022       if (code->expr3->ts.type == BT_DERIVED
7023           && ((codimension && gfc_expr_attr (code->expr3).lock_comp)
7024               || (code->expr3->ts.u.derived->from_intmod
7025                      == INTMOD_ISO_FORTRAN_ENV
7026                   && code->expr3->ts.u.derived->intmod_sym_id
7027                      == ISOFORTRAN_LOCK_TYPE)))
7028         {
7029           gfc_error ("The source-expr at %L shall neither be of type "
7030                      "LOCK_TYPE nor have a LOCK_TYPE component if "
7031                       "allocate-object at %L is a coarray",
7032                       &code->expr3->where, &e->where);
7033           goto failure;
7034         }
7035     }
7036
7037   /* Check F08:C629.  */
7038   if (is_abstract && code->ext.alloc.ts.type == BT_UNKNOWN
7039       && !code->expr3)
7040     {
7041       gcc_assert (e->ts.type == BT_CLASS);
7042       gfc_error ("Allocating %s of ABSTRACT base type at %L requires a "
7043                  "type-spec or source-expr", sym->name, &e->where);
7044       goto failure;
7045     }
7046
7047   if (code->ext.alloc.ts.type == BT_CHARACTER && !e->ts.deferred)
7048     {
7049       int cmp = gfc_dep_compare_expr (e->ts.u.cl->length,
7050                                       code->ext.alloc.ts.u.cl->length);
7051       if (cmp == 1 || cmp == -1 || cmp == -3)
7052         {
7053           gfc_error ("Allocating %s at %L with type-spec requires the same "
7054                      "character-length parameter as in the declaration",
7055                      sym->name, &e->where);
7056           goto failure;
7057         }
7058     }
7059
7060   /* In the variable definition context checks, gfc_expr_attr is used
7061      on the expression.  This is fooled by the array specification
7062      present in e, thus we have to eliminate that one temporarily.  */
7063   e2 = remove_last_array_ref (e);
7064   t = SUCCESS;
7065   if (t == SUCCESS && pointer)
7066     t = gfc_check_vardef_context (e2, true, true, _("ALLOCATE object"));
7067   if (t == SUCCESS)
7068     t = gfc_check_vardef_context (e2, false, true, _("ALLOCATE object"));
7069   gfc_free_expr (e2);
7070   if (t == FAILURE)
7071     goto failure;
7072
7073   if (e->ts.type == BT_CLASS && CLASS_DATA (e)->attr.dimension
7074         && !code->expr3 && code->ext.alloc.ts.type == BT_DERIVED)
7075     {
7076       /* For class arrays, the initialization with SOURCE is done
7077          using _copy and trans_call. It is convenient to exploit that
7078          when the allocated type is different from the declared type but
7079          no SOURCE exists by setting expr3.  */
7080       code->expr3 = gfc_default_initializer (&code->ext.alloc.ts); 
7081     }
7082   else if (!code->expr3)
7083     {
7084       /* Set up default initializer if needed.  */
7085       gfc_typespec ts;
7086       gfc_expr *init_e;
7087
7088       if (code->ext.alloc.ts.type == BT_DERIVED)
7089         ts = code->ext.alloc.ts;
7090       else
7091         ts = e->ts;
7092
7093       if (ts.type == BT_CLASS)
7094         ts = ts.u.derived->components->ts;
7095
7096       if (ts.type == BT_DERIVED && (init_e = gfc_default_initializer (&ts)))
7097         {
7098           gfc_code *init_st = gfc_get_code ();
7099           init_st->loc = code->loc;
7100           init_st->op = EXEC_INIT_ASSIGN;
7101           init_st->expr1 = gfc_expr_to_initialize (e);
7102           init_st->expr2 = init_e;
7103           init_st->next = code->next;
7104           code->next = init_st;
7105         }
7106     }
7107   else if (code->expr3->mold && code->expr3->ts.type == BT_DERIVED)
7108     {
7109       /* Default initialization via MOLD (non-polymorphic).  */
7110       gfc_expr *rhs = gfc_default_initializer (&code->expr3->ts);
7111       gfc_resolve_expr (rhs);
7112       gfc_free_expr (code->expr3);
7113       code->expr3 = rhs;
7114     }
7115
7116   if (e->ts.type == BT_CLASS)
7117     {
7118       /* Make sure the vtab symbol is present when
7119          the module variables are generated.  */
7120       gfc_typespec ts = e->ts;
7121       if (code->expr3)
7122         ts = code->expr3->ts;
7123       else if (code->ext.alloc.ts.type == BT_DERIVED)
7124         ts = code->ext.alloc.ts;
7125       gfc_find_derived_vtab (ts.u.derived);
7126       if (dimension)
7127         e = gfc_expr_to_initialize (e);
7128     }
7129
7130   if (dimension == 0 && codimension == 0)
7131     goto success;
7132
7133   /* Make sure the last reference node is an array specification.  */
7134
7135   if (!ref2 || ref2->type != REF_ARRAY || ref2->u.ar.type == AR_FULL
7136       || (dimension && ref2->u.ar.dimen == 0))
7137     {
7138       gfc_error ("Array specification required in ALLOCATE statement "
7139                  "at %L", &e->where);
7140       goto failure;
7141     }
7142
7143   /* Make sure that the array section reference makes sense in the
7144     context of an ALLOCATE specification.  */
7145
7146   ar = &ref2->u.ar;
7147
7148   if (codimension)
7149     for (i = ar->dimen; i < ar->dimen + ar->codimen; i++)
7150       if (ar->dimen_type[i] == DIMEN_THIS_IMAGE)
7151         {
7152           gfc_error ("Coarray specification required in ALLOCATE statement "
7153                      "at %L", &e->where);
7154           goto failure;
7155         }
7156
7157   for (i = 0; i < ar->dimen; i++)
7158     {
7159       if (ref2->u.ar.type == AR_ELEMENT)
7160         goto check_symbols;
7161
7162       switch (ar->dimen_type[i])
7163         {
7164         case DIMEN_ELEMENT:
7165           break;
7166
7167         case DIMEN_RANGE:
7168           if (ar->start[i] != NULL
7169               && ar->end[i] != NULL
7170               && ar->stride[i] == NULL)
7171             break;
7172
7173           /* Fall Through...  */
7174
7175         case DIMEN_UNKNOWN:
7176         case DIMEN_VECTOR:
7177         case DIMEN_STAR:
7178         case DIMEN_THIS_IMAGE:
7179           gfc_error ("Bad array specification in ALLOCATE statement at %L",
7180                      &e->where);
7181           goto failure;
7182         }
7183
7184 check_symbols:
7185       for (a = code->ext.alloc.list; a; a = a->next)
7186         {
7187           sym = a->expr->symtree->n.sym;
7188
7189           /* TODO - check derived type components.  */
7190           if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
7191             continue;
7192
7193           if ((ar->start[i] != NULL
7194                && gfc_find_sym_in_expr (sym, ar->start[i]))
7195               || (ar->end[i] != NULL
7196                   && gfc_find_sym_in_expr (sym, ar->end[i])))
7197             {
7198               gfc_error ("'%s' must not appear in the array specification at "
7199                          "%L in the same ALLOCATE statement where it is "
7200                          "itself allocated", sym->name, &ar->where);
7201               goto failure;
7202             }
7203         }
7204     }
7205
7206   for (i = ar->dimen; i < ar->codimen + ar->dimen; i++)
7207     {
7208       if (ar->dimen_type[i] == DIMEN_ELEMENT
7209           || ar->dimen_type[i] == DIMEN_RANGE)
7210         {
7211           if (i == (ar->dimen + ar->codimen - 1))
7212             {
7213               gfc_error ("Expected '*' in coindex specification in ALLOCATE "
7214                          "statement at %L", &e->where);
7215               goto failure;
7216             }
7217           break;
7218         }
7219
7220       if (ar->dimen_type[i] == DIMEN_STAR && i == (ar->dimen + ar->codimen - 1)
7221           && ar->stride[i] == NULL)
7222         break;
7223
7224       gfc_error ("Bad coarray specification in ALLOCATE statement at %L",
7225                  &e->where);
7226       goto failure;
7227     }
7228
7229 success:
7230   return SUCCESS;
7231
7232 failure:
7233   return FAILURE;
7234 }
7235
7236 static void
7237 resolve_allocate_deallocate (gfc_code *code, const char *fcn)
7238 {
7239   gfc_expr *stat, *errmsg, *pe, *qe;
7240   gfc_alloc *a, *p, *q;
7241
7242   stat = code->expr1;
7243   errmsg = code->expr2;
7244
7245   /* Check the stat variable.  */
7246   if (stat)
7247     {
7248       gfc_check_vardef_context (stat, false, false, _("STAT variable"));
7249
7250       if ((stat->ts.type != BT_INTEGER
7251            && !(stat->ref && (stat->ref->type == REF_ARRAY
7252                               || stat->ref->type == REF_COMPONENT)))
7253           || stat->rank > 0)
7254         gfc_error ("Stat-variable at %L must be a scalar INTEGER "
7255                    "variable", &stat->where);
7256
7257       for (p = code->ext.alloc.list; p; p = p->next)
7258         if (p->expr->symtree->n.sym->name == stat->symtree->n.sym->name)
7259           {
7260             gfc_ref *ref1, *ref2;
7261             bool found = true;
7262
7263             for (ref1 = p->expr->ref, ref2 = stat->ref; ref1 && ref2;
7264                  ref1 = ref1->next, ref2 = ref2->next)
7265               {
7266                 if (ref1->type != REF_COMPONENT || ref2->type != REF_COMPONENT)
7267                   continue;
7268                 if (ref1->u.c.component->name != ref2->u.c.component->name)
7269                   {
7270                     found = false;
7271                     break;
7272                   }
7273               }
7274
7275             if (found)
7276               {
7277                 gfc_error ("Stat-variable at %L shall not be %sd within "
7278                            "the same %s statement", &stat->where, fcn, fcn);
7279                 break;
7280               }
7281           }
7282     }
7283
7284   /* Check the errmsg variable.  */
7285   if (errmsg)
7286     {
7287       if (!stat)
7288         gfc_warning ("ERRMSG at %L is useless without a STAT tag",
7289                      &errmsg->where);
7290
7291       gfc_check_vardef_context (errmsg, false, false, _("ERRMSG variable"));
7292
7293       if ((errmsg->ts.type != BT_CHARACTER
7294            && !(errmsg->ref
7295                 && (errmsg->ref->type == REF_ARRAY
7296                     || errmsg->ref->type == REF_COMPONENT)))
7297           || errmsg->rank > 0 )
7298         gfc_error ("Errmsg-variable at %L must be a scalar CHARACTER "
7299                    "variable", &errmsg->where);
7300
7301       for (p = code->ext.alloc.list; p; p = p->next)
7302         if (p->expr->symtree->n.sym->name == errmsg->symtree->n.sym->name)
7303           {
7304             gfc_ref *ref1, *ref2;
7305             bool found = true;
7306
7307             for (ref1 = p->expr->ref, ref2 = errmsg->ref; ref1 && ref2;
7308                  ref1 = ref1->next, ref2 = ref2->next)
7309               {
7310                 if (ref1->type != REF_COMPONENT || ref2->type != REF_COMPONENT)
7311                   continue;
7312                 if (ref1->u.c.component->name != ref2->u.c.component->name)
7313                   {
7314                     found = false;
7315                     break;
7316                   }
7317               }
7318
7319             if (found)
7320               {
7321                 gfc_error ("Errmsg-variable at %L shall not be %sd within "
7322                            "the same %s statement", &errmsg->where, fcn, fcn);
7323                 break;
7324               }
7325           }
7326     }
7327
7328   /* Check that an allocate-object appears only once in the statement.  
7329      FIXME: Checking derived types is disabled.  */
7330   for (p = code->ext.alloc.list; p; p = p->next)
7331     {
7332       pe = p->expr;
7333       for (q = p->next; q; q = q->next)
7334         {
7335           qe = q->expr;
7336           if (pe->symtree->n.sym->name == qe->symtree->n.sym->name)
7337             {
7338               /* This is a potential collision.  */
7339               gfc_ref *pr = pe->ref;
7340               gfc_ref *qr = qe->ref;
7341               
7342               /* Follow the references  until
7343                  a) They start to differ, in which case there is no error;
7344                  you can deallocate a%b and a%c in a single statement
7345                  b) Both of them stop, which is an error
7346                  c) One of them stops, which is also an error.  */
7347               while (1)
7348                 {
7349                   if (pr == NULL && qr == NULL)
7350                     {
7351                       gfc_error ("Allocate-object at %L also appears at %L",
7352                                  &pe->where, &qe->where);
7353                       break;
7354                     }
7355                   else if (pr != NULL && qr == NULL)
7356                     {
7357                       gfc_error ("Allocate-object at %L is subobject of"
7358                                  " object at %L", &pe->where, &qe->where);
7359                       break;
7360                     }
7361                   else if (pr == NULL && qr != NULL)
7362                     {
7363                       gfc_error ("Allocate-object at %L is subobject of"
7364                                  " object at %L", &qe->where, &pe->where);
7365                       break;
7366                     }
7367                   /* Here, pr != NULL && qr != NULL  */
7368                   gcc_assert(pr->type == qr->type);
7369                   if (pr->type == REF_ARRAY)
7370                     {
7371                       /* Handle cases like allocate(v(3)%x(3), v(2)%x(3)),
7372                          which are legal.  */
7373                       gcc_assert (qr->type == REF_ARRAY);
7374
7375                       if (pr->next && qr->next)
7376                         {
7377                           gfc_array_ref *par = &(pr->u.ar);
7378                           gfc_array_ref *qar = &(qr->u.ar);
7379                           if (gfc_dep_compare_expr (par->start[0],
7380                                                     qar->start[0]) != 0)
7381                               break;
7382                         }
7383                     }
7384                   else
7385                     {
7386                       if (pr->u.c.component->name != qr->u.c.component->name)
7387                         break;
7388                     }
7389                   
7390                   pr = pr->next;
7391                   qr = qr->next;
7392                 }
7393             }
7394         }
7395     }
7396
7397   if (strcmp (fcn, "ALLOCATE") == 0)
7398     {
7399       for (a = code->ext.alloc.list; a; a = a->next)
7400         resolve_allocate_expr (a->expr, code);
7401     }
7402   else
7403     {
7404       for (a = code->ext.alloc.list; a; a = a->next)
7405         resolve_deallocate_expr (a->expr);
7406     }
7407 }
7408
7409
7410 /************ SELECT CASE resolution subroutines ************/
7411
7412 /* Callback function for our mergesort variant.  Determines interval
7413    overlaps for CASEs. Return <0 if op1 < op2, 0 for overlap, >0 for
7414    op1 > op2.  Assumes we're not dealing with the default case.  
7415    We have op1 = (:L), (K:L) or (K:) and op2 = (:N), (M:N) or (M:).
7416    There are nine situations to check.  */
7417
7418 static int
7419 compare_cases (const gfc_case *op1, const gfc_case *op2)
7420 {
7421   int retval;
7422
7423   if (op1->low == NULL) /* op1 = (:L)  */
7424     {
7425       /* op2 = (:N), so overlap.  */
7426       retval = 0;
7427       /* op2 = (M:) or (M:N),  L < M  */
7428       if (op2->low != NULL
7429           && gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
7430         retval = -1;
7431     }
7432   else if (op1->high == NULL) /* op1 = (K:)  */
7433     {
7434       /* op2 = (M:), so overlap.  */
7435       retval = 0;
7436       /* op2 = (:N) or (M:N), K > N  */
7437       if (op2->high != NULL
7438           && gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
7439         retval = 1;
7440     }
7441   else /* op1 = (K:L)  */
7442     {
7443       if (op2->low == NULL)       /* op2 = (:N), K > N  */
7444         retval = (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
7445                  ? 1 : 0;
7446       else if (op2->high == NULL) /* op2 = (M:), L < M  */
7447         retval = (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
7448                  ? -1 : 0;
7449       else                      /* op2 = (M:N)  */
7450         {
7451           retval =  0;
7452           /* L < M  */
7453           if (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
7454             retval =  -1;
7455           /* K > N  */
7456           else if (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
7457             retval =  1;
7458         }
7459     }
7460
7461   return retval;
7462 }
7463
7464
7465 /* Merge-sort a double linked case list, detecting overlap in the
7466    process.  LIST is the head of the double linked case list before it
7467    is sorted.  Returns the head of the sorted list if we don't see any
7468    overlap, or NULL otherwise.  */
7469
7470 static gfc_case *
7471 check_case_overlap (gfc_case *list)
7472 {
7473   gfc_case *p, *q, *e, *tail;
7474   int insize, nmerges, psize, qsize, cmp, overlap_seen;
7475
7476   /* If the passed list was empty, return immediately.  */
7477   if (!list)
7478     return NULL;
7479
7480   overlap_seen = 0;
7481   insize = 1;
7482
7483   /* Loop unconditionally.  The only exit from this loop is a return
7484      statement, when we've finished sorting the case list.  */
7485   for (;;)
7486     {
7487       p = list;
7488       list = NULL;
7489       tail = NULL;
7490
7491       /* Count the number of merges we do in this pass.  */
7492       nmerges = 0;
7493
7494       /* Loop while there exists a merge to be done.  */
7495       while (p)
7496         {
7497           int i;
7498
7499           /* Count this merge.  */
7500           nmerges++;
7501
7502           /* Cut the list in two pieces by stepping INSIZE places
7503              forward in the list, starting from P.  */
7504           psize = 0;
7505           q = p;
7506           for (i = 0; i < insize; i++)
7507             {
7508               psize++;
7509               q = q->right;
7510               if (!q)
7511                 break;
7512             }
7513           qsize = insize;
7514
7515           /* Now we have two lists.  Merge them!  */
7516           while (psize > 0 || (qsize > 0 && q != NULL))
7517             {
7518               /* See from which the next case to merge comes from.  */
7519               if (psize == 0)
7520                 {
7521                   /* P is empty so the next case must come from Q.  */
7522                   e = q;
7523                   q = q->right;
7524                   qsize--;
7525                 }
7526               else if (qsize == 0 || q == NULL)
7527                 {
7528                   /* Q is empty.  */
7529                   e = p;
7530                   p = p->right;
7531                   psize--;
7532                 }
7533               else
7534                 {
7535                   cmp = compare_cases (p, q);
7536                   if (cmp < 0)
7537                     {
7538                       /* The whole case range for P is less than the
7539                          one for Q.  */
7540                       e = p;
7541                       p = p->right;
7542                       psize--;
7543                     }
7544                   else if (cmp > 0)
7545                     {
7546                       /* The whole case range for Q is greater than
7547                          the case range for P.  */
7548                       e = q;
7549                       q = q->right;
7550                       qsize--;
7551                     }
7552                   else
7553                     {
7554                       /* The cases overlap, or they are the same
7555                          element in the list.  Either way, we must
7556                          issue an error and get the next case from P.  */
7557                       /* FIXME: Sort P and Q by line number.  */
7558                       gfc_error ("CASE label at %L overlaps with CASE "
7559                                  "label at %L", &p->where, &q->where);
7560                       overlap_seen = 1;
7561                       e = p;
7562                       p = p->right;
7563                       psize--;
7564                     }
7565                 }
7566
7567                 /* Add the next element to the merged list.  */
7568               if (tail)
7569                 tail->right = e;
7570               else
7571                 list = e;
7572               e->left = tail;
7573               tail = e;
7574             }
7575
7576           /* P has now stepped INSIZE places along, and so has Q.  So
7577              they're the same.  */
7578           p = q;
7579         }
7580       tail->right = NULL;
7581
7582       /* If we have done only one merge or none at all, we've
7583          finished sorting the cases.  */
7584       if (nmerges <= 1)
7585         {
7586           if (!overlap_seen)
7587             return list;
7588           else
7589             return NULL;
7590         }
7591
7592       /* Otherwise repeat, merging lists twice the size.  */
7593       insize *= 2;
7594     }
7595 }
7596
7597
7598 /* Check to see if an expression is suitable for use in a CASE statement.
7599    Makes sure that all case expressions are scalar constants of the same
7600    type.  Return FAILURE if anything is wrong.  */
7601
7602 static gfc_try
7603 validate_case_label_expr (gfc_expr *e, gfc_expr *case_expr)
7604 {
7605   if (e == NULL) return SUCCESS;
7606
7607   if (e->ts.type != case_expr->ts.type)
7608     {
7609       gfc_error ("Expression in CASE statement at %L must be of type %s",
7610                  &e->where, gfc_basic_typename (case_expr->ts.type));
7611       return FAILURE;
7612     }
7613
7614   /* C805 (R808) For a given case-construct, each case-value shall be of
7615      the same type as case-expr.  For character type, length differences
7616      are allowed, but the kind type parameters shall be the same.  */
7617
7618   if (case_expr->ts.type == BT_CHARACTER && e->ts.kind != case_expr->ts.kind)
7619     {
7620       gfc_error ("Expression in CASE statement at %L must be of kind %d",
7621                  &e->where, case_expr->ts.kind);
7622       return FAILURE;
7623     }
7624
7625   /* Convert the case value kind to that of case expression kind,
7626      if needed */
7627
7628   if (e->ts.kind != case_expr->ts.kind)
7629     gfc_convert_type_warn (e, &case_expr->ts, 2, 0);
7630
7631   if (e->rank != 0)
7632     {
7633       gfc_error ("Expression in CASE statement at %L must be scalar",
7634                  &e->where);
7635       return FAILURE;
7636     }
7637
7638   return SUCCESS;
7639 }
7640
7641
7642 /* Given a completely parsed select statement, we:
7643
7644      - Validate all expressions and code within the SELECT.
7645      - Make sure that the selection expression is not of the wrong type.
7646      - Make sure that no case ranges overlap.
7647      - Eliminate unreachable cases and unreachable code resulting from
7648        removing case labels.
7649
7650    The standard does allow unreachable cases, e.g. CASE (5:3).  But
7651    they are a hassle for code generation, and to prevent that, we just
7652    cut them out here.  This is not necessary for overlapping cases
7653    because they are illegal and we never even try to generate code.
7654
7655    We have the additional caveat that a SELECT construct could have
7656    been a computed GOTO in the source code. Fortunately we can fairly
7657    easily work around that here: The case_expr for a "real" SELECT CASE
7658    is in code->expr1, but for a computed GOTO it is in code->expr2. All
7659    we have to do is make sure that the case_expr is a scalar integer
7660    expression.  */
7661
7662 static void
7663 resolve_select (gfc_code *code)
7664 {
7665   gfc_code *body;
7666   gfc_expr *case_expr;
7667   gfc_case *cp, *default_case, *tail, *head;
7668   int seen_unreachable;
7669   int seen_logical;
7670   int ncases;
7671   bt type;
7672   gfc_try t;
7673
7674   if (code->expr1 == NULL)
7675     {
7676       /* This was actually a computed GOTO statement.  */
7677       case_expr = code->expr2;
7678       if (case_expr->ts.type != BT_INTEGER|| case_expr->rank != 0)
7679         gfc_error ("Selection expression in computed GOTO statement "
7680                    "at %L must be a scalar integer expression",
7681                    &case_expr->where);
7682
7683       /* Further checking is not necessary because this SELECT was built
7684          by the compiler, so it should always be OK.  Just move the
7685          case_expr from expr2 to expr so that we can handle computed
7686          GOTOs as normal SELECTs from here on.  */
7687       code->expr1 = code->expr2;
7688       code->expr2 = NULL;
7689       return;
7690     }
7691
7692   case_expr = code->expr1;
7693
7694   type = case_expr->ts.type;
7695   if (type != BT_LOGICAL && type != BT_INTEGER && type != BT_CHARACTER)
7696     {
7697       gfc_error ("Argument of SELECT statement at %L cannot be %s",
7698                  &case_expr->where, gfc_typename (&case_expr->ts));
7699
7700       /* Punt. Going on here just produce more garbage error messages.  */
7701       return;
7702     }
7703
7704   /* Raise a warning if an INTEGER case value exceeds the range of
7705      the case-expr. Later, all expressions will be promoted to the
7706      largest kind of all case-labels.  */
7707
7708   if (type == BT_INTEGER)
7709     for (body = code->block; body; body = body->block)
7710       for (cp = body->ext.block.case_list; cp; cp = cp->next)
7711         {
7712           if (cp->low
7713               && gfc_check_integer_range (cp->low->value.integer,
7714                                           case_expr->ts.kind) != ARITH_OK)
7715             gfc_warning ("Expression in CASE statement at %L is "
7716                          "not in the range of %s", &cp->low->where,
7717                          gfc_typename (&case_expr->ts));
7718
7719           if (cp->high
7720               && cp->low != cp->high
7721               && gfc_check_integer_range (cp->high->value.integer,
7722                                           case_expr->ts.kind) != ARITH_OK)
7723             gfc_warning ("Expression in CASE statement at %L is "
7724                          "not in the range of %s", &cp->high->where,
7725                          gfc_typename (&case_expr->ts));
7726         }
7727
7728   /* PR 19168 has a long discussion concerning a mismatch of the kinds
7729      of the SELECT CASE expression and its CASE values.  Walk the lists
7730      of case values, and if we find a mismatch, promote case_expr to
7731      the appropriate kind.  */
7732
7733   if (type == BT_LOGICAL || type == BT_INTEGER)
7734     {
7735       for (body = code->block; body; body = body->block)
7736         {
7737           /* Walk the case label list.  */
7738           for (cp = body->ext.block.case_list; cp; cp = cp->next)
7739             {
7740               /* Intercept the DEFAULT case.  It does not have a kind.  */
7741               if (cp->low == NULL && cp->high == NULL)
7742                 continue;
7743
7744               /* Unreachable case ranges are discarded, so ignore.  */
7745               if (cp->low != NULL && cp->high != NULL
7746                   && cp->low != cp->high
7747                   && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
7748                 continue;
7749
7750               if (cp->low != NULL
7751                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->low))
7752                 gfc_convert_type_warn (case_expr, &cp->low->ts, 2, 0);
7753
7754               if (cp->high != NULL
7755                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->high))
7756                 gfc_convert_type_warn (case_expr, &cp->high->ts, 2, 0);
7757             }
7758          }
7759     }
7760
7761   /* Assume there is no DEFAULT case.  */
7762   default_case = NULL;
7763   head = tail = NULL;
7764   ncases = 0;
7765   seen_logical = 0;
7766
7767   for (body = code->block; body; body = body->block)
7768     {
7769       /* Assume the CASE list is OK, and all CASE labels can be matched.  */
7770       t = SUCCESS;
7771       seen_unreachable = 0;
7772
7773       /* Walk the case label list, making sure that all case labels
7774          are legal.  */
7775       for (cp = body->ext.block.case_list; cp; cp = cp->next)
7776         {
7777           /* Count the number of cases in the whole construct.  */
7778           ncases++;
7779
7780           /* Intercept the DEFAULT case.  */
7781           if (cp->low == NULL && cp->high == NULL)
7782             {
7783               if (default_case != NULL)
7784                 {
7785                   gfc_error ("The DEFAULT CASE at %L cannot be followed "
7786                              "by a second DEFAULT CASE at %L",
7787                              &default_case->where, &cp->where);
7788                   t = FAILURE;
7789                   break;
7790                 }
7791               else
7792                 {
7793                   default_case = cp;
7794                   continue;
7795                 }
7796             }
7797
7798           /* Deal with single value cases and case ranges.  Errors are
7799              issued from the validation function.  */
7800           if (validate_case_label_expr (cp->low, case_expr) != SUCCESS
7801               || validate_case_label_expr (cp->high, case_expr) != SUCCESS)
7802             {
7803               t = FAILURE;
7804               break;
7805             }
7806
7807           if (type == BT_LOGICAL
7808               && ((cp->low == NULL || cp->high == NULL)
7809                   || cp->low != cp->high))
7810             {
7811               gfc_error ("Logical range in CASE statement at %L is not "
7812                          "allowed", &cp->low->where);
7813               t = FAILURE;
7814               break;
7815             }
7816
7817           if (type == BT_LOGICAL && cp->low->expr_type == EXPR_CONSTANT)
7818             {
7819               int value;
7820               value = cp->low->value.logical == 0 ? 2 : 1;
7821               if (value & seen_logical)
7822                 {
7823                   gfc_error ("Constant logical value in CASE statement "
7824                              "is repeated at %L",
7825                              &cp->low->where);
7826                   t = FAILURE;
7827                   break;
7828                 }
7829               seen_logical |= value;
7830             }
7831
7832           if (cp->low != NULL && cp->high != NULL
7833               && cp->low != cp->high
7834               && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
7835             {
7836               if (gfc_option.warn_surprising)
7837                 gfc_warning ("Range specification at %L can never "
7838                              "be matched", &cp->where);
7839
7840               cp->unreachable = 1;
7841               seen_unreachable = 1;
7842             }
7843           else
7844             {
7845               /* If the case range can be matched, it can also overlap with
7846                  other cases.  To make sure it does not, we put it in a
7847                  double linked list here.  We sort that with a merge sort
7848                  later on to detect any overlapping cases.  */
7849               if (!head)
7850                 {
7851                   head = tail = cp;
7852                   head->right = head->left = NULL;
7853                 }
7854               else
7855                 {
7856                   tail->right = cp;
7857                   tail->right->left = tail;
7858                   tail = tail->right;
7859                   tail->right = NULL;
7860                 }
7861             }
7862         }
7863
7864       /* It there was a failure in the previous case label, give up
7865          for this case label list.  Continue with the next block.  */
7866       if (t == FAILURE)
7867         continue;
7868
7869       /* See if any case labels that are unreachable have been seen.
7870          If so, we eliminate them.  This is a bit of a kludge because
7871          the case lists for a single case statement (label) is a
7872          single forward linked lists.  */
7873       if (seen_unreachable)
7874       {
7875         /* Advance until the first case in the list is reachable.  */
7876         while (body->ext.block.case_list != NULL
7877                && body->ext.block.case_list->unreachable)
7878           {
7879             gfc_case *n = body->ext.block.case_list;
7880             body->ext.block.case_list = body->ext.block.case_list->next;
7881             n->next = NULL;
7882             gfc_free_case_list (n);
7883           }
7884
7885         /* Strip all other unreachable cases.  */
7886         if (body->ext.block.case_list)
7887           {
7888             for (cp = body->ext.block.case_list; cp->next; cp = cp->next)
7889               {
7890                 if (cp->next->unreachable)
7891                   {
7892                     gfc_case *n = cp->next;
7893                     cp->next = cp->next->next;
7894                     n->next = NULL;
7895                     gfc_free_case_list (n);
7896                   }
7897               }
7898           }
7899       }
7900     }
7901
7902   /* See if there were overlapping cases.  If the check returns NULL,
7903      there was overlap.  In that case we don't do anything.  If head
7904      is non-NULL, we prepend the DEFAULT case.  The sorted list can
7905      then used during code generation for SELECT CASE constructs with
7906      a case expression of a CHARACTER type.  */
7907   if (head)
7908     {
7909       head = check_case_overlap (head);
7910
7911       /* Prepend the default_case if it is there.  */
7912       if (head != NULL && default_case)
7913         {
7914           default_case->left = NULL;
7915           default_case->right = head;
7916           head->left = default_case;
7917         }
7918     }
7919
7920   /* Eliminate dead blocks that may be the result if we've seen
7921      unreachable case labels for a block.  */
7922   for (body = code; body && body->block; body = body->block)
7923     {
7924       if (body->block->ext.block.case_list == NULL)
7925         {
7926           /* Cut the unreachable block from the code chain.  */
7927           gfc_code *c = body->block;
7928           body->block = c->block;
7929
7930           /* Kill the dead block, but not the blocks below it.  */
7931           c->block = NULL;
7932           gfc_free_statements (c);
7933         }
7934     }
7935
7936   /* More than two cases is legal but insane for logical selects.
7937      Issue a warning for it.  */
7938   if (gfc_option.warn_surprising && type == BT_LOGICAL
7939       && ncases > 2)
7940     gfc_warning ("Logical SELECT CASE block at %L has more that two cases",
7941                  &code->loc);
7942 }
7943
7944
7945 /* Check if a derived type is extensible.  */
7946
7947 bool
7948 gfc_type_is_extensible (gfc_symbol *sym)
7949 {
7950   return !(sym->attr.is_bind_c || sym->attr.sequence);
7951 }
7952
7953
7954 /* Resolve an associate-name:  Resolve target and ensure the type-spec is
7955    correct as well as possibly the array-spec.  */
7956
7957 static void
7958 resolve_assoc_var (gfc_symbol* sym, bool resolve_target)
7959 {
7960   gfc_expr* target;
7961
7962   gcc_assert (sym->assoc);
7963   gcc_assert (sym->attr.flavor == FL_VARIABLE);
7964
7965   /* If this is for SELECT TYPE, the target may not yet be set.  In that
7966      case, return.  Resolution will be called later manually again when
7967      this is done.  */
7968   target = sym->assoc->target;
7969   if (!target)
7970     return;
7971   gcc_assert (!sym->assoc->dangling);
7972
7973   if (resolve_target && gfc_resolve_expr (target) != SUCCESS)
7974     return;
7975
7976   /* For variable targets, we get some attributes from the target.  */
7977   if (target->expr_type == EXPR_VARIABLE)
7978     {
7979       gfc_symbol* tsym;
7980
7981       gcc_assert (target->symtree);
7982       tsym = target->symtree->n.sym;
7983
7984       sym->attr.asynchronous = tsym->attr.asynchronous;
7985       sym->attr.volatile_ = tsym->attr.volatile_;
7986
7987       sym->attr.target = tsym->attr.target
7988                          || gfc_expr_attr (target).pointer;
7989     }
7990
7991   /* Get type if this was not already set.  Note that it can be
7992      some other type than the target in case this is a SELECT TYPE
7993      selector!  So we must not update when the type is already there.  */
7994   if (sym->ts.type == BT_UNKNOWN)
7995     sym->ts = target->ts;
7996   gcc_assert (sym->ts.type != BT_UNKNOWN);
7997
7998   /* See if this is a valid association-to-variable.  */
7999   sym->assoc->variable = (target->expr_type == EXPR_VARIABLE
8000                           && !gfc_has_vector_subscript (target));
8001
8002   /* Finally resolve if this is an array or not.  */
8003   if (sym->attr.dimension && target->rank == 0)
8004     {
8005       gfc_error ("Associate-name '%s' at %L is used as array",
8006                  sym->name, &sym->declared_at);
8007       sym->attr.dimension = 0;
8008       return;
8009     }
8010
8011   /* We cannot deal with class selectors that need temporaries.  */
8012   if (target->ts.type == BT_CLASS
8013         && gfc_ref_needs_temporary_p (target->ref))
8014     {
8015       gfc_error ("CLASS selector at %L needs a temporary which is not "
8016                  "yet implemented", &target->where);
8017       return;
8018     }
8019
8020   if (target->ts.type != BT_CLASS && target->rank > 0)
8021     sym->attr.dimension = 1;
8022   else if (target->ts.type == BT_CLASS)
8023     gfc_fix_class_refs (target);
8024
8025   /* The associate-name will have a correct type by now. Make absolutely
8026      sure that it has not picked up a dimension attribute.  */
8027   if (sym->ts.type == BT_CLASS)
8028     sym->attr.dimension = 0;
8029
8030   if (sym->attr.dimension)
8031     {
8032       sym->as = gfc_get_array_spec ();
8033       sym->as->rank = target->rank;
8034       sym->as->type = AS_DEFERRED;
8035
8036       /* Target must not be coindexed, thus the associate-variable
8037          has no corank.  */
8038       sym->as->corank = 0;
8039     }
8040 }
8041
8042
8043 /* Resolve a SELECT TYPE statement.  */
8044
8045 static void
8046 resolve_select_type (gfc_code *code, gfc_namespace *old_ns)
8047 {
8048   gfc_symbol *selector_type;
8049   gfc_code *body, *new_st, *if_st, *tail;
8050   gfc_code *class_is = NULL, *default_case = NULL;
8051   gfc_case *c;
8052   gfc_symtree *st;
8053   char name[GFC_MAX_SYMBOL_LEN];
8054   gfc_namespace *ns;
8055   int error = 0;
8056
8057   ns = code->ext.block.ns;
8058   gfc_resolve (ns);
8059
8060   /* Check for F03:C813.  */
8061   if (code->expr1->ts.type != BT_CLASS
8062       && !(code->expr2 && code->expr2->ts.type == BT_CLASS))
8063     {
8064       gfc_error ("Selector shall be polymorphic in SELECT TYPE statement "
8065                  "at %L", &code->loc);
8066       return;
8067     }
8068
8069   if (!code->expr1->symtree->n.sym->attr.class_ok)
8070     return;
8071
8072   if (code->expr2)
8073     {
8074       if (code->expr1->symtree->n.sym->attr.untyped)
8075         code->expr1->symtree->n.sym->ts = code->expr2->ts;
8076       selector_type = CLASS_DATA (code->expr2)->ts.u.derived;
8077     }
8078   else
8079     selector_type = CLASS_DATA (code->expr1)->ts.u.derived;
8080
8081   /* Loop over TYPE IS / CLASS IS cases.  */
8082   for (body = code->block; body; body = body->block)
8083     {
8084       c = body->ext.block.case_list;
8085
8086       /* Check F03:C815.  */
8087       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
8088           && !gfc_type_is_extensible (c->ts.u.derived))
8089         {
8090           gfc_error ("Derived type '%s' at %L must be extensible",
8091                      c->ts.u.derived->name, &c->where);
8092           error++;
8093           continue;
8094         }
8095
8096       /* Check F03:C816.  */
8097       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
8098           && !gfc_type_is_extension_of (selector_type, c->ts.u.derived))
8099         {
8100           gfc_error ("Derived type '%s' at %L must be an extension of '%s'",
8101                      c->ts.u.derived->name, &c->where, selector_type->name);
8102           error++;
8103           continue;
8104         }
8105
8106       /* Intercept the DEFAULT case.  */
8107       if (c->ts.type == BT_UNKNOWN)
8108         {
8109           /* Check F03:C818.  */
8110           if (default_case)
8111             {
8112               gfc_error ("The DEFAULT CASE at %L cannot be followed "
8113                          "by a second DEFAULT CASE at %L",
8114                          &default_case->ext.block.case_list->where, &c->where);
8115               error++;
8116               continue;
8117             }
8118
8119           default_case = body;
8120         }
8121     }
8122     
8123   if (error > 0)
8124     return;
8125
8126   /* Transform SELECT TYPE statement to BLOCK and associate selector to
8127      target if present.  If there are any EXIT statements referring to the
8128      SELECT TYPE construct, this is no problem because the gfc_code
8129      reference stays the same and EXIT is equally possible from the BLOCK
8130      it is changed to.  */
8131   code->op = EXEC_BLOCK;
8132   if (code->expr2)
8133     {
8134       gfc_association_list* assoc;
8135
8136       assoc = gfc_get_association_list ();
8137       assoc->st = code->expr1->symtree;
8138       assoc->target = gfc_copy_expr (code->expr2);
8139       assoc->target->where = code->expr2->where;
8140       /* assoc->variable will be set by resolve_assoc_var.  */
8141       
8142       code->ext.block.assoc = assoc;
8143       code->expr1->symtree->n.sym->assoc = assoc;
8144
8145       resolve_assoc_var (code->expr1->symtree->n.sym, false);
8146     }
8147   else
8148     code->ext.block.assoc = NULL;
8149
8150   /* Add EXEC_SELECT to switch on type.  */
8151   new_st = gfc_get_code ();
8152   new_st->op = code->op;
8153   new_st->expr1 = code->expr1;
8154   new_st->expr2 = code->expr2;
8155   new_st->block = code->block;
8156   code->expr1 = code->expr2 =  NULL;
8157   code->block = NULL;
8158   if (!ns->code)
8159     ns->code = new_st;
8160   else
8161     ns->code->next = new_st;
8162   code = new_st;
8163   code->op = EXEC_SELECT;
8164   gfc_add_vptr_component (code->expr1);
8165   gfc_add_hash_component (code->expr1);
8166
8167   /* Loop over TYPE IS / CLASS IS cases.  */
8168   for (body = code->block; body; body = body->block)
8169     {
8170       c = body->ext.block.case_list;
8171
8172       if (c->ts.type == BT_DERIVED)
8173         c->low = c->high = gfc_get_int_expr (gfc_default_integer_kind, NULL,
8174                                              c->ts.u.derived->hash_value);
8175
8176       else if (c->ts.type == BT_UNKNOWN)
8177         continue;
8178
8179       /* Associate temporary to selector.  This should only be done
8180          when this case is actually true, so build a new ASSOCIATE
8181          that does precisely this here (instead of using the
8182          'global' one).  */
8183
8184       if (c->ts.type == BT_CLASS)
8185         sprintf (name, "__tmp_class_%s", c->ts.u.derived->name);
8186       else
8187         sprintf (name, "__tmp_type_%s", c->ts.u.derived->name);
8188       st = gfc_find_symtree (ns->sym_root, name);
8189       gcc_assert (st->n.sym->assoc);
8190       st->n.sym->assoc->target = gfc_get_variable_expr (code->expr1->symtree);
8191       st->n.sym->assoc->target->where = code->expr1->where;
8192       if (c->ts.type == BT_DERIVED)
8193         gfc_add_data_component (st->n.sym->assoc->target);
8194
8195       new_st = gfc_get_code ();
8196       new_st->op = EXEC_BLOCK;
8197       new_st->ext.block.ns = gfc_build_block_ns (ns);
8198       new_st->ext.block.ns->code = body->next;
8199       body->next = new_st;
8200
8201       /* Chain in the new list only if it is marked as dangling.  Otherwise
8202          there is a CASE label overlap and this is already used.  Just ignore,
8203          the error is diagnosed elsewhere.  */
8204       if (st->n.sym->assoc->dangling)
8205         {
8206           new_st->ext.block.assoc = st->n.sym->assoc;
8207           st->n.sym->assoc->dangling = 0;
8208         }
8209
8210       resolve_assoc_var (st->n.sym, false);
8211     }
8212     
8213   /* Take out CLASS IS cases for separate treatment.  */
8214   body = code;
8215   while (body && body->block)
8216     {
8217       if (body->block->ext.block.case_list->ts.type == BT_CLASS)
8218         {
8219           /* Add to class_is list.  */
8220           if (class_is == NULL)
8221             { 
8222               class_is = body->block;
8223               tail = class_is;
8224             }
8225           else
8226             {
8227               for (tail = class_is; tail->block; tail = tail->block) ;
8228               tail->block = body->block;
8229               tail = tail->block;
8230             }
8231           /* Remove from EXEC_SELECT list.  */
8232           body->block = body->block->block;
8233           tail->block = NULL;
8234         }
8235       else
8236         body = body->block;
8237     }
8238
8239   if (class_is)
8240     {
8241       gfc_symbol *vtab;
8242       
8243       if (!default_case)
8244         {
8245           /* Add a default case to hold the CLASS IS cases.  */
8246           for (tail = code; tail->block; tail = tail->block) ;
8247           tail->block = gfc_get_code ();
8248           tail = tail->block;
8249           tail->op = EXEC_SELECT_TYPE;
8250           tail->ext.block.case_list = gfc_get_case ();
8251           tail->ext.block.case_list->ts.type = BT_UNKNOWN;
8252           tail->next = NULL;
8253           default_case = tail;
8254         }
8255
8256       /* More than one CLASS IS block?  */
8257       if (class_is->block)
8258         {
8259           gfc_code **c1,*c2;
8260           bool swapped;
8261           /* Sort CLASS IS blocks by extension level.  */
8262           do
8263             {
8264               swapped = false;
8265               for (c1 = &class_is; (*c1) && (*c1)->block; c1 = &((*c1)->block))
8266                 {
8267                   c2 = (*c1)->block;
8268                   /* F03:C817 (check for doubles).  */
8269                   if ((*c1)->ext.block.case_list->ts.u.derived->hash_value
8270                       == c2->ext.block.case_list->ts.u.derived->hash_value)
8271                     {
8272                       gfc_error ("Double CLASS IS block in SELECT TYPE "
8273                                  "statement at %L",
8274                                  &c2->ext.block.case_list->where);
8275                       return;
8276                     }
8277                   if ((*c1)->ext.block.case_list->ts.u.derived->attr.extension
8278                       < c2->ext.block.case_list->ts.u.derived->attr.extension)
8279                     {
8280                       /* Swap.  */
8281                       (*c1)->block = c2->block;
8282                       c2->block = *c1;
8283                       *c1 = c2;
8284                       swapped = true;
8285                     }
8286                 }
8287             }
8288           while (swapped);
8289         }
8290         
8291       /* Generate IF chain.  */
8292       if_st = gfc_get_code ();
8293       if_st->op = EXEC_IF;
8294       new_st = if_st;
8295       for (body = class_is; body; body = body->block)
8296         {
8297           new_st->block = gfc_get_code ();
8298           new_st = new_st->block;
8299           new_st->op = EXEC_IF;
8300           /* Set up IF condition: Call _gfortran_is_extension_of.  */
8301           new_st->expr1 = gfc_get_expr ();
8302           new_st->expr1->expr_type = EXPR_FUNCTION;
8303           new_st->expr1->ts.type = BT_LOGICAL;
8304           new_st->expr1->ts.kind = 4;
8305           new_st->expr1->value.function.name = gfc_get_string (PREFIX ("is_extension_of"));
8306           new_st->expr1->value.function.isym = XCNEW (gfc_intrinsic_sym);
8307           new_st->expr1->value.function.isym->id = GFC_ISYM_EXTENDS_TYPE_OF;
8308           /* Set up arguments.  */
8309           new_st->expr1->value.function.actual = gfc_get_actual_arglist ();
8310           new_st->expr1->value.function.actual->expr = gfc_get_variable_expr (code->expr1->symtree);
8311           new_st->expr1->value.function.actual->expr->where = code->loc;
8312           gfc_add_vptr_component (new_st->expr1->value.function.actual->expr);
8313           vtab = gfc_find_derived_vtab (body->ext.block.case_list->ts.u.derived);
8314           st = gfc_find_symtree (vtab->ns->sym_root, vtab->name);
8315           new_st->expr1->value.function.actual->next = gfc_get_actual_arglist ();
8316           new_st->expr1->value.function.actual->next->expr = gfc_get_variable_expr (st);
8317           new_st->next = body->next;
8318         }
8319         if (default_case->next)
8320           {
8321             new_st->block = gfc_get_code ();
8322             new_st = new_st->block;
8323             new_st->op = EXEC_IF;
8324             new_st->next = default_case->next;
8325           }
8326           
8327         /* Replace CLASS DEFAULT code by the IF chain.  */
8328         default_case->next = if_st;
8329     }
8330
8331   /* Resolve the internal code.  This can not be done earlier because
8332      it requires that the sym->assoc of selectors is set already.  */
8333   gfc_current_ns = ns;
8334   gfc_resolve_blocks (code->block, gfc_current_ns);
8335   gfc_current_ns = old_ns;
8336
8337   resolve_select (code);
8338 }
8339
8340
8341 /* Resolve a transfer statement. This is making sure that:
8342    -- a derived type being transferred has only non-pointer components
8343    -- a derived type being transferred doesn't have private components, unless 
8344       it's being transferred from the module where the type was defined
8345    -- we're not trying to transfer a whole assumed size array.  */
8346
8347 static void
8348 resolve_transfer (gfc_code *code)
8349 {
8350   gfc_typespec *ts;
8351   gfc_symbol *sym;
8352   gfc_ref *ref;
8353   gfc_expr *exp;
8354
8355   exp = code->expr1;
8356
8357   while (exp != NULL && exp->expr_type == EXPR_OP
8358          && exp->value.op.op == INTRINSIC_PARENTHESES)
8359     exp = exp->value.op.op1;
8360
8361   if (exp && exp->expr_type == EXPR_NULL && exp->ts.type == BT_UNKNOWN)
8362     {
8363       gfc_error ("NULL intrinsic at %L in data transfer statement requires "
8364                  "MOLD=", &exp->where);
8365       return;
8366     }
8367
8368   if (exp == NULL || (exp->expr_type != EXPR_VARIABLE
8369                       && exp->expr_type != EXPR_FUNCTION))
8370     return;
8371
8372   /* If we are reading, the variable will be changed.  Note that
8373      code->ext.dt may be NULL if the TRANSFER is related to
8374      an INQUIRE statement -- but in this case, we are not reading, either.  */
8375   if (code->ext.dt && code->ext.dt->dt_io_kind->value.iokind == M_READ
8376       && gfc_check_vardef_context (exp, false, false, _("item in READ"))
8377          == FAILURE)
8378     return;
8379
8380   sym = exp->symtree->n.sym;
8381   ts = &sym->ts;
8382
8383   /* Go to actual component transferred.  */
8384   for (ref = exp->ref; ref; ref = ref->next)
8385     if (ref->type == REF_COMPONENT)
8386       ts = &ref->u.c.component->ts;
8387
8388   if (ts->type == BT_CLASS)
8389     {
8390       /* FIXME: Test for defined input/output.  */
8391       gfc_error ("Data transfer element at %L cannot be polymorphic unless "
8392                 "it is processed by a defined input/output procedure",
8393                 &code->loc);
8394       return;
8395     }
8396
8397   if (ts->type == BT_DERIVED)
8398     {
8399       /* Check that transferred derived type doesn't contain POINTER
8400          components.  */
8401       if (ts->u.derived->attr.pointer_comp)
8402         {
8403           gfc_error ("Data transfer element at %L cannot have POINTER "
8404                      "components unless it is processed by a defined "
8405                      "input/output procedure", &code->loc);
8406           return;
8407         }
8408
8409       /* F08:C935.  */
8410       if (ts->u.derived->attr.proc_pointer_comp)
8411         {
8412           gfc_error ("Data transfer element at %L cannot have "
8413                      "procedure pointer components", &code->loc);
8414           return;
8415         }
8416
8417       if (ts->u.derived->attr.alloc_comp)
8418         {
8419           gfc_error ("Data transfer element at %L cannot have ALLOCATABLE "
8420                      "components unless it is processed by a defined "
8421                      "input/output procedure", &code->loc);
8422           return;
8423         }
8424
8425       if (derived_inaccessible (ts->u.derived))
8426         {
8427           gfc_error ("Data transfer element at %L cannot have "
8428                      "PRIVATE components",&code->loc);
8429           return;
8430         }
8431     }
8432
8433   if (sym->as != NULL && sym->as->type == AS_ASSUMED_SIZE && exp->ref
8434       && exp->ref->type == REF_ARRAY && exp->ref->u.ar.type == AR_FULL)
8435     {
8436       gfc_error ("Data transfer element at %L cannot be a full reference to "
8437                  "an assumed-size array", &code->loc);
8438       return;
8439     }
8440 }
8441
8442
8443 /*********** Toplevel code resolution subroutines ***********/
8444
8445 /* Find the set of labels that are reachable from this block.  We also
8446    record the last statement in each block.  */
8447      
8448 static void
8449 find_reachable_labels (gfc_code *block)
8450 {
8451   gfc_code *c;
8452
8453   if (!block)
8454     return;
8455
8456   cs_base->reachable_labels = bitmap_obstack_alloc (&labels_obstack);
8457
8458   /* Collect labels in this block.  We don't keep those corresponding
8459      to END {IF|SELECT}, these are checked in resolve_branch by going
8460      up through the code_stack.  */
8461   for (c = block; c; c = c->next)
8462     {
8463       if (c->here && c->op != EXEC_END_NESTED_BLOCK)
8464         bitmap_set_bit (cs_base->reachable_labels, c->here->value);
8465     }
8466
8467   /* Merge with labels from parent block.  */
8468   if (cs_base->prev)
8469     {
8470       gcc_assert (cs_base->prev->reachable_labels);
8471       bitmap_ior_into (cs_base->reachable_labels,
8472                        cs_base->prev->reachable_labels);
8473     }
8474 }
8475
8476
8477 static void
8478 resolve_lock_unlock (gfc_code *code)
8479 {
8480   if (code->expr1->ts.type != BT_DERIVED
8481       || code->expr1->expr_type != EXPR_VARIABLE
8482       || code->expr1->ts.u.derived->from_intmod != INTMOD_ISO_FORTRAN_ENV
8483       || code->expr1->ts.u.derived->intmod_sym_id != ISOFORTRAN_LOCK_TYPE
8484       || code->expr1->rank != 0
8485       || (!gfc_is_coarray (code->expr1) && !gfc_is_coindexed (code->expr1)))
8486     gfc_error ("Lock variable at %L must be a scalar of type LOCK_TYPE",
8487                &code->expr1->where);
8488
8489   /* Check STAT.  */
8490   if (code->expr2
8491       && (code->expr2->ts.type != BT_INTEGER || code->expr2->rank != 0
8492           || code->expr2->expr_type != EXPR_VARIABLE))
8493     gfc_error ("STAT= argument at %L must be a scalar INTEGER variable",
8494                &code->expr2->where);
8495
8496   if (code->expr2
8497       && gfc_check_vardef_context (code->expr2, false, false,
8498                                    _("STAT variable")) == FAILURE)
8499     return;
8500
8501   /* Check ERRMSG.  */
8502   if (code->expr3
8503       && (code->expr3->ts.type != BT_CHARACTER || code->expr3->rank != 0
8504           || code->expr3->expr_type != EXPR_VARIABLE))
8505     gfc_error ("ERRMSG= argument at %L must be a scalar CHARACTER variable",
8506                &code->expr3->where);
8507
8508   if (code->expr3
8509       && gfc_check_vardef_context (code->expr3, false, false,
8510                                    _("ERRMSG variable")) == FAILURE)
8511     return;
8512
8513   /* Check ACQUIRED_LOCK.  */
8514   if (code->expr4
8515       && (code->expr4->ts.type != BT_LOGICAL || code->expr4->rank != 0
8516           || code->expr4->expr_type != EXPR_VARIABLE))
8517     gfc_error ("ACQUIRED_LOCK= argument at %L must be a scalar LOGICAL "
8518                "variable", &code->expr4->where);
8519
8520   if (code->expr4
8521       && gfc_check_vardef_context (code->expr4, false, false,
8522                                    _("ACQUIRED_LOCK variable")) == FAILURE)
8523     return;
8524 }
8525
8526
8527 static void
8528 resolve_sync (gfc_code *code)
8529 {
8530   /* Check imageset. The * case matches expr1 == NULL.  */
8531   if (code->expr1)
8532     {
8533       if (code->expr1->ts.type != BT_INTEGER || code->expr1->rank > 1)
8534         gfc_error ("Imageset argument at %L must be a scalar or rank-1 "
8535                    "INTEGER expression", &code->expr1->where);
8536       if (code->expr1->expr_type == EXPR_CONSTANT && code->expr1->rank == 0
8537           && mpz_cmp_si (code->expr1->value.integer, 1) < 0)
8538         gfc_error ("Imageset argument at %L must between 1 and num_images()",
8539                    &code->expr1->where);
8540       else if (code->expr1->expr_type == EXPR_ARRAY
8541                && gfc_simplify_expr (code->expr1, 0) == SUCCESS)
8542         {
8543            gfc_constructor *cons;
8544            cons = gfc_constructor_first (code->expr1->value.constructor);
8545            for (; cons; cons = gfc_constructor_next (cons))
8546              if (cons->expr->expr_type == EXPR_CONSTANT
8547                  &&  mpz_cmp_si (cons->expr->value.integer, 1) < 0)
8548                gfc_error ("Imageset argument at %L must between 1 and "
8549                           "num_images()", &cons->expr->where);
8550         }
8551     }
8552
8553   /* Check STAT.  */
8554   if (code->expr2
8555       && (code->expr2->ts.type != BT_INTEGER || code->expr2->rank != 0
8556           || code->expr2->expr_type != EXPR_VARIABLE))
8557     gfc_error ("STAT= argument at %L must be a scalar INTEGER variable",
8558                &code->expr2->where);
8559
8560   /* Check ERRMSG.  */
8561   if (code->expr3
8562       && (code->expr3->ts.type != BT_CHARACTER || code->expr3->rank != 0
8563           || code->expr3->expr_type != EXPR_VARIABLE))
8564     gfc_error ("ERRMSG= argument at %L must be a scalar CHARACTER variable",
8565                &code->expr3->where);
8566 }
8567
8568
8569 /* Given a branch to a label, see if the branch is conforming.
8570    The code node describes where the branch is located.  */
8571
8572 static void
8573 resolve_branch (gfc_st_label *label, gfc_code *code)
8574 {
8575   code_stack *stack;
8576
8577   if (label == NULL)
8578     return;
8579
8580   /* Step one: is this a valid branching target?  */
8581
8582   if (label->defined == ST_LABEL_UNKNOWN)
8583     {
8584       gfc_error ("Label %d referenced at %L is never defined", label->value,
8585                  &label->where);
8586       return;
8587     }
8588
8589   if (label->defined != ST_LABEL_TARGET)
8590     {
8591       gfc_error ("Statement at %L is not a valid branch target statement "
8592                  "for the branch statement at %L", &label->where, &code->loc);
8593       return;
8594     }
8595
8596   /* Step two: make sure this branch is not a branch to itself ;-)  */
8597
8598   if (code->here == label)
8599     {
8600       gfc_warning ("Branch at %L may result in an infinite loop", &code->loc);
8601       return;
8602     }
8603
8604   /* Step three:  See if the label is in the same block as the
8605      branching statement.  The hard work has been done by setting up
8606      the bitmap reachable_labels.  */
8607
8608   if (bitmap_bit_p (cs_base->reachable_labels, label->value))
8609     {
8610       /* Check now whether there is a CRITICAL construct; if so, check
8611          whether the label is still visible outside of the CRITICAL block,
8612          which is invalid.  */
8613       for (stack = cs_base; stack; stack = stack->prev)
8614         {
8615           if (stack->current->op == EXEC_CRITICAL
8616               && bitmap_bit_p (stack->reachable_labels, label->value))
8617             gfc_error ("GOTO statement at %L leaves CRITICAL construct for "
8618                       "label at %L", &code->loc, &label->where);
8619           else if (stack->current->op == EXEC_DO_CONCURRENT
8620                    && bitmap_bit_p (stack->reachable_labels, label->value))
8621             gfc_error ("GOTO statement at %L leaves DO CONCURRENT construct "
8622                       "for label at %L", &code->loc, &label->where);
8623         }
8624
8625       return;
8626     }
8627
8628   /* Step four:  If we haven't found the label in the bitmap, it may
8629     still be the label of the END of the enclosing block, in which
8630     case we find it by going up the code_stack.  */
8631
8632   for (stack = cs_base; stack; stack = stack->prev)
8633     {
8634       if (stack->current->next && stack->current->next->here == label)
8635         break;
8636       if (stack->current->op == EXEC_CRITICAL)
8637         {
8638           /* Note: A label at END CRITICAL does not leave the CRITICAL
8639              construct as END CRITICAL is still part of it.  */
8640           gfc_error ("GOTO statement at %L leaves CRITICAL construct for label"
8641                       " at %L", &code->loc, &label->where);
8642           return;
8643         }
8644       else if (stack->current->op == EXEC_DO_CONCURRENT)
8645         {
8646           gfc_error ("GOTO statement at %L leaves DO CONCURRENT construct for "
8647                      "label at %L", &code->loc, &label->where);
8648           return;
8649         }
8650     }
8651
8652   if (stack)
8653     {
8654       gcc_assert (stack->current->next->op == EXEC_END_NESTED_BLOCK);
8655       return;
8656     }
8657
8658   /* The label is not in an enclosing block, so illegal.  This was
8659      allowed in Fortran 66, so we allow it as extension.  No
8660      further checks are necessary in this case.  */
8661   gfc_notify_std (GFC_STD_LEGACY, "Label at %L is not in the same block "
8662                   "as the GOTO statement at %L", &label->where,
8663                   &code->loc);
8664   return;
8665 }
8666
8667
8668 /* Check whether EXPR1 has the same shape as EXPR2.  */
8669
8670 static gfc_try
8671 resolve_where_shape (gfc_expr *expr1, gfc_expr *expr2)
8672 {
8673   mpz_t shape[GFC_MAX_DIMENSIONS];
8674   mpz_t shape2[GFC_MAX_DIMENSIONS];
8675   gfc_try result = FAILURE;
8676   int i;
8677
8678   /* Compare the rank.  */
8679   if (expr1->rank != expr2->rank)
8680     return result;
8681
8682   /* Compare the size of each dimension.  */
8683   for (i=0; i<expr1->rank; i++)
8684     {
8685       if (gfc_array_dimen_size (expr1, i, &shape[i]) == FAILURE)
8686         goto ignore;
8687
8688       if (gfc_array_dimen_size (expr2, i, &shape2[i]) == FAILURE)
8689         goto ignore;
8690
8691       if (mpz_cmp (shape[i], shape2[i]))
8692         goto over;
8693     }
8694
8695   /* When either of the two expression is an assumed size array, we
8696      ignore the comparison of dimension sizes.  */
8697 ignore:
8698   result = SUCCESS;
8699
8700 over:
8701   gfc_clear_shape (shape, i);
8702   gfc_clear_shape (shape2, i);
8703   return result;
8704 }
8705
8706
8707 /* Check whether a WHERE assignment target or a WHERE mask expression
8708    has the same shape as the outmost WHERE mask expression.  */
8709
8710 static void
8711 resolve_where (gfc_code *code, gfc_expr *mask)
8712 {
8713   gfc_code *cblock;
8714   gfc_code *cnext;
8715   gfc_expr *e = NULL;
8716
8717   cblock = code->block;
8718
8719   /* Store the first WHERE mask-expr of the WHERE statement or construct.
8720      In case of nested WHERE, only the outmost one is stored.  */
8721   if (mask == NULL) /* outmost WHERE */
8722     e = cblock->expr1;
8723   else /* inner WHERE */
8724     e = mask;
8725
8726   while (cblock)
8727     {
8728       if (cblock->expr1)
8729         {
8730           /* Check if the mask-expr has a consistent shape with the
8731              outmost WHERE mask-expr.  */
8732           if (resolve_where_shape (cblock->expr1, e) == FAILURE)
8733             gfc_error ("WHERE mask at %L has inconsistent shape",
8734                        &cblock->expr1->where);
8735          }
8736
8737       /* the assignment statement of a WHERE statement, or the first
8738          statement in where-body-construct of a WHERE construct */
8739       cnext = cblock->next;
8740       while (cnext)
8741         {
8742           switch (cnext->op)
8743             {
8744             /* WHERE assignment statement */
8745             case EXEC_ASSIGN:
8746
8747               /* Check shape consistent for WHERE assignment target.  */
8748               if (e && resolve_where_shape (cnext->expr1, e) == FAILURE)
8749                gfc_error ("WHERE assignment target at %L has "
8750                           "inconsistent shape", &cnext->expr1->where);
8751               break;
8752
8753   
8754             case EXEC_ASSIGN_CALL:
8755               resolve_call (cnext);
8756               if (!cnext->resolved_sym->attr.elemental)
8757                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
8758                           &cnext->ext.actual->expr->where);
8759               break;
8760
8761             /* WHERE or WHERE construct is part of a where-body-construct */
8762             case EXEC_WHERE:
8763               resolve_where (cnext, e);
8764               break;
8765
8766             default:
8767               gfc_error ("Unsupported statement inside WHERE at %L",
8768                          &cnext->loc);
8769             }
8770          /* the next statement within the same where-body-construct */
8771          cnext = cnext->next;
8772        }
8773     /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
8774     cblock = cblock->block;
8775   }
8776 }
8777
8778
8779 /* Resolve assignment in FORALL construct.
8780    NVAR is the number of FORALL index variables, and VAR_EXPR records the
8781    FORALL index variables.  */
8782
8783 static void
8784 gfc_resolve_assign_in_forall (gfc_code *code, int nvar, gfc_expr **var_expr)
8785 {
8786   int n;
8787
8788   for (n = 0; n < nvar; n++)
8789     {
8790       gfc_symbol *forall_index;
8791
8792       forall_index = var_expr[n]->symtree->n.sym;
8793
8794       /* Check whether the assignment target is one of the FORALL index
8795          variable.  */
8796       if ((code->expr1->expr_type == EXPR_VARIABLE)
8797           && (code->expr1->symtree->n.sym == forall_index))
8798         gfc_error ("Assignment to a FORALL index variable at %L",
8799                    &code->expr1->where);
8800       else
8801         {
8802           /* If one of the FORALL index variables doesn't appear in the
8803              assignment variable, then there could be a many-to-one
8804              assignment.  Emit a warning rather than an error because the
8805              mask could be resolving this problem.  */
8806           if (find_forall_index (code->expr1, forall_index, 0) == FAILURE)
8807             gfc_warning ("The FORALL with index '%s' is not used on the "
8808                          "left side of the assignment at %L and so might "
8809                          "cause multiple assignment to this object",
8810                          var_expr[n]->symtree->name, &code->expr1->where);
8811         }
8812     }
8813 }
8814
8815
8816 /* Resolve WHERE statement in FORALL construct.  */
8817
8818 static void
8819 gfc_resolve_where_code_in_forall (gfc_code *code, int nvar,
8820                                   gfc_expr **var_expr)
8821 {
8822   gfc_code *cblock;
8823   gfc_code *cnext;
8824
8825   cblock = code->block;
8826   while (cblock)
8827     {
8828       /* the assignment statement of a WHERE statement, or the first
8829          statement in where-body-construct of a WHERE construct */
8830       cnext = cblock->next;
8831       while (cnext)
8832         {
8833           switch (cnext->op)
8834             {
8835             /* WHERE assignment statement */
8836             case EXEC_ASSIGN:
8837               gfc_resolve_assign_in_forall (cnext, nvar, var_expr);
8838               break;
8839   
8840             /* WHERE operator assignment statement */
8841             case EXEC_ASSIGN_CALL:
8842               resolve_call (cnext);
8843               if (!cnext->resolved_sym->attr.elemental)
8844                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
8845                           &cnext->ext.actual->expr->where);
8846               break;
8847
8848             /* WHERE or WHERE construct is part of a where-body-construct */
8849             case EXEC_WHERE:
8850               gfc_resolve_where_code_in_forall (cnext, nvar, var_expr);
8851               break;
8852
8853             default:
8854               gfc_error ("Unsupported statement inside WHERE at %L",
8855                          &cnext->loc);
8856             }
8857           /* the next statement within the same where-body-construct */
8858           cnext = cnext->next;
8859         }
8860       /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
8861       cblock = cblock->block;
8862     }
8863 }
8864
8865
8866 /* Traverse the FORALL body to check whether the following errors exist:
8867    1. For assignment, check if a many-to-one assignment happens.
8868    2. For WHERE statement, check the WHERE body to see if there is any
8869       many-to-one assignment.  */
8870
8871 static void
8872 gfc_resolve_forall_body (gfc_code *code, int nvar, gfc_expr **var_expr)
8873 {
8874   gfc_code *c;
8875
8876   c = code->block->next;
8877   while (c)
8878     {
8879       switch (c->op)
8880         {
8881         case EXEC_ASSIGN:
8882         case EXEC_POINTER_ASSIGN:
8883           gfc_resolve_assign_in_forall (c, nvar, var_expr);
8884           break;
8885
8886         case EXEC_ASSIGN_CALL:
8887           resolve_call (c);
8888           break;
8889
8890         /* Because the gfc_resolve_blocks() will handle the nested FORALL,
8891            there is no need to handle it here.  */
8892         case EXEC_FORALL:
8893           break;
8894         case EXEC_WHERE:
8895           gfc_resolve_where_code_in_forall(c, nvar, var_expr);
8896           break;
8897         default:
8898           break;
8899         }
8900       /* The next statement in the FORALL body.  */
8901       c = c->next;
8902     }
8903 }
8904
8905
8906 /* Counts the number of iterators needed inside a forall construct, including
8907    nested forall constructs. This is used to allocate the needed memory 
8908    in gfc_resolve_forall.  */
8909
8910 static int 
8911 gfc_count_forall_iterators (gfc_code *code)
8912 {
8913   int max_iters, sub_iters, current_iters;
8914   gfc_forall_iterator *fa;
8915
8916   gcc_assert(code->op == EXEC_FORALL);
8917   max_iters = 0;
8918   current_iters = 0;
8919
8920   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
8921     current_iters ++;
8922   
8923   code = code->block->next;
8924
8925   while (code)
8926     {          
8927       if (code->op == EXEC_FORALL)
8928         {
8929           sub_iters = gfc_count_forall_iterators (code);
8930           if (sub_iters > max_iters)
8931             max_iters = sub_iters;
8932         }
8933       code = code->next;
8934     }
8935
8936   return current_iters + max_iters;
8937 }
8938
8939
8940 /* Given a FORALL construct, first resolve the FORALL iterator, then call
8941    gfc_resolve_forall_body to resolve the FORALL body.  */
8942
8943 static void
8944 gfc_resolve_forall (gfc_code *code, gfc_namespace *ns, int forall_save)
8945 {
8946   static gfc_expr **var_expr;
8947   static int total_var = 0;
8948   static int nvar = 0;
8949   int old_nvar, tmp;
8950   gfc_forall_iterator *fa;
8951   int i;
8952
8953   old_nvar = nvar;
8954
8955   /* Start to resolve a FORALL construct   */
8956   if (forall_save == 0)
8957     {
8958       /* Count the total number of FORALL index in the nested FORALL
8959          construct in order to allocate the VAR_EXPR with proper size.  */
8960       total_var = gfc_count_forall_iterators (code);
8961
8962       /* Allocate VAR_EXPR with NUMBER_OF_FORALL_INDEX elements.  */
8963       var_expr = XCNEWVEC (gfc_expr *, total_var);
8964     }
8965
8966   /* The information about FORALL iterator, including FORALL index start, end
8967      and stride. The FORALL index can not appear in start, end or stride.  */
8968   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
8969     {
8970       /* Check if any outer FORALL index name is the same as the current
8971          one.  */
8972       for (i = 0; i < nvar; i++)
8973         {
8974           if (fa->var->symtree->n.sym == var_expr[i]->symtree->n.sym)
8975             {
8976               gfc_error ("An outer FORALL construct already has an index "
8977                          "with this name %L", &fa->var->where);
8978             }
8979         }
8980
8981       /* Record the current FORALL index.  */
8982       var_expr[nvar] = gfc_copy_expr (fa->var);
8983
8984       nvar++;
8985
8986       /* No memory leak.  */
8987       gcc_assert (nvar <= total_var);
8988     }
8989
8990   /* Resolve the FORALL body.  */
8991   gfc_resolve_forall_body (code, nvar, var_expr);
8992
8993   /* May call gfc_resolve_forall to resolve the inner FORALL loop.  */
8994   gfc_resolve_blocks (code->block, ns);
8995
8996   tmp = nvar;
8997   nvar = old_nvar;
8998   /* Free only the VAR_EXPRs allocated in this frame.  */
8999   for (i = nvar; i < tmp; i++)
9000      gfc_free_expr (var_expr[i]);
9001
9002   if (nvar == 0)
9003     {
9004       /* We are in the outermost FORALL construct.  */
9005       gcc_assert (forall_save == 0);
9006
9007       /* VAR_EXPR is not needed any more.  */
9008       free (var_expr);
9009       total_var = 0;
9010     }
9011 }
9012
9013
9014 /* Resolve a BLOCK construct statement.  */
9015
9016 static void
9017 resolve_block_construct (gfc_code* code)
9018 {
9019   /* Resolve the BLOCK's namespace.  */
9020   gfc_resolve (code->ext.block.ns);
9021
9022   /* For an ASSOCIATE block, the associations (and their targets) are already
9023      resolved during resolve_symbol.  */
9024 }
9025
9026
9027 /* Resolve lists of blocks found in IF, SELECT CASE, WHERE, FORALL, GOTO and
9028    DO code nodes.  */
9029
9030 static void resolve_code (gfc_code *, gfc_namespace *);
9031
9032 void
9033 gfc_resolve_blocks (gfc_code *b, gfc_namespace *ns)
9034 {
9035   gfc_try t;
9036
9037   for (; b; b = b->block)
9038     {
9039       t = gfc_resolve_expr (b->expr1);
9040       if (gfc_resolve_expr (b->expr2) == FAILURE)
9041         t = FAILURE;
9042
9043       switch (b->op)
9044         {
9045         case EXEC_IF:
9046           if (t == SUCCESS && b->expr1 != NULL
9047               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank != 0))
9048             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
9049                        &b->expr1->where);
9050           break;
9051
9052         case EXEC_WHERE:
9053           if (t == SUCCESS
9054               && b->expr1 != NULL
9055               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank == 0))
9056             gfc_error ("WHERE/ELSEWHERE clause at %L requires a LOGICAL array",
9057                        &b->expr1->where);
9058           break;
9059
9060         case EXEC_GOTO:
9061           resolve_branch (b->label1, b);
9062           break;
9063
9064         case EXEC_BLOCK:
9065           resolve_block_construct (b);
9066           break;
9067
9068         case EXEC_SELECT:
9069         case EXEC_SELECT_TYPE:
9070         case EXEC_FORALL:
9071         case EXEC_DO:
9072         case EXEC_DO_WHILE:
9073         case EXEC_DO_CONCURRENT:
9074         case EXEC_CRITICAL:
9075         case EXEC_READ:
9076         case EXEC_WRITE:
9077         case EXEC_IOLENGTH:
9078         case EXEC_WAIT:
9079           break;
9080
9081         case EXEC_OMP_ATOMIC:
9082         case EXEC_OMP_CRITICAL:
9083         case EXEC_OMP_DO:
9084         case EXEC_OMP_MASTER:
9085         case EXEC_OMP_ORDERED:
9086         case EXEC_OMP_PARALLEL:
9087         case EXEC_OMP_PARALLEL_DO:
9088         case EXEC_OMP_PARALLEL_SECTIONS:
9089         case EXEC_OMP_PARALLEL_WORKSHARE:
9090         case EXEC_OMP_SECTIONS:
9091         case EXEC_OMP_SINGLE:
9092         case EXEC_OMP_TASK:
9093         case EXEC_OMP_TASKWAIT:
9094         case EXEC_OMP_TASKYIELD:
9095         case EXEC_OMP_WORKSHARE:
9096           break;
9097
9098         default:
9099           gfc_internal_error ("gfc_resolve_blocks(): Bad block type");
9100         }
9101
9102       resolve_code (b->next, ns);
9103     }
9104 }
9105
9106
9107 /* Does everything to resolve an ordinary assignment.  Returns true
9108    if this is an interface assignment.  */
9109 static bool
9110 resolve_ordinary_assign (gfc_code *code, gfc_namespace *ns)
9111 {
9112   bool rval = false;
9113   gfc_expr *lhs;
9114   gfc_expr *rhs;
9115   int llen = 0;
9116   int rlen = 0;
9117   int n;
9118   gfc_ref *ref;
9119
9120   if (gfc_extend_assign (code, ns) == SUCCESS)
9121     {
9122       gfc_expr** rhsptr;
9123
9124       if (code->op == EXEC_ASSIGN_CALL)
9125         {
9126           lhs = code->ext.actual->expr;
9127           rhsptr = &code->ext.actual->next->expr;
9128         }
9129       else
9130         {
9131           gfc_actual_arglist* args;
9132           gfc_typebound_proc* tbp;
9133
9134           gcc_assert (code->op == EXEC_COMPCALL);
9135
9136           args = code->expr1->value.compcall.actual;
9137           lhs = args->expr;
9138           rhsptr = &args->next->expr;
9139
9140           tbp = code->expr1->value.compcall.tbp;
9141           gcc_assert (!tbp->is_generic);
9142         }
9143
9144       /* Make a temporary rhs when there is a default initializer
9145          and rhs is the same symbol as the lhs.  */
9146       if ((*rhsptr)->expr_type == EXPR_VARIABLE
9147             && (*rhsptr)->symtree->n.sym->ts.type == BT_DERIVED
9148             && gfc_has_default_initializer ((*rhsptr)->symtree->n.sym->ts.u.derived)
9149             && (lhs->symtree->n.sym == (*rhsptr)->symtree->n.sym))
9150         *rhsptr = gfc_get_parentheses (*rhsptr);
9151
9152       return true;
9153     }
9154
9155   lhs = code->expr1;
9156   rhs = code->expr2;
9157
9158   if (rhs->is_boz
9159       && gfc_notify_std (GFC_STD_GNU, "Extension: BOZ literal at %L outside "
9160                          "a DATA statement and outside INT/REAL/DBLE/CMPLX",
9161                          &code->loc) == FAILURE)
9162     return false;
9163
9164   /* Handle the case of a BOZ literal on the RHS.  */
9165   if (rhs->is_boz && lhs->ts.type != BT_INTEGER)
9166     {
9167       int rc;
9168       if (gfc_option.warn_surprising)
9169         gfc_warning ("BOZ literal at %L is bitwise transferred "
9170                      "non-integer symbol '%s'", &code->loc,
9171                      lhs->symtree->n.sym->name);
9172
9173       if (!gfc_convert_boz (rhs, &lhs->ts))
9174         return false;
9175       if ((rc = gfc_range_check (rhs)) != ARITH_OK)
9176         {
9177           if (rc == ARITH_UNDERFLOW)
9178             gfc_error ("Arithmetic underflow of bit-wise transferred BOZ at %L"
9179                        ". This check can be disabled with the option "
9180                        "-fno-range-check", &rhs->where);
9181           else if (rc == ARITH_OVERFLOW)
9182             gfc_error ("Arithmetic overflow of bit-wise transferred BOZ at %L"
9183                        ". This check can be disabled with the option "
9184                        "-fno-range-check", &rhs->where);
9185           else if (rc == ARITH_NAN)
9186             gfc_error ("Arithmetic NaN of bit-wise transferred BOZ at %L"
9187                        ". This check can be disabled with the option "
9188                        "-fno-range-check", &rhs->where);
9189           return false;
9190         }
9191     }
9192
9193   if (lhs->ts.type == BT_CHARACTER
9194         && gfc_option.warn_character_truncation)
9195     {
9196       if (lhs->ts.u.cl != NULL
9197             && lhs->ts.u.cl->length != NULL
9198             && lhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
9199         llen = mpz_get_si (lhs->ts.u.cl->length->value.integer);
9200
9201       if (rhs->expr_type == EXPR_CONSTANT)
9202         rlen = rhs->value.character.length;
9203
9204       else if (rhs->ts.u.cl != NULL
9205                  && rhs->ts.u.cl->length != NULL
9206                  && rhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
9207         rlen = mpz_get_si (rhs->ts.u.cl->length->value.integer);
9208
9209       if (rlen && llen && rlen > llen)
9210         gfc_warning_now ("CHARACTER expression will be truncated "
9211                          "in assignment (%d/%d) at %L",
9212                          llen, rlen, &code->loc);
9213     }
9214
9215   /* Ensure that a vector index expression for the lvalue is evaluated
9216      to a temporary if the lvalue symbol is referenced in it.  */
9217   if (lhs->rank)
9218     {
9219       for (ref = lhs->ref; ref; ref= ref->next)
9220         if (ref->type == REF_ARRAY)
9221           {
9222             for (n = 0; n < ref->u.ar.dimen; n++)
9223               if (ref->u.ar.dimen_type[n] == DIMEN_VECTOR
9224                   && gfc_find_sym_in_expr (lhs->symtree->n.sym,
9225                                            ref->u.ar.start[n]))
9226                 ref->u.ar.start[n]
9227                         = gfc_get_parentheses (ref->u.ar.start[n]);
9228           }
9229     }
9230
9231   if (gfc_pure (NULL))
9232     {
9233       if (lhs->ts.type == BT_DERIVED
9234             && lhs->expr_type == EXPR_VARIABLE
9235             && lhs->ts.u.derived->attr.pointer_comp
9236             && rhs->expr_type == EXPR_VARIABLE
9237             && (gfc_impure_variable (rhs->symtree->n.sym)
9238                 || gfc_is_coindexed (rhs)))
9239         {
9240           /* F2008, C1283.  */
9241           if (gfc_is_coindexed (rhs))
9242             gfc_error ("Coindexed expression at %L is assigned to "
9243                         "a derived type variable with a POINTER "
9244                         "component in a PURE procedure",
9245                         &rhs->where);
9246           else
9247             gfc_error ("The impure variable at %L is assigned to "
9248                         "a derived type variable with a POINTER "
9249                         "component in a PURE procedure (12.6)",
9250                         &rhs->where);
9251           return rval;
9252         }
9253
9254       /* Fortran 2008, C1283.  */
9255       if (gfc_is_coindexed (lhs))
9256         {
9257           gfc_error ("Assignment to coindexed variable at %L in a PURE "
9258                      "procedure", &rhs->where);
9259           return rval;
9260         }
9261     }
9262
9263   if (gfc_implicit_pure (NULL))
9264     {
9265       if (lhs->expr_type == EXPR_VARIABLE
9266             && lhs->symtree->n.sym != gfc_current_ns->proc_name
9267             && lhs->symtree->n.sym->ns != gfc_current_ns)
9268         gfc_current_ns->proc_name->attr.implicit_pure = 0;
9269
9270       if (lhs->ts.type == BT_DERIVED
9271             && lhs->expr_type == EXPR_VARIABLE
9272             && lhs->ts.u.derived->attr.pointer_comp
9273             && rhs->expr_type == EXPR_VARIABLE
9274             && (gfc_impure_variable (rhs->symtree->n.sym)
9275                 || gfc_is_coindexed (rhs)))
9276         gfc_current_ns->proc_name->attr.implicit_pure = 0;
9277
9278       /* Fortran 2008, C1283.  */
9279       if (gfc_is_coindexed (lhs))
9280         gfc_current_ns->proc_name->attr.implicit_pure = 0;
9281     }
9282
9283   /* F03:7.4.1.2.  */
9284   /* FIXME: Valid in Fortran 2008, unless the LHS is both polymorphic
9285      and coindexed; cf. F2008, 7.2.1.2 and PR 43366.  */
9286   if (lhs->ts.type == BT_CLASS)
9287     {
9288       gfc_error ("Variable must not be polymorphic in intrinsic assignment at "
9289                  "%L - check that there is a matching specific subroutine "
9290                  "for '=' operator", &lhs->where);
9291       return false;
9292     }
9293
9294   /* F2008, Section 7.2.1.2.  */
9295   if (gfc_is_coindexed (lhs) && gfc_has_ultimate_allocatable (lhs))
9296     {
9297       gfc_error ("Coindexed variable must not be have an allocatable ultimate "
9298                  "component in assignment at %L", &lhs->where);
9299       return false;
9300     }
9301
9302   gfc_check_assign (lhs, rhs, 1);
9303   return false;
9304 }
9305
9306
9307 /* Given a block of code, recursively resolve everything pointed to by this
9308    code block.  */
9309
9310 static void
9311 resolve_code (gfc_code *code, gfc_namespace *ns)
9312 {
9313   int omp_workshare_save;
9314   int forall_save, do_concurrent_save;
9315   code_stack frame;
9316   gfc_try t;
9317
9318   frame.prev = cs_base;
9319   frame.head = code;
9320   cs_base = &frame;
9321
9322   find_reachable_labels (code);
9323
9324   for (; code; code = code->next)
9325     {
9326       frame.current = code;
9327       forall_save = forall_flag;
9328       do_concurrent_save = do_concurrent_flag;
9329
9330       if (code->op == EXEC_FORALL)
9331         {
9332           forall_flag = 1;
9333           gfc_resolve_forall (code, ns, forall_save);
9334           forall_flag = 2;
9335         }
9336       else if (code->block)
9337         {
9338           omp_workshare_save = -1;
9339           switch (code->op)
9340             {
9341             case EXEC_OMP_PARALLEL_WORKSHARE:
9342               omp_workshare_save = omp_workshare_flag;
9343               omp_workshare_flag = 1;
9344               gfc_resolve_omp_parallel_blocks (code, ns);
9345               break;
9346             case EXEC_OMP_PARALLEL:
9347             case EXEC_OMP_PARALLEL_DO:
9348             case EXEC_OMP_PARALLEL_SECTIONS:
9349             case EXEC_OMP_TASK:
9350               omp_workshare_save = omp_workshare_flag;
9351               omp_workshare_flag = 0;
9352               gfc_resolve_omp_parallel_blocks (code, ns);
9353               break;
9354             case EXEC_OMP_DO:
9355               gfc_resolve_omp_do_blocks (code, ns);
9356               break;
9357             case EXEC_SELECT_TYPE:
9358               /* Blocks are handled in resolve_select_type because we have
9359                  to transform the SELECT TYPE into ASSOCIATE first.  */
9360               break;
9361             case EXEC_DO_CONCURRENT:
9362               do_concurrent_flag = 1;
9363               gfc_resolve_blocks (code->block, ns);
9364               do_concurrent_flag = 2;
9365               break;
9366             case EXEC_OMP_WORKSHARE:
9367               omp_workshare_save = omp_workshare_flag;
9368               omp_workshare_flag = 1;
9369               /* FALL THROUGH */
9370             default:
9371               gfc_resolve_blocks (code->block, ns);
9372               break;
9373             }
9374
9375           if (omp_workshare_save != -1)
9376             omp_workshare_flag = omp_workshare_save;
9377         }
9378
9379       t = SUCCESS;
9380       if (code->op != EXEC_COMPCALL && code->op != EXEC_CALL_PPC)
9381         t = gfc_resolve_expr (code->expr1);
9382       forall_flag = forall_save;
9383       do_concurrent_flag = do_concurrent_save;
9384
9385       if (gfc_resolve_expr (code->expr2) == FAILURE)
9386         t = FAILURE;
9387
9388       if (code->op == EXEC_ALLOCATE
9389           && gfc_resolve_expr (code->expr3) == FAILURE)
9390         t = FAILURE;
9391
9392       switch (code->op)
9393         {
9394         case EXEC_NOP:
9395         case EXEC_END_BLOCK:
9396         case EXEC_END_NESTED_BLOCK:
9397         case EXEC_CYCLE:
9398         case EXEC_PAUSE:
9399         case EXEC_STOP:
9400         case EXEC_ERROR_STOP:
9401         case EXEC_EXIT:
9402         case EXEC_CONTINUE:
9403         case EXEC_DT_END:
9404         case EXEC_ASSIGN_CALL:
9405         case EXEC_CRITICAL:
9406           break;
9407
9408         case EXEC_SYNC_ALL:
9409         case EXEC_SYNC_IMAGES:
9410         case EXEC_SYNC_MEMORY:
9411           resolve_sync (code);
9412           break;
9413
9414         case EXEC_LOCK:
9415         case EXEC_UNLOCK:
9416           resolve_lock_unlock (code);
9417           break;
9418
9419         case EXEC_ENTRY:
9420           /* Keep track of which entry we are up to.  */
9421           current_entry_id = code->ext.entry->id;
9422           break;
9423
9424         case EXEC_WHERE:
9425           resolve_where (code, NULL);
9426           break;
9427
9428         case EXEC_GOTO:
9429           if (code->expr1 != NULL)
9430             {
9431               if (code->expr1->ts.type != BT_INTEGER)
9432                 gfc_error ("ASSIGNED GOTO statement at %L requires an "
9433                            "INTEGER variable", &code->expr1->where);
9434               else if (code->expr1->symtree->n.sym->attr.assign != 1)
9435                 gfc_error ("Variable '%s' has not been assigned a target "
9436                            "label at %L", code->expr1->symtree->n.sym->name,
9437                            &code->expr1->where);
9438             }
9439           else
9440             resolve_branch (code->label1, code);
9441           break;
9442
9443         case EXEC_RETURN:
9444           if (code->expr1 != NULL
9445                 && (code->expr1->ts.type != BT_INTEGER || code->expr1->rank))
9446             gfc_error ("Alternate RETURN statement at %L requires a SCALAR-"
9447                        "INTEGER return specifier", &code->expr1->where);
9448           break;
9449
9450         case EXEC_INIT_ASSIGN:
9451         case EXEC_END_PROCEDURE:
9452           break;
9453
9454         case EXEC_ASSIGN:
9455           if (t == FAILURE)
9456             break;
9457
9458           if (gfc_check_vardef_context (code->expr1, false, false,
9459                                         _("assignment")) == FAILURE)
9460             break;
9461
9462           if (resolve_ordinary_assign (code, ns))
9463             {
9464               if (code->op == EXEC_COMPCALL)
9465                 goto compcall;
9466               else
9467                 goto call;
9468             }
9469           break;
9470
9471         case EXEC_LABEL_ASSIGN:
9472           if (code->label1->defined == ST_LABEL_UNKNOWN)
9473             gfc_error ("Label %d referenced at %L is never defined",
9474                        code->label1->value, &code->label1->where);
9475           if (t == SUCCESS
9476               && (code->expr1->expr_type != EXPR_VARIABLE
9477                   || code->expr1->symtree->n.sym->ts.type != BT_INTEGER
9478                   || code->expr1->symtree->n.sym->ts.kind
9479                      != gfc_default_integer_kind
9480                   || code->expr1->symtree->n.sym->as != NULL))
9481             gfc_error ("ASSIGN statement at %L requires a scalar "
9482                        "default INTEGER variable", &code->expr1->where);
9483           break;
9484
9485         case EXEC_POINTER_ASSIGN:
9486           {
9487             gfc_expr* e;
9488
9489             if (t == FAILURE)
9490               break;
9491
9492             /* This is both a variable definition and pointer assignment
9493                context, so check both of them.  For rank remapping, a final
9494                array ref may be present on the LHS and fool gfc_expr_attr
9495                used in gfc_check_vardef_context.  Remove it.  */
9496             e = remove_last_array_ref (code->expr1);
9497             t = gfc_check_vardef_context (e, true, false,
9498                                           _("pointer assignment"));
9499             if (t == SUCCESS)
9500               t = gfc_check_vardef_context (e, false, false,
9501                                             _("pointer assignment"));
9502             gfc_free_expr (e);
9503             if (t == FAILURE)
9504               break;
9505
9506             gfc_check_pointer_assign (code->expr1, code->expr2);
9507             break;
9508           }
9509
9510         case EXEC_ARITHMETIC_IF:
9511           if (t == SUCCESS
9512               && code->expr1->ts.type != BT_INTEGER
9513               && code->expr1->ts.type != BT_REAL)
9514             gfc_error ("Arithmetic IF statement at %L requires a numeric "
9515                        "expression", &code->expr1->where);
9516
9517           resolve_branch (code->label1, code);
9518           resolve_branch (code->label2, code);
9519           resolve_branch (code->label3, code);
9520           break;
9521
9522         case EXEC_IF:
9523           if (t == SUCCESS && code->expr1 != NULL
9524               && (code->expr1->ts.type != BT_LOGICAL
9525                   || code->expr1->rank != 0))
9526             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
9527                        &code->expr1->where);
9528           break;
9529
9530         case EXEC_CALL:
9531         call:
9532           resolve_call (code);
9533           break;
9534
9535         case EXEC_COMPCALL:
9536         compcall:
9537           resolve_typebound_subroutine (code);
9538           break;
9539
9540         case EXEC_CALL_PPC:
9541           resolve_ppc_call (code);
9542           break;
9543
9544         case EXEC_SELECT:
9545           /* Select is complicated. Also, a SELECT construct could be
9546              a transformed computed GOTO.  */
9547           resolve_select (code);
9548           break;
9549
9550         case EXEC_SELECT_TYPE:
9551           resolve_select_type (code, ns);
9552           break;
9553
9554         case EXEC_BLOCK:
9555           resolve_block_construct (code);
9556           break;
9557
9558         case EXEC_DO:
9559           if (code->ext.iterator != NULL)
9560             {
9561               gfc_iterator *iter = code->ext.iterator;
9562               if (gfc_resolve_iterator (iter, true) != FAILURE)
9563                 gfc_resolve_do_iterator (code, iter->var->symtree->n.sym);
9564             }
9565           break;
9566
9567         case EXEC_DO_WHILE:
9568           if (code->expr1 == NULL)
9569             gfc_internal_error ("resolve_code(): No expression on DO WHILE");
9570           if (t == SUCCESS
9571               && (code->expr1->rank != 0
9572                   || code->expr1->ts.type != BT_LOGICAL))
9573             gfc_error ("Exit condition of DO WHILE loop at %L must be "
9574                        "a scalar LOGICAL expression", &code->expr1->where);
9575           break;
9576
9577         case EXEC_ALLOCATE:
9578           if (t == SUCCESS)
9579             resolve_allocate_deallocate (code, "ALLOCATE");
9580
9581           break;
9582
9583         case EXEC_DEALLOCATE:
9584           if (t == SUCCESS)
9585             resolve_allocate_deallocate (code, "DEALLOCATE");
9586
9587           break;
9588
9589         case EXEC_OPEN:
9590           if (gfc_resolve_open (code->ext.open) == FAILURE)
9591             break;
9592
9593           resolve_branch (code->ext.open->err, code);
9594           break;
9595
9596         case EXEC_CLOSE:
9597           if (gfc_resolve_close (code->ext.close) == FAILURE)
9598             break;
9599
9600           resolve_branch (code->ext.close->err, code);
9601           break;
9602
9603         case EXEC_BACKSPACE:
9604         case EXEC_ENDFILE:
9605         case EXEC_REWIND:
9606         case EXEC_FLUSH:
9607           if (gfc_resolve_filepos (code->ext.filepos) == FAILURE)
9608             break;
9609
9610           resolve_branch (code->ext.filepos->err, code);
9611           break;
9612
9613         case EXEC_INQUIRE:
9614           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
9615               break;
9616
9617           resolve_branch (code->ext.inquire->err, code);
9618           break;
9619
9620         case EXEC_IOLENGTH:
9621           gcc_assert (code->ext.inquire != NULL);
9622           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
9623             break;
9624
9625           resolve_branch (code->ext.inquire->err, code);
9626           break;
9627
9628         case EXEC_WAIT:
9629           if (gfc_resolve_wait (code->ext.wait) == FAILURE)
9630             break;
9631
9632           resolve_branch (code->ext.wait->err, code);
9633           resolve_branch (code->ext.wait->end, code);
9634           resolve_branch (code->ext.wait->eor, code);
9635           break;
9636
9637         case EXEC_READ:
9638         case EXEC_WRITE:
9639           if (gfc_resolve_dt (code->ext.dt, &code->loc) == FAILURE)
9640             break;
9641
9642           resolve_branch (code->ext.dt->err, code);
9643           resolve_branch (code->ext.dt->end, code);
9644           resolve_branch (code->ext.dt->eor, code);
9645           break;
9646
9647         case EXEC_TRANSFER:
9648           resolve_transfer (code);
9649           break;
9650
9651         case EXEC_DO_CONCURRENT:
9652         case EXEC_FORALL:
9653           resolve_forall_iterators (code->ext.forall_iterator);
9654
9655           if (code->expr1 != NULL
9656               && (code->expr1->ts.type != BT_LOGICAL || code->expr1->rank))
9657             gfc_error ("FORALL mask clause at %L requires a scalar LOGICAL "
9658                        "expression", &code->expr1->where);
9659           break;
9660
9661         case EXEC_OMP_ATOMIC:
9662         case EXEC_OMP_BARRIER:
9663         case EXEC_OMP_CRITICAL:
9664         case EXEC_OMP_FLUSH:
9665         case EXEC_OMP_DO:
9666         case EXEC_OMP_MASTER:
9667         case EXEC_OMP_ORDERED:
9668         case EXEC_OMP_SECTIONS:
9669         case EXEC_OMP_SINGLE:
9670         case EXEC_OMP_TASKWAIT:
9671         case EXEC_OMP_TASKYIELD:
9672         case EXEC_OMP_WORKSHARE:
9673           gfc_resolve_omp_directive (code, ns);
9674           break;
9675
9676         case EXEC_OMP_PARALLEL:
9677         case EXEC_OMP_PARALLEL_DO:
9678         case EXEC_OMP_PARALLEL_SECTIONS:
9679         case EXEC_OMP_PARALLEL_WORKSHARE:
9680         case EXEC_OMP_TASK:
9681           omp_workshare_save = omp_workshare_flag;
9682           omp_workshare_flag = 0;
9683           gfc_resolve_omp_directive (code, ns);
9684           omp_workshare_flag = omp_workshare_save;
9685           break;
9686
9687         default:
9688           gfc_internal_error ("resolve_code(): Bad statement code");
9689         }
9690     }
9691
9692   cs_base = frame.prev;
9693 }
9694
9695
9696 /* Resolve initial values and make sure they are compatible with
9697    the variable.  */
9698
9699 static void
9700 resolve_values (gfc_symbol *sym)
9701 {
9702   gfc_try t;
9703
9704   if (sym->value == NULL)
9705     return;
9706
9707   if (sym->value->expr_type == EXPR_STRUCTURE)
9708     t= resolve_structure_cons (sym->value, 1);
9709   else 
9710     t = gfc_resolve_expr (sym->value);
9711
9712   if (t == FAILURE)
9713     return;
9714
9715   gfc_check_assign_symbol (sym, sym->value);
9716 }
9717
9718
9719 /* Verify the binding labels for common blocks that are BIND(C).  The label
9720    for a BIND(C) common block must be identical in all scoping units in which
9721    the common block is declared.  Further, the binding label can not collide
9722    with any other global entity in the program.  */
9723
9724 static void
9725 resolve_bind_c_comms (gfc_symtree *comm_block_tree)
9726 {
9727   if (comm_block_tree->n.common->is_bind_c == 1)
9728     {
9729       gfc_gsymbol *binding_label_gsym;
9730       gfc_gsymbol *comm_name_gsym;
9731       const char * bind_label = comm_block_tree->n.common->binding_label 
9732         ? comm_block_tree->n.common->binding_label : "";
9733
9734       /* See if a global symbol exists by the common block's name.  It may
9735          be NULL if the common block is use-associated.  */
9736       comm_name_gsym = gfc_find_gsymbol (gfc_gsym_root,
9737                                          comm_block_tree->n.common->name);
9738       if (comm_name_gsym != NULL && comm_name_gsym->type != GSYM_COMMON)
9739         gfc_error ("Binding label '%s' for common block '%s' at %L collides "
9740                    "with the global entity '%s' at %L",
9741                    bind_label,
9742                    comm_block_tree->n.common->name,
9743                    &(comm_block_tree->n.common->where),
9744                    comm_name_gsym->name, &(comm_name_gsym->where));
9745       else if (comm_name_gsym != NULL
9746                && strcmp (comm_name_gsym->name,
9747                           comm_block_tree->n.common->name) == 0)
9748         {
9749           /* TODO: Need to make sure the fields of gfc_gsymbol are initialized
9750              as expected.  */
9751           if (comm_name_gsym->binding_label == NULL)
9752             /* No binding label for common block stored yet; save this one.  */
9753             comm_name_gsym->binding_label = bind_label;
9754           else if (strcmp (comm_name_gsym->binding_label, bind_label) != 0)
9755               {
9756                 /* Common block names match but binding labels do not.  */
9757                 gfc_error ("Binding label '%s' for common block '%s' at %L "
9758                            "does not match the binding label '%s' for common "
9759                            "block '%s' at %L",
9760                            bind_label,
9761                            comm_block_tree->n.common->name,
9762                            &(comm_block_tree->n.common->where),
9763                            comm_name_gsym->binding_label,
9764                            comm_name_gsym->name,
9765                            &(comm_name_gsym->where));
9766                 return;
9767               }
9768         }
9769
9770       /* There is no binding label (NAME="") so we have nothing further to
9771          check and nothing to add as a global symbol for the label.  */
9772       if (!comm_block_tree->n.common->binding_label)
9773         return;
9774       
9775       binding_label_gsym =
9776         gfc_find_gsymbol (gfc_gsym_root,
9777                           comm_block_tree->n.common->binding_label);
9778       if (binding_label_gsym == NULL)
9779         {
9780           /* Need to make a global symbol for the binding label to prevent
9781              it from colliding with another.  */
9782           binding_label_gsym =
9783             gfc_get_gsymbol (comm_block_tree->n.common->binding_label);
9784           binding_label_gsym->sym_name = comm_block_tree->n.common->name;
9785           binding_label_gsym->type = GSYM_COMMON;
9786         }
9787       else
9788         {
9789           /* If comm_name_gsym is NULL, the name common block is use
9790              associated and the name could be colliding.  */
9791           if (binding_label_gsym->type != GSYM_COMMON)
9792             gfc_error ("Binding label '%s' for common block '%s' at %L "
9793                        "collides with the global entity '%s' at %L",
9794                        comm_block_tree->n.common->binding_label,
9795                        comm_block_tree->n.common->name,
9796                        &(comm_block_tree->n.common->where),
9797                        binding_label_gsym->name,
9798                        &(binding_label_gsym->where));
9799           else if (comm_name_gsym != NULL
9800                    && (strcmp (binding_label_gsym->name,
9801                                comm_name_gsym->binding_label) != 0)
9802                    && (strcmp (binding_label_gsym->sym_name,
9803                                comm_name_gsym->name) != 0))
9804             gfc_error ("Binding label '%s' for common block '%s' at %L "
9805                        "collides with global entity '%s' at %L",
9806                        binding_label_gsym->name, binding_label_gsym->sym_name,
9807                        &(comm_block_tree->n.common->where),
9808                        comm_name_gsym->name, &(comm_name_gsym->where));
9809         }
9810     }
9811   
9812   return;
9813 }
9814
9815
9816 /* Verify any BIND(C) derived types in the namespace so we can report errors
9817    for them once, rather than for each variable declared of that type.  */
9818
9819 static void
9820 resolve_bind_c_derived_types (gfc_symbol *derived_sym)
9821 {
9822   if (derived_sym != NULL && derived_sym->attr.flavor == FL_DERIVED
9823       && derived_sym->attr.is_bind_c == 1)
9824     verify_bind_c_derived_type (derived_sym);
9825   
9826   return;
9827 }
9828
9829
9830 /* Verify that any binding labels used in a given namespace do not collide 
9831    with the names or binding labels of any global symbols.  */
9832
9833 static void
9834 gfc_verify_binding_labels (gfc_symbol *sym)
9835 {
9836   int has_error = 0;
9837   
9838   if (sym != NULL && sym->attr.is_bind_c && sym->attr.is_iso_c == 0 
9839       && sym->attr.flavor != FL_DERIVED && sym->binding_label)
9840     {
9841       gfc_gsymbol *bind_c_sym;
9842
9843       bind_c_sym = gfc_find_gsymbol (gfc_gsym_root, sym->binding_label);
9844       if (bind_c_sym != NULL 
9845           && strcmp (bind_c_sym->name, sym->binding_label) == 0)
9846         {
9847           if (sym->attr.if_source == IFSRC_DECL 
9848               && (bind_c_sym->type != GSYM_SUBROUTINE 
9849                   && bind_c_sym->type != GSYM_FUNCTION) 
9850               && ((sym->attr.contained == 1 
9851                    && strcmp (bind_c_sym->sym_name, sym->name) != 0) 
9852                   || (sym->attr.use_assoc == 1 
9853                       && (strcmp (bind_c_sym->mod_name, sym->module) != 0))))
9854             {
9855               /* Make sure global procedures don't collide with anything.  */
9856               gfc_error ("Binding label '%s' at %L collides with the global "
9857                          "entity '%s' at %L", sym->binding_label,
9858                          &(sym->declared_at), bind_c_sym->name,
9859                          &(bind_c_sym->where));
9860               has_error = 1;
9861             }
9862           else if (sym->attr.contained == 0 
9863                    && (sym->attr.if_source == IFSRC_IFBODY 
9864                        && sym->attr.flavor == FL_PROCEDURE) 
9865                    && (bind_c_sym->sym_name != NULL 
9866                        && strcmp (bind_c_sym->sym_name, sym->name) != 0))
9867             {
9868               /* Make sure procedures in interface bodies don't collide.  */
9869               gfc_error ("Binding label '%s' in interface body at %L collides "
9870                          "with the global entity '%s' at %L",
9871                          sym->binding_label,
9872                          &(sym->declared_at), bind_c_sym->name,
9873                          &(bind_c_sym->where));
9874               has_error = 1;
9875             }
9876           else if (sym->attr.contained == 0 
9877                    && sym->attr.if_source == IFSRC_UNKNOWN)
9878             if ((sym->attr.use_assoc && bind_c_sym->mod_name
9879                  && strcmp (bind_c_sym->mod_name, sym->module) != 0) 
9880                 || sym->attr.use_assoc == 0)
9881               {
9882                 gfc_error ("Binding label '%s' at %L collides with global "
9883                            "entity '%s' at %L", sym->binding_label,
9884                            &(sym->declared_at), bind_c_sym->name,
9885                            &(bind_c_sym->where));
9886                 has_error = 1;
9887               }
9888
9889           if (has_error != 0)
9890             /* Clear the binding label to prevent checking multiple times.  */
9891             sym->binding_label = NULL;
9892         }
9893       else if (bind_c_sym == NULL)
9894         {
9895           bind_c_sym = gfc_get_gsymbol (sym->binding_label);
9896           bind_c_sym->where = sym->declared_at;
9897           bind_c_sym->sym_name = sym->name;
9898
9899           if (sym->attr.use_assoc == 1)
9900             bind_c_sym->mod_name = sym->module;
9901           else
9902             if (sym->ns->proc_name != NULL)
9903               bind_c_sym->mod_name = sym->ns->proc_name->name;
9904
9905           if (sym->attr.contained == 0)
9906             {
9907               if (sym->attr.subroutine)
9908                 bind_c_sym->type = GSYM_SUBROUTINE;
9909               else if (sym->attr.function)
9910                 bind_c_sym->type = GSYM_FUNCTION;
9911             }
9912         }
9913     }
9914   return;
9915 }
9916
9917
9918 /* Resolve an index expression.  */
9919
9920 static gfc_try
9921 resolve_index_expr (gfc_expr *e)
9922 {
9923   if (gfc_resolve_expr (e) == FAILURE)
9924     return FAILURE;
9925
9926   if (gfc_simplify_expr (e, 0) == FAILURE)
9927     return FAILURE;
9928
9929   if (gfc_specification_expr (e) == FAILURE)
9930     return FAILURE;
9931
9932   return SUCCESS;
9933 }
9934
9935
9936 /* Resolve a charlen structure.  */
9937
9938 static gfc_try
9939 resolve_charlen (gfc_charlen *cl)
9940 {
9941   int i, k;
9942
9943   if (cl->resolved)
9944     return SUCCESS;
9945
9946   cl->resolved = 1;
9947
9948
9949   if (cl->length_from_typespec)
9950     {
9951       if (gfc_resolve_expr (cl->length) == FAILURE)
9952         return FAILURE;
9953
9954       if (gfc_simplify_expr (cl->length, 0) == FAILURE)
9955         return FAILURE;
9956     }
9957   else
9958     {
9959       specification_expr = 1;
9960
9961       if (resolve_index_expr (cl->length) == FAILURE)
9962         {
9963           specification_expr = 0;
9964           return FAILURE;
9965         }
9966     }
9967
9968   /* "If the character length parameter value evaluates to a negative
9969      value, the length of character entities declared is zero."  */
9970   if (cl->length && !gfc_extract_int (cl->length, &i) && i < 0)
9971     {
9972       if (gfc_option.warn_surprising)
9973         gfc_warning_now ("CHARACTER variable at %L has negative length %d,"
9974                          " the length has been set to zero",
9975                          &cl->length->where, i);
9976       gfc_replace_expr (cl->length,
9977                         gfc_get_int_expr (gfc_default_integer_kind, NULL, 0));
9978     }
9979
9980   /* Check that the character length is not too large.  */
9981   k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
9982   if (cl->length && cl->length->expr_type == EXPR_CONSTANT
9983       && cl->length->ts.type == BT_INTEGER
9984       && mpz_cmp (cl->length->value.integer, gfc_integer_kinds[k].huge) > 0)
9985     {
9986       gfc_error ("String length at %L is too large", &cl->length->where);
9987       return FAILURE;
9988     }
9989
9990   return SUCCESS;
9991 }
9992
9993
9994 /* Test for non-constant shape arrays.  */
9995
9996 static bool
9997 is_non_constant_shape_array (gfc_symbol *sym)
9998 {
9999   gfc_expr *e;
10000   int i;
10001   bool not_constant;
10002
10003   not_constant = false;
10004   if (sym->as != NULL)
10005     {
10006       /* Unfortunately, !gfc_is_compile_time_shape hits a legal case that
10007          has not been simplified; parameter array references.  Do the
10008          simplification now.  */
10009       for (i = 0; i < sym->as->rank + sym->as->corank; i++)
10010         {
10011           e = sym->as->lower[i];
10012           if (e && (resolve_index_expr (e) == FAILURE
10013                     || !gfc_is_constant_expr (e)))
10014             not_constant = true;
10015           e = sym->as->upper[i];
10016           if (e && (resolve_index_expr (e) == FAILURE
10017                     || !gfc_is_constant_expr (e)))
10018             not_constant = true;
10019         }
10020     }
10021   return not_constant;
10022 }
10023
10024 /* Given a symbol and an initialization expression, add code to initialize
10025    the symbol to the function entry.  */
10026 static void
10027 build_init_assign (gfc_symbol *sym, gfc_expr *init)
10028 {
10029   gfc_expr *lval;
10030   gfc_code *init_st;
10031   gfc_namespace *ns = sym->ns;
10032
10033   /* Search for the function namespace if this is a contained
10034      function without an explicit result.  */
10035   if (sym->attr.function && sym == sym->result
10036       && sym->name != sym->ns->proc_name->name)
10037     {
10038       ns = ns->contained;
10039       for (;ns; ns = ns->sibling)
10040         if (strcmp (ns->proc_name->name, sym->name) == 0)
10041           break;
10042     }
10043
10044   if (ns == NULL)
10045     {
10046       gfc_free_expr (init);
10047       return;
10048     }
10049
10050   /* Build an l-value expression for the result.  */
10051   lval = gfc_lval_expr_from_sym (sym);
10052
10053   /* Add the code at scope entry.  */
10054   init_st = gfc_get_code ();
10055   init_st->next = ns->code;
10056   ns->code = init_st;
10057
10058   /* Assign the default initializer to the l-value.  */
10059   init_st->loc = sym->declared_at;
10060   init_st->op = EXEC_INIT_ASSIGN;
10061   init_st->expr1 = lval;
10062   init_st->expr2 = init;
10063 }
10064
10065 /* Assign the default initializer to a derived type variable or result.  */
10066
10067 static void
10068 apply_default_init (gfc_symbol *sym)
10069 {
10070   gfc_expr *init = NULL;
10071
10072   if (sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
10073     return;
10074
10075   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived)
10076     init = gfc_default_initializer (&sym->ts);
10077
10078   if (init == NULL && sym->ts.type != BT_CLASS)
10079     return;
10080
10081   build_init_assign (sym, init);
10082   sym->attr.referenced = 1;
10083 }
10084
10085 /* Build an initializer for a local integer, real, complex, logical, or
10086    character variable, based on the command line flags finit-local-zero,
10087    finit-integer=, finit-real=, finit-logical=, and finit-runtime.  Returns 
10088    null if the symbol should not have a default initialization.  */
10089 static gfc_expr *
10090 build_default_init_expr (gfc_symbol *sym)
10091 {
10092   int char_len;
10093   gfc_expr *init_expr;
10094   int i;
10095
10096   /* These symbols should never have a default initialization.  */
10097   if (sym->attr.allocatable
10098       || sym->attr.external
10099       || sym->attr.dummy
10100       || sym->attr.pointer
10101       || sym->attr.in_equivalence
10102       || sym->attr.in_common
10103       || sym->attr.data
10104       || sym->module
10105       || sym->attr.cray_pointee
10106       || sym->attr.cray_pointer
10107       || sym->assoc)
10108     return NULL;
10109
10110   /* Now we'll try to build an initializer expression.  */
10111   init_expr = gfc_get_constant_expr (sym->ts.type, sym->ts.kind,
10112                                      &sym->declared_at);
10113
10114   /* We will only initialize integers, reals, complex, logicals, and
10115      characters, and only if the corresponding command-line flags
10116      were set.  Otherwise, we free init_expr and return null.  */
10117   switch (sym->ts.type)
10118     {    
10119     case BT_INTEGER:
10120       if (gfc_option.flag_init_integer != GFC_INIT_INTEGER_OFF)
10121         mpz_set_si (init_expr->value.integer, 
10122                          gfc_option.flag_init_integer_value);
10123       else
10124         {
10125           gfc_free_expr (init_expr);
10126           init_expr = NULL;
10127         }
10128       break;
10129
10130     case BT_REAL:
10131       switch (gfc_option.flag_init_real)
10132         {
10133         case GFC_INIT_REAL_SNAN:
10134           init_expr->is_snan = 1;
10135           /* Fall through.  */
10136         case GFC_INIT_REAL_NAN:
10137           mpfr_set_nan (init_expr->value.real);
10138           break;
10139
10140         case GFC_INIT_REAL_INF:
10141           mpfr_set_inf (init_expr->value.real, 1);
10142           break;
10143
10144         case GFC_INIT_REAL_NEG_INF:
10145           mpfr_set_inf (init_expr->value.real, -1);
10146           break;
10147
10148         case GFC_INIT_REAL_ZERO:
10149           mpfr_set_ui (init_expr->value.real, 0.0, GFC_RND_MODE);
10150           break;
10151
10152         default:
10153           gfc_free_expr (init_expr);
10154           init_expr = NULL;
10155           break;
10156         }
10157       break;
10158           
10159     case BT_COMPLEX:
10160       switch (gfc_option.flag_init_real)
10161         {
10162         case GFC_INIT_REAL_SNAN:
10163           init_expr->is_snan = 1;
10164           /* Fall through.  */
10165         case GFC_INIT_REAL_NAN:
10166           mpfr_set_nan (mpc_realref (init_expr->value.complex));
10167           mpfr_set_nan (mpc_imagref (init_expr->value.complex));
10168           break;
10169
10170         case GFC_INIT_REAL_INF:
10171           mpfr_set_inf (mpc_realref (init_expr->value.complex), 1);
10172           mpfr_set_inf (mpc_imagref (init_expr->value.complex), 1);
10173           break;
10174
10175         case GFC_INIT_REAL_NEG_INF:
10176           mpfr_set_inf (mpc_realref (init_expr->value.complex), -1);
10177           mpfr_set_inf (mpc_imagref (init_expr->value.complex), -1);
10178           break;
10179
10180         case GFC_INIT_REAL_ZERO:
10181           mpc_set_ui (init_expr->value.complex, 0, GFC_MPC_RND_MODE);
10182           break;
10183
10184         default:
10185           gfc_free_expr (init_expr);
10186           init_expr = NULL;
10187           break;
10188         }
10189       break;
10190           
10191     case BT_LOGICAL:
10192       if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_FALSE)
10193         init_expr->value.logical = 0;
10194       else if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_TRUE)
10195         init_expr->value.logical = 1;
10196       else
10197         {
10198           gfc_free_expr (init_expr);
10199           init_expr = NULL;
10200         }
10201       break;
10202           
10203     case BT_CHARACTER:
10204       /* For characters, the length must be constant in order to 
10205          create a default initializer.  */
10206       if (gfc_option.flag_init_character == GFC_INIT_CHARACTER_ON
10207           && sym->ts.u.cl->length
10208           && sym->ts.u.cl->length->expr_type == EXPR_CONSTANT)
10209         {
10210           char_len = mpz_get_si (sym->ts.u.cl->length->value.integer);
10211           init_expr->value.character.length = char_len;
10212           init_expr->value.character.string = gfc_get_wide_string (char_len+1);
10213           for (i = 0; i < char_len; i++)
10214             init_expr->value.character.string[i]
10215               = (unsigned char) gfc_option.flag_init_character_value;
10216         }
10217       else
10218         {
10219           gfc_free_expr (init_expr);
10220           init_expr = NULL;
10221         }
10222       if (!init_expr && gfc_option.flag_init_character == GFC_INIT_CHARACTER_ON
10223           && sym->ts.u.cl->length)
10224         {
10225           gfc_actual_arglist *arg;
10226           init_expr = gfc_get_expr ();
10227           init_expr->where = sym->declared_at;
10228           init_expr->ts = sym->ts;
10229           init_expr->expr_type = EXPR_FUNCTION;
10230           init_expr->value.function.isym =
10231                 gfc_intrinsic_function_by_id (GFC_ISYM_REPEAT);
10232           init_expr->value.function.name = "repeat";
10233           arg = gfc_get_actual_arglist ();
10234           arg->expr = gfc_get_character_expr (sym->ts.kind, &sym->declared_at,
10235                                               NULL, 1);
10236           arg->expr->value.character.string[0]
10237                 = gfc_option.flag_init_character_value;
10238           arg->next = gfc_get_actual_arglist ();
10239           arg->next->expr = gfc_copy_expr (sym->ts.u.cl->length);
10240           init_expr->value.function.actual = arg;
10241         }
10242       break;
10243           
10244     default:
10245      gfc_free_expr (init_expr);
10246      init_expr = NULL;
10247     }
10248   return init_expr;
10249 }
10250
10251 /* Add an initialization expression to a local variable.  */
10252 static void
10253 apply_default_init_local (gfc_symbol *sym)
10254 {
10255   gfc_expr *init = NULL;
10256
10257   /* The symbol should be a variable or a function return value.  */
10258   if ((sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
10259       || (sym->attr.function && sym->result != sym))
10260     return;
10261
10262   /* Try to build the initializer expression.  If we can't initialize
10263      this symbol, then init will be NULL.  */
10264   init = build_default_init_expr (sym);
10265   if (init == NULL)
10266     return;
10267
10268   /* For saved variables, we don't want to add an initializer at function
10269      entry, so we just add a static initializer. Note that automatic variables
10270      are stack allocated even with -fno-automatic.  */
10271   if (sym->attr.save || sym->ns->save_all 
10272       || (gfc_option.flag_max_stack_var_size == 0
10273           && (!sym->attr.dimension || !is_non_constant_shape_array (sym))))
10274     {
10275       /* Don't clobber an existing initializer!  */
10276       gcc_assert (sym->value == NULL);
10277       sym->value = init;
10278       return;
10279     }
10280
10281   build_init_assign (sym, init);
10282 }
10283
10284
10285 /* Resolution of common features of flavors variable and procedure.  */
10286
10287 static gfc_try
10288 resolve_fl_var_and_proc (gfc_symbol *sym, int mp_flag)
10289 {
10290   gfc_array_spec *as;
10291
10292   /* Avoid double diagnostics for function result symbols.  */
10293   if ((sym->result || sym->attr.result) && !sym->attr.dummy
10294       && (sym->ns != gfc_current_ns))
10295     return SUCCESS;
10296
10297   if (sym->ts.type == BT_CLASS && sym->attr.class_ok)
10298     as = CLASS_DATA (sym)->as;
10299   else
10300     as = sym->as;
10301
10302   /* Constraints on deferred shape variable.  */
10303   if (as == NULL || as->type != AS_DEFERRED)
10304     {
10305       bool pointer, allocatable, dimension;
10306
10307       if (sym->ts.type == BT_CLASS && sym->attr.class_ok)
10308         {
10309           pointer = CLASS_DATA (sym)->attr.class_pointer;
10310           allocatable = CLASS_DATA (sym)->attr.allocatable;
10311           dimension = CLASS_DATA (sym)->attr.dimension;
10312         }
10313       else
10314         {
10315           pointer = sym->attr.pointer;
10316           allocatable = sym->attr.allocatable;
10317           dimension = sym->attr.dimension;
10318         }
10319
10320       if (allocatable)
10321         {
10322           if (dimension)
10323             {
10324               gfc_error ("Allocatable array '%s' at %L must have "
10325                          "a deferred shape", sym->name, &sym->declared_at);
10326               return FAILURE;
10327             }
10328           else if (gfc_notify_std (GFC_STD_F2003, "Scalar object '%s' at %L "
10329                                    "may not be ALLOCATABLE", sym->name,
10330                                    &sym->declared_at) == FAILURE)
10331             return FAILURE;
10332         }
10333
10334       if (pointer && dimension)
10335         {
10336           gfc_error ("Array pointer '%s' at %L must have a deferred shape",
10337                      sym->name, &sym->declared_at);
10338           return FAILURE;
10339         }
10340     }
10341   else
10342     {
10343       if (!mp_flag && !sym->attr.allocatable && !sym->attr.pointer
10344           && sym->ts.type != BT_CLASS && !sym->assoc)
10345         {
10346           gfc_error ("Array '%s' at %L cannot have a deferred shape",
10347                      sym->name, &sym->declared_at);
10348           return FAILURE;
10349          }
10350     }
10351
10352   /* Constraints on polymorphic variables.  */
10353   if (sym->ts.type == BT_CLASS && !(sym->result && sym->result != sym))
10354     {
10355       /* F03:C502.  */
10356       if (sym->attr.class_ok
10357           && !gfc_type_is_extensible (CLASS_DATA (sym)->ts.u.derived))
10358         {
10359           gfc_error ("Type '%s' of CLASS variable '%s' at %L is not extensible",
10360                      CLASS_DATA (sym)->ts.u.derived->name, sym->name,
10361                      &sym->declared_at);
10362           return FAILURE;
10363         }
10364
10365       /* F03:C509.  */
10366       /* Assume that use associated symbols were checked in the module ns.
10367          Class-variables that are associate-names are also something special
10368          and excepted from the test.  */
10369       if (!sym->attr.class_ok && !sym->attr.use_assoc && !sym->assoc)
10370         {
10371           gfc_error ("CLASS variable '%s' at %L must be dummy, allocatable "
10372                      "or pointer", sym->name, &sym->declared_at);
10373           return FAILURE;
10374         }
10375     }
10376     
10377   return SUCCESS;
10378 }
10379
10380
10381 /* Additional checks for symbols with flavor variable and derived
10382    type.  To be called from resolve_fl_variable.  */
10383
10384 static gfc_try
10385 resolve_fl_variable_derived (gfc_symbol *sym, int no_init_flag)
10386 {
10387   gcc_assert (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS);
10388
10389   /* Check to see if a derived type is blocked from being host
10390      associated by the presence of another class I symbol in the same
10391      namespace.  14.6.1.3 of the standard and the discussion on
10392      comp.lang.fortran.  */
10393   if (sym->ns != sym->ts.u.derived->ns
10394       && sym->ns->proc_name->attr.if_source != IFSRC_IFBODY)
10395     {
10396       gfc_symbol *s;
10397       gfc_find_symbol (sym->ts.u.derived->name, sym->ns, 0, &s);
10398       if (s && s->attr.generic)
10399         s = gfc_find_dt_in_generic (s);
10400       if (s && s->attr.flavor != FL_DERIVED)
10401         {
10402           gfc_error ("The type '%s' cannot be host associated at %L "
10403                      "because it is blocked by an incompatible object "
10404                      "of the same name declared at %L",
10405                      sym->ts.u.derived->name, &sym->declared_at,
10406                      &s->declared_at);
10407           return FAILURE;
10408         }
10409     }
10410
10411   /* 4th constraint in section 11.3: "If an object of a type for which
10412      component-initialization is specified (R429) appears in the
10413      specification-part of a module and does not have the ALLOCATABLE
10414      or POINTER attribute, the object shall have the SAVE attribute."
10415
10416      The check for initializers is performed with
10417      gfc_has_default_initializer because gfc_default_initializer generates
10418      a hidden default for allocatable components.  */
10419   if (!(sym->value || no_init_flag) && sym->ns->proc_name
10420       && sym->ns->proc_name->attr.flavor == FL_MODULE
10421       && !sym->ns->save_all && !sym->attr.save
10422       && !sym->attr.pointer && !sym->attr.allocatable
10423       && gfc_has_default_initializer (sym->ts.u.derived)
10424       && gfc_notify_std (GFC_STD_F2008, "Fortran 2008: Implied SAVE for "
10425                          "module variable '%s' at %L, needed due to "
10426                          "the default initialization", sym->name,
10427                          &sym->declared_at) == FAILURE)
10428     return FAILURE;
10429
10430   /* Assign default initializer.  */
10431   if (!(sym->value || sym->attr.pointer || sym->attr.allocatable)
10432       && (!no_init_flag || sym->attr.intent == INTENT_OUT))
10433     {
10434       sym->value = gfc_default_initializer (&sym->ts);
10435     }
10436
10437   return SUCCESS;
10438 }
10439
10440
10441 /* Resolve symbols with flavor variable.  */
10442
10443 static gfc_try
10444 resolve_fl_variable (gfc_symbol *sym, int mp_flag)
10445 {
10446   int no_init_flag, automatic_flag;
10447   gfc_expr *e;
10448   const char *auto_save_msg;
10449
10450   auto_save_msg = "Automatic object '%s' at %L cannot have the "
10451                   "SAVE attribute";
10452
10453   if (resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
10454     return FAILURE;
10455
10456   /* Set this flag to check that variables are parameters of all entries.
10457      This check is effected by the call to gfc_resolve_expr through
10458      is_non_constant_shape_array.  */
10459   specification_expr = 1;
10460
10461   if (sym->ns->proc_name
10462       && (sym->ns->proc_name->attr.flavor == FL_MODULE
10463           || sym->ns->proc_name->attr.is_main_program)
10464       && !sym->attr.use_assoc
10465       && !sym->attr.allocatable
10466       && !sym->attr.pointer
10467       && is_non_constant_shape_array (sym))
10468     {
10469       /* The shape of a main program or module array needs to be
10470          constant.  */
10471       gfc_error ("The module or main program array '%s' at %L must "
10472                  "have constant shape", sym->name, &sym->declared_at);
10473       specification_expr = 0;
10474       return FAILURE;
10475     }
10476
10477   /* Constraints on deferred type parameter.  */
10478   if (sym->ts.deferred && !(sym->attr.pointer || sym->attr.allocatable))
10479     {
10480       gfc_error ("Entity '%s' at %L has a deferred type parameter and "
10481                  "requires either the pointer or allocatable attribute",
10482                      sym->name, &sym->declared_at);
10483       return FAILURE;
10484     }
10485
10486   if (sym->ts.type == BT_CHARACTER)
10487     {
10488       /* Make sure that character string variables with assumed length are
10489          dummy arguments.  */
10490       e = sym->ts.u.cl->length;
10491       if (e == NULL && !sym->attr.dummy && !sym->attr.result
10492           && !sym->ts.deferred)
10493         {
10494           gfc_error ("Entity with assumed character length at %L must be a "
10495                      "dummy argument or a PARAMETER", &sym->declared_at);
10496           return FAILURE;
10497         }
10498
10499       if (e && sym->attr.save == SAVE_EXPLICIT && !gfc_is_constant_expr (e))
10500         {
10501           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
10502           return FAILURE;
10503         }
10504
10505       if (!gfc_is_constant_expr (e)
10506           && !(e->expr_type == EXPR_VARIABLE
10507                && e->symtree->n.sym->attr.flavor == FL_PARAMETER))
10508         {
10509           if (!sym->attr.use_assoc && sym->ns->proc_name
10510               && (sym->ns->proc_name->attr.flavor == FL_MODULE
10511                   || sym->ns->proc_name->attr.is_main_program))
10512             {
10513               gfc_error ("'%s' at %L must have constant character length "
10514                         "in this context", sym->name, &sym->declared_at);
10515               return FAILURE;
10516             }
10517           if (sym->attr.in_common)
10518             {
10519               gfc_error ("COMMON variable '%s' at %L must have constant "
10520                          "character length", sym->name, &sym->declared_at);
10521               return FAILURE;
10522             }
10523         }
10524     }
10525
10526   if (sym->value == NULL && sym->attr.referenced)
10527     apply_default_init_local (sym); /* Try to apply a default initialization.  */
10528
10529   /* Determine if the symbol may not have an initializer.  */
10530   no_init_flag = automatic_flag = 0;
10531   if (sym->attr.allocatable || sym->attr.external || sym->attr.dummy
10532       || sym->attr.intrinsic || sym->attr.result)
10533     no_init_flag = 1;
10534   else if ((sym->attr.dimension || sym->attr.codimension) && !sym->attr.pointer
10535            && is_non_constant_shape_array (sym))
10536     {
10537       no_init_flag = automatic_flag = 1;
10538
10539       /* Also, they must not have the SAVE attribute.
10540          SAVE_IMPLICIT is checked below.  */
10541       if (sym->as && sym->attr.codimension)
10542         {
10543           int corank = sym->as->corank;
10544           sym->as->corank = 0;
10545           no_init_flag = automatic_flag = is_non_constant_shape_array (sym);
10546           sym->as->corank = corank;
10547         }
10548       if (automatic_flag && sym->attr.save == SAVE_EXPLICIT)
10549         {
10550           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
10551           return FAILURE;
10552         }
10553     }
10554
10555   /* Ensure that any initializer is simplified.  */
10556   if (sym->value)
10557     gfc_simplify_expr (sym->value, 1);
10558
10559   /* Reject illegal initializers.  */
10560   if (!sym->mark && sym->value)
10561     {
10562       if (sym->attr.allocatable || (sym->ts.type == BT_CLASS
10563                                     && CLASS_DATA (sym)->attr.allocatable))
10564         gfc_error ("Allocatable '%s' at %L cannot have an initializer",
10565                    sym->name, &sym->declared_at);
10566       else if (sym->attr.external)
10567         gfc_error ("External '%s' at %L cannot have an initializer",
10568                    sym->name, &sym->declared_at);
10569       else if (sym->attr.dummy
10570         && !(sym->ts.type == BT_DERIVED && sym->attr.intent == INTENT_OUT))
10571         gfc_error ("Dummy '%s' at %L cannot have an initializer",
10572                    sym->name, &sym->declared_at);
10573       else if (sym->attr.intrinsic)
10574         gfc_error ("Intrinsic '%s' at %L cannot have an initializer",
10575                    sym->name, &sym->declared_at);
10576       else if (sym->attr.result)
10577         gfc_error ("Function result '%s' at %L cannot have an initializer",
10578                    sym->name, &sym->declared_at);
10579       else if (automatic_flag)
10580         gfc_error ("Automatic array '%s' at %L cannot have an initializer",
10581                    sym->name, &sym->declared_at);
10582       else
10583         goto no_init_error;
10584       return FAILURE;
10585     }
10586
10587 no_init_error:
10588   if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
10589     return resolve_fl_variable_derived (sym, no_init_flag);
10590
10591   return SUCCESS;
10592 }
10593
10594
10595 /* Resolve a procedure.  */
10596
10597 static gfc_try
10598 resolve_fl_procedure (gfc_symbol *sym, int mp_flag)
10599 {
10600   gfc_formal_arglist *arg;
10601
10602   if (sym->attr.function
10603       && resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
10604     return FAILURE;
10605
10606   if (sym->ts.type == BT_CHARACTER)
10607     {
10608       gfc_charlen *cl = sym->ts.u.cl;
10609
10610       if (cl && cl->length && gfc_is_constant_expr (cl->length)
10611              && resolve_charlen (cl) == FAILURE)
10612         return FAILURE;
10613
10614       if ((!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
10615           && sym->attr.proc == PROC_ST_FUNCTION)
10616         {
10617           gfc_error ("Character-valued statement function '%s' at %L must "
10618                      "have constant length", sym->name, &sym->declared_at);
10619           return FAILURE;
10620         }
10621     }
10622
10623   /* Ensure that derived type for are not of a private type.  Internal
10624      module procedures are excluded by 2.2.3.3 - i.e., they are not
10625      externally accessible and can access all the objects accessible in
10626      the host.  */
10627   if (!(sym->ns->parent
10628         && sym->ns->parent->proc_name->attr.flavor == FL_MODULE)
10629       && gfc_check_symbol_access (sym))
10630     {
10631       gfc_interface *iface;
10632
10633       for (arg = sym->formal; arg; arg = arg->next)
10634         {
10635           if (arg->sym
10636               && arg->sym->ts.type == BT_DERIVED
10637               && !arg->sym->ts.u.derived->attr.use_assoc
10638               && !gfc_check_symbol_access (arg->sym->ts.u.derived)
10639               && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: '%s' is of a "
10640                                  "PRIVATE type and cannot be a dummy argument"
10641                                  " of '%s', which is PUBLIC at %L",
10642                                  arg->sym->name, sym->name, &sym->declared_at)
10643                  == FAILURE)
10644             {
10645               /* Stop this message from recurring.  */
10646               arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
10647               return FAILURE;
10648             }
10649         }
10650
10651       /* PUBLIC interfaces may expose PRIVATE procedures that take types
10652          PRIVATE to the containing module.  */
10653       for (iface = sym->generic; iface; iface = iface->next)
10654         {
10655           for (arg = iface->sym->formal; arg; arg = arg->next)
10656             {
10657               if (arg->sym
10658                   && arg->sym->ts.type == BT_DERIVED
10659                   && !arg->sym->ts.u.derived->attr.use_assoc
10660                   && !gfc_check_symbol_access (arg->sym->ts.u.derived)
10661                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
10662                                      "'%s' in PUBLIC interface '%s' at %L "
10663                                      "takes dummy arguments of '%s' which is "
10664                                      "PRIVATE", iface->sym->name, sym->name,
10665                                      &iface->sym->declared_at,
10666                                      gfc_typename (&arg->sym->ts)) == FAILURE)
10667                 {
10668                   /* Stop this message from recurring.  */
10669                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
10670                   return FAILURE;
10671                 }
10672              }
10673         }
10674
10675       /* PUBLIC interfaces may expose PRIVATE procedures that take types
10676          PRIVATE to the containing module.  */
10677       for (iface = sym->generic; iface; iface = iface->next)
10678         {
10679           for (arg = iface->sym->formal; arg; arg = arg->next)
10680             {
10681               if (arg->sym
10682                   && arg->sym->ts.type == BT_DERIVED
10683                   && !arg->sym->ts.u.derived->attr.use_assoc
10684                   && !gfc_check_symbol_access (arg->sym->ts.u.derived)
10685                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
10686                                      "'%s' in PUBLIC interface '%s' at %L "
10687                                      "takes dummy arguments of '%s' which is "
10688                                      "PRIVATE", iface->sym->name, sym->name,
10689                                      &iface->sym->declared_at,
10690                                      gfc_typename (&arg->sym->ts)) == FAILURE)
10691                 {
10692                   /* Stop this message from recurring.  */
10693                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
10694                   return FAILURE;
10695                 }
10696              }
10697         }
10698     }
10699
10700   if (sym->attr.function && sym->value && sym->attr.proc != PROC_ST_FUNCTION
10701       && !sym->attr.proc_pointer)
10702     {
10703       gfc_error ("Function '%s' at %L cannot have an initializer",
10704                  sym->name, &sym->declared_at);
10705       return FAILURE;
10706     }
10707
10708   /* An external symbol may not have an initializer because it is taken to be
10709      a procedure. Exception: Procedure Pointers.  */
10710   if (sym->attr.external && sym->value && !sym->attr.proc_pointer)
10711     {
10712       gfc_error ("External object '%s' at %L may not have an initializer",
10713                  sym->name, &sym->declared_at);
10714       return FAILURE;
10715     }
10716
10717   /* An elemental function is required to return a scalar 12.7.1  */
10718   if (sym->attr.elemental && sym->attr.function && sym->as)
10719     {
10720       gfc_error ("ELEMENTAL function '%s' at %L must have a scalar "
10721                  "result", sym->name, &sym->declared_at);
10722       /* Reset so that the error only occurs once.  */
10723       sym->attr.elemental = 0;
10724       return FAILURE;
10725     }
10726
10727   if (sym->attr.proc == PROC_ST_FUNCTION
10728       && (sym->attr.allocatable || sym->attr.pointer))
10729     {
10730       gfc_error ("Statement function '%s' at %L may not have pointer or "
10731                  "allocatable attribute", sym->name, &sym->declared_at);
10732       return FAILURE;
10733     }
10734
10735   /* 5.1.1.5 of the Standard: A function name declared with an asterisk
10736      char-len-param shall not be array-valued, pointer-valued, recursive
10737      or pure.  ....snip... A character value of * may only be used in the
10738      following ways: (i) Dummy arg of procedure - dummy associates with
10739      actual length; (ii) To declare a named constant; or (iii) External
10740      function - but length must be declared in calling scoping unit.  */
10741   if (sym->attr.function
10742       && sym->ts.type == BT_CHARACTER && !sym->ts.deferred
10743       && sym->ts.u.cl && sym->ts.u.cl->length == NULL)
10744     {
10745       if ((sym->as && sym->as->rank) || (sym->attr.pointer)
10746           || (sym->attr.recursive) || (sym->attr.pure))
10747         {
10748           if (sym->as && sym->as->rank)
10749             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10750                        "array-valued", sym->name, &sym->declared_at);
10751
10752           if (sym->attr.pointer)
10753             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10754                        "pointer-valued", sym->name, &sym->declared_at);
10755
10756           if (sym->attr.pure)
10757             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10758                        "pure", sym->name, &sym->declared_at);
10759
10760           if (sym->attr.recursive)
10761             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10762                        "recursive", sym->name, &sym->declared_at);
10763
10764           return FAILURE;
10765         }
10766
10767       /* Appendix B.2 of the standard.  Contained functions give an
10768          error anyway.  Fixed-form is likely to be F77/legacy. Deferred
10769          character length is an F2003 feature.  */
10770       if (!sym->attr.contained
10771             && gfc_current_form != FORM_FIXED
10772             && !sym->ts.deferred)
10773         gfc_notify_std (GFC_STD_F95_OBS, "Obsolescent feature: "
10774                         "CHARACTER(*) function '%s' at %L",
10775                         sym->name, &sym->declared_at);
10776     }
10777
10778   if (sym->attr.is_bind_c && sym->attr.is_c_interop != 1)
10779     {
10780       gfc_formal_arglist *curr_arg;
10781       int has_non_interop_arg = 0;
10782
10783       if (verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
10784                              sym->common_block) == FAILURE)
10785         {
10786           /* Clear these to prevent looking at them again if there was an
10787              error.  */
10788           sym->attr.is_bind_c = 0;
10789           sym->attr.is_c_interop = 0;
10790           sym->ts.is_c_interop = 0;
10791         }
10792       else
10793         {
10794           /* So far, no errors have been found.  */
10795           sym->attr.is_c_interop = 1;
10796           sym->ts.is_c_interop = 1;
10797         }
10798       
10799       curr_arg = sym->formal;
10800       while (curr_arg != NULL)
10801         {
10802           /* Skip implicitly typed dummy args here.  */
10803           if (curr_arg->sym->attr.implicit_type == 0)
10804             if (gfc_verify_c_interop_param (curr_arg->sym) == FAILURE)
10805               /* If something is found to fail, record the fact so we
10806                  can mark the symbol for the procedure as not being
10807                  BIND(C) to try and prevent multiple errors being
10808                  reported.  */
10809               has_non_interop_arg = 1;
10810           
10811           curr_arg = curr_arg->next;
10812         }
10813
10814       /* See if any of the arguments were not interoperable and if so, clear
10815          the procedure symbol to prevent duplicate error messages.  */
10816       if (has_non_interop_arg != 0)
10817         {
10818           sym->attr.is_c_interop = 0;
10819           sym->ts.is_c_interop = 0;
10820           sym->attr.is_bind_c = 0;
10821         }
10822     }
10823   
10824   if (!sym->attr.proc_pointer)
10825     {
10826       if (sym->attr.save == SAVE_EXPLICIT)
10827         {
10828           gfc_error ("PROCEDURE attribute conflicts with SAVE attribute "
10829                      "in '%s' at %L", sym->name, &sym->declared_at);
10830           return FAILURE;
10831         }
10832       if (sym->attr.intent)
10833         {
10834           gfc_error ("PROCEDURE attribute conflicts with INTENT attribute "
10835                      "in '%s' at %L", sym->name, &sym->declared_at);
10836           return FAILURE;
10837         }
10838       if (sym->attr.subroutine && sym->attr.result)
10839         {
10840           gfc_error ("PROCEDURE attribute conflicts with RESULT attribute "
10841                      "in '%s' at %L", sym->name, &sym->declared_at);
10842           return FAILURE;
10843         }
10844       if (sym->attr.external && sym->attr.function
10845           && ((sym->attr.if_source == IFSRC_DECL && !sym->attr.procedure)
10846               || sym->attr.contained))
10847         {
10848           gfc_error ("EXTERNAL attribute conflicts with FUNCTION attribute "
10849                      "in '%s' at %L", sym->name, &sym->declared_at);
10850           return FAILURE;
10851         }
10852       if (strcmp ("ppr@", sym->name) == 0)
10853         {
10854           gfc_error ("Procedure pointer result '%s' at %L "
10855                      "is missing the pointer attribute",
10856                      sym->ns->proc_name->name, &sym->declared_at);
10857           return FAILURE;
10858         }
10859     }
10860
10861   return SUCCESS;
10862 }
10863
10864
10865 /* Resolve a list of finalizer procedures.  That is, after they have hopefully
10866    been defined and we now know their defined arguments, check that they fulfill
10867    the requirements of the standard for procedures used as finalizers.  */
10868
10869 static gfc_try
10870 gfc_resolve_finalizers (gfc_symbol* derived)
10871 {
10872   gfc_finalizer* list;
10873   gfc_finalizer** prev_link; /* For removing wrong entries from the list.  */
10874   gfc_try result = SUCCESS;
10875   bool seen_scalar = false;
10876
10877   if (!derived->f2k_derived || !derived->f2k_derived->finalizers)
10878     return SUCCESS;
10879
10880   /* Walk over the list of finalizer-procedures, check them, and if any one
10881      does not fit in with the standard's definition, print an error and remove
10882      it from the list.  */
10883   prev_link = &derived->f2k_derived->finalizers;
10884   for (list = derived->f2k_derived->finalizers; list; list = *prev_link)
10885     {
10886       gfc_symbol* arg;
10887       gfc_finalizer* i;
10888       int my_rank;
10889
10890       /* Skip this finalizer if we already resolved it.  */
10891       if (list->proc_tree)
10892         {
10893           prev_link = &(list->next);
10894           continue;
10895         }
10896
10897       /* Check this exists and is a SUBROUTINE.  */
10898       if (!list->proc_sym->attr.subroutine)
10899         {
10900           gfc_error ("FINAL procedure '%s' at %L is not a SUBROUTINE",
10901                      list->proc_sym->name, &list->where);
10902           goto error;
10903         }
10904
10905       /* We should have exactly one argument.  */
10906       if (!list->proc_sym->formal || list->proc_sym->formal->next)
10907         {
10908           gfc_error ("FINAL procedure at %L must have exactly one argument",
10909                      &list->where);
10910           goto error;
10911         }
10912       arg = list->proc_sym->formal->sym;
10913
10914       /* This argument must be of our type.  */
10915       if (arg->ts.type != BT_DERIVED || arg->ts.u.derived != derived)
10916         {
10917           gfc_error ("Argument of FINAL procedure at %L must be of type '%s'",
10918                      &arg->declared_at, derived->name);
10919           goto error;
10920         }
10921
10922       /* It must neither be a pointer nor allocatable nor optional.  */
10923       if (arg->attr.pointer)
10924         {
10925           gfc_error ("Argument of FINAL procedure at %L must not be a POINTER",
10926                      &arg->declared_at);
10927           goto error;
10928         }
10929       if (arg->attr.allocatable)
10930         {
10931           gfc_error ("Argument of FINAL procedure at %L must not be"
10932                      " ALLOCATABLE", &arg->declared_at);
10933           goto error;
10934         }
10935       if (arg->attr.optional)
10936         {
10937           gfc_error ("Argument of FINAL procedure at %L must not be OPTIONAL",
10938                      &arg->declared_at);
10939           goto error;
10940         }
10941
10942       /* It must not be INTENT(OUT).  */
10943       if (arg->attr.intent == INTENT_OUT)
10944         {
10945           gfc_error ("Argument of FINAL procedure at %L must not be"
10946                      " INTENT(OUT)", &arg->declared_at);
10947           goto error;
10948         }
10949
10950       /* Warn if the procedure is non-scalar and not assumed shape.  */
10951       if (gfc_option.warn_surprising && arg->as && arg->as->rank > 0
10952           && arg->as->type != AS_ASSUMED_SHAPE)
10953         gfc_warning ("Non-scalar FINAL procedure at %L should have assumed"
10954                      " shape argument", &arg->declared_at);
10955
10956       /* Check that it does not match in kind and rank with a FINAL procedure
10957          defined earlier.  To really loop over the *earlier* declarations,
10958          we need to walk the tail of the list as new ones were pushed at the
10959          front.  */
10960       /* TODO: Handle kind parameters once they are implemented.  */
10961       my_rank = (arg->as ? arg->as->rank : 0);
10962       for (i = list->next; i; i = i->next)
10963         {
10964           /* Argument list might be empty; that is an error signalled earlier,
10965              but we nevertheless continued resolving.  */
10966           if (i->proc_sym->formal)
10967             {
10968               gfc_symbol* i_arg = i->proc_sym->formal->sym;
10969               const int i_rank = (i_arg->as ? i_arg->as->rank : 0);
10970               if (i_rank == my_rank)
10971                 {
10972                   gfc_error ("FINAL procedure '%s' declared at %L has the same"
10973                              " rank (%d) as '%s'",
10974                              list->proc_sym->name, &list->where, my_rank, 
10975                              i->proc_sym->name);
10976                   goto error;
10977                 }
10978             }
10979         }
10980
10981         /* Is this the/a scalar finalizer procedure?  */
10982         if (!arg->as || arg->as->rank == 0)
10983           seen_scalar = true;
10984
10985         /* Find the symtree for this procedure.  */
10986         gcc_assert (!list->proc_tree);
10987         list->proc_tree = gfc_find_sym_in_symtree (list->proc_sym);
10988
10989         prev_link = &list->next;
10990         continue;
10991
10992         /* Remove wrong nodes immediately from the list so we don't risk any
10993            troubles in the future when they might fail later expectations.  */
10994 error:
10995         result = FAILURE;
10996         i = list;
10997         *prev_link = list->next;
10998         gfc_free_finalizer (i);
10999     }
11000
11001   /* Warn if we haven't seen a scalar finalizer procedure (but we know there
11002      were nodes in the list, must have been for arrays.  It is surely a good
11003      idea to have a scalar version there if there's something to finalize.  */
11004   if (gfc_option.warn_surprising && result == SUCCESS && !seen_scalar)
11005     gfc_warning ("Only array FINAL procedures declared for derived type '%s'"
11006                  " defined at %L, suggest also scalar one",
11007                  derived->name, &derived->declared_at);
11008
11009   /* TODO:  Remove this error when finalization is finished.  */
11010   gfc_error ("Finalization at %L is not yet implemented",
11011              &derived->declared_at);
11012
11013   return result;
11014 }
11015
11016
11017 /* Check if two GENERIC targets are ambiguous and emit an error is they are.  */
11018
11019 static gfc_try
11020 check_generic_tbp_ambiguity (gfc_tbp_generic* t1, gfc_tbp_generic* t2,
11021                              const char* generic_name, locus where)
11022 {
11023   gfc_symbol* sym1;
11024   gfc_symbol* sym2;
11025
11026   gcc_assert (t1->specific && t2->specific);
11027   gcc_assert (!t1->specific->is_generic);
11028   gcc_assert (!t2->specific->is_generic);
11029   gcc_assert (t1->is_operator == t2->is_operator);
11030
11031   sym1 = t1->specific->u.specific->n.sym;
11032   sym2 = t2->specific->u.specific->n.sym;
11033
11034   if (sym1 == sym2)
11035     return SUCCESS;
11036
11037   /* Both must be SUBROUTINEs or both must be FUNCTIONs.  */
11038   if (sym1->attr.subroutine != sym2->attr.subroutine
11039       || sym1->attr.function != sym2->attr.function)
11040     {
11041       gfc_error ("'%s' and '%s' can't be mixed FUNCTION/SUBROUTINE for"
11042                  " GENERIC '%s' at %L",
11043                  sym1->name, sym2->name, generic_name, &where);
11044       return FAILURE;
11045     }
11046
11047   /* Compare the interfaces.  */
11048   if (gfc_compare_interfaces (sym1, sym2, sym2->name, !t1->is_operator, 0,
11049                               NULL, 0))
11050     {
11051       gfc_error ("'%s' and '%s' for GENERIC '%s' at %L are ambiguous",
11052                  sym1->name, sym2->name, generic_name, &where);
11053       return FAILURE;
11054     }
11055
11056   return SUCCESS;
11057 }
11058
11059
11060 /* Worker function for resolving a generic procedure binding; this is used to
11061    resolve GENERIC as well as user and intrinsic OPERATOR typebound procedures.
11062
11063    The difference between those cases is finding possible inherited bindings
11064    that are overridden, as one has to look for them in tb_sym_root,
11065    tb_uop_root or tb_op, respectively.  Thus the caller must already find
11066    the super-type and set p->overridden correctly.  */
11067
11068 static gfc_try
11069 resolve_tb_generic_targets (gfc_symbol* super_type,
11070                             gfc_typebound_proc* p, const char* name)
11071 {
11072   gfc_tbp_generic* target;
11073   gfc_symtree* first_target;
11074   gfc_symtree* inherited;
11075
11076   gcc_assert (p && p->is_generic);
11077
11078   /* Try to find the specific bindings for the symtrees in our target-list.  */
11079   gcc_assert (p->u.generic);
11080   for (target = p->u.generic; target; target = target->next)
11081     if (!target->specific)
11082       {
11083         gfc_typebound_proc* overridden_tbp;
11084         gfc_tbp_generic* g;
11085         const char* target_name;
11086
11087         target_name = target->specific_st->name;
11088
11089         /* Defined for this type directly.  */
11090         if (target->specific_st->n.tb && !target->specific_st->n.tb->error)
11091           {
11092             target->specific = target->specific_st->n.tb;
11093             goto specific_found;
11094           }
11095
11096         /* Look for an inherited specific binding.  */
11097         if (super_type)
11098           {
11099             inherited = gfc_find_typebound_proc (super_type, NULL, target_name,
11100                                                  true, NULL);
11101
11102             if (inherited)
11103               {
11104                 gcc_assert (inherited->n.tb);
11105                 target->specific = inherited->n.tb;
11106                 goto specific_found;
11107               }
11108           }
11109
11110         gfc_error ("Undefined specific binding '%s' as target of GENERIC '%s'"
11111                    " at %L", target_name, name, &p->where);
11112         return FAILURE;
11113
11114         /* Once we've found the specific binding, check it is not ambiguous with
11115            other specifics already found or inherited for the same GENERIC.  */
11116 specific_found:
11117         gcc_assert (target->specific);
11118
11119         /* This must really be a specific binding!  */
11120         if (target->specific->is_generic)
11121           {
11122             gfc_error ("GENERIC '%s' at %L must target a specific binding,"
11123                        " '%s' is GENERIC, too", name, &p->where, target_name);
11124             return FAILURE;
11125           }
11126
11127         /* Check those already resolved on this type directly.  */
11128         for (g = p->u.generic; g; g = g->next)
11129           if (g != target && g->specific
11130               && check_generic_tbp_ambiguity (target, g, name, p->where)
11131                   == FAILURE)
11132             return FAILURE;
11133
11134         /* Check for ambiguity with inherited specific targets.  */
11135         for (overridden_tbp = p->overridden; overridden_tbp;
11136              overridden_tbp = overridden_tbp->overridden)
11137           if (overridden_tbp->is_generic)
11138             {
11139               for (g = overridden_tbp->u.generic; g; g = g->next)
11140                 {
11141                   gcc_assert (g->specific);
11142                   if (check_generic_tbp_ambiguity (target, g,
11143                                                    name, p->where) == FAILURE)
11144                     return FAILURE;
11145                 }
11146             }
11147       }
11148
11149   /* If we attempt to "overwrite" a specific binding, this is an error.  */
11150   if (p->overridden && !p->overridden->is_generic)
11151     {
11152       gfc_error ("GENERIC '%s' at %L can't overwrite specific binding with"
11153                  " the same name", name, &p->where);
11154       return FAILURE;
11155     }
11156
11157   /* Take the SUBROUTINE/FUNCTION attributes of the first specific target, as
11158      all must have the same attributes here.  */
11159   first_target = p->u.generic->specific->u.specific;
11160   gcc_assert (first_target);
11161   p->subroutine = first_target->n.sym->attr.subroutine;
11162   p->function = first_target->n.sym->attr.function;
11163
11164   return SUCCESS;
11165 }
11166
11167
11168 /* Resolve a GENERIC procedure binding for a derived type.  */
11169
11170 static gfc_try
11171 resolve_typebound_generic (gfc_symbol* derived, gfc_symtree* st)
11172 {
11173   gfc_symbol* super_type;
11174
11175   /* Find the overridden binding if any.  */
11176   st->n.tb->overridden = NULL;
11177   super_type = gfc_get_derived_super_type (derived);
11178   if (super_type)
11179     {
11180       gfc_symtree* overridden;
11181       overridden = gfc_find_typebound_proc (super_type, NULL, st->name,
11182                                             true, NULL);
11183
11184       if (overridden && overridden->n.tb)
11185         st->n.tb->overridden = overridden->n.tb;
11186     }
11187
11188   /* Resolve using worker function.  */
11189   return resolve_tb_generic_targets (super_type, st->n.tb, st->name);
11190 }
11191
11192
11193 /* Retrieve the target-procedure of an operator binding and do some checks in
11194    common for intrinsic and user-defined type-bound operators.  */
11195
11196 static gfc_symbol*
11197 get_checked_tb_operator_target (gfc_tbp_generic* target, locus where)
11198 {
11199   gfc_symbol* target_proc;
11200
11201   gcc_assert (target->specific && !target->specific->is_generic);
11202   target_proc = target->specific->u.specific->n.sym;
11203   gcc_assert (target_proc);
11204
11205   /* All operator bindings must have a passed-object dummy argument.  */
11206   if (target->specific->nopass)
11207     {
11208       gfc_error ("Type-bound operator at %L can't be NOPASS", &where);
11209       return NULL;
11210     }
11211
11212   return target_proc;
11213 }
11214
11215
11216 /* Resolve a type-bound intrinsic operator.  */
11217
11218 static gfc_try
11219 resolve_typebound_intrinsic_op (gfc_symbol* derived, gfc_intrinsic_op op,
11220                                 gfc_typebound_proc* p)
11221 {
11222   gfc_symbol* super_type;
11223   gfc_tbp_generic* target;
11224   
11225   /* If there's already an error here, do nothing (but don't fail again).  */
11226   if (p->error)
11227     return SUCCESS;
11228
11229   /* Operators should always be GENERIC bindings.  */
11230   gcc_assert (p->is_generic);
11231
11232   /* Look for an overridden binding.  */
11233   super_type = gfc_get_derived_super_type (derived);
11234   if (super_type && super_type->f2k_derived)
11235     p->overridden = gfc_find_typebound_intrinsic_op (super_type, NULL,
11236                                                      op, true, NULL);
11237   else
11238     p->overridden = NULL;
11239
11240   /* Resolve general GENERIC properties using worker function.  */
11241   if (resolve_tb_generic_targets (super_type, p, gfc_op2string (op)) == FAILURE)
11242     goto error;
11243
11244   /* Check the targets to be procedures of correct interface.  */
11245   for (target = p->u.generic; target; target = target->next)
11246     {
11247       gfc_symbol* target_proc;
11248
11249       target_proc = get_checked_tb_operator_target (target, p->where);
11250       if (!target_proc)
11251         goto error;
11252
11253       if (!gfc_check_operator_interface (target_proc, op, p->where))
11254         goto error;
11255     }
11256
11257   return SUCCESS;
11258
11259 error:
11260   p->error = 1;
11261   return FAILURE;
11262 }
11263
11264
11265 /* Resolve a type-bound user operator (tree-walker callback).  */
11266
11267 static gfc_symbol* resolve_bindings_derived;
11268 static gfc_try resolve_bindings_result;
11269
11270 static gfc_try check_uop_procedure (gfc_symbol* sym, locus where);
11271
11272 static void
11273 resolve_typebound_user_op (gfc_symtree* stree)
11274 {
11275   gfc_symbol* super_type;
11276   gfc_tbp_generic* target;
11277
11278   gcc_assert (stree && stree->n.tb);
11279
11280   if (stree->n.tb->error)
11281     return;
11282
11283   /* Operators should always be GENERIC bindings.  */
11284   gcc_assert (stree->n.tb->is_generic);
11285
11286   /* Find overridden procedure, if any.  */
11287   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
11288   if (super_type && super_type->f2k_derived)
11289     {
11290       gfc_symtree* overridden;
11291       overridden = gfc_find_typebound_user_op (super_type, NULL,
11292                                                stree->name, true, NULL);
11293
11294       if (overridden && overridden->n.tb)
11295         stree->n.tb->overridden = overridden->n.tb;
11296     }
11297   else
11298     stree->n.tb->overridden = NULL;
11299
11300   /* Resolve basically using worker function.  */
11301   if (resolve_tb_generic_targets (super_type, stree->n.tb, stree->name)
11302         == FAILURE)
11303     goto error;
11304
11305   /* Check the targets to be functions of correct interface.  */
11306   for (target = stree->n.tb->u.generic; target; target = target->next)
11307     {
11308       gfc_symbol* target_proc;
11309
11310       target_proc = get_checked_tb_operator_target (target, stree->n.tb->where);
11311       if (!target_proc)
11312         goto error;
11313
11314       if (check_uop_procedure (target_proc, stree->n.tb->where) == FAILURE)
11315         goto error;
11316     }
11317
11318   return;
11319
11320 error:
11321   resolve_bindings_result = FAILURE;
11322   stree->n.tb->error = 1;
11323 }
11324
11325
11326 /* Resolve the type-bound procedures for a derived type.  */
11327
11328 static void
11329 resolve_typebound_procedure (gfc_symtree* stree)
11330 {
11331   gfc_symbol* proc;
11332   locus where;
11333   gfc_symbol* me_arg;
11334   gfc_symbol* super_type;
11335   gfc_component* comp;
11336
11337   gcc_assert (stree);
11338
11339   /* Undefined specific symbol from GENERIC target definition.  */
11340   if (!stree->n.tb)
11341     return;
11342
11343   if (stree->n.tb->error)
11344     return;
11345
11346   /* If this is a GENERIC binding, use that routine.  */
11347   if (stree->n.tb->is_generic)
11348     {
11349       if (resolve_typebound_generic (resolve_bindings_derived, stree)
11350             == FAILURE)
11351         goto error;
11352       return;
11353     }
11354
11355   /* Get the target-procedure to check it.  */
11356   gcc_assert (!stree->n.tb->is_generic);
11357   gcc_assert (stree->n.tb->u.specific);
11358   proc = stree->n.tb->u.specific->n.sym;
11359   where = stree->n.tb->where;
11360   proc->attr.public_used = 1;
11361
11362   /* Default access should already be resolved from the parser.  */
11363   gcc_assert (stree->n.tb->access != ACCESS_UNKNOWN);
11364
11365   /* It should be a module procedure or an external procedure with explicit
11366      interface.  For DEFERRED bindings, abstract interfaces are ok as well.  */
11367   if ((!proc->attr.subroutine && !proc->attr.function)
11368       || (proc->attr.proc != PROC_MODULE
11369           && proc->attr.if_source != IFSRC_IFBODY)
11370       || (proc->attr.abstract && !stree->n.tb->deferred))
11371     {
11372       gfc_error ("'%s' must be a module procedure or an external procedure with"
11373                  " an explicit interface at %L", proc->name, &where);
11374       goto error;
11375     }
11376   stree->n.tb->subroutine = proc->attr.subroutine;
11377   stree->n.tb->function = proc->attr.function;
11378
11379   /* Find the super-type of the current derived type.  We could do this once and
11380      store in a global if speed is needed, but as long as not I believe this is
11381      more readable and clearer.  */
11382   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
11383
11384   /* If PASS, resolve and check arguments if not already resolved / loaded
11385      from a .mod file.  */
11386   if (!stree->n.tb->nopass && stree->n.tb->pass_arg_num == 0)
11387     {
11388       if (stree->n.tb->pass_arg)
11389         {
11390           gfc_formal_arglist* i;
11391
11392           /* If an explicit passing argument name is given, walk the arg-list
11393              and look for it.  */
11394
11395           me_arg = NULL;
11396           stree->n.tb->pass_arg_num = 1;
11397           for (i = proc->formal; i; i = i->next)
11398             {
11399               if (!strcmp (i->sym->name, stree->n.tb->pass_arg))
11400                 {
11401                   me_arg = i->sym;
11402                   break;
11403                 }
11404               ++stree->n.tb->pass_arg_num;
11405             }
11406
11407           if (!me_arg)
11408             {
11409               gfc_error ("Procedure '%s' with PASS(%s) at %L has no"
11410                          " argument '%s'",
11411                          proc->name, stree->n.tb->pass_arg, &where,
11412                          stree->n.tb->pass_arg);
11413               goto error;
11414             }
11415         }
11416       else
11417         {
11418           /* Otherwise, take the first one; there should in fact be at least
11419              one.  */
11420           stree->n.tb->pass_arg_num = 1;
11421           if (!proc->formal)
11422             {
11423               gfc_error ("Procedure '%s' with PASS at %L must have at"
11424                          " least one argument", proc->name, &where);
11425               goto error;
11426             }
11427           me_arg = proc->formal->sym;
11428         }
11429
11430       /* Now check that the argument-type matches and the passed-object
11431          dummy argument is generally fine.  */
11432
11433       gcc_assert (me_arg);
11434
11435       if (me_arg->ts.type != BT_CLASS)
11436         {
11437           gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
11438                      " at %L", proc->name, &where);
11439           goto error;
11440         }
11441
11442       if (CLASS_DATA (me_arg)->ts.u.derived
11443           != resolve_bindings_derived)
11444         {
11445           gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
11446                      " the derived-type '%s'", me_arg->name, proc->name,
11447                      me_arg->name, &where, resolve_bindings_derived->name);
11448           goto error;
11449         }
11450   
11451       gcc_assert (me_arg->ts.type == BT_CLASS);
11452       if (CLASS_DATA (me_arg)->as && CLASS_DATA (me_arg)->as->rank > 0)
11453         {
11454           gfc_error ("Passed-object dummy argument of '%s' at %L must be"
11455                      " scalar", proc->name, &where);
11456           goto error;
11457         }
11458       if (CLASS_DATA (me_arg)->attr.allocatable)
11459         {
11460           gfc_error ("Passed-object dummy argument of '%s' at %L must not"
11461                      " be ALLOCATABLE", proc->name, &where);
11462           goto error;
11463         }
11464       if (CLASS_DATA (me_arg)->attr.class_pointer)
11465         {
11466           gfc_error ("Passed-object dummy argument of '%s' at %L must not"
11467                      " be POINTER", proc->name, &where);
11468           goto error;
11469         }
11470     }
11471
11472   /* If we are extending some type, check that we don't override a procedure
11473      flagged NON_OVERRIDABLE.  */
11474   stree->n.tb->overridden = NULL;
11475   if (super_type)
11476     {
11477       gfc_symtree* overridden;
11478       overridden = gfc_find_typebound_proc (super_type, NULL,
11479                                             stree->name, true, NULL);
11480
11481       if (overridden)
11482         {
11483           if (overridden->n.tb)
11484             stree->n.tb->overridden = overridden->n.tb;
11485
11486           if (gfc_check_typebound_override (stree, overridden) == FAILURE)
11487             goto error;
11488         }
11489     }
11490
11491   /* See if there's a name collision with a component directly in this type.  */
11492   for (comp = resolve_bindings_derived->components; comp; comp = comp->next)
11493     if (!strcmp (comp->name, stree->name))
11494       {
11495         gfc_error ("Procedure '%s' at %L has the same name as a component of"
11496                    " '%s'",
11497                    stree->name, &where, resolve_bindings_derived->name);
11498         goto error;
11499       }
11500
11501   /* Try to find a name collision with an inherited component.  */
11502   if (super_type && gfc_find_component (super_type, stree->name, true, true))
11503     {
11504       gfc_error ("Procedure '%s' at %L has the same name as an inherited"
11505                  " component of '%s'",
11506                  stree->name, &where, resolve_bindings_derived->name);
11507       goto error;
11508     }
11509
11510   stree->n.tb->error = 0;
11511   return;
11512
11513 error:
11514   resolve_bindings_result = FAILURE;
11515   stree->n.tb->error = 1;
11516 }
11517
11518
11519 static gfc_try
11520 resolve_typebound_procedures (gfc_symbol* derived)
11521 {
11522   int op;
11523   gfc_symbol* super_type;
11524
11525   if (!derived->f2k_derived || !derived->f2k_derived->tb_sym_root)
11526     return SUCCESS;
11527   
11528   super_type = gfc_get_derived_super_type (derived);
11529   if (super_type)
11530     resolve_typebound_procedures (super_type);
11531
11532   resolve_bindings_derived = derived;
11533   resolve_bindings_result = SUCCESS;
11534
11535   /* Make sure the vtab has been generated.  */
11536   gfc_find_derived_vtab (derived);
11537
11538   if (derived->f2k_derived->tb_sym_root)
11539     gfc_traverse_symtree (derived->f2k_derived->tb_sym_root,
11540                           &resolve_typebound_procedure);
11541
11542   if (derived->f2k_derived->tb_uop_root)
11543     gfc_traverse_symtree (derived->f2k_derived->tb_uop_root,
11544                           &resolve_typebound_user_op);
11545
11546   for (op = 0; op != GFC_INTRINSIC_OPS; ++op)
11547     {
11548       gfc_typebound_proc* p = derived->f2k_derived->tb_op[op];
11549       if (p && resolve_typebound_intrinsic_op (derived, (gfc_intrinsic_op) op,
11550                                                p) == FAILURE)
11551         resolve_bindings_result = FAILURE;
11552     }
11553
11554   return resolve_bindings_result;
11555 }
11556
11557
11558 /* Add a derived type to the dt_list.  The dt_list is used in trans-types.c
11559    to give all identical derived types the same backend_decl.  */
11560 static void
11561 add_dt_to_dt_list (gfc_symbol *derived)
11562 {
11563   gfc_dt_list *dt_list;
11564
11565   for (dt_list = gfc_derived_types; dt_list; dt_list = dt_list->next)
11566     if (derived == dt_list->derived)
11567       return;
11568
11569   dt_list = gfc_get_dt_list ();
11570   dt_list->next = gfc_derived_types;
11571   dt_list->derived = derived;
11572   gfc_derived_types = dt_list;
11573 }
11574
11575
11576 /* Ensure that a derived-type is really not abstract, meaning that every
11577    inherited DEFERRED binding is overridden by a non-DEFERRED one.  */
11578
11579 static gfc_try
11580 ensure_not_abstract_walker (gfc_symbol* sub, gfc_symtree* st)
11581 {
11582   if (!st)
11583     return SUCCESS;
11584
11585   if (ensure_not_abstract_walker (sub, st->left) == FAILURE)
11586     return FAILURE;
11587   if (ensure_not_abstract_walker (sub, st->right) == FAILURE)
11588     return FAILURE;
11589
11590   if (st->n.tb && st->n.tb->deferred)
11591     {
11592       gfc_symtree* overriding;
11593       overriding = gfc_find_typebound_proc (sub, NULL, st->name, true, NULL);
11594       if (!overriding)
11595         return FAILURE;
11596       gcc_assert (overriding->n.tb);
11597       if (overriding->n.tb->deferred)
11598         {
11599           gfc_error ("Derived-type '%s' declared at %L must be ABSTRACT because"
11600                      " '%s' is DEFERRED and not overridden",
11601                      sub->name, &sub->declared_at, st->name);
11602           return FAILURE;
11603         }
11604     }
11605
11606   return SUCCESS;
11607 }
11608
11609 static gfc_try
11610 ensure_not_abstract (gfc_symbol* sub, gfc_symbol* ancestor)
11611 {
11612   /* The algorithm used here is to recursively travel up the ancestry of sub
11613      and for each ancestor-type, check all bindings.  If any of them is
11614      DEFERRED, look it up starting from sub and see if the found (overriding)
11615      binding is not DEFERRED.
11616      This is not the most efficient way to do this, but it should be ok and is
11617      clearer than something sophisticated.  */
11618
11619   gcc_assert (ancestor && !sub->attr.abstract);
11620   
11621   if (!ancestor->attr.abstract)
11622     return SUCCESS;
11623
11624   /* Walk bindings of this ancestor.  */
11625   if (ancestor->f2k_derived)
11626     {
11627       gfc_try t;
11628       t = ensure_not_abstract_walker (sub, ancestor->f2k_derived->tb_sym_root);
11629       if (t == FAILURE)
11630         return FAILURE;
11631     }
11632
11633   /* Find next ancestor type and recurse on it.  */
11634   ancestor = gfc_get_derived_super_type (ancestor);
11635   if (ancestor)
11636     return ensure_not_abstract (sub, ancestor);
11637
11638   return SUCCESS;
11639 }
11640
11641
11642 /* Resolve the components of a derived type. This does not have to wait until
11643    resolution stage, but can be done as soon as the dt declaration has been
11644    parsed.  */
11645
11646 static gfc_try
11647 resolve_fl_derived0 (gfc_symbol *sym)
11648 {
11649   gfc_symbol* super_type;
11650   gfc_component *c;
11651
11652   super_type = gfc_get_derived_super_type (sym);
11653
11654   /* F2008, C432. */
11655   if (super_type && sym->attr.coarray_comp && !super_type->attr.coarray_comp)
11656     {
11657       gfc_error ("As extending type '%s' at %L has a coarray component, "
11658                  "parent type '%s' shall also have one", sym->name,
11659                  &sym->declared_at, super_type->name);
11660       return FAILURE;
11661     }
11662
11663   /* Ensure the extended type gets resolved before we do.  */
11664   if (super_type && resolve_fl_derived0 (super_type) == FAILURE)
11665     return FAILURE;
11666
11667   /* An ABSTRACT type must be extensible.  */
11668   if (sym->attr.abstract && !gfc_type_is_extensible (sym))
11669     {
11670       gfc_error ("Non-extensible derived-type '%s' at %L must not be ABSTRACT",
11671                  sym->name, &sym->declared_at);
11672       return FAILURE;
11673     }
11674
11675   c = (sym->attr.is_class) ? sym->components->ts.u.derived->components
11676                            : sym->components;
11677
11678   for ( ; c != NULL; c = c->next)
11679     {
11680       /* See PRs 51550, 47545, 48654, 49050, 51075 - and 45170.  */
11681       if (c->ts.type == BT_CHARACTER && c->ts.deferred && !c->attr.function)
11682         {
11683           gfc_error ("Deferred-length character component '%s' at %L is not "
11684                      "yet supported", c->name, &c->loc);
11685           return FAILURE;
11686         }
11687
11688       /* F2008, C442.  */
11689       if ((!sym->attr.is_class || c != sym->components)
11690           && c->attr.codimension
11691           && (!c->attr.allocatable || (c->as && c->as->type != AS_DEFERRED)))
11692         {
11693           gfc_error ("Coarray component '%s' at %L must be allocatable with "
11694                      "deferred shape", c->name, &c->loc);
11695           return FAILURE;
11696         }
11697
11698       /* F2008, C443.  */
11699       if (c->attr.codimension && c->ts.type == BT_DERIVED
11700           && c->ts.u.derived->ts.is_iso_c)
11701         {
11702           gfc_error ("Component '%s' at %L of TYPE(C_PTR) or TYPE(C_FUNPTR) "
11703                      "shall not be a coarray", c->name, &c->loc);
11704           return FAILURE;
11705         }
11706
11707       /* F2008, C444.  */
11708       if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.coarray_comp
11709           && (c->attr.codimension || c->attr.pointer || c->attr.dimension
11710               || c->attr.allocatable))
11711         {
11712           gfc_error ("Component '%s' at %L with coarray component "
11713                      "shall be a nonpointer, nonallocatable scalar",
11714                      c->name, &c->loc);
11715           return FAILURE;
11716         }
11717
11718       /* F2008, C448.  */
11719       if (c->attr.contiguous && (!c->attr.dimension || !c->attr.pointer))
11720         {
11721           gfc_error ("Component '%s' at %L has the CONTIGUOUS attribute but "
11722                      "is not an array pointer", c->name, &c->loc);
11723           return FAILURE;
11724         }
11725
11726       if (c->attr.proc_pointer && c->ts.interface)
11727         {
11728           if (c->ts.interface->attr.procedure && !sym->attr.vtype)
11729             gfc_error ("Interface '%s', used by procedure pointer component "
11730                        "'%s' at %L, is declared in a later PROCEDURE statement",
11731                        c->ts.interface->name, c->name, &c->loc);
11732
11733           /* Get the attributes from the interface (now resolved).  */
11734           if (c->ts.interface->attr.if_source
11735               || c->ts.interface->attr.intrinsic)
11736             {
11737               gfc_symbol *ifc = c->ts.interface;
11738
11739               if (ifc->formal && !ifc->formal_ns)
11740                 resolve_symbol (ifc);
11741
11742               if (ifc->attr.intrinsic)
11743                 resolve_intrinsic (ifc, &ifc->declared_at);
11744
11745               if (ifc->result)
11746                 {
11747                   c->ts = ifc->result->ts;
11748                   c->attr.allocatable = ifc->result->attr.allocatable;
11749                   c->attr.pointer = ifc->result->attr.pointer;
11750                   c->attr.dimension = ifc->result->attr.dimension;
11751                   c->as = gfc_copy_array_spec (ifc->result->as);
11752                 }
11753               else
11754                 {   
11755                   c->ts = ifc->ts;
11756                   c->attr.allocatable = ifc->attr.allocatable;
11757                   c->attr.pointer = ifc->attr.pointer;
11758                   c->attr.dimension = ifc->attr.dimension;
11759                   c->as = gfc_copy_array_spec (ifc->as);
11760                 }
11761               c->ts.interface = ifc;
11762               c->attr.function = ifc->attr.function;
11763               c->attr.subroutine = ifc->attr.subroutine;
11764               gfc_copy_formal_args_ppc (c, ifc);
11765
11766               c->attr.pure = ifc->attr.pure;
11767               c->attr.elemental = ifc->attr.elemental;
11768               c->attr.recursive = ifc->attr.recursive;
11769               c->attr.always_explicit = ifc->attr.always_explicit;
11770               c->attr.ext_attr |= ifc->attr.ext_attr;
11771               /* Replace symbols in array spec.  */
11772               if (c->as)
11773                 {
11774                   int i;
11775                   for (i = 0; i < c->as->rank; i++)
11776                     {
11777                       gfc_expr_replace_comp (c->as->lower[i], c);
11778                       gfc_expr_replace_comp (c->as->upper[i], c);
11779                     }
11780                 }
11781               /* Copy char length.  */
11782               if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
11783                 {
11784                   gfc_charlen *cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
11785                   gfc_expr_replace_comp (cl->length, c);
11786                   if (cl->length && !cl->resolved
11787                         && gfc_resolve_expr (cl->length) == FAILURE)
11788                     return FAILURE;
11789                   c->ts.u.cl = cl;
11790                 }
11791             }
11792           else if (!sym->attr.vtype && c->ts.interface->name[0] != '\0')
11793             {
11794               gfc_error ("Interface '%s' of procedure pointer component "
11795                          "'%s' at %L must be explicit", c->ts.interface->name,
11796                          c->name, &c->loc);
11797               return FAILURE;
11798             }
11799         }
11800       else if (c->attr.proc_pointer && c->ts.type == BT_UNKNOWN)
11801         {
11802           /* Since PPCs are not implicitly typed, a PPC without an explicit
11803              interface must be a subroutine.  */
11804           gfc_add_subroutine (&c->attr, c->name, &c->loc);
11805         }
11806
11807       /* Procedure pointer components: Check PASS arg.  */
11808       if (c->attr.proc_pointer && !c->tb->nopass && c->tb->pass_arg_num == 0
11809           && !sym->attr.vtype)
11810         {
11811           gfc_symbol* me_arg;
11812
11813           if (c->tb->pass_arg)
11814             {
11815               gfc_formal_arglist* i;
11816
11817               /* If an explicit passing argument name is given, walk the arg-list
11818                 and look for it.  */
11819
11820               me_arg = NULL;
11821               c->tb->pass_arg_num = 1;
11822               for (i = c->formal; i; i = i->next)
11823                 {
11824                   if (!strcmp (i->sym->name, c->tb->pass_arg))
11825                     {
11826                       me_arg = i->sym;
11827                       break;
11828                     }
11829                   c->tb->pass_arg_num++;
11830                 }
11831
11832               if (!me_arg)
11833                 {
11834                   gfc_error ("Procedure pointer component '%s' with PASS(%s) "
11835                              "at %L has no argument '%s'", c->name,
11836                              c->tb->pass_arg, &c->loc, c->tb->pass_arg);
11837                   c->tb->error = 1;
11838                   return FAILURE;
11839                 }
11840             }
11841           else
11842             {
11843               /* Otherwise, take the first one; there should in fact be at least
11844                 one.  */
11845               c->tb->pass_arg_num = 1;
11846               if (!c->formal)
11847                 {
11848                   gfc_error ("Procedure pointer component '%s' with PASS at %L "
11849                              "must have at least one argument",
11850                              c->name, &c->loc);
11851                   c->tb->error = 1;
11852                   return FAILURE;
11853                 }
11854               me_arg = c->formal->sym;
11855             }
11856
11857           /* Now check that the argument-type matches.  */
11858           gcc_assert (me_arg);
11859           if ((me_arg->ts.type != BT_DERIVED && me_arg->ts.type != BT_CLASS)
11860               || (me_arg->ts.type == BT_DERIVED && me_arg->ts.u.derived != sym)
11861               || (me_arg->ts.type == BT_CLASS
11862                   && CLASS_DATA (me_arg)->ts.u.derived != sym))
11863             {
11864               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
11865                          " the derived type '%s'", me_arg->name, c->name,
11866                          me_arg->name, &c->loc, sym->name);
11867               c->tb->error = 1;
11868               return FAILURE;
11869             }
11870
11871           /* Check for C453.  */
11872           if (me_arg->attr.dimension)
11873             {
11874               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
11875                          "must be scalar", me_arg->name, c->name, me_arg->name,
11876                          &c->loc);
11877               c->tb->error = 1;
11878               return FAILURE;
11879             }
11880
11881           if (me_arg->attr.pointer)
11882             {
11883               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
11884                          "may not have the POINTER attribute", me_arg->name,
11885                          c->name, me_arg->name, &c->loc);
11886               c->tb->error = 1;
11887               return FAILURE;
11888             }
11889
11890           if (me_arg->attr.allocatable)
11891             {
11892               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
11893                          "may not be ALLOCATABLE", me_arg->name, c->name,
11894                          me_arg->name, &c->loc);
11895               c->tb->error = 1;
11896               return FAILURE;
11897             }
11898
11899           if (gfc_type_is_extensible (sym) && me_arg->ts.type != BT_CLASS)
11900             gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
11901                        " at %L", c->name, &c->loc);
11902
11903         }
11904
11905       /* Check type-spec if this is not the parent-type component.  */
11906       if (((sym->attr.is_class
11907             && (!sym->components->ts.u.derived->attr.extension
11908                 || c != sym->components->ts.u.derived->components))
11909            || (!sym->attr.is_class
11910                && (!sym->attr.extension || c != sym->components)))
11911           && !sym->attr.vtype
11912           && resolve_typespec_used (&c->ts, &c->loc, c->name) == FAILURE)
11913         return FAILURE;
11914
11915       /* If this type is an extension, set the accessibility of the parent
11916          component.  */
11917       if (super_type
11918           && ((sym->attr.is_class
11919                && c == sym->components->ts.u.derived->components)
11920               || (!sym->attr.is_class && c == sym->components))
11921           && strcmp (super_type->name, c->name) == 0)
11922         c->attr.access = super_type->attr.access;
11923       
11924       /* If this type is an extension, see if this component has the same name
11925          as an inherited type-bound procedure.  */
11926       if (super_type && !sym->attr.is_class
11927           && gfc_find_typebound_proc (super_type, NULL, c->name, true, NULL))
11928         {
11929           gfc_error ("Component '%s' of '%s' at %L has the same name as an"
11930                      " inherited type-bound procedure",
11931                      c->name, sym->name, &c->loc);
11932           return FAILURE;
11933         }
11934
11935       if (c->ts.type == BT_CHARACTER && !c->attr.proc_pointer
11936             && !c->ts.deferred)
11937         {
11938          if (c->ts.u.cl->length == NULL
11939              || (resolve_charlen (c->ts.u.cl) == FAILURE)
11940              || !gfc_is_constant_expr (c->ts.u.cl->length))
11941            {
11942              gfc_error ("Character length of component '%s' needs to "
11943                         "be a constant specification expression at %L",
11944                         c->name,
11945                         c->ts.u.cl->length ? &c->ts.u.cl->length->where : &c->loc);
11946              return FAILURE;
11947            }
11948         }
11949
11950       if (c->ts.type == BT_CHARACTER && c->ts.deferred
11951           && !c->attr.pointer && !c->attr.allocatable)
11952         {
11953           gfc_error ("Character component '%s' of '%s' at %L with deferred "
11954                      "length must be a POINTER or ALLOCATABLE",
11955                      c->name, sym->name, &c->loc);
11956           return FAILURE;
11957         }
11958
11959       if (c->ts.type == BT_DERIVED
11960           && sym->component_access != ACCESS_PRIVATE
11961           && gfc_check_symbol_access (sym)
11962           && !is_sym_host_assoc (c->ts.u.derived, sym->ns)
11963           && !c->ts.u.derived->attr.use_assoc
11964           && !gfc_check_symbol_access (c->ts.u.derived)
11965           && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: the component '%s' "
11966                              "is a PRIVATE type and cannot be a component of "
11967                              "'%s', which is PUBLIC at %L", c->name,
11968                              sym->name, &sym->declared_at) == FAILURE)
11969         return FAILURE;
11970
11971       if ((sym->attr.sequence || sym->attr.is_bind_c) && c->ts.type == BT_CLASS)
11972         {
11973           gfc_error ("Polymorphic component %s at %L in SEQUENCE or BIND(C) "
11974                      "type %s", c->name, &c->loc, sym->name);
11975           return FAILURE;
11976         }
11977
11978       if (sym->attr.sequence)
11979         {
11980           if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.sequence == 0)
11981             {
11982               gfc_error ("Component %s of SEQUENCE type declared at %L does "
11983                          "not have the SEQUENCE attribute",
11984                          c->ts.u.derived->name, &sym->declared_at);
11985               return FAILURE;
11986             }
11987         }
11988
11989       if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.generic)
11990         c->ts.u.derived = gfc_find_dt_in_generic (c->ts.u.derived);
11991       else if (c->ts.type == BT_CLASS && c->attr.class_ok
11992                && CLASS_DATA (c)->ts.u.derived->attr.generic)
11993         CLASS_DATA (c)->ts.u.derived
11994                         = gfc_find_dt_in_generic (CLASS_DATA (c)->ts.u.derived);
11995
11996       if (!sym->attr.is_class && c->ts.type == BT_DERIVED && !sym->attr.vtype
11997           && c->attr.pointer && c->ts.u.derived->components == NULL
11998           && !c->ts.u.derived->attr.zero_comp)
11999         {
12000           gfc_error ("The pointer component '%s' of '%s' at %L is a type "
12001                      "that has not been declared", c->name, sym->name,
12002                      &c->loc);
12003           return FAILURE;
12004         }
12005
12006       if (c->ts.type == BT_CLASS && c->attr.class_ok
12007           && CLASS_DATA (c)->attr.class_pointer
12008           && CLASS_DATA (c)->ts.u.derived->components == NULL
12009           && !CLASS_DATA (c)->ts.u.derived->attr.zero_comp)
12010         {
12011           gfc_error ("The pointer component '%s' of '%s' at %L is a type "
12012                      "that has not been declared", c->name, sym->name,
12013                      &c->loc);
12014           return FAILURE;
12015         }
12016
12017       /* C437.  */
12018       if (c->ts.type == BT_CLASS && c->attr.flavor != FL_PROCEDURE
12019           && (!c->attr.class_ok
12020               || !(CLASS_DATA (c)->attr.class_pointer
12021                    || CLASS_DATA (c)->attr.allocatable)))
12022         {
12023           gfc_error ("Component '%s' with CLASS at %L must be allocatable "
12024                      "or pointer", c->name, &c->loc);
12025           return FAILURE;
12026         }
12027
12028       /* Ensure that all the derived type components are put on the
12029          derived type list; even in formal namespaces, where derived type
12030          pointer components might not have been declared.  */
12031       if (c->ts.type == BT_DERIVED
12032             && c->ts.u.derived
12033             && c->ts.u.derived->components
12034             && c->attr.pointer
12035             && sym != c->ts.u.derived)
12036         add_dt_to_dt_list (c->ts.u.derived);
12037
12038       if (gfc_resolve_array_spec (c->as, !(c->attr.pointer
12039                                            || c->attr.proc_pointer
12040                                            || c->attr.allocatable)) == FAILURE)
12041         return FAILURE;
12042     }
12043
12044   /* If this is a non-ABSTRACT type extending an ABSTRACT one, ensure that
12045      all DEFERRED bindings are overridden.  */
12046   if (super_type && super_type->attr.abstract && !sym->attr.abstract
12047       && !sym->attr.is_class
12048       && ensure_not_abstract (sym, super_type) == FAILURE)
12049     return FAILURE;
12050
12051   /* Add derived type to the derived type list.  */
12052   add_dt_to_dt_list (sym);
12053
12054   return SUCCESS;
12055 }
12056
12057
12058 /* The following procedure does the full resolution of a derived type,
12059    including resolution of all type-bound procedures (if present). In contrast
12060    to 'resolve_fl_derived0' this can only be done after the module has been
12061    parsed completely.  */
12062
12063 static gfc_try
12064 resolve_fl_derived (gfc_symbol *sym)
12065 {
12066   gfc_symbol *gen_dt = NULL;
12067
12068   if (!sym->attr.is_class)
12069     gfc_find_symbol (sym->name, sym->ns, 0, &gen_dt);
12070   if (gen_dt && gen_dt->generic && gen_dt->generic->next
12071       && (!gen_dt->generic->sym->attr.use_assoc
12072           || gen_dt->generic->sym->module != gen_dt->generic->next->sym->module)
12073       && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Generic name '%s' of "
12074                          "function '%s' at %L being the same name as derived "
12075                          "type at %L", sym->name,
12076                          gen_dt->generic->sym == sym
12077                            ? gen_dt->generic->next->sym->name
12078                            : gen_dt->generic->sym->name,
12079                          gen_dt->generic->sym == sym
12080                            ? &gen_dt->generic->next->sym->declared_at
12081                            : &gen_dt->generic->sym->declared_at,
12082                          &sym->declared_at) == FAILURE)
12083     return FAILURE;
12084
12085   if (sym->attr.is_class && sym->ts.u.derived == NULL)
12086     {
12087       /* Fix up incomplete CLASS symbols.  */
12088       gfc_component *data = gfc_find_component (sym, "_data", true, true);
12089       gfc_component *vptr = gfc_find_component (sym, "_vptr", true, true);
12090       if (vptr->ts.u.derived == NULL)
12091         {
12092           gfc_symbol *vtab = gfc_find_derived_vtab (data->ts.u.derived);
12093           gcc_assert (vtab);
12094           vptr->ts.u.derived = vtab->ts.u.derived;
12095         }
12096     }
12097   
12098   if (resolve_fl_derived0 (sym) == FAILURE)
12099     return FAILURE;
12100   
12101   /* Resolve the type-bound procedures.  */
12102   if (resolve_typebound_procedures (sym) == FAILURE)
12103     return FAILURE;
12104
12105   /* Resolve the finalizer procedures.  */
12106   if (gfc_resolve_finalizers (sym) == FAILURE)
12107     return FAILURE;
12108   
12109   return SUCCESS;
12110 }
12111
12112
12113 static gfc_try
12114 resolve_fl_namelist (gfc_symbol *sym)
12115 {
12116   gfc_namelist *nl;
12117   gfc_symbol *nlsym;
12118
12119   for (nl = sym->namelist; nl; nl = nl->next)
12120     {
12121       /* Check again, the check in match only works if NAMELIST comes
12122          after the decl.  */
12123       if (nl->sym->as && nl->sym->as->type == AS_ASSUMED_SIZE)
12124         {
12125           gfc_error ("Assumed size array '%s' in namelist '%s' at %L is not "
12126                      "allowed", nl->sym->name, sym->name, &sym->declared_at);
12127           return FAILURE;
12128         }
12129
12130       if (nl->sym->as && nl->sym->as->type == AS_ASSUMED_SHAPE
12131           && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: NAMELIST array "
12132                              "object '%s' with assumed shape in namelist "
12133                              "'%s' at %L", nl->sym->name, sym->name,
12134                              &sym->declared_at) == FAILURE)
12135         return FAILURE;
12136
12137       if (is_non_constant_shape_array (nl->sym)
12138           && gfc_notify_std (GFC_STD_F2003,  "Fortran 2003: NAMELIST array "
12139                              "object '%s' with nonconstant shape in namelist "
12140                              "'%s' at %L", nl->sym->name, sym->name,
12141                              &sym->declared_at) == FAILURE)
12142         return FAILURE;
12143
12144       if (nl->sym->ts.type == BT_CHARACTER
12145           && (nl->sym->ts.u.cl->length == NULL
12146               || !gfc_is_constant_expr (nl->sym->ts.u.cl->length))
12147           && gfc_notify_std (GFC_STD_F2003,  "Fortran 2003: NAMELIST object "
12148                              "'%s' with nonconstant character length in "
12149                              "namelist '%s' at %L", nl->sym->name, sym->name,
12150                              &sym->declared_at) == FAILURE)
12151         return FAILURE;
12152
12153       /* FIXME: Once UDDTIO is implemented, the following can be
12154          removed.  */
12155       if (nl->sym->ts.type == BT_CLASS)
12156         {
12157           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L is "
12158                      "polymorphic and requires a defined input/output "
12159                      "procedure", nl->sym->name, sym->name, &sym->declared_at);
12160           return FAILURE;
12161         }
12162
12163       if (nl->sym->ts.type == BT_DERIVED
12164           && (nl->sym->ts.u.derived->attr.alloc_comp
12165               || nl->sym->ts.u.derived->attr.pointer_comp))
12166         {
12167           if (gfc_notify_std (GFC_STD_F2003,  "Fortran 2003: NAMELIST object "
12168                               "'%s' in namelist '%s' at %L with ALLOCATABLE "
12169                               "or POINTER components", nl->sym->name,
12170                               sym->name, &sym->declared_at) == FAILURE)
12171             return FAILURE;
12172
12173          /* FIXME: Once UDDTIO is implemented, the following can be
12174             removed.  */
12175           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L has "
12176                      "ALLOCATABLE or POINTER components and thus requires "
12177                      "a defined input/output procedure", nl->sym->name,
12178                      sym->name, &sym->declared_at);
12179           return FAILURE;
12180         }
12181     }
12182
12183   /* Reject PRIVATE objects in a PUBLIC namelist.  */
12184   if (gfc_check_symbol_access (sym))
12185     {
12186       for (nl = sym->namelist; nl; nl = nl->next)
12187         {
12188           if (!nl->sym->attr.use_assoc
12189               && !is_sym_host_assoc (nl->sym, sym->ns)
12190               && !gfc_check_symbol_access (nl->sym))
12191             {
12192               gfc_error ("NAMELIST object '%s' was declared PRIVATE and "
12193                          "cannot be member of PUBLIC namelist '%s' at %L",
12194                          nl->sym->name, sym->name, &sym->declared_at);
12195               return FAILURE;
12196             }
12197
12198           /* Types with private components that came here by USE-association.  */
12199           if (nl->sym->ts.type == BT_DERIVED
12200               && derived_inaccessible (nl->sym->ts.u.derived))
12201             {
12202               gfc_error ("NAMELIST object '%s' has use-associated PRIVATE "
12203                          "components and cannot be member of namelist '%s' at %L",
12204                          nl->sym->name, sym->name, &sym->declared_at);
12205               return FAILURE;
12206             }
12207
12208           /* Types with private components that are defined in the same module.  */
12209           if (nl->sym->ts.type == BT_DERIVED
12210               && !is_sym_host_assoc (nl->sym->ts.u.derived, sym->ns)
12211               && nl->sym->ts.u.derived->attr.private_comp)
12212             {
12213               gfc_error ("NAMELIST object '%s' has PRIVATE components and "
12214                          "cannot be a member of PUBLIC namelist '%s' at %L",
12215                          nl->sym->name, sym->name, &sym->declared_at);
12216               return FAILURE;
12217             }
12218         }
12219     }
12220
12221
12222   /* 14.1.2 A module or internal procedure represent local entities
12223      of the same type as a namelist member and so are not allowed.  */
12224   for (nl = sym->namelist; nl; nl = nl->next)
12225     {
12226       if (nl->sym->ts.kind != 0 && nl->sym->attr.flavor == FL_VARIABLE)
12227         continue;
12228
12229       if (nl->sym->attr.function && nl->sym == nl->sym->result)
12230         if ((nl->sym == sym->ns->proc_name)
12231                ||
12232             (sym->ns->parent && nl->sym == sym->ns->parent->proc_name))
12233           continue;
12234
12235       nlsym = NULL;
12236       if (nl->sym && nl->sym->name)
12237         gfc_find_symbol (nl->sym->name, sym->ns, 1, &nlsym);
12238       if (nlsym && nlsym->attr.flavor == FL_PROCEDURE)
12239         {
12240           gfc_error ("PROCEDURE attribute conflicts with NAMELIST "
12241                      "attribute in '%s' at %L", nlsym->name,
12242                      &sym->declared_at);
12243           return FAILURE;
12244         }
12245     }
12246
12247   return SUCCESS;
12248 }
12249
12250
12251 static gfc_try
12252 resolve_fl_parameter (gfc_symbol *sym)
12253 {
12254   /* A parameter array's shape needs to be constant.  */
12255   if (sym->as != NULL 
12256       && (sym->as->type == AS_DEFERRED
12257           || is_non_constant_shape_array (sym)))
12258     {
12259       gfc_error ("Parameter array '%s' at %L cannot be automatic "
12260                  "or of deferred shape", sym->name, &sym->declared_at);
12261       return FAILURE;
12262     }
12263
12264   /* Make sure a parameter that has been implicitly typed still
12265      matches the implicit type, since PARAMETER statements can precede
12266      IMPLICIT statements.  */
12267   if (sym->attr.implicit_type
12268       && !gfc_compare_types (&sym->ts, gfc_get_default_type (sym->name,
12269                                                              sym->ns)))
12270     {
12271       gfc_error ("Implicitly typed PARAMETER '%s' at %L doesn't match a "
12272                  "later IMPLICIT type", sym->name, &sym->declared_at);
12273       return FAILURE;
12274     }
12275
12276   /* Make sure the types of derived parameters are consistent.  This
12277      type checking is deferred until resolution because the type may
12278      refer to a derived type from the host.  */
12279   if (sym->ts.type == BT_DERIVED
12280       && !gfc_compare_types (&sym->ts, &sym->value->ts))
12281     {
12282       gfc_error ("Incompatible derived type in PARAMETER at %L",
12283                  &sym->value->where);
12284       return FAILURE;
12285     }
12286   return SUCCESS;
12287 }
12288
12289
12290 /* Do anything necessary to resolve a symbol.  Right now, we just
12291    assume that an otherwise unknown symbol is a variable.  This sort
12292    of thing commonly happens for symbols in module.  */
12293
12294 static void
12295 resolve_symbol (gfc_symbol *sym)
12296 {
12297   int check_constant, mp_flag;
12298   gfc_symtree *symtree;
12299   gfc_symtree *this_symtree;
12300   gfc_namespace *ns;
12301   gfc_component *c;
12302   symbol_attribute class_attr;
12303   gfc_array_spec *as;
12304
12305   if (sym->attr.flavor == FL_UNKNOWN
12306       || (sym->attr.flavor == FL_PROCEDURE && !sym->attr.intrinsic
12307           && !sym->attr.generic && !sym->attr.external
12308           && sym->attr.if_source == IFSRC_UNKNOWN))
12309     {
12310
12311     /* If we find that a flavorless symbol is an interface in one of the
12312        parent namespaces, find its symtree in this namespace, free the
12313        symbol and set the symtree to point to the interface symbol.  */
12314       for (ns = gfc_current_ns->parent; ns; ns = ns->parent)
12315         {
12316           symtree = gfc_find_symtree (ns->sym_root, sym->name);
12317           if (symtree && (symtree->n.sym->generic ||
12318                           (symtree->n.sym->attr.flavor == FL_PROCEDURE
12319                            && sym->ns->construct_entities)))
12320             {
12321               this_symtree = gfc_find_symtree (gfc_current_ns->sym_root,
12322                                                sym->name);
12323               gfc_release_symbol (sym);
12324               symtree->n.sym->refs++;
12325               this_symtree->n.sym = symtree->n.sym;
12326               return;
12327             }
12328         }
12329
12330       /* Otherwise give it a flavor according to such attributes as
12331          it has.  */
12332       if (sym->attr.flavor == FL_UNKNOWN && sym->attr.external == 0
12333           && sym->attr.intrinsic == 0)
12334         sym->attr.flavor = FL_VARIABLE;
12335       else if (sym->attr.flavor == FL_UNKNOWN)
12336         {
12337           sym->attr.flavor = FL_PROCEDURE;
12338           if (sym->attr.dimension)
12339             sym->attr.function = 1;
12340         }
12341     }
12342
12343   if (sym->attr.external && sym->ts.type != BT_UNKNOWN && !sym->attr.function)
12344     gfc_add_function (&sym->attr, sym->name, &sym->declared_at);
12345
12346   if (sym->attr.procedure && sym->ts.interface
12347       && sym->attr.if_source != IFSRC_DECL
12348       && resolve_procedure_interface (sym) == FAILURE)
12349     return;
12350
12351   if (sym->attr.is_protected && !sym->attr.proc_pointer
12352       && (sym->attr.procedure || sym->attr.external))
12353     {
12354       if (sym->attr.external)
12355         gfc_error ("PROTECTED attribute conflicts with EXTERNAL attribute "
12356                    "at %L", &sym->declared_at);
12357       else
12358         gfc_error ("PROCEDURE attribute conflicts with PROTECTED attribute "
12359                    "at %L", &sym->declared_at);
12360
12361       return;
12362     }
12363
12364   if (sym->attr.flavor == FL_DERIVED && resolve_fl_derived (sym) == FAILURE)
12365     return;
12366
12367   /* Symbols that are module procedures with results (functions) have
12368      the types and array specification copied for type checking in
12369      procedures that call them, as well as for saving to a module
12370      file.  These symbols can't stand the scrutiny that their results
12371      can.  */
12372   mp_flag = (sym->result != NULL && sym->result != sym);
12373
12374   /* Make sure that the intrinsic is consistent with its internal 
12375      representation. This needs to be done before assigning a default 
12376      type to avoid spurious warnings.  */
12377   if (sym->attr.flavor != FL_MODULE && sym->attr.intrinsic
12378       && resolve_intrinsic (sym, &sym->declared_at) == FAILURE)
12379     return;
12380
12381   /* Resolve associate names.  */
12382   if (sym->assoc)
12383     resolve_assoc_var (sym, true);
12384
12385   /* Assign default type to symbols that need one and don't have one.  */
12386   if (sym->ts.type == BT_UNKNOWN)
12387     {
12388       if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER)
12389         {
12390           gfc_set_default_type (sym, 1, NULL);
12391         }
12392
12393       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.external
12394           && !sym->attr.function && !sym->attr.subroutine
12395           && gfc_get_default_type (sym->name, sym->ns)->type == BT_UNKNOWN)
12396         gfc_add_subroutine (&sym->attr, sym->name, &sym->declared_at);
12397
12398       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.function)
12399         {
12400           /* The specific case of an external procedure should emit an error
12401              in the case that there is no implicit type.  */
12402           if (!mp_flag)
12403             gfc_set_default_type (sym, sym->attr.external, NULL);
12404           else
12405             {
12406               /* Result may be in another namespace.  */
12407               resolve_symbol (sym->result);
12408
12409               if (!sym->result->attr.proc_pointer)
12410                 {
12411                   sym->ts = sym->result->ts;
12412                   sym->as = gfc_copy_array_spec (sym->result->as);
12413                   sym->attr.dimension = sym->result->attr.dimension;
12414                   sym->attr.pointer = sym->result->attr.pointer;
12415                   sym->attr.allocatable = sym->result->attr.allocatable;
12416                   sym->attr.contiguous = sym->result->attr.contiguous;
12417                 }
12418             }
12419         }
12420     }
12421   else if (mp_flag && sym->attr.flavor == FL_PROCEDURE && sym->attr.function)
12422     gfc_resolve_array_spec (sym->result->as, false);
12423
12424   if (sym->ts.type == BT_CLASS && sym->attr.class_ok)
12425     {
12426       as = CLASS_DATA (sym)->as;
12427       class_attr = CLASS_DATA (sym)->attr;
12428       class_attr.pointer = class_attr.class_pointer;
12429     }
12430   else
12431     {
12432       class_attr = sym->attr;
12433       as = sym->as;
12434     }
12435
12436   /* F2008, C530. */
12437   if (sym->attr.contiguous
12438       && (!class_attr.dimension
12439           || (as->type != AS_ASSUMED_SHAPE && !class_attr.pointer)))
12440     {
12441       gfc_error ("'%s' at %L has the CONTIGUOUS attribute but is not an "
12442                   "array pointer or an assumed-shape array", sym->name,
12443                   &sym->declared_at);
12444       return;
12445     }
12446
12447   /* Assumed size arrays and assumed shape arrays must be dummy
12448      arguments.  Array-spec's of implied-shape should have been resolved to
12449      AS_EXPLICIT already.  */
12450
12451   if (as)
12452     {
12453       gcc_assert (as->type != AS_IMPLIED_SHAPE);
12454       if (((as->type == AS_ASSUMED_SIZE && !as->cp_was_assumed)
12455            || as->type == AS_ASSUMED_SHAPE)
12456           && sym->attr.dummy == 0)
12457         {
12458           if (as->type == AS_ASSUMED_SIZE)
12459             gfc_error ("Assumed size array at %L must be a dummy argument",
12460                        &sym->declared_at);
12461           else
12462             gfc_error ("Assumed shape array at %L must be a dummy argument",
12463                        &sym->declared_at);
12464           return;
12465         }
12466     }
12467
12468   /* Make sure symbols with known intent or optional are really dummy
12469      variable.  Because of ENTRY statement, this has to be deferred
12470      until resolution time.  */
12471
12472   if (!sym->attr.dummy
12473       && (sym->attr.optional || sym->attr.intent != INTENT_UNKNOWN))
12474     {
12475       gfc_error ("Symbol at %L is not a DUMMY variable", &sym->declared_at);
12476       return;
12477     }
12478
12479   if (sym->attr.value && !sym->attr.dummy)
12480     {
12481       gfc_error ("'%s' at %L cannot have the VALUE attribute because "
12482                  "it is not a dummy argument", sym->name, &sym->declared_at);
12483       return;
12484     }
12485
12486   if (sym->attr.value && sym->ts.type == BT_CHARACTER)
12487     {
12488       gfc_charlen *cl = sym->ts.u.cl;
12489       if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
12490         {
12491           gfc_error ("Character dummy variable '%s' at %L with VALUE "
12492                      "attribute must have constant length",
12493                      sym->name, &sym->declared_at);
12494           return;
12495         }
12496
12497       if (sym->ts.is_c_interop
12498           && mpz_cmp_si (cl->length->value.integer, 1) != 0)
12499         {
12500           gfc_error ("C interoperable character dummy variable '%s' at %L "
12501                      "with VALUE attribute must have length one",
12502                      sym->name, &sym->declared_at);
12503           return;
12504         }
12505     }
12506
12507   if (sym->ts.type == BT_DERIVED && !sym->attr.is_iso_c
12508       && sym->ts.u.derived->attr.generic)
12509     {
12510       sym->ts.u.derived = gfc_find_dt_in_generic (sym->ts.u.derived);
12511       if (!sym->ts.u.derived)
12512         {
12513           gfc_error ("The derived type '%s' at %L is of type '%s', "
12514                      "which has not been defined", sym->name,
12515                      &sym->declared_at, sym->ts.u.derived->name);
12516           sym->ts.type = BT_UNKNOWN;
12517           return;
12518         }
12519     }
12520
12521   if (sym->ts.type == BT_ASSUMED)
12522     { 
12523       /* TS 29113, C407a.  */
12524       if (!sym->attr.dummy)
12525         {
12526           gfc_error ("Assumed type of variable %s at %L is only permitted "
12527                      "for dummy variables", sym->name, &sym->declared_at);
12528           return;
12529         }
12530       if (sym->attr.allocatable || sym->attr.codimension
12531           || sym->attr.pointer || sym->attr.value)
12532         {
12533           gfc_error ("Assumed-type variable %s at %L may not have the "
12534                      "ALLOCATABLE, CODIMENSION, POINTER or VALUE attribute",
12535                      sym->name, &sym->declared_at);
12536           return;
12537         }
12538       if (sym->attr.dimension && sym->as->type == AS_EXPLICIT)
12539         {
12540           gfc_error ("Assumed-type variable %s at %L shall not be an "
12541                      "explicit-shape array", sym->name, &sym->declared_at);
12542           return;
12543         }
12544     }
12545
12546   /* If the symbol is marked as bind(c), verify it's type and kind.  Do not
12547      do this for something that was implicitly typed because that is handled
12548      in gfc_set_default_type.  Handle dummy arguments and procedure
12549      definitions separately.  Also, anything that is use associated is not
12550      handled here but instead is handled in the module it is declared in.
12551      Finally, derived type definitions are allowed to be BIND(C) since that
12552      only implies that they're interoperable, and they are checked fully for
12553      interoperability when a variable is declared of that type.  */
12554   if (sym->attr.is_bind_c && sym->attr.implicit_type == 0 &&
12555       sym->attr.use_assoc == 0 && sym->attr.dummy == 0 &&
12556       sym->attr.flavor != FL_PROCEDURE && sym->attr.flavor != FL_DERIVED)
12557     {
12558       gfc_try t = SUCCESS;
12559       
12560       /* First, make sure the variable is declared at the
12561          module-level scope (J3/04-007, Section 15.3).  */
12562       if (sym->ns->proc_name->attr.flavor != FL_MODULE &&
12563           sym->attr.in_common == 0)
12564         {
12565           gfc_error ("Variable '%s' at %L cannot be BIND(C) because it "
12566                      "is neither a COMMON block nor declared at the "
12567                      "module level scope", sym->name, &(sym->declared_at));
12568           t = FAILURE;
12569         }
12570       else if (sym->common_head != NULL)
12571         {
12572           t = verify_com_block_vars_c_interop (sym->common_head);
12573         }
12574       else
12575         {
12576           /* If type() declaration, we need to verify that the components
12577              of the given type are all C interoperable, etc.  */
12578           if (sym->ts.type == BT_DERIVED &&
12579               sym->ts.u.derived->attr.is_c_interop != 1)
12580             {
12581               /* Make sure the user marked the derived type as BIND(C).  If
12582                  not, call the verify routine.  This could print an error
12583                  for the derived type more than once if multiple variables
12584                  of that type are declared.  */
12585               if (sym->ts.u.derived->attr.is_bind_c != 1)
12586                 verify_bind_c_derived_type (sym->ts.u.derived);
12587               t = FAILURE;
12588             }
12589           
12590           /* Verify the variable itself as C interoperable if it
12591              is BIND(C).  It is not possible for this to succeed if
12592              the verify_bind_c_derived_type failed, so don't have to handle
12593              any error returned by verify_bind_c_derived_type.  */
12594           t = verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
12595                                  sym->common_block);
12596         }
12597
12598       if (t == FAILURE)
12599         {
12600           /* clear the is_bind_c flag to prevent reporting errors more than
12601              once if something failed.  */
12602           sym->attr.is_bind_c = 0;
12603           return;
12604         }
12605     }
12606
12607   /* If a derived type symbol has reached this point, without its
12608      type being declared, we have an error.  Notice that most
12609      conditions that produce undefined derived types have already
12610      been dealt with.  However, the likes of:
12611      implicit type(t) (t) ..... call foo (t) will get us here if
12612      the type is not declared in the scope of the implicit
12613      statement. Change the type to BT_UNKNOWN, both because it is so
12614      and to prevent an ICE.  */
12615   if (sym->ts.type == BT_DERIVED && !sym->attr.is_iso_c
12616       && sym->ts.u.derived->components == NULL
12617       && !sym->ts.u.derived->attr.zero_comp)
12618     {
12619       gfc_error ("The derived type '%s' at %L is of type '%s', "
12620                  "which has not been defined", sym->name,
12621                   &sym->declared_at, sym->ts.u.derived->name);
12622       sym->ts.type = BT_UNKNOWN;
12623       return;
12624     }
12625
12626   /* Make sure that the derived type has been resolved and that the
12627      derived type is visible in the symbol's namespace, if it is a
12628      module function and is not PRIVATE.  */
12629   if (sym->ts.type == BT_DERIVED
12630         && sym->ts.u.derived->attr.use_assoc
12631         && sym->ns->proc_name
12632         && sym->ns->proc_name->attr.flavor == FL_MODULE
12633         && resolve_fl_derived (sym->ts.u.derived) == FAILURE)
12634     return;
12635
12636   /* Unless the derived-type declaration is use associated, Fortran 95
12637      does not allow public entries of private derived types.
12638      See 4.4.1 (F95) and 4.5.1.1 (F2003); and related interpretation
12639      161 in 95-006r3.  */
12640   if (sym->ts.type == BT_DERIVED
12641       && sym->ns->proc_name && sym->ns->proc_name->attr.flavor == FL_MODULE
12642       && !sym->ts.u.derived->attr.use_assoc
12643       && gfc_check_symbol_access (sym)
12644       && !gfc_check_symbol_access (sym->ts.u.derived)
12645       && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC %s '%s' at %L "
12646                          "of PRIVATE derived type '%s'",
12647                          (sym->attr.flavor == FL_PARAMETER) ? "parameter"
12648                          : "variable", sym->name, &sym->declared_at,
12649                          sym->ts.u.derived->name) == FAILURE)
12650     return;
12651
12652   /* F2008, C1302.  */
12653   if (sym->ts.type == BT_DERIVED
12654       && ((sym->ts.u.derived->from_intmod == INTMOD_ISO_FORTRAN_ENV
12655            && sym->ts.u.derived->intmod_sym_id == ISOFORTRAN_LOCK_TYPE)
12656           || sym->ts.u.derived->attr.lock_comp)
12657       && !sym->attr.codimension && !sym->ts.u.derived->attr.coarray_comp)
12658     {
12659       gfc_error ("Variable %s at %L of type LOCK_TYPE or with subcomponent of "
12660                  "type LOCK_TYPE must be a coarray", sym->name,
12661                  &sym->declared_at);
12662       return;
12663     }
12664
12665   /* An assumed-size array with INTENT(OUT) shall not be of a type for which
12666      default initialization is defined (5.1.2.4.4).  */
12667   if (sym->ts.type == BT_DERIVED
12668       && sym->attr.dummy
12669       && sym->attr.intent == INTENT_OUT
12670       && sym->as
12671       && sym->as->type == AS_ASSUMED_SIZE)
12672     {
12673       for (c = sym->ts.u.derived->components; c; c = c->next)
12674         {
12675           if (c->initializer)
12676             {
12677               gfc_error ("The INTENT(OUT) dummy argument '%s' at %L is "
12678                          "ASSUMED SIZE and so cannot have a default initializer",
12679                          sym->name, &sym->declared_at);
12680               return;
12681             }
12682         }
12683     }
12684
12685   /* F2008, C542.  */
12686   if (sym->ts.type == BT_DERIVED && sym->attr.dummy
12687       && sym->attr.intent == INTENT_OUT && sym->attr.lock_comp)
12688     {
12689       gfc_error ("Dummy argument '%s' at %L of LOCK_TYPE shall not be "
12690                  "INTENT(OUT)", sym->name, &sym->declared_at);
12691       return;
12692     }
12693
12694   /* F2008, C525.  */
12695   if ((((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
12696          || (sym->ts.type == BT_CLASS && sym->attr.class_ok
12697              && CLASS_DATA (sym)->attr.coarray_comp))
12698        || class_attr.codimension)
12699       && (sym->attr.result || sym->result == sym))
12700     {
12701       gfc_error ("Function result '%s' at %L shall not be a coarray or have "
12702                  "a coarray component", sym->name, &sym->declared_at);
12703       return;
12704     }
12705
12706   /* F2008, C524.  */
12707   if (sym->attr.codimension && sym->ts.type == BT_DERIVED
12708       && sym->ts.u.derived->ts.is_iso_c)
12709     {
12710       gfc_error ("Variable '%s' at %L of TYPE(C_PTR) or TYPE(C_FUNPTR) "
12711                  "shall not be a coarray", sym->name, &sym->declared_at);
12712       return;
12713     }
12714
12715   /* F2008, C525.  */
12716   if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
12717         || (sym->ts.type == BT_CLASS && sym->attr.class_ok
12718             && CLASS_DATA (sym)->attr.coarray_comp))
12719       && (class_attr.codimension || class_attr.pointer || class_attr.dimension
12720           || class_attr.allocatable))
12721     {
12722       gfc_error ("Variable '%s' at %L with coarray component "
12723                  "shall be a nonpointer, nonallocatable scalar",
12724                  sym->name, &sym->declared_at);
12725       return;
12726     }
12727
12728   /* F2008, C526.  The function-result case was handled above.  */
12729   if (class_attr.codimension
12730       && !(class_attr.allocatable || sym->attr.dummy || sym->attr.save
12731            || sym->attr.select_type_temporary
12732            || sym->ns->save_all
12733            || sym->ns->proc_name->attr.flavor == FL_MODULE
12734            || sym->ns->proc_name->attr.is_main_program
12735            || sym->attr.function || sym->attr.result || sym->attr.use_assoc))
12736     {
12737       gfc_error ("Variable '%s' at %L is a coarray and is not ALLOCATABLE, SAVE "
12738                  "nor a dummy argument", sym->name, &sym->declared_at);
12739       return;
12740     }
12741   /* F2008, C528.  */
12742   else if (class_attr.codimension && !sym->attr.select_type_temporary
12743            && !class_attr.allocatable && as && as->cotype == AS_DEFERRED)
12744     {
12745       gfc_error ("Coarray variable '%s' at %L shall not have codimensions with "
12746                  "deferred shape", sym->name, &sym->declared_at);
12747       return;
12748     }
12749   else if (class_attr.codimension && class_attr.allocatable && as
12750            && (as->cotype != AS_DEFERRED || as->type != AS_DEFERRED))
12751     {
12752       gfc_error ("Allocatable coarray variable '%s' at %L must have "
12753                  "deferred shape", sym->name, &sym->declared_at);
12754       return;
12755     }
12756
12757   /* F2008, C541.  */
12758   if ((((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
12759         || (sym->ts.type == BT_CLASS && sym->attr.class_ok
12760             && CLASS_DATA (sym)->attr.coarray_comp))
12761        || (class_attr.codimension && class_attr.allocatable))
12762       && sym->attr.dummy && sym->attr.intent == INTENT_OUT)
12763     {
12764       gfc_error ("Variable '%s' at %L is INTENT(OUT) and can thus not be an "
12765                  "allocatable coarray or have coarray components",
12766                  sym->name, &sym->declared_at);
12767       return;
12768     }
12769
12770   if (class_attr.codimension && sym->attr.dummy
12771       && sym->ns->proc_name && sym->ns->proc_name->attr.is_bind_c)
12772     {
12773       gfc_error ("Coarray dummy variable '%s' at %L not allowed in BIND(C) "
12774                  "procedure '%s'", sym->name, &sym->declared_at,
12775                  sym->ns->proc_name->name);
12776       return;
12777     }
12778
12779   switch (sym->attr.flavor)
12780     {
12781     case FL_VARIABLE:
12782       if (resolve_fl_variable (sym, mp_flag) == FAILURE)
12783         return;
12784       break;
12785
12786     case FL_PROCEDURE:
12787       if (resolve_fl_procedure (sym, mp_flag) == FAILURE)
12788         return;
12789       break;
12790
12791     case FL_NAMELIST:
12792       if (resolve_fl_namelist (sym) == FAILURE)
12793         return;
12794       break;
12795
12796     case FL_PARAMETER:
12797       if (resolve_fl_parameter (sym) == FAILURE)
12798         return;
12799       break;
12800
12801     default:
12802       break;
12803     }
12804
12805   /* Resolve array specifier. Check as well some constraints
12806      on COMMON blocks.  */
12807
12808   check_constant = sym->attr.in_common && !sym->attr.pointer;
12809
12810   /* Set the formal_arg_flag so that check_conflict will not throw
12811      an error for host associated variables in the specification
12812      expression for an array_valued function.  */
12813   if (sym->attr.function && sym->as)
12814     formal_arg_flag = 1;
12815
12816   gfc_resolve_array_spec (sym->as, check_constant);
12817
12818   formal_arg_flag = 0;
12819
12820   /* Resolve formal namespaces.  */
12821   if (sym->formal_ns && sym->formal_ns != gfc_current_ns
12822       && !sym->attr.contained && !sym->attr.intrinsic)
12823     gfc_resolve (sym->formal_ns);
12824
12825   /* Make sure the formal namespace is present.  */
12826   if (sym->formal && !sym->formal_ns)
12827     {
12828       gfc_formal_arglist *formal = sym->formal;
12829       while (formal && !formal->sym)
12830         formal = formal->next;
12831
12832       if (formal)
12833         {
12834           sym->formal_ns = formal->sym->ns;
12835           sym->formal_ns->refs++;
12836         }
12837     }
12838
12839   /* Check threadprivate restrictions.  */
12840   if (sym->attr.threadprivate && !sym->attr.save && !sym->ns->save_all
12841       && (!sym->attr.in_common
12842           && sym->module == NULL
12843           && (sym->ns->proc_name == NULL
12844               || sym->ns->proc_name->attr.flavor != FL_MODULE)))
12845     gfc_error ("Threadprivate at %L isn't SAVEd", &sym->declared_at);
12846
12847   /* If we have come this far we can apply default-initializers, as
12848      described in 14.7.5, to those variables that have not already
12849      been assigned one.  */
12850   if (sym->ts.type == BT_DERIVED
12851       && sym->ns == gfc_current_ns
12852       && !sym->value
12853       && !sym->attr.allocatable
12854       && !sym->attr.alloc_comp)
12855     {
12856       symbol_attribute *a = &sym->attr;
12857
12858       if ((!a->save && !a->dummy && !a->pointer
12859            && !a->in_common && !a->use_assoc
12860            && (a->referenced || a->result)
12861            && !(a->function && sym != sym->result))
12862           || (a->dummy && a->intent == INTENT_OUT && !a->pointer))
12863         apply_default_init (sym);
12864     }
12865
12866   if (sym->ts.type == BT_CLASS && sym->ns == gfc_current_ns
12867       && sym->attr.dummy && sym->attr.intent == INTENT_OUT
12868       && !CLASS_DATA (sym)->attr.class_pointer
12869       && !CLASS_DATA (sym)->attr.allocatable)
12870     apply_default_init (sym);
12871
12872   /* If this symbol has a type-spec, check it.  */
12873   if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER
12874       || (sym->attr.flavor == FL_PROCEDURE && sym->attr.function))
12875     if (resolve_typespec_used (&sym->ts, &sym->declared_at, sym->name)
12876           == FAILURE)
12877       return;
12878 }
12879
12880
12881 /************* Resolve DATA statements *************/
12882
12883 static struct
12884 {
12885   gfc_data_value *vnode;
12886   mpz_t left;
12887 }
12888 values;
12889
12890
12891 /* Advance the values structure to point to the next value in the data list.  */
12892
12893 static gfc_try
12894 next_data_value (void)
12895 {
12896   while (mpz_cmp_ui (values.left, 0) == 0)
12897     {
12898
12899       if (values.vnode->next == NULL)
12900         return FAILURE;
12901
12902       values.vnode = values.vnode->next;
12903       mpz_set (values.left, values.vnode->repeat);
12904     }
12905
12906   return SUCCESS;
12907 }
12908
12909
12910 static gfc_try
12911 check_data_variable (gfc_data_variable *var, locus *where)
12912 {
12913   gfc_expr *e;
12914   mpz_t size;
12915   mpz_t offset;
12916   gfc_try t;
12917   ar_type mark = AR_UNKNOWN;
12918   int i;
12919   mpz_t section_index[GFC_MAX_DIMENSIONS];
12920   gfc_ref *ref;
12921   gfc_array_ref *ar;
12922   gfc_symbol *sym;
12923   int has_pointer;
12924
12925   if (gfc_resolve_expr (var->expr) == FAILURE)
12926     return FAILURE;
12927
12928   ar = NULL;
12929   mpz_init_set_si (offset, 0);
12930   e = var->expr;
12931
12932   if (e->expr_type != EXPR_VARIABLE)
12933     gfc_internal_error ("check_data_variable(): Bad expression");
12934
12935   sym = e->symtree->n.sym;
12936
12937   if (sym->ns->is_block_data && !sym->attr.in_common)
12938     {
12939       gfc_error ("BLOCK DATA element '%s' at %L must be in COMMON",
12940                  sym->name, &sym->declared_at);
12941     }
12942
12943   if (e->ref == NULL && sym->as)
12944     {
12945       gfc_error ("DATA array '%s' at %L must be specified in a previous"
12946                  " declaration", sym->name, where);
12947       return FAILURE;
12948     }
12949
12950   has_pointer = sym->attr.pointer;
12951
12952   if (gfc_is_coindexed (e))
12953     {
12954       gfc_error ("DATA element '%s' at %L cannot have a coindex", sym->name,
12955                  where);
12956       return FAILURE;
12957     }
12958
12959   for (ref = e->ref; ref; ref = ref->next)
12960     {
12961       if (ref->type == REF_COMPONENT && ref->u.c.component->attr.pointer)
12962         has_pointer = 1;
12963
12964       if (has_pointer
12965             && ref->type == REF_ARRAY
12966             && ref->u.ar.type != AR_FULL)
12967           {
12968             gfc_error ("DATA element '%s' at %L is a pointer and so must "
12969                         "be a full array", sym->name, where);
12970             return FAILURE;
12971           }
12972     }
12973
12974   if (e->rank == 0 || has_pointer)
12975     {
12976       mpz_init_set_ui (size, 1);
12977       ref = NULL;
12978     }
12979   else
12980     {
12981       ref = e->ref;
12982
12983       /* Find the array section reference.  */
12984       for (ref = e->ref; ref; ref = ref->next)
12985         {
12986           if (ref->type != REF_ARRAY)
12987             continue;
12988           if (ref->u.ar.type == AR_ELEMENT)
12989             continue;
12990           break;
12991         }
12992       gcc_assert (ref);
12993
12994       /* Set marks according to the reference pattern.  */
12995       switch (ref->u.ar.type)
12996         {
12997         case AR_FULL:
12998           mark = AR_FULL;
12999           break;
13000
13001         case AR_SECTION:
13002           ar = &ref->u.ar;
13003           /* Get the start position of array section.  */
13004           gfc_get_section_index (ar, section_index, &offset);
13005           mark = AR_SECTION;
13006           break;
13007
13008         default:
13009           gcc_unreachable ();
13010         }
13011
13012       if (gfc_array_size (e, &size) == FAILURE)
13013         {
13014           gfc_error ("Nonconstant array section at %L in DATA statement",
13015                      &e->where);
13016           mpz_clear (offset);
13017           return FAILURE;
13018         }
13019     }
13020
13021   t = SUCCESS;
13022
13023   while (mpz_cmp_ui (size, 0) > 0)
13024     {
13025       if (next_data_value () == FAILURE)
13026         {
13027           gfc_error ("DATA statement at %L has more variables than values",
13028                      where);
13029           t = FAILURE;
13030           break;
13031         }
13032
13033       t = gfc_check_assign (var->expr, values.vnode->expr, 0);
13034       if (t == FAILURE)
13035         break;
13036
13037       /* If we have more than one element left in the repeat count,
13038          and we have more than one element left in the target variable,
13039          then create a range assignment.  */
13040       /* FIXME: Only done for full arrays for now, since array sections
13041          seem tricky.  */
13042       if (mark == AR_FULL && ref && ref->next == NULL
13043           && mpz_cmp_ui (values.left, 1) > 0 && mpz_cmp_ui (size, 1) > 0)
13044         {
13045           mpz_t range;
13046
13047           if (mpz_cmp (size, values.left) >= 0)
13048             {
13049               mpz_init_set (range, values.left);
13050               mpz_sub (size, size, values.left);
13051               mpz_set_ui (values.left, 0);
13052             }
13053           else
13054             {
13055               mpz_init_set (range, size);
13056               mpz_sub (values.left, values.left, size);
13057               mpz_set_ui (size, 0);
13058             }
13059
13060           t = gfc_assign_data_value (var->expr, values.vnode->expr,
13061                                      offset, &range);
13062
13063           mpz_add (offset, offset, range);
13064           mpz_clear (range);
13065
13066           if (t == FAILURE)
13067             break;
13068         }
13069
13070       /* Assign initial value to symbol.  */
13071       else
13072         {
13073           mpz_sub_ui (values.left, values.left, 1);
13074           mpz_sub_ui (size, size, 1);
13075
13076           t = gfc_assign_data_value (var->expr, values.vnode->expr,
13077                                      offset, NULL);
13078           if (t == FAILURE)
13079             break;
13080
13081           if (mark == AR_FULL)
13082             mpz_add_ui (offset, offset, 1);
13083
13084           /* Modify the array section indexes and recalculate the offset
13085              for next element.  */
13086           else if (mark == AR_SECTION)
13087             gfc_advance_section (section_index, ar, &offset);
13088         }
13089     }
13090
13091   if (mark == AR_SECTION)
13092     {
13093       for (i = 0; i < ar->dimen; i++)
13094         mpz_clear (section_index[i]);
13095     }
13096
13097   mpz_clear (size);
13098   mpz_clear (offset);
13099
13100   return t;
13101 }
13102
13103
13104 static gfc_try traverse_data_var (gfc_data_variable *, locus *);
13105
13106 /* Iterate over a list of elements in a DATA statement.  */
13107
13108 static gfc_try
13109 traverse_data_list (gfc_data_variable *var, locus *where)
13110 {
13111   mpz_t trip;
13112   iterator_stack frame;
13113   gfc_expr *e, *start, *end, *step;
13114   gfc_try retval = SUCCESS;
13115
13116   mpz_init (frame.value);
13117   mpz_init (trip);
13118
13119   start = gfc_copy_expr (var->iter.start);
13120   end = gfc_copy_expr (var->iter.end);
13121   step = gfc_copy_expr (var->iter.step);
13122
13123   if (gfc_simplify_expr (start, 1) == FAILURE
13124       || start->expr_type != EXPR_CONSTANT)
13125     {
13126       gfc_error ("start of implied-do loop at %L could not be "
13127                  "simplified to a constant value", &start->where);
13128       retval = FAILURE;
13129       goto cleanup;
13130     }
13131   if (gfc_simplify_expr (end, 1) == FAILURE
13132       || end->expr_type != EXPR_CONSTANT)
13133     {
13134       gfc_error ("end of implied-do loop at %L could not be "
13135                  "simplified to a constant value", &start->where);
13136       retval = FAILURE;
13137       goto cleanup;
13138     }
13139   if (gfc_simplify_expr (step, 1) == FAILURE
13140       || step->expr_type != EXPR_CONSTANT)
13141     {
13142       gfc_error ("step of implied-do loop at %L could not be "
13143                  "simplified to a constant value", &start->where);
13144       retval = FAILURE;
13145       goto cleanup;
13146     }
13147
13148   mpz_set (trip, end->value.integer);
13149   mpz_sub (trip, trip, start->value.integer);
13150   mpz_add (trip, trip, step->value.integer);
13151
13152   mpz_div (trip, trip, step->value.integer);
13153
13154   mpz_set (frame.value, start->value.integer);
13155
13156   frame.prev = iter_stack;
13157   frame.variable = var->iter.var->symtree;
13158   iter_stack = &frame;
13159
13160   while (mpz_cmp_ui (trip, 0) > 0)
13161     {
13162       if (traverse_data_var (var->list, where) == FAILURE)
13163         {
13164           retval = FAILURE;
13165           goto cleanup;
13166         }
13167
13168       e = gfc_copy_expr (var->expr);
13169       if (gfc_simplify_expr (e, 1) == FAILURE)
13170         {
13171           gfc_free_expr (e);
13172           retval = FAILURE;
13173           goto cleanup;
13174         }
13175
13176       mpz_add (frame.value, frame.value, step->value.integer);
13177
13178       mpz_sub_ui (trip, trip, 1);
13179     }
13180
13181 cleanup:
13182   mpz_clear (frame.value);
13183   mpz_clear (trip);
13184
13185   gfc_free_expr (start);
13186   gfc_free_expr (end);
13187   gfc_free_expr (step);
13188
13189   iter_stack = frame.prev;
13190   return retval;
13191 }
13192
13193
13194 /* Type resolve variables in the variable list of a DATA statement.  */
13195
13196 static gfc_try
13197 traverse_data_var (gfc_data_variable *var, locus *where)
13198 {
13199   gfc_try t;
13200
13201   for (; var; var = var->next)
13202     {
13203       if (var->expr == NULL)
13204         t = traverse_data_list (var, where);
13205       else
13206         t = check_data_variable (var, where);
13207
13208       if (t == FAILURE)
13209         return FAILURE;
13210     }
13211
13212   return SUCCESS;
13213 }
13214
13215
13216 /* Resolve the expressions and iterators associated with a data statement.
13217    This is separate from the assignment checking because data lists should
13218    only be resolved once.  */
13219
13220 static gfc_try
13221 resolve_data_variables (gfc_data_variable *d)
13222 {
13223   for (; d; d = d->next)
13224     {
13225       if (d->list == NULL)
13226         {
13227           if (gfc_resolve_expr (d->expr) == FAILURE)
13228             return FAILURE;
13229         }
13230       else
13231         {
13232           if (gfc_resolve_iterator (&d->iter, false) == FAILURE)
13233             return FAILURE;
13234
13235           if (resolve_data_variables (d->list) == FAILURE)
13236             return FAILURE;
13237         }
13238     }
13239
13240   return SUCCESS;
13241 }
13242
13243
13244 /* Resolve a single DATA statement.  We implement this by storing a pointer to
13245    the value list into static variables, and then recursively traversing the
13246    variables list, expanding iterators and such.  */
13247
13248 static void
13249 resolve_data (gfc_data *d)
13250 {
13251
13252   if (resolve_data_variables (d->var) == FAILURE)
13253     return;
13254
13255   values.vnode = d->value;
13256   if (d->value == NULL)
13257     mpz_set_ui (values.left, 0);
13258   else
13259     mpz_set (values.left, d->value->repeat);
13260
13261   if (traverse_data_var (d->var, &d->where) == FAILURE)
13262     return;
13263
13264   /* At this point, we better not have any values left.  */
13265
13266   if (next_data_value () == SUCCESS)
13267     gfc_error ("DATA statement at %L has more values than variables",
13268                &d->where);
13269 }
13270
13271
13272 /* 12.6 Constraint: In a pure subprogram any variable which is in common or
13273    accessed by host or use association, is a dummy argument to a pure function,
13274    is a dummy argument with INTENT (IN) to a pure subroutine, or an object that
13275    is storage associated with any such variable, shall not be used in the
13276    following contexts: (clients of this function).  */
13277
13278 /* Determines if a variable is not 'pure', i.e., not assignable within a pure
13279    procedure.  Returns zero if assignment is OK, nonzero if there is a
13280    problem.  */
13281 int
13282 gfc_impure_variable (gfc_symbol *sym)
13283 {
13284   gfc_symbol *proc;
13285   gfc_namespace *ns;
13286
13287   if (sym->attr.use_assoc || sym->attr.in_common)
13288     return 1;
13289
13290   /* Check if the symbol's ns is inside the pure procedure.  */
13291   for (ns = gfc_current_ns; ns; ns = ns->parent)
13292     {
13293       if (ns == sym->ns)
13294         break;
13295       if (ns->proc_name->attr.flavor == FL_PROCEDURE && !sym->attr.function)
13296         return 1;
13297     }
13298
13299   proc = sym->ns->proc_name;
13300   if (sym->attr.dummy && gfc_pure (proc)
13301         && ((proc->attr.subroutine && sym->attr.intent == INTENT_IN)
13302                 ||
13303              proc->attr.function))
13304     return 1;
13305
13306   /* TODO: Sort out what can be storage associated, if anything, and include
13307      it here.  In principle equivalences should be scanned but it does not
13308      seem to be possible to storage associate an impure variable this way.  */
13309   return 0;
13310 }
13311
13312
13313 /* Test whether a symbol is pure or not.  For a NULL pointer, checks if the
13314    current namespace is inside a pure procedure.  */
13315
13316 int
13317 gfc_pure (gfc_symbol *sym)
13318 {
13319   symbol_attribute attr;
13320   gfc_namespace *ns;
13321
13322   if (sym == NULL)
13323     {
13324       /* Check if the current namespace or one of its parents
13325         belongs to a pure procedure.  */
13326       for (ns = gfc_current_ns; ns; ns = ns->parent)
13327         {
13328           sym = ns->proc_name;
13329           if (sym == NULL)
13330             return 0;
13331           attr = sym->attr;
13332           if (attr.flavor == FL_PROCEDURE && attr.pure)
13333             return 1;
13334         }
13335       return 0;
13336     }
13337
13338   attr = sym->attr;
13339
13340   return attr.flavor == FL_PROCEDURE && attr.pure;
13341 }
13342
13343
13344 /* Test whether a symbol is implicitly pure or not.  For a NULL pointer,
13345    checks if the current namespace is implicitly pure.  Note that this
13346    function returns false for a PURE procedure.  */
13347
13348 int
13349 gfc_implicit_pure (gfc_symbol *sym)
13350 {
13351   gfc_namespace *ns;
13352
13353   if (sym == NULL)
13354     {
13355       /* Check if the current procedure is implicit_pure.  Walk up
13356          the procedure list until we find a procedure.  */
13357       for (ns = gfc_current_ns; ns; ns = ns->parent)
13358         {
13359           sym = ns->proc_name;
13360           if (sym == NULL)
13361             return 0;
13362           
13363           if (sym->attr.flavor == FL_PROCEDURE)
13364             break;
13365         }
13366     }
13367   
13368   return sym->attr.flavor == FL_PROCEDURE && sym->attr.implicit_pure
13369     && !sym->attr.pure;
13370 }
13371
13372
13373 /* Test whether the current procedure is elemental or not.  */
13374
13375 int
13376 gfc_elemental (gfc_symbol *sym)
13377 {
13378   symbol_attribute attr;
13379
13380   if (sym == NULL)
13381     sym = gfc_current_ns->proc_name;
13382   if (sym == NULL)
13383     return 0;
13384   attr = sym->attr;
13385
13386   return attr.flavor == FL_PROCEDURE && attr.elemental;
13387 }
13388
13389
13390 /* Warn about unused labels.  */
13391
13392 static void
13393 warn_unused_fortran_label (gfc_st_label *label)
13394 {
13395   if (label == NULL)
13396     return;
13397
13398   warn_unused_fortran_label (label->left);
13399
13400   if (label->defined == ST_LABEL_UNKNOWN)
13401     return;
13402
13403   switch (label->referenced)
13404     {
13405     case ST_LABEL_UNKNOWN:
13406       gfc_warning ("Label %d at %L defined but not used", label->value,
13407                    &label->where);
13408       break;
13409
13410     case ST_LABEL_BAD_TARGET:
13411       gfc_warning ("Label %d at %L defined but cannot be used",
13412                    label->value, &label->where);
13413       break;
13414
13415     default:
13416       break;
13417     }
13418
13419   warn_unused_fortran_label (label->right);
13420 }
13421
13422
13423 /* Returns the sequence type of a symbol or sequence.  */
13424
13425 static seq_type
13426 sequence_type (gfc_typespec ts)
13427 {
13428   seq_type result;
13429   gfc_component *c;
13430
13431   switch (ts.type)
13432   {
13433     case BT_DERIVED:
13434
13435       if (ts.u.derived->components == NULL)
13436         return SEQ_NONDEFAULT;
13437
13438       result = sequence_type (ts.u.derived->components->ts);
13439       for (c = ts.u.derived->components->next; c; c = c->next)
13440         if (sequence_type (c->ts) != result)
13441           return SEQ_MIXED;
13442
13443       return result;
13444
13445     case BT_CHARACTER:
13446       if (ts.kind != gfc_default_character_kind)
13447           return SEQ_NONDEFAULT;
13448
13449       return SEQ_CHARACTER;
13450
13451     case BT_INTEGER:
13452       if (ts.kind != gfc_default_integer_kind)
13453           return SEQ_NONDEFAULT;
13454
13455       return SEQ_NUMERIC;
13456
13457     case BT_REAL:
13458       if (!(ts.kind == gfc_default_real_kind
13459             || ts.kind == gfc_default_double_kind))
13460           return SEQ_NONDEFAULT;
13461
13462       return SEQ_NUMERIC;
13463
13464     case BT_COMPLEX:
13465       if (ts.kind != gfc_default_complex_kind)
13466           return SEQ_NONDEFAULT;
13467
13468       return SEQ_NUMERIC;
13469
13470     case BT_LOGICAL:
13471       if (ts.kind != gfc_default_logical_kind)
13472           return SEQ_NONDEFAULT;
13473
13474       return SEQ_NUMERIC;
13475
13476     default:
13477       return SEQ_NONDEFAULT;
13478   }
13479 }
13480
13481
13482 /* Resolve derived type EQUIVALENCE object.  */
13483
13484 static gfc_try
13485 resolve_equivalence_derived (gfc_symbol *derived, gfc_symbol *sym, gfc_expr *e)
13486 {
13487   gfc_component *c = derived->components;
13488
13489   if (!derived)
13490     return SUCCESS;
13491
13492   /* Shall not be an object of nonsequence derived type.  */
13493   if (!derived->attr.sequence)
13494     {
13495       gfc_error ("Derived type variable '%s' at %L must have SEQUENCE "
13496                  "attribute to be an EQUIVALENCE object", sym->name,
13497                  &e->where);
13498       return FAILURE;
13499     }
13500
13501   /* Shall not have allocatable components.  */
13502   if (derived->attr.alloc_comp)
13503     {
13504       gfc_error ("Derived type variable '%s' at %L cannot have ALLOCATABLE "
13505                  "components to be an EQUIVALENCE object",sym->name,
13506                  &e->where);
13507       return FAILURE;
13508     }
13509
13510   if (sym->attr.in_common && gfc_has_default_initializer (sym->ts.u.derived))
13511     {
13512       gfc_error ("Derived type variable '%s' at %L with default "
13513                  "initialization cannot be in EQUIVALENCE with a variable "
13514                  "in COMMON", sym->name, &e->where);
13515       return FAILURE;
13516     }
13517
13518   for (; c ; c = c->next)
13519     {
13520       if (c->ts.type == BT_DERIVED
13521           && (resolve_equivalence_derived (c->ts.u.derived, sym, e) == FAILURE))
13522         return FAILURE;
13523
13524       /* Shall not be an object of sequence derived type containing a pointer
13525          in the structure.  */
13526       if (c->attr.pointer)
13527         {
13528           gfc_error ("Derived type variable '%s' at %L with pointer "
13529                      "component(s) cannot be an EQUIVALENCE object",
13530                      sym->name, &e->where);
13531           return FAILURE;
13532         }
13533     }
13534   return SUCCESS;
13535 }
13536
13537
13538 /* Resolve equivalence object. 
13539    An EQUIVALENCE object shall not be a dummy argument, a pointer, a target,
13540    an allocatable array, an object of nonsequence derived type, an object of
13541    sequence derived type containing a pointer at any level of component
13542    selection, an automatic object, a function name, an entry name, a result
13543    name, a named constant, a structure component, or a subobject of any of
13544    the preceding objects.  A substring shall not have length zero.  A
13545    derived type shall not have components with default initialization nor
13546    shall two objects of an equivalence group be initialized.
13547    Either all or none of the objects shall have an protected attribute.
13548    The simple constraints are done in symbol.c(check_conflict) and the rest
13549    are implemented here.  */
13550
13551 static void
13552 resolve_equivalence (gfc_equiv *eq)
13553 {
13554   gfc_symbol *sym;
13555   gfc_symbol *first_sym;
13556   gfc_expr *e;
13557   gfc_ref *r;
13558   locus *last_where = NULL;
13559   seq_type eq_type, last_eq_type;
13560   gfc_typespec *last_ts;
13561   int object, cnt_protected;
13562   const char *msg;
13563
13564   last_ts = &eq->expr->symtree->n.sym->ts;
13565
13566   first_sym = eq->expr->symtree->n.sym;
13567
13568   cnt_protected = 0;
13569
13570   for (object = 1; eq; eq = eq->eq, object++)
13571     {
13572       e = eq->expr;
13573
13574       e->ts = e->symtree->n.sym->ts;
13575       /* match_varspec might not know yet if it is seeing
13576          array reference or substring reference, as it doesn't
13577          know the types.  */
13578       if (e->ref && e->ref->type == REF_ARRAY)
13579         {
13580           gfc_ref *ref = e->ref;
13581           sym = e->symtree->n.sym;
13582
13583           if (sym->attr.dimension)
13584             {
13585               ref->u.ar.as = sym->as;
13586               ref = ref->next;
13587             }
13588
13589           /* For substrings, convert REF_ARRAY into REF_SUBSTRING.  */
13590           if (e->ts.type == BT_CHARACTER
13591               && ref
13592               && ref->type == REF_ARRAY
13593               && ref->u.ar.dimen == 1
13594               && ref->u.ar.dimen_type[0] == DIMEN_RANGE
13595               && ref->u.ar.stride[0] == NULL)
13596             {
13597               gfc_expr *start = ref->u.ar.start[0];
13598               gfc_expr *end = ref->u.ar.end[0];
13599               void *mem = NULL;
13600
13601               /* Optimize away the (:) reference.  */
13602               if (start == NULL && end == NULL)
13603                 {
13604                   if (e->ref == ref)
13605                     e->ref = ref->next;
13606                   else
13607                     e->ref->next = ref->next;
13608                   mem = ref;
13609                 }
13610               else
13611                 {
13612                   ref->type = REF_SUBSTRING;
13613                   if (start == NULL)
13614                     start = gfc_get_int_expr (gfc_default_integer_kind,
13615                                               NULL, 1);
13616                   ref->u.ss.start = start;
13617                   if (end == NULL && e->ts.u.cl)
13618                     end = gfc_copy_expr (e->ts.u.cl->length);
13619                   ref->u.ss.end = end;
13620                   ref->u.ss.length = e->ts.u.cl;
13621                   e->ts.u.cl = NULL;
13622                 }
13623               ref = ref->next;
13624               free (mem);
13625             }
13626
13627           /* Any further ref is an error.  */
13628           if (ref)
13629             {
13630               gcc_assert (ref->type == REF_ARRAY);
13631               gfc_error ("Syntax error in EQUIVALENCE statement at %L",
13632                          &ref->u.ar.where);
13633               continue;
13634             }
13635         }
13636
13637       if (gfc_resolve_expr (e) == FAILURE)
13638         continue;
13639
13640       sym = e->symtree->n.sym;
13641
13642       if (sym->attr.is_protected)
13643         cnt_protected++;
13644       if (cnt_protected > 0 && cnt_protected != object)
13645         {
13646               gfc_error ("Either all or none of the objects in the "
13647                          "EQUIVALENCE set at %L shall have the "
13648                          "PROTECTED attribute",
13649                          &e->where);
13650               break;
13651         }
13652
13653       /* Shall not equivalence common block variables in a PURE procedure.  */
13654       if (sym->ns->proc_name
13655           && sym->ns->proc_name->attr.pure
13656           && sym->attr.in_common)
13657         {
13658           gfc_error ("Common block member '%s' at %L cannot be an EQUIVALENCE "
13659                      "object in the pure procedure '%s'",
13660                      sym->name, &e->where, sym->ns->proc_name->name);
13661           break;
13662         }
13663
13664       /* Shall not be a named constant.  */
13665       if (e->expr_type == EXPR_CONSTANT)
13666         {
13667           gfc_error ("Named constant '%s' at %L cannot be an EQUIVALENCE "
13668                      "object", sym->name, &e->where);
13669           continue;
13670         }
13671
13672       if (e->ts.type == BT_DERIVED
13673           && resolve_equivalence_derived (e->ts.u.derived, sym, e) == FAILURE)
13674         continue;
13675
13676       /* Check that the types correspond correctly:
13677          Note 5.28:
13678          A numeric sequence structure may be equivalenced to another sequence
13679          structure, an object of default integer type, default real type, double
13680          precision real type, default logical type such that components of the
13681          structure ultimately only become associated to objects of the same
13682          kind. A character sequence structure may be equivalenced to an object
13683          of default character kind or another character sequence structure.
13684          Other objects may be equivalenced only to objects of the same type and
13685          kind parameters.  */
13686
13687       /* Identical types are unconditionally OK.  */
13688       if (object == 1 || gfc_compare_types (last_ts, &sym->ts))
13689         goto identical_types;
13690
13691       last_eq_type = sequence_type (*last_ts);
13692       eq_type = sequence_type (sym->ts);
13693
13694       /* Since the pair of objects is not of the same type, mixed or
13695          non-default sequences can be rejected.  */
13696
13697       msg = "Sequence %s with mixed components in EQUIVALENCE "
13698             "statement at %L with different type objects";
13699       if ((object ==2
13700            && last_eq_type == SEQ_MIXED
13701            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name, last_where)
13702               == FAILURE)
13703           || (eq_type == SEQ_MIXED
13704               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13705                                  &e->where) == FAILURE))
13706         continue;
13707
13708       msg = "Non-default type object or sequence %s in EQUIVALENCE "
13709             "statement at %L with objects of different type";
13710       if ((object ==2
13711            && last_eq_type == SEQ_NONDEFAULT
13712            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name,
13713                               last_where) == FAILURE)
13714           || (eq_type == SEQ_NONDEFAULT
13715               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13716                                  &e->where) == FAILURE))
13717         continue;
13718
13719       msg ="Non-CHARACTER object '%s' in default CHARACTER "
13720            "EQUIVALENCE statement at %L";
13721       if (last_eq_type == SEQ_CHARACTER
13722           && eq_type != SEQ_CHARACTER
13723           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13724                              &e->where) == FAILURE)
13725                 continue;
13726
13727       msg ="Non-NUMERIC object '%s' in default NUMERIC "
13728            "EQUIVALENCE statement at %L";
13729       if (last_eq_type == SEQ_NUMERIC
13730           && eq_type != SEQ_NUMERIC
13731           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13732                              &e->where) == FAILURE)
13733                 continue;
13734
13735   identical_types:
13736       last_ts =&sym->ts;
13737       last_where = &e->where;
13738
13739       if (!e->ref)
13740         continue;
13741
13742       /* Shall not be an automatic array.  */
13743       if (e->ref->type == REF_ARRAY
13744           && gfc_resolve_array_spec (e->ref->u.ar.as, 1) == FAILURE)
13745         {
13746           gfc_error ("Array '%s' at %L with non-constant bounds cannot be "
13747                      "an EQUIVALENCE object", sym->name, &e->where);
13748           continue;
13749         }
13750
13751       r = e->ref;
13752       while (r)
13753         {
13754           /* Shall not be a structure component.  */
13755           if (r->type == REF_COMPONENT)
13756             {
13757               gfc_error ("Structure component '%s' at %L cannot be an "
13758                          "EQUIVALENCE object",
13759                          r->u.c.component->name, &e->where);
13760               break;
13761             }
13762
13763           /* A substring shall not have length zero.  */
13764           if (r->type == REF_SUBSTRING)
13765             {
13766               if (compare_bound (r->u.ss.start, r->u.ss.end) == CMP_GT)
13767                 {
13768                   gfc_error ("Substring at %L has length zero",
13769                              &r->u.ss.start->where);
13770                   break;
13771                 }
13772             }
13773           r = r->next;
13774         }
13775     }
13776 }
13777
13778
13779 /* Resolve function and ENTRY types, issue diagnostics if needed.  */
13780
13781 static void
13782 resolve_fntype (gfc_namespace *ns)
13783 {
13784   gfc_entry_list *el;
13785   gfc_symbol *sym;
13786
13787   if (ns->proc_name == NULL || !ns->proc_name->attr.function)
13788     return;
13789
13790   /* If there are any entries, ns->proc_name is the entry master
13791      synthetic symbol and ns->entries->sym actual FUNCTION symbol.  */
13792   if (ns->entries)
13793     sym = ns->entries->sym;
13794   else
13795     sym = ns->proc_name;
13796   if (sym->result == sym
13797       && sym->ts.type == BT_UNKNOWN
13798       && gfc_set_default_type (sym, 0, NULL) == FAILURE
13799       && !sym->attr.untyped)
13800     {
13801       gfc_error ("Function '%s' at %L has no IMPLICIT type",
13802                  sym->name, &sym->declared_at);
13803       sym->attr.untyped = 1;
13804     }
13805
13806   if (sym->ts.type == BT_DERIVED && !sym->ts.u.derived->attr.use_assoc
13807       && !sym->attr.contained
13808       && !gfc_check_symbol_access (sym->ts.u.derived)
13809       && gfc_check_symbol_access (sym))
13810     {
13811       gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC function '%s' at "
13812                       "%L of PRIVATE type '%s'", sym->name,
13813                       &sym->declared_at, sym->ts.u.derived->name);
13814     }
13815
13816     if (ns->entries)
13817     for (el = ns->entries->next; el; el = el->next)
13818       {
13819         if (el->sym->result == el->sym
13820             && el->sym->ts.type == BT_UNKNOWN
13821             && gfc_set_default_type (el->sym, 0, NULL) == FAILURE
13822             && !el->sym->attr.untyped)
13823           {
13824             gfc_error ("ENTRY '%s' at %L has no IMPLICIT type",
13825                        el->sym->name, &el->sym->declared_at);
13826             el->sym->attr.untyped = 1;
13827           }
13828       }
13829 }
13830
13831
13832 /* 12.3.2.1.1 Defined operators.  */
13833
13834 static gfc_try
13835 check_uop_procedure (gfc_symbol *sym, locus where)
13836 {
13837   gfc_formal_arglist *formal;
13838
13839   if (!sym->attr.function)
13840     {
13841       gfc_error ("User operator procedure '%s' at %L must be a FUNCTION",
13842                  sym->name, &where);
13843       return FAILURE;
13844     }
13845
13846   if (sym->ts.type == BT_CHARACTER
13847       && !(sym->ts.u.cl && sym->ts.u.cl->length)
13848       && !(sym->result && sym->result->ts.u.cl
13849            && sym->result->ts.u.cl->length))
13850     {
13851       gfc_error ("User operator procedure '%s' at %L cannot be assumed "
13852                  "character length", sym->name, &where);
13853       return FAILURE;
13854     }
13855
13856   formal = sym->formal;
13857   if (!formal || !formal->sym)
13858     {
13859       gfc_error ("User operator procedure '%s' at %L must have at least "
13860                  "one argument", sym->name, &where);
13861       return FAILURE;
13862     }
13863
13864   if (formal->sym->attr.intent != INTENT_IN)
13865     {
13866       gfc_error ("First argument of operator interface at %L must be "
13867                  "INTENT(IN)", &where);
13868       return FAILURE;
13869     }
13870
13871   if (formal->sym->attr.optional)
13872     {
13873       gfc_error ("First argument of operator interface at %L cannot be "
13874                  "optional", &where);
13875       return FAILURE;
13876     }
13877
13878   formal = formal->next;
13879   if (!formal || !formal->sym)
13880     return SUCCESS;
13881
13882   if (formal->sym->attr.intent != INTENT_IN)
13883     {
13884       gfc_error ("Second argument of operator interface at %L must be "
13885                  "INTENT(IN)", &where);
13886       return FAILURE;
13887     }
13888
13889   if (formal->sym->attr.optional)
13890     {
13891       gfc_error ("Second argument of operator interface at %L cannot be "
13892                  "optional", &where);
13893       return FAILURE;
13894     }
13895
13896   if (formal->next)
13897     {
13898       gfc_error ("Operator interface at %L must have, at most, two "
13899                  "arguments", &where);
13900       return FAILURE;
13901     }
13902
13903   return SUCCESS;
13904 }
13905
13906 static void
13907 gfc_resolve_uops (gfc_symtree *symtree)
13908 {
13909   gfc_interface *itr;
13910
13911   if (symtree == NULL)
13912     return;
13913
13914   gfc_resolve_uops (symtree->left);
13915   gfc_resolve_uops (symtree->right);
13916
13917   for (itr = symtree->n.uop->op; itr; itr = itr->next)
13918     check_uop_procedure (itr->sym, itr->sym->declared_at);
13919 }
13920
13921
13922 /* Examine all of the expressions associated with a program unit,
13923    assign types to all intermediate expressions, make sure that all
13924    assignments are to compatible types and figure out which names
13925    refer to which functions or subroutines.  It doesn't check code
13926    block, which is handled by resolve_code.  */
13927
13928 static void
13929 resolve_types (gfc_namespace *ns)
13930 {
13931   gfc_namespace *n;
13932   gfc_charlen *cl;
13933   gfc_data *d;
13934   gfc_equiv *eq;
13935   gfc_namespace* old_ns = gfc_current_ns;
13936
13937   /* Check that all IMPLICIT types are ok.  */
13938   if (!ns->seen_implicit_none)
13939     {
13940       unsigned letter;
13941       for (letter = 0; letter != GFC_LETTERS; ++letter)
13942         if (ns->set_flag[letter]
13943             && resolve_typespec_used (&ns->default_type[letter],
13944                                       &ns->implicit_loc[letter],
13945                                       NULL) == FAILURE)
13946           return;
13947     }
13948
13949   gfc_current_ns = ns;
13950
13951   resolve_entries (ns);
13952
13953   resolve_common_vars (ns->blank_common.head, false);
13954   resolve_common_blocks (ns->common_root);
13955
13956   resolve_contained_functions (ns);
13957
13958   if (ns->proc_name && ns->proc_name->attr.flavor == FL_PROCEDURE
13959       && ns->proc_name->attr.if_source == IFSRC_IFBODY)
13960     resolve_formal_arglist (ns->proc_name);
13961
13962   gfc_traverse_ns (ns, resolve_bind_c_derived_types);
13963
13964   for (cl = ns->cl_list; cl; cl = cl->next)
13965     resolve_charlen (cl);
13966
13967   gfc_traverse_ns (ns, resolve_symbol);
13968
13969   resolve_fntype (ns);
13970
13971   for (n = ns->contained; n; n = n->sibling)
13972     {
13973       if (gfc_pure (ns->proc_name) && !gfc_pure (n->proc_name))
13974         gfc_error ("Contained procedure '%s' at %L of a PURE procedure must "
13975                    "also be PURE", n->proc_name->name,
13976                    &n->proc_name->declared_at);
13977
13978       resolve_types (n);
13979     }
13980
13981   forall_flag = 0;
13982   do_concurrent_flag = 0;
13983   gfc_check_interfaces (ns);
13984
13985   gfc_traverse_ns (ns, resolve_values);
13986
13987   if (ns->save_all)
13988     gfc_save_all (ns);
13989
13990   iter_stack = NULL;
13991   for (d = ns->data; d; d = d->next)
13992     resolve_data (d);
13993
13994   iter_stack = NULL;
13995   gfc_traverse_ns (ns, gfc_formalize_init_value);
13996
13997   gfc_traverse_ns (ns, gfc_verify_binding_labels);
13998
13999   if (ns->common_root != NULL)
14000     gfc_traverse_symtree (ns->common_root, resolve_bind_c_comms);
14001
14002   for (eq = ns->equiv; eq; eq = eq->next)
14003     resolve_equivalence (eq);
14004
14005   /* Warn about unused labels.  */
14006   if (warn_unused_label)
14007     warn_unused_fortran_label (ns->st_labels);
14008
14009   gfc_resolve_uops (ns->uop_root);
14010
14011   gfc_current_ns = old_ns;
14012 }
14013
14014
14015 /* Call resolve_code recursively.  */
14016
14017 static void
14018 resolve_codes (gfc_namespace *ns)
14019 {
14020   gfc_namespace *n;
14021   bitmap_obstack old_obstack;
14022
14023   if (ns->resolved == 1)
14024     return;
14025
14026   for (n = ns->contained; n; n = n->sibling)
14027     resolve_codes (n);
14028
14029   gfc_current_ns = ns;
14030
14031   /* Don't clear 'cs_base' if this is the namespace of a BLOCK construct.  */
14032   if (!(ns->proc_name && ns->proc_name->attr.flavor == FL_LABEL))
14033     cs_base = NULL;
14034
14035   /* Set to an out of range value.  */
14036   current_entry_id = -1;
14037
14038   old_obstack = labels_obstack;
14039   bitmap_obstack_initialize (&labels_obstack);
14040
14041   resolve_code (ns->code, ns);
14042
14043   bitmap_obstack_release (&labels_obstack);
14044   labels_obstack = old_obstack;
14045 }
14046
14047
14048 /* This function is called after a complete program unit has been compiled.
14049    Its purpose is to examine all of the expressions associated with a program
14050    unit, assign types to all intermediate expressions, make sure that all
14051    assignments are to compatible types and figure out which names refer to
14052    which functions or subroutines.  */
14053
14054 void
14055 gfc_resolve (gfc_namespace *ns)
14056 {
14057   gfc_namespace *old_ns;
14058   code_stack *old_cs_base;
14059
14060   if (ns->resolved)
14061     return;
14062
14063   ns->resolved = -1;
14064   old_ns = gfc_current_ns;
14065   old_cs_base = cs_base;
14066
14067   resolve_types (ns);
14068   resolve_codes (ns);
14069
14070   gfc_current_ns = old_ns;
14071   cs_base = old_cs_base;
14072   ns->resolved = 1;
14073
14074   gfc_run_passes (ns);
14075 }