2015-05-18 Steven G. Kargl <kargl@gcc.gnu.org>
[official-gcc.git] / gcc / fortran / decl.c
blob93a4554343fe34ced41f6030cc5e04c39959c1e6
1 /* Declaration statement matcher
2 Copyright (C) 2002-2015 Free Software Foundation, Inc.
3 Contributed by Andy Vaught
5 This file is part of GCC.
7 GCC is free software; you can redistribute it and/or modify it under
8 the terms of the GNU General Public License as published by the Free
9 Software Foundation; either version 3, or (at your option) any later
10 version.
12 GCC is distributed in the hope that it will be useful, but WITHOUT ANY
13 WARRANTY; without even the implied warranty of MERCHANTABILITY or
14 FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License
15 for more details.
17 You should have received a copy of the GNU General Public License
18 along with GCC; see the file COPYING3. If not see
19 <http://www.gnu.org/licenses/>. */
21 #include "config.h"
22 #include "system.h"
23 #include "coretypes.h"
24 #include "gfortran.h"
25 #include "match.h"
26 #include "parse.h"
27 #include "flags.h"
28 #include "constructor.h"
29 #include "hash-set.h"
30 #include "machmode.h"
31 #include "vec.h"
32 #include "double-int.h"
33 #include "input.h"
34 #include "alias.h"
35 #include "symtab.h"
36 #include "wide-int.h"
37 #include "inchash.h"
38 #include "tree.h"
39 #include "stringpool.h"
41 /* Macros to access allocate memory for gfc_data_variable,
42 gfc_data_value and gfc_data. */
43 #define gfc_get_data_variable() XCNEW (gfc_data_variable)
44 #define gfc_get_data_value() XCNEW (gfc_data_value)
45 #define gfc_get_data() XCNEW (gfc_data)
48 static bool set_binding_label (const char **, const char *, int);
51 /* This flag is set if an old-style length selector is matched
52 during a type-declaration statement. */
54 static int old_char_selector;
56 /* When variables acquire types and attributes from a declaration
57 statement, they get them from the following static variables. The
58 first part of a declaration sets these variables and the second
59 part copies these into symbol structures. */
61 static gfc_typespec current_ts;
63 static symbol_attribute current_attr;
64 static gfc_array_spec *current_as;
65 static int colon_seen;
67 /* The current binding label (if any). */
68 static const char* curr_binding_label;
69 /* Need to know how many identifiers are on the current data declaration
70 line in case we're given the BIND(C) attribute with a NAME= specifier. */
71 static int num_idents_on_line;
72 /* Need to know if a NAME= specifier was found during gfc_match_bind_c so we
73 can supply a name if the curr_binding_label is nil and NAME= was not. */
74 static int has_name_equals = 0;
76 /* Initializer of the previous enumerator. */
78 static gfc_expr *last_initializer;
80 /* History of all the enumerators is maintained, so that
81 kind values of all the enumerators could be updated depending
82 upon the maximum initialized value. */
84 typedef struct enumerator_history
86 gfc_symbol *sym;
87 gfc_expr *initializer;
88 struct enumerator_history *next;
90 enumerator_history;
92 /* Header of enum history chain. */
94 static enumerator_history *enum_history = NULL;
96 /* Pointer of enum history node containing largest initializer. */
98 static enumerator_history *max_enum = NULL;
100 /* gfc_new_block points to the symbol of a newly matched block. */
102 gfc_symbol *gfc_new_block;
104 bool gfc_matching_function;
107 /********************* DATA statement subroutines *********************/
109 static bool in_match_data = false;
111 bool
112 gfc_in_match_data (void)
114 return in_match_data;
117 static void
118 set_in_match_data (bool set_value)
120 in_match_data = set_value;
123 /* Free a gfc_data_variable structure and everything beneath it. */
125 static void
126 free_variable (gfc_data_variable *p)
128 gfc_data_variable *q;
130 for (; p; p = q)
132 q = p->next;
133 gfc_free_expr (p->expr);
134 gfc_free_iterator (&p->iter, 0);
135 free_variable (p->list);
136 free (p);
141 /* Free a gfc_data_value structure and everything beneath it. */
143 static void
144 free_value (gfc_data_value *p)
146 gfc_data_value *q;
148 for (; p; p = q)
150 q = p->next;
151 mpz_clear (p->repeat);
152 gfc_free_expr (p->expr);
153 free (p);
158 /* Free a list of gfc_data structures. */
160 void
161 gfc_free_data (gfc_data *p)
163 gfc_data *q;
165 for (; p; p = q)
167 q = p->next;
168 free_variable (p->var);
169 free_value (p->value);
170 free (p);
175 /* Free all data in a namespace. */
177 static void
178 gfc_free_data_all (gfc_namespace *ns)
180 gfc_data *d;
182 for (;ns->data;)
184 d = ns->data->next;
185 free (ns->data);
186 ns->data = d;
190 /* Reject data parsed since the last restore point was marked. */
192 void
193 gfc_reject_data (gfc_namespace *ns)
195 gfc_data *d;
197 while (ns->data && ns->data != ns->old_data)
199 d = ns->data->next;
200 free (ns->data);
201 ns->data = d;
205 static match var_element (gfc_data_variable *);
207 /* Match a list of variables terminated by an iterator and a right
208 parenthesis. */
210 static match
211 var_list (gfc_data_variable *parent)
213 gfc_data_variable *tail, var;
214 match m;
216 m = var_element (&var);
217 if (m == MATCH_ERROR)
218 return MATCH_ERROR;
219 if (m == MATCH_NO)
220 goto syntax;
222 tail = gfc_get_data_variable ();
223 *tail = var;
225 parent->list = tail;
227 for (;;)
229 if (gfc_match_char (',') != MATCH_YES)
230 goto syntax;
232 m = gfc_match_iterator (&parent->iter, 1);
233 if (m == MATCH_YES)
234 break;
235 if (m == MATCH_ERROR)
236 return MATCH_ERROR;
238 m = var_element (&var);
239 if (m == MATCH_ERROR)
240 return MATCH_ERROR;
241 if (m == MATCH_NO)
242 goto syntax;
244 tail->next = gfc_get_data_variable ();
245 tail = tail->next;
247 *tail = var;
250 if (gfc_match_char (')') != MATCH_YES)
251 goto syntax;
252 return MATCH_YES;
254 syntax:
255 gfc_syntax_error (ST_DATA);
256 return MATCH_ERROR;
260 /* Match a single element in a data variable list, which can be a
261 variable-iterator list. */
263 static match
264 var_element (gfc_data_variable *new_var)
266 match m;
267 gfc_symbol *sym;
269 memset (new_var, 0, sizeof (gfc_data_variable));
271 if (gfc_match_char ('(') == MATCH_YES)
272 return var_list (new_var);
274 m = gfc_match_variable (&new_var->expr, 0);
275 if (m != MATCH_YES)
276 return m;
278 sym = new_var->expr->symtree->n.sym;
280 /* Symbol should already have an associated type. */
281 if (!gfc_check_symbol_typed (sym, gfc_current_ns, false, gfc_current_locus))
282 return MATCH_ERROR;
284 if (!sym->attr.function && gfc_current_ns->parent
285 && gfc_current_ns->parent == sym->ns)
287 gfc_error ("Host associated variable %qs may not be in the DATA "
288 "statement at %C", sym->name);
289 return MATCH_ERROR;
292 if (gfc_current_state () != COMP_BLOCK_DATA
293 && sym->attr.in_common
294 && !gfc_notify_std (GFC_STD_GNU, "initialization of "
295 "common block variable %qs in DATA statement at %C",
296 sym->name))
297 return MATCH_ERROR;
299 if (!gfc_add_data (&sym->attr, sym->name, &new_var->expr->where))
300 return MATCH_ERROR;
302 return MATCH_YES;
306 /* Match the top-level list of data variables. */
308 static match
309 top_var_list (gfc_data *d)
311 gfc_data_variable var, *tail, *new_var;
312 match m;
314 tail = NULL;
316 for (;;)
318 m = var_element (&var);
319 if (m == MATCH_NO)
320 goto syntax;
321 if (m == MATCH_ERROR)
322 return MATCH_ERROR;
324 new_var = gfc_get_data_variable ();
325 *new_var = var;
327 if (tail == NULL)
328 d->var = new_var;
329 else
330 tail->next = new_var;
332 tail = new_var;
334 if (gfc_match_char ('/') == MATCH_YES)
335 break;
336 if (gfc_match_char (',') != MATCH_YES)
337 goto syntax;
340 return MATCH_YES;
342 syntax:
343 gfc_syntax_error (ST_DATA);
344 gfc_free_data_all (gfc_current_ns);
345 return MATCH_ERROR;
349 static match
350 match_data_constant (gfc_expr **result)
352 char name[GFC_MAX_SYMBOL_LEN + 1];
353 gfc_symbol *sym, *dt_sym = NULL;
354 gfc_expr *expr;
355 match m;
356 locus old_loc;
358 m = gfc_match_literal_constant (&expr, 1);
359 if (m == MATCH_YES)
361 *result = expr;
362 return MATCH_YES;
365 if (m == MATCH_ERROR)
366 return MATCH_ERROR;
368 m = gfc_match_null (result);
369 if (m != MATCH_NO)
370 return m;
372 old_loc = gfc_current_locus;
374 /* Should this be a structure component, try to match it
375 before matching a name. */
376 m = gfc_match_rvalue (result);
377 if (m == MATCH_ERROR)
378 return m;
380 if (m == MATCH_YES && (*result)->expr_type == EXPR_STRUCTURE)
382 if (!gfc_simplify_expr (*result, 0))
383 m = MATCH_ERROR;
384 return m;
386 else if (m == MATCH_YES)
387 gfc_free_expr (*result);
389 gfc_current_locus = old_loc;
391 m = gfc_match_name (name);
392 if (m != MATCH_YES)
393 return m;
395 if (gfc_find_symbol (name, NULL, 1, &sym))
396 return MATCH_ERROR;
398 if (sym && sym->attr.generic)
399 dt_sym = gfc_find_dt_in_generic (sym);
401 if (sym == NULL
402 || (sym->attr.flavor != FL_PARAMETER
403 && (!dt_sym || dt_sym->attr.flavor != FL_DERIVED)))
405 gfc_error ("Symbol %qs must be a PARAMETER in DATA statement at %C",
406 name);
407 return MATCH_ERROR;
409 else if (dt_sym && dt_sym->attr.flavor == FL_DERIVED)
410 return gfc_match_structure_constructor (dt_sym, result);
412 /* Check to see if the value is an initialization array expression. */
413 if (sym->value->expr_type == EXPR_ARRAY)
415 gfc_current_locus = old_loc;
417 m = gfc_match_init_expr (result);
418 if (m == MATCH_ERROR)
419 return m;
421 if (m == MATCH_YES)
423 if (!gfc_simplify_expr (*result, 0))
424 m = MATCH_ERROR;
426 if ((*result)->expr_type == EXPR_CONSTANT)
427 return m;
428 else
430 gfc_error ("Invalid initializer %s in Data statement at %C", name);
431 return MATCH_ERROR;
436 *result = gfc_copy_expr (sym->value);
437 return MATCH_YES;
441 /* Match a list of values in a DATA statement. The leading '/' has
442 already been seen at this point. */
444 static match
445 top_val_list (gfc_data *data)
447 gfc_data_value *new_val, *tail;
448 gfc_expr *expr;
449 match m;
451 tail = NULL;
453 for (;;)
455 m = match_data_constant (&expr);
456 if (m == MATCH_NO)
457 goto syntax;
458 if (m == MATCH_ERROR)
459 return MATCH_ERROR;
461 new_val = gfc_get_data_value ();
462 mpz_init (new_val->repeat);
464 if (tail == NULL)
465 data->value = new_val;
466 else
467 tail->next = new_val;
469 tail = new_val;
471 if (expr->ts.type != BT_INTEGER || gfc_match_char ('*') != MATCH_YES)
473 tail->expr = expr;
474 mpz_set_ui (tail->repeat, 1);
476 else
478 mpz_set (tail->repeat, expr->value.integer);
479 gfc_free_expr (expr);
481 m = match_data_constant (&tail->expr);
482 if (m == MATCH_NO)
483 goto syntax;
484 if (m == MATCH_ERROR)
485 return MATCH_ERROR;
488 if (gfc_match_char ('/') == MATCH_YES)
489 break;
490 if (gfc_match_char (',') == MATCH_NO)
491 goto syntax;
494 return MATCH_YES;
496 syntax:
497 gfc_syntax_error (ST_DATA);
498 gfc_free_data_all (gfc_current_ns);
499 return MATCH_ERROR;
503 /* Matches an old style initialization. */
505 static match
506 match_old_style_init (const char *name)
508 match m;
509 gfc_symtree *st;
510 gfc_symbol *sym;
511 gfc_data *newdata;
513 /* Set up data structure to hold initializers. */
514 gfc_find_sym_tree (name, NULL, 0, &st);
515 sym = st->n.sym;
517 newdata = gfc_get_data ();
518 newdata->var = gfc_get_data_variable ();
519 newdata->var->expr = gfc_get_variable_expr (st);
520 newdata->where = gfc_current_locus;
522 /* Match initial value list. This also eats the terminal '/'. */
523 m = top_val_list (newdata);
524 if (m != MATCH_YES)
526 free (newdata);
527 return m;
530 if (gfc_pure (NULL))
532 gfc_error ("Initialization at %C is not allowed in a PURE procedure");
533 free (newdata);
534 return MATCH_ERROR;
536 gfc_unset_implicit_pure (gfc_current_ns->proc_name);
538 /* Mark the variable as having appeared in a data statement. */
539 if (!gfc_add_data (&sym->attr, sym->name, &sym->declared_at))
541 free (newdata);
542 return MATCH_ERROR;
545 /* Chain in namespace list of DATA initializers. */
546 newdata->next = gfc_current_ns->data;
547 gfc_current_ns->data = newdata;
549 return m;
553 /* Match the stuff following a DATA statement. If ERROR_FLAG is set,
554 we are matching a DATA statement and are therefore issuing an error
555 if we encounter something unexpected, if not, we're trying to match
556 an old-style initialization expression of the form INTEGER I /2/. */
558 match
559 gfc_match_data (void)
561 gfc_data *new_data;
562 match m;
564 set_in_match_data (true);
566 for (;;)
568 new_data = gfc_get_data ();
569 new_data->where = gfc_current_locus;
571 m = top_var_list (new_data);
572 if (m != MATCH_YES)
573 goto cleanup;
575 m = top_val_list (new_data);
576 if (m != MATCH_YES)
577 goto cleanup;
579 new_data->next = gfc_current_ns->data;
580 gfc_current_ns->data = new_data;
582 if (gfc_match_eos () == MATCH_YES)
583 break;
585 gfc_match_char (','); /* Optional comma */
588 set_in_match_data (false);
590 if (gfc_pure (NULL))
592 gfc_error ("DATA statement at %C is not allowed in a PURE procedure");
593 return MATCH_ERROR;
595 gfc_unset_implicit_pure (gfc_current_ns->proc_name);
597 return MATCH_YES;
599 cleanup:
600 set_in_match_data (false);
601 gfc_free_data (new_data);
602 return MATCH_ERROR;
606 /************************ Declaration statements *********************/
609 /* Auxiliary function to merge DIMENSION and CODIMENSION array specs. */
611 static bool
612 merge_array_spec (gfc_array_spec *from, gfc_array_spec *to, bool copy)
614 int i;
616 if ((from->type == AS_ASSUMED_RANK && to->corank)
617 || (to->type == AS_ASSUMED_RANK && from->corank))
619 gfc_error ("The assumed-rank array at %C shall not have a codimension");
620 return false;
623 if (to->rank == 0 && from->rank > 0)
625 to->rank = from->rank;
626 to->type = from->type;
627 to->cray_pointee = from->cray_pointee;
628 to->cp_was_assumed = from->cp_was_assumed;
630 for (i = 0; i < to->corank; i++)
632 to->lower[from->rank + i] = to->lower[i];
633 to->upper[from->rank + i] = to->upper[i];
635 for (i = 0; i < from->rank; i++)
637 if (copy)
639 to->lower[i] = gfc_copy_expr (from->lower[i]);
640 to->upper[i] = gfc_copy_expr (from->upper[i]);
642 else
644 to->lower[i] = from->lower[i];
645 to->upper[i] = from->upper[i];
649 else if (to->corank == 0 && from->corank > 0)
651 to->corank = from->corank;
652 to->cotype = from->cotype;
654 for (i = 0; i < from->corank; i++)
656 if (copy)
658 to->lower[to->rank + i] = gfc_copy_expr (from->lower[i]);
659 to->upper[to->rank + i] = gfc_copy_expr (from->upper[i]);
661 else
663 to->lower[to->rank + i] = from->lower[i];
664 to->upper[to->rank + i] = from->upper[i];
669 return true;
673 /* Match an intent specification. Since this can only happen after an
674 INTENT word, a legal intent-spec must follow. */
676 static sym_intent
677 match_intent_spec (void)
680 if (gfc_match (" ( in out )") == MATCH_YES)
681 return INTENT_INOUT;
682 if (gfc_match (" ( in )") == MATCH_YES)
683 return INTENT_IN;
684 if (gfc_match (" ( out )") == MATCH_YES)
685 return INTENT_OUT;
687 gfc_error ("Bad INTENT specification at %C");
688 return INTENT_UNKNOWN;
692 /* Matches a character length specification, which is either a
693 specification expression, '*', or ':'. */
695 static match
696 char_len_param_value (gfc_expr **expr, bool *deferred)
698 match m;
700 *expr = NULL;
701 *deferred = false;
703 if (gfc_match_char ('*') == MATCH_YES)
704 return MATCH_YES;
706 if (gfc_match_char (':') == MATCH_YES)
708 if (!gfc_notify_std (GFC_STD_F2003, "deferred type "
709 "parameter at %C"))
710 return MATCH_ERROR;
712 *deferred = true;
714 return MATCH_YES;
717 m = gfc_match_expr (expr);
719 if (m == MATCH_YES
720 && !gfc_expr_check_typed (*expr, gfc_current_ns, false))
721 return MATCH_ERROR;
723 if (m == MATCH_YES && (*expr)->expr_type == EXPR_FUNCTION)
725 if ((*expr)->value.function.actual
726 && (*expr)->value.function.actual->expr->symtree)
728 gfc_expr *e;
729 e = (*expr)->value.function.actual->expr;
730 if (e->symtree->n.sym->attr.flavor == FL_PROCEDURE
731 && e->expr_type == EXPR_VARIABLE)
733 if (e->symtree->n.sym->ts.type == BT_UNKNOWN)
734 goto syntax;
735 if (e->symtree->n.sym->ts.type == BT_CHARACTER
736 && e->symtree->n.sym->ts.u.cl
737 && e->symtree->n.sym->ts.u.cl->length->ts.type == BT_UNKNOWN)
738 goto syntax;
742 return m;
744 syntax:
745 gfc_error ("Conflict in attributes of function argument at %C");
746 return MATCH_ERROR;
750 /* A character length is a '*' followed by a literal integer or a
751 char_len_param_value in parenthesis. */
753 static match
754 match_char_length (gfc_expr **expr, bool *deferred, bool obsolescent_check)
756 int length;
757 match m;
759 *deferred = false;
760 m = gfc_match_char ('*');
761 if (m != MATCH_YES)
762 return m;
764 m = gfc_match_small_literal_int (&length, NULL);
765 if (m == MATCH_ERROR)
766 return m;
768 if (m == MATCH_YES)
770 if (obsolescent_check
771 && !gfc_notify_std (GFC_STD_F95_OBS, "Old-style character length at %C"))
772 return MATCH_ERROR;
773 *expr = gfc_get_int_expr (gfc_default_integer_kind, NULL, length);
774 return m;
777 if (gfc_match_char ('(') == MATCH_NO)
778 goto syntax;
780 m = char_len_param_value (expr, deferred);
781 if (m != MATCH_YES && gfc_matching_function)
783 gfc_undo_symbols ();
784 m = MATCH_YES;
787 if (m == MATCH_ERROR)
788 return m;
789 if (m == MATCH_NO)
790 goto syntax;
792 if (gfc_match_char (')') == MATCH_NO)
794 gfc_free_expr (*expr);
795 *expr = NULL;
796 goto syntax;
799 return MATCH_YES;
801 syntax:
802 gfc_error ("Syntax error in character length specification at %C");
803 return MATCH_ERROR;
807 /* Special subroutine for finding a symbol. Check if the name is found
808 in the current name space. If not, and we're compiling a function or
809 subroutine and the parent compilation unit is an interface, then check
810 to see if the name we've been given is the name of the interface
811 (located in another namespace). */
813 static int
814 find_special (const char *name, gfc_symbol **result, bool allow_subroutine)
816 gfc_state_data *s;
817 gfc_symtree *st;
818 int i;
820 i = gfc_get_sym_tree (name, NULL, &st, allow_subroutine);
821 if (i == 0)
823 *result = st ? st->n.sym : NULL;
824 goto end;
827 if (gfc_current_state () != COMP_SUBROUTINE
828 && gfc_current_state () != COMP_FUNCTION)
829 goto end;
831 s = gfc_state_stack->previous;
832 if (s == NULL)
833 goto end;
835 if (s->state != COMP_INTERFACE)
836 goto end;
837 if (s->sym == NULL)
838 goto end; /* Nameless interface. */
840 if (strcmp (name, s->sym->name) == 0)
842 *result = s->sym;
843 return 0;
846 end:
847 return i;
851 /* Special subroutine for getting a symbol node associated with a
852 procedure name, used in SUBROUTINE and FUNCTION statements. The
853 symbol is created in the parent using with symtree node in the
854 child unit pointing to the symbol. If the current namespace has no
855 parent, then the symbol is just created in the current unit. */
857 static int
858 get_proc_name (const char *name, gfc_symbol **result, bool module_fcn_entry)
860 gfc_symtree *st;
861 gfc_symbol *sym;
862 int rc = 0;
864 /* Module functions have to be left in their own namespace because
865 they have potentially (almost certainly!) already been referenced.
866 In this sense, they are rather like external functions. This is
867 fixed up in resolve.c(resolve_entries), where the symbol name-
868 space is set to point to the master function, so that the fake
869 result mechanism can work. */
870 if (module_fcn_entry)
872 /* Present if entry is declared to be a module procedure. */
873 rc = gfc_find_symbol (name, gfc_current_ns->parent, 0, result);
875 if (*result == NULL)
876 rc = gfc_get_symbol (name, NULL, result);
877 else if (!gfc_get_symbol (name, NULL, &sym) && sym
878 && (*result)->ts.type == BT_UNKNOWN
879 && sym->attr.flavor == FL_UNKNOWN)
880 /* Pick up the typespec for the entry, if declared in the function
881 body. Note that this symbol is FL_UNKNOWN because it will
882 only have appeared in a type declaration. The local symtree
883 is set to point to the module symbol and a unique symtree
884 to the local version. This latter ensures a correct clearing
885 of the symbols. */
887 /* If the ENTRY proceeds its specification, we need to ensure
888 that this does not raise a "has no IMPLICIT type" error. */
889 if (sym->ts.type == BT_UNKNOWN)
890 sym->attr.untyped = 1;
892 (*result)->ts = sym->ts;
894 /* Put the symbol in the procedure namespace so that, should
895 the ENTRY precede its specification, the specification
896 can be applied. */
897 (*result)->ns = gfc_current_ns;
899 gfc_find_sym_tree (name, gfc_current_ns, 0, &st);
900 st->n.sym = *result;
901 st = gfc_get_unique_symtree (gfc_current_ns);
902 st->n.sym = sym;
905 else
906 rc = gfc_get_symbol (name, gfc_current_ns->parent, result);
908 if (rc)
909 return rc;
911 sym = *result;
913 if (sym && !sym->gfc_new && gfc_current_state () != COMP_INTERFACE)
915 /* Trap another encompassed procedure with the same name. All
916 these conditions are necessary to avoid picking up an entry
917 whose name clashes with that of the encompassing procedure;
918 this is handled using gsymbols to register unique,globally
919 accessible names. */
920 if (sym->attr.flavor != 0
921 && sym->attr.proc != 0
922 && (sym->attr.subroutine || sym->attr.function)
923 && sym->attr.if_source != IFSRC_UNKNOWN)
924 gfc_error_now_1 ("Procedure '%s' at %C is already defined at %L",
925 name, &sym->declared_at);
927 /* Trap a procedure with a name the same as interface in the
928 encompassing scope. */
929 if (sym->attr.generic != 0
930 && (sym->attr.subroutine || sym->attr.function)
931 && !sym->attr.mod_proc)
932 gfc_error_now_1 ("Name '%s' at %C is already defined"
933 " as a generic interface at %L",
934 name, &sym->declared_at);
936 /* Trap declarations of attributes in encompassing scope. The
937 signature for this is that ts.kind is set. Legitimate
938 references only set ts.type. */
939 if (sym->ts.kind != 0
940 && !sym->attr.implicit_type
941 && sym->attr.proc == 0
942 && gfc_current_ns->parent != NULL
943 && sym->attr.access == 0
944 && !module_fcn_entry)
945 gfc_error_now_1 ("Procedure '%s' at %C has an explicit interface "
946 "and must not have attributes declared at %L",
947 name, &sym->declared_at);
950 if (gfc_current_ns->parent == NULL || *result == NULL)
951 return rc;
953 /* Module function entries will already have a symtree in
954 the current namespace but will need one at module level. */
955 if (module_fcn_entry)
957 /* Present if entry is declared to be a module procedure. */
958 rc = gfc_find_sym_tree (name, gfc_current_ns->parent, 0, &st);
959 if (st == NULL)
960 st = gfc_new_symtree (&gfc_current_ns->parent->sym_root, name);
962 else
963 st = gfc_new_symtree (&gfc_current_ns->sym_root, name);
965 st->n.sym = sym;
966 sym->refs++;
968 /* See if the procedure should be a module procedure. */
970 if (((sym->ns->proc_name != NULL
971 && sym->ns->proc_name->attr.flavor == FL_MODULE
972 && sym->attr.proc != PROC_MODULE)
973 || (module_fcn_entry && sym->attr.proc != PROC_MODULE))
974 && !gfc_add_procedure (&sym->attr, PROC_MODULE, sym->name, NULL))
975 rc = 2;
977 return rc;
981 /* Verify that the given symbol representing a parameter is C
982 interoperable, by checking to see if it was marked as such after
983 its declaration. If the given symbol is not interoperable, a
984 warning is reported, thus removing the need to return the status to
985 the calling function. The standard does not require the user use
986 one of the iso_c_binding named constants to declare an
987 interoperable parameter, but we can't be sure if the param is C
988 interop or not if the user doesn't. For example, integer(4) may be
989 legal Fortran, but doesn't have meaning in C. It may interop with
990 a number of the C types, which causes a problem because the
991 compiler can't know which one. This code is almost certainly not
992 portable, and the user will get what they deserve if the C type
993 across platforms isn't always interoperable with integer(4). If
994 the user had used something like integer(c_int) or integer(c_long),
995 the compiler could have automatically handled the varying sizes
996 across platforms. */
998 bool
999 gfc_verify_c_interop_param (gfc_symbol *sym)
1001 int is_c_interop = 0;
1002 bool retval = true;
1004 /* We check implicitly typed variables in symbol.c:gfc_set_default_type().
1005 Don't repeat the checks here. */
1006 if (sym->attr.implicit_type)
1007 return true;
1009 /* For subroutines or functions that are passed to a BIND(C) procedure,
1010 they're interoperable if they're BIND(C) and their params are all
1011 interoperable. */
1012 if (sym->attr.flavor == FL_PROCEDURE)
1014 if (sym->attr.is_bind_c == 0)
1016 gfc_error_now ("Procedure %qs at %L must have the BIND(C) "
1017 "attribute to be C interoperable", sym->name,
1018 &(sym->declared_at));
1019 return false;
1021 else
1023 if (sym->attr.is_c_interop == 1)
1024 /* We've already checked this procedure; don't check it again. */
1025 return true;
1026 else
1027 return verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
1028 sym->common_block);
1032 /* See if we've stored a reference to a procedure that owns sym. */
1033 if (sym->ns != NULL && sym->ns->proc_name != NULL)
1035 if (sym->ns->proc_name->attr.is_bind_c == 1)
1037 is_c_interop = (gfc_verify_c_interop(&(sym->ts)) ? 1 : 0);
1039 if (is_c_interop != 1)
1041 /* Make personalized messages to give better feedback. */
1042 if (sym->ts.type == BT_DERIVED)
1043 gfc_error ("Variable %qs at %L is a dummy argument to the "
1044 "BIND(C) procedure %qs but is not C interoperable "
1045 "because derived type %qs is not C interoperable",
1046 sym->name, &(sym->declared_at),
1047 sym->ns->proc_name->name,
1048 sym->ts.u.derived->name);
1049 else if (sym->ts.type == BT_CLASS)
1050 gfc_error ("Variable %qs at %L is a dummy argument to the "
1051 "BIND(C) procedure %qs but is not C interoperable "
1052 "because it is polymorphic",
1053 sym->name, &(sym->declared_at),
1054 sym->ns->proc_name->name);
1055 else if (warn_c_binding_type)
1056 gfc_warning (OPT_Wc_binding_type,
1057 "Variable %qs at %L is a dummy argument of the "
1058 "BIND(C) procedure %qs but may not be C "
1059 "interoperable",
1060 sym->name, &(sym->declared_at),
1061 sym->ns->proc_name->name);
1064 /* Character strings are only C interoperable if they have a
1065 length of 1. */
1066 if (sym->ts.type == BT_CHARACTER)
1068 gfc_charlen *cl = sym->ts.u.cl;
1069 if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT
1070 || mpz_cmp_si (cl->length->value.integer, 1) != 0)
1072 gfc_error ("Character argument %qs at %L "
1073 "must be length 1 because "
1074 "procedure %qs is BIND(C)",
1075 sym->name, &sym->declared_at,
1076 sym->ns->proc_name->name);
1077 retval = false;
1081 /* We have to make sure that any param to a bind(c) routine does
1082 not have the allocatable, pointer, or optional attributes,
1083 according to J3/04-007, section 5.1. */
1084 if (sym->attr.allocatable == 1
1085 && !gfc_notify_std (GFC_STD_F2008_TS, "Variable %qs at %L with "
1086 "ALLOCATABLE attribute in procedure %qs "
1087 "with BIND(C)", sym->name,
1088 &(sym->declared_at),
1089 sym->ns->proc_name->name))
1090 retval = false;
1092 if (sym->attr.pointer == 1
1093 && !gfc_notify_std (GFC_STD_F2008_TS, "Variable %qs at %L with "
1094 "POINTER attribute in procedure %qs "
1095 "with BIND(C)", sym->name,
1096 &(sym->declared_at),
1097 sym->ns->proc_name->name))
1098 retval = false;
1100 if ((sym->attr.allocatable || sym->attr.pointer) && !sym->as)
1102 gfc_error ("Scalar variable %qs at %L with POINTER or "
1103 "ALLOCATABLE in procedure %qs with BIND(C) is not yet"
1104 " supported", sym->name, &(sym->declared_at),
1105 sym->ns->proc_name->name);
1106 retval = false;
1109 if (sym->attr.optional == 1 && sym->attr.value)
1111 gfc_error ("Variable %qs at %L cannot have both the OPTIONAL "
1112 "and the VALUE attribute because procedure %qs "
1113 "is BIND(C)", sym->name, &(sym->declared_at),
1114 sym->ns->proc_name->name);
1115 retval = false;
1117 else if (sym->attr.optional == 1
1118 && !gfc_notify_std (GFC_STD_F2008_TS, "Variable %qs "
1119 "at %L with OPTIONAL attribute in "
1120 "procedure %qs which is BIND(C)",
1121 sym->name, &(sym->declared_at),
1122 sym->ns->proc_name->name))
1123 retval = false;
1125 /* Make sure that if it has the dimension attribute, that it is
1126 either assumed size or explicit shape. Deferred shape is already
1127 covered by the pointer/allocatable attribute. */
1128 if (sym->as != NULL && sym->as->type == AS_ASSUMED_SHAPE
1129 && !gfc_notify_std (GFC_STD_F2008_TS, "Assumed-shape array %qs "
1130 "at %L as dummy argument to the BIND(C) "
1131 "procedure '%s' at %L", sym->name,
1132 &(sym->declared_at),
1133 sym->ns->proc_name->name,
1134 &(sym->ns->proc_name->declared_at)))
1135 retval = false;
1139 return retval;
1144 /* Function called by variable_decl() that adds a name to the symbol table. */
1146 static bool
1147 build_sym (const char *name, gfc_charlen *cl, bool cl_deferred,
1148 gfc_array_spec **as, locus *var_locus)
1150 symbol_attribute attr;
1151 gfc_symbol *sym;
1153 if (gfc_get_symbol (name, NULL, &sym))
1154 return false;
1156 /* Start updating the symbol table. Add basic type attribute if present. */
1157 if (current_ts.type != BT_UNKNOWN
1158 && (sym->attr.implicit_type == 0
1159 || !gfc_compare_types (&sym->ts, &current_ts))
1160 && !gfc_add_type (sym, &current_ts, var_locus))
1161 return false;
1163 if (sym->ts.type == BT_CHARACTER)
1165 sym->ts.u.cl = cl;
1166 sym->ts.deferred = cl_deferred;
1169 /* Add dimension attribute if present. */
1170 if (!gfc_set_array_spec (sym, *as, var_locus))
1171 return false;
1172 *as = NULL;
1174 /* Add attribute to symbol. The copy is so that we can reset the
1175 dimension attribute. */
1176 attr = current_attr;
1177 attr.dimension = 0;
1178 attr.codimension = 0;
1180 if (!gfc_copy_attr (&sym->attr, &attr, var_locus))
1181 return false;
1183 /* Finish any work that may need to be done for the binding label,
1184 if it's a bind(c). The bind(c) attr is found before the symbol
1185 is made, and before the symbol name (for data decls), so the
1186 current_ts is holding the binding label, or nothing if the
1187 name= attr wasn't given. Therefore, test here if we're dealing
1188 with a bind(c) and make sure the binding label is set correctly. */
1189 if (sym->attr.is_bind_c == 1)
1191 if (!sym->binding_label)
1193 /* Set the binding label and verify that if a NAME= was specified
1194 then only one identifier was in the entity-decl-list. */
1195 if (!set_binding_label (&sym->binding_label, sym->name,
1196 num_idents_on_line))
1197 return false;
1201 /* See if we know we're in a common block, and if it's a bind(c)
1202 common then we need to make sure we're an interoperable type. */
1203 if (sym->attr.in_common == 1)
1205 /* Test the common block object. */
1206 if (sym->common_block != NULL && sym->common_block->is_bind_c == 1
1207 && sym->ts.is_c_interop != 1)
1209 gfc_error_now ("Variable %qs in common block %qs at %C "
1210 "must be declared with a C interoperable "
1211 "kind since common block %qs is BIND(C)",
1212 sym->name, sym->common_block->name,
1213 sym->common_block->name);
1214 gfc_clear_error ();
1218 sym->attr.implied_index = 0;
1220 if (sym->ts.type == BT_CLASS)
1221 return gfc_build_class_symbol (&sym->ts, &sym->attr, &sym->as);
1223 return true;
1227 /* Set character constant to the given length. The constant will be padded or
1228 truncated. If we're inside an array constructor without a typespec, we
1229 additionally check that all elements have the same length; check_len -1
1230 means no checking. */
1232 void
1233 gfc_set_constant_character_len (int len, gfc_expr *expr, int check_len)
1235 gfc_char_t *s;
1236 int slen;
1238 gcc_assert (expr->expr_type == EXPR_CONSTANT);
1239 gcc_assert (expr->ts.type == BT_CHARACTER);
1241 slen = expr->value.character.length;
1242 if (len != slen)
1244 s = gfc_get_wide_string (len + 1);
1245 memcpy (s, expr->value.character.string,
1246 MIN (len, slen) * sizeof (gfc_char_t));
1247 if (len > slen)
1248 gfc_wide_memset (&s[slen], ' ', len - slen);
1250 if (warn_character_truncation && slen > len)
1251 gfc_warning_now (OPT_Wcharacter_truncation,
1252 "CHARACTER expression at %L is being truncated "
1253 "(%d/%d)", &expr->where, slen, len);
1255 /* Apply the standard by 'hand' otherwise it gets cleared for
1256 initializers. */
1257 if (check_len != -1 && slen != check_len
1258 && !(gfc_option.allow_std & GFC_STD_GNU))
1259 gfc_error_now ("The CHARACTER elements of the array constructor "
1260 "at %L must have the same length (%d/%d)",
1261 &expr->where, slen, check_len);
1263 s[len] = '\0';
1264 free (expr->value.character.string);
1265 expr->value.character.string = s;
1266 expr->value.character.length = len;
1271 /* Function to create and update the enumerator history
1272 using the information passed as arguments.
1273 Pointer "max_enum" is also updated, to point to
1274 enum history node containing largest initializer.
1276 SYM points to the symbol node of enumerator.
1277 INIT points to its enumerator value. */
1279 static void
1280 create_enum_history (gfc_symbol *sym, gfc_expr *init)
1282 enumerator_history *new_enum_history;
1283 gcc_assert (sym != NULL && init != NULL);
1285 new_enum_history = XCNEW (enumerator_history);
1287 new_enum_history->sym = sym;
1288 new_enum_history->initializer = init;
1289 new_enum_history->next = NULL;
1291 if (enum_history == NULL)
1293 enum_history = new_enum_history;
1294 max_enum = enum_history;
1296 else
1298 new_enum_history->next = enum_history;
1299 enum_history = new_enum_history;
1301 if (mpz_cmp (max_enum->initializer->value.integer,
1302 new_enum_history->initializer->value.integer) < 0)
1303 max_enum = new_enum_history;
1308 /* Function to free enum kind history. */
1310 void
1311 gfc_free_enum_history (void)
1313 enumerator_history *current = enum_history;
1314 enumerator_history *next;
1316 while (current != NULL)
1318 next = current->next;
1319 free (current);
1320 current = next;
1322 max_enum = NULL;
1323 enum_history = NULL;
1327 /* Function called by variable_decl() that adds an initialization
1328 expression to a symbol. */
1330 static bool
1331 add_init_expr_to_sym (const char *name, gfc_expr **initp, locus *var_locus)
1333 symbol_attribute attr;
1334 gfc_symbol *sym;
1335 gfc_expr *init;
1337 init = *initp;
1338 if (find_special (name, &sym, false))
1339 return false;
1341 attr = sym->attr;
1343 /* If this symbol is confirming an implicit parameter type,
1344 then an initialization expression is not allowed. */
1345 if (attr.flavor == FL_PARAMETER
1346 && sym->value != NULL
1347 && *initp != NULL)
1349 gfc_error ("Initializer not allowed for PARAMETER %qs at %C",
1350 sym->name);
1351 return false;
1354 if (init == NULL)
1356 /* An initializer is required for PARAMETER declarations. */
1357 if (attr.flavor == FL_PARAMETER)
1359 gfc_error ("PARAMETER at %L is missing an initializer", var_locus);
1360 return false;
1363 else
1365 /* If a variable appears in a DATA block, it cannot have an
1366 initializer. */
1367 if (sym->attr.data)
1369 gfc_error ("Variable %qs at %C with an initializer already "
1370 "appears in a DATA statement", sym->name);
1371 return false;
1374 /* Check if the assignment can happen. This has to be put off
1375 until later for derived type variables and procedure pointers. */
1376 if (sym->ts.type != BT_DERIVED && init->ts.type != BT_DERIVED
1377 && sym->ts.type != BT_CLASS && init->ts.type != BT_CLASS
1378 && !sym->attr.proc_pointer
1379 && !gfc_check_assign_symbol (sym, NULL, init))
1380 return false;
1382 if (sym->ts.type == BT_CHARACTER && sym->ts.u.cl
1383 && init->ts.type == BT_CHARACTER)
1385 /* Update symbol character length according initializer. */
1386 if (!gfc_check_assign_symbol (sym, NULL, init))
1387 return false;
1389 if (sym->ts.u.cl->length == NULL)
1391 int clen;
1392 /* If there are multiple CHARACTER variables declared on the
1393 same line, we don't want them to share the same length. */
1394 sym->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
1396 if (sym->attr.flavor == FL_PARAMETER)
1398 if (init->expr_type == EXPR_CONSTANT)
1400 clen = init->value.character.length;
1401 sym->ts.u.cl->length
1402 = gfc_get_int_expr (gfc_default_integer_kind,
1403 NULL, clen);
1405 else if (init->expr_type == EXPR_ARRAY)
1407 clen = mpz_get_si (init->ts.u.cl->length->value.integer);
1408 sym->ts.u.cl->length
1409 = gfc_get_int_expr (gfc_default_integer_kind,
1410 NULL, clen);
1412 else if (init->ts.u.cl && init->ts.u.cl->length)
1413 sym->ts.u.cl->length =
1414 gfc_copy_expr (sym->value->ts.u.cl->length);
1417 /* Update initializer character length according symbol. */
1418 else if (sym->ts.u.cl->length->expr_type == EXPR_CONSTANT)
1420 int len = mpz_get_si (sym->ts.u.cl->length->value.integer);
1422 if (init->expr_type == EXPR_CONSTANT)
1423 gfc_set_constant_character_len (len, init, -1);
1424 else if (init->expr_type == EXPR_ARRAY)
1426 gfc_constructor *c;
1428 /* Build a new charlen to prevent simplification from
1429 deleting the length before it is resolved. */
1430 init->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
1431 init->ts.u.cl->length = gfc_copy_expr (sym->ts.u.cl->length);
1433 for (c = gfc_constructor_first (init->value.constructor);
1434 c; c = gfc_constructor_next (c))
1435 gfc_set_constant_character_len (len, c->expr, -1);
1440 /* If sym is implied-shape, set its upper bounds from init. */
1441 if (sym->attr.flavor == FL_PARAMETER && sym->attr.dimension
1442 && sym->as->type == AS_IMPLIED_SHAPE)
1444 int dim;
1446 if (init->rank == 0)
1448 gfc_error ("Can't initialize implied-shape array at %L"
1449 " with scalar", &sym->declared_at);
1450 return false;
1452 gcc_assert (sym->as->rank == init->rank);
1454 /* Shape should be present, we get an initialization expression. */
1455 gcc_assert (init->shape);
1457 for (dim = 0; dim < sym->as->rank; ++dim)
1459 int k;
1460 gfc_expr* lower;
1461 gfc_expr* e;
1463 lower = sym->as->lower[dim];
1464 if (lower->expr_type != EXPR_CONSTANT)
1466 gfc_error ("Non-constant lower bound in implied-shape"
1467 " declaration at %L", &lower->where);
1468 return false;
1471 /* All dimensions must be without upper bound. */
1472 gcc_assert (!sym->as->upper[dim]);
1474 k = lower->ts.kind;
1475 e = gfc_get_constant_expr (BT_INTEGER, k, &sym->declared_at);
1476 mpz_add (e->value.integer,
1477 lower->value.integer, init->shape[dim]);
1478 mpz_sub_ui (e->value.integer, e->value.integer, 1);
1479 sym->as->upper[dim] = e;
1482 sym->as->type = AS_EXPLICIT;
1485 /* Need to check if the expression we initialized this
1486 to was one of the iso_c_binding named constants. If so,
1487 and we're a parameter (constant), let it be iso_c.
1488 For example:
1489 integer(c_int), parameter :: my_int = c_int
1490 integer(my_int) :: my_int_2
1491 If we mark my_int as iso_c (since we can see it's value
1492 is equal to one of the named constants), then my_int_2
1493 will be considered C interoperable. */
1494 if (sym->ts.type != BT_CHARACTER && sym->ts.type != BT_DERIVED)
1496 sym->ts.is_iso_c |= init->ts.is_iso_c;
1497 sym->ts.is_c_interop |= init->ts.is_c_interop;
1498 /* attr bits needed for module files. */
1499 sym->attr.is_iso_c |= init->ts.is_iso_c;
1500 sym->attr.is_c_interop |= init->ts.is_c_interop;
1501 if (init->ts.is_iso_c)
1502 sym->ts.f90_type = init->ts.f90_type;
1505 /* Add initializer. Make sure we keep the ranks sane. */
1506 if (sym->attr.dimension && init->rank == 0)
1508 mpz_t size;
1509 gfc_expr *array;
1510 int n;
1511 if (sym->attr.flavor == FL_PARAMETER
1512 && init->expr_type == EXPR_CONSTANT
1513 && spec_size (sym->as, &size)
1514 && mpz_cmp_si (size, 0) > 0)
1516 array = gfc_get_array_expr (init->ts.type, init->ts.kind,
1517 &init->where);
1518 for (n = 0; n < (int)mpz_get_si (size); n++)
1519 gfc_constructor_append_expr (&array->value.constructor,
1520 n == 0
1521 ? init
1522 : gfc_copy_expr (init),
1523 &init->where);
1525 array->shape = gfc_get_shape (sym->as->rank);
1526 for (n = 0; n < sym->as->rank; n++)
1527 spec_dimen_size (sym->as, n, &array->shape[n]);
1529 init = array;
1530 mpz_clear (size);
1532 init->rank = sym->as->rank;
1535 sym->value = init;
1536 if (sym->attr.save == SAVE_NONE)
1537 sym->attr.save = SAVE_IMPLICIT;
1538 *initp = NULL;
1541 return true;
1545 /* Function called by variable_decl() that adds a name to a structure
1546 being built. */
1548 static bool
1549 build_struct (const char *name, gfc_charlen *cl, gfc_expr **init,
1550 gfc_array_spec **as)
1552 gfc_component *c;
1553 bool t = true;
1555 /* F03:C438/C439. If the current symbol is of the same derived type that we're
1556 constructing, it must have the pointer attribute. */
1557 if ((current_ts.type == BT_DERIVED || current_ts.type == BT_CLASS)
1558 && current_ts.u.derived == gfc_current_block ()
1559 && current_attr.pointer == 0)
1561 gfc_error ("Component at %C must have the POINTER attribute");
1562 return false;
1565 if (gfc_current_block ()->attr.pointer && (*as)->rank != 0)
1567 if ((*as)->type != AS_DEFERRED && (*as)->type != AS_EXPLICIT)
1569 gfc_error ("Array component of structure at %C must have explicit "
1570 "or deferred shape");
1571 return false;
1575 if (!gfc_add_component (gfc_current_block(), name, &c))
1576 return false;
1578 c->ts = current_ts;
1579 if (c->ts.type == BT_CHARACTER)
1580 c->ts.u.cl = cl;
1581 c->attr = current_attr;
1583 c->initializer = *init;
1584 *init = NULL;
1586 c->as = *as;
1587 if (c->as != NULL)
1589 if (c->as->corank)
1590 c->attr.codimension = 1;
1591 if (c->as->rank)
1592 c->attr.dimension = 1;
1594 *as = NULL;
1596 /* Should this ever get more complicated, combine with similar section
1597 in add_init_expr_to_sym into a separate function. */
1598 if (c->ts.type == BT_CHARACTER && !c->attr.pointer && c->initializer
1599 && c->ts.u.cl
1600 && c->ts.u.cl->length && c->ts.u.cl->length->expr_type == EXPR_CONSTANT)
1602 int len;
1604 gcc_assert (c->ts.u.cl && c->ts.u.cl->length);
1605 gcc_assert (c->ts.u.cl->length->expr_type == EXPR_CONSTANT);
1606 gcc_assert (c->ts.u.cl->length->ts.type == BT_INTEGER);
1608 len = mpz_get_si (c->ts.u.cl->length->value.integer);
1610 if (c->initializer->expr_type == EXPR_CONSTANT)
1611 gfc_set_constant_character_len (len, c->initializer, -1);
1612 else if (mpz_cmp (c->ts.u.cl->length->value.integer,
1613 c->initializer->ts.u.cl->length->value.integer))
1615 gfc_constructor *ctor;
1616 ctor = gfc_constructor_first (c->initializer->value.constructor);
1618 if (ctor)
1620 int first_len;
1621 bool has_ts = (c->initializer->ts.u.cl
1622 && c->initializer->ts.u.cl->length_from_typespec);
1624 /* Remember the length of the first element for checking
1625 that all elements *in the constructor* have the same
1626 length. This need not be the length of the LHS! */
1627 gcc_assert (ctor->expr->expr_type == EXPR_CONSTANT);
1628 gcc_assert (ctor->expr->ts.type == BT_CHARACTER);
1629 first_len = ctor->expr->value.character.length;
1631 for ( ; ctor; ctor = gfc_constructor_next (ctor))
1632 if (ctor->expr->expr_type == EXPR_CONSTANT)
1634 gfc_set_constant_character_len (len, ctor->expr,
1635 has_ts ? -1 : first_len);
1636 ctor->expr->ts.u.cl->length = gfc_copy_expr (c->ts.u.cl->length);
1642 /* Check array components. */
1643 if (!c->attr.dimension)
1644 goto scalar;
1646 if (c->attr.pointer)
1648 if (c->as->type != AS_DEFERRED)
1650 gfc_error ("Pointer array component of structure at %C must have a "
1651 "deferred shape");
1652 t = false;
1655 else if (c->attr.allocatable)
1657 if (c->as->type != AS_DEFERRED)
1659 gfc_error ("Allocatable component of structure at %C must have a "
1660 "deferred shape");
1661 t = false;
1664 else
1666 if (c->as->type != AS_EXPLICIT)
1668 gfc_error ("Array component of structure at %C must have an "
1669 "explicit shape");
1670 t = false;
1674 scalar:
1675 if (c->ts.type == BT_CLASS)
1677 bool t2 = gfc_build_class_symbol (&c->ts, &c->attr, &c->as);
1679 if (t)
1680 t = t2;
1683 return t;
1687 /* Match a 'NULL()', and possibly take care of some side effects. */
1689 match
1690 gfc_match_null (gfc_expr **result)
1692 gfc_symbol *sym;
1693 match m, m2 = MATCH_NO;
1695 if ((m = gfc_match (" null ( )")) == MATCH_ERROR)
1696 return MATCH_ERROR;
1698 if (m == MATCH_NO)
1700 locus old_loc;
1701 char name[GFC_MAX_SYMBOL_LEN + 1];
1703 if ((m2 = gfc_match (" null (")) != MATCH_YES)
1704 return m2;
1706 old_loc = gfc_current_locus;
1707 if ((m2 = gfc_match (" %n ) ", name)) == MATCH_ERROR)
1708 return MATCH_ERROR;
1709 if (m2 != MATCH_YES
1710 && ((m2 = gfc_match (" mold = %n )", name)) == MATCH_ERROR))
1711 return MATCH_ERROR;
1712 if (m2 == MATCH_NO)
1714 gfc_current_locus = old_loc;
1715 return MATCH_NO;
1719 /* The NULL symbol now has to be/become an intrinsic function. */
1720 if (gfc_get_symbol ("null", NULL, &sym))
1722 gfc_error ("NULL() initialization at %C is ambiguous");
1723 return MATCH_ERROR;
1726 gfc_intrinsic_symbol (sym);
1728 if (sym->attr.proc != PROC_INTRINSIC
1729 && !(sym->attr.use_assoc && sym->attr.intrinsic)
1730 && (!gfc_add_procedure(&sym->attr, PROC_INTRINSIC, sym->name, NULL)
1731 || !gfc_add_function (&sym->attr, sym->name, NULL)))
1732 return MATCH_ERROR;
1734 *result = gfc_get_null_expr (&gfc_current_locus);
1736 /* Invalid per F2008, C512. */
1737 if (m2 == MATCH_YES)
1739 gfc_error ("NULL() initialization at %C may not have MOLD");
1740 return MATCH_ERROR;
1743 return MATCH_YES;
1747 /* Match the initialization expr for a data pointer or procedure pointer. */
1749 static match
1750 match_pointer_init (gfc_expr **init, int procptr)
1752 match m;
1754 if (gfc_pure (NULL) && gfc_state_stack->state != COMP_DERIVED)
1756 gfc_error ("Initialization of pointer at %C is not allowed in "
1757 "a PURE procedure");
1758 return MATCH_ERROR;
1760 gfc_unset_implicit_pure (gfc_current_ns->proc_name);
1762 /* Match NULL() initialization. */
1763 m = gfc_match_null (init);
1764 if (m != MATCH_NO)
1765 return m;
1767 /* Match non-NULL initialization. */
1768 gfc_matching_ptr_assignment = !procptr;
1769 gfc_matching_procptr_assignment = procptr;
1770 m = gfc_match_rvalue (init);
1771 gfc_matching_ptr_assignment = 0;
1772 gfc_matching_procptr_assignment = 0;
1773 if (m == MATCH_ERROR)
1774 return MATCH_ERROR;
1775 else if (m == MATCH_NO)
1777 gfc_error ("Error in pointer initialization at %C");
1778 return MATCH_ERROR;
1781 if (!procptr && !gfc_resolve_expr (*init))
1782 return MATCH_ERROR;
1784 if (!gfc_notify_std (GFC_STD_F2008, "non-NULL pointer "
1785 "initialization at %C"))
1786 return MATCH_ERROR;
1788 return MATCH_YES;
1792 static bool
1793 check_function_name (char *name)
1795 /* In functions that have a RESULT variable defined, the function name always
1796 refers to function calls. Therefore, the name is not allowed to appear in
1797 specification statements. When checking this, be careful about
1798 'hidden' procedure pointer results ('ppr@'). */
1800 if (gfc_current_state () == COMP_FUNCTION)
1802 gfc_symbol *block = gfc_current_block ();
1803 if (block && block->result && block->result != block
1804 && strcmp (block->result->name, "ppr@") != 0
1805 && strcmp (block->name, name) == 0)
1807 gfc_error ("Function name %qs not allowed at %C", name);
1808 return false;
1812 return true;
1816 /* Match a variable name with an optional initializer. When this
1817 subroutine is called, a variable is expected to be parsed next.
1818 Depending on what is happening at the moment, updates either the
1819 symbol table or the current interface. */
1821 static match
1822 variable_decl (int elem)
1824 char name[GFC_MAX_SYMBOL_LEN + 1];
1825 gfc_expr *initializer, *char_len;
1826 gfc_array_spec *as;
1827 gfc_array_spec *cp_as; /* Extra copy for Cray Pointees. */
1828 gfc_charlen *cl;
1829 bool cl_deferred;
1830 locus var_locus;
1831 match m;
1832 bool t;
1833 gfc_symbol *sym;
1835 initializer = NULL;
1836 as = NULL;
1837 cp_as = NULL;
1839 /* When we get here, we've just matched a list of attributes and
1840 maybe a type and a double colon. The next thing we expect to see
1841 is the name of the symbol. */
1842 m = gfc_match_name (name);
1843 if (m != MATCH_YES)
1844 goto cleanup;
1846 var_locus = gfc_current_locus;
1848 /* Now we could see the optional array spec. or character length. */
1849 m = gfc_match_array_spec (&as, true, true);
1850 if (m == MATCH_ERROR)
1851 goto cleanup;
1853 if (m == MATCH_NO)
1854 as = gfc_copy_array_spec (current_as);
1855 else if (current_as
1856 && !merge_array_spec (current_as, as, true))
1858 m = MATCH_ERROR;
1859 goto cleanup;
1862 if (flag_cray_pointer)
1863 cp_as = gfc_copy_array_spec (as);
1865 /* At this point, we know for sure if the symbol is PARAMETER and can thus
1866 determine (and check) whether it can be implied-shape. If it
1867 was parsed as assumed-size, change it because PARAMETERs can not
1868 be assumed-size. */
1869 if (as)
1871 if (as->type == AS_IMPLIED_SHAPE && current_attr.flavor != FL_PARAMETER)
1873 m = MATCH_ERROR;
1874 gfc_error ("Non-PARAMETER symbol %qs at %L can't be implied-shape",
1875 name, &var_locus);
1876 goto cleanup;
1879 if (as->type == AS_ASSUMED_SIZE && as->rank == 1
1880 && current_attr.flavor == FL_PARAMETER)
1881 as->type = AS_IMPLIED_SHAPE;
1883 if (as->type == AS_IMPLIED_SHAPE
1884 && !gfc_notify_std (GFC_STD_F2008, "Implied-shape array at %L",
1885 &var_locus))
1887 m = MATCH_ERROR;
1888 goto cleanup;
1892 char_len = NULL;
1893 cl = NULL;
1894 cl_deferred = false;
1896 if (current_ts.type == BT_CHARACTER)
1898 switch (match_char_length (&char_len, &cl_deferred, false))
1900 case MATCH_YES:
1901 cl = gfc_new_charlen (gfc_current_ns, NULL);
1903 cl->length = char_len;
1904 break;
1906 /* Non-constant lengths need to be copied after the first
1907 element. Also copy assumed lengths. */
1908 case MATCH_NO:
1909 if (elem > 1
1910 && (current_ts.u.cl->length == NULL
1911 || current_ts.u.cl->length->expr_type != EXPR_CONSTANT))
1913 cl = gfc_new_charlen (gfc_current_ns, NULL);
1914 cl->length = gfc_copy_expr (current_ts.u.cl->length);
1916 else
1917 cl = current_ts.u.cl;
1919 cl_deferred = current_ts.deferred;
1921 break;
1923 case MATCH_ERROR:
1924 goto cleanup;
1928 /* If this symbol has already shown up in a Cray Pointer declaration,
1929 and this is not a component declaration,
1930 then we want to set the type & bail out. */
1931 if (flag_cray_pointer && gfc_current_state () != COMP_DERIVED)
1933 gfc_find_symbol (name, gfc_current_ns, 1, &sym);
1934 if (sym != NULL && sym->attr.cray_pointee)
1936 sym->ts.type = current_ts.type;
1937 sym->ts.kind = current_ts.kind;
1938 sym->ts.u.cl = cl;
1939 sym->ts.u.derived = current_ts.u.derived;
1940 sym->ts.is_c_interop = current_ts.is_c_interop;
1941 sym->ts.is_iso_c = current_ts.is_iso_c;
1942 m = MATCH_YES;
1944 /* Check to see if we have an array specification. */
1945 if (cp_as != NULL)
1947 if (sym->as != NULL)
1949 gfc_error ("Duplicate array spec for Cray pointee at %C");
1950 gfc_free_array_spec (cp_as);
1951 m = MATCH_ERROR;
1952 goto cleanup;
1954 else
1956 if (!gfc_set_array_spec (sym, cp_as, &var_locus))
1957 gfc_internal_error ("Couldn't set pointee array spec.");
1959 /* Fix the array spec. */
1960 m = gfc_mod_pointee_as (sym->as);
1961 if (m == MATCH_ERROR)
1962 goto cleanup;
1965 goto cleanup;
1967 else
1969 gfc_free_array_spec (cp_as);
1973 /* Procedure pointer as function result. */
1974 if (gfc_current_state () == COMP_FUNCTION
1975 && strcmp ("ppr@", gfc_current_block ()->name) == 0
1976 && strcmp (name, gfc_current_block ()->ns->proc_name->name) == 0)
1977 strcpy (name, "ppr@");
1979 if (gfc_current_state () == COMP_FUNCTION
1980 && strcmp (name, gfc_current_block ()->name) == 0
1981 && gfc_current_block ()->result
1982 && strcmp ("ppr@", gfc_current_block ()->result->name) == 0)
1983 strcpy (name, "ppr@");
1985 /* OK, we've successfully matched the declaration. Now put the
1986 symbol in the current namespace, because it might be used in the
1987 optional initialization expression for this symbol, e.g. this is
1988 perfectly legal:
1990 integer, parameter :: i = huge(i)
1992 This is only true for parameters or variables of a basic type.
1993 For components of derived types, it is not true, so we don't
1994 create a symbol for those yet. If we fail to create the symbol,
1995 bail out. */
1996 if (gfc_current_state () != COMP_DERIVED
1997 && !build_sym (name, cl, cl_deferred, &as, &var_locus))
1999 m = MATCH_ERROR;
2000 goto cleanup;
2003 if (!check_function_name (name))
2005 m = MATCH_ERROR;
2006 goto cleanup;
2009 /* We allow old-style initializations of the form
2010 integer i /2/, j(4) /3*3, 1/
2011 (if no colon has been seen). These are different from data
2012 statements in that initializers are only allowed to apply to the
2013 variable immediately preceding, i.e.
2014 integer i, j /1, 2/
2015 is not allowed. Therefore we have to do some work manually, that
2016 could otherwise be left to the matchers for DATA statements. */
2018 if (!colon_seen && gfc_match (" /") == MATCH_YES)
2020 if (!gfc_notify_std (GFC_STD_GNU, "Old-style "
2021 "initialization at %C"))
2022 return MATCH_ERROR;
2023 else if (gfc_current_state () == COMP_DERIVED)
2025 gfc_error ("Invalid old style initialization for derived type "
2026 "component at %C");
2027 m = MATCH_ERROR;
2028 goto cleanup;
2031 return match_old_style_init (name);
2034 /* The double colon must be present in order to have initializers.
2035 Otherwise the statement is ambiguous with an assignment statement. */
2036 if (colon_seen)
2038 if (gfc_match (" =>") == MATCH_YES)
2040 if (!current_attr.pointer)
2042 gfc_error ("Initialization at %C isn't for a pointer variable");
2043 m = MATCH_ERROR;
2044 goto cleanup;
2047 m = match_pointer_init (&initializer, 0);
2048 if (m != MATCH_YES)
2049 goto cleanup;
2051 else if (gfc_match_char ('=') == MATCH_YES)
2053 if (current_attr.pointer)
2055 gfc_error ("Pointer initialization at %C requires %<=>%>, "
2056 "not %<=%>");
2057 m = MATCH_ERROR;
2058 goto cleanup;
2061 m = gfc_match_init_expr (&initializer);
2062 if (m == MATCH_NO)
2064 gfc_error ("Expected an initialization expression at %C");
2065 m = MATCH_ERROR;
2068 if (current_attr.flavor != FL_PARAMETER && gfc_pure (NULL)
2069 && gfc_state_stack->state != COMP_DERIVED)
2071 gfc_error ("Initialization of variable at %C is not allowed in "
2072 "a PURE procedure");
2073 m = MATCH_ERROR;
2076 if (current_attr.flavor != FL_PARAMETER
2077 && gfc_state_stack->state != COMP_DERIVED)
2078 gfc_unset_implicit_pure (gfc_current_ns->proc_name);
2080 if (m != MATCH_YES)
2081 goto cleanup;
2085 if (initializer != NULL && current_attr.allocatable
2086 && gfc_current_state () == COMP_DERIVED)
2088 gfc_error ("Initialization of allocatable component at %C is not "
2089 "allowed");
2090 m = MATCH_ERROR;
2091 goto cleanup;
2094 /* Add the initializer. Note that it is fine if initializer is
2095 NULL here, because we sometimes also need to check if a
2096 declaration *must* have an initialization expression. */
2097 if (gfc_current_state () != COMP_DERIVED)
2098 t = add_init_expr_to_sym (name, &initializer, &var_locus);
2099 else
2101 if (current_ts.type == BT_DERIVED
2102 && !current_attr.pointer && !initializer)
2103 initializer = gfc_default_initializer (&current_ts);
2104 t = build_struct (name, cl, &initializer, &as);
2107 m = (t) ? MATCH_YES : MATCH_ERROR;
2109 cleanup:
2110 /* Free stuff up and return. */
2111 gfc_free_expr (initializer);
2112 gfc_free_array_spec (as);
2114 return m;
2118 /* Match an extended-f77 "TYPESPEC*bytesize"-style kind specification.
2119 This assumes that the byte size is equal to the kind number for
2120 non-COMPLEX types, and equal to twice the kind number for COMPLEX. */
2122 match
2123 gfc_match_old_kind_spec (gfc_typespec *ts)
2125 match m;
2126 int original_kind;
2128 if (gfc_match_char ('*') != MATCH_YES)
2129 return MATCH_NO;
2131 m = gfc_match_small_literal_int (&ts->kind, NULL);
2132 if (m != MATCH_YES)
2133 return MATCH_ERROR;
2135 original_kind = ts->kind;
2137 /* Massage the kind numbers for complex types. */
2138 if (ts->type == BT_COMPLEX)
2140 if (ts->kind % 2)
2142 gfc_error ("Old-style type declaration %s*%d not supported at %C",
2143 gfc_basic_typename (ts->type), original_kind);
2144 return MATCH_ERROR;
2146 ts->kind /= 2;
2150 if (ts->type == BT_INTEGER && ts->kind == 4 && flag_integer4_kind == 8)
2151 ts->kind = 8;
2153 if (ts->type == BT_REAL || ts->type == BT_COMPLEX)
2155 if (ts->kind == 4)
2157 if (flag_real4_kind == 8)
2158 ts->kind = 8;
2159 if (flag_real4_kind == 10)
2160 ts->kind = 10;
2161 if (flag_real4_kind == 16)
2162 ts->kind = 16;
2165 if (ts->kind == 8)
2167 if (flag_real8_kind == 4)
2168 ts->kind = 4;
2169 if (flag_real8_kind == 10)
2170 ts->kind = 10;
2171 if (flag_real8_kind == 16)
2172 ts->kind = 16;
2176 if (gfc_validate_kind (ts->type, ts->kind, true) < 0)
2178 gfc_error ("Old-style type declaration %s*%d not supported at %C",
2179 gfc_basic_typename (ts->type), original_kind);
2180 return MATCH_ERROR;
2183 if (!gfc_notify_std (GFC_STD_GNU,
2184 "Nonstandard type declaration %s*%d at %C",
2185 gfc_basic_typename(ts->type), original_kind))
2186 return MATCH_ERROR;
2188 return MATCH_YES;
2192 /* Match a kind specification. Since kinds are generally optional, we
2193 usually return MATCH_NO if something goes wrong. If a "kind="
2194 string is found, then we know we have an error. */
2196 match
2197 gfc_match_kind_spec (gfc_typespec *ts, bool kind_expr_only)
2199 locus where, loc;
2200 gfc_expr *e;
2201 match m, n;
2202 char c;
2203 const char *msg;
2205 m = MATCH_NO;
2206 n = MATCH_YES;
2207 e = NULL;
2209 where = loc = gfc_current_locus;
2211 if (kind_expr_only)
2212 goto kind_expr;
2214 if (gfc_match_char ('(') == MATCH_NO)
2215 return MATCH_NO;
2217 /* Also gobbles optional text. */
2218 if (gfc_match (" kind = ") == MATCH_YES)
2219 m = MATCH_ERROR;
2221 loc = gfc_current_locus;
2223 kind_expr:
2224 n = gfc_match_init_expr (&e);
2226 if (n != MATCH_YES)
2228 if (gfc_matching_function)
2230 /* The function kind expression might include use associated or
2231 imported parameters and try again after the specification
2232 expressions..... */
2233 if (gfc_match_char (')') != MATCH_YES)
2235 gfc_error ("Missing right parenthesis at %C");
2236 m = MATCH_ERROR;
2237 goto no_match;
2240 gfc_free_expr (e);
2241 gfc_undo_symbols ();
2242 return MATCH_YES;
2244 else
2246 /* ....or else, the match is real. */
2247 if (n == MATCH_NO)
2248 gfc_error ("Expected initialization expression at %C");
2249 if (n != MATCH_YES)
2250 return MATCH_ERROR;
2254 if (e->rank != 0)
2256 gfc_error ("Expected scalar initialization expression at %C");
2257 m = MATCH_ERROR;
2258 goto no_match;
2261 msg = gfc_extract_int (e, &ts->kind);
2263 if (msg != NULL)
2265 gfc_error (msg);
2266 m = MATCH_ERROR;
2267 goto no_match;
2270 /* Before throwing away the expression, let's see if we had a
2271 C interoperable kind (and store the fact). */
2272 if (e->ts.is_c_interop == 1)
2274 /* Mark this as C interoperable if being declared with one
2275 of the named constants from iso_c_binding. */
2276 ts->is_c_interop = e->ts.is_iso_c;
2277 ts->f90_type = e->ts.f90_type;
2280 gfc_free_expr (e);
2281 e = NULL;
2283 /* Ignore errors to this point, if we've gotten here. This means
2284 we ignore the m=MATCH_ERROR from above. */
2285 if (gfc_validate_kind (ts->type, ts->kind, true) < 0)
2287 gfc_error ("Kind %d not supported for type %s at %C", ts->kind,
2288 gfc_basic_typename (ts->type));
2289 gfc_current_locus = where;
2290 return MATCH_ERROR;
2293 /* Warn if, e.g., c_int is used for a REAL variable, but not
2294 if, e.g., c_double is used for COMPLEX as the standard
2295 explicitly says that the kind type parameter for complex and real
2296 variable is the same, i.e. c_float == c_float_complex. */
2297 if (ts->f90_type != BT_UNKNOWN && ts->f90_type != ts->type
2298 && !((ts->f90_type == BT_REAL && ts->type == BT_COMPLEX)
2299 || (ts->f90_type == BT_COMPLEX && ts->type == BT_REAL)))
2300 gfc_warning_now (0, "C kind type parameter is for type %s but type at %L "
2301 "is %s", gfc_basic_typename (ts->f90_type), &where,
2302 gfc_basic_typename (ts->type));
2304 gfc_gobble_whitespace ();
2305 if ((c = gfc_next_ascii_char ()) != ')'
2306 && (ts->type != BT_CHARACTER || c != ','))
2308 if (ts->type == BT_CHARACTER)
2309 gfc_error ("Missing right parenthesis or comma at %C");
2310 else
2311 gfc_error ("Missing right parenthesis at %C");
2312 m = MATCH_ERROR;
2314 else
2315 /* All tests passed. */
2316 m = MATCH_YES;
2318 if(m == MATCH_ERROR)
2319 gfc_current_locus = where;
2321 if (ts->type == BT_INTEGER && ts->kind == 4 && flag_integer4_kind == 8)
2322 ts->kind = 8;
2324 if (ts->type == BT_REAL || ts->type == BT_COMPLEX)
2326 if (ts->kind == 4)
2328 if (flag_real4_kind == 8)
2329 ts->kind = 8;
2330 if (flag_real4_kind == 10)
2331 ts->kind = 10;
2332 if (flag_real4_kind == 16)
2333 ts->kind = 16;
2336 if (ts->kind == 8)
2338 if (flag_real8_kind == 4)
2339 ts->kind = 4;
2340 if (flag_real8_kind == 10)
2341 ts->kind = 10;
2342 if (flag_real8_kind == 16)
2343 ts->kind = 16;
2347 /* Return what we know from the test(s). */
2348 return m;
2350 no_match:
2351 gfc_free_expr (e);
2352 gfc_current_locus = where;
2353 return m;
2357 static match
2358 match_char_kind (int * kind, int * is_iso_c)
2360 locus where;
2361 gfc_expr *e;
2362 match m, n;
2363 const char *msg;
2365 m = MATCH_NO;
2366 e = NULL;
2367 where = gfc_current_locus;
2369 n = gfc_match_init_expr (&e);
2371 if (n != MATCH_YES && gfc_matching_function)
2373 /* The expression might include use-associated or imported
2374 parameters and try again after the specification
2375 expressions. */
2376 gfc_free_expr (e);
2377 gfc_undo_symbols ();
2378 return MATCH_YES;
2381 if (n == MATCH_NO)
2382 gfc_error ("Expected initialization expression at %C");
2383 if (n != MATCH_YES)
2384 return MATCH_ERROR;
2386 if (e->rank != 0)
2388 gfc_error ("Expected scalar initialization expression at %C");
2389 m = MATCH_ERROR;
2390 goto no_match;
2393 msg = gfc_extract_int (e, kind);
2394 *is_iso_c = e->ts.is_iso_c;
2395 if (msg != NULL)
2397 gfc_error (msg);
2398 m = MATCH_ERROR;
2399 goto no_match;
2402 gfc_free_expr (e);
2404 /* Ignore errors to this point, if we've gotten here. This means
2405 we ignore the m=MATCH_ERROR from above. */
2406 if (gfc_validate_kind (BT_CHARACTER, *kind, true) < 0)
2408 gfc_error ("Kind %d is not supported for CHARACTER at %C", *kind);
2409 m = MATCH_ERROR;
2411 else
2412 /* All tests passed. */
2413 m = MATCH_YES;
2415 if (m == MATCH_ERROR)
2416 gfc_current_locus = where;
2418 /* Return what we know from the test(s). */
2419 return m;
2421 no_match:
2422 gfc_free_expr (e);
2423 gfc_current_locus = where;
2424 return m;
2428 /* Match the various kind/length specifications in a CHARACTER
2429 declaration. We don't return MATCH_NO. */
2431 match
2432 gfc_match_char_spec (gfc_typespec *ts)
2434 int kind, seen_length, is_iso_c;
2435 gfc_charlen *cl;
2436 gfc_expr *len;
2437 match m;
2438 bool deferred;
2440 len = NULL;
2441 seen_length = 0;
2442 kind = 0;
2443 is_iso_c = 0;
2444 deferred = false;
2446 /* Try the old-style specification first. */
2447 old_char_selector = 0;
2449 m = match_char_length (&len, &deferred, true);
2450 if (m != MATCH_NO)
2452 if (m == MATCH_YES)
2453 old_char_selector = 1;
2454 seen_length = 1;
2455 goto done;
2458 m = gfc_match_char ('(');
2459 if (m != MATCH_YES)
2461 m = MATCH_YES; /* Character without length is a single char. */
2462 goto done;
2465 /* Try the weird case: ( KIND = <int> [ , LEN = <len-param> ] ). */
2466 if (gfc_match (" kind =") == MATCH_YES)
2468 m = match_char_kind (&kind, &is_iso_c);
2470 if (m == MATCH_ERROR)
2471 goto done;
2472 if (m == MATCH_NO)
2473 goto syntax;
2475 if (gfc_match (" , len =") == MATCH_NO)
2476 goto rparen;
2478 m = char_len_param_value (&len, &deferred);
2479 if (m == MATCH_NO)
2480 goto syntax;
2481 if (m == MATCH_ERROR)
2482 goto done;
2483 seen_length = 1;
2485 goto rparen;
2488 /* Try to match "LEN = <len-param>" or "LEN = <len-param>, KIND = <int>". */
2489 if (gfc_match (" len =") == MATCH_YES)
2491 m = char_len_param_value (&len, &deferred);
2492 if (m == MATCH_NO)
2493 goto syntax;
2494 if (m == MATCH_ERROR)
2495 goto done;
2496 seen_length = 1;
2498 if (gfc_match_char (')') == MATCH_YES)
2499 goto done;
2501 if (gfc_match (" , kind =") != MATCH_YES)
2502 goto syntax;
2504 if (match_char_kind (&kind, &is_iso_c) == MATCH_ERROR)
2505 goto done;
2507 goto rparen;
2510 /* Try to match ( <len-param> ) or ( <len-param> , [ KIND = ] <int> ). */
2511 m = char_len_param_value (&len, &deferred);
2512 if (m == MATCH_NO)
2513 goto syntax;
2514 if (m == MATCH_ERROR)
2515 goto done;
2516 seen_length = 1;
2518 m = gfc_match_char (')');
2519 if (m == MATCH_YES)
2520 goto done;
2522 if (gfc_match_char (',') != MATCH_YES)
2523 goto syntax;
2525 gfc_match (" kind ="); /* Gobble optional text. */
2527 m = match_char_kind (&kind, &is_iso_c);
2528 if (m == MATCH_ERROR)
2529 goto done;
2530 if (m == MATCH_NO)
2531 goto syntax;
2533 rparen:
2534 /* Require a right-paren at this point. */
2535 m = gfc_match_char (')');
2536 if (m == MATCH_YES)
2537 goto done;
2539 syntax:
2540 gfc_error ("Syntax error in CHARACTER declaration at %C");
2541 m = MATCH_ERROR;
2542 gfc_free_expr (len);
2543 return m;
2545 done:
2546 /* Deal with character functions after USE and IMPORT statements. */
2547 if (gfc_matching_function)
2549 gfc_free_expr (len);
2550 gfc_undo_symbols ();
2551 return MATCH_YES;
2554 if (m != MATCH_YES)
2556 gfc_free_expr (len);
2557 return m;
2560 /* Do some final massaging of the length values. */
2561 cl = gfc_new_charlen (gfc_current_ns, NULL);
2563 if (seen_length == 0)
2564 cl->length = gfc_get_int_expr (gfc_default_integer_kind, NULL, 1);
2565 else
2566 cl->length = len;
2568 ts->u.cl = cl;
2569 ts->kind = kind == 0 ? gfc_default_character_kind : kind;
2570 ts->deferred = deferred;
2572 /* We have to know if it was a C interoperable kind so we can
2573 do accurate type checking of bind(c) procs, etc. */
2574 if (kind != 0)
2575 /* Mark this as C interoperable if being declared with one
2576 of the named constants from iso_c_binding. */
2577 ts->is_c_interop = is_iso_c;
2578 else if (len != NULL)
2579 /* Here, we might have parsed something such as: character(c_char)
2580 In this case, the parsing code above grabs the c_char when
2581 looking for the length (line 1690, roughly). it's the last
2582 testcase for parsing the kind params of a character variable.
2583 However, it's not actually the length. this seems like it
2584 could be an error.
2585 To see if the user used a C interop kind, test the expr
2586 of the so called length, and see if it's C interoperable. */
2587 ts->is_c_interop = len->ts.is_iso_c;
2589 return MATCH_YES;
2593 /* Matches a declaration-type-spec (F03:R502). If successful, sets the ts
2594 structure to the matched specification. This is necessary for FUNCTION and
2595 IMPLICIT statements.
2597 If implicit_flag is nonzero, then we don't check for the optional
2598 kind specification. Not doing so is needed for matching an IMPLICIT
2599 statement correctly. */
2601 match
2602 gfc_match_decl_type_spec (gfc_typespec *ts, int implicit_flag)
2604 char name[GFC_MAX_SYMBOL_LEN + 1];
2605 gfc_symbol *sym, *dt_sym;
2606 match m;
2607 char c;
2608 bool seen_deferred_kind, matched_type;
2609 const char *dt_name;
2611 /* A belt and braces check that the typespec is correctly being treated
2612 as a deferred characteristic association. */
2613 seen_deferred_kind = (gfc_current_state () == COMP_FUNCTION)
2614 && (gfc_current_block ()->result->ts.kind == -1)
2615 && (ts->kind == -1);
2616 gfc_clear_ts (ts);
2617 if (seen_deferred_kind)
2618 ts->kind = -1;
2620 /* Clear the current binding label, in case one is given. */
2621 curr_binding_label = NULL;
2623 if (gfc_match (" byte") == MATCH_YES)
2625 if (!gfc_notify_std (GFC_STD_GNU, "BYTE type at %C"))
2626 return MATCH_ERROR;
2628 if (gfc_validate_kind (BT_INTEGER, 1, true) < 0)
2630 gfc_error ("BYTE type used at %C "
2631 "is not available on the target machine");
2632 return MATCH_ERROR;
2635 ts->type = BT_INTEGER;
2636 ts->kind = 1;
2637 return MATCH_YES;
2641 m = gfc_match (" type (");
2642 matched_type = (m == MATCH_YES);
2643 if (matched_type)
2645 gfc_gobble_whitespace ();
2646 if (gfc_peek_ascii_char () == '*')
2648 if ((m = gfc_match ("*)")) != MATCH_YES)
2649 return m;
2650 if (gfc_current_state () == COMP_DERIVED)
2652 gfc_error ("Assumed type at %C is not allowed for components");
2653 return MATCH_ERROR;
2655 if (!gfc_notify_std (GFC_STD_F2008_TS, "Assumed type "
2656 "at %C"))
2657 return MATCH_ERROR;
2658 ts->type = BT_ASSUMED;
2659 return MATCH_YES;
2662 m = gfc_match ("%n", name);
2663 matched_type = (m == MATCH_YES);
2666 if ((matched_type && strcmp ("integer", name) == 0)
2667 || (!matched_type && gfc_match (" integer") == MATCH_YES))
2669 ts->type = BT_INTEGER;
2670 ts->kind = gfc_default_integer_kind;
2671 goto get_kind;
2674 if ((matched_type && strcmp ("character", name) == 0)
2675 || (!matched_type && gfc_match (" character") == MATCH_YES))
2677 if (matched_type
2678 && !gfc_notify_std (GFC_STD_F2008, "TYPE with "
2679 "intrinsic-type-spec at %C"))
2680 return MATCH_ERROR;
2682 ts->type = BT_CHARACTER;
2683 if (implicit_flag == 0)
2684 m = gfc_match_char_spec (ts);
2685 else
2686 m = MATCH_YES;
2688 if (matched_type && m == MATCH_YES && gfc_match_char (')') != MATCH_YES)
2689 m = MATCH_ERROR;
2691 return m;
2694 if ((matched_type && strcmp ("real", name) == 0)
2695 || (!matched_type && gfc_match (" real") == MATCH_YES))
2697 ts->type = BT_REAL;
2698 ts->kind = gfc_default_real_kind;
2699 goto get_kind;
2702 if ((matched_type
2703 && (strcmp ("doubleprecision", name) == 0
2704 || (strcmp ("double", name) == 0
2705 && gfc_match (" precision") == MATCH_YES)))
2706 || (!matched_type && gfc_match (" double precision") == MATCH_YES))
2708 if (matched_type
2709 && !gfc_notify_std (GFC_STD_F2008, "TYPE with "
2710 "intrinsic-type-spec at %C"))
2711 return MATCH_ERROR;
2712 if (matched_type && gfc_match_char (')') != MATCH_YES)
2713 return MATCH_ERROR;
2715 ts->type = BT_REAL;
2716 ts->kind = gfc_default_double_kind;
2717 return MATCH_YES;
2720 if ((matched_type && strcmp ("complex", name) == 0)
2721 || (!matched_type && gfc_match (" complex") == MATCH_YES))
2723 ts->type = BT_COMPLEX;
2724 ts->kind = gfc_default_complex_kind;
2725 goto get_kind;
2728 if ((matched_type
2729 && (strcmp ("doublecomplex", name) == 0
2730 || (strcmp ("double", name) == 0
2731 && gfc_match (" complex") == MATCH_YES)))
2732 || (!matched_type && gfc_match (" double complex") == MATCH_YES))
2734 if (!gfc_notify_std (GFC_STD_GNU, "DOUBLE COMPLEX at %C"))
2735 return MATCH_ERROR;
2737 if (matched_type
2738 && !gfc_notify_std (GFC_STD_F2008, "TYPE with "
2739 "intrinsic-type-spec at %C"))
2740 return MATCH_ERROR;
2742 if (matched_type && gfc_match_char (')') != MATCH_YES)
2743 return MATCH_ERROR;
2745 ts->type = BT_COMPLEX;
2746 ts->kind = gfc_default_double_kind;
2747 return MATCH_YES;
2750 if ((matched_type && strcmp ("logical", name) == 0)
2751 || (!matched_type && gfc_match (" logical") == MATCH_YES))
2753 ts->type = BT_LOGICAL;
2754 ts->kind = gfc_default_logical_kind;
2755 goto get_kind;
2758 if (matched_type)
2759 m = gfc_match_char (')');
2761 if (m == MATCH_YES)
2762 ts->type = BT_DERIVED;
2763 else
2765 /* Match CLASS declarations. */
2766 m = gfc_match (" class ( * )");
2767 if (m == MATCH_ERROR)
2768 return MATCH_ERROR;
2769 else if (m == MATCH_YES)
2771 gfc_symbol *upe;
2772 gfc_symtree *st;
2773 ts->type = BT_CLASS;
2774 gfc_find_symbol ("STAR", gfc_current_ns, 1, &upe);
2775 if (upe == NULL)
2777 upe = gfc_new_symbol ("STAR", gfc_current_ns);
2778 st = gfc_new_symtree (&gfc_current_ns->sym_root, "STAR");
2779 st->n.sym = upe;
2780 gfc_set_sym_referenced (upe);
2781 upe->refs++;
2782 upe->ts.type = BT_VOID;
2783 upe->attr.unlimited_polymorphic = 1;
2784 /* This is essential to force the construction of
2785 unlimited polymorphic component class containers. */
2786 upe->attr.zero_comp = 1;
2787 if (!gfc_add_flavor (&upe->attr, FL_DERIVED, NULL,
2788 &gfc_current_locus))
2789 return MATCH_ERROR;
2791 else
2793 st = gfc_find_symtree (gfc_current_ns->sym_root, "STAR");
2794 if (st == NULL)
2795 st = gfc_new_symtree (&gfc_current_ns->sym_root, "STAR");
2796 st->n.sym = upe;
2797 upe->refs++;
2799 ts->u.derived = upe;
2800 return m;
2803 m = gfc_match (" class ( %n )", name);
2804 if (m != MATCH_YES)
2805 return m;
2806 ts->type = BT_CLASS;
2808 if (!gfc_notify_std (GFC_STD_F2003, "CLASS statement at %C"))
2809 return MATCH_ERROR;
2812 /* Defer association of the derived type until the end of the
2813 specification block. However, if the derived type can be
2814 found, add it to the typespec. */
2815 if (gfc_matching_function)
2817 ts->u.derived = NULL;
2818 if (gfc_current_state () != COMP_INTERFACE
2819 && !gfc_find_symbol (name, NULL, 1, &sym) && sym)
2821 sym = gfc_find_dt_in_generic (sym);
2822 ts->u.derived = sym;
2824 return MATCH_YES;
2827 /* Search for the name but allow the components to be defined later. If
2828 type = -1, this typespec has been seen in a function declaration but
2829 the type could not be accessed at that point. The actual derived type is
2830 stored in a symtree with the first letter of the name capitalized; the
2831 symtree with the all lower-case name contains the associated
2832 generic function. */
2833 dt_name = gfc_get_string ("%c%s",
2834 (char) TOUPPER ((unsigned char) name[0]),
2835 (const char*)&name[1]);
2836 sym = NULL;
2837 dt_sym = NULL;
2838 if (ts->kind != -1)
2840 gfc_get_ha_symbol (name, &sym);
2841 if (sym->generic && gfc_find_symbol (dt_name, NULL, 0, &dt_sym))
2843 gfc_error ("Type name %qs at %C is ambiguous", name);
2844 return MATCH_ERROR;
2846 if (sym->generic && !dt_sym)
2847 dt_sym = gfc_find_dt_in_generic (sym);
2849 else if (ts->kind == -1)
2851 int iface = gfc_state_stack->previous->state != COMP_INTERFACE
2852 || gfc_current_ns->has_import_set;
2853 gfc_find_symbol (name, NULL, iface, &sym);
2854 if (sym && sym->generic && gfc_find_symbol (dt_name, NULL, 1, &dt_sym))
2856 gfc_error ("Type name %qs at %C is ambiguous", name);
2857 return MATCH_ERROR;
2859 if (sym && sym->generic && !dt_sym)
2860 dt_sym = gfc_find_dt_in_generic (sym);
2862 ts->kind = 0;
2863 if (sym == NULL)
2864 return MATCH_NO;
2867 if ((sym->attr.flavor != FL_UNKNOWN
2868 && !(sym->attr.flavor == FL_PROCEDURE && sym->attr.generic))
2869 || sym->attr.subroutine)
2871 gfc_error_1 ("Type name '%s' at %C conflicts with previously declared "
2872 "entity at %L, which has the same name", name,
2873 &sym->declared_at);
2874 return MATCH_ERROR;
2877 gfc_save_symbol_data (sym);
2878 gfc_set_sym_referenced (sym);
2879 if (!sym->attr.generic
2880 && !gfc_add_generic (&sym->attr, sym->name, NULL))
2881 return MATCH_ERROR;
2883 if (!sym->attr.function
2884 && !gfc_add_function (&sym->attr, sym->name, NULL))
2885 return MATCH_ERROR;
2887 if (!dt_sym)
2889 gfc_interface *intr, *head;
2891 /* Use upper case to save the actual derived-type symbol. */
2892 gfc_get_symbol (dt_name, NULL, &dt_sym);
2893 dt_sym->name = gfc_get_string (sym->name);
2894 head = sym->generic;
2895 intr = gfc_get_interface ();
2896 intr->sym = dt_sym;
2897 intr->where = gfc_current_locus;
2898 intr->next = head;
2899 sym->generic = intr;
2900 sym->attr.if_source = IFSRC_DECL;
2902 else
2903 gfc_save_symbol_data (dt_sym);
2905 gfc_set_sym_referenced (dt_sym);
2907 if (dt_sym->attr.flavor != FL_DERIVED
2908 && !gfc_add_flavor (&dt_sym->attr, FL_DERIVED, sym->name, NULL))
2909 return MATCH_ERROR;
2911 ts->u.derived = dt_sym;
2913 return MATCH_YES;
2915 get_kind:
2916 if (matched_type
2917 && !gfc_notify_std (GFC_STD_F2008, "TYPE with "
2918 "intrinsic-type-spec at %C"))
2919 return MATCH_ERROR;
2921 /* For all types except double, derived and character, look for an
2922 optional kind specifier. MATCH_NO is actually OK at this point. */
2923 if (implicit_flag == 1)
2925 if (matched_type && gfc_match_char (')') != MATCH_YES)
2926 return MATCH_ERROR;
2928 return MATCH_YES;
2931 if (gfc_current_form == FORM_FREE)
2933 c = gfc_peek_ascii_char ();
2934 if (!gfc_is_whitespace (c) && c != '*' && c != '('
2935 && c != ':' && c != ',')
2937 if (matched_type && c == ')')
2939 gfc_next_ascii_char ();
2940 return MATCH_YES;
2942 return MATCH_NO;
2946 m = gfc_match_kind_spec (ts, false);
2947 if (m == MATCH_NO && ts->type != BT_CHARACTER)
2948 m = gfc_match_old_kind_spec (ts);
2950 if (matched_type && gfc_match_char (')') != MATCH_YES)
2951 return MATCH_ERROR;
2953 /* Defer association of the KIND expression of function results
2954 until after USE and IMPORT statements. */
2955 if ((gfc_current_state () == COMP_NONE && gfc_error_flag_test ())
2956 || gfc_matching_function)
2957 return MATCH_YES;
2959 if (m == MATCH_NO)
2960 m = MATCH_YES; /* No kind specifier found. */
2962 return m;
2966 /* Match an IMPLICIT NONE statement. Actually, this statement is
2967 already matched in parse.c, or we would not end up here in the
2968 first place. So the only thing we need to check, is if there is
2969 trailing garbage. If not, the match is successful. */
2971 match
2972 gfc_match_implicit_none (void)
2974 char c;
2975 match m;
2976 char name[GFC_MAX_SYMBOL_LEN + 1];
2977 bool type = false;
2978 bool external = false;
2979 locus cur_loc = gfc_current_locus;
2981 if (gfc_current_ns->seen_implicit_none
2982 || gfc_current_ns->has_implicit_none_export)
2984 gfc_error ("Duplicate IMPLICIT NONE statement at %C");
2985 return MATCH_ERROR;
2988 gfc_gobble_whitespace ();
2989 c = gfc_peek_ascii_char ();
2990 if (c == '(')
2992 (void) gfc_next_ascii_char ();
2993 if (!gfc_notify_std (GFC_STD_F2015, "IMPORT NONE with spec list at %C"))
2994 return MATCH_ERROR;
2996 gfc_gobble_whitespace ();
2997 if (gfc_peek_ascii_char () == ')')
2999 (void) gfc_next_ascii_char ();
3000 type = true;
3002 else
3003 for(;;)
3005 m = gfc_match (" %n", name);
3006 if (m != MATCH_YES)
3007 return MATCH_ERROR;
3009 if (strcmp (name, "type") == 0)
3010 type = true;
3011 else if (strcmp (name, "external") == 0)
3012 external = true;
3013 else
3014 return MATCH_ERROR;
3016 gfc_gobble_whitespace ();
3017 c = gfc_next_ascii_char ();
3018 if (c == ',')
3019 continue;
3020 if (c == ')')
3021 break;
3022 return MATCH_ERROR;
3025 else
3026 type = true;
3028 if (gfc_match_eos () != MATCH_YES)
3029 return MATCH_ERROR;
3031 gfc_set_implicit_none (type, external, &cur_loc);
3033 return MATCH_YES;
3037 /* Match the letter range(s) of an IMPLICIT statement. */
3039 static match
3040 match_implicit_range (void)
3042 char c, c1, c2;
3043 int inner;
3044 locus cur_loc;
3046 cur_loc = gfc_current_locus;
3048 gfc_gobble_whitespace ();
3049 c = gfc_next_ascii_char ();
3050 if (c != '(')
3052 gfc_error ("Missing character range in IMPLICIT at %C");
3053 goto bad;
3056 inner = 1;
3057 while (inner)
3059 gfc_gobble_whitespace ();
3060 c1 = gfc_next_ascii_char ();
3061 if (!ISALPHA (c1))
3062 goto bad;
3064 gfc_gobble_whitespace ();
3065 c = gfc_next_ascii_char ();
3067 switch (c)
3069 case ')':
3070 inner = 0; /* Fall through. */
3072 case ',':
3073 c2 = c1;
3074 break;
3076 case '-':
3077 gfc_gobble_whitespace ();
3078 c2 = gfc_next_ascii_char ();
3079 if (!ISALPHA (c2))
3080 goto bad;
3082 gfc_gobble_whitespace ();
3083 c = gfc_next_ascii_char ();
3085 if ((c != ',') && (c != ')'))
3086 goto bad;
3087 if (c == ')')
3088 inner = 0;
3090 break;
3092 default:
3093 goto bad;
3096 if (c1 > c2)
3098 gfc_error ("Letters must be in alphabetic order in "
3099 "IMPLICIT statement at %C");
3100 goto bad;
3103 /* See if we can add the newly matched range to the pending
3104 implicits from this IMPLICIT statement. We do not check for
3105 conflicts with whatever earlier IMPLICIT statements may have
3106 set. This is done when we've successfully finished matching
3107 the current one. */
3108 if (!gfc_add_new_implicit_range (c1, c2))
3109 goto bad;
3112 return MATCH_YES;
3114 bad:
3115 gfc_syntax_error (ST_IMPLICIT);
3117 gfc_current_locus = cur_loc;
3118 return MATCH_ERROR;
3122 /* Match an IMPLICIT statement, storing the types for
3123 gfc_set_implicit() if the statement is accepted by the parser.
3124 There is a strange looking, but legal syntactic construction
3125 possible. It looks like:
3127 IMPLICIT INTEGER (a-b) (c-d)
3129 This is legal if "a-b" is a constant expression that happens to
3130 equal one of the legal kinds for integers. The real problem
3131 happens with an implicit specification that looks like:
3133 IMPLICIT INTEGER (a-b)
3135 In this case, a typespec matcher that is "greedy" (as most of the
3136 matchers are) gobbles the character range as a kindspec, leaving
3137 nothing left. We therefore have to go a bit more slowly in the
3138 matching process by inhibiting the kindspec checking during
3139 typespec matching and checking for a kind later. */
3141 match
3142 gfc_match_implicit (void)
3144 gfc_typespec ts;
3145 locus cur_loc;
3146 char c;
3147 match m;
3149 if (gfc_current_ns->seen_implicit_none)
3151 gfc_error ("IMPLICIT statement at %C following an IMPLICIT NONE (type) "
3152 "statement");
3153 return MATCH_ERROR;
3156 gfc_clear_ts (&ts);
3158 /* We don't allow empty implicit statements. */
3159 if (gfc_match_eos () == MATCH_YES)
3161 gfc_error ("Empty IMPLICIT statement at %C");
3162 return MATCH_ERROR;
3167 /* First cleanup. */
3168 gfc_clear_new_implicit ();
3170 /* A basic type is mandatory here. */
3171 m = gfc_match_decl_type_spec (&ts, 1);
3172 if (m == MATCH_ERROR)
3173 goto error;
3174 if (m == MATCH_NO)
3175 goto syntax;
3177 cur_loc = gfc_current_locus;
3178 m = match_implicit_range ();
3180 if (m == MATCH_YES)
3182 /* We may have <TYPE> (<RANGE>). */
3183 gfc_gobble_whitespace ();
3184 c = gfc_peek_ascii_char ();
3185 if (c == ',' || c == '\n' || c == ';' || c == '!')
3187 /* Check for CHARACTER with no length parameter. */
3188 if (ts.type == BT_CHARACTER && !ts.u.cl)
3190 ts.kind = gfc_default_character_kind;
3191 ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
3192 ts.u.cl->length = gfc_get_int_expr (gfc_default_integer_kind,
3193 NULL, 1);
3196 /* Record the Successful match. */
3197 if (!gfc_merge_new_implicit (&ts))
3198 return MATCH_ERROR;
3199 if (c == ',')
3200 c = gfc_next_ascii_char ();
3201 else if (gfc_match_eos () == MATCH_ERROR)
3202 goto error;
3203 continue;
3206 gfc_current_locus = cur_loc;
3209 /* Discard the (incorrectly) matched range. */
3210 gfc_clear_new_implicit ();
3212 /* Last chance -- check <TYPE> <SELECTOR> (<RANGE>). */
3213 if (ts.type == BT_CHARACTER)
3214 m = gfc_match_char_spec (&ts);
3215 else
3217 m = gfc_match_kind_spec (&ts, false);
3218 if (m == MATCH_NO)
3220 m = gfc_match_old_kind_spec (&ts);
3221 if (m == MATCH_ERROR)
3222 goto error;
3223 if (m == MATCH_NO)
3224 goto syntax;
3227 if (m == MATCH_ERROR)
3228 goto error;
3230 m = match_implicit_range ();
3231 if (m == MATCH_ERROR)
3232 goto error;
3233 if (m == MATCH_NO)
3234 goto syntax;
3236 gfc_gobble_whitespace ();
3237 c = gfc_next_ascii_char ();
3238 if (c != ',' && gfc_match_eos () != MATCH_YES)
3239 goto syntax;
3241 if (!gfc_merge_new_implicit (&ts))
3242 return MATCH_ERROR;
3244 while (c == ',');
3246 return MATCH_YES;
3248 syntax:
3249 gfc_syntax_error (ST_IMPLICIT);
3251 error:
3252 return MATCH_ERROR;
3256 match
3257 gfc_match_import (void)
3259 char name[GFC_MAX_SYMBOL_LEN + 1];
3260 match m;
3261 gfc_symbol *sym;
3262 gfc_symtree *st;
3264 if (gfc_current_ns->proc_name == NULL
3265 || gfc_current_ns->proc_name->attr.if_source != IFSRC_IFBODY)
3267 gfc_error ("IMPORT statement at %C only permitted in "
3268 "an INTERFACE body");
3269 return MATCH_ERROR;
3272 if (!gfc_notify_std (GFC_STD_F2003, "IMPORT statement at %C"))
3273 return MATCH_ERROR;
3275 if (gfc_match_eos () == MATCH_YES)
3277 /* All host variables should be imported. */
3278 gfc_current_ns->has_import_set = 1;
3279 return MATCH_YES;
3282 if (gfc_match (" ::") == MATCH_YES)
3284 if (gfc_match_eos () == MATCH_YES)
3286 gfc_error ("Expecting list of named entities at %C");
3287 return MATCH_ERROR;
3291 for(;;)
3293 sym = NULL;
3294 m = gfc_match (" %n", name);
3295 switch (m)
3297 case MATCH_YES:
3298 if (gfc_current_ns->parent != NULL
3299 && gfc_find_symbol (name, gfc_current_ns->parent, 1, &sym))
3301 gfc_error ("Type name %qs at %C is ambiguous", name);
3302 return MATCH_ERROR;
3304 else if (!sym && gfc_current_ns->proc_name->ns->parent != NULL
3305 && gfc_find_symbol (name,
3306 gfc_current_ns->proc_name->ns->parent,
3307 1, &sym))
3309 gfc_error ("Type name %qs at %C is ambiguous", name);
3310 return MATCH_ERROR;
3313 if (sym == NULL)
3315 gfc_error ("Cannot IMPORT %qs from host scoping unit "
3316 "at %C - does not exist.", name);
3317 return MATCH_ERROR;
3320 if (gfc_find_symtree (gfc_current_ns->sym_root, name))
3322 gfc_warning (0, "%qs is already IMPORTed from host scoping unit "
3323 "at %C", name);
3324 goto next_item;
3327 st = gfc_new_symtree (&gfc_current_ns->sym_root, name);
3328 st->n.sym = sym;
3329 sym->refs++;
3330 sym->attr.imported = 1;
3332 if (sym->attr.generic && (sym = gfc_find_dt_in_generic (sym)))
3334 /* The actual derived type is stored in a symtree with the first
3335 letter of the name capitalized; the symtree with the all
3336 lower-case name contains the associated generic function. */
3337 st = gfc_new_symtree (&gfc_current_ns->sym_root,
3338 gfc_get_string ("%c%s",
3339 (char) TOUPPER ((unsigned char) name[0]),
3340 &name[1]));
3341 st->n.sym = sym;
3342 sym->refs++;
3343 sym->attr.imported = 1;
3346 goto next_item;
3348 case MATCH_NO:
3349 break;
3351 case MATCH_ERROR:
3352 return MATCH_ERROR;
3355 next_item:
3356 if (gfc_match_eos () == MATCH_YES)
3357 break;
3358 if (gfc_match_char (',') != MATCH_YES)
3359 goto syntax;
3362 return MATCH_YES;
3364 syntax:
3365 gfc_error ("Syntax error in IMPORT statement at %C");
3366 return MATCH_ERROR;
3370 /* A minimal implementation of gfc_match without whitespace, escape
3371 characters or variable arguments. Returns true if the next
3372 characters match the TARGET template exactly. */
3374 static bool
3375 match_string_p (const char *target)
3377 const char *p;
3379 for (p = target; *p; p++)
3380 if ((char) gfc_next_ascii_char () != *p)
3381 return false;
3382 return true;
3385 /* Matches an attribute specification including array specs. If
3386 successful, leaves the variables current_attr and current_as
3387 holding the specification. Also sets the colon_seen variable for
3388 later use by matchers associated with initializations.
3390 This subroutine is a little tricky in the sense that we don't know
3391 if we really have an attr-spec until we hit the double colon.
3392 Until that time, we can only return MATCH_NO. This forces us to
3393 check for duplicate specification at this level. */
3395 static match
3396 match_attr_spec (void)
3398 /* Modifiers that can exist in a type statement. */
3399 enum
3400 { GFC_DECL_BEGIN = 0,
3401 DECL_ALLOCATABLE = GFC_DECL_BEGIN, DECL_DIMENSION, DECL_EXTERNAL,
3402 DECL_IN, DECL_OUT, DECL_INOUT, DECL_INTRINSIC, DECL_OPTIONAL,
3403 DECL_PARAMETER, DECL_POINTER, DECL_PROTECTED, DECL_PRIVATE,
3404 DECL_PUBLIC, DECL_SAVE, DECL_TARGET, DECL_VALUE, DECL_VOLATILE,
3405 DECL_IS_BIND_C, DECL_CODIMENSION, DECL_ASYNCHRONOUS, DECL_CONTIGUOUS,
3406 DECL_NONE, GFC_DECL_END /* Sentinel */
3409 /* GFC_DECL_END is the sentinel, index starts at 0. */
3410 #define NUM_DECL GFC_DECL_END
3412 locus start, seen_at[NUM_DECL];
3413 int seen[NUM_DECL];
3414 unsigned int d;
3415 const char *attr;
3416 match m;
3417 bool t;
3419 gfc_clear_attr (&current_attr);
3420 start = gfc_current_locus;
3422 current_as = NULL;
3423 colon_seen = 0;
3425 /* See if we get all of the keywords up to the final double colon. */
3426 for (d = GFC_DECL_BEGIN; d != GFC_DECL_END; d++)
3427 seen[d] = 0;
3429 for (;;)
3431 char ch;
3433 d = DECL_NONE;
3434 gfc_gobble_whitespace ();
3436 ch = gfc_next_ascii_char ();
3437 if (ch == ':')
3439 /* This is the successful exit condition for the loop. */
3440 if (gfc_next_ascii_char () == ':')
3441 break;
3443 else if (ch == ',')
3445 gfc_gobble_whitespace ();
3446 switch (gfc_peek_ascii_char ())
3448 case 'a':
3449 gfc_next_ascii_char ();
3450 switch (gfc_next_ascii_char ())
3452 case 'l':
3453 if (match_string_p ("locatable"))
3455 /* Matched "allocatable". */
3456 d = DECL_ALLOCATABLE;
3458 break;
3460 case 's':
3461 if (match_string_p ("ynchronous"))
3463 /* Matched "asynchronous". */
3464 d = DECL_ASYNCHRONOUS;
3466 break;
3468 break;
3470 case 'b':
3471 /* Try and match the bind(c). */
3472 m = gfc_match_bind_c (NULL, true);
3473 if (m == MATCH_YES)
3474 d = DECL_IS_BIND_C;
3475 else if (m == MATCH_ERROR)
3476 goto cleanup;
3477 break;
3479 case 'c':
3480 gfc_next_ascii_char ();
3481 if ('o' != gfc_next_ascii_char ())
3482 break;
3483 switch (gfc_next_ascii_char ())
3485 case 'd':
3486 if (match_string_p ("imension"))
3488 d = DECL_CODIMENSION;
3489 break;
3491 case 'n':
3492 if (match_string_p ("tiguous"))
3494 d = DECL_CONTIGUOUS;
3495 break;
3498 break;
3500 case 'd':
3501 if (match_string_p ("dimension"))
3502 d = DECL_DIMENSION;
3503 break;
3505 case 'e':
3506 if (match_string_p ("external"))
3507 d = DECL_EXTERNAL;
3508 break;
3510 case 'i':
3511 if (match_string_p ("int"))
3513 ch = gfc_next_ascii_char ();
3514 if (ch == 'e')
3516 if (match_string_p ("nt"))
3518 /* Matched "intent". */
3519 /* TODO: Call match_intent_spec from here. */
3520 if (gfc_match (" ( in out )") == MATCH_YES)
3521 d = DECL_INOUT;
3522 else if (gfc_match (" ( in )") == MATCH_YES)
3523 d = DECL_IN;
3524 else if (gfc_match (" ( out )") == MATCH_YES)
3525 d = DECL_OUT;
3528 else if (ch == 'r')
3530 if (match_string_p ("insic"))
3532 /* Matched "intrinsic". */
3533 d = DECL_INTRINSIC;
3537 break;
3539 case 'o':
3540 if (match_string_p ("optional"))
3541 d = DECL_OPTIONAL;
3542 break;
3544 case 'p':
3545 gfc_next_ascii_char ();
3546 switch (gfc_next_ascii_char ())
3548 case 'a':
3549 if (match_string_p ("rameter"))
3551 /* Matched "parameter". */
3552 d = DECL_PARAMETER;
3554 break;
3556 case 'o':
3557 if (match_string_p ("inter"))
3559 /* Matched "pointer". */
3560 d = DECL_POINTER;
3562 break;
3564 case 'r':
3565 ch = gfc_next_ascii_char ();
3566 if (ch == 'i')
3568 if (match_string_p ("vate"))
3570 /* Matched "private". */
3571 d = DECL_PRIVATE;
3574 else if (ch == 'o')
3576 if (match_string_p ("tected"))
3578 /* Matched "protected". */
3579 d = DECL_PROTECTED;
3582 break;
3584 case 'u':
3585 if (match_string_p ("blic"))
3587 /* Matched "public". */
3588 d = DECL_PUBLIC;
3590 break;
3592 break;
3594 case 's':
3595 if (match_string_p ("save"))
3596 d = DECL_SAVE;
3597 break;
3599 case 't':
3600 if (match_string_p ("target"))
3601 d = DECL_TARGET;
3602 break;
3604 case 'v':
3605 gfc_next_ascii_char ();
3606 ch = gfc_next_ascii_char ();
3607 if (ch == 'a')
3609 if (match_string_p ("lue"))
3611 /* Matched "value". */
3612 d = DECL_VALUE;
3615 else if (ch == 'o')
3617 if (match_string_p ("latile"))
3619 /* Matched "volatile". */
3620 d = DECL_VOLATILE;
3623 break;
3627 /* No double colon and no recognizable decl_type, so assume that
3628 we've been looking at something else the whole time. */
3629 if (d == DECL_NONE)
3631 m = MATCH_NO;
3632 goto cleanup;
3635 /* Check to make sure any parens are paired up correctly. */
3636 if (gfc_match_parens () == MATCH_ERROR)
3638 m = MATCH_ERROR;
3639 goto cleanup;
3642 seen[d]++;
3643 seen_at[d] = gfc_current_locus;
3645 if (d == DECL_DIMENSION || d == DECL_CODIMENSION)
3647 gfc_array_spec *as = NULL;
3649 m = gfc_match_array_spec (&as, d == DECL_DIMENSION,
3650 d == DECL_CODIMENSION);
3652 if (current_as == NULL)
3653 current_as = as;
3654 else if (m == MATCH_YES)
3656 if (!merge_array_spec (as, current_as, false))
3657 m = MATCH_ERROR;
3658 free (as);
3661 if (m == MATCH_NO)
3663 if (d == DECL_CODIMENSION)
3664 gfc_error ("Missing codimension specification at %C");
3665 else
3666 gfc_error ("Missing dimension specification at %C");
3667 m = MATCH_ERROR;
3670 if (m == MATCH_ERROR)
3671 goto cleanup;
3675 /* Since we've seen a double colon, we have to be looking at an
3676 attr-spec. This means that we can now issue errors. */
3677 for (d = GFC_DECL_BEGIN; d != GFC_DECL_END; d++)
3678 if (seen[d] > 1)
3680 switch (d)
3682 case DECL_ALLOCATABLE:
3683 attr = "ALLOCATABLE";
3684 break;
3685 case DECL_ASYNCHRONOUS:
3686 attr = "ASYNCHRONOUS";
3687 break;
3688 case DECL_CODIMENSION:
3689 attr = "CODIMENSION";
3690 break;
3691 case DECL_CONTIGUOUS:
3692 attr = "CONTIGUOUS";
3693 break;
3694 case DECL_DIMENSION:
3695 attr = "DIMENSION";
3696 break;
3697 case DECL_EXTERNAL:
3698 attr = "EXTERNAL";
3699 break;
3700 case DECL_IN:
3701 attr = "INTENT (IN)";
3702 break;
3703 case DECL_OUT:
3704 attr = "INTENT (OUT)";
3705 break;
3706 case DECL_INOUT:
3707 attr = "INTENT (IN OUT)";
3708 break;
3709 case DECL_INTRINSIC:
3710 attr = "INTRINSIC";
3711 break;
3712 case DECL_OPTIONAL:
3713 attr = "OPTIONAL";
3714 break;
3715 case DECL_PARAMETER:
3716 attr = "PARAMETER";
3717 break;
3718 case DECL_POINTER:
3719 attr = "POINTER";
3720 break;
3721 case DECL_PROTECTED:
3722 attr = "PROTECTED";
3723 break;
3724 case DECL_PRIVATE:
3725 attr = "PRIVATE";
3726 break;
3727 case DECL_PUBLIC:
3728 attr = "PUBLIC";
3729 break;
3730 case DECL_SAVE:
3731 attr = "SAVE";
3732 break;
3733 case DECL_TARGET:
3734 attr = "TARGET";
3735 break;
3736 case DECL_IS_BIND_C:
3737 attr = "IS_BIND_C";
3738 break;
3739 case DECL_VALUE:
3740 attr = "VALUE";
3741 break;
3742 case DECL_VOLATILE:
3743 attr = "VOLATILE";
3744 break;
3745 default:
3746 attr = NULL; /* This shouldn't happen. */
3749 gfc_error ("Duplicate %s attribute at %L", attr, &seen_at[d]);
3750 m = MATCH_ERROR;
3751 goto cleanup;
3754 /* Now that we've dealt with duplicate attributes, add the attributes
3755 to the current attribute. */
3756 for (d = GFC_DECL_BEGIN; d != GFC_DECL_END; d++)
3758 if (seen[d] == 0)
3759 continue;
3761 if (gfc_current_state () == COMP_DERIVED
3762 && d != DECL_DIMENSION && d != DECL_CODIMENSION
3763 && d != DECL_POINTER && d != DECL_PRIVATE
3764 && d != DECL_PUBLIC && d != DECL_CONTIGUOUS && d != DECL_NONE)
3766 if (d == DECL_ALLOCATABLE)
3768 if (!gfc_notify_std (GFC_STD_F2003, "ALLOCATABLE "
3769 "attribute at %C in a TYPE definition"))
3771 m = MATCH_ERROR;
3772 goto cleanup;
3775 else
3777 gfc_error ("Attribute at %L is not allowed in a TYPE definition",
3778 &seen_at[d]);
3779 m = MATCH_ERROR;
3780 goto cleanup;
3784 if ((d == DECL_PRIVATE || d == DECL_PUBLIC)
3785 && gfc_current_state () != COMP_MODULE)
3787 if (d == DECL_PRIVATE)
3788 attr = "PRIVATE";
3789 else
3790 attr = "PUBLIC";
3791 if (gfc_current_state () == COMP_DERIVED
3792 && gfc_state_stack->previous
3793 && gfc_state_stack->previous->state == COMP_MODULE)
3795 if (!gfc_notify_std (GFC_STD_F2003, "Attribute %s "
3796 "at %L in a TYPE definition", attr,
3797 &seen_at[d]))
3799 m = MATCH_ERROR;
3800 goto cleanup;
3803 else
3805 gfc_error ("%s attribute at %L is not allowed outside of the "
3806 "specification part of a module", attr, &seen_at[d]);
3807 m = MATCH_ERROR;
3808 goto cleanup;
3812 switch (d)
3814 case DECL_ALLOCATABLE:
3815 t = gfc_add_allocatable (&current_attr, &seen_at[d]);
3816 break;
3818 case DECL_ASYNCHRONOUS:
3819 if (!gfc_notify_std (GFC_STD_F2003, "ASYNCHRONOUS attribute at %C"))
3820 t = false;
3821 else
3822 t = gfc_add_asynchronous (&current_attr, NULL, &seen_at[d]);
3823 break;
3825 case DECL_CODIMENSION:
3826 t = gfc_add_codimension (&current_attr, NULL, &seen_at[d]);
3827 break;
3829 case DECL_CONTIGUOUS:
3830 if (!gfc_notify_std (GFC_STD_F2008, "CONTIGUOUS attribute at %C"))
3831 t = false;
3832 else
3833 t = gfc_add_contiguous (&current_attr, NULL, &seen_at[d]);
3834 break;
3836 case DECL_DIMENSION:
3837 t = gfc_add_dimension (&current_attr, NULL, &seen_at[d]);
3838 break;
3840 case DECL_EXTERNAL:
3841 t = gfc_add_external (&current_attr, &seen_at[d]);
3842 break;
3844 case DECL_IN:
3845 t = gfc_add_intent (&current_attr, INTENT_IN, &seen_at[d]);
3846 break;
3848 case DECL_OUT:
3849 t = gfc_add_intent (&current_attr, INTENT_OUT, &seen_at[d]);
3850 break;
3852 case DECL_INOUT:
3853 t = gfc_add_intent (&current_attr, INTENT_INOUT, &seen_at[d]);
3854 break;
3856 case DECL_INTRINSIC:
3857 t = gfc_add_intrinsic (&current_attr, &seen_at[d]);
3858 break;
3860 case DECL_OPTIONAL:
3861 t = gfc_add_optional (&current_attr, &seen_at[d]);
3862 break;
3864 case DECL_PARAMETER:
3865 t = gfc_add_flavor (&current_attr, FL_PARAMETER, NULL, &seen_at[d]);
3866 break;
3868 case DECL_POINTER:
3869 t = gfc_add_pointer (&current_attr, &seen_at[d]);
3870 break;
3872 case DECL_PROTECTED:
3873 if (gfc_current_ns->proc_name->attr.flavor != FL_MODULE)
3875 gfc_error ("PROTECTED at %C only allowed in specification "
3876 "part of a module");
3877 t = false;
3878 break;
3881 if (!gfc_notify_std (GFC_STD_F2003, "PROTECTED attribute at %C"))
3882 t = false;
3883 else
3884 t = gfc_add_protected (&current_attr, NULL, &seen_at[d]);
3885 break;
3887 case DECL_PRIVATE:
3888 t = gfc_add_access (&current_attr, ACCESS_PRIVATE, NULL,
3889 &seen_at[d]);
3890 break;
3892 case DECL_PUBLIC:
3893 t = gfc_add_access (&current_attr, ACCESS_PUBLIC, NULL,
3894 &seen_at[d]);
3895 break;
3897 case DECL_SAVE:
3898 t = gfc_add_save (&current_attr, SAVE_EXPLICIT, NULL, &seen_at[d]);
3899 break;
3901 case DECL_TARGET:
3902 t = gfc_add_target (&current_attr, &seen_at[d]);
3903 break;
3905 case DECL_IS_BIND_C:
3906 t = gfc_add_is_bind_c(&current_attr, NULL, &seen_at[d], 0);
3907 break;
3909 case DECL_VALUE:
3910 if (!gfc_notify_std (GFC_STD_F2003, "VALUE attribute at %C"))
3911 t = false;
3912 else
3913 t = gfc_add_value (&current_attr, NULL, &seen_at[d]);
3914 break;
3916 case DECL_VOLATILE:
3917 if (!gfc_notify_std (GFC_STD_F2003, "VOLATILE attribute at %C"))
3918 t = false;
3919 else
3920 t = gfc_add_volatile (&current_attr, NULL, &seen_at[d]);
3921 break;
3923 default:
3924 gfc_internal_error ("match_attr_spec(): Bad attribute");
3927 if (!t)
3929 m = MATCH_ERROR;
3930 goto cleanup;
3934 /* Since Fortran 2008 module variables implicitly have the SAVE attribute. */
3935 if (gfc_current_state () == COMP_MODULE && !current_attr.save
3936 && (gfc_option.allow_std & GFC_STD_F2008) != 0)
3937 current_attr.save = SAVE_IMPLICIT;
3939 colon_seen = 1;
3940 return MATCH_YES;
3942 cleanup:
3943 gfc_current_locus = start;
3944 gfc_free_array_spec (current_as);
3945 current_as = NULL;
3946 return m;
3950 /* Set the binding label, dest_label, either with the binding label
3951 stored in the given gfc_typespec, ts, or if none was provided, it
3952 will be the symbol name in all lower case, as required by the draft
3953 (J3/04-007, section 15.4.1). If a binding label was given and
3954 there is more than one argument (num_idents), it is an error. */
3956 static bool
3957 set_binding_label (const char **dest_label, const char *sym_name,
3958 int num_idents)
3960 if (num_idents > 1 && has_name_equals)
3962 gfc_error ("Multiple identifiers provided with "
3963 "single NAME= specifier at %C");
3964 return false;
3967 if (curr_binding_label)
3968 /* Binding label given; store in temp holder till have sym. */
3969 *dest_label = curr_binding_label;
3970 else
3972 /* No binding label given, and the NAME= specifier did not exist,
3973 which means there was no NAME="". */
3974 if (sym_name != NULL && has_name_equals == 0)
3975 *dest_label = IDENTIFIER_POINTER (get_identifier (sym_name));
3978 return true;
3982 /* Set the status of the given common block as being BIND(C) or not,
3983 depending on the given parameter, is_bind_c. */
3985 void
3986 set_com_block_bind_c (gfc_common_head *com_block, int is_bind_c)
3988 com_block->is_bind_c = is_bind_c;
3989 return;
3993 /* Verify that the given gfc_typespec is for a C interoperable type. */
3995 bool
3996 gfc_verify_c_interop (gfc_typespec *ts)
3998 if (ts->type == BT_DERIVED && ts->u.derived != NULL)
3999 return (ts->u.derived->ts.is_c_interop || ts->u.derived->attr.is_bind_c)
4000 ? true : false;
4001 else if (ts->type == BT_CLASS)
4002 return false;
4003 else if (ts->is_c_interop != 1 && ts->type != BT_ASSUMED)
4004 return false;
4006 return true;
4010 /* Verify that the variables of a given common block, which has been
4011 defined with the attribute specifier bind(c), to be of a C
4012 interoperable type. Errors will be reported here, if
4013 encountered. */
4015 bool
4016 verify_com_block_vars_c_interop (gfc_common_head *com_block)
4018 gfc_symbol *curr_sym = NULL;
4019 bool retval = true;
4021 curr_sym = com_block->head;
4023 /* Make sure we have at least one symbol. */
4024 if (curr_sym == NULL)
4025 return retval;
4027 /* Here we know we have a symbol, so we'll execute this loop
4028 at least once. */
4031 /* The second to last param, 1, says this is in a common block. */
4032 retval = verify_bind_c_sym (curr_sym, &(curr_sym->ts), 1, com_block);
4033 curr_sym = curr_sym->common_next;
4034 } while (curr_sym != NULL);
4036 return retval;
4040 /* Verify that a given BIND(C) symbol is C interoperable. If it is not,
4041 an appropriate error message is reported. */
4043 bool
4044 verify_bind_c_sym (gfc_symbol *tmp_sym, gfc_typespec *ts,
4045 int is_in_common, gfc_common_head *com_block)
4047 bool bind_c_function = false;
4048 bool retval = true;
4050 if (tmp_sym->attr.function && tmp_sym->attr.is_bind_c)
4051 bind_c_function = true;
4053 if (tmp_sym->attr.function && tmp_sym->result != NULL)
4055 tmp_sym = tmp_sym->result;
4056 /* Make sure it wasn't an implicitly typed result. */
4057 if (tmp_sym->attr.implicit_type && warn_c_binding_type)
4059 gfc_warning (OPT_Wc_binding_type,
4060 "Implicitly declared BIND(C) function %qs at "
4061 "%L may not be C interoperable", tmp_sym->name,
4062 &tmp_sym->declared_at);
4063 tmp_sym->ts.f90_type = tmp_sym->ts.type;
4064 /* Mark it as C interoperable to prevent duplicate warnings. */
4065 tmp_sym->ts.is_c_interop = 1;
4066 tmp_sym->attr.is_c_interop = 1;
4070 /* Here, we know we have the bind(c) attribute, so if we have
4071 enough type info, then verify that it's a C interop kind.
4072 The info could be in the symbol already, or possibly still in
4073 the given ts (current_ts), so look in both. */
4074 if (tmp_sym->ts.type != BT_UNKNOWN || ts->type != BT_UNKNOWN)
4076 if (!gfc_verify_c_interop (&(tmp_sym->ts)))
4078 /* See if we're dealing with a sym in a common block or not. */
4079 if (is_in_common == 1 && warn_c_binding_type)
4081 gfc_warning (OPT_Wc_binding_type,
4082 "Variable %qs in common block %qs at %L "
4083 "may not be a C interoperable "
4084 "kind though common block %qs is BIND(C)",
4085 tmp_sym->name, com_block->name,
4086 &(tmp_sym->declared_at), com_block->name);
4088 else
4090 if (tmp_sym->ts.type == BT_DERIVED || ts->type == BT_DERIVED)
4091 gfc_error ("Type declaration %qs at %L is not C "
4092 "interoperable but it is BIND(C)",
4093 tmp_sym->name, &(tmp_sym->declared_at));
4094 else if (warn_c_binding_type)
4095 gfc_warning (OPT_Wc_binding_type, "Variable %qs at %L "
4096 "may not be a C interoperable "
4097 "kind but it is BIND(C)",
4098 tmp_sym->name, &(tmp_sym->declared_at));
4102 /* Variables declared w/in a common block can't be bind(c)
4103 since there's no way for C to see these variables, so there's
4104 semantically no reason for the attribute. */
4105 if (is_in_common == 1 && tmp_sym->attr.is_bind_c == 1)
4107 gfc_error ("Variable %qs in common block %qs at "
4108 "%L cannot be declared with BIND(C) "
4109 "since it is not a global",
4110 tmp_sym->name, com_block->name,
4111 &(tmp_sym->declared_at));
4112 retval = false;
4115 /* Scalar variables that are bind(c) can not have the pointer
4116 or allocatable attributes. */
4117 if (tmp_sym->attr.is_bind_c == 1)
4119 if (tmp_sym->attr.pointer == 1)
4121 gfc_error ("Variable %qs at %L cannot have both the "
4122 "POINTER and BIND(C) attributes",
4123 tmp_sym->name, &(tmp_sym->declared_at));
4124 retval = false;
4127 if (tmp_sym->attr.allocatable == 1)
4129 gfc_error ("Variable %qs at %L cannot have both the "
4130 "ALLOCATABLE and BIND(C) attributes",
4131 tmp_sym->name, &(tmp_sym->declared_at));
4132 retval = false;
4137 /* If it is a BIND(C) function, make sure the return value is a
4138 scalar value. The previous tests in this function made sure
4139 the type is interoperable. */
4140 if (bind_c_function && tmp_sym->as != NULL)
4141 gfc_error ("Return type of BIND(C) function %qs at %L cannot "
4142 "be an array", tmp_sym->name, &(tmp_sym->declared_at));
4144 /* BIND(C) functions can not return a character string. */
4145 if (bind_c_function && tmp_sym->ts.type == BT_CHARACTER)
4146 if (tmp_sym->ts.u.cl == NULL || tmp_sym->ts.u.cl->length == NULL
4147 || tmp_sym->ts.u.cl->length->expr_type != EXPR_CONSTANT
4148 || mpz_cmp_si (tmp_sym->ts.u.cl->length->value.integer, 1) != 0)
4149 gfc_error ("Return type of BIND(C) function %qs at %L cannot "
4150 "be a character string", tmp_sym->name,
4151 &(tmp_sym->declared_at));
4154 /* See if the symbol has been marked as private. If it has, make sure
4155 there is no binding label and warn the user if there is one. */
4156 if (tmp_sym->attr.access == ACCESS_PRIVATE
4157 && tmp_sym->binding_label)
4158 /* Use gfc_warning_now because we won't say that the symbol fails
4159 just because of this. */
4160 gfc_warning_now (0, "Symbol %qs at %L is marked PRIVATE but has been "
4161 "given the binding label %qs", tmp_sym->name,
4162 &(tmp_sym->declared_at), tmp_sym->binding_label);
4164 return retval;
4168 /* Set the appropriate fields for a symbol that's been declared as
4169 BIND(C) (the is_bind_c flag and the binding label), and verify that
4170 the type is C interoperable. Errors are reported by the functions
4171 used to set/test these fields. */
4173 bool
4174 set_verify_bind_c_sym (gfc_symbol *tmp_sym, int num_idents)
4176 bool retval = true;
4178 /* TODO: Do we need to make sure the vars aren't marked private? */
4180 /* Set the is_bind_c bit in symbol_attribute. */
4181 gfc_add_is_bind_c (&(tmp_sym->attr), tmp_sym->name, &gfc_current_locus, 0);
4183 if (!set_binding_label (&tmp_sym->binding_label, tmp_sym->name, num_idents))
4184 return false;
4186 return retval;
4190 /* Set the fields marking the given common block as BIND(C), including
4191 a binding label, and report any errors encountered. */
4193 bool
4194 set_verify_bind_c_com_block (gfc_common_head *com_block, int num_idents)
4196 bool retval = true;
4198 /* destLabel, common name, typespec (which may have binding label). */
4199 if (!set_binding_label (&com_block->binding_label, com_block->name,
4200 num_idents))
4201 return false;
4203 /* Set the given common block (com_block) to being bind(c) (1). */
4204 set_com_block_bind_c (com_block, 1);
4206 return retval;
4210 /* Retrieve the list of one or more identifiers that the given bind(c)
4211 attribute applies to. */
4213 bool
4214 get_bind_c_idents (void)
4216 char name[GFC_MAX_SYMBOL_LEN + 1];
4217 int num_idents = 0;
4218 gfc_symbol *tmp_sym = NULL;
4219 match found_id;
4220 gfc_common_head *com_block = NULL;
4222 if (gfc_match_name (name) == MATCH_YES)
4224 found_id = MATCH_YES;
4225 gfc_get_ha_symbol (name, &tmp_sym);
4227 else if (match_common_name (name) == MATCH_YES)
4229 found_id = MATCH_YES;
4230 com_block = gfc_get_common (name, 0);
4232 else
4234 gfc_error ("Need either entity or common block name for "
4235 "attribute specification statement at %C");
4236 return false;
4239 /* Save the current identifier and look for more. */
4242 /* Increment the number of identifiers found for this spec stmt. */
4243 num_idents++;
4245 /* Make sure we have a sym or com block, and verify that it can
4246 be bind(c). Set the appropriate field(s) and look for more
4247 identifiers. */
4248 if (tmp_sym != NULL || com_block != NULL)
4250 if (tmp_sym != NULL)
4252 if (!set_verify_bind_c_sym (tmp_sym, num_idents))
4253 return false;
4255 else
4257 if (!set_verify_bind_c_com_block (com_block, num_idents))
4258 return false;
4261 /* Look to see if we have another identifier. */
4262 tmp_sym = NULL;
4263 if (gfc_match_eos () == MATCH_YES)
4264 found_id = MATCH_NO;
4265 else if (gfc_match_char (',') != MATCH_YES)
4266 found_id = MATCH_NO;
4267 else if (gfc_match_name (name) == MATCH_YES)
4269 found_id = MATCH_YES;
4270 gfc_get_ha_symbol (name, &tmp_sym);
4272 else if (match_common_name (name) == MATCH_YES)
4274 found_id = MATCH_YES;
4275 com_block = gfc_get_common (name, 0);
4277 else
4279 gfc_error ("Missing entity or common block name for "
4280 "attribute specification statement at %C");
4281 return false;
4284 else
4286 gfc_internal_error ("Missing symbol");
4288 } while (found_id == MATCH_YES);
4290 /* if we get here we were successful */
4291 return true;
4295 /* Try and match a BIND(C) attribute specification statement. */
4297 match
4298 gfc_match_bind_c_stmt (void)
4300 match found_match = MATCH_NO;
4301 gfc_typespec *ts;
4303 ts = &current_ts;
4305 /* This may not be necessary. */
4306 gfc_clear_ts (ts);
4307 /* Clear the temporary binding label holder. */
4308 curr_binding_label = NULL;
4310 /* Look for the bind(c). */
4311 found_match = gfc_match_bind_c (NULL, true);
4313 if (found_match == MATCH_YES)
4315 if (!gfc_notify_std (GFC_STD_F2003, "BIND(C) statement at %C"))
4316 return MATCH_ERROR;
4318 /* Look for the :: now, but it is not required. */
4319 gfc_match (" :: ");
4321 /* Get the identifier(s) that needs to be updated. This may need to
4322 change to hand the flag(s) for the attr specified so all identifiers
4323 found can have all appropriate parts updated (assuming that the same
4324 spec stmt can have multiple attrs, such as both bind(c) and
4325 allocatable...). */
4326 if (!get_bind_c_idents ())
4327 /* Error message should have printed already. */
4328 return MATCH_ERROR;
4331 return found_match;
4335 /* Match a data declaration statement. */
4337 match
4338 gfc_match_data_decl (void)
4340 gfc_symbol *sym;
4341 match m;
4342 int elem;
4344 num_idents_on_line = 0;
4346 m = gfc_match_decl_type_spec (&current_ts, 0);
4347 if (m != MATCH_YES)
4348 return m;
4350 if ((current_ts.type == BT_DERIVED || current_ts.type == BT_CLASS)
4351 && gfc_current_state () != COMP_DERIVED)
4353 sym = gfc_use_derived (current_ts.u.derived);
4355 if (sym == NULL)
4357 m = MATCH_ERROR;
4358 goto cleanup;
4361 current_ts.u.derived = sym;
4364 m = match_attr_spec ();
4365 if (m == MATCH_ERROR)
4367 m = MATCH_NO;
4368 goto cleanup;
4371 if (current_ts.type == BT_CLASS
4372 && current_ts.u.derived->attr.unlimited_polymorphic)
4373 goto ok;
4375 if ((current_ts.type == BT_DERIVED || current_ts.type == BT_CLASS)
4376 && current_ts.u.derived->components == NULL
4377 && !current_ts.u.derived->attr.zero_comp)
4380 if (current_attr.pointer && gfc_current_state () == COMP_DERIVED)
4381 goto ok;
4383 gfc_find_symbol (current_ts.u.derived->name,
4384 current_ts.u.derived->ns, 1, &sym);
4386 /* Any symbol that we find had better be a type definition
4387 which has its components defined. */
4388 if (sym != NULL && sym->attr.flavor == FL_DERIVED
4389 && (current_ts.u.derived->components != NULL
4390 || current_ts.u.derived->attr.zero_comp))
4391 goto ok;
4393 gfc_error ("Derived type at %C has not been previously defined "
4394 "and so cannot appear in a derived type definition");
4395 m = MATCH_ERROR;
4396 goto cleanup;
4400 /* If we have an old-style character declaration, and no new-style
4401 attribute specifications, then there a comma is optional between
4402 the type specification and the variable list. */
4403 if (m == MATCH_NO && current_ts.type == BT_CHARACTER && old_char_selector)
4404 gfc_match_char (',');
4406 /* Give the types/attributes to symbols that follow. Give the element
4407 a number so that repeat character length expressions can be copied. */
4408 elem = 1;
4409 for (;;)
4411 num_idents_on_line++;
4412 m = variable_decl (elem++);
4413 if (m == MATCH_ERROR)
4414 goto cleanup;
4415 if (m == MATCH_NO)
4416 break;
4418 if (gfc_match_eos () == MATCH_YES)
4419 goto cleanup;
4420 if (gfc_match_char (',') != MATCH_YES)
4421 break;
4424 if (!gfc_error_flag_test ())
4425 gfc_error ("Syntax error in data declaration at %C");
4426 m = MATCH_ERROR;
4428 gfc_free_data_all (gfc_current_ns);
4430 cleanup:
4431 gfc_free_array_spec (current_as);
4432 current_as = NULL;
4433 return m;
4437 /* Match a prefix associated with a function or subroutine
4438 declaration. If the typespec pointer is nonnull, then a typespec
4439 can be matched. Note that if nothing matches, MATCH_YES is
4440 returned (the null string was matched). */
4442 match
4443 gfc_match_prefix (gfc_typespec *ts)
4445 bool seen_type;
4446 bool seen_impure;
4447 bool found_prefix;
4449 gfc_clear_attr (&current_attr);
4450 seen_type = false;
4451 seen_impure = false;
4453 gcc_assert (!gfc_matching_prefix);
4454 gfc_matching_prefix = true;
4458 found_prefix = false;
4460 if (!seen_type && ts != NULL
4461 && gfc_match_decl_type_spec (ts, 0) == MATCH_YES
4462 && gfc_match_space () == MATCH_YES)
4465 seen_type = true;
4466 found_prefix = true;
4469 if (gfc_match ("elemental% ") == MATCH_YES)
4471 if (!gfc_add_elemental (&current_attr, NULL))
4472 goto error;
4474 found_prefix = true;
4477 if (gfc_match ("pure% ") == MATCH_YES)
4479 if (!gfc_add_pure (&current_attr, NULL))
4480 goto error;
4482 found_prefix = true;
4485 if (gfc_match ("recursive% ") == MATCH_YES)
4487 if (!gfc_add_recursive (&current_attr, NULL))
4488 goto error;
4490 found_prefix = true;
4493 /* IMPURE is a somewhat special case, as it needs not set an actual
4494 attribute but rather only prevents ELEMENTAL routines from being
4495 automatically PURE. */
4496 if (gfc_match ("impure% ") == MATCH_YES)
4498 if (!gfc_notify_std (GFC_STD_F2008, "IMPURE procedure at %C"))
4499 goto error;
4501 seen_impure = true;
4502 found_prefix = true;
4505 while (found_prefix);
4507 /* IMPURE and PURE must not both appear, of course. */
4508 if (seen_impure && current_attr.pure)
4510 gfc_error ("PURE and IMPURE must not appear both at %C");
4511 goto error;
4514 /* If IMPURE it not seen but the procedure is ELEMENTAL, mark it as PURE. */
4515 if (!seen_impure && current_attr.elemental && !current_attr.pure)
4517 if (!gfc_add_pure (&current_attr, NULL))
4518 goto error;
4521 /* At this point, the next item is not a prefix. */
4522 gcc_assert (gfc_matching_prefix);
4523 gfc_matching_prefix = false;
4524 return MATCH_YES;
4526 error:
4527 gcc_assert (gfc_matching_prefix);
4528 gfc_matching_prefix = false;
4529 return MATCH_ERROR;
4533 /* Copy attributes matched by gfc_match_prefix() to attributes on a symbol. */
4535 static bool
4536 copy_prefix (symbol_attribute *dest, locus *where)
4538 if (current_attr.pure && !gfc_add_pure (dest, where))
4539 return false;
4541 if (current_attr.elemental && !gfc_add_elemental (dest, where))
4542 return false;
4544 if (current_attr.recursive && !gfc_add_recursive (dest, where))
4545 return false;
4547 return true;
4551 /* Match a formal argument list. */
4553 match
4554 gfc_match_formal_arglist (gfc_symbol *progname, int st_flag, int null_flag)
4556 gfc_formal_arglist *head, *tail, *p, *q;
4557 char name[GFC_MAX_SYMBOL_LEN + 1];
4558 gfc_symbol *sym;
4559 match m;
4561 head = tail = NULL;
4563 if (gfc_match_char ('(') != MATCH_YES)
4565 if (null_flag)
4566 goto ok;
4567 return MATCH_NO;
4570 if (gfc_match_char (')') == MATCH_YES)
4571 goto ok;
4573 for (;;)
4575 if (gfc_match_char ('*') == MATCH_YES)
4577 sym = NULL;
4578 if (!gfc_notify_std (GFC_STD_F95_OBS, "Alternate-return argument "
4579 "at %C"))
4581 m = MATCH_ERROR;
4582 goto cleanup;
4585 else
4587 m = gfc_match_name (name);
4588 if (m != MATCH_YES)
4589 goto cleanup;
4591 if (gfc_get_symbol (name, NULL, &sym))
4592 goto cleanup;
4595 p = gfc_get_formal_arglist ();
4597 if (head == NULL)
4598 head = tail = p;
4599 else
4601 tail->next = p;
4602 tail = p;
4605 tail->sym = sym;
4607 /* We don't add the VARIABLE flavor because the name could be a
4608 dummy procedure. We don't apply these attributes to formal
4609 arguments of statement functions. */
4610 if (sym != NULL && !st_flag
4611 && (!gfc_add_dummy(&sym->attr, sym->name, NULL)
4612 || !gfc_missing_attr (&sym->attr, NULL)))
4614 m = MATCH_ERROR;
4615 goto cleanup;
4618 /* The name of a program unit can be in a different namespace,
4619 so check for it explicitly. After the statement is accepted,
4620 the name is checked for especially in gfc_get_symbol(). */
4621 if (gfc_new_block != NULL && sym != NULL
4622 && strcmp (sym->name, gfc_new_block->name) == 0)
4624 gfc_error ("Name %qs at %C is the name of the procedure",
4625 sym->name);
4626 m = MATCH_ERROR;
4627 goto cleanup;
4630 if (gfc_match_char (')') == MATCH_YES)
4631 goto ok;
4633 m = gfc_match_char (',');
4634 if (m != MATCH_YES)
4636 gfc_error ("Unexpected junk in formal argument list at %C");
4637 goto cleanup;
4642 /* Check for duplicate symbols in the formal argument list. */
4643 if (head != NULL)
4645 for (p = head; p->next; p = p->next)
4647 if (p->sym == NULL)
4648 continue;
4650 for (q = p->next; q; q = q->next)
4651 if (p->sym == q->sym)
4653 gfc_error ("Duplicate symbol %qs in formal argument list "
4654 "at %C", p->sym->name);
4656 m = MATCH_ERROR;
4657 goto cleanup;
4662 if (!gfc_add_explicit_interface (progname, IFSRC_DECL, head, NULL))
4664 m = MATCH_ERROR;
4665 goto cleanup;
4668 return MATCH_YES;
4670 cleanup:
4671 gfc_free_formal_arglist (head);
4672 return m;
4676 /* Match a RESULT specification following a function declaration or
4677 ENTRY statement. Also matches the end-of-statement. */
4679 static match
4680 match_result (gfc_symbol *function, gfc_symbol **result)
4682 char name[GFC_MAX_SYMBOL_LEN + 1];
4683 gfc_symbol *r;
4684 match m;
4686 if (gfc_match (" result (") != MATCH_YES)
4687 return MATCH_NO;
4689 m = gfc_match_name (name);
4690 if (m != MATCH_YES)
4691 return m;
4693 /* Get the right paren, and that's it because there could be the
4694 bind(c) attribute after the result clause. */
4695 if (gfc_match_char (')') != MATCH_YES)
4697 /* TODO: should report the missing right paren here. */
4698 return MATCH_ERROR;
4701 if (strcmp (function->name, name) == 0)
4703 gfc_error ("RESULT variable at %C must be different than function name");
4704 return MATCH_ERROR;
4707 if (gfc_get_symbol (name, NULL, &r))
4708 return MATCH_ERROR;
4710 if (!gfc_add_result (&r->attr, r->name, NULL))
4711 return MATCH_ERROR;
4713 *result = r;
4715 return MATCH_YES;
4719 /* Match a function suffix, which could be a combination of a result
4720 clause and BIND(C), either one, or neither. The draft does not
4721 require them to come in a specific order. */
4723 match
4724 gfc_match_suffix (gfc_symbol *sym, gfc_symbol **result)
4726 match is_bind_c; /* Found bind(c). */
4727 match is_result; /* Found result clause. */
4728 match found_match; /* Status of whether we've found a good match. */
4729 char peek_char; /* Character we're going to peek at. */
4730 bool allow_binding_name;
4732 /* Initialize to having found nothing. */
4733 found_match = MATCH_NO;
4734 is_bind_c = MATCH_NO;
4735 is_result = MATCH_NO;
4737 /* Get the next char to narrow between result and bind(c). */
4738 gfc_gobble_whitespace ();
4739 peek_char = gfc_peek_ascii_char ();
4741 /* C binding names are not allowed for internal procedures. */
4742 if (gfc_current_state () == COMP_CONTAINS
4743 && sym->ns->proc_name->attr.flavor != FL_MODULE)
4744 allow_binding_name = false;
4745 else
4746 allow_binding_name = true;
4748 switch (peek_char)
4750 case 'r':
4751 /* Look for result clause. */
4752 is_result = match_result (sym, result);
4753 if (is_result == MATCH_YES)
4755 /* Now see if there is a bind(c) after it. */
4756 is_bind_c = gfc_match_bind_c (sym, allow_binding_name);
4757 /* We've found the result clause and possibly bind(c). */
4758 found_match = MATCH_YES;
4760 else
4761 /* This should only be MATCH_ERROR. */
4762 found_match = is_result;
4763 break;
4764 case 'b':
4765 /* Look for bind(c) first. */
4766 is_bind_c = gfc_match_bind_c (sym, allow_binding_name);
4767 if (is_bind_c == MATCH_YES)
4769 /* Now see if a result clause followed it. */
4770 is_result = match_result (sym, result);
4771 found_match = MATCH_YES;
4773 else
4775 /* Should only be a MATCH_ERROR if we get here after seeing 'b'. */
4776 found_match = MATCH_ERROR;
4778 break;
4779 default:
4780 gfc_error ("Unexpected junk after function declaration at %C");
4781 found_match = MATCH_ERROR;
4782 break;
4785 if (is_bind_c == MATCH_YES)
4787 /* Fortran 2008 draft allows BIND(C) for internal procedures. */
4788 if (gfc_current_state () == COMP_CONTAINS
4789 && sym->ns->proc_name->attr.flavor != FL_MODULE
4790 && !gfc_notify_std (GFC_STD_F2008, "BIND(C) attribute "
4791 "at %L may not be specified for an internal "
4792 "procedure", &gfc_current_locus))
4793 return MATCH_ERROR;
4795 if (!gfc_add_is_bind_c (&(sym->attr), sym->name, &gfc_current_locus, 1))
4796 return MATCH_ERROR;
4799 return found_match;
4803 /* Procedure pointer return value without RESULT statement:
4804 Add "hidden" result variable named "ppr@". */
4806 static bool
4807 add_hidden_procptr_result (gfc_symbol *sym)
4809 bool case1,case2;
4811 if (gfc_notification_std (GFC_STD_F2003) == ERROR)
4812 return false;
4814 /* First usage case: PROCEDURE and EXTERNAL statements. */
4815 case1 = gfc_current_state () == COMP_FUNCTION && gfc_current_block ()
4816 && strcmp (gfc_current_block ()->name, sym->name) == 0
4817 && sym->attr.external;
4818 /* Second usage case: INTERFACE statements. */
4819 case2 = gfc_current_state () == COMP_INTERFACE && gfc_state_stack->previous
4820 && gfc_state_stack->previous->state == COMP_FUNCTION
4821 && strcmp (gfc_state_stack->previous->sym->name, sym->name) == 0;
4823 if (case1 || case2)
4825 gfc_symtree *stree;
4826 if (case1)
4827 gfc_get_sym_tree ("ppr@", gfc_current_ns, &stree, false);
4828 else if (case2)
4830 gfc_symtree *st2;
4831 gfc_get_sym_tree ("ppr@", gfc_current_ns->parent, &stree, false);
4832 st2 = gfc_new_symtree (&gfc_current_ns->sym_root, "ppr@");
4833 st2->n.sym = stree->n.sym;
4835 sym->result = stree->n.sym;
4837 sym->result->attr.proc_pointer = sym->attr.proc_pointer;
4838 sym->result->attr.pointer = sym->attr.pointer;
4839 sym->result->attr.external = sym->attr.external;
4840 sym->result->attr.referenced = sym->attr.referenced;
4841 sym->result->ts = sym->ts;
4842 sym->attr.proc_pointer = 0;
4843 sym->attr.pointer = 0;
4844 sym->attr.external = 0;
4845 if (sym->result->attr.external && sym->result->attr.pointer)
4847 sym->result->attr.pointer = 0;
4848 sym->result->attr.proc_pointer = 1;
4851 return gfc_add_result (&sym->result->attr, sym->result->name, NULL);
4853 /* POINTER after PROCEDURE/EXTERNAL/INTERFACE statement. */
4854 else if (sym->attr.function && !sym->attr.external && sym->attr.pointer
4855 && sym->result && sym->result != sym && sym->result->attr.external
4856 && sym == gfc_current_ns->proc_name
4857 && sym == sym->result->ns->proc_name
4858 && strcmp ("ppr@", sym->result->name) == 0)
4860 sym->result->attr.proc_pointer = 1;
4861 sym->attr.pointer = 0;
4862 return true;
4864 else
4865 return false;
4869 /* Match the interface for a PROCEDURE declaration,
4870 including brackets (R1212). */
4872 static match
4873 match_procedure_interface (gfc_symbol **proc_if)
4875 match m;
4876 gfc_symtree *st;
4877 locus old_loc, entry_loc;
4878 gfc_namespace *old_ns = gfc_current_ns;
4879 char name[GFC_MAX_SYMBOL_LEN + 1];
4881 old_loc = entry_loc = gfc_current_locus;
4882 gfc_clear_ts (&current_ts);
4884 if (gfc_match (" (") != MATCH_YES)
4886 gfc_current_locus = entry_loc;
4887 return MATCH_NO;
4890 /* Get the type spec. for the procedure interface. */
4891 old_loc = gfc_current_locus;
4892 m = gfc_match_decl_type_spec (&current_ts, 0);
4893 gfc_gobble_whitespace ();
4894 if (m == MATCH_YES || (m == MATCH_NO && gfc_peek_ascii_char () == ')'))
4895 goto got_ts;
4897 if (m == MATCH_ERROR)
4898 return m;
4900 /* Procedure interface is itself a procedure. */
4901 gfc_current_locus = old_loc;
4902 m = gfc_match_name (name);
4904 /* First look to see if it is already accessible in the current
4905 namespace because it is use associated or contained. */
4906 st = NULL;
4907 if (gfc_find_sym_tree (name, NULL, 0, &st))
4908 return MATCH_ERROR;
4910 /* If it is still not found, then try the parent namespace, if it
4911 exists and create the symbol there if it is still not found. */
4912 if (gfc_current_ns->parent)
4913 gfc_current_ns = gfc_current_ns->parent;
4914 if (st == NULL && gfc_get_ha_sym_tree (name, &st))
4915 return MATCH_ERROR;
4917 gfc_current_ns = old_ns;
4918 *proc_if = st->n.sym;
4920 if (*proc_if)
4922 (*proc_if)->refs++;
4923 /* Resolve interface if possible. That way, attr.procedure is only set
4924 if it is declared by a later procedure-declaration-stmt, which is
4925 invalid per F08:C1216 (cf. resolve_procedure_interface). */
4926 while ((*proc_if)->ts.interface)
4927 *proc_if = (*proc_if)->ts.interface;
4929 if ((*proc_if)->attr.flavor == FL_UNKNOWN
4930 && (*proc_if)->ts.type == BT_UNKNOWN
4931 && !gfc_add_flavor (&(*proc_if)->attr, FL_PROCEDURE,
4932 (*proc_if)->name, NULL))
4933 return MATCH_ERROR;
4936 got_ts:
4937 if (gfc_match (" )") != MATCH_YES)
4939 gfc_current_locus = entry_loc;
4940 return MATCH_NO;
4943 return MATCH_YES;
4947 /* Match a PROCEDURE declaration (R1211). */
4949 static match
4950 match_procedure_decl (void)
4952 match m;
4953 gfc_symbol *sym, *proc_if = NULL;
4954 int num;
4955 gfc_expr *initializer = NULL;
4957 /* Parse interface (with brackets). */
4958 m = match_procedure_interface (&proc_if);
4959 if (m != MATCH_YES)
4960 return m;
4962 /* Parse attributes (with colons). */
4963 m = match_attr_spec();
4964 if (m == MATCH_ERROR)
4965 return MATCH_ERROR;
4967 if (proc_if && proc_if->attr.is_bind_c && !current_attr.is_bind_c)
4969 current_attr.is_bind_c = 1;
4970 has_name_equals = 0;
4971 curr_binding_label = NULL;
4974 /* Get procedure symbols. */
4975 for(num=1;;num++)
4977 m = gfc_match_symbol (&sym, 0);
4978 if (m == MATCH_NO)
4979 goto syntax;
4980 else if (m == MATCH_ERROR)
4981 return m;
4983 /* Add current_attr to the symbol attributes. */
4984 if (!gfc_copy_attr (&sym->attr, &current_attr, NULL))
4985 return MATCH_ERROR;
4987 if (sym->attr.is_bind_c)
4989 /* Check for C1218. */
4990 if (!proc_if || !proc_if->attr.is_bind_c)
4992 gfc_error ("BIND(C) attribute at %C requires "
4993 "an interface with BIND(C)");
4994 return MATCH_ERROR;
4996 /* Check for C1217. */
4997 if (has_name_equals && sym->attr.pointer)
4999 gfc_error ("BIND(C) procedure with NAME may not have "
5000 "POINTER attribute at %C");
5001 return MATCH_ERROR;
5003 if (has_name_equals && sym->attr.dummy)
5005 gfc_error ("Dummy procedure at %C may not have "
5006 "BIND(C) attribute with NAME");
5007 return MATCH_ERROR;
5009 /* Set binding label for BIND(C). */
5010 if (!set_binding_label (&sym->binding_label, sym->name, num))
5011 return MATCH_ERROR;
5014 if (!gfc_add_external (&sym->attr, NULL))
5015 return MATCH_ERROR;
5017 if (add_hidden_procptr_result (sym))
5018 sym = sym->result;
5020 if (!gfc_add_proc (&sym->attr, sym->name, NULL))
5021 return MATCH_ERROR;
5023 /* Set interface. */
5024 if (proc_if != NULL)
5026 if (sym->ts.type != BT_UNKNOWN)
5028 gfc_error ("Procedure %qs at %L already has basic type of %s",
5029 sym->name, &gfc_current_locus,
5030 gfc_basic_typename (sym->ts.type));
5031 return MATCH_ERROR;
5033 sym->ts.interface = proc_if;
5034 sym->attr.untyped = 1;
5035 sym->attr.if_source = IFSRC_IFBODY;
5037 else if (current_ts.type != BT_UNKNOWN)
5039 if (!gfc_add_type (sym, &current_ts, &gfc_current_locus))
5040 return MATCH_ERROR;
5041 sym->ts.interface = gfc_new_symbol ("", gfc_current_ns);
5042 sym->ts.interface->ts = current_ts;
5043 sym->ts.interface->attr.flavor = FL_PROCEDURE;
5044 sym->ts.interface->attr.function = 1;
5045 sym->attr.function = 1;
5046 sym->attr.if_source = IFSRC_UNKNOWN;
5049 if (gfc_match (" =>") == MATCH_YES)
5051 if (!current_attr.pointer)
5053 gfc_error ("Initialization at %C isn't for a pointer variable");
5054 m = MATCH_ERROR;
5055 goto cleanup;
5058 m = match_pointer_init (&initializer, 1);
5059 if (m != MATCH_YES)
5060 goto cleanup;
5062 if (!add_init_expr_to_sym (sym->name, &initializer, &gfc_current_locus))
5063 goto cleanup;
5067 if (gfc_match_eos () == MATCH_YES)
5068 return MATCH_YES;
5069 if (gfc_match_char (',') != MATCH_YES)
5070 goto syntax;
5073 syntax:
5074 gfc_error ("Syntax error in PROCEDURE statement at %C");
5075 return MATCH_ERROR;
5077 cleanup:
5078 /* Free stuff up and return. */
5079 gfc_free_expr (initializer);
5080 return m;
5084 static match
5085 match_binding_attributes (gfc_typebound_proc* ba, bool generic, bool ppc);
5088 /* Match a procedure pointer component declaration (R445). */
5090 static match
5091 match_ppc_decl (void)
5093 match m;
5094 gfc_symbol *proc_if = NULL;
5095 gfc_typespec ts;
5096 int num;
5097 gfc_component *c;
5098 gfc_expr *initializer = NULL;
5099 gfc_typebound_proc* tb;
5100 char name[GFC_MAX_SYMBOL_LEN + 1];
5102 /* Parse interface (with brackets). */
5103 m = match_procedure_interface (&proc_if);
5104 if (m != MATCH_YES)
5105 goto syntax;
5107 /* Parse attributes. */
5108 tb = XCNEW (gfc_typebound_proc);
5109 tb->where = gfc_current_locus;
5110 m = match_binding_attributes (tb, false, true);
5111 if (m == MATCH_ERROR)
5112 return m;
5114 gfc_clear_attr (&current_attr);
5115 current_attr.procedure = 1;
5116 current_attr.proc_pointer = 1;
5117 current_attr.access = tb->access;
5118 current_attr.flavor = FL_PROCEDURE;
5120 /* Match the colons (required). */
5121 if (gfc_match (" ::") != MATCH_YES)
5123 gfc_error ("Expected %<::%> after binding-attributes at %C");
5124 return MATCH_ERROR;
5127 /* Check for C450. */
5128 if (!tb->nopass && proc_if == NULL)
5130 gfc_error("NOPASS or explicit interface required at %C");
5131 return MATCH_ERROR;
5134 if (!gfc_notify_std (GFC_STD_F2003, "Procedure pointer component at %C"))
5135 return MATCH_ERROR;
5137 /* Match PPC names. */
5138 ts = current_ts;
5139 for(num=1;;num++)
5141 m = gfc_match_name (name);
5142 if (m == MATCH_NO)
5143 goto syntax;
5144 else if (m == MATCH_ERROR)
5145 return m;
5147 if (!gfc_add_component (gfc_current_block(), name, &c))
5148 return MATCH_ERROR;
5150 /* Add current_attr to the symbol attributes. */
5151 if (!gfc_copy_attr (&c->attr, &current_attr, NULL))
5152 return MATCH_ERROR;
5154 if (!gfc_add_external (&c->attr, NULL))
5155 return MATCH_ERROR;
5157 if (!gfc_add_proc (&c->attr, name, NULL))
5158 return MATCH_ERROR;
5160 if (num == 1)
5161 c->tb = tb;
5162 else
5164 c->tb = XCNEW (gfc_typebound_proc);
5165 c->tb->where = gfc_current_locus;
5166 *c->tb = *tb;
5169 /* Set interface. */
5170 if (proc_if != NULL)
5172 c->ts.interface = proc_if;
5173 c->attr.untyped = 1;
5174 c->attr.if_source = IFSRC_IFBODY;
5176 else if (ts.type != BT_UNKNOWN)
5178 c->ts = ts;
5179 c->ts.interface = gfc_new_symbol ("", gfc_current_ns);
5180 c->ts.interface->result = c->ts.interface;
5181 c->ts.interface->ts = ts;
5182 c->ts.interface->attr.flavor = FL_PROCEDURE;
5183 c->ts.interface->attr.function = 1;
5184 c->attr.function = 1;
5185 c->attr.if_source = IFSRC_UNKNOWN;
5188 if (gfc_match (" =>") == MATCH_YES)
5190 m = match_pointer_init (&initializer, 1);
5191 if (m != MATCH_YES)
5193 gfc_free_expr (initializer);
5194 return m;
5196 c->initializer = initializer;
5199 if (gfc_match_eos () == MATCH_YES)
5200 return MATCH_YES;
5201 if (gfc_match_char (',') != MATCH_YES)
5202 goto syntax;
5205 syntax:
5206 gfc_error ("Syntax error in procedure pointer component at %C");
5207 return MATCH_ERROR;
5211 /* Match a PROCEDURE declaration inside an interface (R1206). */
5213 static match
5214 match_procedure_in_interface (void)
5216 match m;
5217 gfc_symbol *sym;
5218 char name[GFC_MAX_SYMBOL_LEN + 1];
5219 locus old_locus;
5221 if (current_interface.type == INTERFACE_NAMELESS
5222 || current_interface.type == INTERFACE_ABSTRACT)
5224 gfc_error ("PROCEDURE at %C must be in a generic interface");
5225 return MATCH_ERROR;
5228 /* Check if the F2008 optional double colon appears. */
5229 gfc_gobble_whitespace ();
5230 old_locus = gfc_current_locus;
5231 if (gfc_match ("::") == MATCH_YES)
5233 if (!gfc_notify_std (GFC_STD_F2008, "double colon in "
5234 "MODULE PROCEDURE statement at %L", &old_locus))
5235 return MATCH_ERROR;
5237 else
5238 gfc_current_locus = old_locus;
5240 for(;;)
5242 m = gfc_match_name (name);
5243 if (m == MATCH_NO)
5244 goto syntax;
5245 else if (m == MATCH_ERROR)
5246 return m;
5247 if (gfc_get_symbol (name, gfc_current_ns->parent, &sym))
5248 return MATCH_ERROR;
5250 if (!gfc_add_interface (sym))
5251 return MATCH_ERROR;
5253 if (gfc_match_eos () == MATCH_YES)
5254 break;
5255 if (gfc_match_char (',') != MATCH_YES)
5256 goto syntax;
5259 return MATCH_YES;
5261 syntax:
5262 gfc_error ("Syntax error in PROCEDURE statement at %C");
5263 return MATCH_ERROR;
5267 /* General matcher for PROCEDURE declarations. */
5269 static match match_procedure_in_type (void);
5271 match
5272 gfc_match_procedure (void)
5274 match m;
5276 switch (gfc_current_state ())
5278 case COMP_NONE:
5279 case COMP_PROGRAM:
5280 case COMP_MODULE:
5281 case COMP_SUBROUTINE:
5282 case COMP_FUNCTION:
5283 case COMP_BLOCK:
5284 m = match_procedure_decl ();
5285 break;
5286 case COMP_INTERFACE:
5287 m = match_procedure_in_interface ();
5288 break;
5289 case COMP_DERIVED:
5290 m = match_ppc_decl ();
5291 break;
5292 case COMP_DERIVED_CONTAINS:
5293 m = match_procedure_in_type ();
5294 break;
5295 default:
5296 return MATCH_NO;
5299 if (m != MATCH_YES)
5300 return m;
5302 if (!gfc_notify_std (GFC_STD_F2003, "PROCEDURE statement at %C"))
5303 return MATCH_ERROR;
5305 return m;
5309 /* Warn if a matched procedure has the same name as an intrinsic; this is
5310 simply a wrapper around gfc_warn_intrinsic_shadow that interprets the current
5311 parser-state-stack to find out whether we're in a module. */
5313 static void
5314 do_warn_intrinsic_shadow (const gfc_symbol* sym, bool func)
5316 bool in_module;
5318 in_module = (gfc_state_stack->previous
5319 && gfc_state_stack->previous->state == COMP_MODULE);
5321 gfc_warn_intrinsic_shadow (sym, in_module, func);
5325 /* Match a function declaration. */
5327 match
5328 gfc_match_function_decl (void)
5330 char name[GFC_MAX_SYMBOL_LEN + 1];
5331 gfc_symbol *sym, *result;
5332 locus old_loc;
5333 match m;
5334 match suffix_match;
5335 match found_match; /* Status returned by match func. */
5337 if (gfc_current_state () != COMP_NONE
5338 && gfc_current_state () != COMP_INTERFACE
5339 && gfc_current_state () != COMP_CONTAINS)
5340 return MATCH_NO;
5342 gfc_clear_ts (&current_ts);
5344 old_loc = gfc_current_locus;
5346 m = gfc_match_prefix (&current_ts);
5347 if (m != MATCH_YES)
5349 gfc_current_locus = old_loc;
5350 return m;
5353 if (gfc_match ("function% %n", name) != MATCH_YES)
5355 gfc_current_locus = old_loc;
5356 return MATCH_NO;
5358 if (get_proc_name (name, &sym, false))
5359 return MATCH_ERROR;
5361 if (add_hidden_procptr_result (sym))
5362 sym = sym->result;
5364 gfc_new_block = sym;
5366 m = gfc_match_formal_arglist (sym, 0, 0);
5367 if (m == MATCH_NO)
5369 gfc_error ("Expected formal argument list in function "
5370 "definition at %C");
5371 m = MATCH_ERROR;
5372 goto cleanup;
5374 else if (m == MATCH_ERROR)
5375 goto cleanup;
5377 result = NULL;
5379 /* According to the draft, the bind(c) and result clause can
5380 come in either order after the formal_arg_list (i.e., either
5381 can be first, both can exist together or by themselves or neither
5382 one). Therefore, the match_result can't match the end of the
5383 string, and check for the bind(c) or result clause in either order. */
5384 found_match = gfc_match_eos ();
5386 /* Make sure that it isn't already declared as BIND(C). If it is, it
5387 must have been marked BIND(C) with a BIND(C) attribute and that is
5388 not allowed for procedures. */
5389 if (sym->attr.is_bind_c == 1)
5391 sym->attr.is_bind_c = 0;
5392 if (sym->old_symbol != NULL)
5393 gfc_error_now ("BIND(C) attribute at %L can only be used for "
5394 "variables or common blocks",
5395 &(sym->old_symbol->declared_at));
5396 else
5397 gfc_error_now ("BIND(C) attribute at %L can only be used for "
5398 "variables or common blocks", &gfc_current_locus);
5401 if (found_match != MATCH_YES)
5403 /* If we haven't found the end-of-statement, look for a suffix. */
5404 suffix_match = gfc_match_suffix (sym, &result);
5405 if (suffix_match == MATCH_YES)
5406 /* Need to get the eos now. */
5407 found_match = gfc_match_eos ();
5408 else
5409 found_match = suffix_match;
5412 if(found_match != MATCH_YES)
5413 m = MATCH_ERROR;
5414 else
5416 /* Make changes to the symbol. */
5417 m = MATCH_ERROR;
5419 if (!gfc_add_function (&sym->attr, sym->name, NULL))
5420 goto cleanup;
5422 if (!gfc_missing_attr (&sym->attr, NULL)
5423 || !copy_prefix (&sym->attr, &sym->declared_at))
5424 goto cleanup;
5426 /* Delay matching the function characteristics until after the
5427 specification block by signalling kind=-1. */
5428 sym->declared_at = old_loc;
5429 if (current_ts.type != BT_UNKNOWN)
5430 current_ts.kind = -1;
5431 else
5432 current_ts.kind = 0;
5434 if (result == NULL)
5436 if (current_ts.type != BT_UNKNOWN
5437 && !gfc_add_type (sym, &current_ts, &gfc_current_locus))
5438 goto cleanup;
5439 sym->result = sym;
5441 else
5443 if (current_ts.type != BT_UNKNOWN
5444 && !gfc_add_type (result, &current_ts, &gfc_current_locus))
5445 goto cleanup;
5446 sym->result = result;
5449 /* Warn if this procedure has the same name as an intrinsic. */
5450 do_warn_intrinsic_shadow (sym, true);
5452 return MATCH_YES;
5455 cleanup:
5456 gfc_current_locus = old_loc;
5457 return m;
5461 /* This is mostly a copy of parse.c(add_global_procedure) but modified to
5462 pass the name of the entry, rather than the gfc_current_block name, and
5463 to return false upon finding an existing global entry. */
5465 static bool
5466 add_global_entry (const char *name, const char *binding_label, bool sub,
5467 locus *where)
5469 gfc_gsymbol *s;
5470 enum gfc_symbol_type type;
5472 type = sub ? GSYM_SUBROUTINE : GSYM_FUNCTION;
5474 /* Only in Fortran 2003: For procedures with a binding label also the Fortran
5475 name is a global identifier. */
5476 if (!binding_label || gfc_notification_std (GFC_STD_F2008))
5478 s = gfc_get_gsymbol (name);
5480 if (s->defined || (s->type != GSYM_UNKNOWN && s->type != type))
5482 gfc_global_used (s, where);
5483 return false;
5485 else
5487 s->type = type;
5488 s->sym_name = name;
5489 s->where = *where;
5490 s->defined = 1;
5491 s->ns = gfc_current_ns;
5495 /* Don't add the symbol multiple times. */
5496 if (binding_label
5497 && (!gfc_notification_std (GFC_STD_F2008)
5498 || strcmp (name, binding_label) != 0))
5500 s = gfc_get_gsymbol (binding_label);
5502 if (s->defined || (s->type != GSYM_UNKNOWN && s->type != type))
5504 gfc_global_used (s, where);
5505 return false;
5507 else
5509 s->type = type;
5510 s->sym_name = name;
5511 s->binding_label = binding_label;
5512 s->where = *where;
5513 s->defined = 1;
5514 s->ns = gfc_current_ns;
5518 return true;
5522 /* Match an ENTRY statement. */
5524 match
5525 gfc_match_entry (void)
5527 gfc_symbol *proc;
5528 gfc_symbol *result;
5529 gfc_symbol *entry;
5530 char name[GFC_MAX_SYMBOL_LEN + 1];
5531 gfc_compile_state state;
5532 match m;
5533 gfc_entry_list *el;
5534 locus old_loc;
5535 bool module_procedure;
5536 char peek_char;
5537 match is_bind_c;
5539 m = gfc_match_name (name);
5540 if (m != MATCH_YES)
5541 return m;
5543 if (!gfc_notify_std (GFC_STD_F2008_OBS, "ENTRY statement at %C"))
5544 return MATCH_ERROR;
5546 state = gfc_current_state ();
5547 if (state != COMP_SUBROUTINE && state != COMP_FUNCTION)
5549 switch (state)
5551 case COMP_PROGRAM:
5552 gfc_error ("ENTRY statement at %C cannot appear within a PROGRAM");
5553 break;
5554 case COMP_MODULE:
5555 gfc_error ("ENTRY statement at %C cannot appear within a MODULE");
5556 break;
5557 case COMP_BLOCK_DATA:
5558 gfc_error ("ENTRY statement at %C cannot appear within "
5559 "a BLOCK DATA");
5560 break;
5561 case COMP_INTERFACE:
5562 gfc_error ("ENTRY statement at %C cannot appear within "
5563 "an INTERFACE");
5564 break;
5565 case COMP_DERIVED:
5566 gfc_error ("ENTRY statement at %C cannot appear within "
5567 "a DERIVED TYPE block");
5568 break;
5569 case COMP_IF:
5570 gfc_error ("ENTRY statement at %C cannot appear within "
5571 "an IF-THEN block");
5572 break;
5573 case COMP_DO:
5574 case COMP_DO_CONCURRENT:
5575 gfc_error ("ENTRY statement at %C cannot appear within "
5576 "a DO block");
5577 break;
5578 case COMP_SELECT:
5579 gfc_error ("ENTRY statement at %C cannot appear within "
5580 "a SELECT block");
5581 break;
5582 case COMP_FORALL:
5583 gfc_error ("ENTRY statement at %C cannot appear within "
5584 "a FORALL block");
5585 break;
5586 case COMP_WHERE:
5587 gfc_error ("ENTRY statement at %C cannot appear within "
5588 "a WHERE block");
5589 break;
5590 case COMP_CONTAINS:
5591 gfc_error ("ENTRY statement at %C cannot appear within "
5592 "a contained subprogram");
5593 break;
5594 default:
5595 gfc_error ("Unexpected ENTRY statement at %C");
5597 return MATCH_ERROR;
5600 module_procedure = gfc_current_ns->parent != NULL
5601 && gfc_current_ns->parent->proc_name
5602 && gfc_current_ns->parent->proc_name->attr.flavor
5603 == FL_MODULE;
5605 if (gfc_current_ns->parent != NULL
5606 && gfc_current_ns->parent->proc_name
5607 && !module_procedure)
5609 gfc_error("ENTRY statement at %C cannot appear in a "
5610 "contained procedure");
5611 return MATCH_ERROR;
5614 /* Module function entries need special care in get_proc_name
5615 because previous references within the function will have
5616 created symbols attached to the current namespace. */
5617 if (get_proc_name (name, &entry,
5618 gfc_current_ns->parent != NULL
5619 && module_procedure))
5620 return MATCH_ERROR;
5622 proc = gfc_current_block ();
5624 /* Make sure that it isn't already declared as BIND(C). If it is, it
5625 must have been marked BIND(C) with a BIND(C) attribute and that is
5626 not allowed for procedures. */
5627 if (entry->attr.is_bind_c == 1)
5629 entry->attr.is_bind_c = 0;
5630 if (entry->old_symbol != NULL)
5631 gfc_error_now ("BIND(C) attribute at %L can only be used for "
5632 "variables or common blocks",
5633 &(entry->old_symbol->declared_at));
5634 else
5635 gfc_error_now ("BIND(C) attribute at %L can only be used for "
5636 "variables or common blocks", &gfc_current_locus);
5639 /* Check what next non-whitespace character is so we can tell if there
5640 is the required parens if we have a BIND(C). */
5641 old_loc = gfc_current_locus;
5642 gfc_gobble_whitespace ();
5643 peek_char = gfc_peek_ascii_char ();
5645 if (state == COMP_SUBROUTINE)
5647 m = gfc_match_formal_arglist (entry, 0, 1);
5648 if (m != MATCH_YES)
5649 return MATCH_ERROR;
5651 /* Call gfc_match_bind_c with allow_binding_name = true as ENTRY can
5652 never be an internal procedure. */
5653 is_bind_c = gfc_match_bind_c (entry, true);
5654 if (is_bind_c == MATCH_ERROR)
5655 return MATCH_ERROR;
5656 if (is_bind_c == MATCH_YES)
5658 if (peek_char != '(')
5660 gfc_error ("Missing required parentheses before BIND(C) at %C");
5661 return MATCH_ERROR;
5663 if (!gfc_add_is_bind_c (&(entry->attr), entry->name,
5664 &(entry->declared_at), 1))
5665 return MATCH_ERROR;
5668 if (!gfc_current_ns->parent
5669 && !add_global_entry (name, entry->binding_label, true,
5670 &old_loc))
5671 return MATCH_ERROR;
5673 /* An entry in a subroutine. */
5674 if (!gfc_add_entry (&entry->attr, entry->name, NULL)
5675 || !gfc_add_subroutine (&entry->attr, entry->name, NULL))
5676 return MATCH_ERROR;
5678 else
5680 /* An entry in a function.
5681 We need to take special care because writing
5682 ENTRY f()
5684 ENTRY f
5685 is allowed, whereas
5686 ENTRY f() RESULT (r)
5687 can't be written as
5688 ENTRY f RESULT (r). */
5689 if (gfc_match_eos () == MATCH_YES)
5691 gfc_current_locus = old_loc;
5692 /* Match the empty argument list, and add the interface to
5693 the symbol. */
5694 m = gfc_match_formal_arglist (entry, 0, 1);
5696 else
5697 m = gfc_match_formal_arglist (entry, 0, 0);
5699 if (m != MATCH_YES)
5700 return MATCH_ERROR;
5702 result = NULL;
5704 if (gfc_match_eos () == MATCH_YES)
5706 if (!gfc_add_entry (&entry->attr, entry->name, NULL)
5707 || !gfc_add_function (&entry->attr, entry->name, NULL))
5708 return MATCH_ERROR;
5710 entry->result = entry;
5712 else
5714 m = gfc_match_suffix (entry, &result);
5715 if (m == MATCH_NO)
5716 gfc_syntax_error (ST_ENTRY);
5717 if (m != MATCH_YES)
5718 return MATCH_ERROR;
5720 if (result)
5722 if (!gfc_add_result (&result->attr, result->name, NULL)
5723 || !gfc_add_entry (&entry->attr, result->name, NULL)
5724 || !gfc_add_function (&entry->attr, result->name, NULL))
5725 return MATCH_ERROR;
5726 entry->result = result;
5728 else
5730 if (!gfc_add_entry (&entry->attr, entry->name, NULL)
5731 || !gfc_add_function (&entry->attr, entry->name, NULL))
5732 return MATCH_ERROR;
5733 entry->result = entry;
5737 if (!gfc_current_ns->parent
5738 && !add_global_entry (name, entry->binding_label, false,
5739 &old_loc))
5740 return MATCH_ERROR;
5743 if (gfc_match_eos () != MATCH_YES)
5745 gfc_syntax_error (ST_ENTRY);
5746 return MATCH_ERROR;
5749 entry->attr.recursive = proc->attr.recursive;
5750 entry->attr.elemental = proc->attr.elemental;
5751 entry->attr.pure = proc->attr.pure;
5753 el = gfc_get_entry_list ();
5754 el->sym = entry;
5755 el->next = gfc_current_ns->entries;
5756 gfc_current_ns->entries = el;
5757 if (el->next)
5758 el->id = el->next->id + 1;
5759 else
5760 el->id = 1;
5762 new_st.op = EXEC_ENTRY;
5763 new_st.ext.entry = el;
5765 return MATCH_YES;
5769 /* Match a subroutine statement, including optional prefixes. */
5771 match
5772 gfc_match_subroutine (void)
5774 char name[GFC_MAX_SYMBOL_LEN + 1];
5775 gfc_symbol *sym;
5776 match m;
5777 match is_bind_c;
5778 char peek_char;
5779 bool allow_binding_name;
5781 if (gfc_current_state () != COMP_NONE
5782 && gfc_current_state () != COMP_INTERFACE
5783 && gfc_current_state () != COMP_CONTAINS)
5784 return MATCH_NO;
5786 m = gfc_match_prefix (NULL);
5787 if (m != MATCH_YES)
5788 return m;
5790 m = gfc_match ("subroutine% %n", name);
5791 if (m != MATCH_YES)
5792 return m;
5794 if (get_proc_name (name, &sym, false))
5795 return MATCH_ERROR;
5797 /* Set declared_at as it might point to, e.g., a PUBLIC statement, if
5798 the symbol existed before. */
5799 sym->declared_at = gfc_current_locus;
5801 if (add_hidden_procptr_result (sym))
5802 sym = sym->result;
5804 gfc_new_block = sym;
5806 /* Check what next non-whitespace character is so we can tell if there
5807 is the required parens if we have a BIND(C). */
5808 gfc_gobble_whitespace ();
5809 peek_char = gfc_peek_ascii_char ();
5811 if (!gfc_add_subroutine (&sym->attr, sym->name, NULL))
5812 return MATCH_ERROR;
5814 if (gfc_match_formal_arglist (sym, 0, 1) != MATCH_YES)
5815 return MATCH_ERROR;
5817 /* Make sure that it isn't already declared as BIND(C). If it is, it
5818 must have been marked BIND(C) with a BIND(C) attribute and that is
5819 not allowed for procedures. */
5820 if (sym->attr.is_bind_c == 1)
5822 sym->attr.is_bind_c = 0;
5823 if (sym->old_symbol != NULL)
5824 gfc_error_now ("BIND(C) attribute at %L can only be used for "
5825 "variables or common blocks",
5826 &(sym->old_symbol->declared_at));
5827 else
5828 gfc_error_now ("BIND(C) attribute at %L can only be used for "
5829 "variables or common blocks", &gfc_current_locus);
5832 /* C binding names are not allowed for internal procedures. */
5833 if (gfc_current_state () == COMP_CONTAINS
5834 && sym->ns->proc_name->attr.flavor != FL_MODULE)
5835 allow_binding_name = false;
5836 else
5837 allow_binding_name = true;
5839 /* Here, we are just checking if it has the bind(c) attribute, and if
5840 so, then we need to make sure it's all correct. If it doesn't,
5841 we still need to continue matching the rest of the subroutine line. */
5842 is_bind_c = gfc_match_bind_c (sym, allow_binding_name);
5843 if (is_bind_c == MATCH_ERROR)
5845 /* There was an attempt at the bind(c), but it was wrong. An
5846 error message should have been printed w/in the gfc_match_bind_c
5847 so here we'll just return the MATCH_ERROR. */
5848 return MATCH_ERROR;
5851 if (is_bind_c == MATCH_YES)
5853 /* The following is allowed in the Fortran 2008 draft. */
5854 if (gfc_current_state () == COMP_CONTAINS
5855 && sym->ns->proc_name->attr.flavor != FL_MODULE
5856 && !gfc_notify_std (GFC_STD_F2008, "BIND(C) attribute "
5857 "at %L may not be specified for an internal "
5858 "procedure", &gfc_current_locus))
5859 return MATCH_ERROR;
5861 if (peek_char != '(')
5863 gfc_error ("Missing required parentheses before BIND(C) at %C");
5864 return MATCH_ERROR;
5866 if (!gfc_add_is_bind_c (&(sym->attr), sym->name,
5867 &(sym->declared_at), 1))
5868 return MATCH_ERROR;
5871 if (gfc_match_eos () != MATCH_YES)
5873 gfc_syntax_error (ST_SUBROUTINE);
5874 return MATCH_ERROR;
5877 if (!copy_prefix (&sym->attr, &sym->declared_at))
5878 return MATCH_ERROR;
5880 /* Warn if it has the same name as an intrinsic. */
5881 do_warn_intrinsic_shadow (sym, false);
5883 return MATCH_YES;
5887 /* Check that the NAME identifier in a BIND attribute or statement
5888 is conform to C identifier rules. */
5890 match
5891 check_bind_name_identifier (char **name)
5893 char *n = *name, *p;
5895 /* Remove leading spaces. */
5896 while (*n == ' ')
5897 n++;
5899 /* On an empty string, free memory and set name to NULL. */
5900 if (*n == '\0')
5902 free (*name);
5903 *name = NULL;
5904 return MATCH_YES;
5907 /* Remove trailing spaces. */
5908 p = n + strlen(n) - 1;
5909 while (*p == ' ')
5910 *(p--) = '\0';
5912 /* Insert the identifier into the symbol table. */
5913 p = xstrdup (n);
5914 free (*name);
5915 *name = p;
5917 /* Now check that identifier is valid under C rules. */
5918 if (ISDIGIT (*p))
5920 gfc_error ("Invalid C identifier in NAME= specifier at %C");
5921 return MATCH_ERROR;
5924 for (; *p; p++)
5925 if (!(ISALNUM (*p) || *p == '_' || *p == '$'))
5927 gfc_error ("Invalid C identifier in NAME= specifier at %C");
5928 return MATCH_ERROR;
5931 return MATCH_YES;
5935 /* Match a BIND(C) specifier, with the optional 'name=' specifier if
5936 given, and set the binding label in either the given symbol (if not
5937 NULL), or in the current_ts. The symbol may be NULL because we may
5938 encounter the BIND(C) before the declaration itself. Return
5939 MATCH_NO if what we're looking at isn't a BIND(C) specifier,
5940 MATCH_ERROR if it is a BIND(C) clause but an error was encountered,
5941 or MATCH_YES if the specifier was correct and the binding label and
5942 bind(c) fields were set correctly for the given symbol or the
5943 current_ts. If allow_binding_name is false, no binding name may be
5944 given. */
5946 match
5947 gfc_match_bind_c (gfc_symbol *sym, bool allow_binding_name)
5949 char *binding_label = NULL;
5950 gfc_expr *e = NULL;
5952 /* Initialize the flag that specifies whether we encountered a NAME=
5953 specifier or not. */
5954 has_name_equals = 0;
5956 /* This much we have to be able to match, in this order, if
5957 there is a bind(c) label. */
5958 if (gfc_match (" bind ( c ") != MATCH_YES)
5959 return MATCH_NO;
5961 /* Now see if there is a binding label, or if we've reached the
5962 end of the bind(c) attribute without one. */
5963 if (gfc_match_char (',') == MATCH_YES)
5965 if (gfc_match (" name = ") != MATCH_YES)
5967 gfc_error ("Syntax error in NAME= specifier for binding label "
5968 "at %C");
5969 /* should give an error message here */
5970 return MATCH_ERROR;
5973 has_name_equals = 1;
5975 if (gfc_match_init_expr (&e) != MATCH_YES)
5977 gfc_free_expr (e);
5978 return MATCH_ERROR;
5981 if (!gfc_simplify_expr(e, 0))
5983 gfc_error ("NAME= specifier at %C should be a constant expression");
5984 gfc_free_expr (e);
5985 return MATCH_ERROR;
5988 if (e->expr_type != EXPR_CONSTANT || e->ts.type != BT_CHARACTER
5989 || e->ts.kind != gfc_default_character_kind || e->rank != 0)
5991 gfc_error ("NAME= specifier at %C should be a scalar of "
5992 "default character kind");
5993 gfc_free_expr(e);
5994 return MATCH_ERROR;
5997 // Get a C string from the Fortran string constant
5998 binding_label = gfc_widechar_to_char (e->value.character.string,
5999 e->value.character.length);
6000 gfc_free_expr(e);
6002 // Check that it is valid (old gfc_match_name_C)
6003 if (check_bind_name_identifier (&binding_label) != MATCH_YES)
6004 return MATCH_ERROR;
6007 /* Get the required right paren. */
6008 if (gfc_match_char (')') != MATCH_YES)
6010 gfc_error ("Missing closing paren for binding label at %C");
6011 return MATCH_ERROR;
6014 if (has_name_equals && !allow_binding_name)
6016 gfc_error ("No binding name is allowed in BIND(C) at %C");
6017 return MATCH_ERROR;
6020 if (has_name_equals && sym != NULL && sym->attr.dummy)
6022 gfc_error ("For dummy procedure %s, no binding name is "
6023 "allowed in BIND(C) at %C", sym->name);
6024 return MATCH_ERROR;
6028 /* Save the binding label to the symbol. If sym is null, we're
6029 probably matching the typespec attributes of a declaration and
6030 haven't gotten the name yet, and therefore, no symbol yet. */
6031 if (binding_label)
6033 if (sym != NULL)
6034 sym->binding_label = binding_label;
6035 else
6036 curr_binding_label = binding_label;
6038 else if (allow_binding_name)
6040 /* No binding label, but if symbol isn't null, we
6041 can set the label for it here.
6042 If name="" or allow_binding_name is false, no C binding name is
6043 created. */
6044 if (sym != NULL && sym->name != NULL && has_name_equals == 0)
6045 sym->binding_label = IDENTIFIER_POINTER (get_identifier (sym->name));
6048 if (has_name_equals && gfc_current_state () == COMP_INTERFACE
6049 && current_interface.type == INTERFACE_ABSTRACT)
6051 gfc_error ("NAME not allowed on BIND(C) for ABSTRACT INTERFACE at %C");
6052 return MATCH_ERROR;
6055 return MATCH_YES;
6059 /* Return nonzero if we're currently compiling a contained procedure. */
6061 static int
6062 contained_procedure (void)
6064 gfc_state_data *s = gfc_state_stack;
6066 if ((s->state == COMP_SUBROUTINE || s->state == COMP_FUNCTION)
6067 && s->previous != NULL && s->previous->state == COMP_CONTAINS)
6068 return 1;
6070 return 0;
6073 /* Set the kind of each enumerator. The kind is selected such that it is
6074 interoperable with the corresponding C enumeration type, making
6075 sure that -fshort-enums is honored. */
6077 static void
6078 set_enum_kind(void)
6080 enumerator_history *current_history = NULL;
6081 int kind;
6082 int i;
6084 if (max_enum == NULL || enum_history == NULL)
6085 return;
6087 if (!flag_short_enums)
6088 return;
6090 i = 0;
6093 kind = gfc_integer_kinds[i++].kind;
6095 while (kind < gfc_c_int_kind
6096 && gfc_check_integer_range (max_enum->initializer->value.integer,
6097 kind) != ARITH_OK);
6099 current_history = enum_history;
6100 while (current_history != NULL)
6102 current_history->sym->ts.kind = kind;
6103 current_history = current_history->next;
6108 /* Match any of the various end-block statements. Returns the type of
6109 END to the caller. The END INTERFACE, END IF, END DO, END SELECT
6110 and END BLOCK statements cannot be replaced by a single END statement. */
6112 match
6113 gfc_match_end (gfc_statement *st)
6115 char name[GFC_MAX_SYMBOL_LEN + 1];
6116 gfc_compile_state state;
6117 locus old_loc;
6118 const char *block_name;
6119 const char *target;
6120 int eos_ok;
6121 match m;
6122 gfc_namespace *parent_ns, *ns, *prev_ns;
6123 gfc_namespace **nsp;
6125 old_loc = gfc_current_locus;
6126 if (gfc_match ("end") != MATCH_YES)
6127 return MATCH_NO;
6129 state = gfc_current_state ();
6130 block_name = gfc_current_block () == NULL
6131 ? NULL : gfc_current_block ()->name;
6133 switch (state)
6135 case COMP_ASSOCIATE:
6136 case COMP_BLOCK:
6137 if (!strncmp (block_name, "block@", strlen("block@")))
6138 block_name = NULL;
6139 break;
6141 case COMP_CONTAINS:
6142 case COMP_DERIVED_CONTAINS:
6143 state = gfc_state_stack->previous->state;
6144 block_name = gfc_state_stack->previous->sym == NULL
6145 ? NULL : gfc_state_stack->previous->sym->name;
6146 break;
6148 default:
6149 break;
6152 switch (state)
6154 case COMP_NONE:
6155 case COMP_PROGRAM:
6156 *st = ST_END_PROGRAM;
6157 target = " program";
6158 eos_ok = 1;
6159 break;
6161 case COMP_SUBROUTINE:
6162 *st = ST_END_SUBROUTINE;
6163 target = " subroutine";
6164 eos_ok = !contained_procedure ();
6165 break;
6167 case COMP_FUNCTION:
6168 *st = ST_END_FUNCTION;
6169 target = " function";
6170 eos_ok = !contained_procedure ();
6171 break;
6173 case COMP_BLOCK_DATA:
6174 *st = ST_END_BLOCK_DATA;
6175 target = " block data";
6176 eos_ok = 1;
6177 break;
6179 case COMP_MODULE:
6180 *st = ST_END_MODULE;
6181 target = " module";
6182 eos_ok = 1;
6183 break;
6185 case COMP_INTERFACE:
6186 *st = ST_END_INTERFACE;
6187 target = " interface";
6188 eos_ok = 0;
6189 break;
6191 case COMP_DERIVED:
6192 case COMP_DERIVED_CONTAINS:
6193 *st = ST_END_TYPE;
6194 target = " type";
6195 eos_ok = 0;
6196 break;
6198 case COMP_ASSOCIATE:
6199 *st = ST_END_ASSOCIATE;
6200 target = " associate";
6201 eos_ok = 0;
6202 break;
6204 case COMP_BLOCK:
6205 *st = ST_END_BLOCK;
6206 target = " block";
6207 eos_ok = 0;
6208 break;
6210 case COMP_IF:
6211 *st = ST_ENDIF;
6212 target = " if";
6213 eos_ok = 0;
6214 break;
6216 case COMP_DO:
6217 case COMP_DO_CONCURRENT:
6218 *st = ST_ENDDO;
6219 target = " do";
6220 eos_ok = 0;
6221 break;
6223 case COMP_CRITICAL:
6224 *st = ST_END_CRITICAL;
6225 target = " critical";
6226 eos_ok = 0;
6227 break;
6229 case COMP_SELECT:
6230 case COMP_SELECT_TYPE:
6231 *st = ST_END_SELECT;
6232 target = " select";
6233 eos_ok = 0;
6234 break;
6236 case COMP_FORALL:
6237 *st = ST_END_FORALL;
6238 target = " forall";
6239 eos_ok = 0;
6240 break;
6242 case COMP_WHERE:
6243 *st = ST_END_WHERE;
6244 target = " where";
6245 eos_ok = 0;
6246 break;
6248 case COMP_ENUM:
6249 *st = ST_END_ENUM;
6250 target = " enum";
6251 eos_ok = 0;
6252 last_initializer = NULL;
6253 set_enum_kind ();
6254 gfc_free_enum_history ();
6255 break;
6257 default:
6258 gfc_error ("Unexpected END statement at %C");
6259 goto cleanup;
6262 old_loc = gfc_current_locus;
6263 if (gfc_match_eos () == MATCH_YES)
6265 if (!eos_ok && (*st == ST_END_SUBROUTINE || *st == ST_END_FUNCTION))
6267 if (!gfc_notify_std (GFC_STD_F2008, "END statement "
6268 "instead of %s statement at %L",
6269 gfc_ascii_statement(*st), &old_loc))
6270 goto cleanup;
6272 else if (!eos_ok)
6274 /* We would have required END [something]. */
6275 gfc_error ("%s statement expected at %L",
6276 gfc_ascii_statement (*st), &old_loc);
6277 goto cleanup;
6280 return MATCH_YES;
6283 /* Verify that we've got the sort of end-block that we're expecting. */
6284 if (gfc_match (target) != MATCH_YES)
6286 gfc_error ("Expecting %s statement at %L", gfc_ascii_statement (*st),
6287 &old_loc);
6288 goto cleanup;
6291 old_loc = gfc_current_locus;
6292 /* If we're at the end, make sure a block name wasn't required. */
6293 if (gfc_match_eos () == MATCH_YES)
6296 if (*st != ST_ENDDO && *st != ST_ENDIF && *st != ST_END_SELECT
6297 && *st != ST_END_FORALL && *st != ST_END_WHERE && *st != ST_END_BLOCK
6298 && *st != ST_END_ASSOCIATE && *st != ST_END_CRITICAL)
6299 return MATCH_YES;
6301 if (!block_name)
6302 return MATCH_YES;
6304 gfc_error ("Expected block name of %qs in %s statement at %L",
6305 block_name, gfc_ascii_statement (*st), &old_loc);
6307 return MATCH_ERROR;
6310 /* END INTERFACE has a special handler for its several possible endings. */
6311 if (*st == ST_END_INTERFACE)
6312 return gfc_match_end_interface ();
6314 /* We haven't hit the end of statement, so what is left must be an
6315 end-name. */
6316 m = gfc_match_space ();
6317 if (m == MATCH_YES)
6318 m = gfc_match_name (name);
6320 if (m == MATCH_NO)
6321 gfc_error ("Expected terminating name at %C");
6322 if (m != MATCH_YES)
6323 goto cleanup;
6325 if (block_name == NULL)
6326 goto syntax;
6328 if (strcmp (name, block_name) != 0 && strcmp (block_name, "ppr@") != 0)
6330 gfc_error ("Expected label %qs for %s statement at %C", block_name,
6331 gfc_ascii_statement (*st));
6332 goto cleanup;
6334 /* Procedure pointer as function result. */
6335 else if (strcmp (block_name, "ppr@") == 0
6336 && strcmp (name, gfc_current_block ()->ns->proc_name->name) != 0)
6338 gfc_error ("Expected label %qs for %s statement at %C",
6339 gfc_current_block ()->ns->proc_name->name,
6340 gfc_ascii_statement (*st));
6341 goto cleanup;
6344 if (gfc_match_eos () == MATCH_YES)
6345 return MATCH_YES;
6347 syntax:
6348 gfc_syntax_error (*st);
6350 cleanup:
6351 gfc_current_locus = old_loc;
6353 /* If we are missing an END BLOCK, we created a half-ready namespace.
6354 Remove it from the parent namespace's sibling list. */
6356 if (state == COMP_BLOCK)
6358 parent_ns = gfc_current_ns->parent;
6360 nsp = &(gfc_state_stack->previous->tail->ext.block.ns);
6362 prev_ns = NULL;
6363 ns = *nsp;
6364 while (ns)
6366 if (ns == gfc_current_ns)
6368 if (prev_ns == NULL)
6369 *nsp = NULL;
6370 else
6371 prev_ns->sibling = ns->sibling;
6373 prev_ns = ns;
6374 ns = ns->sibling;
6377 gfc_free_namespace (gfc_current_ns);
6378 gfc_current_ns = parent_ns;
6381 return MATCH_ERROR;
6386 /***************** Attribute declaration statements ****************/
6388 /* Set the attribute of a single variable. */
6390 static match
6391 attr_decl1 (void)
6393 char name[GFC_MAX_SYMBOL_LEN + 1];
6394 gfc_array_spec *as;
6396 /* Workaround -Wmaybe-uninitialized false positive during
6397 profiledbootstrap by initializing them. */
6398 gfc_symbol *sym = NULL;
6399 locus var_locus;
6400 match m;
6402 as = NULL;
6404 m = gfc_match_name (name);
6405 if (m != MATCH_YES)
6406 goto cleanup;
6408 if (find_special (name, &sym, false))
6409 return MATCH_ERROR;
6411 if (!check_function_name (name))
6413 m = MATCH_ERROR;
6414 goto cleanup;
6417 var_locus = gfc_current_locus;
6419 /* Deal with possible array specification for certain attributes. */
6420 if (current_attr.dimension
6421 || current_attr.codimension
6422 || current_attr.allocatable
6423 || current_attr.pointer
6424 || current_attr.target)
6426 m = gfc_match_array_spec (&as, !current_attr.codimension,
6427 !current_attr.dimension
6428 && !current_attr.pointer
6429 && !current_attr.target);
6430 if (m == MATCH_ERROR)
6431 goto cleanup;
6433 if (current_attr.dimension && m == MATCH_NO)
6435 gfc_error ("Missing array specification at %L in DIMENSION "
6436 "statement", &var_locus);
6437 m = MATCH_ERROR;
6438 goto cleanup;
6441 if (current_attr.dimension && sym->value)
6443 gfc_error ("Dimensions specified for %s at %L after its "
6444 "initialisation", sym->name, &var_locus);
6445 m = MATCH_ERROR;
6446 goto cleanup;
6449 if (current_attr.codimension && m == MATCH_NO)
6451 gfc_error ("Missing array specification at %L in CODIMENSION "
6452 "statement", &var_locus);
6453 m = MATCH_ERROR;
6454 goto cleanup;
6457 if ((current_attr.allocatable || current_attr.pointer)
6458 && (m == MATCH_YES) && (as->type != AS_DEFERRED))
6460 gfc_error ("Array specification must be deferred at %L", &var_locus);
6461 m = MATCH_ERROR;
6462 goto cleanup;
6466 /* Update symbol table. DIMENSION attribute is set in
6467 gfc_set_array_spec(). For CLASS variables, this must be applied
6468 to the first component, or '_data' field. */
6469 if (sym->ts.type == BT_CLASS && sym->ts.u.derived->attr.is_class)
6471 if (!gfc_copy_attr (&CLASS_DATA(sym)->attr, &current_attr, &var_locus))
6473 m = MATCH_ERROR;
6474 goto cleanup;
6477 else
6479 if (current_attr.dimension == 0 && current_attr.codimension == 0
6480 && !gfc_copy_attr (&sym->attr, &current_attr, &var_locus))
6482 m = MATCH_ERROR;
6483 goto cleanup;
6487 if (sym->ts.type == BT_CLASS
6488 && !gfc_build_class_symbol (&sym->ts, &sym->attr, &sym->as))
6490 m = MATCH_ERROR;
6491 goto cleanup;
6494 if (!gfc_set_array_spec (sym, as, &var_locus))
6496 m = MATCH_ERROR;
6497 goto cleanup;
6500 if (sym->attr.cray_pointee && sym->as != NULL)
6502 /* Fix the array spec. */
6503 m = gfc_mod_pointee_as (sym->as);
6504 if (m == MATCH_ERROR)
6505 goto cleanup;
6508 if (!gfc_add_attribute (&sym->attr, &var_locus))
6510 m = MATCH_ERROR;
6511 goto cleanup;
6514 if ((current_attr.external || current_attr.intrinsic)
6515 && sym->attr.flavor != FL_PROCEDURE
6516 && !gfc_add_flavor (&sym->attr, FL_PROCEDURE, sym->name, NULL))
6518 m = MATCH_ERROR;
6519 goto cleanup;
6522 add_hidden_procptr_result (sym);
6524 return MATCH_YES;
6526 cleanup:
6527 gfc_free_array_spec (as);
6528 return m;
6532 /* Generic attribute declaration subroutine. Used for attributes that
6533 just have a list of names. */
6535 static match
6536 attr_decl (void)
6538 match m;
6540 /* Gobble the optional double colon, by simply ignoring the result
6541 of gfc_match(). */
6542 gfc_match (" ::");
6544 for (;;)
6546 m = attr_decl1 ();
6547 if (m != MATCH_YES)
6548 break;
6550 if (gfc_match_eos () == MATCH_YES)
6552 m = MATCH_YES;
6553 break;
6556 if (gfc_match_char (',') != MATCH_YES)
6558 gfc_error ("Unexpected character in variable list at %C");
6559 m = MATCH_ERROR;
6560 break;
6564 return m;
6568 /* This routine matches Cray Pointer declarations of the form:
6569 pointer ( <pointer>, <pointee> )
6571 pointer ( <pointer1>, <pointee1> ), ( <pointer2>, <pointee2> ), ...
6572 The pointer, if already declared, should be an integer. Otherwise, we
6573 set it as BT_INTEGER with kind gfc_index_integer_kind. The pointee may
6574 be either a scalar, or an array declaration. No space is allocated for
6575 the pointee. For the statement
6576 pointer (ipt, ar(10))
6577 any subsequent uses of ar will be translated (in C-notation) as
6578 ar(i) => ((<type> *) ipt)(i)
6579 After gimplification, pointee variable will disappear in the code. */
6581 static match
6582 cray_pointer_decl (void)
6584 match m;
6585 gfc_array_spec *as = NULL;
6586 gfc_symbol *cptr; /* Pointer symbol. */
6587 gfc_symbol *cpte; /* Pointee symbol. */
6588 locus var_locus;
6589 bool done = false;
6591 while (!done)
6593 if (gfc_match_char ('(') != MATCH_YES)
6595 gfc_error ("Expected %<(%> at %C");
6596 return MATCH_ERROR;
6599 /* Match pointer. */
6600 var_locus = gfc_current_locus;
6601 gfc_clear_attr (&current_attr);
6602 gfc_add_cray_pointer (&current_attr, &var_locus);
6603 current_ts.type = BT_INTEGER;
6604 current_ts.kind = gfc_index_integer_kind;
6606 m = gfc_match_symbol (&cptr, 0);
6607 if (m != MATCH_YES)
6609 gfc_error ("Expected variable name at %C");
6610 return m;
6613 if (!gfc_add_cray_pointer (&cptr->attr, &var_locus))
6614 return MATCH_ERROR;
6616 gfc_set_sym_referenced (cptr);
6618 if (cptr->ts.type == BT_UNKNOWN) /* Override the type, if necessary. */
6620 cptr->ts.type = BT_INTEGER;
6621 cptr->ts.kind = gfc_index_integer_kind;
6623 else if (cptr->ts.type != BT_INTEGER)
6625 gfc_error ("Cray pointer at %C must be an integer");
6626 return MATCH_ERROR;
6628 else if (cptr->ts.kind < gfc_index_integer_kind)
6629 gfc_warning (0, "Cray pointer at %C has %d bytes of precision;"
6630 " memory addresses require %d bytes",
6631 cptr->ts.kind, gfc_index_integer_kind);
6633 if (gfc_match_char (',') != MATCH_YES)
6635 gfc_error ("Expected \",\" at %C");
6636 return MATCH_ERROR;
6639 /* Match Pointee. */
6640 var_locus = gfc_current_locus;
6641 gfc_clear_attr (&current_attr);
6642 gfc_add_cray_pointee (&current_attr, &var_locus);
6643 current_ts.type = BT_UNKNOWN;
6644 current_ts.kind = 0;
6646 m = gfc_match_symbol (&cpte, 0);
6647 if (m != MATCH_YES)
6649 gfc_error ("Expected variable name at %C");
6650 return m;
6653 /* Check for an optional array spec. */
6654 m = gfc_match_array_spec (&as, true, false);
6655 if (m == MATCH_ERROR)
6657 gfc_free_array_spec (as);
6658 return m;
6660 else if (m == MATCH_NO)
6662 gfc_free_array_spec (as);
6663 as = NULL;
6666 if (!gfc_add_cray_pointee (&cpte->attr, &var_locus))
6667 return MATCH_ERROR;
6669 gfc_set_sym_referenced (cpte);
6671 if (cpte->as == NULL)
6673 if (!gfc_set_array_spec (cpte, as, &var_locus))
6674 gfc_internal_error ("Couldn't set Cray pointee array spec.");
6676 else if (as != NULL)
6678 gfc_error ("Duplicate array spec for Cray pointee at %C");
6679 gfc_free_array_spec (as);
6680 return MATCH_ERROR;
6683 as = NULL;
6685 if (cpte->as != NULL)
6687 /* Fix array spec. */
6688 m = gfc_mod_pointee_as (cpte->as);
6689 if (m == MATCH_ERROR)
6690 return m;
6693 /* Point the Pointee at the Pointer. */
6694 cpte->cp_pointer = cptr;
6696 if (gfc_match_char (')') != MATCH_YES)
6698 gfc_error ("Expected \")\" at %C");
6699 return MATCH_ERROR;
6701 m = gfc_match_char (',');
6702 if (m != MATCH_YES)
6703 done = true; /* Stop searching for more declarations. */
6707 if (m == MATCH_ERROR /* Failed when trying to find ',' above. */
6708 || gfc_match_eos () != MATCH_YES)
6710 gfc_error ("Expected %<,%> or end of statement at %C");
6711 return MATCH_ERROR;
6713 return MATCH_YES;
6717 match
6718 gfc_match_external (void)
6721 gfc_clear_attr (&current_attr);
6722 current_attr.external = 1;
6724 return attr_decl ();
6728 match
6729 gfc_match_intent (void)
6731 sym_intent intent;
6733 /* This is not allowed within a BLOCK construct! */
6734 if (gfc_current_state () == COMP_BLOCK)
6736 gfc_error ("INTENT is not allowed inside of BLOCK at %C");
6737 return MATCH_ERROR;
6740 intent = match_intent_spec ();
6741 if (intent == INTENT_UNKNOWN)
6742 return MATCH_ERROR;
6744 gfc_clear_attr (&current_attr);
6745 current_attr.intent = intent;
6747 return attr_decl ();
6751 match
6752 gfc_match_intrinsic (void)
6755 gfc_clear_attr (&current_attr);
6756 current_attr.intrinsic = 1;
6758 return attr_decl ();
6762 match
6763 gfc_match_optional (void)
6765 /* This is not allowed within a BLOCK construct! */
6766 if (gfc_current_state () == COMP_BLOCK)
6768 gfc_error ("OPTIONAL is not allowed inside of BLOCK at %C");
6769 return MATCH_ERROR;
6772 gfc_clear_attr (&current_attr);
6773 current_attr.optional = 1;
6775 return attr_decl ();
6779 match
6780 gfc_match_pointer (void)
6782 gfc_gobble_whitespace ();
6783 if (gfc_peek_ascii_char () == '(')
6785 if (!flag_cray_pointer)
6787 gfc_error ("Cray pointer declaration at %C requires -fcray-pointer "
6788 "flag");
6789 return MATCH_ERROR;
6791 return cray_pointer_decl ();
6793 else
6795 gfc_clear_attr (&current_attr);
6796 current_attr.pointer = 1;
6798 return attr_decl ();
6803 match
6804 gfc_match_allocatable (void)
6806 gfc_clear_attr (&current_attr);
6807 current_attr.allocatable = 1;
6809 return attr_decl ();
6813 match
6814 gfc_match_codimension (void)
6816 gfc_clear_attr (&current_attr);
6817 current_attr.codimension = 1;
6819 return attr_decl ();
6823 match
6824 gfc_match_contiguous (void)
6826 if (!gfc_notify_std (GFC_STD_F2008, "CONTIGUOUS statement at %C"))
6827 return MATCH_ERROR;
6829 gfc_clear_attr (&current_attr);
6830 current_attr.contiguous = 1;
6832 return attr_decl ();
6836 match
6837 gfc_match_dimension (void)
6839 gfc_clear_attr (&current_attr);
6840 current_attr.dimension = 1;
6842 return attr_decl ();
6846 match
6847 gfc_match_target (void)
6849 gfc_clear_attr (&current_attr);
6850 current_attr.target = 1;
6852 return attr_decl ();
6856 /* Match the list of entities being specified in a PUBLIC or PRIVATE
6857 statement. */
6859 static match
6860 access_attr_decl (gfc_statement st)
6862 char name[GFC_MAX_SYMBOL_LEN + 1];
6863 interface_type type;
6864 gfc_user_op *uop;
6865 gfc_symbol *sym, *dt_sym;
6866 gfc_intrinsic_op op;
6867 match m;
6869 if (gfc_match (" ::") == MATCH_NO && gfc_match_space () == MATCH_NO)
6870 goto done;
6872 for (;;)
6874 m = gfc_match_generic_spec (&type, name, &op);
6875 if (m == MATCH_NO)
6876 goto syntax;
6877 if (m == MATCH_ERROR)
6878 return MATCH_ERROR;
6880 switch (type)
6882 case INTERFACE_NAMELESS:
6883 case INTERFACE_ABSTRACT:
6884 goto syntax;
6886 case INTERFACE_GENERIC:
6887 if (gfc_get_symbol (name, NULL, &sym))
6888 goto done;
6890 if (!gfc_add_access (&sym->attr,
6891 (st == ST_PUBLIC)
6892 ? ACCESS_PUBLIC : ACCESS_PRIVATE,
6893 sym->name, NULL))
6894 return MATCH_ERROR;
6896 if (sym->attr.generic && (dt_sym = gfc_find_dt_in_generic (sym))
6897 && !gfc_add_access (&dt_sym->attr,
6898 (st == ST_PUBLIC)
6899 ? ACCESS_PUBLIC : ACCESS_PRIVATE,
6900 sym->name, NULL))
6901 return MATCH_ERROR;
6903 break;
6905 case INTERFACE_INTRINSIC_OP:
6906 if (gfc_current_ns->operator_access[op] == ACCESS_UNKNOWN)
6908 gfc_intrinsic_op other_op;
6910 gfc_current_ns->operator_access[op] =
6911 (st == ST_PUBLIC) ? ACCESS_PUBLIC : ACCESS_PRIVATE;
6913 /* Handle the case if there is another op with the same
6914 function, for INTRINSIC_EQ vs. INTRINSIC_EQ_OS and so on. */
6915 other_op = gfc_equivalent_op (op);
6917 if (other_op != INTRINSIC_NONE)
6918 gfc_current_ns->operator_access[other_op] =
6919 (st == ST_PUBLIC) ? ACCESS_PUBLIC : ACCESS_PRIVATE;
6922 else
6924 gfc_error ("Access specification of the %s operator at %C has "
6925 "already been specified", gfc_op2string (op));
6926 goto done;
6929 break;
6931 case INTERFACE_USER_OP:
6932 uop = gfc_get_uop (name);
6934 if (uop->access == ACCESS_UNKNOWN)
6936 uop->access = (st == ST_PUBLIC)
6937 ? ACCESS_PUBLIC : ACCESS_PRIVATE;
6939 else
6941 gfc_error ("Access specification of the .%s. operator at %C "
6942 "has already been specified", sym->name);
6943 goto done;
6946 break;
6949 if (gfc_match_char (',') == MATCH_NO)
6950 break;
6953 if (gfc_match_eos () != MATCH_YES)
6954 goto syntax;
6955 return MATCH_YES;
6957 syntax:
6958 gfc_syntax_error (st);
6960 done:
6961 return MATCH_ERROR;
6965 match
6966 gfc_match_protected (void)
6968 gfc_symbol *sym;
6969 match m;
6971 if (!gfc_current_ns->proc_name
6972 || gfc_current_ns->proc_name->attr.flavor != FL_MODULE)
6974 gfc_error ("PROTECTED at %C only allowed in specification "
6975 "part of a module");
6976 return MATCH_ERROR;
6980 if (!gfc_notify_std (GFC_STD_F2003, "PROTECTED statement at %C"))
6981 return MATCH_ERROR;
6983 if (gfc_match (" ::") == MATCH_NO && gfc_match_space () == MATCH_NO)
6985 return MATCH_ERROR;
6988 if (gfc_match_eos () == MATCH_YES)
6989 goto syntax;
6991 for(;;)
6993 m = gfc_match_symbol (&sym, 0);
6994 switch (m)
6996 case MATCH_YES:
6997 if (!gfc_add_protected (&sym->attr, sym->name, &gfc_current_locus))
6998 return MATCH_ERROR;
6999 goto next_item;
7001 case MATCH_NO:
7002 break;
7004 case MATCH_ERROR:
7005 return MATCH_ERROR;
7008 next_item:
7009 if (gfc_match_eos () == MATCH_YES)
7010 break;
7011 if (gfc_match_char (',') != MATCH_YES)
7012 goto syntax;
7015 return MATCH_YES;
7017 syntax:
7018 gfc_error ("Syntax error in PROTECTED statement at %C");
7019 return MATCH_ERROR;
7023 /* The PRIVATE statement is a bit weird in that it can be an attribute
7024 declaration, but also works as a standalone statement inside of a
7025 type declaration or a module. */
7027 match
7028 gfc_match_private (gfc_statement *st)
7031 if (gfc_match ("private") != MATCH_YES)
7032 return MATCH_NO;
7034 if (gfc_current_state () != COMP_MODULE
7035 && !(gfc_current_state () == COMP_DERIVED
7036 && gfc_state_stack->previous
7037 && gfc_state_stack->previous->state == COMP_MODULE)
7038 && !(gfc_current_state () == COMP_DERIVED_CONTAINS
7039 && gfc_state_stack->previous && gfc_state_stack->previous->previous
7040 && gfc_state_stack->previous->previous->state == COMP_MODULE))
7042 gfc_error ("PRIVATE statement at %C is only allowed in the "
7043 "specification part of a module");
7044 return MATCH_ERROR;
7047 if (gfc_current_state () == COMP_DERIVED)
7049 if (gfc_match_eos () == MATCH_YES)
7051 *st = ST_PRIVATE;
7052 return MATCH_YES;
7055 gfc_syntax_error (ST_PRIVATE);
7056 return MATCH_ERROR;
7059 if (gfc_match_eos () == MATCH_YES)
7061 *st = ST_PRIVATE;
7062 return MATCH_YES;
7065 *st = ST_ATTR_DECL;
7066 return access_attr_decl (ST_PRIVATE);
7070 match
7071 gfc_match_public (gfc_statement *st)
7074 if (gfc_match ("public") != MATCH_YES)
7075 return MATCH_NO;
7077 if (gfc_current_state () != COMP_MODULE)
7079 gfc_error ("PUBLIC statement at %C is only allowed in the "
7080 "specification part of a module");
7081 return MATCH_ERROR;
7084 if (gfc_match_eos () == MATCH_YES)
7086 *st = ST_PUBLIC;
7087 return MATCH_YES;
7090 *st = ST_ATTR_DECL;
7091 return access_attr_decl (ST_PUBLIC);
7095 /* Workhorse for gfc_match_parameter. */
7097 static match
7098 do_parm (void)
7100 gfc_symbol *sym;
7101 gfc_expr *init;
7102 match m;
7103 bool t;
7105 m = gfc_match_symbol (&sym, 0);
7106 if (m == MATCH_NO)
7107 gfc_error ("Expected variable name at %C in PARAMETER statement");
7109 if (m != MATCH_YES)
7110 return m;
7112 if (gfc_match_char ('=') == MATCH_NO)
7114 gfc_error ("Expected = sign in PARAMETER statement at %C");
7115 return MATCH_ERROR;
7118 m = gfc_match_init_expr (&init);
7119 if (m == MATCH_NO)
7120 gfc_error ("Expected expression at %C in PARAMETER statement");
7121 if (m != MATCH_YES)
7122 return m;
7124 if (sym->ts.type == BT_UNKNOWN
7125 && !gfc_set_default_type (sym, 1, NULL))
7127 m = MATCH_ERROR;
7128 goto cleanup;
7131 if (!gfc_check_assign_symbol (sym, NULL, init)
7132 || !gfc_add_flavor (&sym->attr, FL_PARAMETER, sym->name, NULL))
7134 m = MATCH_ERROR;
7135 goto cleanup;
7138 if (sym->value)
7140 gfc_error ("Initializing already initialized variable at %C");
7141 m = MATCH_ERROR;
7142 goto cleanup;
7145 t = add_init_expr_to_sym (sym->name, &init, &gfc_current_locus);
7146 return (t) ? MATCH_YES : MATCH_ERROR;
7148 cleanup:
7149 gfc_free_expr (init);
7150 return m;
7154 /* Match a parameter statement, with the weird syntax that these have. */
7156 match
7157 gfc_match_parameter (void)
7159 match m;
7161 if (gfc_match_char ('(') == MATCH_NO)
7162 return MATCH_NO;
7164 for (;;)
7166 m = do_parm ();
7167 if (m != MATCH_YES)
7168 break;
7170 if (gfc_match (" )%t") == MATCH_YES)
7171 break;
7173 if (gfc_match_char (',') != MATCH_YES)
7175 gfc_error ("Unexpected characters in PARAMETER statement at %C");
7176 m = MATCH_ERROR;
7177 break;
7181 return m;
7185 /* Save statements have a special syntax. */
7187 match
7188 gfc_match_save (void)
7190 char n[GFC_MAX_SYMBOL_LEN+1];
7191 gfc_common_head *c;
7192 gfc_symbol *sym;
7193 match m;
7195 if (gfc_match_eos () == MATCH_YES)
7197 if (gfc_current_ns->seen_save)
7199 if (!gfc_notify_std (GFC_STD_LEGACY, "Blanket SAVE statement at %C "
7200 "follows previous SAVE statement"))
7201 return MATCH_ERROR;
7204 gfc_current_ns->save_all = gfc_current_ns->seen_save = 1;
7205 return MATCH_YES;
7208 if (gfc_current_ns->save_all)
7210 if (!gfc_notify_std (GFC_STD_LEGACY, "SAVE statement at %C follows "
7211 "blanket SAVE statement"))
7212 return MATCH_ERROR;
7215 gfc_match (" ::");
7217 for (;;)
7219 m = gfc_match_symbol (&sym, 0);
7220 switch (m)
7222 case MATCH_YES:
7223 if (!gfc_add_save (&sym->attr, SAVE_EXPLICIT, sym->name,
7224 &gfc_current_locus))
7225 return MATCH_ERROR;
7226 goto next_item;
7228 case MATCH_NO:
7229 break;
7231 case MATCH_ERROR:
7232 return MATCH_ERROR;
7235 m = gfc_match (" / %n /", &n);
7236 if (m == MATCH_ERROR)
7237 return MATCH_ERROR;
7238 if (m == MATCH_NO)
7239 goto syntax;
7241 c = gfc_get_common (n, 0);
7242 c->saved = 1;
7244 gfc_current_ns->seen_save = 1;
7246 next_item:
7247 if (gfc_match_eos () == MATCH_YES)
7248 break;
7249 if (gfc_match_char (',') != MATCH_YES)
7250 goto syntax;
7253 return MATCH_YES;
7255 syntax:
7256 gfc_error ("Syntax error in SAVE statement at %C");
7257 return MATCH_ERROR;
7261 match
7262 gfc_match_value (void)
7264 gfc_symbol *sym;
7265 match m;
7267 /* This is not allowed within a BLOCK construct! */
7268 if (gfc_current_state () == COMP_BLOCK)
7270 gfc_error ("VALUE is not allowed inside of BLOCK at %C");
7271 return MATCH_ERROR;
7274 if (!gfc_notify_std (GFC_STD_F2003, "VALUE statement at %C"))
7275 return MATCH_ERROR;
7277 if (gfc_match (" ::") == MATCH_NO && gfc_match_space () == MATCH_NO)
7279 return MATCH_ERROR;
7282 if (gfc_match_eos () == MATCH_YES)
7283 goto syntax;
7285 for(;;)
7287 m = gfc_match_symbol (&sym, 0);
7288 switch (m)
7290 case MATCH_YES:
7291 if (!gfc_add_value (&sym->attr, sym->name, &gfc_current_locus))
7292 return MATCH_ERROR;
7293 goto next_item;
7295 case MATCH_NO:
7296 break;
7298 case MATCH_ERROR:
7299 return MATCH_ERROR;
7302 next_item:
7303 if (gfc_match_eos () == MATCH_YES)
7304 break;
7305 if (gfc_match_char (',') != MATCH_YES)
7306 goto syntax;
7309 return MATCH_YES;
7311 syntax:
7312 gfc_error ("Syntax error in VALUE statement at %C");
7313 return MATCH_ERROR;
7317 match
7318 gfc_match_volatile (void)
7320 gfc_symbol *sym;
7321 match m;
7323 if (!gfc_notify_std (GFC_STD_F2003, "VOLATILE statement at %C"))
7324 return MATCH_ERROR;
7326 if (gfc_match (" ::") == MATCH_NO && gfc_match_space () == MATCH_NO)
7328 return MATCH_ERROR;
7331 if (gfc_match_eos () == MATCH_YES)
7332 goto syntax;
7334 for(;;)
7336 /* VOLATILE is special because it can be added to host-associated
7337 symbols locally. Except for coarrays. */
7338 m = gfc_match_symbol (&sym, 1);
7339 switch (m)
7341 case MATCH_YES:
7342 /* F2008, C560+C561. VOLATILE for host-/use-associated variable or
7343 for variable in a BLOCK which is defined outside of the BLOCK. */
7344 if (sym->ns != gfc_current_ns && sym->attr.codimension)
7346 gfc_error ("Specifying VOLATILE for coarray variable %qs at "
7347 "%C, which is use-/host-associated", sym->name);
7348 return MATCH_ERROR;
7350 if (!gfc_add_volatile (&sym->attr, sym->name, &gfc_current_locus))
7351 return MATCH_ERROR;
7352 goto next_item;
7354 case MATCH_NO:
7355 break;
7357 case MATCH_ERROR:
7358 return MATCH_ERROR;
7361 next_item:
7362 if (gfc_match_eos () == MATCH_YES)
7363 break;
7364 if (gfc_match_char (',') != MATCH_YES)
7365 goto syntax;
7368 return MATCH_YES;
7370 syntax:
7371 gfc_error ("Syntax error in VOLATILE statement at %C");
7372 return MATCH_ERROR;
7376 match
7377 gfc_match_asynchronous (void)
7379 gfc_symbol *sym;
7380 match m;
7382 if (!gfc_notify_std (GFC_STD_F2003, "ASYNCHRONOUS statement at %C"))
7383 return MATCH_ERROR;
7385 if (gfc_match (" ::") == MATCH_NO && gfc_match_space () == MATCH_NO)
7387 return MATCH_ERROR;
7390 if (gfc_match_eos () == MATCH_YES)
7391 goto syntax;
7393 for(;;)
7395 /* ASYNCHRONOUS is special because it can be added to host-associated
7396 symbols locally. */
7397 m = gfc_match_symbol (&sym, 1);
7398 switch (m)
7400 case MATCH_YES:
7401 if (!gfc_add_asynchronous (&sym->attr, sym->name, &gfc_current_locus))
7402 return MATCH_ERROR;
7403 goto next_item;
7405 case MATCH_NO:
7406 break;
7408 case MATCH_ERROR:
7409 return MATCH_ERROR;
7412 next_item:
7413 if (gfc_match_eos () == MATCH_YES)
7414 break;
7415 if (gfc_match_char (',') != MATCH_YES)
7416 goto syntax;
7419 return MATCH_YES;
7421 syntax:
7422 gfc_error ("Syntax error in ASYNCHRONOUS statement at %C");
7423 return MATCH_ERROR;
7427 /* Match a module procedure statement. Note that we have to modify
7428 symbols in the parent's namespace because the current one was there
7429 to receive symbols that are in an interface's formal argument list. */
7431 match
7432 gfc_match_modproc (void)
7434 char name[GFC_MAX_SYMBOL_LEN + 1];
7435 gfc_symbol *sym;
7436 match m;
7437 locus old_locus;
7438 gfc_namespace *module_ns;
7439 gfc_interface *old_interface_head, *interface;
7441 if (gfc_state_stack->state != COMP_INTERFACE
7442 || gfc_state_stack->previous == NULL
7443 || current_interface.type == INTERFACE_NAMELESS
7444 || current_interface.type == INTERFACE_ABSTRACT)
7446 gfc_error ("MODULE PROCEDURE at %C must be in a generic module "
7447 "interface");
7448 return MATCH_ERROR;
7451 module_ns = gfc_current_ns->parent;
7452 for (; module_ns; module_ns = module_ns->parent)
7453 if (module_ns->proc_name->attr.flavor == FL_MODULE
7454 || module_ns->proc_name->attr.flavor == FL_PROGRAM
7455 || (module_ns->proc_name->attr.flavor == FL_PROCEDURE
7456 && !module_ns->proc_name->attr.contained))
7457 break;
7459 if (module_ns == NULL)
7460 return MATCH_ERROR;
7462 /* Store the current state of the interface. We will need it if we
7463 end up with a syntax error and need to recover. */
7464 old_interface_head = gfc_current_interface_head ();
7466 /* Check if the F2008 optional double colon appears. */
7467 gfc_gobble_whitespace ();
7468 old_locus = gfc_current_locus;
7469 if (gfc_match ("::") == MATCH_YES)
7471 if (!gfc_notify_std (GFC_STD_F2008, "double colon in "
7472 "MODULE PROCEDURE statement at %L", &old_locus))
7473 return MATCH_ERROR;
7475 else
7476 gfc_current_locus = old_locus;
7478 for (;;)
7480 bool last = false;
7481 old_locus = gfc_current_locus;
7483 m = gfc_match_name (name);
7484 if (m == MATCH_NO)
7485 goto syntax;
7486 if (m != MATCH_YES)
7487 return MATCH_ERROR;
7489 /* Check for syntax error before starting to add symbols to the
7490 current namespace. */
7491 if (gfc_match_eos () == MATCH_YES)
7492 last = true;
7494 if (!last && gfc_match_char (',') != MATCH_YES)
7495 goto syntax;
7497 /* Now we're sure the syntax is valid, we process this item
7498 further. */
7499 if (gfc_get_symbol (name, module_ns, &sym))
7500 return MATCH_ERROR;
7502 if (sym->attr.intrinsic)
7504 gfc_error ("Intrinsic procedure at %L cannot be a MODULE "
7505 "PROCEDURE", &old_locus);
7506 return MATCH_ERROR;
7509 if (sym->attr.proc != PROC_MODULE
7510 && !gfc_add_procedure (&sym->attr, PROC_MODULE, sym->name, NULL))
7511 return MATCH_ERROR;
7513 if (!gfc_add_interface (sym))
7514 return MATCH_ERROR;
7516 sym->attr.mod_proc = 1;
7517 sym->declared_at = old_locus;
7519 if (last)
7520 break;
7523 return MATCH_YES;
7525 syntax:
7526 /* Restore the previous state of the interface. */
7527 interface = gfc_current_interface_head ();
7528 gfc_set_current_interface_head (old_interface_head);
7530 /* Free the new interfaces. */
7531 while (interface != old_interface_head)
7533 gfc_interface *i = interface->next;
7534 free (interface);
7535 interface = i;
7538 /* And issue a syntax error. */
7539 gfc_syntax_error (ST_MODULE_PROC);
7540 return MATCH_ERROR;
7544 /* Check a derived type that is being extended. */
7546 static gfc_symbol*
7547 check_extended_derived_type (char *name)
7549 gfc_symbol *extended;
7551 if (gfc_find_symbol (name, gfc_current_ns, 1, &extended))
7553 gfc_error ("Ambiguous symbol in TYPE definition at %C");
7554 return NULL;
7557 extended = gfc_find_dt_in_generic (extended);
7559 /* F08:C428. */
7560 if (!extended)
7562 gfc_error ("Symbol %qs at %C has not been previously defined", name);
7563 return NULL;
7566 if (extended->attr.flavor != FL_DERIVED)
7568 gfc_error ("%qs in EXTENDS expression at %C is not a "
7569 "derived type", name);
7570 return NULL;
7573 if (extended->attr.is_bind_c)
7575 gfc_error ("%qs cannot be extended at %C because it "
7576 "is BIND(C)", extended->name);
7577 return NULL;
7580 if (extended->attr.sequence)
7582 gfc_error ("%qs cannot be extended at %C because it "
7583 "is a SEQUENCE type", extended->name);
7584 return NULL;
7587 return extended;
7591 /* Match the optional attribute specifiers for a type declaration.
7592 Return MATCH_ERROR if an error is encountered in one of the handled
7593 attributes (public, private, bind(c)), MATCH_NO if what's found is
7594 not a handled attribute, and MATCH_YES otherwise. TODO: More error
7595 checking on attribute conflicts needs to be done. */
7597 match
7598 gfc_get_type_attr_spec (symbol_attribute *attr, char *name)
7600 /* See if the derived type is marked as private. */
7601 if (gfc_match (" , private") == MATCH_YES)
7603 if (gfc_current_state () != COMP_MODULE)
7605 gfc_error ("Derived type at %C can only be PRIVATE in the "
7606 "specification part of a module");
7607 return MATCH_ERROR;
7610 if (!gfc_add_access (attr, ACCESS_PRIVATE, NULL, NULL))
7611 return MATCH_ERROR;
7613 else if (gfc_match (" , public") == MATCH_YES)
7615 if (gfc_current_state () != COMP_MODULE)
7617 gfc_error ("Derived type at %C can only be PUBLIC in the "
7618 "specification part of a module");
7619 return MATCH_ERROR;
7622 if (!gfc_add_access (attr, ACCESS_PUBLIC, NULL, NULL))
7623 return MATCH_ERROR;
7625 else if (gfc_match (" , bind ( c )") == MATCH_YES)
7627 /* If the type is defined to be bind(c) it then needs to make
7628 sure that all fields are interoperable. This will
7629 need to be a semantic check on the finished derived type.
7630 See 15.2.3 (lines 9-12) of F2003 draft. */
7631 if (!gfc_add_is_bind_c (attr, NULL, &gfc_current_locus, 0))
7632 return MATCH_ERROR;
7634 /* TODO: attr conflicts need to be checked, probably in symbol.c. */
7636 else if (gfc_match (" , abstract") == MATCH_YES)
7638 if (!gfc_notify_std (GFC_STD_F2003, "ABSTRACT type at %C"))
7639 return MATCH_ERROR;
7641 if (!gfc_add_abstract (attr, &gfc_current_locus))
7642 return MATCH_ERROR;
7644 else if (name && gfc_match (" , extends ( %n )", name) == MATCH_YES)
7646 if (!gfc_add_extension (attr, &gfc_current_locus))
7647 return MATCH_ERROR;
7649 else
7650 return MATCH_NO;
7652 /* If we get here, something matched. */
7653 return MATCH_YES;
7657 /* Match the beginning of a derived type declaration. If a type name
7658 was the result of a function, then it is possible to have a symbol
7659 already to be known as a derived type yet have no components. */
7661 match
7662 gfc_match_derived_decl (void)
7664 char name[GFC_MAX_SYMBOL_LEN + 1];
7665 char parent[GFC_MAX_SYMBOL_LEN + 1];
7666 symbol_attribute attr;
7667 gfc_symbol *sym, *gensym;
7668 gfc_symbol *extended;
7669 match m;
7670 match is_type_attr_spec = MATCH_NO;
7671 bool seen_attr = false;
7672 gfc_interface *intr = NULL, *head;
7674 if (gfc_current_state () == COMP_DERIVED)
7675 return MATCH_NO;
7677 name[0] = '\0';
7678 parent[0] = '\0';
7679 gfc_clear_attr (&attr);
7680 extended = NULL;
7684 is_type_attr_spec = gfc_get_type_attr_spec (&attr, parent);
7685 if (is_type_attr_spec == MATCH_ERROR)
7686 return MATCH_ERROR;
7687 if (is_type_attr_spec == MATCH_YES)
7688 seen_attr = true;
7689 } while (is_type_attr_spec == MATCH_YES);
7691 /* Deal with derived type extensions. The extension attribute has
7692 been added to 'attr' but now the parent type must be found and
7693 checked. */
7694 if (parent[0])
7695 extended = check_extended_derived_type (parent);
7697 if (parent[0] && !extended)
7698 return MATCH_ERROR;
7700 if (gfc_match (" ::") != MATCH_YES && seen_attr)
7702 gfc_error ("Expected :: in TYPE definition at %C");
7703 return MATCH_ERROR;
7706 m = gfc_match (" %n%t", name);
7707 if (m != MATCH_YES)
7708 return m;
7710 /* Make sure the name is not the name of an intrinsic type. */
7711 if (gfc_is_intrinsic_typename (name))
7713 gfc_error ("Type name %qs at %C cannot be the same as an intrinsic "
7714 "type", name);
7715 return MATCH_ERROR;
7718 if (gfc_get_symbol (name, NULL, &gensym))
7719 return MATCH_ERROR;
7721 if (!gensym->attr.generic && gensym->ts.type != BT_UNKNOWN)
7723 gfc_error ("Derived type name %qs at %C already has a basic type "
7724 "of %s", gensym->name, gfc_typename (&gensym->ts));
7725 return MATCH_ERROR;
7728 if (!gensym->attr.generic
7729 && !gfc_add_generic (&gensym->attr, gensym->name, NULL))
7730 return MATCH_ERROR;
7732 if (!gensym->attr.function
7733 && !gfc_add_function (&gensym->attr, gensym->name, NULL))
7734 return MATCH_ERROR;
7736 sym = gfc_find_dt_in_generic (gensym);
7738 if (sym && (sym->components != NULL || sym->attr.zero_comp))
7740 gfc_error ("Derived type definition of %qs at %C has already been "
7741 "defined", sym->name);
7742 return MATCH_ERROR;
7745 if (!sym)
7747 /* Use upper case to save the actual derived-type symbol. */
7748 gfc_get_symbol (gfc_get_string ("%c%s",
7749 (char) TOUPPER ((unsigned char) gensym->name[0]),
7750 &gensym->name[1]), NULL, &sym);
7751 sym->name = gfc_get_string (gensym->name);
7752 head = gensym->generic;
7753 intr = gfc_get_interface ();
7754 intr->sym = sym;
7755 intr->where = gfc_current_locus;
7756 intr->sym->declared_at = gfc_current_locus;
7757 intr->next = head;
7758 gensym->generic = intr;
7759 gensym->attr.if_source = IFSRC_DECL;
7762 /* The symbol may already have the derived attribute without the
7763 components. The ways this can happen is via a function
7764 definition, an INTRINSIC statement or a subtype in another
7765 derived type that is a pointer. The first part of the AND clause
7766 is true if the symbol is not the return value of a function. */
7767 if (sym->attr.flavor != FL_DERIVED
7768 && !gfc_add_flavor (&sym->attr, FL_DERIVED, sym->name, NULL))
7769 return MATCH_ERROR;
7771 if (attr.access != ACCESS_UNKNOWN
7772 && !gfc_add_access (&sym->attr, attr.access, sym->name, NULL))
7773 return MATCH_ERROR;
7774 else if (sym->attr.access == ACCESS_UNKNOWN
7775 && gensym->attr.access != ACCESS_UNKNOWN
7776 && !gfc_add_access (&sym->attr, gensym->attr.access,
7777 sym->name, NULL))
7778 return MATCH_ERROR;
7780 if (sym->attr.access != ACCESS_UNKNOWN
7781 && gensym->attr.access == ACCESS_UNKNOWN)
7782 gensym->attr.access = sym->attr.access;
7784 /* See if the derived type was labeled as bind(c). */
7785 if (attr.is_bind_c != 0)
7786 sym->attr.is_bind_c = attr.is_bind_c;
7788 /* Construct the f2k_derived namespace if it is not yet there. */
7789 if (!sym->f2k_derived)
7790 sym->f2k_derived = gfc_get_namespace (NULL, 0);
7792 if (extended && !sym->components)
7794 gfc_component *p;
7796 /* Add the extended derived type as the first component. */
7797 gfc_add_component (sym, parent, &p);
7798 extended->refs++;
7799 gfc_set_sym_referenced (extended);
7801 p->ts.type = BT_DERIVED;
7802 p->ts.u.derived = extended;
7803 p->initializer = gfc_default_initializer (&p->ts);
7805 /* Set extension level. */
7806 if (extended->attr.extension == 255)
7808 /* Since the extension field is 8 bit wide, we can only have
7809 up to 255 extension levels. */
7810 gfc_error ("Maximum extension level reached with type %qs at %L",
7811 extended->name, &extended->declared_at);
7812 return MATCH_ERROR;
7814 sym->attr.extension = extended->attr.extension + 1;
7816 /* Provide the links between the extended type and its extension. */
7817 if (!extended->f2k_derived)
7818 extended->f2k_derived = gfc_get_namespace (NULL, 0);
7821 if (!sym->hash_value)
7822 /* Set the hash for the compound name for this type. */
7823 sym->hash_value = gfc_hash_value (sym);
7825 /* Take over the ABSTRACT attribute. */
7826 sym->attr.abstract = attr.abstract;
7828 gfc_new_block = sym;
7830 return MATCH_YES;
7834 /* Cray Pointees can be declared as:
7835 pointer (ipt, a (n,m,...,*)) */
7837 match
7838 gfc_mod_pointee_as (gfc_array_spec *as)
7840 as->cray_pointee = true; /* This will be useful to know later. */
7841 if (as->type == AS_ASSUMED_SIZE)
7842 as->cp_was_assumed = true;
7843 else if (as->type == AS_ASSUMED_SHAPE)
7845 gfc_error ("Cray Pointee at %C cannot be assumed shape array");
7846 return MATCH_ERROR;
7848 return MATCH_YES;
7852 /* Match the enum definition statement, here we are trying to match
7853 the first line of enum definition statement.
7854 Returns MATCH_YES if match is found. */
7856 match
7857 gfc_match_enum (void)
7859 match m;
7861 m = gfc_match_eos ();
7862 if (m != MATCH_YES)
7863 return m;
7865 if (!gfc_notify_std (GFC_STD_F2003, "ENUM and ENUMERATOR at %C"))
7866 return MATCH_ERROR;
7868 return MATCH_YES;
7872 /* Returns an initializer whose value is one higher than the value of the
7873 LAST_INITIALIZER argument. If the argument is NULL, the
7874 initializers value will be set to zero. The initializer's kind
7875 will be set to gfc_c_int_kind.
7877 If -fshort-enums is given, the appropriate kind will be selected
7878 later after all enumerators have been parsed. A warning is issued
7879 here if an initializer exceeds gfc_c_int_kind. */
7881 static gfc_expr *
7882 enum_initializer (gfc_expr *last_initializer, locus where)
7884 gfc_expr *result;
7885 result = gfc_get_constant_expr (BT_INTEGER, gfc_c_int_kind, &where);
7887 mpz_init (result->value.integer);
7889 if (last_initializer != NULL)
7891 mpz_add_ui (result->value.integer, last_initializer->value.integer, 1);
7892 result->where = last_initializer->where;
7894 if (gfc_check_integer_range (result->value.integer,
7895 gfc_c_int_kind) != ARITH_OK)
7897 gfc_error ("Enumerator exceeds the C integer type at %C");
7898 return NULL;
7901 else
7903 /* Control comes here, if it's the very first enumerator and no
7904 initializer has been given. It will be initialized to zero. */
7905 mpz_set_si (result->value.integer, 0);
7908 return result;
7912 /* Match a variable name with an optional initializer. When this
7913 subroutine is called, a variable is expected to be parsed next.
7914 Depending on what is happening at the moment, updates either the
7915 symbol table or the current interface. */
7917 static match
7918 enumerator_decl (void)
7920 char name[GFC_MAX_SYMBOL_LEN + 1];
7921 gfc_expr *initializer;
7922 gfc_array_spec *as = NULL;
7923 gfc_symbol *sym;
7924 locus var_locus;
7925 match m;
7926 bool t;
7927 locus old_locus;
7929 initializer = NULL;
7930 old_locus = gfc_current_locus;
7932 /* When we get here, we've just matched a list of attributes and
7933 maybe a type and a double colon. The next thing we expect to see
7934 is the name of the symbol. */
7935 m = gfc_match_name (name);
7936 if (m != MATCH_YES)
7937 goto cleanup;
7939 var_locus = gfc_current_locus;
7941 /* OK, we've successfully matched the declaration. Now put the
7942 symbol in the current namespace. If we fail to create the symbol,
7943 bail out. */
7944 if (!build_sym (name, NULL, false, &as, &var_locus))
7946 m = MATCH_ERROR;
7947 goto cleanup;
7950 /* The double colon must be present in order to have initializers.
7951 Otherwise the statement is ambiguous with an assignment statement. */
7952 if (colon_seen)
7954 if (gfc_match_char ('=') == MATCH_YES)
7956 m = gfc_match_init_expr (&initializer);
7957 if (m == MATCH_NO)
7959 gfc_error ("Expected an initialization expression at %C");
7960 m = MATCH_ERROR;
7963 if (m != MATCH_YES)
7964 goto cleanup;
7968 /* If we do not have an initializer, the initialization value of the
7969 previous enumerator (stored in last_initializer) is incremented
7970 by 1 and is used to initialize the current enumerator. */
7971 if (initializer == NULL)
7972 initializer = enum_initializer (last_initializer, old_locus);
7974 if (initializer == NULL || initializer->ts.type != BT_INTEGER)
7976 gfc_error ("ENUMERATOR %L not initialized with integer expression",
7977 &var_locus);
7978 m = MATCH_ERROR;
7979 goto cleanup;
7982 /* Store this current initializer, for the next enumerator variable
7983 to be parsed. add_init_expr_to_sym() zeros initializer, so we
7984 use last_initializer below. */
7985 last_initializer = initializer;
7986 t = add_init_expr_to_sym (name, &initializer, &var_locus);
7988 /* Maintain enumerator history. */
7989 gfc_find_symbol (name, NULL, 0, &sym);
7990 create_enum_history (sym, last_initializer);
7992 return (t) ? MATCH_YES : MATCH_ERROR;
7994 cleanup:
7995 /* Free stuff up and return. */
7996 gfc_free_expr (initializer);
7998 return m;
8002 /* Match the enumerator definition statement. */
8004 match
8005 gfc_match_enumerator_def (void)
8007 match m;
8008 bool t;
8010 gfc_clear_ts (&current_ts);
8012 m = gfc_match (" enumerator");
8013 if (m != MATCH_YES)
8014 return m;
8016 m = gfc_match (" :: ");
8017 if (m == MATCH_ERROR)
8018 return m;
8020 colon_seen = (m == MATCH_YES);
8022 if (gfc_current_state () != COMP_ENUM)
8024 gfc_error ("ENUM definition statement expected before %C");
8025 gfc_free_enum_history ();
8026 return MATCH_ERROR;
8029 (&current_ts)->type = BT_INTEGER;
8030 (&current_ts)->kind = gfc_c_int_kind;
8032 gfc_clear_attr (&current_attr);
8033 t = gfc_add_flavor (&current_attr, FL_PARAMETER, NULL, NULL);
8034 if (!t)
8036 m = MATCH_ERROR;
8037 goto cleanup;
8040 for (;;)
8042 m = enumerator_decl ();
8043 if (m == MATCH_ERROR)
8045 gfc_free_enum_history ();
8046 goto cleanup;
8048 if (m == MATCH_NO)
8049 break;
8051 if (gfc_match_eos () == MATCH_YES)
8052 goto cleanup;
8053 if (gfc_match_char (',') != MATCH_YES)
8054 break;
8057 if (gfc_current_state () == COMP_ENUM)
8059 gfc_free_enum_history ();
8060 gfc_error ("Syntax error in ENUMERATOR definition at %C");
8061 m = MATCH_ERROR;
8064 cleanup:
8065 gfc_free_array_spec (current_as);
8066 current_as = NULL;
8067 return m;
8072 /* Match binding attributes. */
8074 static match
8075 match_binding_attributes (gfc_typebound_proc* ba, bool generic, bool ppc)
8077 bool found_passing = false;
8078 bool seen_ptr = false;
8079 match m = MATCH_YES;
8081 /* Initialize to defaults. Do so even before the MATCH_NO check so that in
8082 this case the defaults are in there. */
8083 ba->access = ACCESS_UNKNOWN;
8084 ba->pass_arg = NULL;
8085 ba->pass_arg_num = 0;
8086 ba->nopass = 0;
8087 ba->non_overridable = 0;
8088 ba->deferred = 0;
8089 ba->ppc = ppc;
8091 /* If we find a comma, we believe there are binding attributes. */
8092 m = gfc_match_char (',');
8093 if (m == MATCH_NO)
8094 goto done;
8098 /* Access specifier. */
8100 m = gfc_match (" public");
8101 if (m == MATCH_ERROR)
8102 goto error;
8103 if (m == MATCH_YES)
8105 if (ba->access != ACCESS_UNKNOWN)
8107 gfc_error ("Duplicate access-specifier at %C");
8108 goto error;
8111 ba->access = ACCESS_PUBLIC;
8112 continue;
8115 m = gfc_match (" private");
8116 if (m == MATCH_ERROR)
8117 goto error;
8118 if (m == MATCH_YES)
8120 if (ba->access != ACCESS_UNKNOWN)
8122 gfc_error ("Duplicate access-specifier at %C");
8123 goto error;
8126 ba->access = ACCESS_PRIVATE;
8127 continue;
8130 /* If inside GENERIC, the following is not allowed. */
8131 if (!generic)
8134 /* NOPASS flag. */
8135 m = gfc_match (" nopass");
8136 if (m == MATCH_ERROR)
8137 goto error;
8138 if (m == MATCH_YES)
8140 if (found_passing)
8142 gfc_error ("Binding attributes already specify passing,"
8143 " illegal NOPASS at %C");
8144 goto error;
8147 found_passing = true;
8148 ba->nopass = 1;
8149 continue;
8152 /* PASS possibly including argument. */
8153 m = gfc_match (" pass");
8154 if (m == MATCH_ERROR)
8155 goto error;
8156 if (m == MATCH_YES)
8158 char arg[GFC_MAX_SYMBOL_LEN + 1];
8160 if (found_passing)
8162 gfc_error ("Binding attributes already specify passing,"
8163 " illegal PASS at %C");
8164 goto error;
8167 m = gfc_match (" ( %n )", arg);
8168 if (m == MATCH_ERROR)
8169 goto error;
8170 if (m == MATCH_YES)
8171 ba->pass_arg = gfc_get_string (arg);
8172 gcc_assert ((m == MATCH_YES) == (ba->pass_arg != NULL));
8174 found_passing = true;
8175 ba->nopass = 0;
8176 continue;
8179 if (ppc)
8181 /* POINTER flag. */
8182 m = gfc_match (" pointer");
8183 if (m == MATCH_ERROR)
8184 goto error;
8185 if (m == MATCH_YES)
8187 if (seen_ptr)
8189 gfc_error ("Duplicate POINTER attribute at %C");
8190 goto error;
8193 seen_ptr = true;
8194 continue;
8197 else
8199 /* NON_OVERRIDABLE flag. */
8200 m = gfc_match (" non_overridable");
8201 if (m == MATCH_ERROR)
8202 goto error;
8203 if (m == MATCH_YES)
8205 if (ba->non_overridable)
8207 gfc_error ("Duplicate NON_OVERRIDABLE at %C");
8208 goto error;
8211 ba->non_overridable = 1;
8212 continue;
8215 /* DEFERRED flag. */
8216 m = gfc_match (" deferred");
8217 if (m == MATCH_ERROR)
8218 goto error;
8219 if (m == MATCH_YES)
8221 if (ba->deferred)
8223 gfc_error ("Duplicate DEFERRED at %C");
8224 goto error;
8227 ba->deferred = 1;
8228 continue;
8234 /* Nothing matching found. */
8235 if (generic)
8236 gfc_error ("Expected access-specifier at %C");
8237 else
8238 gfc_error ("Expected binding attribute at %C");
8239 goto error;
8241 while (gfc_match_char (',') == MATCH_YES);
8243 /* NON_OVERRIDABLE and DEFERRED exclude themselves. */
8244 if (ba->non_overridable && ba->deferred)
8246 gfc_error ("NON_OVERRIDABLE and DEFERRED can't both appear at %C");
8247 goto error;
8250 m = MATCH_YES;
8252 done:
8253 if (ba->access == ACCESS_UNKNOWN)
8254 ba->access = gfc_typebound_default_access;
8256 if (ppc && !seen_ptr)
8258 gfc_error ("POINTER attribute is required for procedure pointer component"
8259 " at %C");
8260 goto error;
8263 return m;
8265 error:
8266 return MATCH_ERROR;
8270 /* Match a PROCEDURE specific binding inside a derived type. */
8272 static match
8273 match_procedure_in_type (void)
8275 char name[GFC_MAX_SYMBOL_LEN + 1];
8276 char target_buf[GFC_MAX_SYMBOL_LEN + 1];
8277 char* target = NULL, *ifc = NULL;
8278 gfc_typebound_proc tb;
8279 bool seen_colons;
8280 bool seen_attrs;
8281 match m;
8282 gfc_symtree* stree;
8283 gfc_namespace* ns;
8284 gfc_symbol* block;
8285 int num;
8287 /* Check current state. */
8288 gcc_assert (gfc_state_stack->state == COMP_DERIVED_CONTAINS);
8289 block = gfc_state_stack->previous->sym;
8290 gcc_assert (block);
8292 /* Try to match PROCEDURE(interface). */
8293 if (gfc_match (" (") == MATCH_YES)
8295 m = gfc_match_name (target_buf);
8296 if (m == MATCH_ERROR)
8297 return m;
8298 if (m != MATCH_YES)
8300 gfc_error ("Interface-name expected after %<(%> at %C");
8301 return MATCH_ERROR;
8304 if (gfc_match (" )") != MATCH_YES)
8306 gfc_error ("%<)%> expected at %C");
8307 return MATCH_ERROR;
8310 ifc = target_buf;
8313 /* Construct the data structure. */
8314 memset (&tb, 0, sizeof (tb));
8315 tb.where = gfc_current_locus;
8317 /* Match binding attributes. */
8318 m = match_binding_attributes (&tb, false, false);
8319 if (m == MATCH_ERROR)
8320 return m;
8321 seen_attrs = (m == MATCH_YES);
8323 /* Check that attribute DEFERRED is given if an interface is specified. */
8324 if (tb.deferred && !ifc)
8326 gfc_error ("Interface must be specified for DEFERRED binding at %C");
8327 return MATCH_ERROR;
8329 if (ifc && !tb.deferred)
8331 gfc_error ("PROCEDURE(interface) at %C should be declared DEFERRED");
8332 return MATCH_ERROR;
8335 /* Match the colons. */
8336 m = gfc_match (" ::");
8337 if (m == MATCH_ERROR)
8338 return m;
8339 seen_colons = (m == MATCH_YES);
8340 if (seen_attrs && !seen_colons)
8342 gfc_error ("Expected %<::%> after binding-attributes at %C");
8343 return MATCH_ERROR;
8346 /* Match the binding names. */
8347 for(num=1;;num++)
8349 m = gfc_match_name (name);
8350 if (m == MATCH_ERROR)
8351 return m;
8352 if (m == MATCH_NO)
8354 gfc_error ("Expected binding name at %C");
8355 return MATCH_ERROR;
8358 if (num>1 && !gfc_notify_std (GFC_STD_F2008, "PROCEDURE list at %C"))
8359 return MATCH_ERROR;
8361 /* Try to match the '=> target', if it's there. */
8362 target = ifc;
8363 m = gfc_match (" =>");
8364 if (m == MATCH_ERROR)
8365 return m;
8366 if (m == MATCH_YES)
8368 if (tb.deferred)
8370 gfc_error ("%<=> target%> is invalid for DEFERRED binding at %C");
8371 return MATCH_ERROR;
8374 if (!seen_colons)
8376 gfc_error ("%<::%> needed in PROCEDURE binding with explicit target"
8377 " at %C");
8378 return MATCH_ERROR;
8381 m = gfc_match_name (target_buf);
8382 if (m == MATCH_ERROR)
8383 return m;
8384 if (m == MATCH_NO)
8386 gfc_error ("Expected binding target after %<=>%> at %C");
8387 return MATCH_ERROR;
8389 target = target_buf;
8392 /* If no target was found, it has the same name as the binding. */
8393 if (!target)
8394 target = name;
8396 /* Get the namespace to insert the symbols into. */
8397 ns = block->f2k_derived;
8398 gcc_assert (ns);
8400 /* If the binding is DEFERRED, check that the containing type is ABSTRACT. */
8401 if (tb.deferred && !block->attr.abstract)
8403 gfc_error ("Type %qs containing DEFERRED binding at %C "
8404 "is not ABSTRACT", block->name);
8405 return MATCH_ERROR;
8408 /* See if we already have a binding with this name in the symtree which
8409 would be an error. If a GENERIC already targeted this binding, it may
8410 be already there but then typebound is still NULL. */
8411 stree = gfc_find_symtree (ns->tb_sym_root, name);
8412 if (stree && stree->n.tb)
8414 gfc_error ("There is already a procedure with binding name %qs for "
8415 "the derived type %qs at %C", name, block->name);
8416 return MATCH_ERROR;
8419 /* Insert it and set attributes. */
8421 if (!stree)
8423 stree = gfc_new_symtree (&ns->tb_sym_root, name);
8424 gcc_assert (stree);
8426 stree->n.tb = gfc_get_typebound_proc (&tb);
8428 if (gfc_get_sym_tree (target, gfc_current_ns, &stree->n.tb->u.specific,
8429 false))
8430 return MATCH_ERROR;
8431 gfc_set_sym_referenced (stree->n.tb->u.specific->n.sym);
8433 if (gfc_match_eos () == MATCH_YES)
8434 return MATCH_YES;
8435 if (gfc_match_char (',') != MATCH_YES)
8436 goto syntax;
8439 syntax:
8440 gfc_error ("Syntax error in PROCEDURE statement at %C");
8441 return MATCH_ERROR;
8445 /* Match a GENERIC procedure binding inside a derived type. */
8447 match
8448 gfc_match_generic (void)
8450 char name[GFC_MAX_SYMBOL_LEN + 1];
8451 char bind_name[GFC_MAX_SYMBOL_LEN + 16]; /* Allow space for OPERATOR(...). */
8452 gfc_symbol* block;
8453 gfc_typebound_proc tbattr; /* Used for match_binding_attributes. */
8454 gfc_typebound_proc* tb;
8455 gfc_namespace* ns;
8456 interface_type op_type;
8457 gfc_intrinsic_op op;
8458 match m;
8460 /* Check current state. */
8461 if (gfc_current_state () == COMP_DERIVED)
8463 gfc_error ("GENERIC at %C must be inside a derived-type CONTAINS");
8464 return MATCH_ERROR;
8466 if (gfc_current_state () != COMP_DERIVED_CONTAINS)
8467 return MATCH_NO;
8468 block = gfc_state_stack->previous->sym;
8469 ns = block->f2k_derived;
8470 gcc_assert (block && ns);
8472 memset (&tbattr, 0, sizeof (tbattr));
8473 tbattr.where = gfc_current_locus;
8475 /* See if we get an access-specifier. */
8476 m = match_binding_attributes (&tbattr, true, false);
8477 if (m == MATCH_ERROR)
8478 goto error;
8480 /* Now the colons, those are required. */
8481 if (gfc_match (" ::") != MATCH_YES)
8483 gfc_error ("Expected %<::%> at %C");
8484 goto error;
8487 /* Match the binding name; depending on type (operator / generic) format
8488 it for future error messages into bind_name. */
8490 m = gfc_match_generic_spec (&op_type, name, &op);
8491 if (m == MATCH_ERROR)
8492 return MATCH_ERROR;
8493 if (m == MATCH_NO)
8495 gfc_error ("Expected generic name or operator descriptor at %C");
8496 goto error;
8499 switch (op_type)
8501 case INTERFACE_GENERIC:
8502 snprintf (bind_name, sizeof (bind_name), "%s", name);
8503 break;
8505 case INTERFACE_USER_OP:
8506 snprintf (bind_name, sizeof (bind_name), "OPERATOR(.%s.)", name);
8507 break;
8509 case INTERFACE_INTRINSIC_OP:
8510 snprintf (bind_name, sizeof (bind_name), "OPERATOR(%s)",
8511 gfc_op2string (op));
8512 break;
8514 default:
8515 gcc_unreachable ();
8518 /* Match the required =>. */
8519 if (gfc_match (" =>") != MATCH_YES)
8521 gfc_error ("Expected %<=>%> at %C");
8522 goto error;
8525 /* Try to find existing GENERIC binding with this name / for this operator;
8526 if there is something, check that it is another GENERIC and then extend
8527 it rather than building a new node. Otherwise, create it and put it
8528 at the right position. */
8530 switch (op_type)
8532 case INTERFACE_USER_OP:
8533 case INTERFACE_GENERIC:
8535 const bool is_op = (op_type == INTERFACE_USER_OP);
8536 gfc_symtree* st;
8538 st = gfc_find_symtree (is_op ? ns->tb_uop_root : ns->tb_sym_root, name);
8539 if (st)
8541 tb = st->n.tb;
8542 gcc_assert (tb);
8544 else
8545 tb = NULL;
8547 break;
8550 case INTERFACE_INTRINSIC_OP:
8551 tb = ns->tb_op[op];
8552 break;
8554 default:
8555 gcc_unreachable ();
8558 if (tb)
8560 if (!tb->is_generic)
8562 gcc_assert (op_type == INTERFACE_GENERIC);
8563 gfc_error ("There's already a non-generic procedure with binding name"
8564 " %qs for the derived type %qs at %C",
8565 bind_name, block->name);
8566 goto error;
8569 if (tb->access != tbattr.access)
8571 gfc_error ("Binding at %C must have the same access as already"
8572 " defined binding %qs", bind_name);
8573 goto error;
8576 else
8578 tb = gfc_get_typebound_proc (NULL);
8579 tb->where = gfc_current_locus;
8580 tb->access = tbattr.access;
8581 tb->is_generic = 1;
8582 tb->u.generic = NULL;
8584 switch (op_type)
8586 case INTERFACE_GENERIC:
8587 case INTERFACE_USER_OP:
8589 const bool is_op = (op_type == INTERFACE_USER_OP);
8590 gfc_symtree* st;
8592 st = gfc_new_symtree (is_op ? &ns->tb_uop_root : &ns->tb_sym_root,
8593 name);
8594 gcc_assert (st);
8595 st->n.tb = tb;
8597 break;
8600 case INTERFACE_INTRINSIC_OP:
8601 ns->tb_op[op] = tb;
8602 break;
8604 default:
8605 gcc_unreachable ();
8609 /* Now, match all following names as specific targets. */
8612 gfc_symtree* target_st;
8613 gfc_tbp_generic* target;
8615 m = gfc_match_name (name);
8616 if (m == MATCH_ERROR)
8617 goto error;
8618 if (m == MATCH_NO)
8620 gfc_error ("Expected specific binding name at %C");
8621 goto error;
8624 target_st = gfc_get_tbp_symtree (&ns->tb_sym_root, name);
8626 /* See if this is a duplicate specification. */
8627 for (target = tb->u.generic; target; target = target->next)
8628 if (target_st == target->specific_st)
8630 gfc_error ("%qs already defined as specific binding for the"
8631 " generic %qs at %C", name, bind_name);
8632 goto error;
8635 target = gfc_get_tbp_generic ();
8636 target->specific_st = target_st;
8637 target->specific = NULL;
8638 target->next = tb->u.generic;
8639 target->is_operator = ((op_type == INTERFACE_USER_OP)
8640 || (op_type == INTERFACE_INTRINSIC_OP));
8641 tb->u.generic = target;
8643 while (gfc_match (" ,") == MATCH_YES);
8645 /* Here should be the end. */
8646 if (gfc_match_eos () != MATCH_YES)
8648 gfc_error ("Junk after GENERIC binding at %C");
8649 goto error;
8652 return MATCH_YES;
8654 error:
8655 return MATCH_ERROR;
8659 /* Match a FINAL declaration inside a derived type. */
8661 match
8662 gfc_match_final_decl (void)
8664 char name[GFC_MAX_SYMBOL_LEN + 1];
8665 gfc_symbol* sym;
8666 match m;
8667 gfc_namespace* module_ns;
8668 bool first, last;
8669 gfc_symbol* block;
8671 if (gfc_current_form == FORM_FREE)
8673 char c = gfc_peek_ascii_char ();
8674 if (!gfc_is_whitespace (c) && c != ':')
8675 return MATCH_NO;
8678 if (gfc_state_stack->state != COMP_DERIVED_CONTAINS)
8680 if (gfc_current_form == FORM_FIXED)
8681 return MATCH_NO;
8683 gfc_error ("FINAL declaration at %C must be inside a derived type "
8684 "CONTAINS section");
8685 return MATCH_ERROR;
8688 block = gfc_state_stack->previous->sym;
8689 gcc_assert (block);
8691 if (!gfc_state_stack->previous || !gfc_state_stack->previous->previous
8692 || gfc_state_stack->previous->previous->state != COMP_MODULE)
8694 gfc_error ("Derived type declaration with FINAL at %C must be in the"
8695 " specification part of a MODULE");
8696 return MATCH_ERROR;
8699 module_ns = gfc_current_ns;
8700 gcc_assert (module_ns);
8701 gcc_assert (module_ns->proc_name->attr.flavor == FL_MODULE);
8703 /* Match optional ::, don't care about MATCH_YES or MATCH_NO. */
8704 if (gfc_match (" ::") == MATCH_ERROR)
8705 return MATCH_ERROR;
8707 /* Match the sequence of procedure names. */
8708 first = true;
8709 last = false;
8712 gfc_finalizer* f;
8714 if (first && gfc_match_eos () == MATCH_YES)
8716 gfc_error ("Empty FINAL at %C");
8717 return MATCH_ERROR;
8720 m = gfc_match_name (name);
8721 if (m == MATCH_NO)
8723 gfc_error ("Expected module procedure name at %C");
8724 return MATCH_ERROR;
8726 else if (m != MATCH_YES)
8727 return MATCH_ERROR;
8729 if (gfc_match_eos () == MATCH_YES)
8730 last = true;
8731 if (!last && gfc_match_char (',') != MATCH_YES)
8733 gfc_error ("Expected %<,%> at %C");
8734 return MATCH_ERROR;
8737 if (gfc_get_symbol (name, module_ns, &sym))
8739 gfc_error ("Unknown procedure name %qs at %C", name);
8740 return MATCH_ERROR;
8743 /* Mark the symbol as module procedure. */
8744 if (sym->attr.proc != PROC_MODULE
8745 && !gfc_add_procedure (&sym->attr, PROC_MODULE, sym->name, NULL))
8746 return MATCH_ERROR;
8748 /* Check if we already have this symbol in the list, this is an error. */
8749 for (f = block->f2k_derived->finalizers; f; f = f->next)
8750 if (f->proc_sym == sym)
8752 gfc_error ("%qs at %C is already defined as FINAL procedure!",
8753 name);
8754 return MATCH_ERROR;
8757 /* Add this symbol to the list of finalizers. */
8758 gcc_assert (block->f2k_derived);
8759 ++sym->refs;
8760 f = XCNEW (gfc_finalizer);
8761 f->proc_sym = sym;
8762 f->proc_tree = NULL;
8763 f->where = gfc_current_locus;
8764 f->next = block->f2k_derived->finalizers;
8765 block->f2k_derived->finalizers = f;
8767 first = false;
8769 while (!last);
8771 return MATCH_YES;
8775 const ext_attr_t ext_attr_list[] = {
8776 { "dllimport", EXT_ATTR_DLLIMPORT, "dllimport" },
8777 { "dllexport", EXT_ATTR_DLLEXPORT, "dllexport" },
8778 { "cdecl", EXT_ATTR_CDECL, "cdecl" },
8779 { "stdcall", EXT_ATTR_STDCALL, "stdcall" },
8780 { "fastcall", EXT_ATTR_FASTCALL, "fastcall" },
8781 { "no_arg_check", EXT_ATTR_NO_ARG_CHECK, NULL },
8782 { NULL, EXT_ATTR_LAST, NULL }
8785 /* Match a !GCC$ ATTRIBUTES statement of the form:
8786 !GCC$ ATTRIBUTES attribute-list :: var-name [, var-name] ...
8787 When we come here, we have already matched the !GCC$ ATTRIBUTES string.
8789 TODO: We should support all GCC attributes using the same syntax for
8790 the attribute list, i.e. the list in C
8791 __attributes(( attribute-list ))
8792 matches then
8793 !GCC$ ATTRIBUTES attribute-list ::
8794 Cf. c-parser.c's c_parser_attributes; the data can then directly be
8795 saved into a TREE.
8797 As there is absolutely no risk of confusion, we should never return
8798 MATCH_NO. */
8799 match
8800 gfc_match_gcc_attributes (void)
8802 symbol_attribute attr;
8803 char name[GFC_MAX_SYMBOL_LEN + 1];
8804 unsigned id;
8805 gfc_symbol *sym;
8806 match m;
8808 gfc_clear_attr (&attr);
8809 for(;;)
8811 char ch;
8813 if (gfc_match_name (name) != MATCH_YES)
8814 return MATCH_ERROR;
8816 for (id = 0; id < EXT_ATTR_LAST; id++)
8817 if (strcmp (name, ext_attr_list[id].name) == 0)
8818 break;
8820 if (id == EXT_ATTR_LAST)
8822 gfc_error ("Unknown attribute in !GCC$ ATTRIBUTES statement at %C");
8823 return MATCH_ERROR;
8826 if (!gfc_add_ext_attribute (&attr, (ext_attr_id_t)id, &gfc_current_locus))
8827 return MATCH_ERROR;
8829 gfc_gobble_whitespace ();
8830 ch = gfc_next_ascii_char ();
8831 if (ch == ':')
8833 /* This is the successful exit condition for the loop. */
8834 if (gfc_next_ascii_char () == ':')
8835 break;
8838 if (ch == ',')
8839 continue;
8841 goto syntax;
8844 if (gfc_match_eos () == MATCH_YES)
8845 goto syntax;
8847 for(;;)
8849 m = gfc_match_name (name);
8850 if (m != MATCH_YES)
8851 return m;
8853 if (find_special (name, &sym, true))
8854 return MATCH_ERROR;
8856 sym->attr.ext_attr |= attr.ext_attr;
8858 if (gfc_match_eos () == MATCH_YES)
8859 break;
8861 if (gfc_match_char (',') != MATCH_YES)
8862 goto syntax;
8865 return MATCH_YES;
8867 syntax:
8868 gfc_error ("Syntax error in !GCC$ ATTRIBUTES statement at %C");
8869 return MATCH_ERROR;