re PR testsuite/40567 (Revision 149002 caused many failures)
[official-gcc.git] / gcc / fortran / decl.c
blob179d1e2e61af8d62808f5b305359d126361ff2ad
1 /* Declaration statement matcher
2 Copyright (C) 2002, 2004, 2005, 2006, 2007, 2008, 2009
3 Free Software Foundation, Inc.
4 Contributed by Andy Vaught
6 This file is part of GCC.
8 GCC is free software; you can redistribute it and/or modify it under
9 the terms of the GNU General Public License as published by the Free
10 Software Foundation; either version 3, or (at your option) any later
11 version.
13 GCC is distributed in the hope that it will be useful, but WITHOUT ANY
14 WARRANTY; without even the implied warranty of MERCHANTABILITY or
15 FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License
16 for more details.
18 You should have received a copy of the GNU General Public License
19 along with GCC; see the file COPYING3. If not see
20 <http://www.gnu.org/licenses/>. */
22 #include "config.h"
23 #include "system.h"
24 #include "gfortran.h"
25 #include "match.h"
26 #include "parse.h"
27 #include "flags.h"
30 /* Macros to access allocate memory for gfc_data_variable,
31 gfc_data_value and gfc_data. */
32 #define gfc_get_data_variable() XCNEW (gfc_data_variable)
33 #define gfc_get_data_value() XCNEW (gfc_data_value)
34 #define gfc_get_data() XCNEW (gfc_data)
37 /* This flag is set if an old-style length selector is matched
38 during a type-declaration statement. */
40 static int old_char_selector;
42 /* When variables acquire types and attributes from a declaration
43 statement, they get them from the following static variables. The
44 first part of a declaration sets these variables and the second
45 part copies these into symbol structures. */
47 static gfc_typespec current_ts;
49 static symbol_attribute current_attr;
50 static gfc_array_spec *current_as;
51 static int colon_seen;
53 /* The current binding label (if any). */
54 static char curr_binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
55 /* Need to know how many identifiers are on the current data declaration
56 line in case we're given the BIND(C) attribute with a NAME= specifier. */
57 static int num_idents_on_line;
58 /* Need to know if a NAME= specifier was found during gfc_match_bind_c so we
59 can supply a name if the curr_binding_label is nil and NAME= was not. */
60 static int has_name_equals = 0;
62 /* Initializer of the previous enumerator. */
64 static gfc_expr *last_initializer;
66 /* History of all the enumerators is maintained, so that
67 kind values of all the enumerators could be updated depending
68 upon the maximum initialized value. */
70 typedef struct enumerator_history
72 gfc_symbol *sym;
73 gfc_expr *initializer;
74 struct enumerator_history *next;
76 enumerator_history;
78 /* Header of enum history chain. */
80 static enumerator_history *enum_history = NULL;
82 /* Pointer of enum history node containing largest initializer. */
84 static enumerator_history *max_enum = NULL;
86 /* gfc_new_block points to the symbol of a newly matched block. */
88 gfc_symbol *gfc_new_block;
90 bool gfc_matching_function;
93 /********************* DATA statement subroutines *********************/
95 static bool in_match_data = false;
97 bool
98 gfc_in_match_data (void)
100 return in_match_data;
103 static void
104 set_in_match_data (bool set_value)
106 in_match_data = set_value;
109 /* Free a gfc_data_variable structure and everything beneath it. */
111 static void
112 free_variable (gfc_data_variable *p)
114 gfc_data_variable *q;
116 for (; p; p = q)
118 q = p->next;
119 gfc_free_expr (p->expr);
120 gfc_free_iterator (&p->iter, 0);
121 free_variable (p->list);
122 gfc_free (p);
127 /* Free a gfc_data_value structure and everything beneath it. */
129 static void
130 free_value (gfc_data_value *p)
132 gfc_data_value *q;
134 for (; p; p = q)
136 q = p->next;
137 gfc_free_expr (p->expr);
138 gfc_free (p);
143 /* Free a list of gfc_data structures. */
145 void
146 gfc_free_data (gfc_data *p)
148 gfc_data *q;
150 for (; p; p = q)
152 q = p->next;
153 free_variable (p->var);
154 free_value (p->value);
155 gfc_free (p);
160 /* Free all data in a namespace. */
162 static void
163 gfc_free_data_all (gfc_namespace *ns)
165 gfc_data *d;
167 for (;ns->data;)
169 d = ns->data->next;
170 gfc_free (ns->data);
171 ns->data = d;
176 static match var_element (gfc_data_variable *);
178 /* Match a list of variables terminated by an iterator and a right
179 parenthesis. */
181 static match
182 var_list (gfc_data_variable *parent)
184 gfc_data_variable *tail, var;
185 match m;
187 m = var_element (&var);
188 if (m == MATCH_ERROR)
189 return MATCH_ERROR;
190 if (m == MATCH_NO)
191 goto syntax;
193 tail = gfc_get_data_variable ();
194 *tail = var;
196 parent->list = tail;
198 for (;;)
200 if (gfc_match_char (',') != MATCH_YES)
201 goto syntax;
203 m = gfc_match_iterator (&parent->iter, 1);
204 if (m == MATCH_YES)
205 break;
206 if (m == MATCH_ERROR)
207 return MATCH_ERROR;
209 m = var_element (&var);
210 if (m == MATCH_ERROR)
211 return MATCH_ERROR;
212 if (m == MATCH_NO)
213 goto syntax;
215 tail->next = gfc_get_data_variable ();
216 tail = tail->next;
218 *tail = var;
221 if (gfc_match_char (')') != MATCH_YES)
222 goto syntax;
223 return MATCH_YES;
225 syntax:
226 gfc_syntax_error (ST_DATA);
227 return MATCH_ERROR;
231 /* Match a single element in a data variable list, which can be a
232 variable-iterator list. */
234 static match
235 var_element (gfc_data_variable *new_var)
237 match m;
238 gfc_symbol *sym;
240 memset (new_var, 0, sizeof (gfc_data_variable));
242 if (gfc_match_char ('(') == MATCH_YES)
243 return var_list (new_var);
245 m = gfc_match_variable (&new_var->expr, 0);
246 if (m != MATCH_YES)
247 return m;
249 sym = new_var->expr->symtree->n.sym;
251 /* Symbol should already have an associated type. */
252 if (gfc_check_symbol_typed (sym, gfc_current_ns,
253 false, gfc_current_locus) == FAILURE)
254 return MATCH_ERROR;
256 if (!sym->attr.function && gfc_current_ns->parent
257 && gfc_current_ns->parent == sym->ns)
259 gfc_error ("Host associated variable '%s' may not be in the DATA "
260 "statement at %C", sym->name);
261 return MATCH_ERROR;
264 if (gfc_current_state () != COMP_BLOCK_DATA
265 && sym->attr.in_common
266 && gfc_notify_std (GFC_STD_GNU, "Extension: initialization of "
267 "common block variable '%s' in DATA statement at %C",
268 sym->name) == FAILURE)
269 return MATCH_ERROR;
271 if (gfc_add_data (&sym->attr, sym->name, &new_var->expr->where) == FAILURE)
272 return MATCH_ERROR;
274 return MATCH_YES;
278 /* Match the top-level list of data variables. */
280 static match
281 top_var_list (gfc_data *d)
283 gfc_data_variable var, *tail, *new_var;
284 match m;
286 tail = NULL;
288 for (;;)
290 m = var_element (&var);
291 if (m == MATCH_NO)
292 goto syntax;
293 if (m == MATCH_ERROR)
294 return MATCH_ERROR;
296 new_var = gfc_get_data_variable ();
297 *new_var = var;
299 if (tail == NULL)
300 d->var = new_var;
301 else
302 tail->next = new_var;
304 tail = new_var;
306 if (gfc_match_char ('/') == MATCH_YES)
307 break;
308 if (gfc_match_char (',') != MATCH_YES)
309 goto syntax;
312 return MATCH_YES;
314 syntax:
315 gfc_syntax_error (ST_DATA);
316 gfc_free_data_all (gfc_current_ns);
317 return MATCH_ERROR;
321 static match
322 match_data_constant (gfc_expr **result)
324 char name[GFC_MAX_SYMBOL_LEN + 1];
325 gfc_symbol *sym;
326 gfc_expr *expr;
327 match m;
328 locus old_loc;
330 m = gfc_match_literal_constant (&expr, 1);
331 if (m == MATCH_YES)
333 *result = expr;
334 return MATCH_YES;
337 if (m == MATCH_ERROR)
338 return MATCH_ERROR;
340 m = gfc_match_null (result);
341 if (m != MATCH_NO)
342 return m;
344 old_loc = gfc_current_locus;
346 /* Should this be a structure component, try to match it
347 before matching a name. */
348 m = gfc_match_rvalue (result);
349 if (m == MATCH_ERROR)
350 return m;
352 if (m == MATCH_YES && (*result)->expr_type == EXPR_STRUCTURE)
354 if (gfc_simplify_expr (*result, 0) == FAILURE)
355 m = MATCH_ERROR;
356 return m;
359 gfc_current_locus = old_loc;
361 m = gfc_match_name (name);
362 if (m != MATCH_YES)
363 return m;
365 if (gfc_find_symbol (name, NULL, 1, &sym))
366 return MATCH_ERROR;
368 if (sym == NULL
369 || (sym->attr.flavor != FL_PARAMETER && sym->attr.flavor != FL_DERIVED))
371 gfc_error ("Symbol '%s' must be a PARAMETER in DATA statement at %C",
372 name);
373 return MATCH_ERROR;
375 else if (sym->attr.flavor == FL_DERIVED)
376 return gfc_match_structure_constructor (sym, result, false);
378 /* Check to see if the value is an initialization array expression. */
379 if (sym->value->expr_type == EXPR_ARRAY)
381 gfc_current_locus = old_loc;
383 m = gfc_match_init_expr (result);
384 if (m == MATCH_ERROR)
385 return m;
387 if (m == MATCH_YES)
389 if (gfc_simplify_expr (*result, 0) == FAILURE)
390 m = MATCH_ERROR;
392 if ((*result)->expr_type == EXPR_CONSTANT)
393 return m;
394 else
396 gfc_error ("Invalid initializer %s in Data statement at %C", name);
397 return MATCH_ERROR;
402 *result = gfc_copy_expr (sym->value);
403 return MATCH_YES;
407 /* Match a list of values in a DATA statement. The leading '/' has
408 already been seen at this point. */
410 static match
411 top_val_list (gfc_data *data)
413 gfc_data_value *new_val, *tail;
414 gfc_expr *expr;
415 match m;
417 tail = NULL;
419 for (;;)
421 m = match_data_constant (&expr);
422 if (m == MATCH_NO)
423 goto syntax;
424 if (m == MATCH_ERROR)
425 return MATCH_ERROR;
427 new_val = gfc_get_data_value ();
428 mpz_init (new_val->repeat);
430 if (tail == NULL)
431 data->value = new_val;
432 else
433 tail->next = new_val;
435 tail = new_val;
437 if (expr->ts.type != BT_INTEGER || gfc_match_char ('*') != MATCH_YES)
439 tail->expr = expr;
440 mpz_set_ui (tail->repeat, 1);
442 else
444 if (expr->ts.type == BT_INTEGER)
445 mpz_set (tail->repeat, expr->value.integer);
446 gfc_free_expr (expr);
448 m = match_data_constant (&tail->expr);
449 if (m == MATCH_NO)
450 goto syntax;
451 if (m == MATCH_ERROR)
452 return MATCH_ERROR;
455 if (gfc_match_char ('/') == MATCH_YES)
456 break;
457 if (gfc_match_char (',') == MATCH_NO)
458 goto syntax;
461 return MATCH_YES;
463 syntax:
464 gfc_syntax_error (ST_DATA);
465 gfc_free_data_all (gfc_current_ns);
466 return MATCH_ERROR;
470 /* Matches an old style initialization. */
472 static match
473 match_old_style_init (const char *name)
475 match m;
476 gfc_symtree *st;
477 gfc_symbol *sym;
478 gfc_data *newdata;
480 /* Set up data structure to hold initializers. */
481 gfc_find_sym_tree (name, NULL, 0, &st);
482 sym = st->n.sym;
484 newdata = gfc_get_data ();
485 newdata->var = gfc_get_data_variable ();
486 newdata->var->expr = gfc_get_variable_expr (st);
487 newdata->where = gfc_current_locus;
489 /* Match initial value list. This also eats the terminal '/'. */
490 m = top_val_list (newdata);
491 if (m != MATCH_YES)
493 gfc_free (newdata);
494 return m;
497 if (gfc_pure (NULL))
499 gfc_error ("Initialization at %C is not allowed in a PURE procedure");
500 gfc_free (newdata);
501 return MATCH_ERROR;
504 /* Mark the variable as having appeared in a data statement. */
505 if (gfc_add_data (&sym->attr, sym->name, &sym->declared_at) == FAILURE)
507 gfc_free (newdata);
508 return MATCH_ERROR;
511 /* Chain in namespace list of DATA initializers. */
512 newdata->next = gfc_current_ns->data;
513 gfc_current_ns->data = newdata;
515 return m;
519 /* Match the stuff following a DATA statement. If ERROR_FLAG is set,
520 we are matching a DATA statement and are therefore issuing an error
521 if we encounter something unexpected, if not, we're trying to match
522 an old-style initialization expression of the form INTEGER I /2/. */
524 match
525 gfc_match_data (void)
527 gfc_data *new_data;
528 match m;
530 set_in_match_data (true);
532 for (;;)
534 new_data = gfc_get_data ();
535 new_data->where = gfc_current_locus;
537 m = top_var_list (new_data);
538 if (m != MATCH_YES)
539 goto cleanup;
541 m = top_val_list (new_data);
542 if (m != MATCH_YES)
543 goto cleanup;
545 new_data->next = gfc_current_ns->data;
546 gfc_current_ns->data = new_data;
548 if (gfc_match_eos () == MATCH_YES)
549 break;
551 gfc_match_char (','); /* Optional comma */
554 set_in_match_data (false);
556 if (gfc_pure (NULL))
558 gfc_error ("DATA statement at %C is not allowed in a PURE procedure");
559 return MATCH_ERROR;
562 return MATCH_YES;
564 cleanup:
565 set_in_match_data (false);
566 gfc_free_data (new_data);
567 return MATCH_ERROR;
571 /************************ Declaration statements *********************/
573 /* Match an intent specification. Since this can only happen after an
574 INTENT word, a legal intent-spec must follow. */
576 static sym_intent
577 match_intent_spec (void)
580 if (gfc_match (" ( in out )") == MATCH_YES)
581 return INTENT_INOUT;
582 if (gfc_match (" ( in )") == MATCH_YES)
583 return INTENT_IN;
584 if (gfc_match (" ( out )") == MATCH_YES)
585 return INTENT_OUT;
587 gfc_error ("Bad INTENT specification at %C");
588 return INTENT_UNKNOWN;
592 /* Matches a character length specification, which is either a
593 specification expression or a '*'. */
595 static match
596 char_len_param_value (gfc_expr **expr)
598 match m;
600 if (gfc_match_char ('*') == MATCH_YES)
602 *expr = NULL;
603 return MATCH_YES;
606 m = gfc_match_expr (expr);
608 if (m == MATCH_YES
609 && gfc_expr_check_typed (*expr, gfc_current_ns, false) == FAILURE)
610 return MATCH_ERROR;
612 if (m == MATCH_YES && (*expr)->expr_type == EXPR_FUNCTION)
614 if ((*expr)->value.function.actual
615 && (*expr)->value.function.actual->expr->symtree)
617 gfc_expr *e;
618 e = (*expr)->value.function.actual->expr;
619 if (e->symtree->n.sym->attr.flavor == FL_PROCEDURE
620 && e->expr_type == EXPR_VARIABLE)
622 if (e->symtree->n.sym->ts.type == BT_UNKNOWN)
623 goto syntax;
624 if (e->symtree->n.sym->ts.type == BT_CHARACTER
625 && e->symtree->n.sym->ts.cl
626 && e->symtree->n.sym->ts.cl->length->ts.type == BT_UNKNOWN)
627 goto syntax;
631 return m;
633 syntax:
634 gfc_error ("Conflict in attributes of function argument at %C");
635 return MATCH_ERROR;
639 /* A character length is a '*' followed by a literal integer or a
640 char_len_param_value in parenthesis. */
642 static match
643 match_char_length (gfc_expr **expr)
645 int length;
646 match m;
648 m = gfc_match_char ('*');
649 if (m != MATCH_YES)
650 return m;
652 m = gfc_match_small_literal_int (&length, NULL);
653 if (m == MATCH_ERROR)
654 return m;
656 if (m == MATCH_YES)
658 *expr = gfc_int_expr (length);
659 return m;
662 if (gfc_match_char ('(') == MATCH_NO)
663 goto syntax;
665 m = char_len_param_value (expr);
666 if (m != MATCH_YES && gfc_matching_function)
668 gfc_undo_symbols ();
669 m = MATCH_YES;
672 if (m == MATCH_ERROR)
673 return m;
674 if (m == MATCH_NO)
675 goto syntax;
677 if (gfc_match_char (')') == MATCH_NO)
679 gfc_free_expr (*expr);
680 *expr = NULL;
681 goto syntax;
684 return MATCH_YES;
686 syntax:
687 gfc_error ("Syntax error in character length specification at %C");
688 return MATCH_ERROR;
692 /* Special subroutine for finding a symbol. Check if the name is found
693 in the current name space. If not, and we're compiling a function or
694 subroutine and the parent compilation unit is an interface, then check
695 to see if the name we've been given is the name of the interface
696 (located in another namespace). */
698 static int
699 find_special (const char *name, gfc_symbol **result)
701 gfc_state_data *s;
702 int i;
704 i = gfc_get_symbol (name, NULL, result);
705 if (i == 0)
706 goto end;
708 if (gfc_current_state () != COMP_SUBROUTINE
709 && gfc_current_state () != COMP_FUNCTION)
710 goto end;
712 s = gfc_state_stack->previous;
713 if (s == NULL)
714 goto end;
716 if (s->state != COMP_INTERFACE)
717 goto end;
718 if (s->sym == NULL)
719 goto end; /* Nameless interface. */
721 if (strcmp (name, s->sym->name) == 0)
723 *result = s->sym;
724 return 0;
727 end:
728 return i;
732 /* Special subroutine for getting a symbol node associated with a
733 procedure name, used in SUBROUTINE and FUNCTION statements. The
734 symbol is created in the parent using with symtree node in the
735 child unit pointing to the symbol. If the current namespace has no
736 parent, then the symbol is just created in the current unit. */
738 static int
739 get_proc_name (const char *name, gfc_symbol **result, bool module_fcn_entry)
741 gfc_symtree *st;
742 gfc_symbol *sym;
743 int rc = 0;
745 /* Module functions have to be left in their own namespace because
746 they have potentially (almost certainly!) already been referenced.
747 In this sense, they are rather like external functions. This is
748 fixed up in resolve.c(resolve_entries), where the symbol name-
749 space is set to point to the master function, so that the fake
750 result mechanism can work. */
751 if (module_fcn_entry)
753 /* Present if entry is declared to be a module procedure. */
754 rc = gfc_find_symbol (name, gfc_current_ns->parent, 0, result);
756 if (*result == NULL)
757 rc = gfc_get_symbol (name, NULL, result);
758 else if (!gfc_get_symbol (name, NULL, &sym) && sym
759 && (*result)->ts.type == BT_UNKNOWN
760 && sym->attr.flavor == FL_UNKNOWN)
761 /* Pick up the typespec for the entry, if declared in the function
762 body. Note that this symbol is FL_UNKNOWN because it will
763 only have appeared in a type declaration. The local symtree
764 is set to point to the module symbol and a unique symtree
765 to the local version. This latter ensures a correct clearing
766 of the symbols. */
768 /* If the ENTRY proceeds its specification, we need to ensure
769 that this does not raise a "has no IMPLICIT type" error. */
770 if (sym->ts.type == BT_UNKNOWN)
771 sym->attr.untyped = 1;
773 (*result)->ts = sym->ts;
775 /* Put the symbol in the procedure namespace so that, should
776 the ENTRY precede its specification, the specification
777 can be applied. */
778 (*result)->ns = gfc_current_ns;
780 gfc_find_sym_tree (name, gfc_current_ns, 0, &st);
781 st->n.sym = *result;
782 st = gfc_get_unique_symtree (gfc_current_ns);
783 st->n.sym = sym;
786 else
787 rc = gfc_get_symbol (name, gfc_current_ns->parent, result);
789 if (rc)
790 return rc;
792 sym = *result;
793 gfc_current_ns->refs++;
795 if (sym && !sym->gfc_new && gfc_current_state () != COMP_INTERFACE)
797 /* Trap another encompassed procedure with the same name. All
798 these conditions are necessary to avoid picking up an entry
799 whose name clashes with that of the encompassing procedure;
800 this is handled using gsymbols to register unique,globally
801 accessible names. */
802 if (sym->attr.flavor != 0
803 && sym->attr.proc != 0
804 && (sym->attr.subroutine || sym->attr.function)
805 && sym->attr.if_source != IFSRC_UNKNOWN)
806 gfc_error_now ("Procedure '%s' at %C is already defined at %L",
807 name, &sym->declared_at);
809 /* Trap a procedure with a name the same as interface in the
810 encompassing scope. */
811 if (sym->attr.generic != 0
812 && (sym->attr.subroutine || sym->attr.function)
813 && !sym->attr.mod_proc)
814 gfc_error_now ("Name '%s' at %C is already defined"
815 " as a generic interface at %L",
816 name, &sym->declared_at);
818 /* Trap declarations of attributes in encompassing scope. The
819 signature for this is that ts.kind is set. Legitimate
820 references only set ts.type. */
821 if (sym->ts.kind != 0
822 && !sym->attr.implicit_type
823 && sym->attr.proc == 0
824 && gfc_current_ns->parent != NULL
825 && sym->attr.access == 0
826 && !module_fcn_entry)
827 gfc_error_now ("Procedure '%s' at %C has an explicit interface "
828 "and must not have attributes declared at %L",
829 name, &sym->declared_at);
832 if (gfc_current_ns->parent == NULL || *result == NULL)
833 return rc;
835 /* Module function entries will already have a symtree in
836 the current namespace but will need one at module level. */
837 if (module_fcn_entry)
839 /* Present if entry is declared to be a module procedure. */
840 rc = gfc_find_sym_tree (name, gfc_current_ns->parent, 0, &st);
841 if (st == NULL)
842 st = gfc_new_symtree (&gfc_current_ns->parent->sym_root, name);
844 else
845 st = gfc_new_symtree (&gfc_current_ns->sym_root, name);
847 st->n.sym = sym;
848 sym->refs++;
850 /* See if the procedure should be a module procedure. */
852 if (((sym->ns->proc_name != NULL
853 && sym->ns->proc_name->attr.flavor == FL_MODULE
854 && sym->attr.proc != PROC_MODULE)
855 || (module_fcn_entry && sym->attr.proc != PROC_MODULE))
856 && gfc_add_procedure (&sym->attr, PROC_MODULE,
857 sym->name, NULL) == FAILURE)
858 rc = 2;
860 return rc;
864 /* Verify that the given symbol representing a parameter is C
865 interoperable, by checking to see if it was marked as such after
866 its declaration. If the given symbol is not interoperable, a
867 warning is reported, thus removing the need to return the status to
868 the calling function. The standard does not require the user use
869 one of the iso_c_binding named constants to declare an
870 interoperable parameter, but we can't be sure if the param is C
871 interop or not if the user doesn't. For example, integer(4) may be
872 legal Fortran, but doesn't have meaning in C. It may interop with
873 a number of the C types, which causes a problem because the
874 compiler can't know which one. This code is almost certainly not
875 portable, and the user will get what they deserve if the C type
876 across platforms isn't always interoperable with integer(4). If
877 the user had used something like integer(c_int) or integer(c_long),
878 the compiler could have automatically handled the varying sizes
879 across platforms. */
881 gfc_try
882 verify_c_interop_param (gfc_symbol *sym)
884 int is_c_interop = 0;
885 gfc_try retval = SUCCESS;
887 /* We check implicitly typed variables in symbol.c:gfc_set_default_type().
888 Don't repeat the checks here. */
889 if (sym->attr.implicit_type)
890 return SUCCESS;
892 /* For subroutines or functions that are passed to a BIND(C) procedure,
893 they're interoperable if they're BIND(C) and their params are all
894 interoperable. */
895 if (sym->attr.flavor == FL_PROCEDURE)
897 if (sym->attr.is_bind_c == 0)
899 gfc_error_now ("Procedure '%s' at %L must have the BIND(C) "
900 "attribute to be C interoperable", sym->name,
901 &(sym->declared_at));
903 return FAILURE;
905 else
907 if (sym->attr.is_c_interop == 1)
908 /* We've already checked this procedure; don't check it again. */
909 return SUCCESS;
910 else
911 return verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
912 sym->common_block);
916 /* See if we've stored a reference to a procedure that owns sym. */
917 if (sym->ns != NULL && sym->ns->proc_name != NULL)
919 if (sym->ns->proc_name->attr.is_bind_c == 1)
921 is_c_interop =
922 (verify_c_interop (&(sym->ts))
923 == SUCCESS ? 1 : 0);
925 if (is_c_interop != 1)
927 /* Make personalized messages to give better feedback. */
928 if (sym->ts.type == BT_DERIVED)
929 gfc_error ("Type '%s' at %L is a parameter to the BIND(C) "
930 " procedure '%s' but is not C interoperable "
931 "because derived type '%s' is not C interoperable",
932 sym->name, &(sym->declared_at),
933 sym->ns->proc_name->name,
934 sym->ts.derived->name);
935 else
936 gfc_warning ("Variable '%s' at %L is a parameter to the "
937 "BIND(C) procedure '%s' but may not be C "
938 "interoperable",
939 sym->name, &(sym->declared_at),
940 sym->ns->proc_name->name);
943 /* Character strings are only C interoperable if they have a
944 length of 1. */
945 if (sym->ts.type == BT_CHARACTER)
947 gfc_charlen *cl = sym->ts.cl;
948 if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT
949 || mpz_cmp_si (cl->length->value.integer, 1) != 0)
951 gfc_error ("Character argument '%s' at %L "
952 "must be length 1 because "
953 "procedure '%s' is BIND(C)",
954 sym->name, &sym->declared_at,
955 sym->ns->proc_name->name);
956 retval = FAILURE;
960 /* We have to make sure that any param to a bind(c) routine does
961 not have the allocatable, pointer, or optional attributes,
962 according to J3/04-007, section 5.1. */
963 if (sym->attr.allocatable == 1)
965 gfc_error ("Variable '%s' at %L cannot have the "
966 "ALLOCATABLE attribute because procedure '%s'"
967 " is BIND(C)", sym->name, &(sym->declared_at),
968 sym->ns->proc_name->name);
969 retval = FAILURE;
972 if (sym->attr.pointer == 1)
974 gfc_error ("Variable '%s' at %L cannot have the "
975 "POINTER attribute because procedure '%s'"
976 " is BIND(C)", sym->name, &(sym->declared_at),
977 sym->ns->proc_name->name);
978 retval = FAILURE;
981 if (sym->attr.optional == 1)
983 gfc_error ("Variable '%s' at %L cannot have the "
984 "OPTIONAL attribute because procedure '%s'"
985 " is BIND(C)", sym->name, &(sym->declared_at),
986 sym->ns->proc_name->name);
987 retval = FAILURE;
990 /* Make sure that if it has the dimension attribute, that it is
991 either assumed size or explicit shape. */
992 if (sym->as != NULL)
994 if (sym->as->type == AS_ASSUMED_SHAPE)
996 gfc_error ("Assumed-shape array '%s' at %L cannot be an "
997 "argument to the procedure '%s' at %L because "
998 "the procedure is BIND(C)", sym->name,
999 &(sym->declared_at), sym->ns->proc_name->name,
1000 &(sym->ns->proc_name->declared_at));
1001 retval = FAILURE;
1004 if (sym->as->type == AS_DEFERRED)
1006 gfc_error ("Deferred-shape array '%s' at %L cannot be an "
1007 "argument to the procedure '%s' at %L because "
1008 "the procedure is BIND(C)", sym->name,
1009 &(sym->declared_at), sym->ns->proc_name->name,
1010 &(sym->ns->proc_name->declared_at));
1011 retval = FAILURE;
1017 return retval;
1021 /* Function called by variable_decl() that adds a name to the symbol table. */
1023 static gfc_try
1024 build_sym (const char *name, gfc_charlen *cl,
1025 gfc_array_spec **as, locus *var_locus)
1027 symbol_attribute attr;
1028 gfc_symbol *sym;
1030 if (gfc_get_symbol (name, NULL, &sym))
1031 return FAILURE;
1033 /* Start updating the symbol table. Add basic type attribute if present. */
1034 if (current_ts.type != BT_UNKNOWN
1035 && (sym->attr.implicit_type == 0
1036 || !gfc_compare_types (&sym->ts, &current_ts))
1037 && gfc_add_type (sym, &current_ts, var_locus) == FAILURE)
1038 return FAILURE;
1040 if (sym->ts.type == BT_CHARACTER)
1041 sym->ts.cl = cl;
1043 /* Add dimension attribute if present. */
1044 if (gfc_set_array_spec (sym, *as, var_locus) == FAILURE)
1045 return FAILURE;
1046 *as = NULL;
1048 /* Add attribute to symbol. The copy is so that we can reset the
1049 dimension attribute. */
1050 attr = current_attr;
1051 attr.dimension = 0;
1053 if (gfc_copy_attr (&sym->attr, &attr, var_locus) == FAILURE)
1054 return FAILURE;
1056 /* Finish any work that may need to be done for the binding label,
1057 if it's a bind(c). The bind(c) attr is found before the symbol
1058 is made, and before the symbol name (for data decls), so the
1059 current_ts is holding the binding label, or nothing if the
1060 name= attr wasn't given. Therefore, test here if we're dealing
1061 with a bind(c) and make sure the binding label is set correctly. */
1062 if (sym->attr.is_bind_c == 1)
1064 if (sym->binding_label[0] == '\0')
1066 /* Set the binding label and verify that if a NAME= was specified
1067 then only one identifier was in the entity-decl-list. */
1068 if (set_binding_label (sym->binding_label, sym->name,
1069 num_idents_on_line) == FAILURE)
1070 return FAILURE;
1074 /* See if we know we're in a common block, and if it's a bind(c)
1075 common then we need to make sure we're an interoperable type. */
1076 if (sym->attr.in_common == 1)
1078 /* Test the common block object. */
1079 if (sym->common_block != NULL && sym->common_block->is_bind_c == 1
1080 && sym->ts.is_c_interop != 1)
1082 gfc_error_now ("Variable '%s' in common block '%s' at %C "
1083 "must be declared with a C interoperable "
1084 "kind since common block '%s' is BIND(C)",
1085 sym->name, sym->common_block->name,
1086 sym->common_block->name);
1087 gfc_clear_error ();
1091 sym->attr.implied_index = 0;
1093 return SUCCESS;
1097 /* Set character constant to the given length. The constant will be padded or
1098 truncated. If we're inside an array constructor without a typespec, we
1099 additionally check that all elements have the same length; check_len -1
1100 means no checking. */
1102 void
1103 gfc_set_constant_character_len (int len, gfc_expr *expr, int check_len)
1105 gfc_char_t *s;
1106 int slen;
1108 gcc_assert (expr->expr_type == EXPR_CONSTANT);
1109 gcc_assert (expr->ts.type == BT_CHARACTER);
1111 slen = expr->value.character.length;
1112 if (len != slen)
1114 s = gfc_get_wide_string (len + 1);
1115 memcpy (s, expr->value.character.string,
1116 MIN (len, slen) * sizeof (gfc_char_t));
1117 if (len > slen)
1118 gfc_wide_memset (&s[slen], ' ', len - slen);
1120 if (gfc_option.warn_character_truncation && slen > len)
1121 gfc_warning_now ("CHARACTER expression at %L is being truncated "
1122 "(%d/%d)", &expr->where, slen, len);
1124 /* Apply the standard by 'hand' otherwise it gets cleared for
1125 initializers. */
1126 if (check_len != -1 && slen != check_len
1127 && !(gfc_option.allow_std & GFC_STD_GNU))
1128 gfc_error_now ("The CHARACTER elements of the array constructor "
1129 "at %L must have the same length (%d/%d)",
1130 &expr->where, slen, check_len);
1132 s[len] = '\0';
1133 gfc_free (expr->value.character.string);
1134 expr->value.character.string = s;
1135 expr->value.character.length = len;
1140 /* Function to create and update the enumerator history
1141 using the information passed as arguments.
1142 Pointer "max_enum" is also updated, to point to
1143 enum history node containing largest initializer.
1145 SYM points to the symbol node of enumerator.
1146 INIT points to its enumerator value. */
1148 static void
1149 create_enum_history (gfc_symbol *sym, gfc_expr *init)
1151 enumerator_history *new_enum_history;
1152 gcc_assert (sym != NULL && init != NULL);
1154 new_enum_history = XCNEW (enumerator_history);
1156 new_enum_history->sym = sym;
1157 new_enum_history->initializer = init;
1158 new_enum_history->next = NULL;
1160 if (enum_history == NULL)
1162 enum_history = new_enum_history;
1163 max_enum = enum_history;
1165 else
1167 new_enum_history->next = enum_history;
1168 enum_history = new_enum_history;
1170 if (mpz_cmp (max_enum->initializer->value.integer,
1171 new_enum_history->initializer->value.integer) < 0)
1172 max_enum = new_enum_history;
1177 /* Function to free enum kind history. */
1179 void
1180 gfc_free_enum_history (void)
1182 enumerator_history *current = enum_history;
1183 enumerator_history *next;
1185 while (current != NULL)
1187 next = current->next;
1188 gfc_free (current);
1189 current = next;
1191 max_enum = NULL;
1192 enum_history = NULL;
1196 /* Function called by variable_decl() that adds an initialization
1197 expression to a symbol. */
1199 static gfc_try
1200 add_init_expr_to_sym (const char *name, gfc_expr **initp, locus *var_locus)
1202 symbol_attribute attr;
1203 gfc_symbol *sym;
1204 gfc_expr *init;
1206 init = *initp;
1207 if (find_special (name, &sym))
1208 return FAILURE;
1210 attr = sym->attr;
1212 /* If this symbol is confirming an implicit parameter type,
1213 then an initialization expression is not allowed. */
1214 if (attr.flavor == FL_PARAMETER
1215 && sym->value != NULL
1216 && *initp != NULL)
1218 gfc_error ("Initializer not allowed for PARAMETER '%s' at %C",
1219 sym->name);
1220 return FAILURE;
1223 if (init == NULL)
1225 /* An initializer is required for PARAMETER declarations. */
1226 if (attr.flavor == FL_PARAMETER)
1228 gfc_error ("PARAMETER at %L is missing an initializer", var_locus);
1229 return FAILURE;
1232 else
1234 /* If a variable appears in a DATA block, it cannot have an
1235 initializer. */
1236 if (sym->attr.data)
1238 gfc_error ("Variable '%s' at %C with an initializer already "
1239 "appears in a DATA statement", sym->name);
1240 return FAILURE;
1243 /* Check if the assignment can happen. This has to be put off
1244 until later for a derived type variable. */
1245 if (sym->ts.type != BT_DERIVED && init->ts.type != BT_DERIVED
1246 && gfc_check_assign_symbol (sym, init) == FAILURE)
1247 return FAILURE;
1249 if (sym->ts.type == BT_CHARACTER && sym->ts.cl)
1251 /* Update symbol character length according initializer. */
1252 if (sym->ts.cl->length == NULL)
1254 int clen;
1255 /* If there are multiple CHARACTER variables declared on the
1256 same line, we don't want them to share the same length. */
1257 sym->ts.cl = gfc_get_charlen ();
1258 sym->ts.cl->next = gfc_current_ns->cl_list;
1259 gfc_current_ns->cl_list = sym->ts.cl;
1261 if (sym->attr.flavor == FL_PARAMETER)
1263 if (init->expr_type == EXPR_CONSTANT)
1265 clen = init->value.character.length;
1266 sym->ts.cl->length = gfc_int_expr (clen);
1268 else if (init->expr_type == EXPR_ARRAY)
1270 gfc_expr *p = init->value.constructor->expr;
1271 clen = p->value.character.length;
1272 sym->ts.cl->length = gfc_int_expr (clen);
1274 else if (init->ts.cl && init->ts.cl->length)
1275 sym->ts.cl->length =
1276 gfc_copy_expr (sym->value->ts.cl->length);
1279 /* Update initializer character length according symbol. */
1280 else if (sym->ts.cl->length->expr_type == EXPR_CONSTANT)
1282 int len = mpz_get_si (sym->ts.cl->length->value.integer);
1283 gfc_constructor * p;
1285 if (init->expr_type == EXPR_CONSTANT)
1286 gfc_set_constant_character_len (len, init, -1);
1287 else if (init->expr_type == EXPR_ARRAY)
1289 /* Build a new charlen to prevent simplification from
1290 deleting the length before it is resolved. */
1291 init->ts.cl = gfc_get_charlen ();
1292 init->ts.cl->next = gfc_current_ns->cl_list;
1293 gfc_current_ns->cl_list = sym->ts.cl;
1294 init->ts.cl->length = gfc_copy_expr (sym->ts.cl->length);
1296 for (p = init->value.constructor; p; p = p->next)
1297 gfc_set_constant_character_len (len, p->expr, -1);
1302 /* Need to check if the expression we initialized this
1303 to was one of the iso_c_binding named constants. If so,
1304 and we're a parameter (constant), let it be iso_c.
1305 For example:
1306 integer(c_int), parameter :: my_int = c_int
1307 integer(my_int) :: my_int_2
1308 If we mark my_int as iso_c (since we can see it's value
1309 is equal to one of the named constants), then my_int_2
1310 will be considered C interoperable. */
1311 if (sym->ts.type != BT_CHARACTER && sym->ts.type != BT_DERIVED)
1313 sym->ts.is_iso_c |= init->ts.is_iso_c;
1314 sym->ts.is_c_interop |= init->ts.is_c_interop;
1315 /* attr bits needed for module files. */
1316 sym->attr.is_iso_c |= init->ts.is_iso_c;
1317 sym->attr.is_c_interop |= init->ts.is_c_interop;
1318 if (init->ts.is_iso_c)
1319 sym->ts.f90_type = init->ts.f90_type;
1322 /* Add initializer. Make sure we keep the ranks sane. */
1323 if (sym->attr.dimension && init->rank == 0)
1325 mpz_t size;
1326 gfc_expr *array;
1327 gfc_constructor *c;
1328 int n;
1329 if (sym->attr.flavor == FL_PARAMETER
1330 && init->expr_type == EXPR_CONSTANT
1331 && spec_size (sym->as, &size) == SUCCESS
1332 && mpz_cmp_si (size, 0) > 0)
1334 array = gfc_start_constructor (init->ts.type, init->ts.kind,
1335 &init->where);
1337 array->value.constructor = c = NULL;
1338 for (n = 0; n < (int)mpz_get_si (size); n++)
1340 if (array->value.constructor == NULL)
1342 array->value.constructor = c = gfc_get_constructor ();
1343 c->expr = init;
1345 else
1347 c->next = gfc_get_constructor ();
1348 c = c->next;
1349 c->expr = gfc_copy_expr (init);
1353 array->shape = gfc_get_shape (sym->as->rank);
1354 for (n = 0; n < sym->as->rank; n++)
1355 spec_dimen_size (sym->as, n, &array->shape[n]);
1357 init = array;
1358 mpz_clear (size);
1360 init->rank = sym->as->rank;
1363 sym->value = init;
1364 if (sym->attr.save == SAVE_NONE)
1365 sym->attr.save = SAVE_IMPLICIT;
1366 *initp = NULL;
1369 return SUCCESS;
1373 /* Function called by variable_decl() that adds a name to a structure
1374 being built. */
1376 static gfc_try
1377 build_struct (const char *name, gfc_charlen *cl, gfc_expr **init,
1378 gfc_array_spec **as)
1380 gfc_component *c;
1382 /* If the current symbol is of the same derived type that we're
1383 constructing, it must have the pointer attribute. */
1384 if (current_ts.type == BT_DERIVED
1385 && current_ts.derived == gfc_current_block ()
1386 && current_attr.pointer == 0)
1388 gfc_error ("Component at %C must have the POINTER attribute");
1389 return FAILURE;
1392 if (gfc_current_block ()->attr.pointer && (*as)->rank != 0)
1394 if ((*as)->type != AS_DEFERRED && (*as)->type != AS_EXPLICIT)
1396 gfc_error ("Array component of structure at %C must have explicit "
1397 "or deferred shape");
1398 return FAILURE;
1402 if (gfc_add_component (gfc_current_block (), name, &c) == FAILURE)
1403 return FAILURE;
1405 c->ts = current_ts;
1406 c->ts.cl = cl;
1407 c->attr = current_attr;
1409 c->initializer = *init;
1410 *init = NULL;
1412 c->as = *as;
1413 if (c->as != NULL)
1414 c->attr.dimension = 1;
1415 *as = NULL;
1417 /* Should this ever get more complicated, combine with similar section
1418 in add_init_expr_to_sym into a separate function. */
1419 if (c->ts.type == BT_CHARACTER && !c->attr.pointer && c->initializer && c->ts.cl
1420 && c->ts.cl->length && c->ts.cl->length->expr_type == EXPR_CONSTANT)
1422 int len;
1424 gcc_assert (c->ts.cl && c->ts.cl->length);
1425 gcc_assert (c->ts.cl->length->expr_type == EXPR_CONSTANT);
1426 gcc_assert (c->ts.cl->length->ts.type == BT_INTEGER);
1428 len = mpz_get_si (c->ts.cl->length->value.integer);
1430 if (c->initializer->expr_type == EXPR_CONSTANT)
1431 gfc_set_constant_character_len (len, c->initializer, -1);
1432 else if (mpz_cmp (c->ts.cl->length->value.integer,
1433 c->initializer->ts.cl->length->value.integer))
1435 bool has_ts;
1436 gfc_constructor *ctor = c->initializer->value.constructor;
1438 has_ts = (c->initializer->ts.cl
1439 && c->initializer->ts.cl->length_from_typespec);
1441 if (ctor)
1443 int first_len;
1445 /* Remember the length of the first element for checking
1446 that all elements *in the constructor* have the same
1447 length. This need not be the length of the LHS! */
1448 gcc_assert (ctor->expr->expr_type == EXPR_CONSTANT);
1449 gcc_assert (ctor->expr->ts.type == BT_CHARACTER);
1450 first_len = ctor->expr->value.character.length;
1452 for (; ctor; ctor = ctor->next)
1454 if (ctor->expr->expr_type == EXPR_CONSTANT)
1455 gfc_set_constant_character_len (len, ctor->expr,
1456 has_ts ? -1 : first_len);
1462 /* Check array components. */
1463 if (!c->attr.dimension)
1465 if (c->attr.allocatable)
1467 gfc_error ("Allocatable component at %C must be an array");
1468 return FAILURE;
1470 else
1471 return SUCCESS;
1474 if (c->attr.pointer)
1476 if (c->as->type != AS_DEFERRED)
1478 gfc_error ("Pointer array component of structure at %C must have a "
1479 "deferred shape");
1480 return FAILURE;
1483 else if (c->attr.allocatable)
1485 if (c->as->type != AS_DEFERRED)
1487 gfc_error ("Allocatable component of structure at %C must have a "
1488 "deferred shape");
1489 return FAILURE;
1492 else
1494 if (c->as->type != AS_EXPLICIT)
1496 gfc_error ("Array component of structure at %C must have an "
1497 "explicit shape");
1498 return FAILURE;
1502 return SUCCESS;
1506 /* Match a 'NULL()', and possibly take care of some side effects. */
1508 match
1509 gfc_match_null (gfc_expr **result)
1511 gfc_symbol *sym;
1512 gfc_expr *e;
1513 match m;
1515 m = gfc_match (" null ( )");
1516 if (m != MATCH_YES)
1517 return m;
1519 /* The NULL symbol now has to be/become an intrinsic function. */
1520 if (gfc_get_symbol ("null", NULL, &sym))
1522 gfc_error ("NULL() initialization at %C is ambiguous");
1523 return MATCH_ERROR;
1526 gfc_intrinsic_symbol (sym);
1528 if (sym->attr.proc != PROC_INTRINSIC
1529 && (gfc_add_procedure (&sym->attr, PROC_INTRINSIC,
1530 sym->name, NULL) == FAILURE
1531 || gfc_add_function (&sym->attr, sym->name, NULL) == FAILURE))
1532 return MATCH_ERROR;
1534 e = gfc_get_expr ();
1535 e->where = gfc_current_locus;
1536 e->expr_type = EXPR_NULL;
1537 e->ts.type = BT_UNKNOWN;
1539 *result = e;
1541 return MATCH_YES;
1545 /* Match a variable name with an optional initializer. When this
1546 subroutine is called, a variable is expected to be parsed next.
1547 Depending on what is happening at the moment, updates either the
1548 symbol table or the current interface. */
1550 static match
1551 variable_decl (int elem)
1553 char name[GFC_MAX_SYMBOL_LEN + 1];
1554 gfc_expr *initializer, *char_len;
1555 gfc_array_spec *as;
1556 gfc_array_spec *cp_as; /* Extra copy for Cray Pointees. */
1557 gfc_charlen *cl;
1558 locus var_locus;
1559 match m;
1560 gfc_try t;
1561 gfc_symbol *sym;
1562 locus old_locus;
1564 initializer = NULL;
1565 as = NULL;
1566 cp_as = NULL;
1567 old_locus = gfc_current_locus;
1569 /* When we get here, we've just matched a list of attributes and
1570 maybe a type and a double colon. The next thing we expect to see
1571 is the name of the symbol. */
1572 m = gfc_match_name (name);
1573 if (m != MATCH_YES)
1574 goto cleanup;
1576 var_locus = gfc_current_locus;
1578 /* Now we could see the optional array spec. or character length. */
1579 m = gfc_match_array_spec (&as);
1580 if (gfc_option.flag_cray_pointer && m == MATCH_YES)
1581 cp_as = gfc_copy_array_spec (as);
1582 else if (m == MATCH_ERROR)
1583 goto cleanup;
1585 if (m == MATCH_NO)
1586 as = gfc_copy_array_spec (current_as);
1588 char_len = NULL;
1589 cl = NULL;
1591 if (current_ts.type == BT_CHARACTER)
1593 switch (match_char_length (&char_len))
1595 case MATCH_YES:
1596 cl = gfc_get_charlen ();
1597 cl->next = gfc_current_ns->cl_list;
1598 gfc_current_ns->cl_list = cl;
1600 cl->length = char_len;
1601 break;
1603 /* Non-constant lengths need to be copied after the first
1604 element. Also copy assumed lengths. */
1605 case MATCH_NO:
1606 if (elem > 1
1607 && (current_ts.cl->length == NULL
1608 || current_ts.cl->length->expr_type != EXPR_CONSTANT))
1610 cl = gfc_get_charlen ();
1611 cl->next = gfc_current_ns->cl_list;
1612 gfc_current_ns->cl_list = cl;
1613 cl->length = gfc_copy_expr (current_ts.cl->length);
1615 else
1616 cl = current_ts.cl;
1618 break;
1620 case MATCH_ERROR:
1621 goto cleanup;
1625 /* If this symbol has already shown up in a Cray Pointer declaration,
1626 then we want to set the type & bail out. */
1627 if (gfc_option.flag_cray_pointer)
1629 gfc_find_symbol (name, gfc_current_ns, 1, &sym);
1630 if (sym != NULL && sym->attr.cray_pointee)
1632 sym->ts.type = current_ts.type;
1633 sym->ts.kind = current_ts.kind;
1634 sym->ts.cl = cl;
1635 sym->ts.derived = current_ts.derived;
1636 sym->ts.is_c_interop = current_ts.is_c_interop;
1637 sym->ts.is_iso_c = current_ts.is_iso_c;
1638 m = MATCH_YES;
1640 /* Check to see if we have an array specification. */
1641 if (cp_as != NULL)
1643 if (sym->as != NULL)
1645 gfc_error ("Duplicate array spec for Cray pointee at %C");
1646 gfc_free_array_spec (cp_as);
1647 m = MATCH_ERROR;
1648 goto cleanup;
1650 else
1652 if (gfc_set_array_spec (sym, cp_as, &var_locus) == FAILURE)
1653 gfc_internal_error ("Couldn't set pointee array spec.");
1655 /* Fix the array spec. */
1656 m = gfc_mod_pointee_as (sym->as);
1657 if (m == MATCH_ERROR)
1658 goto cleanup;
1661 goto cleanup;
1663 else
1665 gfc_free_array_spec (cp_as);
1669 /* Procedure pointer as function result. */
1670 if (gfc_current_state () == COMP_FUNCTION
1671 && strcmp ("ppr@", gfc_current_block ()->name) == 0
1672 && strcmp (name, gfc_current_block ()->ns->proc_name->name) == 0)
1673 strcpy (name, "ppr@");
1675 if (gfc_current_state () == COMP_FUNCTION
1676 && strcmp (name, gfc_current_block ()->name) == 0
1677 && gfc_current_block ()->result
1678 && strcmp ("ppr@", gfc_current_block ()->result->name) == 0)
1679 strcpy (name, "ppr@");
1681 /* OK, we've successfully matched the declaration. Now put the
1682 symbol in the current namespace, because it might be used in the
1683 optional initialization expression for this symbol, e.g. this is
1684 perfectly legal:
1686 integer, parameter :: i = huge(i)
1688 This is only true for parameters or variables of a basic type.
1689 For components of derived types, it is not true, so we don't
1690 create a symbol for those yet. If we fail to create the symbol,
1691 bail out. */
1692 if (gfc_current_state () != COMP_DERIVED
1693 && build_sym (name, cl, &as, &var_locus) == FAILURE)
1695 m = MATCH_ERROR;
1696 goto cleanup;
1699 /* An interface body specifies all of the procedure's
1700 characteristics and these shall be consistent with those
1701 specified in the procedure definition, except that the interface
1702 may specify a procedure that is not pure if the procedure is
1703 defined to be pure(12.3.2). */
1704 if (current_ts.type == BT_DERIVED
1705 && gfc_current_ns->proc_name
1706 && gfc_current_ns->proc_name->attr.if_source == IFSRC_IFBODY
1707 && current_ts.derived->ns != gfc_current_ns)
1709 gfc_symtree *st;
1710 st = gfc_find_symtree (gfc_current_ns->sym_root, current_ts.derived->name);
1711 if (!(current_ts.derived->attr.imported
1712 && st != NULL
1713 && st->n.sym == current_ts.derived)
1714 && !gfc_current_ns->has_import_set)
1716 gfc_error ("the type of '%s' at %C has not been declared within the "
1717 "interface", name);
1718 m = MATCH_ERROR;
1719 goto cleanup;
1723 /* In functions that have a RESULT variable defined, the function
1724 name always refers to function calls. Therefore, the name is
1725 not allowed to appear in specification statements. */
1726 if (gfc_current_state () == COMP_FUNCTION
1727 && gfc_current_block () != NULL
1728 && gfc_current_block ()->result != NULL
1729 && gfc_current_block ()->result != gfc_current_block ()
1730 && strcmp (gfc_current_block ()->name, name) == 0)
1732 gfc_error ("Function name '%s' not allowed at %C", name);
1733 m = MATCH_ERROR;
1734 goto cleanup;
1737 /* We allow old-style initializations of the form
1738 integer i /2/, j(4) /3*3, 1/
1739 (if no colon has been seen). These are different from data
1740 statements in that initializers are only allowed to apply to the
1741 variable immediately preceding, i.e.
1742 integer i, j /1, 2/
1743 is not allowed. Therefore we have to do some work manually, that
1744 could otherwise be left to the matchers for DATA statements. */
1746 if (!colon_seen && gfc_match (" /") == MATCH_YES)
1748 if (gfc_notify_std (GFC_STD_GNU, "Extension: Old-style "
1749 "initialization at %C") == FAILURE)
1750 return MATCH_ERROR;
1752 return match_old_style_init (name);
1755 /* The double colon must be present in order to have initializers.
1756 Otherwise the statement is ambiguous with an assignment statement. */
1757 if (colon_seen)
1759 if (gfc_match (" =>") == MATCH_YES)
1761 if (!current_attr.pointer)
1763 gfc_error ("Initialization at %C isn't for a pointer variable");
1764 m = MATCH_ERROR;
1765 goto cleanup;
1768 m = gfc_match_null (&initializer);
1769 if (m == MATCH_NO)
1771 gfc_error ("Pointer initialization requires a NULL() at %C");
1772 m = MATCH_ERROR;
1775 if (gfc_pure (NULL))
1777 gfc_error ("Initialization of pointer at %C is not allowed in "
1778 "a PURE procedure");
1779 m = MATCH_ERROR;
1782 if (m != MATCH_YES)
1783 goto cleanup;
1786 else if (gfc_match_char ('=') == MATCH_YES)
1788 if (current_attr.pointer)
1790 gfc_error ("Pointer initialization at %C requires '=>', "
1791 "not '='");
1792 m = MATCH_ERROR;
1793 goto cleanup;
1796 m = gfc_match_init_expr (&initializer);
1797 if (m == MATCH_NO)
1799 gfc_error ("Expected an initialization expression at %C");
1800 m = MATCH_ERROR;
1803 if (current_attr.flavor != FL_PARAMETER && gfc_pure (NULL))
1805 gfc_error ("Initialization of variable at %C is not allowed in "
1806 "a PURE procedure");
1807 m = MATCH_ERROR;
1810 if (m != MATCH_YES)
1811 goto cleanup;
1815 if (initializer != NULL && current_attr.allocatable
1816 && gfc_current_state () == COMP_DERIVED)
1818 gfc_error ("Initialization of allocatable component at %C is not "
1819 "allowed");
1820 m = MATCH_ERROR;
1821 goto cleanup;
1824 /* Add the initializer. Note that it is fine if initializer is
1825 NULL here, because we sometimes also need to check if a
1826 declaration *must* have an initialization expression. */
1827 if (gfc_current_state () != COMP_DERIVED)
1828 t = add_init_expr_to_sym (name, &initializer, &var_locus);
1829 else
1831 if (current_ts.type == BT_DERIVED
1832 && !current_attr.pointer && !initializer)
1833 initializer = gfc_default_initializer (&current_ts);
1834 t = build_struct (name, cl, &initializer, &as);
1837 m = (t == SUCCESS) ? MATCH_YES : MATCH_ERROR;
1839 cleanup:
1840 /* Free stuff up and return. */
1841 gfc_free_expr (initializer);
1842 gfc_free_array_spec (as);
1844 return m;
1848 /* Match an extended-f77 "TYPESPEC*bytesize"-style kind specification.
1849 This assumes that the byte size is equal to the kind number for
1850 non-COMPLEX types, and equal to twice the kind number for COMPLEX. */
1852 match
1853 gfc_match_old_kind_spec (gfc_typespec *ts)
1855 match m;
1856 int original_kind;
1858 if (gfc_match_char ('*') != MATCH_YES)
1859 return MATCH_NO;
1861 m = gfc_match_small_literal_int (&ts->kind, NULL);
1862 if (m != MATCH_YES)
1863 return MATCH_ERROR;
1865 original_kind = ts->kind;
1867 /* Massage the kind numbers for complex types. */
1868 if (ts->type == BT_COMPLEX)
1870 if (ts->kind % 2)
1872 gfc_error ("Old-style type declaration %s*%d not supported at %C",
1873 gfc_basic_typename (ts->type), original_kind);
1874 return MATCH_ERROR;
1876 ts->kind /= 2;
1879 if (gfc_validate_kind (ts->type, ts->kind, true) < 0)
1881 gfc_error ("Old-style type declaration %s*%d not supported at %C",
1882 gfc_basic_typename (ts->type), original_kind);
1883 return MATCH_ERROR;
1886 if (gfc_notify_std (GFC_STD_GNU, "Nonstandard type declaration %s*%d at %C",
1887 gfc_basic_typename (ts->type), original_kind) == FAILURE)
1888 return MATCH_ERROR;
1890 return MATCH_YES;
1894 /* Match a kind specification. Since kinds are generally optional, we
1895 usually return MATCH_NO if something goes wrong. If a "kind="
1896 string is found, then we know we have an error. */
1898 match
1899 gfc_match_kind_spec (gfc_typespec *ts, bool kind_expr_only)
1901 locus where, loc;
1902 gfc_expr *e;
1903 match m, n;
1904 char c;
1905 const char *msg;
1907 m = MATCH_NO;
1908 n = MATCH_YES;
1909 e = NULL;
1911 where = loc = gfc_current_locus;
1913 if (kind_expr_only)
1914 goto kind_expr;
1916 if (gfc_match_char ('(') == MATCH_NO)
1917 return MATCH_NO;
1919 /* Also gobbles optional text. */
1920 if (gfc_match (" kind = ") == MATCH_YES)
1921 m = MATCH_ERROR;
1923 loc = gfc_current_locus;
1925 kind_expr:
1926 n = gfc_match_init_expr (&e);
1928 if (n != MATCH_YES)
1930 if (gfc_matching_function)
1932 /* The function kind expression might include use associated or
1933 imported parameters and try again after the specification
1934 expressions..... */
1935 if (gfc_match_char (')') != MATCH_YES)
1937 gfc_error ("Missing right parenthesis at %C");
1938 m = MATCH_ERROR;
1939 goto no_match;
1942 gfc_free_expr (e);
1943 gfc_undo_symbols ();
1944 return MATCH_YES;
1946 else
1948 /* ....or else, the match is real. */
1949 if (n == MATCH_NO)
1950 gfc_error ("Expected initialization expression at %C");
1951 if (n != MATCH_YES)
1952 return MATCH_ERROR;
1956 if (e->rank != 0)
1958 gfc_error ("Expected scalar initialization expression at %C");
1959 m = MATCH_ERROR;
1960 goto no_match;
1963 msg = gfc_extract_int (e, &ts->kind);
1965 if (msg != NULL)
1967 gfc_error (msg);
1968 m = MATCH_ERROR;
1969 goto no_match;
1972 /* Before throwing away the expression, let's see if we had a
1973 C interoperable kind (and store the fact). */
1974 if (e->ts.is_c_interop == 1)
1976 /* Mark this as c interoperable if being declared with one
1977 of the named constants from iso_c_binding. */
1978 ts->is_c_interop = e->ts.is_iso_c;
1979 ts->f90_type = e->ts.f90_type;
1982 gfc_free_expr (e);
1983 e = NULL;
1985 /* Ignore errors to this point, if we've gotten here. This means
1986 we ignore the m=MATCH_ERROR from above. */
1987 if (gfc_validate_kind (ts->type, ts->kind, true) < 0)
1989 gfc_error ("Kind %d not supported for type %s at %C", ts->kind,
1990 gfc_basic_typename (ts->type));
1991 gfc_current_locus = where;
1992 return MATCH_ERROR;
1995 /* Warn if, e.g., c_int is used for a REAL variable, but not
1996 if, e.g., c_double is used for COMPLEX as the standard
1997 explicitly says that the kind type parameter for complex and real
1998 variable is the same, i.e. c_float == c_float_complex. */
1999 if (ts->f90_type != BT_UNKNOWN && ts->f90_type != ts->type
2000 && !((ts->f90_type == BT_REAL && ts->type == BT_COMPLEX)
2001 || (ts->f90_type == BT_COMPLEX && ts->type == BT_REAL)))
2002 gfc_warning_now ("C kind type parameter is for type %s but type at %L "
2003 "is %s", gfc_basic_typename (ts->f90_type), &where,
2004 gfc_basic_typename (ts->type));
2006 gfc_gobble_whitespace ();
2007 if ((c = gfc_next_ascii_char ()) != ')'
2008 && (ts->type != BT_CHARACTER || c != ','))
2010 if (ts->type == BT_CHARACTER)
2011 gfc_error ("Missing right parenthesis or comma at %C");
2012 else
2013 gfc_error ("Missing right parenthesis at %C");
2014 m = MATCH_ERROR;
2016 else
2017 /* All tests passed. */
2018 m = MATCH_YES;
2020 if(m == MATCH_ERROR)
2021 gfc_current_locus = where;
2023 /* Return what we know from the test(s). */
2024 return m;
2026 no_match:
2027 gfc_free_expr (e);
2028 gfc_current_locus = where;
2029 return m;
2033 static match
2034 match_char_kind (int * kind, int * is_iso_c)
2036 locus where;
2037 gfc_expr *e;
2038 match m, n;
2039 const char *msg;
2041 m = MATCH_NO;
2042 e = NULL;
2043 where = gfc_current_locus;
2045 n = gfc_match_init_expr (&e);
2047 if (n != MATCH_YES && gfc_matching_function)
2049 /* The expression might include use-associated or imported
2050 parameters and try again after the specification
2051 expressions. */
2052 gfc_free_expr (e);
2053 gfc_undo_symbols ();
2054 return MATCH_YES;
2057 if (n == MATCH_NO)
2058 gfc_error ("Expected initialization expression at %C");
2059 if (n != MATCH_YES)
2060 return MATCH_ERROR;
2062 if (e->rank != 0)
2064 gfc_error ("Expected scalar initialization expression at %C");
2065 m = MATCH_ERROR;
2066 goto no_match;
2069 msg = gfc_extract_int (e, kind);
2070 *is_iso_c = e->ts.is_iso_c;
2071 if (msg != NULL)
2073 gfc_error (msg);
2074 m = MATCH_ERROR;
2075 goto no_match;
2078 gfc_free_expr (e);
2080 /* Ignore errors to this point, if we've gotten here. This means
2081 we ignore the m=MATCH_ERROR from above. */
2082 if (gfc_validate_kind (BT_CHARACTER, *kind, true) < 0)
2084 gfc_error ("Kind %d is not supported for CHARACTER at %C", *kind);
2085 m = MATCH_ERROR;
2087 else
2088 /* All tests passed. */
2089 m = MATCH_YES;
2091 if (m == MATCH_ERROR)
2092 gfc_current_locus = where;
2094 /* Return what we know from the test(s). */
2095 return m;
2097 no_match:
2098 gfc_free_expr (e);
2099 gfc_current_locus = where;
2100 return m;
2103 /* Match the various kind/length specifications in a CHARACTER
2104 declaration. We don't return MATCH_NO. */
2106 static match
2107 match_char_spec (gfc_typespec *ts)
2109 int kind, seen_length, is_iso_c;
2110 gfc_charlen *cl;
2111 gfc_expr *len;
2112 match m;
2114 len = NULL;
2115 seen_length = 0;
2116 kind = 0;
2117 is_iso_c = 0;
2119 /* Try the old-style specification first. */
2120 old_char_selector = 0;
2122 m = match_char_length (&len);
2123 if (m != MATCH_NO)
2125 if (m == MATCH_YES)
2126 old_char_selector = 1;
2127 seen_length = 1;
2128 goto done;
2131 m = gfc_match_char ('(');
2132 if (m != MATCH_YES)
2134 m = MATCH_YES; /* Character without length is a single char. */
2135 goto done;
2138 /* Try the weird case: ( KIND = <int> [ , LEN = <len-param> ] ). */
2139 if (gfc_match (" kind =") == MATCH_YES)
2141 m = match_char_kind (&kind, &is_iso_c);
2143 if (m == MATCH_ERROR)
2144 goto done;
2145 if (m == MATCH_NO)
2146 goto syntax;
2148 if (gfc_match (" , len =") == MATCH_NO)
2149 goto rparen;
2151 m = char_len_param_value (&len);
2152 if (m == MATCH_NO)
2153 goto syntax;
2154 if (m == MATCH_ERROR)
2155 goto done;
2156 seen_length = 1;
2158 goto rparen;
2161 /* Try to match "LEN = <len-param>" or "LEN = <len-param>, KIND = <int>". */
2162 if (gfc_match (" len =") == MATCH_YES)
2164 m = char_len_param_value (&len);
2165 if (m == MATCH_NO)
2166 goto syntax;
2167 if (m == MATCH_ERROR)
2168 goto done;
2169 seen_length = 1;
2171 if (gfc_match_char (')') == MATCH_YES)
2172 goto done;
2174 if (gfc_match (" , kind =") != MATCH_YES)
2175 goto syntax;
2177 if (match_char_kind (&kind, &is_iso_c) == MATCH_ERROR)
2178 goto done;
2180 goto rparen;
2183 /* Try to match ( <len-param> ) or ( <len-param> , [ KIND = ] <int> ). */
2184 m = char_len_param_value (&len);
2185 if (m == MATCH_NO)
2186 goto syntax;
2187 if (m == MATCH_ERROR)
2188 goto done;
2189 seen_length = 1;
2191 m = gfc_match_char (')');
2192 if (m == MATCH_YES)
2193 goto done;
2195 if (gfc_match_char (',') != MATCH_YES)
2196 goto syntax;
2198 gfc_match (" kind ="); /* Gobble optional text. */
2200 m = match_char_kind (&kind, &is_iso_c);
2201 if (m == MATCH_ERROR)
2202 goto done;
2203 if (m == MATCH_NO)
2204 goto syntax;
2206 rparen:
2207 /* Require a right-paren at this point. */
2208 m = gfc_match_char (')');
2209 if (m == MATCH_YES)
2210 goto done;
2212 syntax:
2213 gfc_error ("Syntax error in CHARACTER declaration at %C");
2214 m = MATCH_ERROR;
2215 gfc_free_expr (len);
2216 return m;
2218 done:
2219 /* Deal with character functions after USE and IMPORT statements. */
2220 if (gfc_matching_function)
2222 gfc_free_expr (len);
2223 gfc_undo_symbols ();
2224 return MATCH_YES;
2227 if (m != MATCH_YES)
2229 gfc_free_expr (len);
2230 return m;
2233 /* Do some final massaging of the length values. */
2234 cl = gfc_get_charlen ();
2235 cl->next = gfc_current_ns->cl_list;
2236 gfc_current_ns->cl_list = cl;
2238 if (seen_length == 0)
2239 cl->length = gfc_int_expr (1);
2240 else
2241 cl->length = len;
2243 ts->cl = cl;
2244 ts->kind = kind == 0 ? gfc_default_character_kind : kind;
2246 /* We have to know if it was a c interoperable kind so we can
2247 do accurate type checking of bind(c) procs, etc. */
2248 if (kind != 0)
2249 /* Mark this as c interoperable if being declared with one
2250 of the named constants from iso_c_binding. */
2251 ts->is_c_interop = is_iso_c;
2252 else if (len != NULL)
2253 /* Here, we might have parsed something such as: character(c_char)
2254 In this case, the parsing code above grabs the c_char when
2255 looking for the length (line 1690, roughly). it's the last
2256 testcase for parsing the kind params of a character variable.
2257 However, it's not actually the length. this seems like it
2258 could be an error.
2259 To see if the user used a C interop kind, test the expr
2260 of the so called length, and see if it's C interoperable. */
2261 ts->is_c_interop = len->ts.is_iso_c;
2263 return MATCH_YES;
2267 /* Matches a type specification. If successful, sets the ts structure
2268 to the matched specification. This is necessary for FUNCTION and
2269 IMPLICIT statements.
2271 If implicit_flag is nonzero, then we don't check for the optional
2272 kind specification. Not doing so is needed for matching an IMPLICIT
2273 statement correctly. */
2275 match
2276 gfc_match_type_spec (gfc_typespec *ts, int implicit_flag)
2278 char name[GFC_MAX_SYMBOL_LEN + 1];
2279 gfc_symbol *sym;
2280 match m;
2281 char c;
2282 bool seen_deferred_kind;
2284 /* A belt and braces check that the typespec is correctly being treated
2285 as a deferred characteristic association. */
2286 seen_deferred_kind = (gfc_current_state () == COMP_FUNCTION)
2287 && (gfc_current_block ()->result->ts.kind == -1)
2288 && (ts->kind == -1);
2289 gfc_clear_ts (ts);
2290 if (seen_deferred_kind)
2291 ts->kind = -1;
2293 /* Clear the current binding label, in case one is given. */
2294 curr_binding_label[0] = '\0';
2296 if (gfc_match (" byte") == MATCH_YES)
2298 if (gfc_notify_std(GFC_STD_GNU, "Extension: BYTE type at %C")
2299 == FAILURE)
2300 return MATCH_ERROR;
2302 if (gfc_validate_kind (BT_INTEGER, 1, true) < 0)
2304 gfc_error ("BYTE type used at %C "
2305 "is not available on the target machine");
2306 return MATCH_ERROR;
2309 ts->type = BT_INTEGER;
2310 ts->kind = 1;
2311 return MATCH_YES;
2314 if (gfc_match (" integer") == MATCH_YES)
2316 ts->type = BT_INTEGER;
2317 ts->kind = gfc_default_integer_kind;
2318 goto get_kind;
2321 if (gfc_match (" character") == MATCH_YES)
2323 ts->type = BT_CHARACTER;
2324 if (implicit_flag == 0)
2325 return match_char_spec (ts);
2326 else
2327 return MATCH_YES;
2330 if (gfc_match (" real") == MATCH_YES)
2332 ts->type = BT_REAL;
2333 ts->kind = gfc_default_real_kind;
2334 goto get_kind;
2337 if (gfc_match (" double precision") == MATCH_YES)
2339 ts->type = BT_REAL;
2340 ts->kind = gfc_default_double_kind;
2341 return MATCH_YES;
2344 if (gfc_match (" complex") == MATCH_YES)
2346 ts->type = BT_COMPLEX;
2347 ts->kind = gfc_default_complex_kind;
2348 goto get_kind;
2351 if (gfc_match (" double complex") == MATCH_YES)
2353 if (gfc_notify_std (GFC_STD_GNU, "DOUBLE COMPLEX at %C does not "
2354 "conform to the Fortran 95 standard") == FAILURE)
2355 return MATCH_ERROR;
2357 ts->type = BT_COMPLEX;
2358 ts->kind = gfc_default_double_kind;
2359 return MATCH_YES;
2362 if (gfc_match (" logical") == MATCH_YES)
2364 ts->type = BT_LOGICAL;
2365 ts->kind = gfc_default_logical_kind;
2366 goto get_kind;
2369 m = gfc_match (" type ( %n )", name);
2370 if (m != MATCH_YES)
2371 return m;
2373 ts->type = BT_DERIVED;
2375 /* Defer association of the derived type until the end of the
2376 specification block. However, if the derived type can be
2377 found, add it to the typespec. */
2378 if (gfc_matching_function)
2380 ts->derived = NULL;
2381 if (gfc_current_state () != COMP_INTERFACE
2382 && !gfc_find_symbol (name, NULL, 1, &sym) && sym)
2383 ts->derived = sym;
2384 return MATCH_YES;
2387 /* Search for the name but allow the components to be defined later. If
2388 type = -1, this typespec has been seen in a function declaration but
2389 the type could not be accessed at that point. */
2390 sym = NULL;
2391 if (ts->kind != -1 && gfc_get_ha_symbol (name, &sym))
2393 gfc_error ("Type name '%s' at %C is ambiguous", name);
2394 return MATCH_ERROR;
2396 else if (ts->kind == -1)
2398 int iface = gfc_state_stack->previous->state != COMP_INTERFACE
2399 || gfc_current_ns->has_import_set;
2400 if (gfc_find_symbol (name, NULL, iface, &sym))
2402 gfc_error ("Type name '%s' at %C is ambiguous", name);
2403 return MATCH_ERROR;
2406 ts->kind = 0;
2407 if (sym == NULL)
2408 return MATCH_NO;
2411 if (sym->attr.flavor != FL_DERIVED
2412 && gfc_add_flavor (&sym->attr, FL_DERIVED, sym->name, NULL) == FAILURE)
2413 return MATCH_ERROR;
2415 gfc_set_sym_referenced (sym);
2416 ts->derived = sym;
2418 return MATCH_YES;
2420 get_kind:
2421 /* For all types except double, derived and character, look for an
2422 optional kind specifier. MATCH_NO is actually OK at this point. */
2423 if (implicit_flag == 1)
2424 return MATCH_YES;
2426 if (gfc_current_form == FORM_FREE)
2428 c = gfc_peek_ascii_char();
2429 if (!gfc_is_whitespace(c) && c != '*' && c != '('
2430 && c != ':' && c != ',')
2431 return MATCH_NO;
2434 m = gfc_match_kind_spec (ts, false);
2435 if (m == MATCH_NO && ts->type != BT_CHARACTER)
2436 m = gfc_match_old_kind_spec (ts);
2438 /* Defer association of the KIND expression of function results
2439 until after USE and IMPORT statements. */
2440 if ((gfc_current_state () == COMP_NONE && gfc_error_flag_test ())
2441 || gfc_matching_function)
2442 return MATCH_YES;
2444 if (m == MATCH_NO)
2445 m = MATCH_YES; /* No kind specifier found. */
2447 return m;
2451 /* Match an IMPLICIT NONE statement. Actually, this statement is
2452 already matched in parse.c, or we would not end up here in the
2453 first place. So the only thing we need to check, is if there is
2454 trailing garbage. If not, the match is successful. */
2456 match
2457 gfc_match_implicit_none (void)
2459 return (gfc_match_eos () == MATCH_YES) ? MATCH_YES : MATCH_NO;
2463 /* Match the letter range(s) of an IMPLICIT statement. */
2465 static match
2466 match_implicit_range (void)
2468 char c, c1, c2;
2469 int inner;
2470 locus cur_loc;
2472 cur_loc = gfc_current_locus;
2474 gfc_gobble_whitespace ();
2475 c = gfc_next_ascii_char ();
2476 if (c != '(')
2478 gfc_error ("Missing character range in IMPLICIT at %C");
2479 goto bad;
2482 inner = 1;
2483 while (inner)
2485 gfc_gobble_whitespace ();
2486 c1 = gfc_next_ascii_char ();
2487 if (!ISALPHA (c1))
2488 goto bad;
2490 gfc_gobble_whitespace ();
2491 c = gfc_next_ascii_char ();
2493 switch (c)
2495 case ')':
2496 inner = 0; /* Fall through. */
2498 case ',':
2499 c2 = c1;
2500 break;
2502 case '-':
2503 gfc_gobble_whitespace ();
2504 c2 = gfc_next_ascii_char ();
2505 if (!ISALPHA (c2))
2506 goto bad;
2508 gfc_gobble_whitespace ();
2509 c = gfc_next_ascii_char ();
2511 if ((c != ',') && (c != ')'))
2512 goto bad;
2513 if (c == ')')
2514 inner = 0;
2516 break;
2518 default:
2519 goto bad;
2522 if (c1 > c2)
2524 gfc_error ("Letters must be in alphabetic order in "
2525 "IMPLICIT statement at %C");
2526 goto bad;
2529 /* See if we can add the newly matched range to the pending
2530 implicits from this IMPLICIT statement. We do not check for
2531 conflicts with whatever earlier IMPLICIT statements may have
2532 set. This is done when we've successfully finished matching
2533 the current one. */
2534 if (gfc_add_new_implicit_range (c1, c2) != SUCCESS)
2535 goto bad;
2538 return MATCH_YES;
2540 bad:
2541 gfc_syntax_error (ST_IMPLICIT);
2543 gfc_current_locus = cur_loc;
2544 return MATCH_ERROR;
2548 /* Match an IMPLICIT statement, storing the types for
2549 gfc_set_implicit() if the statement is accepted by the parser.
2550 There is a strange looking, but legal syntactic construction
2551 possible. It looks like:
2553 IMPLICIT INTEGER (a-b) (c-d)
2555 This is legal if "a-b" is a constant expression that happens to
2556 equal one of the legal kinds for integers. The real problem
2557 happens with an implicit specification that looks like:
2559 IMPLICIT INTEGER (a-b)
2561 In this case, a typespec matcher that is "greedy" (as most of the
2562 matchers are) gobbles the character range as a kindspec, leaving
2563 nothing left. We therefore have to go a bit more slowly in the
2564 matching process by inhibiting the kindspec checking during
2565 typespec matching and checking for a kind later. */
2567 match
2568 gfc_match_implicit (void)
2570 gfc_typespec ts;
2571 locus cur_loc;
2572 char c;
2573 match m;
2575 gfc_clear_ts (&ts);
2577 /* We don't allow empty implicit statements. */
2578 if (gfc_match_eos () == MATCH_YES)
2580 gfc_error ("Empty IMPLICIT statement at %C");
2581 return MATCH_ERROR;
2586 /* First cleanup. */
2587 gfc_clear_new_implicit ();
2589 /* A basic type is mandatory here. */
2590 m = gfc_match_type_spec (&ts, 1);
2591 if (m == MATCH_ERROR)
2592 goto error;
2593 if (m == MATCH_NO)
2594 goto syntax;
2596 cur_loc = gfc_current_locus;
2597 m = match_implicit_range ();
2599 if (m == MATCH_YES)
2601 /* We may have <TYPE> (<RANGE>). */
2602 gfc_gobble_whitespace ();
2603 c = gfc_next_ascii_char ();
2604 if ((c == '\n') || (c == ','))
2606 /* Check for CHARACTER with no length parameter. */
2607 if (ts.type == BT_CHARACTER && !ts.cl)
2609 ts.kind = gfc_default_character_kind;
2610 ts.cl = gfc_get_charlen ();
2611 ts.cl->next = gfc_current_ns->cl_list;
2612 gfc_current_ns->cl_list = ts.cl;
2613 ts.cl->length = gfc_int_expr (1);
2616 /* Record the Successful match. */
2617 if (gfc_merge_new_implicit (&ts) != SUCCESS)
2618 return MATCH_ERROR;
2619 continue;
2622 gfc_current_locus = cur_loc;
2625 /* Discard the (incorrectly) matched range. */
2626 gfc_clear_new_implicit ();
2628 /* Last chance -- check <TYPE> <SELECTOR> (<RANGE>). */
2629 if (ts.type == BT_CHARACTER)
2630 m = match_char_spec (&ts);
2631 else
2633 m = gfc_match_kind_spec (&ts, false);
2634 if (m == MATCH_NO)
2636 m = gfc_match_old_kind_spec (&ts);
2637 if (m == MATCH_ERROR)
2638 goto error;
2639 if (m == MATCH_NO)
2640 goto syntax;
2643 if (m == MATCH_ERROR)
2644 goto error;
2646 m = match_implicit_range ();
2647 if (m == MATCH_ERROR)
2648 goto error;
2649 if (m == MATCH_NO)
2650 goto syntax;
2652 gfc_gobble_whitespace ();
2653 c = gfc_next_ascii_char ();
2654 if ((c != '\n') && (c != ','))
2655 goto syntax;
2657 if (gfc_merge_new_implicit (&ts) != SUCCESS)
2658 return MATCH_ERROR;
2660 while (c == ',');
2662 return MATCH_YES;
2664 syntax:
2665 gfc_syntax_error (ST_IMPLICIT);
2667 error:
2668 return MATCH_ERROR;
2672 match
2673 gfc_match_import (void)
2675 char name[GFC_MAX_SYMBOL_LEN + 1];
2676 match m;
2677 gfc_symbol *sym;
2678 gfc_symtree *st;
2680 if (gfc_current_ns->proc_name == NULL
2681 || gfc_current_ns->proc_name->attr.if_source != IFSRC_IFBODY)
2683 gfc_error ("IMPORT statement at %C only permitted in "
2684 "an INTERFACE body");
2685 return MATCH_ERROR;
2688 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: IMPORT statement at %C")
2689 == FAILURE)
2690 return MATCH_ERROR;
2692 if (gfc_match_eos () == MATCH_YES)
2694 /* All host variables should be imported. */
2695 gfc_current_ns->has_import_set = 1;
2696 return MATCH_YES;
2699 if (gfc_match (" ::") == MATCH_YES)
2701 if (gfc_match_eos () == MATCH_YES)
2703 gfc_error ("Expecting list of named entities at %C");
2704 return MATCH_ERROR;
2708 for(;;)
2710 m = gfc_match (" %n", name);
2711 switch (m)
2713 case MATCH_YES:
2714 if (gfc_current_ns->parent != NULL
2715 && gfc_find_symbol (name, gfc_current_ns->parent, 1, &sym))
2717 gfc_error ("Type name '%s' at %C is ambiguous", name);
2718 return MATCH_ERROR;
2720 else if (gfc_current_ns->proc_name->ns->parent != NULL
2721 && gfc_find_symbol (name,
2722 gfc_current_ns->proc_name->ns->parent,
2723 1, &sym))
2725 gfc_error ("Type name '%s' at %C is ambiguous", name);
2726 return MATCH_ERROR;
2729 if (sym == NULL)
2731 gfc_error ("Cannot IMPORT '%s' from host scoping unit "
2732 "at %C - does not exist.", name);
2733 return MATCH_ERROR;
2736 if (gfc_find_symtree (gfc_current_ns->sym_root,name))
2738 gfc_warning ("'%s' is already IMPORTed from host scoping unit "
2739 "at %C.", name);
2740 goto next_item;
2743 st = gfc_new_symtree (&gfc_current_ns->sym_root, sym->name);
2744 st->n.sym = sym;
2745 sym->refs++;
2746 sym->attr.imported = 1;
2748 goto next_item;
2750 case MATCH_NO:
2751 break;
2753 case MATCH_ERROR:
2754 return MATCH_ERROR;
2757 next_item:
2758 if (gfc_match_eos () == MATCH_YES)
2759 break;
2760 if (gfc_match_char (',') != MATCH_YES)
2761 goto syntax;
2764 return MATCH_YES;
2766 syntax:
2767 gfc_error ("Syntax error in IMPORT statement at %C");
2768 return MATCH_ERROR;
2772 /* A minimal implementation of gfc_match without whitespace, escape
2773 characters or variable arguments. Returns true if the next
2774 characters match the TARGET template exactly. */
2776 static bool
2777 match_string_p (const char *target)
2779 const char *p;
2781 for (p = target; *p; p++)
2782 if ((char) gfc_next_ascii_char () != *p)
2783 return false;
2784 return true;
2787 /* Matches an attribute specification including array specs. If
2788 successful, leaves the variables current_attr and current_as
2789 holding the specification. Also sets the colon_seen variable for
2790 later use by matchers associated with initializations.
2792 This subroutine is a little tricky in the sense that we don't know
2793 if we really have an attr-spec until we hit the double colon.
2794 Until that time, we can only return MATCH_NO. This forces us to
2795 check for duplicate specification at this level. */
2797 static match
2798 match_attr_spec (void)
2800 /* Modifiers that can exist in a type statement. */
2801 typedef enum
2802 { GFC_DECL_BEGIN = 0,
2803 DECL_ALLOCATABLE = GFC_DECL_BEGIN, DECL_DIMENSION, DECL_EXTERNAL,
2804 DECL_IN, DECL_OUT, DECL_INOUT, DECL_INTRINSIC, DECL_OPTIONAL,
2805 DECL_PARAMETER, DECL_POINTER, DECL_PROTECTED, DECL_PRIVATE,
2806 DECL_PUBLIC, DECL_SAVE, DECL_TARGET, DECL_VALUE, DECL_VOLATILE,
2807 DECL_IS_BIND_C, DECL_NONE,
2808 GFC_DECL_END /* Sentinel */
2810 decl_types;
2812 /* GFC_DECL_END is the sentinel, index starts at 0. */
2813 #define NUM_DECL GFC_DECL_END
2815 locus start, seen_at[NUM_DECL];
2816 int seen[NUM_DECL];
2817 unsigned int d;
2818 const char *attr;
2819 match m;
2820 gfc_try t;
2822 gfc_clear_attr (&current_attr);
2823 start = gfc_current_locus;
2825 current_as = NULL;
2826 colon_seen = 0;
2828 /* See if we get all of the keywords up to the final double colon. */
2829 for (d = GFC_DECL_BEGIN; d != GFC_DECL_END; d++)
2830 seen[d] = 0;
2832 for (;;)
2834 char ch;
2836 d = DECL_NONE;
2837 gfc_gobble_whitespace ();
2839 ch = gfc_next_ascii_char ();
2840 if (ch == ':')
2842 /* This is the successful exit condition for the loop. */
2843 if (gfc_next_ascii_char () == ':')
2844 break;
2846 else if (ch == ',')
2848 gfc_gobble_whitespace ();
2849 switch (gfc_peek_ascii_char ())
2851 case 'a':
2852 if (match_string_p ("allocatable"))
2853 d = DECL_ALLOCATABLE;
2854 break;
2856 case 'b':
2857 /* Try and match the bind(c). */
2858 m = gfc_match_bind_c (NULL, true);
2859 if (m == MATCH_YES)
2860 d = DECL_IS_BIND_C;
2861 else if (m == MATCH_ERROR)
2862 goto cleanup;
2863 break;
2865 case 'd':
2866 if (match_string_p ("dimension"))
2867 d = DECL_DIMENSION;
2868 break;
2870 case 'e':
2871 if (match_string_p ("external"))
2872 d = DECL_EXTERNAL;
2873 break;
2875 case 'i':
2876 if (match_string_p ("int"))
2878 ch = gfc_next_ascii_char ();
2879 if (ch == 'e')
2881 if (match_string_p ("nt"))
2883 /* Matched "intent". */
2884 /* TODO: Call match_intent_spec from here. */
2885 if (gfc_match (" ( in out )") == MATCH_YES)
2886 d = DECL_INOUT;
2887 else if (gfc_match (" ( in )") == MATCH_YES)
2888 d = DECL_IN;
2889 else if (gfc_match (" ( out )") == MATCH_YES)
2890 d = DECL_OUT;
2893 else if (ch == 'r')
2895 if (match_string_p ("insic"))
2897 /* Matched "intrinsic". */
2898 d = DECL_INTRINSIC;
2902 break;
2904 case 'o':
2905 if (match_string_p ("optional"))
2906 d = DECL_OPTIONAL;
2907 break;
2909 case 'p':
2910 gfc_next_ascii_char ();
2911 switch (gfc_next_ascii_char ())
2913 case 'a':
2914 if (match_string_p ("rameter"))
2916 /* Matched "parameter". */
2917 d = DECL_PARAMETER;
2919 break;
2921 case 'o':
2922 if (match_string_p ("inter"))
2924 /* Matched "pointer". */
2925 d = DECL_POINTER;
2927 break;
2929 case 'r':
2930 ch = gfc_next_ascii_char ();
2931 if (ch == 'i')
2933 if (match_string_p ("vate"))
2935 /* Matched "private". */
2936 d = DECL_PRIVATE;
2939 else if (ch == 'o')
2941 if (match_string_p ("tected"))
2943 /* Matched "protected". */
2944 d = DECL_PROTECTED;
2947 break;
2949 case 'u':
2950 if (match_string_p ("blic"))
2952 /* Matched "public". */
2953 d = DECL_PUBLIC;
2955 break;
2957 break;
2959 case 's':
2960 if (match_string_p ("save"))
2961 d = DECL_SAVE;
2962 break;
2964 case 't':
2965 if (match_string_p ("target"))
2966 d = DECL_TARGET;
2967 break;
2969 case 'v':
2970 gfc_next_ascii_char ();
2971 ch = gfc_next_ascii_char ();
2972 if (ch == 'a')
2974 if (match_string_p ("lue"))
2976 /* Matched "value". */
2977 d = DECL_VALUE;
2980 else if (ch == 'o')
2982 if (match_string_p ("latile"))
2984 /* Matched "volatile". */
2985 d = DECL_VOLATILE;
2988 break;
2992 /* No double colon and no recognizable decl_type, so assume that
2993 we've been looking at something else the whole time. */
2994 if (d == DECL_NONE)
2996 m = MATCH_NO;
2997 goto cleanup;
3000 /* Check to make sure any parens are paired up correctly. */
3001 if (gfc_match_parens () == MATCH_ERROR)
3003 m = MATCH_ERROR;
3004 goto cleanup;
3007 seen[d]++;
3008 seen_at[d] = gfc_current_locus;
3010 if (d == DECL_DIMENSION)
3012 m = gfc_match_array_spec (&current_as);
3014 if (m == MATCH_NO)
3016 gfc_error ("Missing dimension specification at %C");
3017 m = MATCH_ERROR;
3020 if (m == MATCH_ERROR)
3021 goto cleanup;
3025 /* Since we've seen a double colon, we have to be looking at an
3026 attr-spec. This means that we can now issue errors. */
3027 for (d = GFC_DECL_BEGIN; d != GFC_DECL_END; d++)
3028 if (seen[d] > 1)
3030 switch (d)
3032 case DECL_ALLOCATABLE:
3033 attr = "ALLOCATABLE";
3034 break;
3035 case DECL_DIMENSION:
3036 attr = "DIMENSION";
3037 break;
3038 case DECL_EXTERNAL:
3039 attr = "EXTERNAL";
3040 break;
3041 case DECL_IN:
3042 attr = "INTENT (IN)";
3043 break;
3044 case DECL_OUT:
3045 attr = "INTENT (OUT)";
3046 break;
3047 case DECL_INOUT:
3048 attr = "INTENT (IN OUT)";
3049 break;
3050 case DECL_INTRINSIC:
3051 attr = "INTRINSIC";
3052 break;
3053 case DECL_OPTIONAL:
3054 attr = "OPTIONAL";
3055 break;
3056 case DECL_PARAMETER:
3057 attr = "PARAMETER";
3058 break;
3059 case DECL_POINTER:
3060 attr = "POINTER";
3061 break;
3062 case DECL_PROTECTED:
3063 attr = "PROTECTED";
3064 break;
3065 case DECL_PRIVATE:
3066 attr = "PRIVATE";
3067 break;
3068 case DECL_PUBLIC:
3069 attr = "PUBLIC";
3070 break;
3071 case DECL_SAVE:
3072 attr = "SAVE";
3073 break;
3074 case DECL_TARGET:
3075 attr = "TARGET";
3076 break;
3077 case DECL_IS_BIND_C:
3078 attr = "IS_BIND_C";
3079 break;
3080 case DECL_VALUE:
3081 attr = "VALUE";
3082 break;
3083 case DECL_VOLATILE:
3084 attr = "VOLATILE";
3085 break;
3086 default:
3087 attr = NULL; /* This shouldn't happen. */
3090 gfc_error ("Duplicate %s attribute at %L", attr, &seen_at[d]);
3091 m = MATCH_ERROR;
3092 goto cleanup;
3095 /* Now that we've dealt with duplicate attributes, add the attributes
3096 to the current attribute. */
3097 for (d = GFC_DECL_BEGIN; d != GFC_DECL_END; d++)
3099 if (seen[d] == 0)
3100 continue;
3102 if (gfc_current_state () == COMP_DERIVED
3103 && d != DECL_DIMENSION && d != DECL_POINTER
3104 && d != DECL_PRIVATE && d != DECL_PUBLIC
3105 && d != DECL_NONE)
3107 if (d == DECL_ALLOCATABLE)
3109 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: ALLOCATABLE "
3110 "attribute at %C in a TYPE definition")
3111 == FAILURE)
3113 m = MATCH_ERROR;
3114 goto cleanup;
3117 else
3119 gfc_error ("Attribute at %L is not allowed in a TYPE definition",
3120 &seen_at[d]);
3121 m = MATCH_ERROR;
3122 goto cleanup;
3126 if ((d == DECL_PRIVATE || d == DECL_PUBLIC)
3127 && gfc_current_state () != COMP_MODULE)
3129 if (d == DECL_PRIVATE)
3130 attr = "PRIVATE";
3131 else
3132 attr = "PUBLIC";
3133 if (gfc_current_state () == COMP_DERIVED
3134 && gfc_state_stack->previous
3135 && gfc_state_stack->previous->state == COMP_MODULE)
3137 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Attribute %s "
3138 "at %L in a TYPE definition", attr,
3139 &seen_at[d])
3140 == FAILURE)
3142 m = MATCH_ERROR;
3143 goto cleanup;
3146 else
3148 gfc_error ("%s attribute at %L is not allowed outside of the "
3149 "specification part of a module", attr, &seen_at[d]);
3150 m = MATCH_ERROR;
3151 goto cleanup;
3155 switch (d)
3157 case DECL_ALLOCATABLE:
3158 t = gfc_add_allocatable (&current_attr, &seen_at[d]);
3159 break;
3161 case DECL_DIMENSION:
3162 t = gfc_add_dimension (&current_attr, NULL, &seen_at[d]);
3163 break;
3165 case DECL_EXTERNAL:
3166 t = gfc_add_external (&current_attr, &seen_at[d]);
3167 break;
3169 case DECL_IN:
3170 t = gfc_add_intent (&current_attr, INTENT_IN, &seen_at[d]);
3171 break;
3173 case DECL_OUT:
3174 t = gfc_add_intent (&current_attr, INTENT_OUT, &seen_at[d]);
3175 break;
3177 case DECL_INOUT:
3178 t = gfc_add_intent (&current_attr, INTENT_INOUT, &seen_at[d]);
3179 break;
3181 case DECL_INTRINSIC:
3182 t = gfc_add_intrinsic (&current_attr, &seen_at[d]);
3183 break;
3185 case DECL_OPTIONAL:
3186 t = gfc_add_optional (&current_attr, &seen_at[d]);
3187 break;
3189 case DECL_PARAMETER:
3190 t = gfc_add_flavor (&current_attr, FL_PARAMETER, NULL, &seen_at[d]);
3191 break;
3193 case DECL_POINTER:
3194 t = gfc_add_pointer (&current_attr, &seen_at[d]);
3195 break;
3197 case DECL_PROTECTED:
3198 if (gfc_current_ns->proc_name->attr.flavor != FL_MODULE)
3200 gfc_error ("PROTECTED at %C only allowed in specification "
3201 "part of a module");
3202 t = FAILURE;
3203 break;
3206 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PROTECTED "
3207 "attribute at %C")
3208 == FAILURE)
3209 t = FAILURE;
3210 else
3211 t = gfc_add_protected (&current_attr, NULL, &seen_at[d]);
3212 break;
3214 case DECL_PRIVATE:
3215 t = gfc_add_access (&current_attr, ACCESS_PRIVATE, NULL,
3216 &seen_at[d]);
3217 break;
3219 case DECL_PUBLIC:
3220 t = gfc_add_access (&current_attr, ACCESS_PUBLIC, NULL,
3221 &seen_at[d]);
3222 break;
3224 case DECL_SAVE:
3225 t = gfc_add_save (&current_attr, NULL, &seen_at[d]);
3226 break;
3228 case DECL_TARGET:
3229 t = gfc_add_target (&current_attr, &seen_at[d]);
3230 break;
3232 case DECL_IS_BIND_C:
3233 t = gfc_add_is_bind_c(&current_attr, NULL, &seen_at[d], 0);
3234 break;
3236 case DECL_VALUE:
3237 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: VALUE attribute "
3238 "at %C")
3239 == FAILURE)
3240 t = FAILURE;
3241 else
3242 t = gfc_add_value (&current_attr, NULL, &seen_at[d]);
3243 break;
3245 case DECL_VOLATILE:
3246 if (gfc_notify_std (GFC_STD_F2003,
3247 "Fortran 2003: VOLATILE attribute at %C")
3248 == FAILURE)
3249 t = FAILURE;
3250 else
3251 t = gfc_add_volatile (&current_attr, NULL, &seen_at[d]);
3252 break;
3254 default:
3255 gfc_internal_error ("match_attr_spec(): Bad attribute");
3258 if (t == FAILURE)
3260 m = MATCH_ERROR;
3261 goto cleanup;
3265 colon_seen = 1;
3266 return MATCH_YES;
3268 cleanup:
3269 gfc_current_locus = start;
3270 gfc_free_array_spec (current_as);
3271 current_as = NULL;
3272 return m;
3276 /* Set the binding label, dest_label, either with the binding label
3277 stored in the given gfc_typespec, ts, or if none was provided, it
3278 will be the symbol name in all lower case, as required by the draft
3279 (J3/04-007, section 15.4.1). If a binding label was given and
3280 there is more than one argument (num_idents), it is an error. */
3282 gfc_try
3283 set_binding_label (char *dest_label, const char *sym_name, int num_idents)
3285 if (num_idents > 1 && has_name_equals)
3287 gfc_error ("Multiple identifiers provided with "
3288 "single NAME= specifier at %C");
3289 return FAILURE;
3292 if (curr_binding_label[0] != '\0')
3294 /* Binding label given; store in temp holder til have sym. */
3295 strcpy (dest_label, curr_binding_label);
3297 else
3299 /* No binding label given, and the NAME= specifier did not exist,
3300 which means there was no NAME="". */
3301 if (sym_name != NULL && has_name_equals == 0)
3302 strcpy (dest_label, sym_name);
3305 return SUCCESS;
3309 /* Set the status of the given common block as being BIND(C) or not,
3310 depending on the given parameter, is_bind_c. */
3312 void
3313 set_com_block_bind_c (gfc_common_head *com_block, int is_bind_c)
3315 com_block->is_bind_c = is_bind_c;
3316 return;
3320 /* Verify that the given gfc_typespec is for a C interoperable type. */
3322 gfc_try
3323 verify_c_interop (gfc_typespec *ts)
3325 if (ts->type == BT_DERIVED && ts->derived != NULL)
3326 return (ts->derived->ts.is_c_interop ? SUCCESS : FAILURE);
3327 else if (ts->is_c_interop != 1)
3328 return FAILURE;
3330 return SUCCESS;
3334 /* Verify that the variables of a given common block, which has been
3335 defined with the attribute specifier bind(c), to be of a C
3336 interoperable type. Errors will be reported here, if
3337 encountered. */
3339 gfc_try
3340 verify_com_block_vars_c_interop (gfc_common_head *com_block)
3342 gfc_symbol *curr_sym = NULL;
3343 gfc_try retval = SUCCESS;
3345 curr_sym = com_block->head;
3347 /* Make sure we have at least one symbol. */
3348 if (curr_sym == NULL)
3349 return retval;
3351 /* Here we know we have a symbol, so we'll execute this loop
3352 at least once. */
3355 /* The second to last param, 1, says this is in a common block. */
3356 retval = verify_bind_c_sym (curr_sym, &(curr_sym->ts), 1, com_block);
3357 curr_sym = curr_sym->common_next;
3358 } while (curr_sym != NULL);
3360 return retval;
3364 /* Verify that a given BIND(C) symbol is C interoperable. If it is not,
3365 an appropriate error message is reported. */
3367 gfc_try
3368 verify_bind_c_sym (gfc_symbol *tmp_sym, gfc_typespec *ts,
3369 int is_in_common, gfc_common_head *com_block)
3371 bool bind_c_function = false;
3372 gfc_try retval = SUCCESS;
3374 if (tmp_sym->attr.function && tmp_sym->attr.is_bind_c)
3375 bind_c_function = true;
3377 if (tmp_sym->attr.function && tmp_sym->result != NULL)
3379 tmp_sym = tmp_sym->result;
3380 /* Make sure it wasn't an implicitly typed result. */
3381 if (tmp_sym->attr.implicit_type)
3383 gfc_warning ("Implicitly declared BIND(C) function '%s' at "
3384 "%L may not be C interoperable", tmp_sym->name,
3385 &tmp_sym->declared_at);
3386 tmp_sym->ts.f90_type = tmp_sym->ts.type;
3387 /* Mark it as C interoperable to prevent duplicate warnings. */
3388 tmp_sym->ts.is_c_interop = 1;
3389 tmp_sym->attr.is_c_interop = 1;
3393 /* Here, we know we have the bind(c) attribute, so if we have
3394 enough type info, then verify that it's a C interop kind.
3395 The info could be in the symbol already, or possibly still in
3396 the given ts (current_ts), so look in both. */
3397 if (tmp_sym->ts.type != BT_UNKNOWN || ts->type != BT_UNKNOWN)
3399 if (verify_c_interop (&(tmp_sym->ts)) != SUCCESS)
3401 /* See if we're dealing with a sym in a common block or not. */
3402 if (is_in_common == 1)
3404 gfc_warning ("Variable '%s' in common block '%s' at %L "
3405 "may not be a C interoperable "
3406 "kind though common block '%s' is BIND(C)",
3407 tmp_sym->name, com_block->name,
3408 &(tmp_sym->declared_at), com_block->name);
3410 else
3412 if (tmp_sym->ts.type == BT_DERIVED || ts->type == BT_DERIVED)
3413 gfc_error ("Type declaration '%s' at %L is not C "
3414 "interoperable but it is BIND(C)",
3415 tmp_sym->name, &(tmp_sym->declared_at));
3416 else
3417 gfc_warning ("Variable '%s' at %L "
3418 "may not be a C interoperable "
3419 "kind but it is bind(c)",
3420 tmp_sym->name, &(tmp_sym->declared_at));
3424 /* Variables declared w/in a common block can't be bind(c)
3425 since there's no way for C to see these variables, so there's
3426 semantically no reason for the attribute. */
3427 if (is_in_common == 1 && tmp_sym->attr.is_bind_c == 1)
3429 gfc_error ("Variable '%s' in common block '%s' at "
3430 "%L cannot be declared with BIND(C) "
3431 "since it is not a global",
3432 tmp_sym->name, com_block->name,
3433 &(tmp_sym->declared_at));
3434 retval = FAILURE;
3437 /* Scalar variables that are bind(c) can not have the pointer
3438 or allocatable attributes. */
3439 if (tmp_sym->attr.is_bind_c == 1)
3441 if (tmp_sym->attr.pointer == 1)
3443 gfc_error ("Variable '%s' at %L cannot have both the "
3444 "POINTER and BIND(C) attributes",
3445 tmp_sym->name, &(tmp_sym->declared_at));
3446 retval = FAILURE;
3449 if (tmp_sym->attr.allocatable == 1)
3451 gfc_error ("Variable '%s' at %L cannot have both the "
3452 "ALLOCATABLE and BIND(C) attributes",
3453 tmp_sym->name, &(tmp_sym->declared_at));
3454 retval = FAILURE;
3459 /* If it is a BIND(C) function, make sure the return value is a
3460 scalar value. The previous tests in this function made sure
3461 the type is interoperable. */
3462 if (bind_c_function && tmp_sym->as != NULL)
3463 gfc_error ("Return type of BIND(C) function '%s' at %L cannot "
3464 "be an array", tmp_sym->name, &(tmp_sym->declared_at));
3466 /* BIND(C) functions can not return a character string. */
3467 if (bind_c_function && tmp_sym->ts.type == BT_CHARACTER)
3468 if (tmp_sym->ts.cl == NULL || tmp_sym->ts.cl->length == NULL
3469 || tmp_sym->ts.cl->length->expr_type != EXPR_CONSTANT
3470 || mpz_cmp_si (tmp_sym->ts.cl->length->value.integer, 1) != 0)
3471 gfc_error ("Return type of BIND(C) function '%s' at %L cannot "
3472 "be a character string", tmp_sym->name,
3473 &(tmp_sym->declared_at));
3476 /* See if the symbol has been marked as private. If it has, make sure
3477 there is no binding label and warn the user if there is one. */
3478 if (tmp_sym->attr.access == ACCESS_PRIVATE
3479 && tmp_sym->binding_label[0] != '\0')
3480 /* Use gfc_warning_now because we won't say that the symbol fails
3481 just because of this. */
3482 gfc_warning_now ("Symbol '%s' at %L is marked PRIVATE but has been "
3483 "given the binding label '%s'", tmp_sym->name,
3484 &(tmp_sym->declared_at), tmp_sym->binding_label);
3486 return retval;
3490 /* Set the appropriate fields for a symbol that's been declared as
3491 BIND(C) (the is_bind_c flag and the binding label), and verify that
3492 the type is C interoperable. Errors are reported by the functions
3493 used to set/test these fields. */
3495 gfc_try
3496 set_verify_bind_c_sym (gfc_symbol *tmp_sym, int num_idents)
3498 gfc_try retval = SUCCESS;
3500 /* TODO: Do we need to make sure the vars aren't marked private? */
3502 /* Set the is_bind_c bit in symbol_attribute. */
3503 gfc_add_is_bind_c (&(tmp_sym->attr), tmp_sym->name, &gfc_current_locus, 0);
3505 if (set_binding_label (tmp_sym->binding_label, tmp_sym->name,
3506 num_idents) != SUCCESS)
3507 return FAILURE;
3509 return retval;
3513 /* Set the fields marking the given common block as BIND(C), including
3514 a binding label, and report any errors encountered. */
3516 gfc_try
3517 set_verify_bind_c_com_block (gfc_common_head *com_block, int num_idents)
3519 gfc_try retval = SUCCESS;
3521 /* destLabel, common name, typespec (which may have binding label). */
3522 if (set_binding_label (com_block->binding_label, com_block->name, num_idents)
3523 != SUCCESS)
3524 return FAILURE;
3526 /* Set the given common block (com_block) to being bind(c) (1). */
3527 set_com_block_bind_c (com_block, 1);
3529 return retval;
3533 /* Retrieve the list of one or more identifiers that the given bind(c)
3534 attribute applies to. */
3536 gfc_try
3537 get_bind_c_idents (void)
3539 char name[GFC_MAX_SYMBOL_LEN + 1];
3540 int num_idents = 0;
3541 gfc_symbol *tmp_sym = NULL;
3542 match found_id;
3543 gfc_common_head *com_block = NULL;
3545 if (gfc_match_name (name) == MATCH_YES)
3547 found_id = MATCH_YES;
3548 gfc_get_ha_symbol (name, &tmp_sym);
3550 else if (match_common_name (name) == MATCH_YES)
3552 found_id = MATCH_YES;
3553 com_block = gfc_get_common (name, 0);
3555 else
3557 gfc_error ("Need either entity or common block name for "
3558 "attribute specification statement at %C");
3559 return FAILURE;
3562 /* Save the current identifier and look for more. */
3565 /* Increment the number of identifiers found for this spec stmt. */
3566 num_idents++;
3568 /* Make sure we have a sym or com block, and verify that it can
3569 be bind(c). Set the appropriate field(s) and look for more
3570 identifiers. */
3571 if (tmp_sym != NULL || com_block != NULL)
3573 if (tmp_sym != NULL)
3575 if (set_verify_bind_c_sym (tmp_sym, num_idents)
3576 != SUCCESS)
3577 return FAILURE;
3579 else
3581 if (set_verify_bind_c_com_block(com_block, num_idents)
3582 != SUCCESS)
3583 return FAILURE;
3586 /* Look to see if we have another identifier. */
3587 tmp_sym = NULL;
3588 if (gfc_match_eos () == MATCH_YES)
3589 found_id = MATCH_NO;
3590 else if (gfc_match_char (',') != MATCH_YES)
3591 found_id = MATCH_NO;
3592 else if (gfc_match_name (name) == MATCH_YES)
3594 found_id = MATCH_YES;
3595 gfc_get_ha_symbol (name, &tmp_sym);
3597 else if (match_common_name (name) == MATCH_YES)
3599 found_id = MATCH_YES;
3600 com_block = gfc_get_common (name, 0);
3602 else
3604 gfc_error ("Missing entity or common block name for "
3605 "attribute specification statement at %C");
3606 return FAILURE;
3609 else
3611 gfc_internal_error ("Missing symbol");
3613 } while (found_id == MATCH_YES);
3615 /* if we get here we were successful */
3616 return SUCCESS;
3620 /* Try and match a BIND(C) attribute specification statement. */
3622 match
3623 gfc_match_bind_c_stmt (void)
3625 match found_match = MATCH_NO;
3626 gfc_typespec *ts;
3628 ts = &current_ts;
3630 /* This may not be necessary. */
3631 gfc_clear_ts (ts);
3632 /* Clear the temporary binding label holder. */
3633 curr_binding_label[0] = '\0';
3635 /* Look for the bind(c). */
3636 found_match = gfc_match_bind_c (NULL, true);
3638 if (found_match == MATCH_YES)
3640 /* Look for the :: now, but it is not required. */
3641 gfc_match (" :: ");
3643 /* Get the identifier(s) that needs to be updated. This may need to
3644 change to hand the flag(s) for the attr specified so all identifiers
3645 found can have all appropriate parts updated (assuming that the same
3646 spec stmt can have multiple attrs, such as both bind(c) and
3647 allocatable...). */
3648 if (get_bind_c_idents () != SUCCESS)
3649 /* Error message should have printed already. */
3650 return MATCH_ERROR;
3653 return found_match;
3657 /* Match a data declaration statement. */
3659 match
3660 gfc_match_data_decl (void)
3662 gfc_symbol *sym;
3663 match m;
3664 int elem;
3666 num_idents_on_line = 0;
3668 m = gfc_match_type_spec (&current_ts, 0);
3669 if (m != MATCH_YES)
3670 return m;
3672 if (current_ts.type == BT_DERIVED && gfc_current_state () != COMP_DERIVED)
3674 sym = gfc_use_derived (current_ts.derived);
3676 if (sym == NULL)
3678 m = MATCH_ERROR;
3679 goto cleanup;
3682 current_ts.derived = sym;
3685 m = match_attr_spec ();
3686 if (m == MATCH_ERROR)
3688 m = MATCH_NO;
3689 goto cleanup;
3692 if (current_ts.type == BT_DERIVED && current_ts.derived->components == NULL
3693 && !current_ts.derived->attr.zero_comp)
3696 if (current_attr.pointer && gfc_current_state () == COMP_DERIVED)
3697 goto ok;
3699 gfc_find_symbol (current_ts.derived->name,
3700 current_ts.derived->ns->parent, 1, &sym);
3702 /* Any symbol that we find had better be a type definition
3703 which has its components defined. */
3704 if (sym != NULL && sym->attr.flavor == FL_DERIVED
3705 && (current_ts.derived->components != NULL
3706 || current_ts.derived->attr.zero_comp))
3707 goto ok;
3709 /* Now we have an error, which we signal, and then fix up
3710 because the knock-on is plain and simple confusing. */
3711 gfc_error_now ("Derived type at %C has not been previously defined "
3712 "and so cannot appear in a derived type definition");
3713 current_attr.pointer = 1;
3714 goto ok;
3718 /* If we have an old-style character declaration, and no new-style
3719 attribute specifications, then there a comma is optional between
3720 the type specification and the variable list. */
3721 if (m == MATCH_NO && current_ts.type == BT_CHARACTER && old_char_selector)
3722 gfc_match_char (',');
3724 /* Give the types/attributes to symbols that follow. Give the element
3725 a number so that repeat character length expressions can be copied. */
3726 elem = 1;
3727 for (;;)
3729 num_idents_on_line++;
3730 m = variable_decl (elem++);
3731 if (m == MATCH_ERROR)
3732 goto cleanup;
3733 if (m == MATCH_NO)
3734 break;
3736 if (gfc_match_eos () == MATCH_YES)
3737 goto cleanup;
3738 if (gfc_match_char (',') != MATCH_YES)
3739 break;
3742 if (gfc_error_flag_test () == 0)
3743 gfc_error ("Syntax error in data declaration at %C");
3744 m = MATCH_ERROR;
3746 gfc_free_data_all (gfc_current_ns);
3748 cleanup:
3749 gfc_free_array_spec (current_as);
3750 current_as = NULL;
3751 return m;
3755 /* Match a prefix associated with a function or subroutine
3756 declaration. If the typespec pointer is nonnull, then a typespec
3757 can be matched. Note that if nothing matches, MATCH_YES is
3758 returned (the null string was matched). */
3760 match
3761 gfc_match_prefix (gfc_typespec *ts)
3763 bool seen_type;
3765 gfc_clear_attr (&current_attr);
3766 seen_type = 0;
3768 gcc_assert (!gfc_matching_prefix);
3769 gfc_matching_prefix = true;
3771 loop:
3772 if (!seen_type && ts != NULL
3773 && gfc_match_type_spec (ts, 0) == MATCH_YES
3774 && gfc_match_space () == MATCH_YES)
3777 seen_type = 1;
3778 goto loop;
3781 if (gfc_match ("elemental% ") == MATCH_YES)
3783 if (gfc_add_elemental (&current_attr, NULL) == FAILURE)
3784 goto error;
3786 goto loop;
3789 if (gfc_match ("pure% ") == MATCH_YES)
3791 if (gfc_add_pure (&current_attr, NULL) == FAILURE)
3792 goto error;
3794 goto loop;
3797 if (gfc_match ("recursive% ") == MATCH_YES)
3799 if (gfc_add_recursive (&current_attr, NULL) == FAILURE)
3800 goto error;
3802 goto loop;
3805 /* At this point, the next item is not a prefix. */
3806 gcc_assert (gfc_matching_prefix);
3807 gfc_matching_prefix = false;
3808 return MATCH_YES;
3810 error:
3811 gcc_assert (gfc_matching_prefix);
3812 gfc_matching_prefix = false;
3813 return MATCH_ERROR;
3817 /* Copy attributes matched by gfc_match_prefix() to attributes on a symbol. */
3819 static gfc_try
3820 copy_prefix (symbol_attribute *dest, locus *where)
3822 if (current_attr.pure && gfc_add_pure (dest, where) == FAILURE)
3823 return FAILURE;
3825 if (current_attr.elemental && gfc_add_elemental (dest, where) == FAILURE)
3826 return FAILURE;
3828 if (current_attr.recursive && gfc_add_recursive (dest, where) == FAILURE)
3829 return FAILURE;
3831 return SUCCESS;
3835 /* Match a formal argument list. */
3837 match
3838 gfc_match_formal_arglist (gfc_symbol *progname, int st_flag, int null_flag)
3840 gfc_formal_arglist *head, *tail, *p, *q;
3841 char name[GFC_MAX_SYMBOL_LEN + 1];
3842 gfc_symbol *sym;
3843 match m;
3845 head = tail = NULL;
3847 if (gfc_match_char ('(') != MATCH_YES)
3849 if (null_flag)
3850 goto ok;
3851 return MATCH_NO;
3854 if (gfc_match_char (')') == MATCH_YES)
3855 goto ok;
3857 for (;;)
3859 if (gfc_match_char ('*') == MATCH_YES)
3860 sym = NULL;
3861 else
3863 m = gfc_match_name (name);
3864 if (m != MATCH_YES)
3865 goto cleanup;
3867 if (gfc_get_symbol (name, NULL, &sym))
3868 goto cleanup;
3871 p = gfc_get_formal_arglist ();
3873 if (head == NULL)
3874 head = tail = p;
3875 else
3877 tail->next = p;
3878 tail = p;
3881 tail->sym = sym;
3883 /* We don't add the VARIABLE flavor because the name could be a
3884 dummy procedure. We don't apply these attributes to formal
3885 arguments of statement functions. */
3886 if (sym != NULL && !st_flag
3887 && (gfc_add_dummy (&sym->attr, sym->name, NULL) == FAILURE
3888 || gfc_missing_attr (&sym->attr, NULL) == FAILURE))
3890 m = MATCH_ERROR;
3891 goto cleanup;
3894 /* The name of a program unit can be in a different namespace,
3895 so check for it explicitly. After the statement is accepted,
3896 the name is checked for especially in gfc_get_symbol(). */
3897 if (gfc_new_block != NULL && sym != NULL
3898 && strcmp (sym->name, gfc_new_block->name) == 0)
3900 gfc_error ("Name '%s' at %C is the name of the procedure",
3901 sym->name);
3902 m = MATCH_ERROR;
3903 goto cleanup;
3906 if (gfc_match_char (')') == MATCH_YES)
3907 goto ok;
3909 m = gfc_match_char (',');
3910 if (m != MATCH_YES)
3912 gfc_error ("Unexpected junk in formal argument list at %C");
3913 goto cleanup;
3918 /* Check for duplicate symbols in the formal argument list. */
3919 if (head != NULL)
3921 for (p = head; p->next; p = p->next)
3923 if (p->sym == NULL)
3924 continue;
3926 for (q = p->next; q; q = q->next)
3927 if (p->sym == q->sym)
3929 gfc_error ("Duplicate symbol '%s' in formal argument list "
3930 "at %C", p->sym->name);
3932 m = MATCH_ERROR;
3933 goto cleanup;
3938 if (gfc_add_explicit_interface (progname, IFSRC_DECL, head, NULL)
3939 == FAILURE)
3941 m = MATCH_ERROR;
3942 goto cleanup;
3945 return MATCH_YES;
3947 cleanup:
3948 gfc_free_formal_arglist (head);
3949 return m;
3953 /* Match a RESULT specification following a function declaration or
3954 ENTRY statement. Also matches the end-of-statement. */
3956 static match
3957 match_result (gfc_symbol *function, gfc_symbol **result)
3959 char name[GFC_MAX_SYMBOL_LEN + 1];
3960 gfc_symbol *r;
3961 match m;
3963 if (gfc_match (" result (") != MATCH_YES)
3964 return MATCH_NO;
3966 m = gfc_match_name (name);
3967 if (m != MATCH_YES)
3968 return m;
3970 /* Get the right paren, and that's it because there could be the
3971 bind(c) attribute after the result clause. */
3972 if (gfc_match_char(')') != MATCH_YES)
3974 /* TODO: should report the missing right paren here. */
3975 return MATCH_ERROR;
3978 if (strcmp (function->name, name) == 0)
3980 gfc_error ("RESULT variable at %C must be different than function name");
3981 return MATCH_ERROR;
3984 if (gfc_get_symbol (name, NULL, &r))
3985 return MATCH_ERROR;
3987 if (gfc_add_result (&r->attr, r->name, NULL) == FAILURE)
3988 return MATCH_ERROR;
3990 *result = r;
3992 return MATCH_YES;
3996 /* Match a function suffix, which could be a combination of a result
3997 clause and BIND(C), either one, or neither. The draft does not
3998 require them to come in a specific order. */
4000 match
4001 gfc_match_suffix (gfc_symbol *sym, gfc_symbol **result)
4003 match is_bind_c; /* Found bind(c). */
4004 match is_result; /* Found result clause. */
4005 match found_match; /* Status of whether we've found a good match. */
4006 char peek_char; /* Character we're going to peek at. */
4007 bool allow_binding_name;
4009 /* Initialize to having found nothing. */
4010 found_match = MATCH_NO;
4011 is_bind_c = MATCH_NO;
4012 is_result = MATCH_NO;
4014 /* Get the next char to narrow between result and bind(c). */
4015 gfc_gobble_whitespace ();
4016 peek_char = gfc_peek_ascii_char ();
4018 /* C binding names are not allowed for internal procedures. */
4019 if (gfc_current_state () == COMP_CONTAINS
4020 && sym->ns->proc_name->attr.flavor != FL_MODULE)
4021 allow_binding_name = false;
4022 else
4023 allow_binding_name = true;
4025 switch (peek_char)
4027 case 'r':
4028 /* Look for result clause. */
4029 is_result = match_result (sym, result);
4030 if (is_result == MATCH_YES)
4032 /* Now see if there is a bind(c) after it. */
4033 is_bind_c = gfc_match_bind_c (sym, allow_binding_name);
4034 /* We've found the result clause and possibly bind(c). */
4035 found_match = MATCH_YES;
4037 else
4038 /* This should only be MATCH_ERROR. */
4039 found_match = is_result;
4040 break;
4041 case 'b':
4042 /* Look for bind(c) first. */
4043 is_bind_c = gfc_match_bind_c (sym, allow_binding_name);
4044 if (is_bind_c == MATCH_YES)
4046 /* Now see if a result clause followed it. */
4047 is_result = match_result (sym, result);
4048 found_match = MATCH_YES;
4050 else
4052 /* Should only be a MATCH_ERROR if we get here after seeing 'b'. */
4053 found_match = MATCH_ERROR;
4055 break;
4056 default:
4057 gfc_error ("Unexpected junk after function declaration at %C");
4058 found_match = MATCH_ERROR;
4059 break;
4062 if (is_bind_c == MATCH_YES)
4064 /* Fortran 2008 draft allows BIND(C) for internal procedures. */
4065 if (gfc_current_state () == COMP_CONTAINS
4066 && sym->ns->proc_name->attr.flavor != FL_MODULE
4067 && gfc_notify_std (GFC_STD_F2008, "Fortran 2008: BIND(C) attribute "
4068 "at %L may not be specified for an internal "
4069 "procedure", &gfc_current_locus)
4070 == FAILURE)
4071 return MATCH_ERROR;
4073 if (gfc_add_is_bind_c (&(sym->attr), sym->name, &gfc_current_locus, 1)
4074 == FAILURE)
4075 return MATCH_ERROR;
4078 return found_match;
4082 /* Procedure pointer return value without RESULT statement:
4083 Add "hidden" result variable named "ppr@". */
4085 static gfc_try
4086 add_hidden_procptr_result (gfc_symbol *sym)
4088 bool case1,case2;
4090 if (gfc_notification_std (GFC_STD_F2003) == ERROR)
4091 return FAILURE;
4093 /* First usage case: PROCEDURE and EXTERNAL statements. */
4094 case1 = gfc_current_state () == COMP_FUNCTION && gfc_current_block ()
4095 && strcmp (gfc_current_block ()->name, sym->name) == 0
4096 && sym->attr.external;
4097 /* Second usage case: INTERFACE statements. */
4098 case2 = gfc_current_state () == COMP_INTERFACE && gfc_state_stack->previous
4099 && gfc_state_stack->previous->state == COMP_FUNCTION
4100 && strcmp (gfc_state_stack->previous->sym->name, sym->name) == 0;
4102 if (case1 || case2)
4104 gfc_symtree *stree;
4105 if (case1)
4106 gfc_get_sym_tree ("ppr@", gfc_current_ns, &stree);
4107 else if (case2)
4109 gfc_symtree *st2;
4110 gfc_get_sym_tree ("ppr@", gfc_current_ns->parent, &stree);
4111 st2 = gfc_new_symtree (&gfc_current_ns->sym_root, "ppr@");
4112 st2->n.sym = stree->n.sym;
4114 sym->result = stree->n.sym;
4116 sym->result->attr.proc_pointer = sym->attr.proc_pointer;
4117 sym->result->attr.pointer = sym->attr.pointer;
4118 sym->result->attr.external = sym->attr.external;
4119 sym->result->attr.referenced = sym->attr.referenced;
4120 sym->result->ts = sym->ts;
4121 sym->attr.proc_pointer = 0;
4122 sym->attr.pointer = 0;
4123 sym->attr.external = 0;
4124 if (sym->result->attr.external && sym->result->attr.pointer)
4126 sym->result->attr.pointer = 0;
4127 sym->result->attr.proc_pointer = 1;
4130 return gfc_add_result (&sym->result->attr, sym->result->name, NULL);
4132 /* POINTER after PROCEDURE/EXTERNAL/INTERFACE statement. */
4133 else if (sym->attr.function && !sym->attr.external && sym->attr.pointer
4134 && sym->result && sym->result != sym && sym->result->attr.external
4135 && sym == gfc_current_ns->proc_name
4136 && sym == sym->result->ns->proc_name
4137 && strcmp ("ppr@", sym->result->name) == 0)
4139 sym->result->attr.proc_pointer = 1;
4140 sym->attr.pointer = 0;
4141 return SUCCESS;
4143 else
4144 return FAILURE;
4148 /* Match the interface for a PROCEDURE declaration,
4149 including brackets (R1212). */
4151 static match
4152 match_procedure_interface (gfc_symbol **proc_if)
4154 match m;
4155 locus old_loc, entry_loc;
4156 old_loc = entry_loc = gfc_current_locus;
4158 gfc_clear_ts (&current_ts);
4160 if (gfc_match (" (") != MATCH_YES)
4162 gfc_current_locus = entry_loc;
4163 return MATCH_NO;
4166 /* Get the type spec. for the procedure interface. */
4167 old_loc = gfc_current_locus;
4168 m = gfc_match_type_spec (&current_ts, 0);
4169 gfc_gobble_whitespace ();
4170 if (m == MATCH_YES || (m == MATCH_NO && gfc_peek_ascii_char () == ')'))
4171 goto got_ts;
4173 if (m == MATCH_ERROR)
4174 return m;
4176 gfc_current_locus = old_loc;
4178 /* Get the name of the procedure or abstract interface
4179 to inherit the interface from. */
4180 m = gfc_match_symbol (proc_if, 1);
4181 if (m != MATCH_YES)
4182 return m;
4184 /* Various interface checks. */
4185 if (*proc_if)
4187 (*proc_if)->refs++;
4188 /* Resolve interface if possible. That way, attr.procedure is only set
4189 if it is declared by a later procedure-declaration-stmt, which is
4190 invalid per C1212. */
4191 while ((*proc_if)->ts.interface)
4192 *proc_if = (*proc_if)->ts.interface;
4194 if ((*proc_if)->generic)
4196 gfc_error ("Interface '%s' at %C may not be generic",
4197 (*proc_if)->name);
4198 return MATCH_ERROR;
4200 if ((*proc_if)->attr.proc == PROC_ST_FUNCTION)
4202 gfc_error ("Interface '%s' at %C may not be a statement function",
4203 (*proc_if)->name);
4204 return MATCH_ERROR;
4206 /* Handle intrinsic procedures. */
4207 if (!((*proc_if)->attr.external || (*proc_if)->attr.use_assoc
4208 || (*proc_if)->attr.if_source == IFSRC_IFBODY)
4209 && (gfc_is_intrinsic ((*proc_if), 0, gfc_current_locus)
4210 || gfc_is_intrinsic ((*proc_if), 1, gfc_current_locus)))
4211 (*proc_if)->attr.intrinsic = 1;
4212 if ((*proc_if)->attr.intrinsic
4213 && !gfc_intrinsic_actual_ok ((*proc_if)->name, 0))
4215 gfc_error ("Intrinsic procedure '%s' not allowed "
4216 "in PROCEDURE statement at %C", (*proc_if)->name);
4217 return MATCH_ERROR;
4221 got_ts:
4222 if (gfc_match (" )") != MATCH_YES)
4224 gfc_current_locus = entry_loc;
4225 return MATCH_NO;
4228 return MATCH_YES;
4232 /* Match a PROCEDURE declaration (R1211). */
4234 static match
4235 match_procedure_decl (void)
4237 match m;
4238 gfc_symbol *sym, *proc_if = NULL;
4239 int num;
4240 gfc_expr *initializer = NULL;
4242 /* Parse interface (with brackets). */
4243 m = match_procedure_interface (&proc_if);
4244 if (m != MATCH_YES)
4245 return m;
4247 /* Parse attributes (with colons). */
4248 m = match_attr_spec();
4249 if (m == MATCH_ERROR)
4250 return MATCH_ERROR;
4252 /* Get procedure symbols. */
4253 for(num=1;;num++)
4255 m = gfc_match_symbol (&sym, 0);
4256 if (m == MATCH_NO)
4257 goto syntax;
4258 else if (m == MATCH_ERROR)
4259 return m;
4261 /* Add current_attr to the symbol attributes. */
4262 if (gfc_copy_attr (&sym->attr, &current_attr, NULL) == FAILURE)
4263 return MATCH_ERROR;
4265 if (sym->attr.is_bind_c)
4267 /* Check for C1218. */
4268 if (!proc_if || !proc_if->attr.is_bind_c)
4270 gfc_error ("BIND(C) attribute at %C requires "
4271 "an interface with BIND(C)");
4272 return MATCH_ERROR;
4274 /* Check for C1217. */
4275 if (has_name_equals && sym->attr.pointer)
4277 gfc_error ("BIND(C) procedure with NAME may not have "
4278 "POINTER attribute at %C");
4279 return MATCH_ERROR;
4281 if (has_name_equals && sym->attr.dummy)
4283 gfc_error ("Dummy procedure at %C may not have "
4284 "BIND(C) attribute with NAME");
4285 return MATCH_ERROR;
4287 /* Set binding label for BIND(C). */
4288 if (set_binding_label (sym->binding_label, sym->name, num) != SUCCESS)
4289 return MATCH_ERROR;
4292 if (gfc_add_external (&sym->attr, NULL) == FAILURE)
4293 return MATCH_ERROR;
4295 if (add_hidden_procptr_result (sym) == SUCCESS)
4296 sym = sym->result;
4298 if (gfc_add_proc (&sym->attr, sym->name, NULL) == FAILURE)
4299 return MATCH_ERROR;
4301 /* Set interface. */
4302 if (proc_if != NULL)
4304 if (sym->ts.type != BT_UNKNOWN)
4306 gfc_error ("Procedure '%s' at %L already has basic type of %s",
4307 sym->name, &gfc_current_locus,
4308 gfc_basic_typename (sym->ts.type));
4309 return MATCH_ERROR;
4311 sym->ts.interface = proc_if;
4312 sym->attr.untyped = 1;
4313 sym->attr.if_source = IFSRC_IFBODY;
4315 else if (current_ts.type != BT_UNKNOWN)
4317 if (gfc_add_type (sym, &current_ts, &gfc_current_locus) == FAILURE)
4318 return MATCH_ERROR;
4319 sym->ts.interface = gfc_new_symbol ("", gfc_current_ns);
4320 sym->ts.interface->ts = current_ts;
4321 sym->ts.interface->attr.function = 1;
4322 sym->attr.function = sym->ts.interface->attr.function;
4323 sym->attr.if_source = IFSRC_UNKNOWN;
4326 if (gfc_match (" =>") == MATCH_YES)
4328 if (!current_attr.pointer)
4330 gfc_error ("Initialization at %C isn't for a pointer variable");
4331 m = MATCH_ERROR;
4332 goto cleanup;
4335 m = gfc_match_null (&initializer);
4336 if (m == MATCH_NO)
4338 gfc_error ("Pointer initialization requires a NULL() at %C");
4339 m = MATCH_ERROR;
4342 if (gfc_pure (NULL))
4344 gfc_error ("Initialization of pointer at %C is not allowed in "
4345 "a PURE procedure");
4346 m = MATCH_ERROR;
4349 if (m != MATCH_YES)
4350 goto cleanup;
4352 if (add_init_expr_to_sym (sym->name, &initializer, &gfc_current_locus)
4353 != SUCCESS)
4354 goto cleanup;
4358 gfc_set_sym_referenced (sym);
4360 if (gfc_match_eos () == MATCH_YES)
4361 return MATCH_YES;
4362 if (gfc_match_char (',') != MATCH_YES)
4363 goto syntax;
4366 syntax:
4367 gfc_error ("Syntax error in PROCEDURE statement at %C");
4368 return MATCH_ERROR;
4370 cleanup:
4371 /* Free stuff up and return. */
4372 gfc_free_expr (initializer);
4373 return m;
4377 static match
4378 match_binding_attributes (gfc_typebound_proc* ba, bool generic, bool ppc);
4381 /* Match a procedure pointer component declaration (R445). */
4383 static match
4384 match_ppc_decl (void)
4386 match m;
4387 gfc_symbol *proc_if = NULL;
4388 gfc_typespec ts;
4389 int num;
4390 gfc_component *c;
4391 gfc_expr *initializer = NULL;
4392 gfc_typebound_proc* tb;
4393 char name[GFC_MAX_SYMBOL_LEN + 1];
4395 /* Parse interface (with brackets). */
4396 m = match_procedure_interface (&proc_if);
4397 if (m != MATCH_YES)
4398 goto syntax;
4400 /* Parse attributes. */
4401 tb = XCNEW (gfc_typebound_proc);
4402 tb->where = gfc_current_locus;
4403 m = match_binding_attributes (tb, false, true);
4404 if (m == MATCH_ERROR)
4405 return m;
4407 /* TODO: Implement PASS. */
4408 if (!tb->nopass)
4410 gfc_error ("Procedure Pointer Component with PASS at %C "
4411 "not yet implemented");
4412 return MATCH_ERROR;
4415 gfc_clear_attr (&current_attr);
4416 current_attr.procedure = 1;
4417 current_attr.proc_pointer = 1;
4418 current_attr.access = tb->access;
4419 current_attr.flavor = FL_PROCEDURE;
4421 /* Match the colons (required). */
4422 if (gfc_match (" ::") != MATCH_YES)
4424 gfc_error ("Expected '::' after binding-attributes at %C");
4425 return MATCH_ERROR;
4428 /* Check for C450. */
4429 if (!tb->nopass && proc_if == NULL)
4431 gfc_error("NOPASS or explicit interface required at %C");
4432 return MATCH_ERROR;
4435 /* Match PPC names. */
4436 ts = current_ts;
4437 for(num=1;;num++)
4439 m = gfc_match_name (name);
4440 if (m == MATCH_NO)
4441 goto syntax;
4442 else if (m == MATCH_ERROR)
4443 return m;
4445 if (gfc_add_component (gfc_current_block (), name, &c) == FAILURE)
4446 return MATCH_ERROR;
4448 /* Add current_attr to the symbol attributes. */
4449 if (gfc_copy_attr (&c->attr, &current_attr, NULL) == FAILURE)
4450 return MATCH_ERROR;
4452 if (gfc_add_external (&c->attr, NULL) == FAILURE)
4453 return MATCH_ERROR;
4455 if (gfc_add_proc (&c->attr, name, NULL) == FAILURE)
4456 return MATCH_ERROR;
4458 /* Set interface. */
4459 if (proc_if != NULL)
4461 c->ts.interface = proc_if;
4462 c->attr.untyped = 1;
4463 c->attr.if_source = IFSRC_IFBODY;
4465 else if (ts.type != BT_UNKNOWN)
4467 c->ts = ts;
4468 c->ts.interface = gfc_new_symbol ("", gfc_current_ns);
4469 c->ts.interface->ts = ts;
4470 c->ts.interface->attr.function = 1;
4471 c->attr.function = c->ts.interface->attr.function;
4472 c->attr.if_source = IFSRC_UNKNOWN;
4475 if (gfc_match (" =>") == MATCH_YES)
4477 m = gfc_match_null (&initializer);
4478 if (m == MATCH_NO)
4480 gfc_error ("Pointer initialization requires a NULL() at %C");
4481 m = MATCH_ERROR;
4483 if (gfc_pure (NULL))
4485 gfc_error ("Initialization of pointer at %C is not allowed in "
4486 "a PURE procedure");
4487 m = MATCH_ERROR;
4489 if (m != MATCH_YES)
4491 gfc_free_expr (initializer);
4492 return m;
4494 c->initializer = initializer;
4497 if (gfc_match_eos () == MATCH_YES)
4498 return MATCH_YES;
4499 if (gfc_match_char (',') != MATCH_YES)
4500 goto syntax;
4503 syntax:
4504 gfc_error ("Syntax error in procedure pointer component at %C");
4505 return MATCH_ERROR;
4509 /* Match a PROCEDURE declaration inside an interface (R1206). */
4511 static match
4512 match_procedure_in_interface (void)
4514 match m;
4515 gfc_symbol *sym;
4516 char name[GFC_MAX_SYMBOL_LEN + 1];
4518 if (current_interface.type == INTERFACE_NAMELESS
4519 || current_interface.type == INTERFACE_ABSTRACT)
4521 gfc_error ("PROCEDURE at %C must be in a generic interface");
4522 return MATCH_ERROR;
4525 for(;;)
4527 m = gfc_match_name (name);
4528 if (m == MATCH_NO)
4529 goto syntax;
4530 else if (m == MATCH_ERROR)
4531 return m;
4532 if (gfc_get_symbol (name, gfc_current_ns->parent, &sym))
4533 return MATCH_ERROR;
4535 if (gfc_add_interface (sym) == FAILURE)
4536 return MATCH_ERROR;
4538 if (gfc_match_eos () == MATCH_YES)
4539 break;
4540 if (gfc_match_char (',') != MATCH_YES)
4541 goto syntax;
4544 return MATCH_YES;
4546 syntax:
4547 gfc_error ("Syntax error in PROCEDURE statement at %C");
4548 return MATCH_ERROR;
4552 /* General matcher for PROCEDURE declarations. */
4554 static match match_procedure_in_type (void);
4556 match
4557 gfc_match_procedure (void)
4559 match m;
4561 switch (gfc_current_state ())
4563 case COMP_NONE:
4564 case COMP_PROGRAM:
4565 case COMP_MODULE:
4566 case COMP_SUBROUTINE:
4567 case COMP_FUNCTION:
4568 m = match_procedure_decl ();
4569 break;
4570 case COMP_INTERFACE:
4571 m = match_procedure_in_interface ();
4572 break;
4573 case COMP_DERIVED:
4574 m = match_ppc_decl ();
4575 break;
4576 case COMP_DERIVED_CONTAINS:
4577 m = match_procedure_in_type ();
4578 break;
4579 default:
4580 return MATCH_NO;
4583 if (m != MATCH_YES)
4584 return m;
4586 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PROCEDURE statement at %C")
4587 == FAILURE)
4588 return MATCH_ERROR;
4590 return m;
4594 /* Warn if a matched procedure has the same name as an intrinsic; this is
4595 simply a wrapper around gfc_warn_intrinsic_shadow that interprets the current
4596 parser-state-stack to find out whether we're in a module. */
4598 static void
4599 warn_intrinsic_shadow (const gfc_symbol* sym, bool func)
4601 bool in_module;
4603 in_module = (gfc_state_stack->previous
4604 && gfc_state_stack->previous->state == COMP_MODULE);
4606 gfc_warn_intrinsic_shadow (sym, in_module, func);
4610 /* Match a function declaration. */
4612 match
4613 gfc_match_function_decl (void)
4615 char name[GFC_MAX_SYMBOL_LEN + 1];
4616 gfc_symbol *sym, *result;
4617 locus old_loc;
4618 match m;
4619 match suffix_match;
4620 match found_match; /* Status returned by match func. */
4622 if (gfc_current_state () != COMP_NONE
4623 && gfc_current_state () != COMP_INTERFACE
4624 && gfc_current_state () != COMP_CONTAINS)
4625 return MATCH_NO;
4627 gfc_clear_ts (&current_ts);
4629 old_loc = gfc_current_locus;
4631 m = gfc_match_prefix (&current_ts);
4632 if (m != MATCH_YES)
4634 gfc_current_locus = old_loc;
4635 return m;
4638 if (gfc_match ("function% %n", name) != MATCH_YES)
4640 gfc_current_locus = old_loc;
4641 return MATCH_NO;
4643 if (get_proc_name (name, &sym, false))
4644 return MATCH_ERROR;
4646 if (add_hidden_procptr_result (sym) == SUCCESS)
4647 sym = sym->result;
4649 gfc_new_block = sym;
4651 m = gfc_match_formal_arglist (sym, 0, 0);
4652 if (m == MATCH_NO)
4654 gfc_error ("Expected formal argument list in function "
4655 "definition at %C");
4656 m = MATCH_ERROR;
4657 goto cleanup;
4659 else if (m == MATCH_ERROR)
4660 goto cleanup;
4662 result = NULL;
4664 /* According to the draft, the bind(c) and result clause can
4665 come in either order after the formal_arg_list (i.e., either
4666 can be first, both can exist together or by themselves or neither
4667 one). Therefore, the match_result can't match the end of the
4668 string, and check for the bind(c) or result clause in either order. */
4669 found_match = gfc_match_eos ();
4671 /* Make sure that it isn't already declared as BIND(C). If it is, it
4672 must have been marked BIND(C) with a BIND(C) attribute and that is
4673 not allowed for procedures. */
4674 if (sym->attr.is_bind_c == 1)
4676 sym->attr.is_bind_c = 0;
4677 if (sym->old_symbol != NULL)
4678 gfc_error_now ("BIND(C) attribute at %L can only be used for "
4679 "variables or common blocks",
4680 &(sym->old_symbol->declared_at));
4681 else
4682 gfc_error_now ("BIND(C) attribute at %L can only be used for "
4683 "variables or common blocks", &gfc_current_locus);
4686 if (found_match != MATCH_YES)
4688 /* If we haven't found the end-of-statement, look for a suffix. */
4689 suffix_match = gfc_match_suffix (sym, &result);
4690 if (suffix_match == MATCH_YES)
4691 /* Need to get the eos now. */
4692 found_match = gfc_match_eos ();
4693 else
4694 found_match = suffix_match;
4697 if(found_match != MATCH_YES)
4698 m = MATCH_ERROR;
4699 else
4701 /* Make changes to the symbol. */
4702 m = MATCH_ERROR;
4704 if (gfc_add_function (&sym->attr, sym->name, NULL) == FAILURE)
4705 goto cleanup;
4707 if (gfc_missing_attr (&sym->attr, NULL) == FAILURE
4708 || copy_prefix (&sym->attr, &sym->declared_at) == FAILURE)
4709 goto cleanup;
4711 /* Delay matching the function characteristics until after the
4712 specification block by signalling kind=-1. */
4713 sym->declared_at = old_loc;
4714 if (current_ts.type != BT_UNKNOWN)
4715 current_ts.kind = -1;
4716 else
4717 current_ts.kind = 0;
4719 if (result == NULL)
4721 if (current_ts.type != BT_UNKNOWN
4722 && gfc_add_type (sym, &current_ts, &gfc_current_locus) == FAILURE)
4723 goto cleanup;
4724 sym->result = sym;
4726 else
4728 if (current_ts.type != BT_UNKNOWN
4729 && gfc_add_type (result, &current_ts, &gfc_current_locus)
4730 == FAILURE)
4731 goto cleanup;
4732 sym->result = result;
4735 /* Warn if this procedure has the same name as an intrinsic. */
4736 warn_intrinsic_shadow (sym, true);
4738 return MATCH_YES;
4741 cleanup:
4742 gfc_current_locus = old_loc;
4743 return m;
4747 /* This is mostly a copy of parse.c(add_global_procedure) but modified to
4748 pass the name of the entry, rather than the gfc_current_block name, and
4749 to return false upon finding an existing global entry. */
4751 static bool
4752 add_global_entry (const char *name, int sub)
4754 gfc_gsymbol *s;
4755 enum gfc_symbol_type type;
4757 s = gfc_get_gsymbol(name);
4758 type = sub ? GSYM_SUBROUTINE : GSYM_FUNCTION;
4760 if (s->defined
4761 || (s->type != GSYM_UNKNOWN
4762 && s->type != type))
4763 gfc_global_used(s, NULL);
4764 else
4766 s->type = type;
4767 s->where = gfc_current_locus;
4768 s->defined = 1;
4769 s->ns = gfc_current_ns;
4770 return true;
4772 return false;
4776 /* Match an ENTRY statement. */
4778 match
4779 gfc_match_entry (void)
4781 gfc_symbol *proc;
4782 gfc_symbol *result;
4783 gfc_symbol *entry;
4784 char name[GFC_MAX_SYMBOL_LEN + 1];
4785 gfc_compile_state state;
4786 match m;
4787 gfc_entry_list *el;
4788 locus old_loc;
4789 bool module_procedure;
4790 char peek_char;
4791 match is_bind_c;
4793 m = gfc_match_name (name);
4794 if (m != MATCH_YES)
4795 return m;
4797 state = gfc_current_state ();
4798 if (state != COMP_SUBROUTINE && state != COMP_FUNCTION)
4800 switch (state)
4802 case COMP_PROGRAM:
4803 gfc_error ("ENTRY statement at %C cannot appear within a PROGRAM");
4804 break;
4805 case COMP_MODULE:
4806 gfc_error ("ENTRY statement at %C cannot appear within a MODULE");
4807 break;
4808 case COMP_BLOCK_DATA:
4809 gfc_error ("ENTRY statement at %C cannot appear within "
4810 "a BLOCK DATA");
4811 break;
4812 case COMP_INTERFACE:
4813 gfc_error ("ENTRY statement at %C cannot appear within "
4814 "an INTERFACE");
4815 break;
4816 case COMP_DERIVED:
4817 gfc_error ("ENTRY statement at %C cannot appear within "
4818 "a DERIVED TYPE block");
4819 break;
4820 case COMP_IF:
4821 gfc_error ("ENTRY statement at %C cannot appear within "
4822 "an IF-THEN block");
4823 break;
4824 case COMP_DO:
4825 gfc_error ("ENTRY statement at %C cannot appear within "
4826 "a DO block");
4827 break;
4828 case COMP_SELECT:
4829 gfc_error ("ENTRY statement at %C cannot appear within "
4830 "a SELECT block");
4831 break;
4832 case COMP_FORALL:
4833 gfc_error ("ENTRY statement at %C cannot appear within "
4834 "a FORALL block");
4835 break;
4836 case COMP_WHERE:
4837 gfc_error ("ENTRY statement at %C cannot appear within "
4838 "a WHERE block");
4839 break;
4840 case COMP_CONTAINS:
4841 gfc_error ("ENTRY statement at %C cannot appear within "
4842 "a contained subprogram");
4843 break;
4844 default:
4845 gfc_internal_error ("gfc_match_entry(): Bad state");
4847 return MATCH_ERROR;
4850 module_procedure = gfc_current_ns->parent != NULL
4851 && gfc_current_ns->parent->proc_name
4852 && gfc_current_ns->parent->proc_name->attr.flavor
4853 == FL_MODULE;
4855 if (gfc_current_ns->parent != NULL
4856 && gfc_current_ns->parent->proc_name
4857 && !module_procedure)
4859 gfc_error("ENTRY statement at %C cannot appear in a "
4860 "contained procedure");
4861 return MATCH_ERROR;
4864 /* Module function entries need special care in get_proc_name
4865 because previous references within the function will have
4866 created symbols attached to the current namespace. */
4867 if (get_proc_name (name, &entry,
4868 gfc_current_ns->parent != NULL
4869 && module_procedure))
4870 return MATCH_ERROR;
4872 proc = gfc_current_block ();
4874 /* Make sure that it isn't already declared as BIND(C). If it is, it
4875 must have been marked BIND(C) with a BIND(C) attribute and that is
4876 not allowed for procedures. */
4877 if (entry->attr.is_bind_c == 1)
4879 entry->attr.is_bind_c = 0;
4880 if (entry->old_symbol != NULL)
4881 gfc_error_now ("BIND(C) attribute at %L can only be used for "
4882 "variables or common blocks",
4883 &(entry->old_symbol->declared_at));
4884 else
4885 gfc_error_now ("BIND(C) attribute at %L can only be used for "
4886 "variables or common blocks", &gfc_current_locus);
4889 /* Check what next non-whitespace character is so we can tell if there
4890 is the required parens if we have a BIND(C). */
4891 gfc_gobble_whitespace ();
4892 peek_char = gfc_peek_ascii_char ();
4894 if (state == COMP_SUBROUTINE)
4896 /* An entry in a subroutine. */
4897 if (!gfc_current_ns->parent && !add_global_entry (name, 1))
4898 return MATCH_ERROR;
4900 m = gfc_match_formal_arglist (entry, 0, 1);
4901 if (m != MATCH_YES)
4902 return MATCH_ERROR;
4904 /* Call gfc_match_bind_c with allow_binding_name = true as ENTRY can
4905 never be an internal procedure. */
4906 is_bind_c = gfc_match_bind_c (entry, true);
4907 if (is_bind_c == MATCH_ERROR)
4908 return MATCH_ERROR;
4909 if (is_bind_c == MATCH_YES)
4911 if (peek_char != '(')
4913 gfc_error ("Missing required parentheses before BIND(C) at %C");
4914 return MATCH_ERROR;
4916 if (gfc_add_is_bind_c (&(entry->attr), entry->name, &(entry->declared_at), 1)
4917 == FAILURE)
4918 return MATCH_ERROR;
4921 if (gfc_add_entry (&entry->attr, entry->name, NULL) == FAILURE
4922 || gfc_add_subroutine (&entry->attr, entry->name, NULL) == FAILURE)
4923 return MATCH_ERROR;
4925 else
4927 /* An entry in a function.
4928 We need to take special care because writing
4929 ENTRY f()
4931 ENTRY f
4932 is allowed, whereas
4933 ENTRY f() RESULT (r)
4934 can't be written as
4935 ENTRY f RESULT (r). */
4936 if (!gfc_current_ns->parent && !add_global_entry (name, 0))
4937 return MATCH_ERROR;
4939 old_loc = gfc_current_locus;
4940 if (gfc_match_eos () == MATCH_YES)
4942 gfc_current_locus = old_loc;
4943 /* Match the empty argument list, and add the interface to
4944 the symbol. */
4945 m = gfc_match_formal_arglist (entry, 0, 1);
4947 else
4948 m = gfc_match_formal_arglist (entry, 0, 0);
4950 if (m != MATCH_YES)
4951 return MATCH_ERROR;
4953 result = NULL;
4955 if (gfc_match_eos () == MATCH_YES)
4957 if (gfc_add_entry (&entry->attr, entry->name, NULL) == FAILURE
4958 || gfc_add_function (&entry->attr, entry->name, NULL) == FAILURE)
4959 return MATCH_ERROR;
4961 entry->result = entry;
4963 else
4965 m = gfc_match_suffix (entry, &result);
4966 if (m == MATCH_NO)
4967 gfc_syntax_error (ST_ENTRY);
4968 if (m != MATCH_YES)
4969 return MATCH_ERROR;
4971 if (result)
4973 if (gfc_add_result (&result->attr, result->name, NULL) == FAILURE
4974 || gfc_add_entry (&entry->attr, result->name, NULL) == FAILURE
4975 || gfc_add_function (&entry->attr, result->name, NULL)
4976 == FAILURE)
4977 return MATCH_ERROR;
4978 entry->result = result;
4980 else
4982 if (gfc_add_entry (&entry->attr, entry->name, NULL) == FAILURE
4983 || gfc_add_function (&entry->attr, entry->name, NULL) == FAILURE)
4984 return MATCH_ERROR;
4985 entry->result = entry;
4990 if (gfc_match_eos () != MATCH_YES)
4992 gfc_syntax_error (ST_ENTRY);
4993 return MATCH_ERROR;
4996 entry->attr.recursive = proc->attr.recursive;
4997 entry->attr.elemental = proc->attr.elemental;
4998 entry->attr.pure = proc->attr.pure;
5000 el = gfc_get_entry_list ();
5001 el->sym = entry;
5002 el->next = gfc_current_ns->entries;
5003 gfc_current_ns->entries = el;
5004 if (el->next)
5005 el->id = el->next->id + 1;
5006 else
5007 el->id = 1;
5009 new_st.op = EXEC_ENTRY;
5010 new_st.ext.entry = el;
5012 return MATCH_YES;
5016 /* Match a subroutine statement, including optional prefixes. */
5018 match
5019 gfc_match_subroutine (void)
5021 char name[GFC_MAX_SYMBOL_LEN + 1];
5022 gfc_symbol *sym;
5023 match m;
5024 match is_bind_c;
5025 char peek_char;
5026 bool allow_binding_name;
5028 if (gfc_current_state () != COMP_NONE
5029 && gfc_current_state () != COMP_INTERFACE
5030 && gfc_current_state () != COMP_CONTAINS)
5031 return MATCH_NO;
5033 m = gfc_match_prefix (NULL);
5034 if (m != MATCH_YES)
5035 return m;
5037 m = gfc_match ("subroutine% %n", name);
5038 if (m != MATCH_YES)
5039 return m;
5041 if (get_proc_name (name, &sym, false))
5042 return MATCH_ERROR;
5044 if (add_hidden_procptr_result (sym) == SUCCESS)
5045 sym = sym->result;
5047 gfc_new_block = sym;
5049 /* Check what next non-whitespace character is so we can tell if there
5050 is the required parens if we have a BIND(C). */
5051 gfc_gobble_whitespace ();
5052 peek_char = gfc_peek_ascii_char ();
5054 if (gfc_add_subroutine (&sym->attr, sym->name, NULL) == FAILURE)
5055 return MATCH_ERROR;
5057 if (gfc_match_formal_arglist (sym, 0, 1) != MATCH_YES)
5058 return MATCH_ERROR;
5060 /* Make sure that it isn't already declared as BIND(C). If it is, it
5061 must have been marked BIND(C) with a BIND(C) attribute and that is
5062 not allowed for procedures. */
5063 if (sym->attr.is_bind_c == 1)
5065 sym->attr.is_bind_c = 0;
5066 if (sym->old_symbol != NULL)
5067 gfc_error_now ("BIND(C) attribute at %L can only be used for "
5068 "variables or common blocks",
5069 &(sym->old_symbol->declared_at));
5070 else
5071 gfc_error_now ("BIND(C) attribute at %L can only be used for "
5072 "variables or common blocks", &gfc_current_locus);
5075 /* C binding names are not allowed for internal procedures. */
5076 if (gfc_current_state () == COMP_CONTAINS
5077 && sym->ns->proc_name->attr.flavor != FL_MODULE)
5078 allow_binding_name = false;
5079 else
5080 allow_binding_name = true;
5082 /* Here, we are just checking if it has the bind(c) attribute, and if
5083 so, then we need to make sure it's all correct. If it doesn't,
5084 we still need to continue matching the rest of the subroutine line. */
5085 is_bind_c = gfc_match_bind_c (sym, allow_binding_name);
5086 if (is_bind_c == MATCH_ERROR)
5088 /* There was an attempt at the bind(c), but it was wrong. An
5089 error message should have been printed w/in the gfc_match_bind_c
5090 so here we'll just return the MATCH_ERROR. */
5091 return MATCH_ERROR;
5094 if (is_bind_c == MATCH_YES)
5096 /* The following is allowed in the Fortran 2008 draft. */
5097 if (gfc_current_state () == COMP_CONTAINS
5098 && sym->ns->proc_name->attr.flavor != FL_MODULE
5099 && gfc_notify_std (GFC_STD_F2008, "Fortran 2008: BIND(C) attribute "
5100 "at %L may not be specified for an internal "
5101 "procedure", &gfc_current_locus)
5102 == FAILURE)
5103 return MATCH_ERROR;
5105 if (peek_char != '(')
5107 gfc_error ("Missing required parentheses before BIND(C) at %C");
5108 return MATCH_ERROR;
5110 if (gfc_add_is_bind_c (&(sym->attr), sym->name, &(sym->declared_at), 1)
5111 == FAILURE)
5112 return MATCH_ERROR;
5115 if (gfc_match_eos () != MATCH_YES)
5117 gfc_syntax_error (ST_SUBROUTINE);
5118 return MATCH_ERROR;
5121 if (copy_prefix (&sym->attr, &sym->declared_at) == FAILURE)
5122 return MATCH_ERROR;
5124 /* Warn if it has the same name as an intrinsic. */
5125 warn_intrinsic_shadow (sym, false);
5127 return MATCH_YES;
5131 /* Match a BIND(C) specifier, with the optional 'name=' specifier if
5132 given, and set the binding label in either the given symbol (if not
5133 NULL), or in the current_ts. The symbol may be NULL because we may
5134 encounter the BIND(C) before the declaration itself. Return
5135 MATCH_NO if what we're looking at isn't a BIND(C) specifier,
5136 MATCH_ERROR if it is a BIND(C) clause but an error was encountered,
5137 or MATCH_YES if the specifier was correct and the binding label and
5138 bind(c) fields were set correctly for the given symbol or the
5139 current_ts. If allow_binding_name is false, no binding name may be
5140 given. */
5142 match
5143 gfc_match_bind_c (gfc_symbol *sym, bool allow_binding_name)
5145 /* binding label, if exists */
5146 char binding_label[GFC_MAX_SYMBOL_LEN + 1];
5147 match double_quote;
5148 match single_quote;
5150 /* Initialize the flag that specifies whether we encountered a NAME=
5151 specifier or not. */
5152 has_name_equals = 0;
5154 /* Init the first char to nil so we can catch if we don't have
5155 the label (name attr) or the symbol name yet. */
5156 binding_label[0] = '\0';
5158 /* This much we have to be able to match, in this order, if
5159 there is a bind(c) label. */
5160 if (gfc_match (" bind ( c ") != MATCH_YES)
5161 return MATCH_NO;
5163 /* Now see if there is a binding label, or if we've reached the
5164 end of the bind(c) attribute without one. */
5165 if (gfc_match_char (',') == MATCH_YES)
5167 if (gfc_match (" name = ") != MATCH_YES)
5169 gfc_error ("Syntax error in NAME= specifier for binding label "
5170 "at %C");
5171 /* should give an error message here */
5172 return MATCH_ERROR;
5175 has_name_equals = 1;
5177 /* Get the opening quote. */
5178 double_quote = MATCH_YES;
5179 single_quote = MATCH_YES;
5180 double_quote = gfc_match_char ('"');
5181 if (double_quote != MATCH_YES)
5182 single_quote = gfc_match_char ('\'');
5183 if (double_quote != MATCH_YES && single_quote != MATCH_YES)
5185 gfc_error ("Syntax error in NAME= specifier for binding label "
5186 "at %C");
5187 return MATCH_ERROR;
5190 /* Grab the binding label, using functions that will not lower
5191 case the names automatically. */
5192 if (gfc_match_name_C (binding_label) != MATCH_YES)
5193 return MATCH_ERROR;
5195 /* Get the closing quotation. */
5196 if (double_quote == MATCH_YES)
5198 if (gfc_match_char ('"') != MATCH_YES)
5200 gfc_error ("Missing closing quote '\"' for binding label at %C");
5201 /* User started string with '"' so looked to match it. */
5202 return MATCH_ERROR;
5205 else
5207 if (gfc_match_char ('\'') != MATCH_YES)
5209 gfc_error ("Missing closing quote '\'' for binding label at %C");
5210 /* User started string with "'" char. */
5211 return MATCH_ERROR;
5216 /* Get the required right paren. */
5217 if (gfc_match_char (')') != MATCH_YES)
5219 gfc_error ("Missing closing paren for binding label at %C");
5220 return MATCH_ERROR;
5223 if (has_name_equals && !allow_binding_name)
5225 gfc_error ("No binding name is allowed in BIND(C) at %C");
5226 return MATCH_ERROR;
5229 if (has_name_equals && sym != NULL && sym->attr.dummy)
5231 gfc_error ("For dummy procedure %s, no binding name is "
5232 "allowed in BIND(C) at %C", sym->name);
5233 return MATCH_ERROR;
5237 /* Save the binding label to the symbol. If sym is null, we're
5238 probably matching the typespec attributes of a declaration and
5239 haven't gotten the name yet, and therefore, no symbol yet. */
5240 if (binding_label[0] != '\0')
5242 if (sym != NULL)
5244 strcpy (sym->binding_label, binding_label);
5246 else
5247 strcpy (curr_binding_label, binding_label);
5249 else if (allow_binding_name)
5251 /* No binding label, but if symbol isn't null, we
5252 can set the label for it here.
5253 If name="" or allow_binding_name is false, no C binding name is
5254 created. */
5255 if (sym != NULL && sym->name != NULL && has_name_equals == 0)
5256 strncpy (sym->binding_label, sym->name, strlen (sym->name) + 1);
5259 if (has_name_equals && gfc_current_state () == COMP_INTERFACE
5260 && current_interface.type == INTERFACE_ABSTRACT)
5262 gfc_error ("NAME not allowed on BIND(C) for ABSTRACT INTERFACE at %C");
5263 return MATCH_ERROR;
5266 return MATCH_YES;
5270 /* Return nonzero if we're currently compiling a contained procedure. */
5272 static int
5273 contained_procedure (void)
5275 gfc_state_data *s = gfc_state_stack;
5277 if ((s->state == COMP_SUBROUTINE || s->state == COMP_FUNCTION)
5278 && s->previous != NULL && s->previous->state == COMP_CONTAINS)
5279 return 1;
5281 return 0;
5284 /* Set the kind of each enumerator. The kind is selected such that it is
5285 interoperable with the corresponding C enumeration type, making
5286 sure that -fshort-enums is honored. */
5288 static void
5289 set_enum_kind(void)
5291 enumerator_history *current_history = NULL;
5292 int kind;
5293 int i;
5295 if (max_enum == NULL || enum_history == NULL)
5296 return;
5298 if (!flag_short_enums)
5299 return;
5301 i = 0;
5304 kind = gfc_integer_kinds[i++].kind;
5306 while (kind < gfc_c_int_kind
5307 && gfc_check_integer_range (max_enum->initializer->value.integer,
5308 kind) != ARITH_OK);
5310 current_history = enum_history;
5311 while (current_history != NULL)
5313 current_history->sym->ts.kind = kind;
5314 current_history = current_history->next;
5319 /* Match any of the various end-block statements. Returns the type of
5320 END to the caller. The END INTERFACE, END IF, END DO and END
5321 SELECT statements cannot be replaced by a single END statement. */
5323 match
5324 gfc_match_end (gfc_statement *st)
5326 char name[GFC_MAX_SYMBOL_LEN + 1];
5327 gfc_compile_state state;
5328 locus old_loc;
5329 const char *block_name;
5330 const char *target;
5331 int eos_ok;
5332 match m;
5334 old_loc = gfc_current_locus;
5335 if (gfc_match ("end") != MATCH_YES)
5336 return MATCH_NO;
5338 state = gfc_current_state ();
5339 block_name = gfc_current_block () == NULL
5340 ? NULL : gfc_current_block ()->name;
5342 if (state == COMP_CONTAINS || state == COMP_DERIVED_CONTAINS)
5344 state = gfc_state_stack->previous->state;
5345 block_name = gfc_state_stack->previous->sym == NULL
5346 ? NULL : gfc_state_stack->previous->sym->name;
5349 switch (state)
5351 case COMP_NONE:
5352 case COMP_PROGRAM:
5353 *st = ST_END_PROGRAM;
5354 target = " program";
5355 eos_ok = 1;
5356 break;
5358 case COMP_SUBROUTINE:
5359 *st = ST_END_SUBROUTINE;
5360 target = " subroutine";
5361 eos_ok = !contained_procedure ();
5362 break;
5364 case COMP_FUNCTION:
5365 *st = ST_END_FUNCTION;
5366 target = " function";
5367 eos_ok = !contained_procedure ();
5368 break;
5370 case COMP_BLOCK_DATA:
5371 *st = ST_END_BLOCK_DATA;
5372 target = " block data";
5373 eos_ok = 1;
5374 break;
5376 case COMP_MODULE:
5377 *st = ST_END_MODULE;
5378 target = " module";
5379 eos_ok = 1;
5380 break;
5382 case COMP_INTERFACE:
5383 *st = ST_END_INTERFACE;
5384 target = " interface";
5385 eos_ok = 0;
5386 break;
5388 case COMP_DERIVED:
5389 case COMP_DERIVED_CONTAINS:
5390 *st = ST_END_TYPE;
5391 target = " type";
5392 eos_ok = 0;
5393 break;
5395 case COMP_IF:
5396 *st = ST_ENDIF;
5397 target = " if";
5398 eos_ok = 0;
5399 break;
5401 case COMP_DO:
5402 *st = ST_ENDDO;
5403 target = " do";
5404 eos_ok = 0;
5405 break;
5407 case COMP_SELECT:
5408 *st = ST_END_SELECT;
5409 target = " select";
5410 eos_ok = 0;
5411 break;
5413 case COMP_FORALL:
5414 *st = ST_END_FORALL;
5415 target = " forall";
5416 eos_ok = 0;
5417 break;
5419 case COMP_WHERE:
5420 *st = ST_END_WHERE;
5421 target = " where";
5422 eos_ok = 0;
5423 break;
5425 case COMP_ENUM:
5426 *st = ST_END_ENUM;
5427 target = " enum";
5428 eos_ok = 0;
5429 last_initializer = NULL;
5430 set_enum_kind ();
5431 gfc_free_enum_history ();
5432 break;
5434 default:
5435 gfc_error ("Unexpected END statement at %C");
5436 goto cleanup;
5439 if (gfc_match_eos () == MATCH_YES)
5441 if (!eos_ok)
5443 /* We would have required END [something]. */
5444 gfc_error ("%s statement expected at %L",
5445 gfc_ascii_statement (*st), &old_loc);
5446 goto cleanup;
5449 return MATCH_YES;
5452 /* Verify that we've got the sort of end-block that we're expecting. */
5453 if (gfc_match (target) != MATCH_YES)
5455 gfc_error ("Expecting %s statement at %C", gfc_ascii_statement (*st));
5456 goto cleanup;
5459 /* If we're at the end, make sure a block name wasn't required. */
5460 if (gfc_match_eos () == MATCH_YES)
5463 if (*st != ST_ENDDO && *st != ST_ENDIF && *st != ST_END_SELECT
5464 && *st != ST_END_FORALL && *st != ST_END_WHERE)
5465 return MATCH_YES;
5467 if (gfc_current_block () == NULL)
5468 return MATCH_YES;
5470 gfc_error ("Expected block name of '%s' in %s statement at %C",
5471 block_name, gfc_ascii_statement (*st));
5473 return MATCH_ERROR;
5476 /* END INTERFACE has a special handler for its several possible endings. */
5477 if (*st == ST_END_INTERFACE)
5478 return gfc_match_end_interface ();
5480 /* We haven't hit the end of statement, so what is left must be an
5481 end-name. */
5482 m = gfc_match_space ();
5483 if (m == MATCH_YES)
5484 m = gfc_match_name (name);
5486 if (m == MATCH_NO)
5487 gfc_error ("Expected terminating name at %C");
5488 if (m != MATCH_YES)
5489 goto cleanup;
5491 if (block_name == NULL)
5492 goto syntax;
5494 if (strcmp (name, block_name) != 0 && strcmp (block_name, "ppr@") != 0)
5496 gfc_error ("Expected label '%s' for %s statement at %C", block_name,
5497 gfc_ascii_statement (*st));
5498 goto cleanup;
5500 /* Procedure pointer as function result. */
5501 else if (strcmp (block_name, "ppr@") == 0
5502 && strcmp (name, gfc_current_block ()->ns->proc_name->name) != 0)
5504 gfc_error ("Expected label '%s' for %s statement at %C",
5505 gfc_current_block ()->ns->proc_name->name,
5506 gfc_ascii_statement (*st));
5507 goto cleanup;
5510 if (gfc_match_eos () == MATCH_YES)
5511 return MATCH_YES;
5513 syntax:
5514 gfc_syntax_error (*st);
5516 cleanup:
5517 gfc_current_locus = old_loc;
5518 return MATCH_ERROR;
5523 /***************** Attribute declaration statements ****************/
5525 /* Set the attribute of a single variable. */
5527 static match
5528 attr_decl1 (void)
5530 char name[GFC_MAX_SYMBOL_LEN + 1];
5531 gfc_array_spec *as;
5532 gfc_symbol *sym;
5533 locus var_locus;
5534 match m;
5536 as = NULL;
5538 m = gfc_match_name (name);
5539 if (m != MATCH_YES)
5540 goto cleanup;
5542 if (find_special (name, &sym))
5543 return MATCH_ERROR;
5545 var_locus = gfc_current_locus;
5547 /* Deal with possible array specification for certain attributes. */
5548 if (current_attr.dimension
5549 || current_attr.allocatable
5550 || current_attr.pointer
5551 || current_attr.target)
5553 m = gfc_match_array_spec (&as);
5554 if (m == MATCH_ERROR)
5555 goto cleanup;
5557 if (current_attr.dimension && m == MATCH_NO)
5559 gfc_error ("Missing array specification at %L in DIMENSION "
5560 "statement", &var_locus);
5561 m = MATCH_ERROR;
5562 goto cleanup;
5565 if (current_attr.dimension && sym->value)
5567 gfc_error ("Dimensions specified for %s at %L after its "
5568 "initialisation", sym->name, &var_locus);
5569 m = MATCH_ERROR;
5570 goto cleanup;
5573 if ((current_attr.allocatable || current_attr.pointer)
5574 && (m == MATCH_YES) && (as->type != AS_DEFERRED))
5576 gfc_error ("Array specification must be deferred at %L", &var_locus);
5577 m = MATCH_ERROR;
5578 goto cleanup;
5582 /* Update symbol table. DIMENSION attribute is set
5583 in gfc_set_array_spec(). */
5584 if (current_attr.dimension == 0
5585 && gfc_copy_attr (&sym->attr, &current_attr, &var_locus) == FAILURE)
5587 m = MATCH_ERROR;
5588 goto cleanup;
5591 if (gfc_set_array_spec (sym, as, &var_locus) == FAILURE)
5593 m = MATCH_ERROR;
5594 goto cleanup;
5597 if (sym->attr.cray_pointee && sym->as != NULL)
5599 /* Fix the array spec. */
5600 m = gfc_mod_pointee_as (sym->as);
5601 if (m == MATCH_ERROR)
5602 goto cleanup;
5605 if (gfc_add_attribute (&sym->attr, &var_locus) == FAILURE)
5607 m = MATCH_ERROR;
5608 goto cleanup;
5611 if ((current_attr.external || current_attr.intrinsic)
5612 && sym->attr.flavor != FL_PROCEDURE
5613 && gfc_add_flavor (&sym->attr, FL_PROCEDURE, sym->name, NULL) == FAILURE)
5615 m = MATCH_ERROR;
5616 goto cleanup;
5619 add_hidden_procptr_result (sym);
5621 return MATCH_YES;
5623 cleanup:
5624 gfc_free_array_spec (as);
5625 return m;
5629 /* Generic attribute declaration subroutine. Used for attributes that
5630 just have a list of names. */
5632 static match
5633 attr_decl (void)
5635 match m;
5637 /* Gobble the optional double colon, by simply ignoring the result
5638 of gfc_match(). */
5639 gfc_match (" ::");
5641 for (;;)
5643 m = attr_decl1 ();
5644 if (m != MATCH_YES)
5645 break;
5647 if (gfc_match_eos () == MATCH_YES)
5649 m = MATCH_YES;
5650 break;
5653 if (gfc_match_char (',') != MATCH_YES)
5655 gfc_error ("Unexpected character in variable list at %C");
5656 m = MATCH_ERROR;
5657 break;
5661 return m;
5665 /* This routine matches Cray Pointer declarations of the form:
5666 pointer ( <pointer>, <pointee> )
5668 pointer ( <pointer1>, <pointee1> ), ( <pointer2>, <pointee2> ), ...
5669 The pointer, if already declared, should be an integer. Otherwise, we
5670 set it as BT_INTEGER with kind gfc_index_integer_kind. The pointee may
5671 be either a scalar, or an array declaration. No space is allocated for
5672 the pointee. For the statement
5673 pointer (ipt, ar(10))
5674 any subsequent uses of ar will be translated (in C-notation) as
5675 ar(i) => ((<type> *) ipt)(i)
5676 After gimplification, pointee variable will disappear in the code. */
5678 static match
5679 cray_pointer_decl (void)
5681 match m;
5682 gfc_array_spec *as;
5683 gfc_symbol *cptr; /* Pointer symbol. */
5684 gfc_symbol *cpte; /* Pointee symbol. */
5685 locus var_locus;
5686 bool done = false;
5688 while (!done)
5690 if (gfc_match_char ('(') != MATCH_YES)
5692 gfc_error ("Expected '(' at %C");
5693 return MATCH_ERROR;
5696 /* Match pointer. */
5697 var_locus = gfc_current_locus;
5698 gfc_clear_attr (&current_attr);
5699 gfc_add_cray_pointer (&current_attr, &var_locus);
5700 current_ts.type = BT_INTEGER;
5701 current_ts.kind = gfc_index_integer_kind;
5703 m = gfc_match_symbol (&cptr, 0);
5704 if (m != MATCH_YES)
5706 gfc_error ("Expected variable name at %C");
5707 return m;
5710 if (gfc_add_cray_pointer (&cptr->attr, &var_locus) == FAILURE)
5711 return MATCH_ERROR;
5713 gfc_set_sym_referenced (cptr);
5715 if (cptr->ts.type == BT_UNKNOWN) /* Override the type, if necessary. */
5717 cptr->ts.type = BT_INTEGER;
5718 cptr->ts.kind = gfc_index_integer_kind;
5720 else if (cptr->ts.type != BT_INTEGER)
5722 gfc_error ("Cray pointer at %C must be an integer");
5723 return MATCH_ERROR;
5725 else if (cptr->ts.kind < gfc_index_integer_kind)
5726 gfc_warning ("Cray pointer at %C has %d bytes of precision;"
5727 " memory addresses require %d bytes",
5728 cptr->ts.kind, gfc_index_integer_kind);
5730 if (gfc_match_char (',') != MATCH_YES)
5732 gfc_error ("Expected \",\" at %C");
5733 return MATCH_ERROR;
5736 /* Match Pointee. */
5737 var_locus = gfc_current_locus;
5738 gfc_clear_attr (&current_attr);
5739 gfc_add_cray_pointee (&current_attr, &var_locus);
5740 current_ts.type = BT_UNKNOWN;
5741 current_ts.kind = 0;
5743 m = gfc_match_symbol (&cpte, 0);
5744 if (m != MATCH_YES)
5746 gfc_error ("Expected variable name at %C");
5747 return m;
5750 /* Check for an optional array spec. */
5751 m = gfc_match_array_spec (&as);
5752 if (m == MATCH_ERROR)
5754 gfc_free_array_spec (as);
5755 return m;
5757 else if (m == MATCH_NO)
5759 gfc_free_array_spec (as);
5760 as = NULL;
5763 if (gfc_add_cray_pointee (&cpte->attr, &var_locus) == FAILURE)
5764 return MATCH_ERROR;
5766 gfc_set_sym_referenced (cpte);
5768 if (cpte->as == NULL)
5770 if (gfc_set_array_spec (cpte, as, &var_locus) == FAILURE)
5771 gfc_internal_error ("Couldn't set Cray pointee array spec.");
5773 else if (as != NULL)
5775 gfc_error ("Duplicate array spec for Cray pointee at %C");
5776 gfc_free_array_spec (as);
5777 return MATCH_ERROR;
5780 as = NULL;
5782 if (cpte->as != NULL)
5784 /* Fix array spec. */
5785 m = gfc_mod_pointee_as (cpte->as);
5786 if (m == MATCH_ERROR)
5787 return m;
5790 /* Point the Pointee at the Pointer. */
5791 cpte->cp_pointer = cptr;
5793 if (gfc_match_char (')') != MATCH_YES)
5795 gfc_error ("Expected \")\" at %C");
5796 return MATCH_ERROR;
5798 m = gfc_match_char (',');
5799 if (m != MATCH_YES)
5800 done = true; /* Stop searching for more declarations. */
5804 if (m == MATCH_ERROR /* Failed when trying to find ',' above. */
5805 || gfc_match_eos () != MATCH_YES)
5807 gfc_error ("Expected \",\" or end of statement at %C");
5808 return MATCH_ERROR;
5810 return MATCH_YES;
5814 match
5815 gfc_match_external (void)
5818 gfc_clear_attr (&current_attr);
5819 current_attr.external = 1;
5821 return attr_decl ();
5825 match
5826 gfc_match_intent (void)
5828 sym_intent intent;
5830 intent = match_intent_spec ();
5831 if (intent == INTENT_UNKNOWN)
5832 return MATCH_ERROR;
5834 gfc_clear_attr (&current_attr);
5835 current_attr.intent = intent;
5837 return attr_decl ();
5841 match
5842 gfc_match_intrinsic (void)
5845 gfc_clear_attr (&current_attr);
5846 current_attr.intrinsic = 1;
5848 return attr_decl ();
5852 match
5853 gfc_match_optional (void)
5856 gfc_clear_attr (&current_attr);
5857 current_attr.optional = 1;
5859 return attr_decl ();
5863 match
5864 gfc_match_pointer (void)
5866 gfc_gobble_whitespace ();
5867 if (gfc_peek_ascii_char () == '(')
5869 if (!gfc_option.flag_cray_pointer)
5871 gfc_error ("Cray pointer declaration at %C requires -fcray-pointer "
5872 "flag");
5873 return MATCH_ERROR;
5875 return cray_pointer_decl ();
5877 else
5879 gfc_clear_attr (&current_attr);
5880 current_attr.pointer = 1;
5882 return attr_decl ();
5887 match
5888 gfc_match_allocatable (void)
5890 gfc_clear_attr (&current_attr);
5891 current_attr.allocatable = 1;
5893 return attr_decl ();
5897 match
5898 gfc_match_dimension (void)
5900 gfc_clear_attr (&current_attr);
5901 current_attr.dimension = 1;
5903 return attr_decl ();
5907 match
5908 gfc_match_target (void)
5910 gfc_clear_attr (&current_attr);
5911 current_attr.target = 1;
5913 return attr_decl ();
5917 /* Match the list of entities being specified in a PUBLIC or PRIVATE
5918 statement. */
5920 static match
5921 access_attr_decl (gfc_statement st)
5923 char name[GFC_MAX_SYMBOL_LEN + 1];
5924 interface_type type;
5925 gfc_user_op *uop;
5926 gfc_symbol *sym;
5927 gfc_intrinsic_op op;
5928 match m;
5930 if (gfc_match (" ::") == MATCH_NO && gfc_match_space () == MATCH_NO)
5931 goto done;
5933 for (;;)
5935 m = gfc_match_generic_spec (&type, name, &op);
5936 if (m == MATCH_NO)
5937 goto syntax;
5938 if (m == MATCH_ERROR)
5939 return MATCH_ERROR;
5941 switch (type)
5943 case INTERFACE_NAMELESS:
5944 case INTERFACE_ABSTRACT:
5945 goto syntax;
5947 case INTERFACE_GENERIC:
5948 if (gfc_get_symbol (name, NULL, &sym))
5949 goto done;
5951 if (gfc_add_access (&sym->attr, (st == ST_PUBLIC)
5952 ? ACCESS_PUBLIC : ACCESS_PRIVATE,
5953 sym->name, NULL) == FAILURE)
5954 return MATCH_ERROR;
5956 break;
5958 case INTERFACE_INTRINSIC_OP:
5959 if (gfc_current_ns->operator_access[op] == ACCESS_UNKNOWN)
5961 gfc_current_ns->operator_access[op] =
5962 (st == ST_PUBLIC) ? ACCESS_PUBLIC : ACCESS_PRIVATE;
5964 else
5966 gfc_error ("Access specification of the %s operator at %C has "
5967 "already been specified", gfc_op2string (op));
5968 goto done;
5971 break;
5973 case INTERFACE_USER_OP:
5974 uop = gfc_get_uop (name);
5976 if (uop->access == ACCESS_UNKNOWN)
5978 uop->access = (st == ST_PUBLIC)
5979 ? ACCESS_PUBLIC : ACCESS_PRIVATE;
5981 else
5983 gfc_error ("Access specification of the .%s. operator at %C "
5984 "has already been specified", sym->name);
5985 goto done;
5988 break;
5991 if (gfc_match_char (',') == MATCH_NO)
5992 break;
5995 if (gfc_match_eos () != MATCH_YES)
5996 goto syntax;
5997 return MATCH_YES;
5999 syntax:
6000 gfc_syntax_error (st);
6002 done:
6003 return MATCH_ERROR;
6007 match
6008 gfc_match_protected (void)
6010 gfc_symbol *sym;
6011 match m;
6013 if (gfc_current_ns->proc_name->attr.flavor != FL_MODULE)
6015 gfc_error ("PROTECTED at %C only allowed in specification "
6016 "part of a module");
6017 return MATCH_ERROR;
6021 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PROTECTED statement at %C")
6022 == FAILURE)
6023 return MATCH_ERROR;
6025 if (gfc_match (" ::") == MATCH_NO && gfc_match_space () == MATCH_NO)
6027 return MATCH_ERROR;
6030 if (gfc_match_eos () == MATCH_YES)
6031 goto syntax;
6033 for(;;)
6035 m = gfc_match_symbol (&sym, 0);
6036 switch (m)
6038 case MATCH_YES:
6039 if (gfc_add_protected (&sym->attr, sym->name, &gfc_current_locus)
6040 == FAILURE)
6041 return MATCH_ERROR;
6042 goto next_item;
6044 case MATCH_NO:
6045 break;
6047 case MATCH_ERROR:
6048 return MATCH_ERROR;
6051 next_item:
6052 if (gfc_match_eos () == MATCH_YES)
6053 break;
6054 if (gfc_match_char (',') != MATCH_YES)
6055 goto syntax;
6058 return MATCH_YES;
6060 syntax:
6061 gfc_error ("Syntax error in PROTECTED statement at %C");
6062 return MATCH_ERROR;
6066 /* The PRIVATE statement is a bit weird in that it can be an attribute
6067 declaration, but also works as a standalone statement inside of a
6068 type declaration or a module. */
6070 match
6071 gfc_match_private (gfc_statement *st)
6074 if (gfc_match ("private") != MATCH_YES)
6075 return MATCH_NO;
6077 if (gfc_current_state () != COMP_MODULE
6078 && !(gfc_current_state () == COMP_DERIVED
6079 && gfc_state_stack->previous
6080 && gfc_state_stack->previous->state == COMP_MODULE)
6081 && !(gfc_current_state () == COMP_DERIVED_CONTAINS
6082 && gfc_state_stack->previous && gfc_state_stack->previous->previous
6083 && gfc_state_stack->previous->previous->state == COMP_MODULE))
6085 gfc_error ("PRIVATE statement at %C is only allowed in the "
6086 "specification part of a module");
6087 return MATCH_ERROR;
6090 if (gfc_current_state () == COMP_DERIVED)
6092 if (gfc_match_eos () == MATCH_YES)
6094 *st = ST_PRIVATE;
6095 return MATCH_YES;
6098 gfc_syntax_error (ST_PRIVATE);
6099 return MATCH_ERROR;
6102 if (gfc_match_eos () == MATCH_YES)
6104 *st = ST_PRIVATE;
6105 return MATCH_YES;
6108 *st = ST_ATTR_DECL;
6109 return access_attr_decl (ST_PRIVATE);
6113 match
6114 gfc_match_public (gfc_statement *st)
6117 if (gfc_match ("public") != MATCH_YES)
6118 return MATCH_NO;
6120 if (gfc_current_state () != COMP_MODULE)
6122 gfc_error ("PUBLIC statement at %C is only allowed in the "
6123 "specification part of a module");
6124 return MATCH_ERROR;
6127 if (gfc_match_eos () == MATCH_YES)
6129 *st = ST_PUBLIC;
6130 return MATCH_YES;
6133 *st = ST_ATTR_DECL;
6134 return access_attr_decl (ST_PUBLIC);
6138 /* Workhorse for gfc_match_parameter. */
6140 static match
6141 do_parm (void)
6143 gfc_symbol *sym;
6144 gfc_expr *init;
6145 match m;
6147 m = gfc_match_symbol (&sym, 0);
6148 if (m == MATCH_NO)
6149 gfc_error ("Expected variable name at %C in PARAMETER statement");
6151 if (m != MATCH_YES)
6152 return m;
6154 if (gfc_match_char ('=') == MATCH_NO)
6156 gfc_error ("Expected = sign in PARAMETER statement at %C");
6157 return MATCH_ERROR;
6160 m = gfc_match_init_expr (&init);
6161 if (m == MATCH_NO)
6162 gfc_error ("Expected expression at %C in PARAMETER statement");
6163 if (m != MATCH_YES)
6164 return m;
6166 if (sym->ts.type == BT_UNKNOWN
6167 && gfc_set_default_type (sym, 1, NULL) == FAILURE)
6169 m = MATCH_ERROR;
6170 goto cleanup;
6173 if (gfc_check_assign_symbol (sym, init) == FAILURE
6174 || gfc_add_flavor (&sym->attr, FL_PARAMETER, sym->name, NULL) == FAILURE)
6176 m = MATCH_ERROR;
6177 goto cleanup;
6180 if (sym->value)
6182 gfc_error ("Initializing already initialized variable at %C");
6183 m = MATCH_ERROR;
6184 goto cleanup;
6187 if (sym->ts.type == BT_CHARACTER
6188 && sym->ts.cl != NULL
6189 && sym->ts.cl->length != NULL
6190 && sym->ts.cl->length->expr_type == EXPR_CONSTANT
6191 && init->expr_type == EXPR_CONSTANT
6192 && init->ts.type == BT_CHARACTER)
6193 gfc_set_constant_character_len (
6194 mpz_get_si (sym->ts.cl->length->value.integer), init, -1);
6195 else if (sym->ts.type == BT_CHARACTER && sym->ts.cl != NULL
6196 && sym->ts.cl->length == NULL)
6198 int clen;
6199 if (init->expr_type == EXPR_CONSTANT)
6201 clen = init->value.character.length;
6202 sym->ts.cl->length = gfc_int_expr (clen);
6204 else if (init->expr_type == EXPR_ARRAY)
6206 gfc_expr *p = init->value.constructor->expr;
6207 clen = p->value.character.length;
6208 sym->ts.cl->length = gfc_int_expr (clen);
6210 else if (init->ts.cl && init->ts.cl->length)
6211 sym->ts.cl->length = gfc_copy_expr (sym->value->ts.cl->length);
6214 sym->value = init;
6215 return MATCH_YES;
6217 cleanup:
6218 gfc_free_expr (init);
6219 return m;
6223 /* Match a parameter statement, with the weird syntax that these have. */
6225 match
6226 gfc_match_parameter (void)
6228 match m;
6230 if (gfc_match_char ('(') == MATCH_NO)
6231 return MATCH_NO;
6233 for (;;)
6235 m = do_parm ();
6236 if (m != MATCH_YES)
6237 break;
6239 if (gfc_match (" )%t") == MATCH_YES)
6240 break;
6242 if (gfc_match_char (',') != MATCH_YES)
6244 gfc_error ("Unexpected characters in PARAMETER statement at %C");
6245 m = MATCH_ERROR;
6246 break;
6250 return m;
6254 /* Save statements have a special syntax. */
6256 match
6257 gfc_match_save (void)
6259 char n[GFC_MAX_SYMBOL_LEN+1];
6260 gfc_common_head *c;
6261 gfc_symbol *sym;
6262 match m;
6264 if (gfc_match_eos () == MATCH_YES)
6266 if (gfc_current_ns->seen_save)
6268 if (gfc_notify_std (GFC_STD_LEGACY, "Blanket SAVE statement at %C "
6269 "follows previous SAVE statement")
6270 == FAILURE)
6271 return MATCH_ERROR;
6274 gfc_current_ns->save_all = gfc_current_ns->seen_save = 1;
6275 return MATCH_YES;
6278 if (gfc_current_ns->save_all)
6280 if (gfc_notify_std (GFC_STD_LEGACY, "SAVE statement at %C follows "
6281 "blanket SAVE statement")
6282 == FAILURE)
6283 return MATCH_ERROR;
6286 gfc_match (" ::");
6288 for (;;)
6290 m = gfc_match_symbol (&sym, 0);
6291 switch (m)
6293 case MATCH_YES:
6294 if (gfc_add_save (&sym->attr, sym->name, &gfc_current_locus)
6295 == FAILURE)
6296 return MATCH_ERROR;
6297 goto next_item;
6299 case MATCH_NO:
6300 break;
6302 case MATCH_ERROR:
6303 return MATCH_ERROR;
6306 m = gfc_match (" / %n /", &n);
6307 if (m == MATCH_ERROR)
6308 return MATCH_ERROR;
6309 if (m == MATCH_NO)
6310 goto syntax;
6312 c = gfc_get_common (n, 0);
6313 c->saved = 1;
6315 gfc_current_ns->seen_save = 1;
6317 next_item:
6318 if (gfc_match_eos () == MATCH_YES)
6319 break;
6320 if (gfc_match_char (',') != MATCH_YES)
6321 goto syntax;
6324 return MATCH_YES;
6326 syntax:
6327 gfc_error ("Syntax error in SAVE statement at %C");
6328 return MATCH_ERROR;
6332 match
6333 gfc_match_value (void)
6335 gfc_symbol *sym;
6336 match m;
6338 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: VALUE statement at %C")
6339 == FAILURE)
6340 return MATCH_ERROR;
6342 if (gfc_match (" ::") == MATCH_NO && gfc_match_space () == MATCH_NO)
6344 return MATCH_ERROR;
6347 if (gfc_match_eos () == MATCH_YES)
6348 goto syntax;
6350 for(;;)
6352 m = gfc_match_symbol (&sym, 0);
6353 switch (m)
6355 case MATCH_YES:
6356 if (gfc_add_value (&sym->attr, sym->name, &gfc_current_locus)
6357 == FAILURE)
6358 return MATCH_ERROR;
6359 goto next_item;
6361 case MATCH_NO:
6362 break;
6364 case MATCH_ERROR:
6365 return MATCH_ERROR;
6368 next_item:
6369 if (gfc_match_eos () == MATCH_YES)
6370 break;
6371 if (gfc_match_char (',') != MATCH_YES)
6372 goto syntax;
6375 return MATCH_YES;
6377 syntax:
6378 gfc_error ("Syntax error in VALUE statement at %C");
6379 return MATCH_ERROR;
6383 match
6384 gfc_match_volatile (void)
6386 gfc_symbol *sym;
6387 match m;
6389 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: VOLATILE statement at %C")
6390 == FAILURE)
6391 return MATCH_ERROR;
6393 if (gfc_match (" ::") == MATCH_NO && gfc_match_space () == MATCH_NO)
6395 return MATCH_ERROR;
6398 if (gfc_match_eos () == MATCH_YES)
6399 goto syntax;
6401 for(;;)
6403 /* VOLATILE is special because it can be added to host-associated
6404 symbols locally. */
6405 m = gfc_match_symbol (&sym, 1);
6406 switch (m)
6408 case MATCH_YES:
6409 if (gfc_add_volatile (&sym->attr, sym->name, &gfc_current_locus)
6410 == FAILURE)
6411 return MATCH_ERROR;
6412 goto next_item;
6414 case MATCH_NO:
6415 break;
6417 case MATCH_ERROR:
6418 return MATCH_ERROR;
6421 next_item:
6422 if (gfc_match_eos () == MATCH_YES)
6423 break;
6424 if (gfc_match_char (',') != MATCH_YES)
6425 goto syntax;
6428 return MATCH_YES;
6430 syntax:
6431 gfc_error ("Syntax error in VOLATILE statement at %C");
6432 return MATCH_ERROR;
6436 /* Match a module procedure statement. Note that we have to modify
6437 symbols in the parent's namespace because the current one was there
6438 to receive symbols that are in an interface's formal argument list. */
6440 match
6441 gfc_match_modproc (void)
6443 char name[GFC_MAX_SYMBOL_LEN + 1];
6444 gfc_symbol *sym;
6445 match m;
6446 gfc_namespace *module_ns;
6447 gfc_interface *old_interface_head, *interface;
6449 if (gfc_state_stack->state != COMP_INTERFACE
6450 || gfc_state_stack->previous == NULL
6451 || current_interface.type == INTERFACE_NAMELESS
6452 || current_interface.type == INTERFACE_ABSTRACT)
6454 gfc_error ("MODULE PROCEDURE at %C must be in a generic module "
6455 "interface");
6456 return MATCH_ERROR;
6459 module_ns = gfc_current_ns->parent;
6460 for (; module_ns; module_ns = module_ns->parent)
6461 if (module_ns->proc_name->attr.flavor == FL_MODULE)
6462 break;
6464 if (module_ns == NULL)
6465 return MATCH_ERROR;
6467 /* Store the current state of the interface. We will need it if we
6468 end up with a syntax error and need to recover. */
6469 old_interface_head = gfc_current_interface_head ();
6471 for (;;)
6473 bool last = false;
6475 m = gfc_match_name (name);
6476 if (m == MATCH_NO)
6477 goto syntax;
6478 if (m != MATCH_YES)
6479 return MATCH_ERROR;
6481 /* Check for syntax error before starting to add symbols to the
6482 current namespace. */
6483 if (gfc_match_eos () == MATCH_YES)
6484 last = true;
6485 if (!last && gfc_match_char (',') != MATCH_YES)
6486 goto syntax;
6488 /* Now we're sure the syntax is valid, we process this item
6489 further. */
6490 if (gfc_get_symbol (name, module_ns, &sym))
6491 return MATCH_ERROR;
6493 if (sym->attr.proc != PROC_MODULE
6494 && gfc_add_procedure (&sym->attr, PROC_MODULE,
6495 sym->name, NULL) == FAILURE)
6496 return MATCH_ERROR;
6498 if (gfc_add_interface (sym) == FAILURE)
6499 return MATCH_ERROR;
6501 sym->attr.mod_proc = 1;
6503 if (last)
6504 break;
6507 return MATCH_YES;
6509 syntax:
6510 /* Restore the previous state of the interface. */
6511 interface = gfc_current_interface_head ();
6512 gfc_set_current_interface_head (old_interface_head);
6514 /* Free the new interfaces. */
6515 while (interface != old_interface_head)
6517 gfc_interface *i = interface->next;
6518 gfc_free (interface);
6519 interface = i;
6522 /* And issue a syntax error. */
6523 gfc_syntax_error (ST_MODULE_PROC);
6524 return MATCH_ERROR;
6528 /* Check a derived type that is being extended. */
6529 static gfc_symbol*
6530 check_extended_derived_type (char *name)
6532 gfc_symbol *extended;
6534 if (gfc_find_symbol (name, gfc_current_ns, 1, &extended))
6536 gfc_error ("Ambiguous symbol in TYPE definition at %C");
6537 return NULL;
6540 if (!extended)
6542 gfc_error ("No such symbol in TYPE definition at %C");
6543 return NULL;
6546 if (extended->attr.flavor != FL_DERIVED)
6548 gfc_error ("'%s' in EXTENDS expression at %C is not a "
6549 "derived type", name);
6550 return NULL;
6553 if (extended->attr.is_bind_c)
6555 gfc_error ("'%s' cannot be extended at %C because it "
6556 "is BIND(C)", extended->name);
6557 return NULL;
6560 if (extended->attr.sequence)
6562 gfc_error ("'%s' cannot be extended at %C because it "
6563 "is a SEQUENCE type", extended->name);
6564 return NULL;
6567 return extended;
6571 /* Match the optional attribute specifiers for a type declaration.
6572 Return MATCH_ERROR if an error is encountered in one of the handled
6573 attributes (public, private, bind(c)), MATCH_NO if what's found is
6574 not a handled attribute, and MATCH_YES otherwise. TODO: More error
6575 checking on attribute conflicts needs to be done. */
6577 match
6578 gfc_get_type_attr_spec (symbol_attribute *attr, char *name)
6580 /* See if the derived type is marked as private. */
6581 if (gfc_match (" , private") == MATCH_YES)
6583 if (gfc_current_state () != COMP_MODULE)
6585 gfc_error ("Derived type at %C can only be PRIVATE in the "
6586 "specification part of a module");
6587 return MATCH_ERROR;
6590 if (gfc_add_access (attr, ACCESS_PRIVATE, NULL, NULL) == FAILURE)
6591 return MATCH_ERROR;
6593 else if (gfc_match (" , public") == MATCH_YES)
6595 if (gfc_current_state () != COMP_MODULE)
6597 gfc_error ("Derived type at %C can only be PUBLIC in the "
6598 "specification part of a module");
6599 return MATCH_ERROR;
6602 if (gfc_add_access (attr, ACCESS_PUBLIC, NULL, NULL) == FAILURE)
6603 return MATCH_ERROR;
6605 else if (gfc_match (" , bind ( c )") == MATCH_YES)
6607 /* If the type is defined to be bind(c) it then needs to make
6608 sure that all fields are interoperable. This will
6609 need to be a semantic check on the finished derived type.
6610 See 15.2.3 (lines 9-12) of F2003 draft. */
6611 if (gfc_add_is_bind_c (attr, NULL, &gfc_current_locus, 0) != SUCCESS)
6612 return MATCH_ERROR;
6614 /* TODO: attr conflicts need to be checked, probably in symbol.c. */
6616 else if (gfc_match (" , abstract") == MATCH_YES)
6618 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: ABSTRACT type at %C")
6619 == FAILURE)
6620 return MATCH_ERROR;
6622 if (gfc_add_abstract (attr, &gfc_current_locus) == FAILURE)
6623 return MATCH_ERROR;
6625 else if (name && gfc_match(" , extends ( %n )", name) == MATCH_YES)
6627 if (gfc_add_extension (attr, &gfc_current_locus) == FAILURE)
6628 return MATCH_ERROR;
6630 else
6631 return MATCH_NO;
6633 /* If we get here, something matched. */
6634 return MATCH_YES;
6638 /* Match the beginning of a derived type declaration. If a type name
6639 was the result of a function, then it is possible to have a symbol
6640 already to be known as a derived type yet have no components. */
6642 match
6643 gfc_match_derived_decl (void)
6645 char name[GFC_MAX_SYMBOL_LEN + 1];
6646 char parent[GFC_MAX_SYMBOL_LEN + 1];
6647 symbol_attribute attr;
6648 gfc_symbol *sym;
6649 gfc_symbol *extended;
6650 match m;
6651 match is_type_attr_spec = MATCH_NO;
6652 bool seen_attr = false;
6654 if (gfc_current_state () == COMP_DERIVED)
6655 return MATCH_NO;
6657 name[0] = '\0';
6658 parent[0] = '\0';
6659 gfc_clear_attr (&attr);
6660 extended = NULL;
6664 is_type_attr_spec = gfc_get_type_attr_spec (&attr, parent);
6665 if (is_type_attr_spec == MATCH_ERROR)
6666 return MATCH_ERROR;
6667 if (is_type_attr_spec == MATCH_YES)
6668 seen_attr = true;
6669 } while (is_type_attr_spec == MATCH_YES);
6671 /* Deal with derived type extensions. The extension attribute has
6672 been added to 'attr' but now the parent type must be found and
6673 checked. */
6674 if (parent[0])
6675 extended = check_extended_derived_type (parent);
6677 if (parent[0] && !extended)
6678 return MATCH_ERROR;
6680 if (gfc_match (" ::") != MATCH_YES && seen_attr)
6682 gfc_error ("Expected :: in TYPE definition at %C");
6683 return MATCH_ERROR;
6686 m = gfc_match (" %n%t", name);
6687 if (m != MATCH_YES)
6688 return m;
6690 /* Make sure the name is not the name of an intrinsic type. */
6691 if (gfc_is_intrinsic_typename (name))
6693 gfc_error ("Type name '%s' at %C cannot be the same as an intrinsic "
6694 "type", name);
6695 return MATCH_ERROR;
6698 if (gfc_get_symbol (name, NULL, &sym))
6699 return MATCH_ERROR;
6701 if (sym->ts.type != BT_UNKNOWN)
6703 gfc_error ("Derived type name '%s' at %C already has a basic type "
6704 "of %s", sym->name, gfc_typename (&sym->ts));
6705 return MATCH_ERROR;
6708 /* The symbol may already have the derived attribute without the
6709 components. The ways this can happen is via a function
6710 definition, an INTRINSIC statement or a subtype in another
6711 derived type that is a pointer. The first part of the AND clause
6712 is true if the symbol is not the return value of a function. */
6713 if (sym->attr.flavor != FL_DERIVED
6714 && gfc_add_flavor (&sym->attr, FL_DERIVED, sym->name, NULL) == FAILURE)
6715 return MATCH_ERROR;
6717 if (sym->components != NULL || sym->attr.zero_comp)
6719 gfc_error ("Derived type definition of '%s' at %C has already been "
6720 "defined", sym->name);
6721 return MATCH_ERROR;
6724 if (attr.access != ACCESS_UNKNOWN
6725 && gfc_add_access (&sym->attr, attr.access, sym->name, NULL) == FAILURE)
6726 return MATCH_ERROR;
6728 /* See if the derived type was labeled as bind(c). */
6729 if (attr.is_bind_c != 0)
6730 sym->attr.is_bind_c = attr.is_bind_c;
6732 /* Construct the f2k_derived namespace if it is not yet there. */
6733 if (!sym->f2k_derived)
6734 sym->f2k_derived = gfc_get_namespace (NULL, 0);
6736 if (extended && !sym->components)
6738 gfc_component *p;
6739 gfc_symtree *st;
6741 /* Add the extended derived type as the first component. */
6742 gfc_add_component (sym, parent, &p);
6743 sym->attr.extension = attr.extension;
6744 extended->refs++;
6745 gfc_set_sym_referenced (extended);
6747 p->ts.type = BT_DERIVED;
6748 p->ts.derived = extended;
6749 p->initializer = gfc_default_initializer (&p->ts);
6751 /* Provide the links between the extended type and its extension. */
6752 if (!extended->f2k_derived)
6753 extended->f2k_derived = gfc_get_namespace (NULL, 0);
6754 st = gfc_new_symtree (&extended->f2k_derived->sym_root, sym->name);
6755 st->n.sym = sym;
6758 /* Take over the ABSTRACT attribute. */
6759 sym->attr.abstract = attr.abstract;
6761 gfc_new_block = sym;
6763 return MATCH_YES;
6767 /* Cray Pointees can be declared as:
6768 pointer (ipt, a (n,m,...,*))
6769 By default, this is treated as an AS_ASSUMED_SIZE array. We'll
6770 cheat and set a constant bound of 1 for the last dimension, if this
6771 is the case. Since there is no bounds-checking for Cray Pointees,
6772 this will be okay. */
6774 match
6775 gfc_mod_pointee_as (gfc_array_spec *as)
6777 as->cray_pointee = true; /* This will be useful to know later. */
6778 if (as->type == AS_ASSUMED_SIZE)
6780 as->type = AS_EXPLICIT;
6781 as->upper[as->rank - 1] = gfc_int_expr (1);
6782 as->cp_was_assumed = true;
6784 else if (as->type == AS_ASSUMED_SHAPE)
6786 gfc_error ("Cray Pointee at %C cannot be assumed shape array");
6787 return MATCH_ERROR;
6789 return MATCH_YES;
6793 /* Match the enum definition statement, here we are trying to match
6794 the first line of enum definition statement.
6795 Returns MATCH_YES if match is found. */
6797 match
6798 gfc_match_enum (void)
6800 match m;
6802 m = gfc_match_eos ();
6803 if (m != MATCH_YES)
6804 return m;
6806 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: ENUM and ENUMERATOR at %C")
6807 == FAILURE)
6808 return MATCH_ERROR;
6810 return MATCH_YES;
6814 /* Returns an initializer whose value is one higher than the value of the
6815 LAST_INITIALIZER argument. If the argument is NULL, the
6816 initializers value will be set to zero. The initializer's kind
6817 will be set to gfc_c_int_kind.
6819 If -fshort-enums is given, the appropriate kind will be selected
6820 later after all enumerators have been parsed. A warning is issued
6821 here if an initializer exceeds gfc_c_int_kind. */
6823 static gfc_expr *
6824 enum_initializer (gfc_expr *last_initializer, locus where)
6826 gfc_expr *result;
6828 result = gfc_get_expr ();
6829 result->expr_type = EXPR_CONSTANT;
6830 result->ts.type = BT_INTEGER;
6831 result->ts.kind = gfc_c_int_kind;
6832 result->where = where;
6834 mpz_init (result->value.integer);
6836 if (last_initializer != NULL)
6838 mpz_add_ui (result->value.integer, last_initializer->value.integer, 1);
6839 result->where = last_initializer->where;
6841 if (gfc_check_integer_range (result->value.integer,
6842 gfc_c_int_kind) != ARITH_OK)
6844 gfc_error ("Enumerator exceeds the C integer type at %C");
6845 return NULL;
6848 else
6850 /* Control comes here, if it's the very first enumerator and no
6851 initializer has been given. It will be initialized to zero. */
6852 mpz_set_si (result->value.integer, 0);
6855 return result;
6859 /* Match a variable name with an optional initializer. When this
6860 subroutine is called, a variable is expected to be parsed next.
6861 Depending on what is happening at the moment, updates either the
6862 symbol table or the current interface. */
6864 static match
6865 enumerator_decl (void)
6867 char name[GFC_MAX_SYMBOL_LEN + 1];
6868 gfc_expr *initializer;
6869 gfc_array_spec *as = NULL;
6870 gfc_symbol *sym;
6871 locus var_locus;
6872 match m;
6873 gfc_try t;
6874 locus old_locus;
6876 initializer = NULL;
6877 old_locus = gfc_current_locus;
6879 /* When we get here, we've just matched a list of attributes and
6880 maybe a type and a double colon. The next thing we expect to see
6881 is the name of the symbol. */
6882 m = gfc_match_name (name);
6883 if (m != MATCH_YES)
6884 goto cleanup;
6886 var_locus = gfc_current_locus;
6888 /* OK, we've successfully matched the declaration. Now put the
6889 symbol in the current namespace. If we fail to create the symbol,
6890 bail out. */
6891 if (build_sym (name, NULL, &as, &var_locus) == FAILURE)
6893 m = MATCH_ERROR;
6894 goto cleanup;
6897 /* The double colon must be present in order to have initializers.
6898 Otherwise the statement is ambiguous with an assignment statement. */
6899 if (colon_seen)
6901 if (gfc_match_char ('=') == MATCH_YES)
6903 m = gfc_match_init_expr (&initializer);
6904 if (m == MATCH_NO)
6906 gfc_error ("Expected an initialization expression at %C");
6907 m = MATCH_ERROR;
6910 if (m != MATCH_YES)
6911 goto cleanup;
6915 /* If we do not have an initializer, the initialization value of the
6916 previous enumerator (stored in last_initializer) is incremented
6917 by 1 and is used to initialize the current enumerator. */
6918 if (initializer == NULL)
6919 initializer = enum_initializer (last_initializer, old_locus);
6921 if (initializer == NULL || initializer->ts.type != BT_INTEGER)
6923 gfc_error("ENUMERATOR %L not initialized with integer expression",
6924 &var_locus);
6925 m = MATCH_ERROR;
6926 gfc_free_enum_history ();
6927 goto cleanup;
6930 /* Store this current initializer, for the next enumerator variable
6931 to be parsed. add_init_expr_to_sym() zeros initializer, so we
6932 use last_initializer below. */
6933 last_initializer = initializer;
6934 t = add_init_expr_to_sym (name, &initializer, &var_locus);
6936 /* Maintain enumerator history. */
6937 gfc_find_symbol (name, NULL, 0, &sym);
6938 create_enum_history (sym, last_initializer);
6940 return (t == SUCCESS) ? MATCH_YES : MATCH_ERROR;
6942 cleanup:
6943 /* Free stuff up and return. */
6944 gfc_free_expr (initializer);
6946 return m;
6950 /* Match the enumerator definition statement. */
6952 match
6953 gfc_match_enumerator_def (void)
6955 match m;
6956 gfc_try t;
6958 gfc_clear_ts (&current_ts);
6960 m = gfc_match (" enumerator");
6961 if (m != MATCH_YES)
6962 return m;
6964 m = gfc_match (" :: ");
6965 if (m == MATCH_ERROR)
6966 return m;
6968 colon_seen = (m == MATCH_YES);
6970 if (gfc_current_state () != COMP_ENUM)
6972 gfc_error ("ENUM definition statement expected before %C");
6973 gfc_free_enum_history ();
6974 return MATCH_ERROR;
6977 (&current_ts)->type = BT_INTEGER;
6978 (&current_ts)->kind = gfc_c_int_kind;
6980 gfc_clear_attr (&current_attr);
6981 t = gfc_add_flavor (&current_attr, FL_PARAMETER, NULL, NULL);
6982 if (t == FAILURE)
6984 m = MATCH_ERROR;
6985 goto cleanup;
6988 for (;;)
6990 m = enumerator_decl ();
6991 if (m == MATCH_ERROR)
6992 goto cleanup;
6993 if (m == MATCH_NO)
6994 break;
6996 if (gfc_match_eos () == MATCH_YES)
6997 goto cleanup;
6998 if (gfc_match_char (',') != MATCH_YES)
6999 break;
7002 if (gfc_current_state () == COMP_ENUM)
7004 gfc_free_enum_history ();
7005 gfc_error ("Syntax error in ENUMERATOR definition at %C");
7006 m = MATCH_ERROR;
7009 cleanup:
7010 gfc_free_array_spec (current_as);
7011 current_as = NULL;
7012 return m;
7017 /* Match binding attributes. */
7019 static match
7020 match_binding_attributes (gfc_typebound_proc* ba, bool generic, bool ppc)
7022 bool found_passing = false;
7023 bool seen_ptr = false;
7024 match m;
7026 /* Intialize to defaults. Do so even before the MATCH_NO check so that in
7027 this case the defaults are in there. */
7028 ba->access = ACCESS_UNKNOWN;
7029 ba->pass_arg = NULL;
7030 ba->pass_arg_num = 0;
7031 ba->nopass = 0;
7032 ba->non_overridable = 0;
7033 ba->deferred = 0;
7035 /* If we find a comma, we believe there are binding attributes. */
7036 if (gfc_match_char (',') == MATCH_NO)
7038 ba->access = gfc_typebound_default_access;
7039 return MATCH_NO;
7044 /* Access specifier. */
7046 m = gfc_match (" public");
7047 if (m == MATCH_ERROR)
7048 goto error;
7049 if (m == MATCH_YES)
7051 if (ba->access != ACCESS_UNKNOWN)
7053 gfc_error ("Duplicate access-specifier at %C");
7054 goto error;
7057 ba->access = ACCESS_PUBLIC;
7058 continue;
7061 m = gfc_match (" private");
7062 if (m == MATCH_ERROR)
7063 goto error;
7064 if (m == MATCH_YES)
7066 if (ba->access != ACCESS_UNKNOWN)
7068 gfc_error ("Duplicate access-specifier at %C");
7069 goto error;
7072 ba->access = ACCESS_PRIVATE;
7073 continue;
7076 /* If inside GENERIC, the following is not allowed. */
7077 if (!generic)
7080 /* NOPASS flag. */
7081 m = gfc_match (" nopass");
7082 if (m == MATCH_ERROR)
7083 goto error;
7084 if (m == MATCH_YES)
7086 if (found_passing)
7088 gfc_error ("Binding attributes already specify passing,"
7089 " illegal NOPASS at %C");
7090 goto error;
7093 found_passing = true;
7094 ba->nopass = 1;
7095 continue;
7098 /* PASS possibly including argument. */
7099 m = gfc_match (" pass");
7100 if (m == MATCH_ERROR)
7101 goto error;
7102 if (m == MATCH_YES)
7104 char arg[GFC_MAX_SYMBOL_LEN + 1];
7106 if (found_passing)
7108 gfc_error ("Binding attributes already specify passing,"
7109 " illegal PASS at %C");
7110 goto error;
7113 m = gfc_match (" ( %n )", arg);
7114 if (m == MATCH_ERROR)
7115 goto error;
7116 if (m == MATCH_YES)
7117 ba->pass_arg = xstrdup (arg);
7118 gcc_assert ((m == MATCH_YES) == (ba->pass_arg != NULL));
7120 found_passing = true;
7121 ba->nopass = 0;
7122 continue;
7125 if (ppc)
7127 /* POINTER flag. */
7128 m = gfc_match (" pointer");
7129 if (m == MATCH_ERROR)
7130 goto error;
7131 if (m == MATCH_YES)
7133 if (seen_ptr)
7135 gfc_error ("Duplicate POINTER attribute at %C");
7136 goto error;
7139 seen_ptr = true;
7140 /*ba->ppc = 1;*/
7141 continue;
7144 else
7146 /* NON_OVERRIDABLE flag. */
7147 m = gfc_match (" non_overridable");
7148 if (m == MATCH_ERROR)
7149 goto error;
7150 if (m == MATCH_YES)
7152 if (ba->non_overridable)
7154 gfc_error ("Duplicate NON_OVERRIDABLE at %C");
7155 goto error;
7158 ba->non_overridable = 1;
7159 continue;
7162 /* DEFERRED flag. */
7163 m = gfc_match (" deferred");
7164 if (m == MATCH_ERROR)
7165 goto error;
7166 if (m == MATCH_YES)
7168 if (ba->deferred)
7170 gfc_error ("Duplicate DEFERRED at %C");
7171 goto error;
7174 ba->deferred = 1;
7175 continue;
7181 /* Nothing matching found. */
7182 if (generic)
7183 gfc_error ("Expected access-specifier at %C");
7184 else
7185 gfc_error ("Expected binding attribute at %C");
7186 goto error;
7188 while (gfc_match_char (',') == MATCH_YES);
7190 /* NON_OVERRIDABLE and DEFERRED exclude themselves. */
7191 if (ba->non_overridable && ba->deferred)
7193 gfc_error ("NON_OVERRIDABLE and DEFERRED can't both appear at %C");
7194 goto error;
7197 if (ba->access == ACCESS_UNKNOWN)
7198 ba->access = gfc_typebound_default_access;
7200 if (ppc && !seen_ptr)
7202 gfc_error ("POINTER attribute is required for procedure pointer component"
7203 " at %C");
7204 goto error;
7207 return MATCH_YES;
7209 error:
7210 gfc_free (ba->pass_arg);
7211 return MATCH_ERROR;
7215 /* Match a PROCEDURE specific binding inside a derived type. */
7217 static match
7218 match_procedure_in_type (void)
7220 char name[GFC_MAX_SYMBOL_LEN + 1];
7221 char target_buf[GFC_MAX_SYMBOL_LEN + 1];
7222 char* target = NULL;
7223 gfc_typebound_proc* tb;
7224 bool seen_colons;
7225 bool seen_attrs;
7226 match m;
7227 gfc_symtree* stree;
7228 gfc_namespace* ns;
7229 gfc_symbol* block;
7231 /* Check current state. */
7232 gcc_assert (gfc_state_stack->state == COMP_DERIVED_CONTAINS);
7233 block = gfc_state_stack->previous->sym;
7234 gcc_assert (block);
7236 /* Try to match PROCEDURE(interface). */
7237 if (gfc_match (" (") == MATCH_YES)
7239 m = gfc_match_name (target_buf);
7240 if (m == MATCH_ERROR)
7241 return m;
7242 if (m != MATCH_YES)
7244 gfc_error ("Interface-name expected after '(' at %C");
7245 return MATCH_ERROR;
7248 if (gfc_match (" )") != MATCH_YES)
7250 gfc_error ("')' expected at %C");
7251 return MATCH_ERROR;
7254 target = target_buf;
7257 /* Construct the data structure. */
7258 tb = gfc_get_typebound_proc ();
7259 tb->where = gfc_current_locus;
7260 tb->is_generic = 0;
7262 /* Match binding attributes. */
7263 m = match_binding_attributes (tb, false, false);
7264 if (m == MATCH_ERROR)
7265 return m;
7266 seen_attrs = (m == MATCH_YES);
7268 /* Check that attribute DEFERRED is given iff an interface is specified, which
7269 means target != NULL. */
7270 if (tb->deferred && !target)
7272 gfc_error ("Interface must be specified for DEFERRED binding at %C");
7273 return MATCH_ERROR;
7275 if (target && !tb->deferred)
7277 gfc_error ("PROCEDURE(interface) at %C should be declared DEFERRED");
7278 return MATCH_ERROR;
7281 /* Match the colons. */
7282 m = gfc_match (" ::");
7283 if (m == MATCH_ERROR)
7284 return m;
7285 seen_colons = (m == MATCH_YES);
7286 if (seen_attrs && !seen_colons)
7288 gfc_error ("Expected '::' after binding-attributes at %C");
7289 return MATCH_ERROR;
7292 /* Match the binding name. */
7293 m = gfc_match_name (name);
7294 if (m == MATCH_ERROR)
7295 return m;
7296 if (m == MATCH_NO)
7298 gfc_error ("Expected binding name at %C");
7299 return MATCH_ERROR;
7302 /* Try to match the '=> target', if it's there. */
7303 m = gfc_match (" =>");
7304 if (m == MATCH_ERROR)
7305 return m;
7306 if (m == MATCH_YES)
7308 if (tb->deferred)
7310 gfc_error ("'=> target' is invalid for DEFERRED binding at %C");
7311 return MATCH_ERROR;
7314 if (!seen_colons)
7316 gfc_error ("'::' needed in PROCEDURE binding with explicit target"
7317 " at %C");
7318 return MATCH_ERROR;
7321 m = gfc_match_name (target_buf);
7322 if (m == MATCH_ERROR)
7323 return m;
7324 if (m == MATCH_NO)
7326 gfc_error ("Expected binding target after '=>' at %C");
7327 return MATCH_ERROR;
7329 target = target_buf;
7332 /* Now we should have the end. */
7333 m = gfc_match_eos ();
7334 if (m == MATCH_ERROR)
7335 return m;
7336 if (m == MATCH_NO)
7338 gfc_error ("Junk after PROCEDURE declaration at %C");
7339 return MATCH_ERROR;
7342 /* If no target was found, it has the same name as the binding. */
7343 if (!target)
7344 target = name;
7346 /* Get the namespace to insert the symbols into. */
7347 ns = block->f2k_derived;
7348 gcc_assert (ns);
7350 /* If the binding is DEFERRED, check that the containing type is ABSTRACT. */
7351 if (tb->deferred && !block->attr.abstract)
7353 gfc_error ("Type '%s' containing DEFERRED binding at %C is not ABSTRACT",
7354 block->name);
7355 return MATCH_ERROR;
7358 /* See if we already have a binding with this name in the symtree which would
7359 be an error. If a GENERIC already targetted this binding, it may be
7360 already there but then typebound is still NULL. */
7361 stree = gfc_find_symtree (ns->tb_sym_root, name);
7362 if (stree && stree->n.tb)
7364 gfc_error ("There's already a procedure with binding name '%s' for the"
7365 " derived type '%s' at %C", name, block->name);
7366 return MATCH_ERROR;
7369 /* Insert it and set attributes. */
7371 if (!stree)
7373 stree = gfc_new_symtree (&ns->tb_sym_root, name);
7374 gcc_assert (stree);
7376 stree->n.tb = tb;
7378 if (gfc_get_sym_tree (target, gfc_current_ns, &tb->u.specific))
7379 return MATCH_ERROR;
7380 gfc_set_sym_referenced (tb->u.specific->n.sym);
7382 return MATCH_YES;
7386 /* Match a GENERIC procedure binding inside a derived type. */
7388 match
7389 gfc_match_generic (void)
7391 char name[GFC_MAX_SYMBOL_LEN + 1];
7392 gfc_symbol* block;
7393 gfc_typebound_proc tbattr; /* Used for match_binding_attributes. */
7394 gfc_typebound_proc* tb;
7395 gfc_symtree* st;
7396 gfc_namespace* ns;
7397 match m;
7399 /* Check current state. */
7400 if (gfc_current_state () == COMP_DERIVED)
7402 gfc_error ("GENERIC at %C must be inside a derived-type CONTAINS");
7403 return MATCH_ERROR;
7405 if (gfc_current_state () != COMP_DERIVED_CONTAINS)
7406 return MATCH_NO;
7407 block = gfc_state_stack->previous->sym;
7408 ns = block->f2k_derived;
7409 gcc_assert (block && ns);
7411 /* See if we get an access-specifier. */
7412 m = match_binding_attributes (&tbattr, true, false);
7413 if (m == MATCH_ERROR)
7414 goto error;
7416 /* Now the colons, those are required. */
7417 if (gfc_match (" ::") != MATCH_YES)
7419 gfc_error ("Expected '::' at %C");
7420 goto error;
7423 /* The binding name and =>. */
7424 m = gfc_match (" %n =>", name);
7425 if (m == MATCH_ERROR)
7426 return MATCH_ERROR;
7427 if (m == MATCH_NO)
7429 gfc_error ("Expected generic name at %C");
7430 goto error;
7433 /* If there's already something with this name, check that it is another
7434 GENERIC and then extend that rather than build a new node. */
7435 st = gfc_find_symtree (ns->tb_sym_root, name);
7436 if (st)
7438 gcc_assert (st->n.tb);
7439 tb = st->n.tb;
7441 if (!tb->is_generic)
7443 gfc_error ("There's already a non-generic procedure with binding name"
7444 " '%s' for the derived type '%s' at %C",
7445 name, block->name);
7446 goto error;
7449 if (tb->access != tbattr.access)
7451 gfc_error ("Binding at %C must have the same access as already"
7452 " defined binding '%s'", name);
7453 goto error;
7456 else
7458 st = gfc_new_symtree (&ns->tb_sym_root, name);
7459 gcc_assert (st);
7461 st->n.tb = tb = gfc_get_typebound_proc ();
7462 tb->where = gfc_current_locus;
7463 tb->access = tbattr.access;
7464 tb->is_generic = 1;
7465 tb->u.generic = NULL;
7468 /* Now, match all following names as specific targets. */
7471 gfc_symtree* target_st;
7472 gfc_tbp_generic* target;
7474 m = gfc_match_name (name);
7475 if (m == MATCH_ERROR)
7476 goto error;
7477 if (m == MATCH_NO)
7479 gfc_error ("Expected specific binding name at %C");
7480 goto error;
7483 target_st = gfc_get_tbp_symtree (&ns->tb_sym_root, name);
7485 /* See if this is a duplicate specification. */
7486 for (target = tb->u.generic; target; target = target->next)
7487 if (target_st == target->specific_st)
7489 gfc_error ("'%s' already defined as specific binding for the"
7490 " generic '%s' at %C", name, st->name);
7491 goto error;
7494 target = gfc_get_tbp_generic ();
7495 target->specific_st = target_st;
7496 target->specific = NULL;
7497 target->next = tb->u.generic;
7498 tb->u.generic = target;
7500 while (gfc_match (" ,") == MATCH_YES);
7502 /* Here should be the end. */
7503 if (gfc_match_eos () != MATCH_YES)
7505 gfc_error ("Junk after GENERIC binding at %C");
7506 goto error;
7509 return MATCH_YES;
7511 error:
7512 return MATCH_ERROR;
7516 /* Match a FINAL declaration inside a derived type. */
7518 match
7519 gfc_match_final_decl (void)
7521 char name[GFC_MAX_SYMBOL_LEN + 1];
7522 gfc_symbol* sym;
7523 match m;
7524 gfc_namespace* module_ns;
7525 bool first, last;
7526 gfc_symbol* block;
7528 if (gfc_state_stack->state != COMP_DERIVED_CONTAINS)
7530 gfc_error ("FINAL declaration at %C must be inside a derived type "
7531 "CONTAINS section");
7532 return MATCH_ERROR;
7535 block = gfc_state_stack->previous->sym;
7536 gcc_assert (block);
7538 if (!gfc_state_stack->previous || !gfc_state_stack->previous->previous
7539 || gfc_state_stack->previous->previous->state != COMP_MODULE)
7541 gfc_error ("Derived type declaration with FINAL at %C must be in the"
7542 " specification part of a MODULE");
7543 return MATCH_ERROR;
7546 module_ns = gfc_current_ns;
7547 gcc_assert (module_ns);
7548 gcc_assert (module_ns->proc_name->attr.flavor == FL_MODULE);
7550 /* Match optional ::, don't care about MATCH_YES or MATCH_NO. */
7551 if (gfc_match (" ::") == MATCH_ERROR)
7552 return MATCH_ERROR;
7554 /* Match the sequence of procedure names. */
7555 first = true;
7556 last = false;
7559 gfc_finalizer* f;
7561 if (first && gfc_match_eos () == MATCH_YES)
7563 gfc_error ("Empty FINAL at %C");
7564 return MATCH_ERROR;
7567 m = gfc_match_name (name);
7568 if (m == MATCH_NO)
7570 gfc_error ("Expected module procedure name at %C");
7571 return MATCH_ERROR;
7573 else if (m != MATCH_YES)
7574 return MATCH_ERROR;
7576 if (gfc_match_eos () == MATCH_YES)
7577 last = true;
7578 if (!last && gfc_match_char (',') != MATCH_YES)
7580 gfc_error ("Expected ',' at %C");
7581 return MATCH_ERROR;
7584 if (gfc_get_symbol (name, module_ns, &sym))
7586 gfc_error ("Unknown procedure name \"%s\" at %C", name);
7587 return MATCH_ERROR;
7590 /* Mark the symbol as module procedure. */
7591 if (sym->attr.proc != PROC_MODULE
7592 && gfc_add_procedure (&sym->attr, PROC_MODULE,
7593 sym->name, NULL) == FAILURE)
7594 return MATCH_ERROR;
7596 /* Check if we already have this symbol in the list, this is an error. */
7597 for (f = block->f2k_derived->finalizers; f; f = f->next)
7598 if (f->proc_sym == sym)
7600 gfc_error ("'%s' at %C is already defined as FINAL procedure!",
7601 name);
7602 return MATCH_ERROR;
7605 /* Add this symbol to the list of finalizers. */
7606 gcc_assert (block->f2k_derived);
7607 ++sym->refs;
7608 f = XCNEW (gfc_finalizer);
7609 f->proc_sym = sym;
7610 f->proc_tree = NULL;
7611 f->where = gfc_current_locus;
7612 f->next = block->f2k_derived->finalizers;
7613 block->f2k_derived->finalizers = f;
7615 first = false;
7617 while (!last);
7619 return MATCH_YES;