2009-07-17 Richard Guenther <rguenther@suse.de>
[official-gcc.git] / gcc / fortran / decl.c
blobe2816348643bbce14ea4cc5bbe5797aaf2623e05
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, bool allow_subroutine)
701 gfc_state_data *s;
702 gfc_symtree *st;
703 int i;
705 i = gfc_get_sym_tree (name, NULL, &st, allow_subroutine);
706 if (i == 0)
708 *result = st ? st->n.sym : NULL;
709 goto end;
712 if (gfc_current_state () != COMP_SUBROUTINE
713 && gfc_current_state () != COMP_FUNCTION)
714 goto end;
716 s = gfc_state_stack->previous;
717 if (s == NULL)
718 goto end;
720 if (s->state != COMP_INTERFACE)
721 goto end;
722 if (s->sym == NULL)
723 goto end; /* Nameless interface. */
725 if (strcmp (name, s->sym->name) == 0)
727 *result = s->sym;
728 return 0;
731 end:
732 return i;
736 /* Special subroutine for getting a symbol node associated with a
737 procedure name, used in SUBROUTINE and FUNCTION statements. The
738 symbol is created in the parent using with symtree node in the
739 child unit pointing to the symbol. If the current namespace has no
740 parent, then the symbol is just created in the current unit. */
742 static int
743 get_proc_name (const char *name, gfc_symbol **result, bool module_fcn_entry)
745 gfc_symtree *st;
746 gfc_symbol *sym;
747 int rc = 0;
749 /* Module functions have to be left in their own namespace because
750 they have potentially (almost certainly!) already been referenced.
751 In this sense, they are rather like external functions. This is
752 fixed up in resolve.c(resolve_entries), where the symbol name-
753 space is set to point to the master function, so that the fake
754 result mechanism can work. */
755 if (module_fcn_entry)
757 /* Present if entry is declared to be a module procedure. */
758 rc = gfc_find_symbol (name, gfc_current_ns->parent, 0, result);
760 if (*result == NULL)
761 rc = gfc_get_symbol (name, NULL, result);
762 else if (!gfc_get_symbol (name, NULL, &sym) && sym
763 && (*result)->ts.type == BT_UNKNOWN
764 && sym->attr.flavor == FL_UNKNOWN)
765 /* Pick up the typespec for the entry, if declared in the function
766 body. Note that this symbol is FL_UNKNOWN because it will
767 only have appeared in a type declaration. The local symtree
768 is set to point to the module symbol and a unique symtree
769 to the local version. This latter ensures a correct clearing
770 of the symbols. */
772 /* If the ENTRY proceeds its specification, we need to ensure
773 that this does not raise a "has no IMPLICIT type" error. */
774 if (sym->ts.type == BT_UNKNOWN)
775 sym->attr.untyped = 1;
777 (*result)->ts = sym->ts;
779 /* Put the symbol in the procedure namespace so that, should
780 the ENTRY precede its specification, the specification
781 can be applied. */
782 (*result)->ns = gfc_current_ns;
784 gfc_find_sym_tree (name, gfc_current_ns, 0, &st);
785 st->n.sym = *result;
786 st = gfc_get_unique_symtree (gfc_current_ns);
787 st->n.sym = sym;
790 else
791 rc = gfc_get_symbol (name, gfc_current_ns->parent, result);
793 if (rc)
794 return rc;
796 sym = *result;
797 gfc_current_ns->refs++;
799 if (sym && !sym->gfc_new && gfc_current_state () != COMP_INTERFACE)
801 /* Trap another encompassed procedure with the same name. All
802 these conditions are necessary to avoid picking up an entry
803 whose name clashes with that of the encompassing procedure;
804 this is handled using gsymbols to register unique,globally
805 accessible names. */
806 if (sym->attr.flavor != 0
807 && sym->attr.proc != 0
808 && (sym->attr.subroutine || sym->attr.function)
809 && sym->attr.if_source != IFSRC_UNKNOWN)
810 gfc_error_now ("Procedure '%s' at %C is already defined at %L",
811 name, &sym->declared_at);
813 /* Trap a procedure with a name the same as interface in the
814 encompassing scope. */
815 if (sym->attr.generic != 0
816 && (sym->attr.subroutine || sym->attr.function)
817 && !sym->attr.mod_proc)
818 gfc_error_now ("Name '%s' at %C is already defined"
819 " as a generic interface at %L",
820 name, &sym->declared_at);
822 /* Trap declarations of attributes in encompassing scope. The
823 signature for this is that ts.kind is set. Legitimate
824 references only set ts.type. */
825 if (sym->ts.kind != 0
826 && !sym->attr.implicit_type
827 && sym->attr.proc == 0
828 && gfc_current_ns->parent != NULL
829 && sym->attr.access == 0
830 && !module_fcn_entry)
831 gfc_error_now ("Procedure '%s' at %C has an explicit interface "
832 "and must not have attributes declared at %L",
833 name, &sym->declared_at);
836 if (gfc_current_ns->parent == NULL || *result == NULL)
837 return rc;
839 /* Module function entries will already have a symtree in
840 the current namespace but will need one at module level. */
841 if (module_fcn_entry)
843 /* Present if entry is declared to be a module procedure. */
844 rc = gfc_find_sym_tree (name, gfc_current_ns->parent, 0, &st);
845 if (st == NULL)
846 st = gfc_new_symtree (&gfc_current_ns->parent->sym_root, name);
848 else
849 st = gfc_new_symtree (&gfc_current_ns->sym_root, name);
851 st->n.sym = sym;
852 sym->refs++;
854 /* See if the procedure should be a module procedure. */
856 if (((sym->ns->proc_name != NULL
857 && sym->ns->proc_name->attr.flavor == FL_MODULE
858 && sym->attr.proc != PROC_MODULE)
859 || (module_fcn_entry && sym->attr.proc != PROC_MODULE))
860 && gfc_add_procedure (&sym->attr, PROC_MODULE,
861 sym->name, NULL) == FAILURE)
862 rc = 2;
864 return rc;
868 /* Verify that the given symbol representing a parameter is C
869 interoperable, by checking to see if it was marked as such after
870 its declaration. If the given symbol is not interoperable, a
871 warning is reported, thus removing the need to return the status to
872 the calling function. The standard does not require the user use
873 one of the iso_c_binding named constants to declare an
874 interoperable parameter, but we can't be sure if the param is C
875 interop or not if the user doesn't. For example, integer(4) may be
876 legal Fortran, but doesn't have meaning in C. It may interop with
877 a number of the C types, which causes a problem because the
878 compiler can't know which one. This code is almost certainly not
879 portable, and the user will get what they deserve if the C type
880 across platforms isn't always interoperable with integer(4). If
881 the user had used something like integer(c_int) or integer(c_long),
882 the compiler could have automatically handled the varying sizes
883 across platforms. */
885 gfc_try
886 verify_c_interop_param (gfc_symbol *sym)
888 int is_c_interop = 0;
889 gfc_try retval = SUCCESS;
891 /* We check implicitly typed variables in symbol.c:gfc_set_default_type().
892 Don't repeat the checks here. */
893 if (sym->attr.implicit_type)
894 return SUCCESS;
896 /* For subroutines or functions that are passed to a BIND(C) procedure,
897 they're interoperable if they're BIND(C) and their params are all
898 interoperable. */
899 if (sym->attr.flavor == FL_PROCEDURE)
901 if (sym->attr.is_bind_c == 0)
903 gfc_error_now ("Procedure '%s' at %L must have the BIND(C) "
904 "attribute to be C interoperable", sym->name,
905 &(sym->declared_at));
907 return FAILURE;
909 else
911 if (sym->attr.is_c_interop == 1)
912 /* We've already checked this procedure; don't check it again. */
913 return SUCCESS;
914 else
915 return verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
916 sym->common_block);
920 /* See if we've stored a reference to a procedure that owns sym. */
921 if (sym->ns != NULL && sym->ns->proc_name != NULL)
923 if (sym->ns->proc_name->attr.is_bind_c == 1)
925 is_c_interop =
926 (verify_c_interop (&(sym->ts))
927 == SUCCESS ? 1 : 0);
929 if (is_c_interop != 1)
931 /* Make personalized messages to give better feedback. */
932 if (sym->ts.type == BT_DERIVED)
933 gfc_error ("Type '%s' at %L is a parameter to the BIND(C) "
934 " procedure '%s' but is not C interoperable "
935 "because derived type '%s' is not C interoperable",
936 sym->name, &(sym->declared_at),
937 sym->ns->proc_name->name,
938 sym->ts.derived->name);
939 else
940 gfc_warning ("Variable '%s' at %L is a parameter to the "
941 "BIND(C) procedure '%s' but may not be C "
942 "interoperable",
943 sym->name, &(sym->declared_at),
944 sym->ns->proc_name->name);
947 /* Character strings are only C interoperable if they have a
948 length of 1. */
949 if (sym->ts.type == BT_CHARACTER)
951 gfc_charlen *cl = sym->ts.cl;
952 if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT
953 || mpz_cmp_si (cl->length->value.integer, 1) != 0)
955 gfc_error ("Character argument '%s' at %L "
956 "must be length 1 because "
957 "procedure '%s' is BIND(C)",
958 sym->name, &sym->declared_at,
959 sym->ns->proc_name->name);
960 retval = FAILURE;
964 /* We have to make sure that any param to a bind(c) routine does
965 not have the allocatable, pointer, or optional attributes,
966 according to J3/04-007, section 5.1. */
967 if (sym->attr.allocatable == 1)
969 gfc_error ("Variable '%s' at %L cannot have the "
970 "ALLOCATABLE attribute because procedure '%s'"
971 " is BIND(C)", sym->name, &(sym->declared_at),
972 sym->ns->proc_name->name);
973 retval = FAILURE;
976 if (sym->attr.pointer == 1)
978 gfc_error ("Variable '%s' at %L cannot have the "
979 "POINTER attribute because procedure '%s'"
980 " is BIND(C)", sym->name, &(sym->declared_at),
981 sym->ns->proc_name->name);
982 retval = FAILURE;
985 if (sym->attr.optional == 1)
987 gfc_error ("Variable '%s' at %L cannot have the "
988 "OPTIONAL attribute because procedure '%s'"
989 " is BIND(C)", sym->name, &(sym->declared_at),
990 sym->ns->proc_name->name);
991 retval = FAILURE;
994 /* Make sure that if it has the dimension attribute, that it is
995 either assumed size or explicit shape. */
996 if (sym->as != NULL)
998 if (sym->as->type == AS_ASSUMED_SHAPE)
1000 gfc_error ("Assumed-shape array '%s' at %L cannot be an "
1001 "argument to the procedure '%s' at %L because "
1002 "the procedure is BIND(C)", sym->name,
1003 &(sym->declared_at), sym->ns->proc_name->name,
1004 &(sym->ns->proc_name->declared_at));
1005 retval = FAILURE;
1008 if (sym->as->type == AS_DEFERRED)
1010 gfc_error ("Deferred-shape array '%s' at %L cannot be an "
1011 "argument to the procedure '%s' at %L because "
1012 "the procedure is BIND(C)", sym->name,
1013 &(sym->declared_at), sym->ns->proc_name->name,
1014 &(sym->ns->proc_name->declared_at));
1015 retval = FAILURE;
1021 return retval;
1025 /* Function called by variable_decl() that adds a name to the symbol table. */
1027 static gfc_try
1028 build_sym (const char *name, gfc_charlen *cl,
1029 gfc_array_spec **as, locus *var_locus)
1031 symbol_attribute attr;
1032 gfc_symbol *sym;
1034 if (gfc_get_symbol (name, NULL, &sym))
1035 return FAILURE;
1037 /* Start updating the symbol table. Add basic type attribute if present. */
1038 if (current_ts.type != BT_UNKNOWN
1039 && (sym->attr.implicit_type == 0
1040 || !gfc_compare_types (&sym->ts, &current_ts))
1041 && gfc_add_type (sym, &current_ts, var_locus) == FAILURE)
1042 return FAILURE;
1044 if (sym->ts.type == BT_CHARACTER)
1045 sym->ts.cl = cl;
1047 /* Add dimension attribute if present. */
1048 if (gfc_set_array_spec (sym, *as, var_locus) == FAILURE)
1049 return FAILURE;
1050 *as = NULL;
1052 /* Add attribute to symbol. The copy is so that we can reset the
1053 dimension attribute. */
1054 attr = current_attr;
1055 attr.dimension = 0;
1057 if (gfc_copy_attr (&sym->attr, &attr, var_locus) == FAILURE)
1058 return FAILURE;
1060 /* Finish any work that may need to be done for the binding label,
1061 if it's a bind(c). The bind(c) attr is found before the symbol
1062 is made, and before the symbol name (for data decls), so the
1063 current_ts is holding the binding label, or nothing if the
1064 name= attr wasn't given. Therefore, test here if we're dealing
1065 with a bind(c) and make sure the binding label is set correctly. */
1066 if (sym->attr.is_bind_c == 1)
1068 if (sym->binding_label[0] == '\0')
1070 /* Set the binding label and verify that if a NAME= was specified
1071 then only one identifier was in the entity-decl-list. */
1072 if (set_binding_label (sym->binding_label, sym->name,
1073 num_idents_on_line) == FAILURE)
1074 return FAILURE;
1078 /* See if we know we're in a common block, and if it's a bind(c)
1079 common then we need to make sure we're an interoperable type. */
1080 if (sym->attr.in_common == 1)
1082 /* Test the common block object. */
1083 if (sym->common_block != NULL && sym->common_block->is_bind_c == 1
1084 && sym->ts.is_c_interop != 1)
1086 gfc_error_now ("Variable '%s' in common block '%s' at %C "
1087 "must be declared with a C interoperable "
1088 "kind since common block '%s' is BIND(C)",
1089 sym->name, sym->common_block->name,
1090 sym->common_block->name);
1091 gfc_clear_error ();
1095 sym->attr.implied_index = 0;
1097 return SUCCESS;
1101 /* Set character constant to the given length. The constant will be padded or
1102 truncated. If we're inside an array constructor without a typespec, we
1103 additionally check that all elements have the same length; check_len -1
1104 means no checking. */
1106 void
1107 gfc_set_constant_character_len (int len, gfc_expr *expr, int check_len)
1109 gfc_char_t *s;
1110 int slen;
1112 gcc_assert (expr->expr_type == EXPR_CONSTANT);
1113 gcc_assert (expr->ts.type == BT_CHARACTER);
1115 slen = expr->value.character.length;
1116 if (len != slen)
1118 s = gfc_get_wide_string (len + 1);
1119 memcpy (s, expr->value.character.string,
1120 MIN (len, slen) * sizeof (gfc_char_t));
1121 if (len > slen)
1122 gfc_wide_memset (&s[slen], ' ', len - slen);
1124 if (gfc_option.warn_character_truncation && slen > len)
1125 gfc_warning_now ("CHARACTER expression at %L is being truncated "
1126 "(%d/%d)", &expr->where, slen, len);
1128 /* Apply the standard by 'hand' otherwise it gets cleared for
1129 initializers. */
1130 if (check_len != -1 && slen != check_len
1131 && !(gfc_option.allow_std & GFC_STD_GNU))
1132 gfc_error_now ("The CHARACTER elements of the array constructor "
1133 "at %L must have the same length (%d/%d)",
1134 &expr->where, slen, check_len);
1136 s[len] = '\0';
1137 gfc_free (expr->value.character.string);
1138 expr->value.character.string = s;
1139 expr->value.character.length = len;
1144 /* Function to create and update the enumerator history
1145 using the information passed as arguments.
1146 Pointer "max_enum" is also updated, to point to
1147 enum history node containing largest initializer.
1149 SYM points to the symbol node of enumerator.
1150 INIT points to its enumerator value. */
1152 static void
1153 create_enum_history (gfc_symbol *sym, gfc_expr *init)
1155 enumerator_history *new_enum_history;
1156 gcc_assert (sym != NULL && init != NULL);
1158 new_enum_history = XCNEW (enumerator_history);
1160 new_enum_history->sym = sym;
1161 new_enum_history->initializer = init;
1162 new_enum_history->next = NULL;
1164 if (enum_history == NULL)
1166 enum_history = new_enum_history;
1167 max_enum = enum_history;
1169 else
1171 new_enum_history->next = enum_history;
1172 enum_history = new_enum_history;
1174 if (mpz_cmp (max_enum->initializer->value.integer,
1175 new_enum_history->initializer->value.integer) < 0)
1176 max_enum = new_enum_history;
1181 /* Function to free enum kind history. */
1183 void
1184 gfc_free_enum_history (void)
1186 enumerator_history *current = enum_history;
1187 enumerator_history *next;
1189 while (current != NULL)
1191 next = current->next;
1192 gfc_free (current);
1193 current = next;
1195 max_enum = NULL;
1196 enum_history = NULL;
1200 /* Function called by variable_decl() that adds an initialization
1201 expression to a symbol. */
1203 static gfc_try
1204 add_init_expr_to_sym (const char *name, gfc_expr **initp, locus *var_locus)
1206 symbol_attribute attr;
1207 gfc_symbol *sym;
1208 gfc_expr *init;
1210 init = *initp;
1211 if (find_special (name, &sym, false))
1212 return FAILURE;
1214 attr = sym->attr;
1216 /* If this symbol is confirming an implicit parameter type,
1217 then an initialization expression is not allowed. */
1218 if (attr.flavor == FL_PARAMETER
1219 && sym->value != NULL
1220 && *initp != NULL)
1222 gfc_error ("Initializer not allowed for PARAMETER '%s' at %C",
1223 sym->name);
1224 return FAILURE;
1227 if (init == NULL)
1229 /* An initializer is required for PARAMETER declarations. */
1230 if (attr.flavor == FL_PARAMETER)
1232 gfc_error ("PARAMETER at %L is missing an initializer", var_locus);
1233 return FAILURE;
1236 else
1238 /* If a variable appears in a DATA block, it cannot have an
1239 initializer. */
1240 if (sym->attr.data)
1242 gfc_error ("Variable '%s' at %C with an initializer already "
1243 "appears in a DATA statement", sym->name);
1244 return FAILURE;
1247 /* Check if the assignment can happen. This has to be put off
1248 until later for a derived type variable. */
1249 if (sym->ts.type != BT_DERIVED && init->ts.type != BT_DERIVED
1250 && gfc_check_assign_symbol (sym, init) == FAILURE)
1251 return FAILURE;
1253 if (sym->ts.type == BT_CHARACTER && sym->ts.cl)
1255 /* Update symbol character length according initializer. */
1256 if (sym->ts.cl->length == NULL)
1258 int clen;
1259 /* If there are multiple CHARACTER variables declared on the
1260 same line, we don't want them to share the same length. */
1261 sym->ts.cl = gfc_get_charlen ();
1262 sym->ts.cl->next = gfc_current_ns->cl_list;
1263 gfc_current_ns->cl_list = sym->ts.cl;
1265 if (sym->attr.flavor == FL_PARAMETER)
1267 if (init->expr_type == EXPR_CONSTANT)
1269 clen = init->value.character.length;
1270 sym->ts.cl->length = gfc_int_expr (clen);
1272 else if (init->expr_type == EXPR_ARRAY)
1274 gfc_expr *p = init->value.constructor->expr;
1275 clen = p->value.character.length;
1276 sym->ts.cl->length = gfc_int_expr (clen);
1278 else if (init->ts.cl && init->ts.cl->length)
1279 sym->ts.cl->length =
1280 gfc_copy_expr (sym->value->ts.cl->length);
1283 /* Update initializer character length according symbol. */
1284 else if (sym->ts.cl->length->expr_type == EXPR_CONSTANT)
1286 int len = mpz_get_si (sym->ts.cl->length->value.integer);
1287 gfc_constructor * p;
1289 if (init->expr_type == EXPR_CONSTANT)
1290 gfc_set_constant_character_len (len, init, -1);
1291 else if (init->expr_type == EXPR_ARRAY)
1293 /* Build a new charlen to prevent simplification from
1294 deleting the length before it is resolved. */
1295 init->ts.cl = gfc_get_charlen ();
1296 init->ts.cl->next = gfc_current_ns->cl_list;
1297 gfc_current_ns->cl_list = sym->ts.cl;
1298 init->ts.cl->length = gfc_copy_expr (sym->ts.cl->length);
1300 for (p = init->value.constructor; p; p = p->next)
1301 gfc_set_constant_character_len (len, p->expr, -1);
1306 /* Need to check if the expression we initialized this
1307 to was one of the iso_c_binding named constants. If so,
1308 and we're a parameter (constant), let it be iso_c.
1309 For example:
1310 integer(c_int), parameter :: my_int = c_int
1311 integer(my_int) :: my_int_2
1312 If we mark my_int as iso_c (since we can see it's value
1313 is equal to one of the named constants), then my_int_2
1314 will be considered C interoperable. */
1315 if (sym->ts.type != BT_CHARACTER && sym->ts.type != BT_DERIVED)
1317 sym->ts.is_iso_c |= init->ts.is_iso_c;
1318 sym->ts.is_c_interop |= init->ts.is_c_interop;
1319 /* attr bits needed for module files. */
1320 sym->attr.is_iso_c |= init->ts.is_iso_c;
1321 sym->attr.is_c_interop |= init->ts.is_c_interop;
1322 if (init->ts.is_iso_c)
1323 sym->ts.f90_type = init->ts.f90_type;
1326 /* Add initializer. Make sure we keep the ranks sane. */
1327 if (sym->attr.dimension && init->rank == 0)
1329 mpz_t size;
1330 gfc_expr *array;
1331 gfc_constructor *c;
1332 int n;
1333 if (sym->attr.flavor == FL_PARAMETER
1334 && init->expr_type == EXPR_CONSTANT
1335 && spec_size (sym->as, &size) == SUCCESS
1336 && mpz_cmp_si (size, 0) > 0)
1338 array = gfc_start_constructor (init->ts.type, init->ts.kind,
1339 &init->where);
1341 array->value.constructor = c = NULL;
1342 for (n = 0; n < (int)mpz_get_si (size); n++)
1344 if (array->value.constructor == NULL)
1346 array->value.constructor = c = gfc_get_constructor ();
1347 c->expr = init;
1349 else
1351 c->next = gfc_get_constructor ();
1352 c = c->next;
1353 c->expr = gfc_copy_expr (init);
1357 array->shape = gfc_get_shape (sym->as->rank);
1358 for (n = 0; n < sym->as->rank; n++)
1359 spec_dimen_size (sym->as, n, &array->shape[n]);
1361 init = array;
1362 mpz_clear (size);
1364 init->rank = sym->as->rank;
1367 sym->value = init;
1368 if (sym->attr.save == SAVE_NONE)
1369 sym->attr.save = SAVE_IMPLICIT;
1370 *initp = NULL;
1373 return SUCCESS;
1377 /* Function called by variable_decl() that adds a name to a structure
1378 being built. */
1380 static gfc_try
1381 build_struct (const char *name, gfc_charlen *cl, gfc_expr **init,
1382 gfc_array_spec **as)
1384 gfc_component *c;
1386 /* If the current symbol is of the same derived type that we're
1387 constructing, it must have the pointer attribute. */
1388 if (current_ts.type == BT_DERIVED
1389 && current_ts.derived == gfc_current_block ()
1390 && current_attr.pointer == 0)
1392 gfc_error ("Component at %C must have the POINTER attribute");
1393 return FAILURE;
1396 if (gfc_current_block ()->attr.pointer && (*as)->rank != 0)
1398 if ((*as)->type != AS_DEFERRED && (*as)->type != AS_EXPLICIT)
1400 gfc_error ("Array component of structure at %C must have explicit "
1401 "or deferred shape");
1402 return FAILURE;
1406 if (gfc_add_component (gfc_current_block (), name, &c) == FAILURE)
1407 return FAILURE;
1409 c->ts = current_ts;
1410 c->ts.cl = cl;
1411 c->attr = current_attr;
1413 c->initializer = *init;
1414 *init = NULL;
1416 c->as = *as;
1417 if (c->as != NULL)
1418 c->attr.dimension = 1;
1419 *as = NULL;
1421 /* Should this ever get more complicated, combine with similar section
1422 in add_init_expr_to_sym into a separate function. */
1423 if (c->ts.type == BT_CHARACTER && !c->attr.pointer && c->initializer && c->ts.cl
1424 && c->ts.cl->length && c->ts.cl->length->expr_type == EXPR_CONSTANT)
1426 int len;
1428 gcc_assert (c->ts.cl && c->ts.cl->length);
1429 gcc_assert (c->ts.cl->length->expr_type == EXPR_CONSTANT);
1430 gcc_assert (c->ts.cl->length->ts.type == BT_INTEGER);
1432 len = mpz_get_si (c->ts.cl->length->value.integer);
1434 if (c->initializer->expr_type == EXPR_CONSTANT)
1435 gfc_set_constant_character_len (len, c->initializer, -1);
1436 else if (mpz_cmp (c->ts.cl->length->value.integer,
1437 c->initializer->ts.cl->length->value.integer))
1439 bool has_ts;
1440 gfc_constructor *ctor = c->initializer->value.constructor;
1442 has_ts = (c->initializer->ts.cl
1443 && c->initializer->ts.cl->length_from_typespec);
1445 if (ctor)
1447 int first_len;
1449 /* Remember the length of the first element for checking
1450 that all elements *in the constructor* have the same
1451 length. This need not be the length of the LHS! */
1452 gcc_assert (ctor->expr->expr_type == EXPR_CONSTANT);
1453 gcc_assert (ctor->expr->ts.type == BT_CHARACTER);
1454 first_len = ctor->expr->value.character.length;
1456 for (; ctor; ctor = ctor->next)
1458 if (ctor->expr->expr_type == EXPR_CONSTANT)
1459 gfc_set_constant_character_len (len, ctor->expr,
1460 has_ts ? -1 : first_len);
1466 /* Check array components. */
1467 if (!c->attr.dimension)
1469 if (c->attr.allocatable)
1471 gfc_error ("Allocatable component at %C must be an array");
1472 return FAILURE;
1474 else
1475 return SUCCESS;
1478 if (c->attr.pointer)
1480 if (c->as->type != AS_DEFERRED)
1482 gfc_error ("Pointer array component of structure at %C must have a "
1483 "deferred shape");
1484 return FAILURE;
1487 else if (c->attr.allocatable)
1489 if (c->as->type != AS_DEFERRED)
1491 gfc_error ("Allocatable component of structure at %C must have a "
1492 "deferred shape");
1493 return FAILURE;
1496 else
1498 if (c->as->type != AS_EXPLICIT)
1500 gfc_error ("Array component of structure at %C must have an "
1501 "explicit shape");
1502 return FAILURE;
1506 return SUCCESS;
1510 /* Match a 'NULL()', and possibly take care of some side effects. */
1512 match
1513 gfc_match_null (gfc_expr **result)
1515 gfc_symbol *sym;
1516 gfc_expr *e;
1517 match m;
1519 m = gfc_match (" null ( )");
1520 if (m != MATCH_YES)
1521 return m;
1523 /* The NULL symbol now has to be/become an intrinsic function. */
1524 if (gfc_get_symbol ("null", NULL, &sym))
1526 gfc_error ("NULL() initialization at %C is ambiguous");
1527 return MATCH_ERROR;
1530 gfc_intrinsic_symbol (sym);
1532 if (sym->attr.proc != PROC_INTRINSIC
1533 && (gfc_add_procedure (&sym->attr, PROC_INTRINSIC,
1534 sym->name, NULL) == FAILURE
1535 || gfc_add_function (&sym->attr, sym->name, NULL) == FAILURE))
1536 return MATCH_ERROR;
1538 e = gfc_get_expr ();
1539 e->where = gfc_current_locus;
1540 e->expr_type = EXPR_NULL;
1541 e->ts.type = BT_UNKNOWN;
1543 *result = e;
1545 return MATCH_YES;
1549 /* Match a variable name with an optional initializer. When this
1550 subroutine is called, a variable is expected to be parsed next.
1551 Depending on what is happening at the moment, updates either the
1552 symbol table or the current interface. */
1554 static match
1555 variable_decl (int elem)
1557 char name[GFC_MAX_SYMBOL_LEN + 1];
1558 gfc_expr *initializer, *char_len;
1559 gfc_array_spec *as;
1560 gfc_array_spec *cp_as; /* Extra copy for Cray Pointees. */
1561 gfc_charlen *cl;
1562 locus var_locus;
1563 match m;
1564 gfc_try t;
1565 gfc_symbol *sym;
1566 locus old_locus;
1568 initializer = NULL;
1569 as = NULL;
1570 cp_as = NULL;
1571 old_locus = gfc_current_locus;
1573 /* When we get here, we've just matched a list of attributes and
1574 maybe a type and a double colon. The next thing we expect to see
1575 is the name of the symbol. */
1576 m = gfc_match_name (name);
1577 if (m != MATCH_YES)
1578 goto cleanup;
1580 var_locus = gfc_current_locus;
1582 /* Now we could see the optional array spec. or character length. */
1583 m = gfc_match_array_spec (&as);
1584 if (gfc_option.flag_cray_pointer && m == MATCH_YES)
1585 cp_as = gfc_copy_array_spec (as);
1586 else if (m == MATCH_ERROR)
1587 goto cleanup;
1589 if (m == MATCH_NO)
1590 as = gfc_copy_array_spec (current_as);
1592 char_len = NULL;
1593 cl = NULL;
1595 if (current_ts.type == BT_CHARACTER)
1597 switch (match_char_length (&char_len))
1599 case MATCH_YES:
1600 cl = gfc_get_charlen ();
1601 cl->next = gfc_current_ns->cl_list;
1602 gfc_current_ns->cl_list = cl;
1604 cl->length = char_len;
1605 break;
1607 /* Non-constant lengths need to be copied after the first
1608 element. Also copy assumed lengths. */
1609 case MATCH_NO:
1610 if (elem > 1
1611 && (current_ts.cl->length == NULL
1612 || current_ts.cl->length->expr_type != EXPR_CONSTANT))
1614 cl = gfc_get_charlen ();
1615 cl->next = gfc_current_ns->cl_list;
1616 gfc_current_ns->cl_list = cl;
1617 cl->length = gfc_copy_expr (current_ts.cl->length);
1619 else
1620 cl = current_ts.cl;
1622 break;
1624 case MATCH_ERROR:
1625 goto cleanup;
1629 /* If this symbol has already shown up in a Cray Pointer declaration,
1630 then we want to set the type & bail out. */
1631 if (gfc_option.flag_cray_pointer)
1633 gfc_find_symbol (name, gfc_current_ns, 1, &sym);
1634 if (sym != NULL && sym->attr.cray_pointee)
1636 sym->ts.type = current_ts.type;
1637 sym->ts.kind = current_ts.kind;
1638 sym->ts.cl = cl;
1639 sym->ts.derived = current_ts.derived;
1640 sym->ts.is_c_interop = current_ts.is_c_interop;
1641 sym->ts.is_iso_c = current_ts.is_iso_c;
1642 m = MATCH_YES;
1644 /* Check to see if we have an array specification. */
1645 if (cp_as != NULL)
1647 if (sym->as != NULL)
1649 gfc_error ("Duplicate array spec for Cray pointee at %C");
1650 gfc_free_array_spec (cp_as);
1651 m = MATCH_ERROR;
1652 goto cleanup;
1654 else
1656 if (gfc_set_array_spec (sym, cp_as, &var_locus) == FAILURE)
1657 gfc_internal_error ("Couldn't set pointee array spec.");
1659 /* Fix the array spec. */
1660 m = gfc_mod_pointee_as (sym->as);
1661 if (m == MATCH_ERROR)
1662 goto cleanup;
1665 goto cleanup;
1667 else
1669 gfc_free_array_spec (cp_as);
1673 /* Procedure pointer as function result. */
1674 if (gfc_current_state () == COMP_FUNCTION
1675 && strcmp ("ppr@", gfc_current_block ()->name) == 0
1676 && strcmp (name, gfc_current_block ()->ns->proc_name->name) == 0)
1677 strcpy (name, "ppr@");
1679 if (gfc_current_state () == COMP_FUNCTION
1680 && strcmp (name, gfc_current_block ()->name) == 0
1681 && gfc_current_block ()->result
1682 && strcmp ("ppr@", gfc_current_block ()->result->name) == 0)
1683 strcpy (name, "ppr@");
1685 /* OK, we've successfully matched the declaration. Now put the
1686 symbol in the current namespace, because it might be used in the
1687 optional initialization expression for this symbol, e.g. this is
1688 perfectly legal:
1690 integer, parameter :: i = huge(i)
1692 This is only true for parameters or variables of a basic type.
1693 For components of derived types, it is not true, so we don't
1694 create a symbol for those yet. If we fail to create the symbol,
1695 bail out. */
1696 if (gfc_current_state () != COMP_DERIVED
1697 && build_sym (name, cl, &as, &var_locus) == FAILURE)
1699 m = MATCH_ERROR;
1700 goto cleanup;
1703 /* An interface body specifies all of the procedure's
1704 characteristics and these shall be consistent with those
1705 specified in the procedure definition, except that the interface
1706 may specify a procedure that is not pure if the procedure is
1707 defined to be pure(12.3.2). */
1708 if (current_ts.type == BT_DERIVED
1709 && gfc_current_ns->proc_name
1710 && gfc_current_ns->proc_name->attr.if_source == IFSRC_IFBODY
1711 && current_ts.derived->ns != gfc_current_ns)
1713 gfc_symtree *st;
1714 st = gfc_find_symtree (gfc_current_ns->sym_root, current_ts.derived->name);
1715 if (!(current_ts.derived->attr.imported
1716 && st != NULL
1717 && st->n.sym == current_ts.derived)
1718 && !gfc_current_ns->has_import_set)
1720 gfc_error ("the type of '%s' at %C has not been declared within the "
1721 "interface", name);
1722 m = MATCH_ERROR;
1723 goto cleanup;
1727 /* In functions that have a RESULT variable defined, the function
1728 name always refers to function calls. Therefore, the name is
1729 not allowed to appear in specification statements. */
1730 if (gfc_current_state () == COMP_FUNCTION
1731 && gfc_current_block () != NULL
1732 && gfc_current_block ()->result != NULL
1733 && gfc_current_block ()->result != gfc_current_block ()
1734 && strcmp (gfc_current_block ()->name, name) == 0)
1736 gfc_error ("Function name '%s' not allowed at %C", name);
1737 m = MATCH_ERROR;
1738 goto cleanup;
1741 /* We allow old-style initializations of the form
1742 integer i /2/, j(4) /3*3, 1/
1743 (if no colon has been seen). These are different from data
1744 statements in that initializers are only allowed to apply to the
1745 variable immediately preceding, i.e.
1746 integer i, j /1, 2/
1747 is not allowed. Therefore we have to do some work manually, that
1748 could otherwise be left to the matchers for DATA statements. */
1750 if (!colon_seen && gfc_match (" /") == MATCH_YES)
1752 if (gfc_notify_std (GFC_STD_GNU, "Extension: Old-style "
1753 "initialization at %C") == FAILURE)
1754 return MATCH_ERROR;
1756 return match_old_style_init (name);
1759 /* The double colon must be present in order to have initializers.
1760 Otherwise the statement is ambiguous with an assignment statement. */
1761 if (colon_seen)
1763 if (gfc_match (" =>") == MATCH_YES)
1765 if (!current_attr.pointer)
1767 gfc_error ("Initialization at %C isn't for a pointer variable");
1768 m = MATCH_ERROR;
1769 goto cleanup;
1772 m = gfc_match_null (&initializer);
1773 if (m == MATCH_NO)
1775 gfc_error ("Pointer initialization requires a NULL() at %C");
1776 m = MATCH_ERROR;
1779 if (gfc_pure (NULL))
1781 gfc_error ("Initialization of pointer at %C is not allowed in "
1782 "a PURE procedure");
1783 m = MATCH_ERROR;
1786 if (m != MATCH_YES)
1787 goto cleanup;
1790 else if (gfc_match_char ('=') == MATCH_YES)
1792 if (current_attr.pointer)
1794 gfc_error ("Pointer initialization at %C requires '=>', "
1795 "not '='");
1796 m = MATCH_ERROR;
1797 goto cleanup;
1800 m = gfc_match_init_expr (&initializer);
1801 if (m == MATCH_NO)
1803 gfc_error ("Expected an initialization expression at %C");
1804 m = MATCH_ERROR;
1807 if (current_attr.flavor != FL_PARAMETER && gfc_pure (NULL))
1809 gfc_error ("Initialization of variable at %C is not allowed in "
1810 "a PURE procedure");
1811 m = MATCH_ERROR;
1814 if (m != MATCH_YES)
1815 goto cleanup;
1819 if (initializer != NULL && current_attr.allocatable
1820 && gfc_current_state () == COMP_DERIVED)
1822 gfc_error ("Initialization of allocatable component at %C is not "
1823 "allowed");
1824 m = MATCH_ERROR;
1825 goto cleanup;
1828 /* Add the initializer. Note that it is fine if initializer is
1829 NULL here, because we sometimes also need to check if a
1830 declaration *must* have an initialization expression. */
1831 if (gfc_current_state () != COMP_DERIVED)
1832 t = add_init_expr_to_sym (name, &initializer, &var_locus);
1833 else
1835 if (current_ts.type == BT_DERIVED
1836 && !current_attr.pointer && !initializer)
1837 initializer = gfc_default_initializer (&current_ts);
1838 t = build_struct (name, cl, &initializer, &as);
1841 m = (t == SUCCESS) ? MATCH_YES : MATCH_ERROR;
1843 cleanup:
1844 /* Free stuff up and return. */
1845 gfc_free_expr (initializer);
1846 gfc_free_array_spec (as);
1848 return m;
1852 /* Match an extended-f77 "TYPESPEC*bytesize"-style kind specification.
1853 This assumes that the byte size is equal to the kind number for
1854 non-COMPLEX types, and equal to twice the kind number for COMPLEX. */
1856 match
1857 gfc_match_old_kind_spec (gfc_typespec *ts)
1859 match m;
1860 int original_kind;
1862 if (gfc_match_char ('*') != MATCH_YES)
1863 return MATCH_NO;
1865 m = gfc_match_small_literal_int (&ts->kind, NULL);
1866 if (m != MATCH_YES)
1867 return MATCH_ERROR;
1869 original_kind = ts->kind;
1871 /* Massage the kind numbers for complex types. */
1872 if (ts->type == BT_COMPLEX)
1874 if (ts->kind % 2)
1876 gfc_error ("Old-style type declaration %s*%d not supported at %C",
1877 gfc_basic_typename (ts->type), original_kind);
1878 return MATCH_ERROR;
1880 ts->kind /= 2;
1883 if (gfc_validate_kind (ts->type, ts->kind, true) < 0)
1885 gfc_error ("Old-style type declaration %s*%d not supported at %C",
1886 gfc_basic_typename (ts->type), original_kind);
1887 return MATCH_ERROR;
1890 if (gfc_notify_std (GFC_STD_GNU, "Nonstandard type declaration %s*%d at %C",
1891 gfc_basic_typename (ts->type), original_kind) == FAILURE)
1892 return MATCH_ERROR;
1894 return MATCH_YES;
1898 /* Match a kind specification. Since kinds are generally optional, we
1899 usually return MATCH_NO if something goes wrong. If a "kind="
1900 string is found, then we know we have an error. */
1902 match
1903 gfc_match_kind_spec (gfc_typespec *ts, bool kind_expr_only)
1905 locus where, loc;
1906 gfc_expr *e;
1907 match m, n;
1908 char c;
1909 const char *msg;
1911 m = MATCH_NO;
1912 n = MATCH_YES;
1913 e = NULL;
1915 where = loc = gfc_current_locus;
1917 if (kind_expr_only)
1918 goto kind_expr;
1920 if (gfc_match_char ('(') == MATCH_NO)
1921 return MATCH_NO;
1923 /* Also gobbles optional text. */
1924 if (gfc_match (" kind = ") == MATCH_YES)
1925 m = MATCH_ERROR;
1927 loc = gfc_current_locus;
1929 kind_expr:
1930 n = gfc_match_init_expr (&e);
1932 if (n != MATCH_YES)
1934 if (gfc_matching_function)
1936 /* The function kind expression might include use associated or
1937 imported parameters and try again after the specification
1938 expressions..... */
1939 if (gfc_match_char (')') != MATCH_YES)
1941 gfc_error ("Missing right parenthesis at %C");
1942 m = MATCH_ERROR;
1943 goto no_match;
1946 gfc_free_expr (e);
1947 gfc_undo_symbols ();
1948 return MATCH_YES;
1950 else
1952 /* ....or else, the match is real. */
1953 if (n == MATCH_NO)
1954 gfc_error ("Expected initialization expression at %C");
1955 if (n != MATCH_YES)
1956 return MATCH_ERROR;
1960 if (e->rank != 0)
1962 gfc_error ("Expected scalar initialization expression at %C");
1963 m = MATCH_ERROR;
1964 goto no_match;
1967 msg = gfc_extract_int (e, &ts->kind);
1969 if (msg != NULL)
1971 gfc_error (msg);
1972 m = MATCH_ERROR;
1973 goto no_match;
1976 /* Before throwing away the expression, let's see if we had a
1977 C interoperable kind (and store the fact). */
1978 if (e->ts.is_c_interop == 1)
1980 /* Mark this as c interoperable if being declared with one
1981 of the named constants from iso_c_binding. */
1982 ts->is_c_interop = e->ts.is_iso_c;
1983 ts->f90_type = e->ts.f90_type;
1986 gfc_free_expr (e);
1987 e = NULL;
1989 /* Ignore errors to this point, if we've gotten here. This means
1990 we ignore the m=MATCH_ERROR from above. */
1991 if (gfc_validate_kind (ts->type, ts->kind, true) < 0)
1993 gfc_error ("Kind %d not supported for type %s at %C", ts->kind,
1994 gfc_basic_typename (ts->type));
1995 gfc_current_locus = where;
1996 return MATCH_ERROR;
1999 /* Warn if, e.g., c_int is used for a REAL variable, but not
2000 if, e.g., c_double is used for COMPLEX as the standard
2001 explicitly says that the kind type parameter for complex and real
2002 variable is the same, i.e. c_float == c_float_complex. */
2003 if (ts->f90_type != BT_UNKNOWN && ts->f90_type != ts->type
2004 && !((ts->f90_type == BT_REAL && ts->type == BT_COMPLEX)
2005 || (ts->f90_type == BT_COMPLEX && ts->type == BT_REAL)))
2006 gfc_warning_now ("C kind type parameter is for type %s but type at %L "
2007 "is %s", gfc_basic_typename (ts->f90_type), &where,
2008 gfc_basic_typename (ts->type));
2010 gfc_gobble_whitespace ();
2011 if ((c = gfc_next_ascii_char ()) != ')'
2012 && (ts->type != BT_CHARACTER || c != ','))
2014 if (ts->type == BT_CHARACTER)
2015 gfc_error ("Missing right parenthesis or comma at %C");
2016 else
2017 gfc_error ("Missing right parenthesis at %C");
2018 m = MATCH_ERROR;
2020 else
2021 /* All tests passed. */
2022 m = MATCH_YES;
2024 if(m == MATCH_ERROR)
2025 gfc_current_locus = where;
2027 /* Return what we know from the test(s). */
2028 return m;
2030 no_match:
2031 gfc_free_expr (e);
2032 gfc_current_locus = where;
2033 return m;
2037 static match
2038 match_char_kind (int * kind, int * is_iso_c)
2040 locus where;
2041 gfc_expr *e;
2042 match m, n;
2043 const char *msg;
2045 m = MATCH_NO;
2046 e = NULL;
2047 where = gfc_current_locus;
2049 n = gfc_match_init_expr (&e);
2051 if (n != MATCH_YES && gfc_matching_function)
2053 /* The expression might include use-associated or imported
2054 parameters and try again after the specification
2055 expressions. */
2056 gfc_free_expr (e);
2057 gfc_undo_symbols ();
2058 return MATCH_YES;
2061 if (n == MATCH_NO)
2062 gfc_error ("Expected initialization expression at %C");
2063 if (n != MATCH_YES)
2064 return MATCH_ERROR;
2066 if (e->rank != 0)
2068 gfc_error ("Expected scalar initialization expression at %C");
2069 m = MATCH_ERROR;
2070 goto no_match;
2073 msg = gfc_extract_int (e, kind);
2074 *is_iso_c = e->ts.is_iso_c;
2075 if (msg != NULL)
2077 gfc_error (msg);
2078 m = MATCH_ERROR;
2079 goto no_match;
2082 gfc_free_expr (e);
2084 /* Ignore errors to this point, if we've gotten here. This means
2085 we ignore the m=MATCH_ERROR from above. */
2086 if (gfc_validate_kind (BT_CHARACTER, *kind, true) < 0)
2088 gfc_error ("Kind %d is not supported for CHARACTER at %C", *kind);
2089 m = MATCH_ERROR;
2091 else
2092 /* All tests passed. */
2093 m = MATCH_YES;
2095 if (m == MATCH_ERROR)
2096 gfc_current_locus = where;
2098 /* Return what we know from the test(s). */
2099 return m;
2101 no_match:
2102 gfc_free_expr (e);
2103 gfc_current_locus = where;
2104 return m;
2107 /* Match the various kind/length specifications in a CHARACTER
2108 declaration. We don't return MATCH_NO. */
2110 static match
2111 match_char_spec (gfc_typespec *ts)
2113 int kind, seen_length, is_iso_c;
2114 gfc_charlen *cl;
2115 gfc_expr *len;
2116 match m;
2118 len = NULL;
2119 seen_length = 0;
2120 kind = 0;
2121 is_iso_c = 0;
2123 /* Try the old-style specification first. */
2124 old_char_selector = 0;
2126 m = match_char_length (&len);
2127 if (m != MATCH_NO)
2129 if (m == MATCH_YES)
2130 old_char_selector = 1;
2131 seen_length = 1;
2132 goto done;
2135 m = gfc_match_char ('(');
2136 if (m != MATCH_YES)
2138 m = MATCH_YES; /* Character without length is a single char. */
2139 goto done;
2142 /* Try the weird case: ( KIND = <int> [ , LEN = <len-param> ] ). */
2143 if (gfc_match (" kind =") == MATCH_YES)
2145 m = match_char_kind (&kind, &is_iso_c);
2147 if (m == MATCH_ERROR)
2148 goto done;
2149 if (m == MATCH_NO)
2150 goto syntax;
2152 if (gfc_match (" , len =") == MATCH_NO)
2153 goto rparen;
2155 m = char_len_param_value (&len);
2156 if (m == MATCH_NO)
2157 goto syntax;
2158 if (m == MATCH_ERROR)
2159 goto done;
2160 seen_length = 1;
2162 goto rparen;
2165 /* Try to match "LEN = <len-param>" or "LEN = <len-param>, KIND = <int>". */
2166 if (gfc_match (" len =") == MATCH_YES)
2168 m = char_len_param_value (&len);
2169 if (m == MATCH_NO)
2170 goto syntax;
2171 if (m == MATCH_ERROR)
2172 goto done;
2173 seen_length = 1;
2175 if (gfc_match_char (')') == MATCH_YES)
2176 goto done;
2178 if (gfc_match (" , kind =") != MATCH_YES)
2179 goto syntax;
2181 if (match_char_kind (&kind, &is_iso_c) == MATCH_ERROR)
2182 goto done;
2184 goto rparen;
2187 /* Try to match ( <len-param> ) or ( <len-param> , [ KIND = ] <int> ). */
2188 m = char_len_param_value (&len);
2189 if (m == MATCH_NO)
2190 goto syntax;
2191 if (m == MATCH_ERROR)
2192 goto done;
2193 seen_length = 1;
2195 m = gfc_match_char (')');
2196 if (m == MATCH_YES)
2197 goto done;
2199 if (gfc_match_char (',') != MATCH_YES)
2200 goto syntax;
2202 gfc_match (" kind ="); /* Gobble optional text. */
2204 m = match_char_kind (&kind, &is_iso_c);
2205 if (m == MATCH_ERROR)
2206 goto done;
2207 if (m == MATCH_NO)
2208 goto syntax;
2210 rparen:
2211 /* Require a right-paren at this point. */
2212 m = gfc_match_char (')');
2213 if (m == MATCH_YES)
2214 goto done;
2216 syntax:
2217 gfc_error ("Syntax error in CHARACTER declaration at %C");
2218 m = MATCH_ERROR;
2219 gfc_free_expr (len);
2220 return m;
2222 done:
2223 /* Deal with character functions after USE and IMPORT statements. */
2224 if (gfc_matching_function)
2226 gfc_free_expr (len);
2227 gfc_undo_symbols ();
2228 return MATCH_YES;
2231 if (m != MATCH_YES)
2233 gfc_free_expr (len);
2234 return m;
2237 /* Do some final massaging of the length values. */
2238 cl = gfc_get_charlen ();
2239 cl->next = gfc_current_ns->cl_list;
2240 gfc_current_ns->cl_list = cl;
2242 if (seen_length == 0)
2243 cl->length = gfc_int_expr (1);
2244 else
2245 cl->length = len;
2247 ts->cl = cl;
2248 ts->kind = kind == 0 ? gfc_default_character_kind : kind;
2250 /* We have to know if it was a c interoperable kind so we can
2251 do accurate type checking of bind(c) procs, etc. */
2252 if (kind != 0)
2253 /* Mark this as c interoperable if being declared with one
2254 of the named constants from iso_c_binding. */
2255 ts->is_c_interop = is_iso_c;
2256 else if (len != NULL)
2257 /* Here, we might have parsed something such as: character(c_char)
2258 In this case, the parsing code above grabs the c_char when
2259 looking for the length (line 1690, roughly). it's the last
2260 testcase for parsing the kind params of a character variable.
2261 However, it's not actually the length. this seems like it
2262 could be an error.
2263 To see if the user used a C interop kind, test the expr
2264 of the so called length, and see if it's C interoperable. */
2265 ts->is_c_interop = len->ts.is_iso_c;
2267 return MATCH_YES;
2271 /* Matches a type specification. If successful, sets the ts structure
2272 to the matched specification. This is necessary for FUNCTION and
2273 IMPLICIT statements.
2275 If implicit_flag is nonzero, then we don't check for the optional
2276 kind specification. Not doing so is needed for matching an IMPLICIT
2277 statement correctly. */
2279 match
2280 gfc_match_type_spec (gfc_typespec *ts, int implicit_flag)
2282 char name[GFC_MAX_SYMBOL_LEN + 1];
2283 gfc_symbol *sym;
2284 match m;
2285 char c;
2286 bool seen_deferred_kind;
2288 /* A belt and braces check that the typespec is correctly being treated
2289 as a deferred characteristic association. */
2290 seen_deferred_kind = (gfc_current_state () == COMP_FUNCTION)
2291 && (gfc_current_block ()->result->ts.kind == -1)
2292 && (ts->kind == -1);
2293 gfc_clear_ts (ts);
2294 if (seen_deferred_kind)
2295 ts->kind = -1;
2297 /* Clear the current binding label, in case one is given. */
2298 curr_binding_label[0] = '\0';
2300 if (gfc_match (" byte") == MATCH_YES)
2302 if (gfc_notify_std(GFC_STD_GNU, "Extension: BYTE type at %C")
2303 == FAILURE)
2304 return MATCH_ERROR;
2306 if (gfc_validate_kind (BT_INTEGER, 1, true) < 0)
2308 gfc_error ("BYTE type used at %C "
2309 "is not available on the target machine");
2310 return MATCH_ERROR;
2313 ts->type = BT_INTEGER;
2314 ts->kind = 1;
2315 return MATCH_YES;
2318 if (gfc_match (" integer") == MATCH_YES)
2320 ts->type = BT_INTEGER;
2321 ts->kind = gfc_default_integer_kind;
2322 goto get_kind;
2325 if (gfc_match (" character") == MATCH_YES)
2327 ts->type = BT_CHARACTER;
2328 if (implicit_flag == 0)
2329 return match_char_spec (ts);
2330 else
2331 return MATCH_YES;
2334 if (gfc_match (" real") == MATCH_YES)
2336 ts->type = BT_REAL;
2337 ts->kind = gfc_default_real_kind;
2338 goto get_kind;
2341 if (gfc_match (" double precision") == MATCH_YES)
2343 ts->type = BT_REAL;
2344 ts->kind = gfc_default_double_kind;
2345 return MATCH_YES;
2348 if (gfc_match (" complex") == MATCH_YES)
2350 ts->type = BT_COMPLEX;
2351 ts->kind = gfc_default_complex_kind;
2352 goto get_kind;
2355 if (gfc_match (" double complex") == MATCH_YES)
2357 if (gfc_notify_std (GFC_STD_GNU, "DOUBLE COMPLEX at %C does not "
2358 "conform to the Fortran 95 standard") == FAILURE)
2359 return MATCH_ERROR;
2361 ts->type = BT_COMPLEX;
2362 ts->kind = gfc_default_double_kind;
2363 return MATCH_YES;
2366 if (gfc_match (" logical") == MATCH_YES)
2368 ts->type = BT_LOGICAL;
2369 ts->kind = gfc_default_logical_kind;
2370 goto get_kind;
2373 m = gfc_match (" type ( %n )", name);
2374 if (m != MATCH_YES)
2375 return m;
2377 ts->type = BT_DERIVED;
2379 /* Defer association of the derived type until the end of the
2380 specification block. However, if the derived type can be
2381 found, add it to the typespec. */
2382 if (gfc_matching_function)
2384 ts->derived = NULL;
2385 if (gfc_current_state () != COMP_INTERFACE
2386 && !gfc_find_symbol (name, NULL, 1, &sym) && sym)
2387 ts->derived = sym;
2388 return MATCH_YES;
2391 /* Search for the name but allow the components to be defined later. If
2392 type = -1, this typespec has been seen in a function declaration but
2393 the type could not be accessed at that point. */
2394 sym = NULL;
2395 if (ts->kind != -1 && gfc_get_ha_symbol (name, &sym))
2397 gfc_error ("Type name '%s' at %C is ambiguous", name);
2398 return MATCH_ERROR;
2400 else if (ts->kind == -1)
2402 int iface = gfc_state_stack->previous->state != COMP_INTERFACE
2403 || gfc_current_ns->has_import_set;
2404 if (gfc_find_symbol (name, NULL, iface, &sym))
2406 gfc_error ("Type name '%s' at %C is ambiguous", name);
2407 return MATCH_ERROR;
2410 ts->kind = 0;
2411 if (sym == NULL)
2412 return MATCH_NO;
2415 if (sym->attr.flavor != FL_DERIVED
2416 && gfc_add_flavor (&sym->attr, FL_DERIVED, sym->name, NULL) == FAILURE)
2417 return MATCH_ERROR;
2419 gfc_set_sym_referenced (sym);
2420 ts->derived = sym;
2422 return MATCH_YES;
2424 get_kind:
2425 /* For all types except double, derived and character, look for an
2426 optional kind specifier. MATCH_NO is actually OK at this point. */
2427 if (implicit_flag == 1)
2428 return MATCH_YES;
2430 if (gfc_current_form == FORM_FREE)
2432 c = gfc_peek_ascii_char();
2433 if (!gfc_is_whitespace(c) && c != '*' && c != '('
2434 && c != ':' && c != ',')
2435 return MATCH_NO;
2438 m = gfc_match_kind_spec (ts, false);
2439 if (m == MATCH_NO && ts->type != BT_CHARACTER)
2440 m = gfc_match_old_kind_spec (ts);
2442 /* Defer association of the KIND expression of function results
2443 until after USE and IMPORT statements. */
2444 if ((gfc_current_state () == COMP_NONE && gfc_error_flag_test ())
2445 || gfc_matching_function)
2446 return MATCH_YES;
2448 if (m == MATCH_NO)
2449 m = MATCH_YES; /* No kind specifier found. */
2451 return m;
2455 /* Match an IMPLICIT NONE statement. Actually, this statement is
2456 already matched in parse.c, or we would not end up here in the
2457 first place. So the only thing we need to check, is if there is
2458 trailing garbage. If not, the match is successful. */
2460 match
2461 gfc_match_implicit_none (void)
2463 return (gfc_match_eos () == MATCH_YES) ? MATCH_YES : MATCH_NO;
2467 /* Match the letter range(s) of an IMPLICIT statement. */
2469 static match
2470 match_implicit_range (void)
2472 char c, c1, c2;
2473 int inner;
2474 locus cur_loc;
2476 cur_loc = gfc_current_locus;
2478 gfc_gobble_whitespace ();
2479 c = gfc_next_ascii_char ();
2480 if (c != '(')
2482 gfc_error ("Missing character range in IMPLICIT at %C");
2483 goto bad;
2486 inner = 1;
2487 while (inner)
2489 gfc_gobble_whitespace ();
2490 c1 = gfc_next_ascii_char ();
2491 if (!ISALPHA (c1))
2492 goto bad;
2494 gfc_gobble_whitespace ();
2495 c = gfc_next_ascii_char ();
2497 switch (c)
2499 case ')':
2500 inner = 0; /* Fall through. */
2502 case ',':
2503 c2 = c1;
2504 break;
2506 case '-':
2507 gfc_gobble_whitespace ();
2508 c2 = gfc_next_ascii_char ();
2509 if (!ISALPHA (c2))
2510 goto bad;
2512 gfc_gobble_whitespace ();
2513 c = gfc_next_ascii_char ();
2515 if ((c != ',') && (c != ')'))
2516 goto bad;
2517 if (c == ')')
2518 inner = 0;
2520 break;
2522 default:
2523 goto bad;
2526 if (c1 > c2)
2528 gfc_error ("Letters must be in alphabetic order in "
2529 "IMPLICIT statement at %C");
2530 goto bad;
2533 /* See if we can add the newly matched range to the pending
2534 implicits from this IMPLICIT statement. We do not check for
2535 conflicts with whatever earlier IMPLICIT statements may have
2536 set. This is done when we've successfully finished matching
2537 the current one. */
2538 if (gfc_add_new_implicit_range (c1, c2) != SUCCESS)
2539 goto bad;
2542 return MATCH_YES;
2544 bad:
2545 gfc_syntax_error (ST_IMPLICIT);
2547 gfc_current_locus = cur_loc;
2548 return MATCH_ERROR;
2552 /* Match an IMPLICIT statement, storing the types for
2553 gfc_set_implicit() if the statement is accepted by the parser.
2554 There is a strange looking, but legal syntactic construction
2555 possible. It looks like:
2557 IMPLICIT INTEGER (a-b) (c-d)
2559 This is legal if "a-b" is a constant expression that happens to
2560 equal one of the legal kinds for integers. The real problem
2561 happens with an implicit specification that looks like:
2563 IMPLICIT INTEGER (a-b)
2565 In this case, a typespec matcher that is "greedy" (as most of the
2566 matchers are) gobbles the character range as a kindspec, leaving
2567 nothing left. We therefore have to go a bit more slowly in the
2568 matching process by inhibiting the kindspec checking during
2569 typespec matching and checking for a kind later. */
2571 match
2572 gfc_match_implicit (void)
2574 gfc_typespec ts;
2575 locus cur_loc;
2576 char c;
2577 match m;
2579 gfc_clear_ts (&ts);
2581 /* We don't allow empty implicit statements. */
2582 if (gfc_match_eos () == MATCH_YES)
2584 gfc_error ("Empty IMPLICIT statement at %C");
2585 return MATCH_ERROR;
2590 /* First cleanup. */
2591 gfc_clear_new_implicit ();
2593 /* A basic type is mandatory here. */
2594 m = gfc_match_type_spec (&ts, 1);
2595 if (m == MATCH_ERROR)
2596 goto error;
2597 if (m == MATCH_NO)
2598 goto syntax;
2600 cur_loc = gfc_current_locus;
2601 m = match_implicit_range ();
2603 if (m == MATCH_YES)
2605 /* We may have <TYPE> (<RANGE>). */
2606 gfc_gobble_whitespace ();
2607 c = gfc_next_ascii_char ();
2608 if ((c == '\n') || (c == ','))
2610 /* Check for CHARACTER with no length parameter. */
2611 if (ts.type == BT_CHARACTER && !ts.cl)
2613 ts.kind = gfc_default_character_kind;
2614 ts.cl = gfc_get_charlen ();
2615 ts.cl->next = gfc_current_ns->cl_list;
2616 gfc_current_ns->cl_list = ts.cl;
2617 ts.cl->length = gfc_int_expr (1);
2620 /* Record the Successful match. */
2621 if (gfc_merge_new_implicit (&ts) != SUCCESS)
2622 return MATCH_ERROR;
2623 continue;
2626 gfc_current_locus = cur_loc;
2629 /* Discard the (incorrectly) matched range. */
2630 gfc_clear_new_implicit ();
2632 /* Last chance -- check <TYPE> <SELECTOR> (<RANGE>). */
2633 if (ts.type == BT_CHARACTER)
2634 m = match_char_spec (&ts);
2635 else
2637 m = gfc_match_kind_spec (&ts, false);
2638 if (m == MATCH_NO)
2640 m = gfc_match_old_kind_spec (&ts);
2641 if (m == MATCH_ERROR)
2642 goto error;
2643 if (m == MATCH_NO)
2644 goto syntax;
2647 if (m == MATCH_ERROR)
2648 goto error;
2650 m = match_implicit_range ();
2651 if (m == MATCH_ERROR)
2652 goto error;
2653 if (m == MATCH_NO)
2654 goto syntax;
2656 gfc_gobble_whitespace ();
2657 c = gfc_next_ascii_char ();
2658 if ((c != '\n') && (c != ','))
2659 goto syntax;
2661 if (gfc_merge_new_implicit (&ts) != SUCCESS)
2662 return MATCH_ERROR;
2664 while (c == ',');
2666 return MATCH_YES;
2668 syntax:
2669 gfc_syntax_error (ST_IMPLICIT);
2671 error:
2672 return MATCH_ERROR;
2676 match
2677 gfc_match_import (void)
2679 char name[GFC_MAX_SYMBOL_LEN + 1];
2680 match m;
2681 gfc_symbol *sym;
2682 gfc_symtree *st;
2684 if (gfc_current_ns->proc_name == NULL
2685 || gfc_current_ns->proc_name->attr.if_source != IFSRC_IFBODY)
2687 gfc_error ("IMPORT statement at %C only permitted in "
2688 "an INTERFACE body");
2689 return MATCH_ERROR;
2692 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: IMPORT statement at %C")
2693 == FAILURE)
2694 return MATCH_ERROR;
2696 if (gfc_match_eos () == MATCH_YES)
2698 /* All host variables should be imported. */
2699 gfc_current_ns->has_import_set = 1;
2700 return MATCH_YES;
2703 if (gfc_match (" ::") == MATCH_YES)
2705 if (gfc_match_eos () == MATCH_YES)
2707 gfc_error ("Expecting list of named entities at %C");
2708 return MATCH_ERROR;
2712 for(;;)
2714 m = gfc_match (" %n", name);
2715 switch (m)
2717 case MATCH_YES:
2718 if (gfc_current_ns->parent != NULL
2719 && gfc_find_symbol (name, gfc_current_ns->parent, 1, &sym))
2721 gfc_error ("Type name '%s' at %C is ambiguous", name);
2722 return MATCH_ERROR;
2724 else if (gfc_current_ns->proc_name->ns->parent != NULL
2725 && gfc_find_symbol (name,
2726 gfc_current_ns->proc_name->ns->parent,
2727 1, &sym))
2729 gfc_error ("Type name '%s' at %C is ambiguous", name);
2730 return MATCH_ERROR;
2733 if (sym == NULL)
2735 gfc_error ("Cannot IMPORT '%s' from host scoping unit "
2736 "at %C - does not exist.", name);
2737 return MATCH_ERROR;
2740 if (gfc_find_symtree (gfc_current_ns->sym_root,name))
2742 gfc_warning ("'%s' is already IMPORTed from host scoping unit "
2743 "at %C.", name);
2744 goto next_item;
2747 st = gfc_new_symtree (&gfc_current_ns->sym_root, sym->name);
2748 st->n.sym = sym;
2749 sym->refs++;
2750 sym->attr.imported = 1;
2752 goto next_item;
2754 case MATCH_NO:
2755 break;
2757 case MATCH_ERROR:
2758 return MATCH_ERROR;
2761 next_item:
2762 if (gfc_match_eos () == MATCH_YES)
2763 break;
2764 if (gfc_match_char (',') != MATCH_YES)
2765 goto syntax;
2768 return MATCH_YES;
2770 syntax:
2771 gfc_error ("Syntax error in IMPORT statement at %C");
2772 return MATCH_ERROR;
2776 /* A minimal implementation of gfc_match without whitespace, escape
2777 characters or variable arguments. Returns true if the next
2778 characters match the TARGET template exactly. */
2780 static bool
2781 match_string_p (const char *target)
2783 const char *p;
2785 for (p = target; *p; p++)
2786 if ((char) gfc_next_ascii_char () != *p)
2787 return false;
2788 return true;
2791 /* Matches an attribute specification including array specs. If
2792 successful, leaves the variables current_attr and current_as
2793 holding the specification. Also sets the colon_seen variable for
2794 later use by matchers associated with initializations.
2796 This subroutine is a little tricky in the sense that we don't know
2797 if we really have an attr-spec until we hit the double colon.
2798 Until that time, we can only return MATCH_NO. This forces us to
2799 check for duplicate specification at this level. */
2801 static match
2802 match_attr_spec (void)
2804 /* Modifiers that can exist in a type statement. */
2805 typedef enum
2806 { GFC_DECL_BEGIN = 0,
2807 DECL_ALLOCATABLE = GFC_DECL_BEGIN, DECL_DIMENSION, DECL_EXTERNAL,
2808 DECL_IN, DECL_OUT, DECL_INOUT, DECL_INTRINSIC, DECL_OPTIONAL,
2809 DECL_PARAMETER, DECL_POINTER, DECL_PROTECTED, DECL_PRIVATE,
2810 DECL_PUBLIC, DECL_SAVE, DECL_TARGET, DECL_VALUE, DECL_VOLATILE,
2811 DECL_IS_BIND_C, DECL_NONE,
2812 GFC_DECL_END /* Sentinel */
2814 decl_types;
2816 /* GFC_DECL_END is the sentinel, index starts at 0. */
2817 #define NUM_DECL GFC_DECL_END
2819 locus start, seen_at[NUM_DECL];
2820 int seen[NUM_DECL];
2821 unsigned int d;
2822 const char *attr;
2823 match m;
2824 gfc_try t;
2826 gfc_clear_attr (&current_attr);
2827 start = gfc_current_locus;
2829 current_as = NULL;
2830 colon_seen = 0;
2832 /* See if we get all of the keywords up to the final double colon. */
2833 for (d = GFC_DECL_BEGIN; d != GFC_DECL_END; d++)
2834 seen[d] = 0;
2836 for (;;)
2838 char ch;
2840 d = DECL_NONE;
2841 gfc_gobble_whitespace ();
2843 ch = gfc_next_ascii_char ();
2844 if (ch == ':')
2846 /* This is the successful exit condition for the loop. */
2847 if (gfc_next_ascii_char () == ':')
2848 break;
2850 else if (ch == ',')
2852 gfc_gobble_whitespace ();
2853 switch (gfc_peek_ascii_char ())
2855 case 'a':
2856 if (match_string_p ("allocatable"))
2857 d = DECL_ALLOCATABLE;
2858 break;
2860 case 'b':
2861 /* Try and match the bind(c). */
2862 m = gfc_match_bind_c (NULL, true);
2863 if (m == MATCH_YES)
2864 d = DECL_IS_BIND_C;
2865 else if (m == MATCH_ERROR)
2866 goto cleanup;
2867 break;
2869 case 'd':
2870 if (match_string_p ("dimension"))
2871 d = DECL_DIMENSION;
2872 break;
2874 case 'e':
2875 if (match_string_p ("external"))
2876 d = DECL_EXTERNAL;
2877 break;
2879 case 'i':
2880 if (match_string_p ("int"))
2882 ch = gfc_next_ascii_char ();
2883 if (ch == 'e')
2885 if (match_string_p ("nt"))
2887 /* Matched "intent". */
2888 /* TODO: Call match_intent_spec from here. */
2889 if (gfc_match (" ( in out )") == MATCH_YES)
2890 d = DECL_INOUT;
2891 else if (gfc_match (" ( in )") == MATCH_YES)
2892 d = DECL_IN;
2893 else if (gfc_match (" ( out )") == MATCH_YES)
2894 d = DECL_OUT;
2897 else if (ch == 'r')
2899 if (match_string_p ("insic"))
2901 /* Matched "intrinsic". */
2902 d = DECL_INTRINSIC;
2906 break;
2908 case 'o':
2909 if (match_string_p ("optional"))
2910 d = DECL_OPTIONAL;
2911 break;
2913 case 'p':
2914 gfc_next_ascii_char ();
2915 switch (gfc_next_ascii_char ())
2917 case 'a':
2918 if (match_string_p ("rameter"))
2920 /* Matched "parameter". */
2921 d = DECL_PARAMETER;
2923 break;
2925 case 'o':
2926 if (match_string_p ("inter"))
2928 /* Matched "pointer". */
2929 d = DECL_POINTER;
2931 break;
2933 case 'r':
2934 ch = gfc_next_ascii_char ();
2935 if (ch == 'i')
2937 if (match_string_p ("vate"))
2939 /* Matched "private". */
2940 d = DECL_PRIVATE;
2943 else if (ch == 'o')
2945 if (match_string_p ("tected"))
2947 /* Matched "protected". */
2948 d = DECL_PROTECTED;
2951 break;
2953 case 'u':
2954 if (match_string_p ("blic"))
2956 /* Matched "public". */
2957 d = DECL_PUBLIC;
2959 break;
2961 break;
2963 case 's':
2964 if (match_string_p ("save"))
2965 d = DECL_SAVE;
2966 break;
2968 case 't':
2969 if (match_string_p ("target"))
2970 d = DECL_TARGET;
2971 break;
2973 case 'v':
2974 gfc_next_ascii_char ();
2975 ch = gfc_next_ascii_char ();
2976 if (ch == 'a')
2978 if (match_string_p ("lue"))
2980 /* Matched "value". */
2981 d = DECL_VALUE;
2984 else if (ch == 'o')
2986 if (match_string_p ("latile"))
2988 /* Matched "volatile". */
2989 d = DECL_VOLATILE;
2992 break;
2996 /* No double colon and no recognizable decl_type, so assume that
2997 we've been looking at something else the whole time. */
2998 if (d == DECL_NONE)
3000 m = MATCH_NO;
3001 goto cleanup;
3004 /* Check to make sure any parens are paired up correctly. */
3005 if (gfc_match_parens () == MATCH_ERROR)
3007 m = MATCH_ERROR;
3008 goto cleanup;
3011 seen[d]++;
3012 seen_at[d] = gfc_current_locus;
3014 if (d == DECL_DIMENSION)
3016 m = gfc_match_array_spec (&current_as);
3018 if (m == MATCH_NO)
3020 gfc_error ("Missing dimension specification at %C");
3021 m = MATCH_ERROR;
3024 if (m == MATCH_ERROR)
3025 goto cleanup;
3029 /* Since we've seen a double colon, we have to be looking at an
3030 attr-spec. This means that we can now issue errors. */
3031 for (d = GFC_DECL_BEGIN; d != GFC_DECL_END; d++)
3032 if (seen[d] > 1)
3034 switch (d)
3036 case DECL_ALLOCATABLE:
3037 attr = "ALLOCATABLE";
3038 break;
3039 case DECL_DIMENSION:
3040 attr = "DIMENSION";
3041 break;
3042 case DECL_EXTERNAL:
3043 attr = "EXTERNAL";
3044 break;
3045 case DECL_IN:
3046 attr = "INTENT (IN)";
3047 break;
3048 case DECL_OUT:
3049 attr = "INTENT (OUT)";
3050 break;
3051 case DECL_INOUT:
3052 attr = "INTENT (IN OUT)";
3053 break;
3054 case DECL_INTRINSIC:
3055 attr = "INTRINSIC";
3056 break;
3057 case DECL_OPTIONAL:
3058 attr = "OPTIONAL";
3059 break;
3060 case DECL_PARAMETER:
3061 attr = "PARAMETER";
3062 break;
3063 case DECL_POINTER:
3064 attr = "POINTER";
3065 break;
3066 case DECL_PROTECTED:
3067 attr = "PROTECTED";
3068 break;
3069 case DECL_PRIVATE:
3070 attr = "PRIVATE";
3071 break;
3072 case DECL_PUBLIC:
3073 attr = "PUBLIC";
3074 break;
3075 case DECL_SAVE:
3076 attr = "SAVE";
3077 break;
3078 case DECL_TARGET:
3079 attr = "TARGET";
3080 break;
3081 case DECL_IS_BIND_C:
3082 attr = "IS_BIND_C";
3083 break;
3084 case DECL_VALUE:
3085 attr = "VALUE";
3086 break;
3087 case DECL_VOLATILE:
3088 attr = "VOLATILE";
3089 break;
3090 default:
3091 attr = NULL; /* This shouldn't happen. */
3094 gfc_error ("Duplicate %s attribute at %L", attr, &seen_at[d]);
3095 m = MATCH_ERROR;
3096 goto cleanup;
3099 /* Now that we've dealt with duplicate attributes, add the attributes
3100 to the current attribute. */
3101 for (d = GFC_DECL_BEGIN; d != GFC_DECL_END; d++)
3103 if (seen[d] == 0)
3104 continue;
3106 if (gfc_current_state () == COMP_DERIVED
3107 && d != DECL_DIMENSION && d != DECL_POINTER
3108 && d != DECL_PRIVATE && d != DECL_PUBLIC
3109 && d != DECL_NONE)
3111 if (d == DECL_ALLOCATABLE)
3113 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: ALLOCATABLE "
3114 "attribute at %C in a TYPE definition")
3115 == FAILURE)
3117 m = MATCH_ERROR;
3118 goto cleanup;
3121 else
3123 gfc_error ("Attribute at %L is not allowed in a TYPE definition",
3124 &seen_at[d]);
3125 m = MATCH_ERROR;
3126 goto cleanup;
3130 if ((d == DECL_PRIVATE || d == DECL_PUBLIC)
3131 && gfc_current_state () != COMP_MODULE)
3133 if (d == DECL_PRIVATE)
3134 attr = "PRIVATE";
3135 else
3136 attr = "PUBLIC";
3137 if (gfc_current_state () == COMP_DERIVED
3138 && gfc_state_stack->previous
3139 && gfc_state_stack->previous->state == COMP_MODULE)
3141 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Attribute %s "
3142 "at %L in a TYPE definition", attr,
3143 &seen_at[d])
3144 == FAILURE)
3146 m = MATCH_ERROR;
3147 goto cleanup;
3150 else
3152 gfc_error ("%s attribute at %L is not allowed outside of the "
3153 "specification part of a module", attr, &seen_at[d]);
3154 m = MATCH_ERROR;
3155 goto cleanup;
3159 switch (d)
3161 case DECL_ALLOCATABLE:
3162 t = gfc_add_allocatable (&current_attr, &seen_at[d]);
3163 break;
3165 case DECL_DIMENSION:
3166 t = gfc_add_dimension (&current_attr, NULL, &seen_at[d]);
3167 break;
3169 case DECL_EXTERNAL:
3170 t = gfc_add_external (&current_attr, &seen_at[d]);
3171 break;
3173 case DECL_IN:
3174 t = gfc_add_intent (&current_attr, INTENT_IN, &seen_at[d]);
3175 break;
3177 case DECL_OUT:
3178 t = gfc_add_intent (&current_attr, INTENT_OUT, &seen_at[d]);
3179 break;
3181 case DECL_INOUT:
3182 t = gfc_add_intent (&current_attr, INTENT_INOUT, &seen_at[d]);
3183 break;
3185 case DECL_INTRINSIC:
3186 t = gfc_add_intrinsic (&current_attr, &seen_at[d]);
3187 break;
3189 case DECL_OPTIONAL:
3190 t = gfc_add_optional (&current_attr, &seen_at[d]);
3191 break;
3193 case DECL_PARAMETER:
3194 t = gfc_add_flavor (&current_attr, FL_PARAMETER, NULL, &seen_at[d]);
3195 break;
3197 case DECL_POINTER:
3198 t = gfc_add_pointer (&current_attr, &seen_at[d]);
3199 break;
3201 case DECL_PROTECTED:
3202 if (gfc_current_ns->proc_name->attr.flavor != FL_MODULE)
3204 gfc_error ("PROTECTED at %C only allowed in specification "
3205 "part of a module");
3206 t = FAILURE;
3207 break;
3210 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PROTECTED "
3211 "attribute at %C")
3212 == FAILURE)
3213 t = FAILURE;
3214 else
3215 t = gfc_add_protected (&current_attr, NULL, &seen_at[d]);
3216 break;
3218 case DECL_PRIVATE:
3219 t = gfc_add_access (&current_attr, ACCESS_PRIVATE, NULL,
3220 &seen_at[d]);
3221 break;
3223 case DECL_PUBLIC:
3224 t = gfc_add_access (&current_attr, ACCESS_PUBLIC, NULL,
3225 &seen_at[d]);
3226 break;
3228 case DECL_SAVE:
3229 t = gfc_add_save (&current_attr, NULL, &seen_at[d]);
3230 break;
3232 case DECL_TARGET:
3233 t = gfc_add_target (&current_attr, &seen_at[d]);
3234 break;
3236 case DECL_IS_BIND_C:
3237 t = gfc_add_is_bind_c(&current_attr, NULL, &seen_at[d], 0);
3238 break;
3240 case DECL_VALUE:
3241 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: VALUE attribute "
3242 "at %C")
3243 == FAILURE)
3244 t = FAILURE;
3245 else
3246 t = gfc_add_value (&current_attr, NULL, &seen_at[d]);
3247 break;
3249 case DECL_VOLATILE:
3250 if (gfc_notify_std (GFC_STD_F2003,
3251 "Fortran 2003: VOLATILE attribute at %C")
3252 == FAILURE)
3253 t = FAILURE;
3254 else
3255 t = gfc_add_volatile (&current_attr, NULL, &seen_at[d]);
3256 break;
3258 default:
3259 gfc_internal_error ("match_attr_spec(): Bad attribute");
3262 if (t == FAILURE)
3264 m = MATCH_ERROR;
3265 goto cleanup;
3269 colon_seen = 1;
3270 return MATCH_YES;
3272 cleanup:
3273 gfc_current_locus = start;
3274 gfc_free_array_spec (current_as);
3275 current_as = NULL;
3276 return m;
3280 /* Set the binding label, dest_label, either with the binding label
3281 stored in the given gfc_typespec, ts, or if none was provided, it
3282 will be the symbol name in all lower case, as required by the draft
3283 (J3/04-007, section 15.4.1). If a binding label was given and
3284 there is more than one argument (num_idents), it is an error. */
3286 gfc_try
3287 set_binding_label (char *dest_label, const char *sym_name, int num_idents)
3289 if (num_idents > 1 && has_name_equals)
3291 gfc_error ("Multiple identifiers provided with "
3292 "single NAME= specifier at %C");
3293 return FAILURE;
3296 if (curr_binding_label[0] != '\0')
3298 /* Binding label given; store in temp holder til have sym. */
3299 strcpy (dest_label, curr_binding_label);
3301 else
3303 /* No binding label given, and the NAME= specifier did not exist,
3304 which means there was no NAME="". */
3305 if (sym_name != NULL && has_name_equals == 0)
3306 strcpy (dest_label, sym_name);
3309 return SUCCESS;
3313 /* Set the status of the given common block as being BIND(C) or not,
3314 depending on the given parameter, is_bind_c. */
3316 void
3317 set_com_block_bind_c (gfc_common_head *com_block, int is_bind_c)
3319 com_block->is_bind_c = is_bind_c;
3320 return;
3324 /* Verify that the given gfc_typespec is for a C interoperable type. */
3326 gfc_try
3327 verify_c_interop (gfc_typespec *ts)
3329 if (ts->type == BT_DERIVED && ts->derived != NULL)
3330 return (ts->derived->ts.is_c_interop ? SUCCESS : FAILURE);
3331 else if (ts->is_c_interop != 1)
3332 return FAILURE;
3334 return SUCCESS;
3338 /* Verify that the variables of a given common block, which has been
3339 defined with the attribute specifier bind(c), to be of a C
3340 interoperable type. Errors will be reported here, if
3341 encountered. */
3343 gfc_try
3344 verify_com_block_vars_c_interop (gfc_common_head *com_block)
3346 gfc_symbol *curr_sym = NULL;
3347 gfc_try retval = SUCCESS;
3349 curr_sym = com_block->head;
3351 /* Make sure we have at least one symbol. */
3352 if (curr_sym == NULL)
3353 return retval;
3355 /* Here we know we have a symbol, so we'll execute this loop
3356 at least once. */
3359 /* The second to last param, 1, says this is in a common block. */
3360 retval = verify_bind_c_sym (curr_sym, &(curr_sym->ts), 1, com_block);
3361 curr_sym = curr_sym->common_next;
3362 } while (curr_sym != NULL);
3364 return retval;
3368 /* Verify that a given BIND(C) symbol is C interoperable. If it is not,
3369 an appropriate error message is reported. */
3371 gfc_try
3372 verify_bind_c_sym (gfc_symbol *tmp_sym, gfc_typespec *ts,
3373 int is_in_common, gfc_common_head *com_block)
3375 bool bind_c_function = false;
3376 gfc_try retval = SUCCESS;
3378 if (tmp_sym->attr.function && tmp_sym->attr.is_bind_c)
3379 bind_c_function = true;
3381 if (tmp_sym->attr.function && tmp_sym->result != NULL)
3383 tmp_sym = tmp_sym->result;
3384 /* Make sure it wasn't an implicitly typed result. */
3385 if (tmp_sym->attr.implicit_type)
3387 gfc_warning ("Implicitly declared BIND(C) function '%s' at "
3388 "%L may not be C interoperable", tmp_sym->name,
3389 &tmp_sym->declared_at);
3390 tmp_sym->ts.f90_type = tmp_sym->ts.type;
3391 /* Mark it as C interoperable to prevent duplicate warnings. */
3392 tmp_sym->ts.is_c_interop = 1;
3393 tmp_sym->attr.is_c_interop = 1;
3397 /* Here, we know we have the bind(c) attribute, so if we have
3398 enough type info, then verify that it's a C interop kind.
3399 The info could be in the symbol already, or possibly still in
3400 the given ts (current_ts), so look in both. */
3401 if (tmp_sym->ts.type != BT_UNKNOWN || ts->type != BT_UNKNOWN)
3403 if (verify_c_interop (&(tmp_sym->ts)) != SUCCESS)
3405 /* See if we're dealing with a sym in a common block or not. */
3406 if (is_in_common == 1)
3408 gfc_warning ("Variable '%s' in common block '%s' at %L "
3409 "may not be a C interoperable "
3410 "kind though common block '%s' is BIND(C)",
3411 tmp_sym->name, com_block->name,
3412 &(tmp_sym->declared_at), com_block->name);
3414 else
3416 if (tmp_sym->ts.type == BT_DERIVED || ts->type == BT_DERIVED)
3417 gfc_error ("Type declaration '%s' at %L is not C "
3418 "interoperable but it is BIND(C)",
3419 tmp_sym->name, &(tmp_sym->declared_at));
3420 else
3421 gfc_warning ("Variable '%s' at %L "
3422 "may not be a C interoperable "
3423 "kind but it is bind(c)",
3424 tmp_sym->name, &(tmp_sym->declared_at));
3428 /* Variables declared w/in a common block can't be bind(c)
3429 since there's no way for C to see these variables, so there's
3430 semantically no reason for the attribute. */
3431 if (is_in_common == 1 && tmp_sym->attr.is_bind_c == 1)
3433 gfc_error ("Variable '%s' in common block '%s' at "
3434 "%L cannot be declared with BIND(C) "
3435 "since it is not a global",
3436 tmp_sym->name, com_block->name,
3437 &(tmp_sym->declared_at));
3438 retval = FAILURE;
3441 /* Scalar variables that are bind(c) can not have the pointer
3442 or allocatable attributes. */
3443 if (tmp_sym->attr.is_bind_c == 1)
3445 if (tmp_sym->attr.pointer == 1)
3447 gfc_error ("Variable '%s' at %L cannot have both the "
3448 "POINTER and BIND(C) attributes",
3449 tmp_sym->name, &(tmp_sym->declared_at));
3450 retval = FAILURE;
3453 if (tmp_sym->attr.allocatable == 1)
3455 gfc_error ("Variable '%s' at %L cannot have both the "
3456 "ALLOCATABLE and BIND(C) attributes",
3457 tmp_sym->name, &(tmp_sym->declared_at));
3458 retval = FAILURE;
3463 /* If it is a BIND(C) function, make sure the return value is a
3464 scalar value. The previous tests in this function made sure
3465 the type is interoperable. */
3466 if (bind_c_function && tmp_sym->as != NULL)
3467 gfc_error ("Return type of BIND(C) function '%s' at %L cannot "
3468 "be an array", tmp_sym->name, &(tmp_sym->declared_at));
3470 /* BIND(C) functions can not return a character string. */
3471 if (bind_c_function && tmp_sym->ts.type == BT_CHARACTER)
3472 if (tmp_sym->ts.cl == NULL || tmp_sym->ts.cl->length == NULL
3473 || tmp_sym->ts.cl->length->expr_type != EXPR_CONSTANT
3474 || mpz_cmp_si (tmp_sym->ts.cl->length->value.integer, 1) != 0)
3475 gfc_error ("Return type of BIND(C) function '%s' at %L cannot "
3476 "be a character string", tmp_sym->name,
3477 &(tmp_sym->declared_at));
3480 /* See if the symbol has been marked as private. If it has, make sure
3481 there is no binding label and warn the user if there is one. */
3482 if (tmp_sym->attr.access == ACCESS_PRIVATE
3483 && tmp_sym->binding_label[0] != '\0')
3484 /* Use gfc_warning_now because we won't say that the symbol fails
3485 just because of this. */
3486 gfc_warning_now ("Symbol '%s' at %L is marked PRIVATE but has been "
3487 "given the binding label '%s'", tmp_sym->name,
3488 &(tmp_sym->declared_at), tmp_sym->binding_label);
3490 return retval;
3494 /* Set the appropriate fields for a symbol that's been declared as
3495 BIND(C) (the is_bind_c flag and the binding label), and verify that
3496 the type is C interoperable. Errors are reported by the functions
3497 used to set/test these fields. */
3499 gfc_try
3500 set_verify_bind_c_sym (gfc_symbol *tmp_sym, int num_idents)
3502 gfc_try retval = SUCCESS;
3504 /* TODO: Do we need to make sure the vars aren't marked private? */
3506 /* Set the is_bind_c bit in symbol_attribute. */
3507 gfc_add_is_bind_c (&(tmp_sym->attr), tmp_sym->name, &gfc_current_locus, 0);
3509 if (set_binding_label (tmp_sym->binding_label, tmp_sym->name,
3510 num_idents) != SUCCESS)
3511 return FAILURE;
3513 return retval;
3517 /* Set the fields marking the given common block as BIND(C), including
3518 a binding label, and report any errors encountered. */
3520 gfc_try
3521 set_verify_bind_c_com_block (gfc_common_head *com_block, int num_idents)
3523 gfc_try retval = SUCCESS;
3525 /* destLabel, common name, typespec (which may have binding label). */
3526 if (set_binding_label (com_block->binding_label, com_block->name, num_idents)
3527 != SUCCESS)
3528 return FAILURE;
3530 /* Set the given common block (com_block) to being bind(c) (1). */
3531 set_com_block_bind_c (com_block, 1);
3533 return retval;
3537 /* Retrieve the list of one or more identifiers that the given bind(c)
3538 attribute applies to. */
3540 gfc_try
3541 get_bind_c_idents (void)
3543 char name[GFC_MAX_SYMBOL_LEN + 1];
3544 int num_idents = 0;
3545 gfc_symbol *tmp_sym = NULL;
3546 match found_id;
3547 gfc_common_head *com_block = NULL;
3549 if (gfc_match_name (name) == MATCH_YES)
3551 found_id = MATCH_YES;
3552 gfc_get_ha_symbol (name, &tmp_sym);
3554 else if (match_common_name (name) == MATCH_YES)
3556 found_id = MATCH_YES;
3557 com_block = gfc_get_common (name, 0);
3559 else
3561 gfc_error ("Need either entity or common block name for "
3562 "attribute specification statement at %C");
3563 return FAILURE;
3566 /* Save the current identifier and look for more. */
3569 /* Increment the number of identifiers found for this spec stmt. */
3570 num_idents++;
3572 /* Make sure we have a sym or com block, and verify that it can
3573 be bind(c). Set the appropriate field(s) and look for more
3574 identifiers. */
3575 if (tmp_sym != NULL || com_block != NULL)
3577 if (tmp_sym != NULL)
3579 if (set_verify_bind_c_sym (tmp_sym, num_idents)
3580 != SUCCESS)
3581 return FAILURE;
3583 else
3585 if (set_verify_bind_c_com_block(com_block, num_idents)
3586 != SUCCESS)
3587 return FAILURE;
3590 /* Look to see if we have another identifier. */
3591 tmp_sym = NULL;
3592 if (gfc_match_eos () == MATCH_YES)
3593 found_id = MATCH_NO;
3594 else if (gfc_match_char (',') != MATCH_YES)
3595 found_id = MATCH_NO;
3596 else if (gfc_match_name (name) == MATCH_YES)
3598 found_id = MATCH_YES;
3599 gfc_get_ha_symbol (name, &tmp_sym);
3601 else if (match_common_name (name) == MATCH_YES)
3603 found_id = MATCH_YES;
3604 com_block = gfc_get_common (name, 0);
3606 else
3608 gfc_error ("Missing entity or common block name for "
3609 "attribute specification statement at %C");
3610 return FAILURE;
3613 else
3615 gfc_internal_error ("Missing symbol");
3617 } while (found_id == MATCH_YES);
3619 /* if we get here we were successful */
3620 return SUCCESS;
3624 /* Try and match a BIND(C) attribute specification statement. */
3626 match
3627 gfc_match_bind_c_stmt (void)
3629 match found_match = MATCH_NO;
3630 gfc_typespec *ts;
3632 ts = &current_ts;
3634 /* This may not be necessary. */
3635 gfc_clear_ts (ts);
3636 /* Clear the temporary binding label holder. */
3637 curr_binding_label[0] = '\0';
3639 /* Look for the bind(c). */
3640 found_match = gfc_match_bind_c (NULL, true);
3642 if (found_match == MATCH_YES)
3644 /* Look for the :: now, but it is not required. */
3645 gfc_match (" :: ");
3647 /* Get the identifier(s) that needs to be updated. This may need to
3648 change to hand the flag(s) for the attr specified so all identifiers
3649 found can have all appropriate parts updated (assuming that the same
3650 spec stmt can have multiple attrs, such as both bind(c) and
3651 allocatable...). */
3652 if (get_bind_c_idents () != SUCCESS)
3653 /* Error message should have printed already. */
3654 return MATCH_ERROR;
3657 return found_match;
3661 /* Match a data declaration statement. */
3663 match
3664 gfc_match_data_decl (void)
3666 gfc_symbol *sym;
3667 match m;
3668 int elem;
3670 num_idents_on_line = 0;
3672 m = gfc_match_type_spec (&current_ts, 0);
3673 if (m != MATCH_YES)
3674 return m;
3676 if (current_ts.type == BT_DERIVED && gfc_current_state () != COMP_DERIVED)
3678 sym = gfc_use_derived (current_ts.derived);
3680 if (sym == NULL)
3682 m = MATCH_ERROR;
3683 goto cleanup;
3686 current_ts.derived = sym;
3689 m = match_attr_spec ();
3690 if (m == MATCH_ERROR)
3692 m = MATCH_NO;
3693 goto cleanup;
3696 if (current_ts.type == BT_DERIVED && current_ts.derived->components == NULL
3697 && !current_ts.derived->attr.zero_comp)
3700 if (current_attr.pointer && gfc_current_state () == COMP_DERIVED)
3701 goto ok;
3703 gfc_find_symbol (current_ts.derived->name,
3704 current_ts.derived->ns->parent, 1, &sym);
3706 /* Any symbol that we find had better be a type definition
3707 which has its components defined. */
3708 if (sym != NULL && sym->attr.flavor == FL_DERIVED
3709 && (current_ts.derived->components != NULL
3710 || current_ts.derived->attr.zero_comp))
3711 goto ok;
3713 /* Now we have an error, which we signal, and then fix up
3714 because the knock-on is plain and simple confusing. */
3715 gfc_error_now ("Derived type at %C has not been previously defined "
3716 "and so cannot appear in a derived type definition");
3717 current_attr.pointer = 1;
3718 goto ok;
3722 /* If we have an old-style character declaration, and no new-style
3723 attribute specifications, then there a comma is optional between
3724 the type specification and the variable list. */
3725 if (m == MATCH_NO && current_ts.type == BT_CHARACTER && old_char_selector)
3726 gfc_match_char (',');
3728 /* Give the types/attributes to symbols that follow. Give the element
3729 a number so that repeat character length expressions can be copied. */
3730 elem = 1;
3731 for (;;)
3733 num_idents_on_line++;
3734 m = variable_decl (elem++);
3735 if (m == MATCH_ERROR)
3736 goto cleanup;
3737 if (m == MATCH_NO)
3738 break;
3740 if (gfc_match_eos () == MATCH_YES)
3741 goto cleanup;
3742 if (gfc_match_char (',') != MATCH_YES)
3743 break;
3746 if (gfc_error_flag_test () == 0)
3747 gfc_error ("Syntax error in data declaration at %C");
3748 m = MATCH_ERROR;
3750 gfc_free_data_all (gfc_current_ns);
3752 cleanup:
3753 gfc_free_array_spec (current_as);
3754 current_as = NULL;
3755 return m;
3759 /* Match a prefix associated with a function or subroutine
3760 declaration. If the typespec pointer is nonnull, then a typespec
3761 can be matched. Note that if nothing matches, MATCH_YES is
3762 returned (the null string was matched). */
3764 match
3765 gfc_match_prefix (gfc_typespec *ts)
3767 bool seen_type;
3769 gfc_clear_attr (&current_attr);
3770 seen_type = 0;
3772 gcc_assert (!gfc_matching_prefix);
3773 gfc_matching_prefix = true;
3775 loop:
3776 if (!seen_type && ts != NULL
3777 && gfc_match_type_spec (ts, 0) == MATCH_YES
3778 && gfc_match_space () == MATCH_YES)
3781 seen_type = 1;
3782 goto loop;
3785 if (gfc_match ("elemental% ") == MATCH_YES)
3787 if (gfc_add_elemental (&current_attr, NULL) == FAILURE)
3788 goto error;
3790 goto loop;
3793 if (gfc_match ("pure% ") == MATCH_YES)
3795 if (gfc_add_pure (&current_attr, NULL) == FAILURE)
3796 goto error;
3798 goto loop;
3801 if (gfc_match ("recursive% ") == MATCH_YES)
3803 if (gfc_add_recursive (&current_attr, NULL) == FAILURE)
3804 goto error;
3806 goto loop;
3809 /* At this point, the next item is not a prefix. */
3810 gcc_assert (gfc_matching_prefix);
3811 gfc_matching_prefix = false;
3812 return MATCH_YES;
3814 error:
3815 gcc_assert (gfc_matching_prefix);
3816 gfc_matching_prefix = false;
3817 return MATCH_ERROR;
3821 /* Copy attributes matched by gfc_match_prefix() to attributes on a symbol. */
3823 static gfc_try
3824 copy_prefix (symbol_attribute *dest, locus *where)
3826 if (current_attr.pure && gfc_add_pure (dest, where) == FAILURE)
3827 return FAILURE;
3829 if (current_attr.elemental && gfc_add_elemental (dest, where) == FAILURE)
3830 return FAILURE;
3832 if (current_attr.recursive && gfc_add_recursive (dest, where) == FAILURE)
3833 return FAILURE;
3835 return SUCCESS;
3839 /* Match a formal argument list. */
3841 match
3842 gfc_match_formal_arglist (gfc_symbol *progname, int st_flag, int null_flag)
3844 gfc_formal_arglist *head, *tail, *p, *q;
3845 char name[GFC_MAX_SYMBOL_LEN + 1];
3846 gfc_symbol *sym;
3847 match m;
3849 head = tail = NULL;
3851 if (gfc_match_char ('(') != MATCH_YES)
3853 if (null_flag)
3854 goto ok;
3855 return MATCH_NO;
3858 if (gfc_match_char (')') == MATCH_YES)
3859 goto ok;
3861 for (;;)
3863 if (gfc_match_char ('*') == MATCH_YES)
3864 sym = NULL;
3865 else
3867 m = gfc_match_name (name);
3868 if (m != MATCH_YES)
3869 goto cleanup;
3871 if (gfc_get_symbol (name, NULL, &sym))
3872 goto cleanup;
3875 p = gfc_get_formal_arglist ();
3877 if (head == NULL)
3878 head = tail = p;
3879 else
3881 tail->next = p;
3882 tail = p;
3885 tail->sym = sym;
3887 /* We don't add the VARIABLE flavor because the name could be a
3888 dummy procedure. We don't apply these attributes to formal
3889 arguments of statement functions. */
3890 if (sym != NULL && !st_flag
3891 && (gfc_add_dummy (&sym->attr, sym->name, NULL) == FAILURE
3892 || gfc_missing_attr (&sym->attr, NULL) == FAILURE))
3894 m = MATCH_ERROR;
3895 goto cleanup;
3898 /* The name of a program unit can be in a different namespace,
3899 so check for it explicitly. After the statement is accepted,
3900 the name is checked for especially in gfc_get_symbol(). */
3901 if (gfc_new_block != NULL && sym != NULL
3902 && strcmp (sym->name, gfc_new_block->name) == 0)
3904 gfc_error ("Name '%s' at %C is the name of the procedure",
3905 sym->name);
3906 m = MATCH_ERROR;
3907 goto cleanup;
3910 if (gfc_match_char (')') == MATCH_YES)
3911 goto ok;
3913 m = gfc_match_char (',');
3914 if (m != MATCH_YES)
3916 gfc_error ("Unexpected junk in formal argument list at %C");
3917 goto cleanup;
3922 /* Check for duplicate symbols in the formal argument list. */
3923 if (head != NULL)
3925 for (p = head; p->next; p = p->next)
3927 if (p->sym == NULL)
3928 continue;
3930 for (q = p->next; q; q = q->next)
3931 if (p->sym == q->sym)
3933 gfc_error ("Duplicate symbol '%s' in formal argument list "
3934 "at %C", p->sym->name);
3936 m = MATCH_ERROR;
3937 goto cleanup;
3942 if (gfc_add_explicit_interface (progname, IFSRC_DECL, head, NULL)
3943 == FAILURE)
3945 m = MATCH_ERROR;
3946 goto cleanup;
3949 return MATCH_YES;
3951 cleanup:
3952 gfc_free_formal_arglist (head);
3953 return m;
3957 /* Match a RESULT specification following a function declaration or
3958 ENTRY statement. Also matches the end-of-statement. */
3960 static match
3961 match_result (gfc_symbol *function, gfc_symbol **result)
3963 char name[GFC_MAX_SYMBOL_LEN + 1];
3964 gfc_symbol *r;
3965 match m;
3967 if (gfc_match (" result (") != MATCH_YES)
3968 return MATCH_NO;
3970 m = gfc_match_name (name);
3971 if (m != MATCH_YES)
3972 return m;
3974 /* Get the right paren, and that's it because there could be the
3975 bind(c) attribute after the result clause. */
3976 if (gfc_match_char(')') != MATCH_YES)
3978 /* TODO: should report the missing right paren here. */
3979 return MATCH_ERROR;
3982 if (strcmp (function->name, name) == 0)
3984 gfc_error ("RESULT variable at %C must be different than function name");
3985 return MATCH_ERROR;
3988 if (gfc_get_symbol (name, NULL, &r))
3989 return MATCH_ERROR;
3991 if (gfc_add_result (&r->attr, r->name, NULL) == FAILURE)
3992 return MATCH_ERROR;
3994 *result = r;
3996 return MATCH_YES;
4000 /* Match a function suffix, which could be a combination of a result
4001 clause and BIND(C), either one, or neither. The draft does not
4002 require them to come in a specific order. */
4004 match
4005 gfc_match_suffix (gfc_symbol *sym, gfc_symbol **result)
4007 match is_bind_c; /* Found bind(c). */
4008 match is_result; /* Found result clause. */
4009 match found_match; /* Status of whether we've found a good match. */
4010 char peek_char; /* Character we're going to peek at. */
4011 bool allow_binding_name;
4013 /* Initialize to having found nothing. */
4014 found_match = MATCH_NO;
4015 is_bind_c = MATCH_NO;
4016 is_result = MATCH_NO;
4018 /* Get the next char to narrow between result and bind(c). */
4019 gfc_gobble_whitespace ();
4020 peek_char = gfc_peek_ascii_char ();
4022 /* C binding names are not allowed for internal procedures. */
4023 if (gfc_current_state () == COMP_CONTAINS
4024 && sym->ns->proc_name->attr.flavor != FL_MODULE)
4025 allow_binding_name = false;
4026 else
4027 allow_binding_name = true;
4029 switch (peek_char)
4031 case 'r':
4032 /* Look for result clause. */
4033 is_result = match_result (sym, result);
4034 if (is_result == MATCH_YES)
4036 /* Now see if there is a bind(c) after it. */
4037 is_bind_c = gfc_match_bind_c (sym, allow_binding_name);
4038 /* We've found the result clause and possibly bind(c). */
4039 found_match = MATCH_YES;
4041 else
4042 /* This should only be MATCH_ERROR. */
4043 found_match = is_result;
4044 break;
4045 case 'b':
4046 /* Look for bind(c) first. */
4047 is_bind_c = gfc_match_bind_c (sym, allow_binding_name);
4048 if (is_bind_c == MATCH_YES)
4050 /* Now see if a result clause followed it. */
4051 is_result = match_result (sym, result);
4052 found_match = MATCH_YES;
4054 else
4056 /* Should only be a MATCH_ERROR if we get here after seeing 'b'. */
4057 found_match = MATCH_ERROR;
4059 break;
4060 default:
4061 gfc_error ("Unexpected junk after function declaration at %C");
4062 found_match = MATCH_ERROR;
4063 break;
4066 if (is_bind_c == MATCH_YES)
4068 /* Fortran 2008 draft allows BIND(C) for internal procedures. */
4069 if (gfc_current_state () == COMP_CONTAINS
4070 && sym->ns->proc_name->attr.flavor != FL_MODULE
4071 && gfc_notify_std (GFC_STD_F2008, "Fortran 2008: BIND(C) attribute "
4072 "at %L may not be specified for an internal "
4073 "procedure", &gfc_current_locus)
4074 == FAILURE)
4075 return MATCH_ERROR;
4077 if (gfc_add_is_bind_c (&(sym->attr), sym->name, &gfc_current_locus, 1)
4078 == FAILURE)
4079 return MATCH_ERROR;
4082 return found_match;
4086 /* Procedure pointer return value without RESULT statement:
4087 Add "hidden" result variable named "ppr@". */
4089 static gfc_try
4090 add_hidden_procptr_result (gfc_symbol *sym)
4092 bool case1,case2;
4094 if (gfc_notification_std (GFC_STD_F2003) == ERROR)
4095 return FAILURE;
4097 /* First usage case: PROCEDURE and EXTERNAL statements. */
4098 case1 = gfc_current_state () == COMP_FUNCTION && gfc_current_block ()
4099 && strcmp (gfc_current_block ()->name, sym->name) == 0
4100 && sym->attr.external;
4101 /* Second usage case: INTERFACE statements. */
4102 case2 = gfc_current_state () == COMP_INTERFACE && gfc_state_stack->previous
4103 && gfc_state_stack->previous->state == COMP_FUNCTION
4104 && strcmp (gfc_state_stack->previous->sym->name, sym->name) == 0;
4106 if (case1 || case2)
4108 gfc_symtree *stree;
4109 if (case1)
4110 gfc_get_sym_tree ("ppr@", gfc_current_ns, &stree, false);
4111 else if (case2)
4113 gfc_symtree *st2;
4114 gfc_get_sym_tree ("ppr@", gfc_current_ns->parent, &stree, false);
4115 st2 = gfc_new_symtree (&gfc_current_ns->sym_root, "ppr@");
4116 st2->n.sym = stree->n.sym;
4118 sym->result = stree->n.sym;
4120 sym->result->attr.proc_pointer = sym->attr.proc_pointer;
4121 sym->result->attr.pointer = sym->attr.pointer;
4122 sym->result->attr.external = sym->attr.external;
4123 sym->result->attr.referenced = sym->attr.referenced;
4124 sym->result->ts = sym->ts;
4125 sym->attr.proc_pointer = 0;
4126 sym->attr.pointer = 0;
4127 sym->attr.external = 0;
4128 if (sym->result->attr.external && sym->result->attr.pointer)
4130 sym->result->attr.pointer = 0;
4131 sym->result->attr.proc_pointer = 1;
4134 return gfc_add_result (&sym->result->attr, sym->result->name, NULL);
4136 /* POINTER after PROCEDURE/EXTERNAL/INTERFACE statement. */
4137 else if (sym->attr.function && !sym->attr.external && sym->attr.pointer
4138 && sym->result && sym->result != sym && sym->result->attr.external
4139 && sym == gfc_current_ns->proc_name
4140 && sym == sym->result->ns->proc_name
4141 && strcmp ("ppr@", sym->result->name) == 0)
4143 sym->result->attr.proc_pointer = 1;
4144 sym->attr.pointer = 0;
4145 return SUCCESS;
4147 else
4148 return FAILURE;
4152 /* Match the interface for a PROCEDURE declaration,
4153 including brackets (R1212). */
4155 static match
4156 match_procedure_interface (gfc_symbol **proc_if)
4158 match m;
4159 gfc_symtree *st;
4160 locus old_loc, entry_loc;
4161 gfc_namespace *old_ns = gfc_current_ns;
4162 char name[GFC_MAX_SYMBOL_LEN + 1];
4164 old_loc = entry_loc = gfc_current_locus;
4165 gfc_clear_ts (&current_ts);
4167 if (gfc_match (" (") != MATCH_YES)
4169 gfc_current_locus = entry_loc;
4170 return MATCH_NO;
4173 /* Get the type spec. for the procedure interface. */
4174 old_loc = gfc_current_locus;
4175 m = gfc_match_type_spec (&current_ts, 0);
4176 gfc_gobble_whitespace ();
4177 if (m == MATCH_YES || (m == MATCH_NO && gfc_peek_ascii_char () == ')'))
4178 goto got_ts;
4180 if (m == MATCH_ERROR)
4181 return m;
4183 /* Procedure interface is itself a procedure. */
4184 gfc_current_locus = old_loc;
4185 m = gfc_match_name (name);
4187 /* First look to see if it is already accessible in the current
4188 namespace because it is use associated or contained. */
4189 st = NULL;
4190 if (gfc_find_sym_tree (name, NULL, 0, &st))
4191 return MATCH_ERROR;
4193 /* If it is still not found, then try the parent namespace, if it
4194 exists and create the symbol there if it is still not found. */
4195 if (gfc_current_ns->parent)
4196 gfc_current_ns = gfc_current_ns->parent;
4197 if (st == NULL && gfc_get_ha_sym_tree (name, &st))
4198 return MATCH_ERROR;
4200 gfc_current_ns = old_ns;
4201 *proc_if = st->n.sym;
4203 /* Various interface checks. */
4204 if (*proc_if)
4206 (*proc_if)->refs++;
4207 /* Resolve interface if possible. That way, attr.procedure is only set
4208 if it is declared by a later procedure-declaration-stmt, which is
4209 invalid per C1212. */
4210 while ((*proc_if)->ts.interface)
4211 *proc_if = (*proc_if)->ts.interface;
4213 if ((*proc_if)->generic)
4215 gfc_error ("Interface '%s' at %C may not be generic",
4216 (*proc_if)->name);
4217 return MATCH_ERROR;
4219 if ((*proc_if)->attr.proc == PROC_ST_FUNCTION)
4221 gfc_error ("Interface '%s' at %C may not be a statement function",
4222 (*proc_if)->name);
4223 return MATCH_ERROR;
4225 /* Handle intrinsic procedures. */
4226 if (!((*proc_if)->attr.external || (*proc_if)->attr.use_assoc
4227 || (*proc_if)->attr.if_source == IFSRC_IFBODY)
4228 && (gfc_is_intrinsic ((*proc_if), 0, gfc_current_locus)
4229 || gfc_is_intrinsic ((*proc_if), 1, gfc_current_locus)))
4230 (*proc_if)->attr.intrinsic = 1;
4231 if ((*proc_if)->attr.intrinsic
4232 && !gfc_intrinsic_actual_ok ((*proc_if)->name, 0))
4234 gfc_error ("Intrinsic procedure '%s' not allowed "
4235 "in PROCEDURE statement at %C", (*proc_if)->name);
4236 return MATCH_ERROR;
4240 got_ts:
4241 if (gfc_match (" )") != MATCH_YES)
4243 gfc_current_locus = entry_loc;
4244 return MATCH_NO;
4247 return MATCH_YES;
4251 /* Match a PROCEDURE declaration (R1211). */
4253 static match
4254 match_procedure_decl (void)
4256 match m;
4257 gfc_symbol *sym, *proc_if = NULL;
4258 int num;
4259 gfc_expr *initializer = NULL;
4261 /* Parse interface (with brackets). */
4262 m = match_procedure_interface (&proc_if);
4263 if (m != MATCH_YES)
4264 return m;
4266 /* Parse attributes (with colons). */
4267 m = match_attr_spec();
4268 if (m == MATCH_ERROR)
4269 return MATCH_ERROR;
4271 /* Get procedure symbols. */
4272 for(num=1;;num++)
4274 m = gfc_match_symbol (&sym, 0);
4275 if (m == MATCH_NO)
4276 goto syntax;
4277 else if (m == MATCH_ERROR)
4278 return m;
4280 /* Add current_attr to the symbol attributes. */
4281 if (gfc_copy_attr (&sym->attr, &current_attr, NULL) == FAILURE)
4282 return MATCH_ERROR;
4284 if (sym->attr.is_bind_c)
4286 /* Check for C1218. */
4287 if (!proc_if || !proc_if->attr.is_bind_c)
4289 gfc_error ("BIND(C) attribute at %C requires "
4290 "an interface with BIND(C)");
4291 return MATCH_ERROR;
4293 /* Check for C1217. */
4294 if (has_name_equals && sym->attr.pointer)
4296 gfc_error ("BIND(C) procedure with NAME may not have "
4297 "POINTER attribute at %C");
4298 return MATCH_ERROR;
4300 if (has_name_equals && sym->attr.dummy)
4302 gfc_error ("Dummy procedure at %C may not have "
4303 "BIND(C) attribute with NAME");
4304 return MATCH_ERROR;
4306 /* Set binding label for BIND(C). */
4307 if (set_binding_label (sym->binding_label, sym->name, num) != SUCCESS)
4308 return MATCH_ERROR;
4311 if (gfc_add_external (&sym->attr, NULL) == FAILURE)
4312 return MATCH_ERROR;
4314 if (add_hidden_procptr_result (sym) == SUCCESS)
4315 sym = sym->result;
4317 if (gfc_add_proc (&sym->attr, sym->name, NULL) == FAILURE)
4318 return MATCH_ERROR;
4320 /* Set interface. */
4321 if (proc_if != NULL)
4323 if (sym->ts.type != BT_UNKNOWN)
4325 gfc_error ("Procedure '%s' at %L already has basic type of %s",
4326 sym->name, &gfc_current_locus,
4327 gfc_basic_typename (sym->ts.type));
4328 return MATCH_ERROR;
4330 sym->ts.interface = proc_if;
4331 sym->attr.untyped = 1;
4332 sym->attr.if_source = IFSRC_IFBODY;
4334 else if (current_ts.type != BT_UNKNOWN)
4336 if (gfc_add_type (sym, &current_ts, &gfc_current_locus) == FAILURE)
4337 return MATCH_ERROR;
4338 sym->ts.interface = gfc_new_symbol ("", gfc_current_ns);
4339 sym->ts.interface->ts = current_ts;
4340 sym->ts.interface->attr.function = 1;
4341 sym->attr.function = sym->ts.interface->attr.function;
4342 sym->attr.if_source = IFSRC_UNKNOWN;
4345 if (gfc_match (" =>") == MATCH_YES)
4347 if (!current_attr.pointer)
4349 gfc_error ("Initialization at %C isn't for a pointer variable");
4350 m = MATCH_ERROR;
4351 goto cleanup;
4354 m = gfc_match_null (&initializer);
4355 if (m == MATCH_NO)
4357 gfc_error ("Pointer initialization requires a NULL() at %C");
4358 m = MATCH_ERROR;
4361 if (gfc_pure (NULL))
4363 gfc_error ("Initialization of pointer at %C is not allowed in "
4364 "a PURE procedure");
4365 m = MATCH_ERROR;
4368 if (m != MATCH_YES)
4369 goto cleanup;
4371 if (add_init_expr_to_sym (sym->name, &initializer, &gfc_current_locus)
4372 != SUCCESS)
4373 goto cleanup;
4377 gfc_set_sym_referenced (sym);
4379 if (gfc_match_eos () == MATCH_YES)
4380 return MATCH_YES;
4381 if (gfc_match_char (',') != MATCH_YES)
4382 goto syntax;
4385 syntax:
4386 gfc_error ("Syntax error in PROCEDURE statement at %C");
4387 return MATCH_ERROR;
4389 cleanup:
4390 /* Free stuff up and return. */
4391 gfc_free_expr (initializer);
4392 return m;
4396 static match
4397 match_binding_attributes (gfc_typebound_proc* ba, bool generic, bool ppc);
4400 /* Match a procedure pointer component declaration (R445). */
4402 static match
4403 match_ppc_decl (void)
4405 match m;
4406 gfc_symbol *proc_if = NULL;
4407 gfc_typespec ts;
4408 int num;
4409 gfc_component *c;
4410 gfc_expr *initializer = NULL;
4411 gfc_typebound_proc* tb;
4412 char name[GFC_MAX_SYMBOL_LEN + 1];
4414 /* Parse interface (with brackets). */
4415 m = match_procedure_interface (&proc_if);
4416 if (m != MATCH_YES)
4417 goto syntax;
4419 /* Parse attributes. */
4420 tb = XCNEW (gfc_typebound_proc);
4421 tb->where = gfc_current_locus;
4422 m = match_binding_attributes (tb, false, true);
4423 if (m == MATCH_ERROR)
4424 return m;
4426 /* TODO: Implement PASS. */
4427 if (!tb->nopass)
4429 gfc_error ("Procedure Pointer Component with PASS at %C "
4430 "not yet implemented");
4431 return MATCH_ERROR;
4434 gfc_clear_attr (&current_attr);
4435 current_attr.procedure = 1;
4436 current_attr.proc_pointer = 1;
4437 current_attr.access = tb->access;
4438 current_attr.flavor = FL_PROCEDURE;
4440 /* Match the colons (required). */
4441 if (gfc_match (" ::") != MATCH_YES)
4443 gfc_error ("Expected '::' after binding-attributes at %C");
4444 return MATCH_ERROR;
4447 /* Check for C450. */
4448 if (!tb->nopass && proc_if == NULL)
4450 gfc_error("NOPASS or explicit interface required at %C");
4451 return MATCH_ERROR;
4454 /* Match PPC names. */
4455 ts = current_ts;
4456 for(num=1;;num++)
4458 m = gfc_match_name (name);
4459 if (m == MATCH_NO)
4460 goto syntax;
4461 else if (m == MATCH_ERROR)
4462 return m;
4464 if (gfc_add_component (gfc_current_block (), name, &c) == FAILURE)
4465 return MATCH_ERROR;
4467 /* Add current_attr to the symbol attributes. */
4468 if (gfc_copy_attr (&c->attr, &current_attr, NULL) == FAILURE)
4469 return MATCH_ERROR;
4471 if (gfc_add_external (&c->attr, NULL) == FAILURE)
4472 return MATCH_ERROR;
4474 if (gfc_add_proc (&c->attr, name, NULL) == FAILURE)
4475 return MATCH_ERROR;
4477 /* Set interface. */
4478 if (proc_if != NULL)
4480 c->ts.interface = proc_if;
4481 c->attr.untyped = 1;
4482 c->attr.if_source = IFSRC_IFBODY;
4484 else if (ts.type != BT_UNKNOWN)
4486 c->ts = ts;
4487 c->ts.interface = gfc_new_symbol ("", gfc_current_ns);
4488 c->ts.interface->ts = ts;
4489 c->ts.interface->attr.function = 1;
4490 c->attr.function = c->ts.interface->attr.function;
4491 c->attr.if_source = IFSRC_UNKNOWN;
4494 if (gfc_match (" =>") == MATCH_YES)
4496 m = gfc_match_null (&initializer);
4497 if (m == MATCH_NO)
4499 gfc_error ("Pointer initialization requires a NULL() at %C");
4500 m = MATCH_ERROR;
4502 if (gfc_pure (NULL))
4504 gfc_error ("Initialization of pointer at %C is not allowed in "
4505 "a PURE procedure");
4506 m = MATCH_ERROR;
4508 if (m != MATCH_YES)
4510 gfc_free_expr (initializer);
4511 return m;
4513 c->initializer = initializer;
4516 if (gfc_match_eos () == MATCH_YES)
4517 return MATCH_YES;
4518 if (gfc_match_char (',') != MATCH_YES)
4519 goto syntax;
4522 syntax:
4523 gfc_error ("Syntax error in procedure pointer component at %C");
4524 return MATCH_ERROR;
4528 /* Match a PROCEDURE declaration inside an interface (R1206). */
4530 static match
4531 match_procedure_in_interface (void)
4533 match m;
4534 gfc_symbol *sym;
4535 char name[GFC_MAX_SYMBOL_LEN + 1];
4537 if (current_interface.type == INTERFACE_NAMELESS
4538 || current_interface.type == INTERFACE_ABSTRACT)
4540 gfc_error ("PROCEDURE at %C must be in a generic interface");
4541 return MATCH_ERROR;
4544 for(;;)
4546 m = gfc_match_name (name);
4547 if (m == MATCH_NO)
4548 goto syntax;
4549 else if (m == MATCH_ERROR)
4550 return m;
4551 if (gfc_get_symbol (name, gfc_current_ns->parent, &sym))
4552 return MATCH_ERROR;
4554 if (gfc_add_interface (sym) == FAILURE)
4555 return MATCH_ERROR;
4557 if (gfc_match_eos () == MATCH_YES)
4558 break;
4559 if (gfc_match_char (',') != MATCH_YES)
4560 goto syntax;
4563 return MATCH_YES;
4565 syntax:
4566 gfc_error ("Syntax error in PROCEDURE statement at %C");
4567 return MATCH_ERROR;
4571 /* General matcher for PROCEDURE declarations. */
4573 static match match_procedure_in_type (void);
4575 match
4576 gfc_match_procedure (void)
4578 match m;
4580 switch (gfc_current_state ())
4582 case COMP_NONE:
4583 case COMP_PROGRAM:
4584 case COMP_MODULE:
4585 case COMP_SUBROUTINE:
4586 case COMP_FUNCTION:
4587 m = match_procedure_decl ();
4588 break;
4589 case COMP_INTERFACE:
4590 m = match_procedure_in_interface ();
4591 break;
4592 case COMP_DERIVED:
4593 m = match_ppc_decl ();
4594 break;
4595 case COMP_DERIVED_CONTAINS:
4596 m = match_procedure_in_type ();
4597 break;
4598 default:
4599 return MATCH_NO;
4602 if (m != MATCH_YES)
4603 return m;
4605 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PROCEDURE statement at %C")
4606 == FAILURE)
4607 return MATCH_ERROR;
4609 return m;
4613 /* Warn if a matched procedure has the same name as an intrinsic; this is
4614 simply a wrapper around gfc_warn_intrinsic_shadow that interprets the current
4615 parser-state-stack to find out whether we're in a module. */
4617 static void
4618 warn_intrinsic_shadow (const gfc_symbol* sym, bool func)
4620 bool in_module;
4622 in_module = (gfc_state_stack->previous
4623 && gfc_state_stack->previous->state == COMP_MODULE);
4625 gfc_warn_intrinsic_shadow (sym, in_module, func);
4629 /* Match a function declaration. */
4631 match
4632 gfc_match_function_decl (void)
4634 char name[GFC_MAX_SYMBOL_LEN + 1];
4635 gfc_symbol *sym, *result;
4636 locus old_loc;
4637 match m;
4638 match suffix_match;
4639 match found_match; /* Status returned by match func. */
4641 if (gfc_current_state () != COMP_NONE
4642 && gfc_current_state () != COMP_INTERFACE
4643 && gfc_current_state () != COMP_CONTAINS)
4644 return MATCH_NO;
4646 gfc_clear_ts (&current_ts);
4648 old_loc = gfc_current_locus;
4650 m = gfc_match_prefix (&current_ts);
4651 if (m != MATCH_YES)
4653 gfc_current_locus = old_loc;
4654 return m;
4657 if (gfc_match ("function% %n", name) != MATCH_YES)
4659 gfc_current_locus = old_loc;
4660 return MATCH_NO;
4662 if (get_proc_name (name, &sym, false))
4663 return MATCH_ERROR;
4665 if (add_hidden_procptr_result (sym) == SUCCESS)
4666 sym = sym->result;
4668 gfc_new_block = sym;
4670 m = gfc_match_formal_arglist (sym, 0, 0);
4671 if (m == MATCH_NO)
4673 gfc_error ("Expected formal argument list in function "
4674 "definition at %C");
4675 m = MATCH_ERROR;
4676 goto cleanup;
4678 else if (m == MATCH_ERROR)
4679 goto cleanup;
4681 result = NULL;
4683 /* According to the draft, the bind(c) and result clause can
4684 come in either order after the formal_arg_list (i.e., either
4685 can be first, both can exist together or by themselves or neither
4686 one). Therefore, the match_result can't match the end of the
4687 string, and check for the bind(c) or result clause in either order. */
4688 found_match = gfc_match_eos ();
4690 /* Make sure that it isn't already declared as BIND(C). If it is, it
4691 must have been marked BIND(C) with a BIND(C) attribute and that is
4692 not allowed for procedures. */
4693 if (sym->attr.is_bind_c == 1)
4695 sym->attr.is_bind_c = 0;
4696 if (sym->old_symbol != NULL)
4697 gfc_error_now ("BIND(C) attribute at %L can only be used for "
4698 "variables or common blocks",
4699 &(sym->old_symbol->declared_at));
4700 else
4701 gfc_error_now ("BIND(C) attribute at %L can only be used for "
4702 "variables or common blocks", &gfc_current_locus);
4705 if (found_match != MATCH_YES)
4707 /* If we haven't found the end-of-statement, look for a suffix. */
4708 suffix_match = gfc_match_suffix (sym, &result);
4709 if (suffix_match == MATCH_YES)
4710 /* Need to get the eos now. */
4711 found_match = gfc_match_eos ();
4712 else
4713 found_match = suffix_match;
4716 if(found_match != MATCH_YES)
4717 m = MATCH_ERROR;
4718 else
4720 /* Make changes to the symbol. */
4721 m = MATCH_ERROR;
4723 if (gfc_add_function (&sym->attr, sym->name, NULL) == FAILURE)
4724 goto cleanup;
4726 if (gfc_missing_attr (&sym->attr, NULL) == FAILURE
4727 || copy_prefix (&sym->attr, &sym->declared_at) == FAILURE)
4728 goto cleanup;
4730 /* Delay matching the function characteristics until after the
4731 specification block by signalling kind=-1. */
4732 sym->declared_at = old_loc;
4733 if (current_ts.type != BT_UNKNOWN)
4734 current_ts.kind = -1;
4735 else
4736 current_ts.kind = 0;
4738 if (result == NULL)
4740 if (current_ts.type != BT_UNKNOWN
4741 && gfc_add_type (sym, &current_ts, &gfc_current_locus) == FAILURE)
4742 goto cleanup;
4743 sym->result = sym;
4745 else
4747 if (current_ts.type != BT_UNKNOWN
4748 && gfc_add_type (result, &current_ts, &gfc_current_locus)
4749 == FAILURE)
4750 goto cleanup;
4751 sym->result = result;
4754 /* Warn if this procedure has the same name as an intrinsic. */
4755 warn_intrinsic_shadow (sym, true);
4757 return MATCH_YES;
4760 cleanup:
4761 gfc_current_locus = old_loc;
4762 return m;
4766 /* This is mostly a copy of parse.c(add_global_procedure) but modified to
4767 pass the name of the entry, rather than the gfc_current_block name, and
4768 to return false upon finding an existing global entry. */
4770 static bool
4771 add_global_entry (const char *name, int sub)
4773 gfc_gsymbol *s;
4774 enum gfc_symbol_type type;
4776 s = gfc_get_gsymbol(name);
4777 type = sub ? GSYM_SUBROUTINE : GSYM_FUNCTION;
4779 if (s->defined
4780 || (s->type != GSYM_UNKNOWN
4781 && s->type != type))
4782 gfc_global_used(s, NULL);
4783 else
4785 s->type = type;
4786 s->where = gfc_current_locus;
4787 s->defined = 1;
4788 s->ns = gfc_current_ns;
4789 return true;
4791 return false;
4795 /* Match an ENTRY statement. */
4797 match
4798 gfc_match_entry (void)
4800 gfc_symbol *proc;
4801 gfc_symbol *result;
4802 gfc_symbol *entry;
4803 char name[GFC_MAX_SYMBOL_LEN + 1];
4804 gfc_compile_state state;
4805 match m;
4806 gfc_entry_list *el;
4807 locus old_loc;
4808 bool module_procedure;
4809 char peek_char;
4810 match is_bind_c;
4812 m = gfc_match_name (name);
4813 if (m != MATCH_YES)
4814 return m;
4816 state = gfc_current_state ();
4817 if (state != COMP_SUBROUTINE && state != COMP_FUNCTION)
4819 switch (state)
4821 case COMP_PROGRAM:
4822 gfc_error ("ENTRY statement at %C cannot appear within a PROGRAM");
4823 break;
4824 case COMP_MODULE:
4825 gfc_error ("ENTRY statement at %C cannot appear within a MODULE");
4826 break;
4827 case COMP_BLOCK_DATA:
4828 gfc_error ("ENTRY statement at %C cannot appear within "
4829 "a BLOCK DATA");
4830 break;
4831 case COMP_INTERFACE:
4832 gfc_error ("ENTRY statement at %C cannot appear within "
4833 "an INTERFACE");
4834 break;
4835 case COMP_DERIVED:
4836 gfc_error ("ENTRY statement at %C cannot appear within "
4837 "a DERIVED TYPE block");
4838 break;
4839 case COMP_IF:
4840 gfc_error ("ENTRY statement at %C cannot appear within "
4841 "an IF-THEN block");
4842 break;
4843 case COMP_DO:
4844 gfc_error ("ENTRY statement at %C cannot appear within "
4845 "a DO block");
4846 break;
4847 case COMP_SELECT:
4848 gfc_error ("ENTRY statement at %C cannot appear within "
4849 "a SELECT block");
4850 break;
4851 case COMP_FORALL:
4852 gfc_error ("ENTRY statement at %C cannot appear within "
4853 "a FORALL block");
4854 break;
4855 case COMP_WHERE:
4856 gfc_error ("ENTRY statement at %C cannot appear within "
4857 "a WHERE block");
4858 break;
4859 case COMP_CONTAINS:
4860 gfc_error ("ENTRY statement at %C cannot appear within "
4861 "a contained subprogram");
4862 break;
4863 default:
4864 gfc_internal_error ("gfc_match_entry(): Bad state");
4866 return MATCH_ERROR;
4869 module_procedure = gfc_current_ns->parent != NULL
4870 && gfc_current_ns->parent->proc_name
4871 && gfc_current_ns->parent->proc_name->attr.flavor
4872 == FL_MODULE;
4874 if (gfc_current_ns->parent != NULL
4875 && gfc_current_ns->parent->proc_name
4876 && !module_procedure)
4878 gfc_error("ENTRY statement at %C cannot appear in a "
4879 "contained procedure");
4880 return MATCH_ERROR;
4883 /* Module function entries need special care in get_proc_name
4884 because previous references within the function will have
4885 created symbols attached to the current namespace. */
4886 if (get_proc_name (name, &entry,
4887 gfc_current_ns->parent != NULL
4888 && module_procedure))
4889 return MATCH_ERROR;
4891 proc = gfc_current_block ();
4893 /* Make sure that it isn't already declared as BIND(C). If it is, it
4894 must have been marked BIND(C) with a BIND(C) attribute and that is
4895 not allowed for procedures. */
4896 if (entry->attr.is_bind_c == 1)
4898 entry->attr.is_bind_c = 0;
4899 if (entry->old_symbol != NULL)
4900 gfc_error_now ("BIND(C) attribute at %L can only be used for "
4901 "variables or common blocks",
4902 &(entry->old_symbol->declared_at));
4903 else
4904 gfc_error_now ("BIND(C) attribute at %L can only be used for "
4905 "variables or common blocks", &gfc_current_locus);
4908 /* Check what next non-whitespace character is so we can tell if there
4909 is the required parens if we have a BIND(C). */
4910 gfc_gobble_whitespace ();
4911 peek_char = gfc_peek_ascii_char ();
4913 if (state == COMP_SUBROUTINE)
4915 /* An entry in a subroutine. */
4916 if (!gfc_current_ns->parent && !add_global_entry (name, 1))
4917 return MATCH_ERROR;
4919 m = gfc_match_formal_arglist (entry, 0, 1);
4920 if (m != MATCH_YES)
4921 return MATCH_ERROR;
4923 /* Call gfc_match_bind_c with allow_binding_name = true as ENTRY can
4924 never be an internal procedure. */
4925 is_bind_c = gfc_match_bind_c (entry, true);
4926 if (is_bind_c == MATCH_ERROR)
4927 return MATCH_ERROR;
4928 if (is_bind_c == MATCH_YES)
4930 if (peek_char != '(')
4932 gfc_error ("Missing required parentheses before BIND(C) at %C");
4933 return MATCH_ERROR;
4935 if (gfc_add_is_bind_c (&(entry->attr), entry->name, &(entry->declared_at), 1)
4936 == FAILURE)
4937 return MATCH_ERROR;
4940 if (gfc_add_entry (&entry->attr, entry->name, NULL) == FAILURE
4941 || gfc_add_subroutine (&entry->attr, entry->name, NULL) == FAILURE)
4942 return MATCH_ERROR;
4944 else
4946 /* An entry in a function.
4947 We need to take special care because writing
4948 ENTRY f()
4950 ENTRY f
4951 is allowed, whereas
4952 ENTRY f() RESULT (r)
4953 can't be written as
4954 ENTRY f RESULT (r). */
4955 if (!gfc_current_ns->parent && !add_global_entry (name, 0))
4956 return MATCH_ERROR;
4958 old_loc = gfc_current_locus;
4959 if (gfc_match_eos () == MATCH_YES)
4961 gfc_current_locus = old_loc;
4962 /* Match the empty argument list, and add the interface to
4963 the symbol. */
4964 m = gfc_match_formal_arglist (entry, 0, 1);
4966 else
4967 m = gfc_match_formal_arglist (entry, 0, 0);
4969 if (m != MATCH_YES)
4970 return MATCH_ERROR;
4972 result = NULL;
4974 if (gfc_match_eos () == MATCH_YES)
4976 if (gfc_add_entry (&entry->attr, entry->name, NULL) == FAILURE
4977 || gfc_add_function (&entry->attr, entry->name, NULL) == FAILURE)
4978 return MATCH_ERROR;
4980 entry->result = entry;
4982 else
4984 m = gfc_match_suffix (entry, &result);
4985 if (m == MATCH_NO)
4986 gfc_syntax_error (ST_ENTRY);
4987 if (m != MATCH_YES)
4988 return MATCH_ERROR;
4990 if (result)
4992 if (gfc_add_result (&result->attr, result->name, NULL) == FAILURE
4993 || gfc_add_entry (&entry->attr, result->name, NULL) == FAILURE
4994 || gfc_add_function (&entry->attr, result->name, NULL)
4995 == FAILURE)
4996 return MATCH_ERROR;
4997 entry->result = result;
4999 else
5001 if (gfc_add_entry (&entry->attr, entry->name, NULL) == FAILURE
5002 || gfc_add_function (&entry->attr, entry->name, NULL) == FAILURE)
5003 return MATCH_ERROR;
5004 entry->result = entry;
5009 if (gfc_match_eos () != MATCH_YES)
5011 gfc_syntax_error (ST_ENTRY);
5012 return MATCH_ERROR;
5015 entry->attr.recursive = proc->attr.recursive;
5016 entry->attr.elemental = proc->attr.elemental;
5017 entry->attr.pure = proc->attr.pure;
5019 el = gfc_get_entry_list ();
5020 el->sym = entry;
5021 el->next = gfc_current_ns->entries;
5022 gfc_current_ns->entries = el;
5023 if (el->next)
5024 el->id = el->next->id + 1;
5025 else
5026 el->id = 1;
5028 new_st.op = EXEC_ENTRY;
5029 new_st.ext.entry = el;
5031 return MATCH_YES;
5035 /* Match a subroutine statement, including optional prefixes. */
5037 match
5038 gfc_match_subroutine (void)
5040 char name[GFC_MAX_SYMBOL_LEN + 1];
5041 gfc_symbol *sym;
5042 match m;
5043 match is_bind_c;
5044 char peek_char;
5045 bool allow_binding_name;
5047 if (gfc_current_state () != COMP_NONE
5048 && gfc_current_state () != COMP_INTERFACE
5049 && gfc_current_state () != COMP_CONTAINS)
5050 return MATCH_NO;
5052 m = gfc_match_prefix (NULL);
5053 if (m != MATCH_YES)
5054 return m;
5056 m = gfc_match ("subroutine% %n", name);
5057 if (m != MATCH_YES)
5058 return m;
5060 if (get_proc_name (name, &sym, false))
5061 return MATCH_ERROR;
5063 if (add_hidden_procptr_result (sym) == SUCCESS)
5064 sym = sym->result;
5066 gfc_new_block = sym;
5068 /* Check what next non-whitespace character is so we can tell if there
5069 is the required parens if we have a BIND(C). */
5070 gfc_gobble_whitespace ();
5071 peek_char = gfc_peek_ascii_char ();
5073 if (gfc_add_subroutine (&sym->attr, sym->name, NULL) == FAILURE)
5074 return MATCH_ERROR;
5076 if (gfc_match_formal_arglist (sym, 0, 1) != MATCH_YES)
5077 return MATCH_ERROR;
5079 /* Make sure that it isn't already declared as BIND(C). If it is, it
5080 must have been marked BIND(C) with a BIND(C) attribute and that is
5081 not allowed for procedures. */
5082 if (sym->attr.is_bind_c == 1)
5084 sym->attr.is_bind_c = 0;
5085 if (sym->old_symbol != NULL)
5086 gfc_error_now ("BIND(C) attribute at %L can only be used for "
5087 "variables or common blocks",
5088 &(sym->old_symbol->declared_at));
5089 else
5090 gfc_error_now ("BIND(C) attribute at %L can only be used for "
5091 "variables or common blocks", &gfc_current_locus);
5094 /* C binding names are not allowed for internal procedures. */
5095 if (gfc_current_state () == COMP_CONTAINS
5096 && sym->ns->proc_name->attr.flavor != FL_MODULE)
5097 allow_binding_name = false;
5098 else
5099 allow_binding_name = true;
5101 /* Here, we are just checking if it has the bind(c) attribute, and if
5102 so, then we need to make sure it's all correct. If it doesn't,
5103 we still need to continue matching the rest of the subroutine line. */
5104 is_bind_c = gfc_match_bind_c (sym, allow_binding_name);
5105 if (is_bind_c == MATCH_ERROR)
5107 /* There was an attempt at the bind(c), but it was wrong. An
5108 error message should have been printed w/in the gfc_match_bind_c
5109 so here we'll just return the MATCH_ERROR. */
5110 return MATCH_ERROR;
5113 if (is_bind_c == MATCH_YES)
5115 /* The following is allowed in the Fortran 2008 draft. */
5116 if (gfc_current_state () == COMP_CONTAINS
5117 && sym->ns->proc_name->attr.flavor != FL_MODULE
5118 && gfc_notify_std (GFC_STD_F2008, "Fortran 2008: BIND(C) attribute "
5119 "at %L may not be specified for an internal "
5120 "procedure", &gfc_current_locus)
5121 == FAILURE)
5122 return MATCH_ERROR;
5124 if (peek_char != '(')
5126 gfc_error ("Missing required parentheses before BIND(C) at %C");
5127 return MATCH_ERROR;
5129 if (gfc_add_is_bind_c (&(sym->attr), sym->name, &(sym->declared_at), 1)
5130 == FAILURE)
5131 return MATCH_ERROR;
5134 if (gfc_match_eos () != MATCH_YES)
5136 gfc_syntax_error (ST_SUBROUTINE);
5137 return MATCH_ERROR;
5140 if (copy_prefix (&sym->attr, &sym->declared_at) == FAILURE)
5141 return MATCH_ERROR;
5143 /* Warn if it has the same name as an intrinsic. */
5144 warn_intrinsic_shadow (sym, false);
5146 return MATCH_YES;
5150 /* Match a BIND(C) specifier, with the optional 'name=' specifier if
5151 given, and set the binding label in either the given symbol (if not
5152 NULL), or in the current_ts. The symbol may be NULL because we may
5153 encounter the BIND(C) before the declaration itself. Return
5154 MATCH_NO if what we're looking at isn't a BIND(C) specifier,
5155 MATCH_ERROR if it is a BIND(C) clause but an error was encountered,
5156 or MATCH_YES if the specifier was correct and the binding label and
5157 bind(c) fields were set correctly for the given symbol or the
5158 current_ts. If allow_binding_name is false, no binding name may be
5159 given. */
5161 match
5162 gfc_match_bind_c (gfc_symbol *sym, bool allow_binding_name)
5164 /* binding label, if exists */
5165 char binding_label[GFC_MAX_SYMBOL_LEN + 1];
5166 match double_quote;
5167 match single_quote;
5169 /* Initialize the flag that specifies whether we encountered a NAME=
5170 specifier or not. */
5171 has_name_equals = 0;
5173 /* Init the first char to nil so we can catch if we don't have
5174 the label (name attr) or the symbol name yet. */
5175 binding_label[0] = '\0';
5177 /* This much we have to be able to match, in this order, if
5178 there is a bind(c) label. */
5179 if (gfc_match (" bind ( c ") != MATCH_YES)
5180 return MATCH_NO;
5182 /* Now see if there is a binding label, or if we've reached the
5183 end of the bind(c) attribute without one. */
5184 if (gfc_match_char (',') == MATCH_YES)
5186 if (gfc_match (" name = ") != MATCH_YES)
5188 gfc_error ("Syntax error in NAME= specifier for binding label "
5189 "at %C");
5190 /* should give an error message here */
5191 return MATCH_ERROR;
5194 has_name_equals = 1;
5196 /* Get the opening quote. */
5197 double_quote = MATCH_YES;
5198 single_quote = MATCH_YES;
5199 double_quote = gfc_match_char ('"');
5200 if (double_quote != MATCH_YES)
5201 single_quote = gfc_match_char ('\'');
5202 if (double_quote != MATCH_YES && single_quote != MATCH_YES)
5204 gfc_error ("Syntax error in NAME= specifier for binding label "
5205 "at %C");
5206 return MATCH_ERROR;
5209 /* Grab the binding label, using functions that will not lower
5210 case the names automatically. */
5211 if (gfc_match_name_C (binding_label) != MATCH_YES)
5212 return MATCH_ERROR;
5214 /* Get the closing quotation. */
5215 if (double_quote == MATCH_YES)
5217 if (gfc_match_char ('"') != MATCH_YES)
5219 gfc_error ("Missing closing quote '\"' for binding label at %C");
5220 /* User started string with '"' so looked to match it. */
5221 return MATCH_ERROR;
5224 else
5226 if (gfc_match_char ('\'') != MATCH_YES)
5228 gfc_error ("Missing closing quote '\'' for binding label at %C");
5229 /* User started string with "'" char. */
5230 return MATCH_ERROR;
5235 /* Get the required right paren. */
5236 if (gfc_match_char (')') != MATCH_YES)
5238 gfc_error ("Missing closing paren for binding label at %C");
5239 return MATCH_ERROR;
5242 if (has_name_equals && !allow_binding_name)
5244 gfc_error ("No binding name is allowed in BIND(C) at %C");
5245 return MATCH_ERROR;
5248 if (has_name_equals && sym != NULL && sym->attr.dummy)
5250 gfc_error ("For dummy procedure %s, no binding name is "
5251 "allowed in BIND(C) at %C", sym->name);
5252 return MATCH_ERROR;
5256 /* Save the binding label to the symbol. If sym is null, we're
5257 probably matching the typespec attributes of a declaration and
5258 haven't gotten the name yet, and therefore, no symbol yet. */
5259 if (binding_label[0] != '\0')
5261 if (sym != NULL)
5263 strcpy (sym->binding_label, binding_label);
5265 else
5266 strcpy (curr_binding_label, binding_label);
5268 else if (allow_binding_name)
5270 /* No binding label, but if symbol isn't null, we
5271 can set the label for it here.
5272 If name="" or allow_binding_name is false, no C binding name is
5273 created. */
5274 if (sym != NULL && sym->name != NULL && has_name_equals == 0)
5275 strncpy (sym->binding_label, sym->name, strlen (sym->name) + 1);
5278 if (has_name_equals && gfc_current_state () == COMP_INTERFACE
5279 && current_interface.type == INTERFACE_ABSTRACT)
5281 gfc_error ("NAME not allowed on BIND(C) for ABSTRACT INTERFACE at %C");
5282 return MATCH_ERROR;
5285 return MATCH_YES;
5289 /* Return nonzero if we're currently compiling a contained procedure. */
5291 static int
5292 contained_procedure (void)
5294 gfc_state_data *s = gfc_state_stack;
5296 if ((s->state == COMP_SUBROUTINE || s->state == COMP_FUNCTION)
5297 && s->previous != NULL && s->previous->state == COMP_CONTAINS)
5298 return 1;
5300 return 0;
5303 /* Set the kind of each enumerator. The kind is selected such that it is
5304 interoperable with the corresponding C enumeration type, making
5305 sure that -fshort-enums is honored. */
5307 static void
5308 set_enum_kind(void)
5310 enumerator_history *current_history = NULL;
5311 int kind;
5312 int i;
5314 if (max_enum == NULL || enum_history == NULL)
5315 return;
5317 if (!flag_short_enums)
5318 return;
5320 i = 0;
5323 kind = gfc_integer_kinds[i++].kind;
5325 while (kind < gfc_c_int_kind
5326 && gfc_check_integer_range (max_enum->initializer->value.integer,
5327 kind) != ARITH_OK);
5329 current_history = enum_history;
5330 while (current_history != NULL)
5332 current_history->sym->ts.kind = kind;
5333 current_history = current_history->next;
5338 /* Match any of the various end-block statements. Returns the type of
5339 END to the caller. The END INTERFACE, END IF, END DO and END
5340 SELECT statements cannot be replaced by a single END statement. */
5342 match
5343 gfc_match_end (gfc_statement *st)
5345 char name[GFC_MAX_SYMBOL_LEN + 1];
5346 gfc_compile_state state;
5347 locus old_loc;
5348 const char *block_name;
5349 const char *target;
5350 int eos_ok;
5351 match m;
5353 old_loc = gfc_current_locus;
5354 if (gfc_match ("end") != MATCH_YES)
5355 return MATCH_NO;
5357 state = gfc_current_state ();
5358 block_name = gfc_current_block () == NULL
5359 ? NULL : gfc_current_block ()->name;
5361 if (state == COMP_CONTAINS || state == COMP_DERIVED_CONTAINS)
5363 state = gfc_state_stack->previous->state;
5364 block_name = gfc_state_stack->previous->sym == NULL
5365 ? NULL : gfc_state_stack->previous->sym->name;
5368 switch (state)
5370 case COMP_NONE:
5371 case COMP_PROGRAM:
5372 *st = ST_END_PROGRAM;
5373 target = " program";
5374 eos_ok = 1;
5375 break;
5377 case COMP_SUBROUTINE:
5378 *st = ST_END_SUBROUTINE;
5379 target = " subroutine";
5380 eos_ok = !contained_procedure ();
5381 break;
5383 case COMP_FUNCTION:
5384 *st = ST_END_FUNCTION;
5385 target = " function";
5386 eos_ok = !contained_procedure ();
5387 break;
5389 case COMP_BLOCK_DATA:
5390 *st = ST_END_BLOCK_DATA;
5391 target = " block data";
5392 eos_ok = 1;
5393 break;
5395 case COMP_MODULE:
5396 *st = ST_END_MODULE;
5397 target = " module";
5398 eos_ok = 1;
5399 break;
5401 case COMP_INTERFACE:
5402 *st = ST_END_INTERFACE;
5403 target = " interface";
5404 eos_ok = 0;
5405 break;
5407 case COMP_DERIVED:
5408 case COMP_DERIVED_CONTAINS:
5409 *st = ST_END_TYPE;
5410 target = " type";
5411 eos_ok = 0;
5412 break;
5414 case COMP_IF:
5415 *st = ST_ENDIF;
5416 target = " if";
5417 eos_ok = 0;
5418 break;
5420 case COMP_DO:
5421 *st = ST_ENDDO;
5422 target = " do";
5423 eos_ok = 0;
5424 break;
5426 case COMP_SELECT:
5427 *st = ST_END_SELECT;
5428 target = " select";
5429 eos_ok = 0;
5430 break;
5432 case COMP_FORALL:
5433 *st = ST_END_FORALL;
5434 target = " forall";
5435 eos_ok = 0;
5436 break;
5438 case COMP_WHERE:
5439 *st = ST_END_WHERE;
5440 target = " where";
5441 eos_ok = 0;
5442 break;
5444 case COMP_ENUM:
5445 *st = ST_END_ENUM;
5446 target = " enum";
5447 eos_ok = 0;
5448 last_initializer = NULL;
5449 set_enum_kind ();
5450 gfc_free_enum_history ();
5451 break;
5453 default:
5454 gfc_error ("Unexpected END statement at %C");
5455 goto cleanup;
5458 if (gfc_match_eos () == MATCH_YES)
5460 if (!eos_ok)
5462 /* We would have required END [something]. */
5463 gfc_error ("%s statement expected at %L",
5464 gfc_ascii_statement (*st), &old_loc);
5465 goto cleanup;
5468 return MATCH_YES;
5471 /* Verify that we've got the sort of end-block that we're expecting. */
5472 if (gfc_match (target) != MATCH_YES)
5474 gfc_error ("Expecting %s statement at %C", gfc_ascii_statement (*st));
5475 goto cleanup;
5478 /* If we're at the end, make sure a block name wasn't required. */
5479 if (gfc_match_eos () == MATCH_YES)
5482 if (*st != ST_ENDDO && *st != ST_ENDIF && *st != ST_END_SELECT
5483 && *st != ST_END_FORALL && *st != ST_END_WHERE)
5484 return MATCH_YES;
5486 if (gfc_current_block () == NULL)
5487 return MATCH_YES;
5489 gfc_error ("Expected block name of '%s' in %s statement at %C",
5490 block_name, gfc_ascii_statement (*st));
5492 return MATCH_ERROR;
5495 /* END INTERFACE has a special handler for its several possible endings. */
5496 if (*st == ST_END_INTERFACE)
5497 return gfc_match_end_interface ();
5499 /* We haven't hit the end of statement, so what is left must be an
5500 end-name. */
5501 m = gfc_match_space ();
5502 if (m == MATCH_YES)
5503 m = gfc_match_name (name);
5505 if (m == MATCH_NO)
5506 gfc_error ("Expected terminating name at %C");
5507 if (m != MATCH_YES)
5508 goto cleanup;
5510 if (block_name == NULL)
5511 goto syntax;
5513 if (strcmp (name, block_name) != 0 && strcmp (block_name, "ppr@") != 0)
5515 gfc_error ("Expected label '%s' for %s statement at %C", block_name,
5516 gfc_ascii_statement (*st));
5517 goto cleanup;
5519 /* Procedure pointer as function result. */
5520 else if (strcmp (block_name, "ppr@") == 0
5521 && strcmp (name, gfc_current_block ()->ns->proc_name->name) != 0)
5523 gfc_error ("Expected label '%s' for %s statement at %C",
5524 gfc_current_block ()->ns->proc_name->name,
5525 gfc_ascii_statement (*st));
5526 goto cleanup;
5529 if (gfc_match_eos () == MATCH_YES)
5530 return MATCH_YES;
5532 syntax:
5533 gfc_syntax_error (*st);
5535 cleanup:
5536 gfc_current_locus = old_loc;
5537 return MATCH_ERROR;
5542 /***************** Attribute declaration statements ****************/
5544 /* Set the attribute of a single variable. */
5546 static match
5547 attr_decl1 (void)
5549 char name[GFC_MAX_SYMBOL_LEN + 1];
5550 gfc_array_spec *as;
5551 gfc_symbol *sym;
5552 locus var_locus;
5553 match m;
5555 as = NULL;
5557 m = gfc_match_name (name);
5558 if (m != MATCH_YES)
5559 goto cleanup;
5561 if (find_special (name, &sym, false))
5562 return MATCH_ERROR;
5564 var_locus = gfc_current_locus;
5566 /* Deal with possible array specification for certain attributes. */
5567 if (current_attr.dimension
5568 || current_attr.allocatable
5569 || current_attr.pointer
5570 || current_attr.target)
5572 m = gfc_match_array_spec (&as);
5573 if (m == MATCH_ERROR)
5574 goto cleanup;
5576 if (current_attr.dimension && m == MATCH_NO)
5578 gfc_error ("Missing array specification at %L in DIMENSION "
5579 "statement", &var_locus);
5580 m = MATCH_ERROR;
5581 goto cleanup;
5584 if (current_attr.dimension && sym->value)
5586 gfc_error ("Dimensions specified for %s at %L after its "
5587 "initialisation", sym->name, &var_locus);
5588 m = MATCH_ERROR;
5589 goto cleanup;
5592 if ((current_attr.allocatable || current_attr.pointer)
5593 && (m == MATCH_YES) && (as->type != AS_DEFERRED))
5595 gfc_error ("Array specification must be deferred at %L", &var_locus);
5596 m = MATCH_ERROR;
5597 goto cleanup;
5601 /* Update symbol table. DIMENSION attribute is set
5602 in gfc_set_array_spec(). */
5603 if (current_attr.dimension == 0
5604 && gfc_copy_attr (&sym->attr, &current_attr, &var_locus) == FAILURE)
5606 m = MATCH_ERROR;
5607 goto cleanup;
5610 if (gfc_set_array_spec (sym, as, &var_locus) == FAILURE)
5612 m = MATCH_ERROR;
5613 goto cleanup;
5616 if (sym->attr.cray_pointee && sym->as != NULL)
5618 /* Fix the array spec. */
5619 m = gfc_mod_pointee_as (sym->as);
5620 if (m == MATCH_ERROR)
5621 goto cleanup;
5624 if (gfc_add_attribute (&sym->attr, &var_locus) == FAILURE)
5626 m = MATCH_ERROR;
5627 goto cleanup;
5630 if ((current_attr.external || current_attr.intrinsic)
5631 && sym->attr.flavor != FL_PROCEDURE
5632 && gfc_add_flavor (&sym->attr, FL_PROCEDURE, sym->name, NULL) == FAILURE)
5634 m = MATCH_ERROR;
5635 goto cleanup;
5638 add_hidden_procptr_result (sym);
5640 return MATCH_YES;
5642 cleanup:
5643 gfc_free_array_spec (as);
5644 return m;
5648 /* Generic attribute declaration subroutine. Used for attributes that
5649 just have a list of names. */
5651 static match
5652 attr_decl (void)
5654 match m;
5656 /* Gobble the optional double colon, by simply ignoring the result
5657 of gfc_match(). */
5658 gfc_match (" ::");
5660 for (;;)
5662 m = attr_decl1 ();
5663 if (m != MATCH_YES)
5664 break;
5666 if (gfc_match_eos () == MATCH_YES)
5668 m = MATCH_YES;
5669 break;
5672 if (gfc_match_char (',') != MATCH_YES)
5674 gfc_error ("Unexpected character in variable list at %C");
5675 m = MATCH_ERROR;
5676 break;
5680 return m;
5684 /* This routine matches Cray Pointer declarations of the form:
5685 pointer ( <pointer>, <pointee> )
5687 pointer ( <pointer1>, <pointee1> ), ( <pointer2>, <pointee2> ), ...
5688 The pointer, if already declared, should be an integer. Otherwise, we
5689 set it as BT_INTEGER with kind gfc_index_integer_kind. The pointee may
5690 be either a scalar, or an array declaration. No space is allocated for
5691 the pointee. For the statement
5692 pointer (ipt, ar(10))
5693 any subsequent uses of ar will be translated (in C-notation) as
5694 ar(i) => ((<type> *) ipt)(i)
5695 After gimplification, pointee variable will disappear in the code. */
5697 static match
5698 cray_pointer_decl (void)
5700 match m;
5701 gfc_array_spec *as;
5702 gfc_symbol *cptr; /* Pointer symbol. */
5703 gfc_symbol *cpte; /* Pointee symbol. */
5704 locus var_locus;
5705 bool done = false;
5707 while (!done)
5709 if (gfc_match_char ('(') != MATCH_YES)
5711 gfc_error ("Expected '(' at %C");
5712 return MATCH_ERROR;
5715 /* Match pointer. */
5716 var_locus = gfc_current_locus;
5717 gfc_clear_attr (&current_attr);
5718 gfc_add_cray_pointer (&current_attr, &var_locus);
5719 current_ts.type = BT_INTEGER;
5720 current_ts.kind = gfc_index_integer_kind;
5722 m = gfc_match_symbol (&cptr, 0);
5723 if (m != MATCH_YES)
5725 gfc_error ("Expected variable name at %C");
5726 return m;
5729 if (gfc_add_cray_pointer (&cptr->attr, &var_locus) == FAILURE)
5730 return MATCH_ERROR;
5732 gfc_set_sym_referenced (cptr);
5734 if (cptr->ts.type == BT_UNKNOWN) /* Override the type, if necessary. */
5736 cptr->ts.type = BT_INTEGER;
5737 cptr->ts.kind = gfc_index_integer_kind;
5739 else if (cptr->ts.type != BT_INTEGER)
5741 gfc_error ("Cray pointer at %C must be an integer");
5742 return MATCH_ERROR;
5744 else if (cptr->ts.kind < gfc_index_integer_kind)
5745 gfc_warning ("Cray pointer at %C has %d bytes of precision;"
5746 " memory addresses require %d bytes",
5747 cptr->ts.kind, gfc_index_integer_kind);
5749 if (gfc_match_char (',') != MATCH_YES)
5751 gfc_error ("Expected \",\" at %C");
5752 return MATCH_ERROR;
5755 /* Match Pointee. */
5756 var_locus = gfc_current_locus;
5757 gfc_clear_attr (&current_attr);
5758 gfc_add_cray_pointee (&current_attr, &var_locus);
5759 current_ts.type = BT_UNKNOWN;
5760 current_ts.kind = 0;
5762 m = gfc_match_symbol (&cpte, 0);
5763 if (m != MATCH_YES)
5765 gfc_error ("Expected variable name at %C");
5766 return m;
5769 /* Check for an optional array spec. */
5770 m = gfc_match_array_spec (&as);
5771 if (m == MATCH_ERROR)
5773 gfc_free_array_spec (as);
5774 return m;
5776 else if (m == MATCH_NO)
5778 gfc_free_array_spec (as);
5779 as = NULL;
5782 if (gfc_add_cray_pointee (&cpte->attr, &var_locus) == FAILURE)
5783 return MATCH_ERROR;
5785 gfc_set_sym_referenced (cpte);
5787 if (cpte->as == NULL)
5789 if (gfc_set_array_spec (cpte, as, &var_locus) == FAILURE)
5790 gfc_internal_error ("Couldn't set Cray pointee array spec.");
5792 else if (as != NULL)
5794 gfc_error ("Duplicate array spec for Cray pointee at %C");
5795 gfc_free_array_spec (as);
5796 return MATCH_ERROR;
5799 as = NULL;
5801 if (cpte->as != NULL)
5803 /* Fix array spec. */
5804 m = gfc_mod_pointee_as (cpte->as);
5805 if (m == MATCH_ERROR)
5806 return m;
5809 /* Point the Pointee at the Pointer. */
5810 cpte->cp_pointer = cptr;
5812 if (gfc_match_char (')') != MATCH_YES)
5814 gfc_error ("Expected \")\" at %C");
5815 return MATCH_ERROR;
5817 m = gfc_match_char (',');
5818 if (m != MATCH_YES)
5819 done = true; /* Stop searching for more declarations. */
5823 if (m == MATCH_ERROR /* Failed when trying to find ',' above. */
5824 || gfc_match_eos () != MATCH_YES)
5826 gfc_error ("Expected \",\" or end of statement at %C");
5827 return MATCH_ERROR;
5829 return MATCH_YES;
5833 match
5834 gfc_match_external (void)
5837 gfc_clear_attr (&current_attr);
5838 current_attr.external = 1;
5840 return attr_decl ();
5844 match
5845 gfc_match_intent (void)
5847 sym_intent intent;
5849 intent = match_intent_spec ();
5850 if (intent == INTENT_UNKNOWN)
5851 return MATCH_ERROR;
5853 gfc_clear_attr (&current_attr);
5854 current_attr.intent = intent;
5856 return attr_decl ();
5860 match
5861 gfc_match_intrinsic (void)
5864 gfc_clear_attr (&current_attr);
5865 current_attr.intrinsic = 1;
5867 return attr_decl ();
5871 match
5872 gfc_match_optional (void)
5875 gfc_clear_attr (&current_attr);
5876 current_attr.optional = 1;
5878 return attr_decl ();
5882 match
5883 gfc_match_pointer (void)
5885 gfc_gobble_whitespace ();
5886 if (gfc_peek_ascii_char () == '(')
5888 if (!gfc_option.flag_cray_pointer)
5890 gfc_error ("Cray pointer declaration at %C requires -fcray-pointer "
5891 "flag");
5892 return MATCH_ERROR;
5894 return cray_pointer_decl ();
5896 else
5898 gfc_clear_attr (&current_attr);
5899 current_attr.pointer = 1;
5901 return attr_decl ();
5906 match
5907 gfc_match_allocatable (void)
5909 gfc_clear_attr (&current_attr);
5910 current_attr.allocatable = 1;
5912 return attr_decl ();
5916 match
5917 gfc_match_dimension (void)
5919 gfc_clear_attr (&current_attr);
5920 current_attr.dimension = 1;
5922 return attr_decl ();
5926 match
5927 gfc_match_target (void)
5929 gfc_clear_attr (&current_attr);
5930 current_attr.target = 1;
5932 return attr_decl ();
5936 /* Match the list of entities being specified in a PUBLIC or PRIVATE
5937 statement. */
5939 static match
5940 access_attr_decl (gfc_statement st)
5942 char name[GFC_MAX_SYMBOL_LEN + 1];
5943 interface_type type;
5944 gfc_user_op *uop;
5945 gfc_symbol *sym;
5946 gfc_intrinsic_op op;
5947 match m;
5949 if (gfc_match (" ::") == MATCH_NO && gfc_match_space () == MATCH_NO)
5950 goto done;
5952 for (;;)
5954 m = gfc_match_generic_spec (&type, name, &op);
5955 if (m == MATCH_NO)
5956 goto syntax;
5957 if (m == MATCH_ERROR)
5958 return MATCH_ERROR;
5960 switch (type)
5962 case INTERFACE_NAMELESS:
5963 case INTERFACE_ABSTRACT:
5964 goto syntax;
5966 case INTERFACE_GENERIC:
5967 if (gfc_get_symbol (name, NULL, &sym))
5968 goto done;
5970 if (gfc_add_access (&sym->attr, (st == ST_PUBLIC)
5971 ? ACCESS_PUBLIC : ACCESS_PRIVATE,
5972 sym->name, NULL) == FAILURE)
5973 return MATCH_ERROR;
5975 break;
5977 case INTERFACE_INTRINSIC_OP:
5978 if (gfc_current_ns->operator_access[op] == ACCESS_UNKNOWN)
5980 gfc_current_ns->operator_access[op] =
5981 (st == ST_PUBLIC) ? ACCESS_PUBLIC : ACCESS_PRIVATE;
5983 else
5985 gfc_error ("Access specification of the %s operator at %C has "
5986 "already been specified", gfc_op2string (op));
5987 goto done;
5990 break;
5992 case INTERFACE_USER_OP:
5993 uop = gfc_get_uop (name);
5995 if (uop->access == ACCESS_UNKNOWN)
5997 uop->access = (st == ST_PUBLIC)
5998 ? ACCESS_PUBLIC : ACCESS_PRIVATE;
6000 else
6002 gfc_error ("Access specification of the .%s. operator at %C "
6003 "has already been specified", sym->name);
6004 goto done;
6007 break;
6010 if (gfc_match_char (',') == MATCH_NO)
6011 break;
6014 if (gfc_match_eos () != MATCH_YES)
6015 goto syntax;
6016 return MATCH_YES;
6018 syntax:
6019 gfc_syntax_error (st);
6021 done:
6022 return MATCH_ERROR;
6026 match
6027 gfc_match_protected (void)
6029 gfc_symbol *sym;
6030 match m;
6032 if (gfc_current_ns->proc_name->attr.flavor != FL_MODULE)
6034 gfc_error ("PROTECTED at %C only allowed in specification "
6035 "part of a module");
6036 return MATCH_ERROR;
6040 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PROTECTED statement at %C")
6041 == FAILURE)
6042 return MATCH_ERROR;
6044 if (gfc_match (" ::") == MATCH_NO && gfc_match_space () == MATCH_NO)
6046 return MATCH_ERROR;
6049 if (gfc_match_eos () == MATCH_YES)
6050 goto syntax;
6052 for(;;)
6054 m = gfc_match_symbol (&sym, 0);
6055 switch (m)
6057 case MATCH_YES:
6058 if (gfc_add_protected (&sym->attr, sym->name, &gfc_current_locus)
6059 == FAILURE)
6060 return MATCH_ERROR;
6061 goto next_item;
6063 case MATCH_NO:
6064 break;
6066 case MATCH_ERROR:
6067 return MATCH_ERROR;
6070 next_item:
6071 if (gfc_match_eos () == MATCH_YES)
6072 break;
6073 if (gfc_match_char (',') != MATCH_YES)
6074 goto syntax;
6077 return MATCH_YES;
6079 syntax:
6080 gfc_error ("Syntax error in PROTECTED statement at %C");
6081 return MATCH_ERROR;
6085 /* The PRIVATE statement is a bit weird in that it can be an attribute
6086 declaration, but also works as a standalone statement inside of a
6087 type declaration or a module. */
6089 match
6090 gfc_match_private (gfc_statement *st)
6093 if (gfc_match ("private") != MATCH_YES)
6094 return MATCH_NO;
6096 if (gfc_current_state () != COMP_MODULE
6097 && !(gfc_current_state () == COMP_DERIVED
6098 && gfc_state_stack->previous
6099 && gfc_state_stack->previous->state == COMP_MODULE)
6100 && !(gfc_current_state () == COMP_DERIVED_CONTAINS
6101 && gfc_state_stack->previous && gfc_state_stack->previous->previous
6102 && gfc_state_stack->previous->previous->state == COMP_MODULE))
6104 gfc_error ("PRIVATE statement at %C is only allowed in the "
6105 "specification part of a module");
6106 return MATCH_ERROR;
6109 if (gfc_current_state () == COMP_DERIVED)
6111 if (gfc_match_eos () == MATCH_YES)
6113 *st = ST_PRIVATE;
6114 return MATCH_YES;
6117 gfc_syntax_error (ST_PRIVATE);
6118 return MATCH_ERROR;
6121 if (gfc_match_eos () == MATCH_YES)
6123 *st = ST_PRIVATE;
6124 return MATCH_YES;
6127 *st = ST_ATTR_DECL;
6128 return access_attr_decl (ST_PRIVATE);
6132 match
6133 gfc_match_public (gfc_statement *st)
6136 if (gfc_match ("public") != MATCH_YES)
6137 return MATCH_NO;
6139 if (gfc_current_state () != COMP_MODULE)
6141 gfc_error ("PUBLIC statement at %C is only allowed in the "
6142 "specification part of a module");
6143 return MATCH_ERROR;
6146 if (gfc_match_eos () == MATCH_YES)
6148 *st = ST_PUBLIC;
6149 return MATCH_YES;
6152 *st = ST_ATTR_DECL;
6153 return access_attr_decl (ST_PUBLIC);
6157 /* Workhorse for gfc_match_parameter. */
6159 static match
6160 do_parm (void)
6162 gfc_symbol *sym;
6163 gfc_expr *init;
6164 match m;
6166 m = gfc_match_symbol (&sym, 0);
6167 if (m == MATCH_NO)
6168 gfc_error ("Expected variable name at %C in PARAMETER statement");
6170 if (m != MATCH_YES)
6171 return m;
6173 if (gfc_match_char ('=') == MATCH_NO)
6175 gfc_error ("Expected = sign in PARAMETER statement at %C");
6176 return MATCH_ERROR;
6179 m = gfc_match_init_expr (&init);
6180 if (m == MATCH_NO)
6181 gfc_error ("Expected expression at %C in PARAMETER statement");
6182 if (m != MATCH_YES)
6183 return m;
6185 if (sym->ts.type == BT_UNKNOWN
6186 && gfc_set_default_type (sym, 1, NULL) == FAILURE)
6188 m = MATCH_ERROR;
6189 goto cleanup;
6192 if (gfc_check_assign_symbol (sym, init) == FAILURE
6193 || gfc_add_flavor (&sym->attr, FL_PARAMETER, sym->name, NULL) == FAILURE)
6195 m = MATCH_ERROR;
6196 goto cleanup;
6199 if (sym->value)
6201 gfc_error ("Initializing already initialized variable at %C");
6202 m = MATCH_ERROR;
6203 goto cleanup;
6206 if (sym->ts.type == BT_CHARACTER
6207 && sym->ts.cl != NULL
6208 && sym->ts.cl->length != NULL
6209 && sym->ts.cl->length->expr_type == EXPR_CONSTANT
6210 && init->expr_type == EXPR_CONSTANT
6211 && init->ts.type == BT_CHARACTER)
6212 gfc_set_constant_character_len (
6213 mpz_get_si (sym->ts.cl->length->value.integer), init, -1);
6214 else if (sym->ts.type == BT_CHARACTER && sym->ts.cl != NULL
6215 && sym->ts.cl->length == NULL)
6217 int clen;
6218 if (init->expr_type == EXPR_CONSTANT)
6220 clen = init->value.character.length;
6221 sym->ts.cl->length = gfc_int_expr (clen);
6223 else if (init->expr_type == EXPR_ARRAY)
6225 gfc_expr *p = init->value.constructor->expr;
6226 clen = p->value.character.length;
6227 sym->ts.cl->length = gfc_int_expr (clen);
6229 else if (init->ts.cl && init->ts.cl->length)
6230 sym->ts.cl->length = gfc_copy_expr (sym->value->ts.cl->length);
6233 sym->value = init;
6234 return MATCH_YES;
6236 cleanup:
6237 gfc_free_expr (init);
6238 return m;
6242 /* Match a parameter statement, with the weird syntax that these have. */
6244 match
6245 gfc_match_parameter (void)
6247 match m;
6249 if (gfc_match_char ('(') == MATCH_NO)
6250 return MATCH_NO;
6252 for (;;)
6254 m = do_parm ();
6255 if (m != MATCH_YES)
6256 break;
6258 if (gfc_match (" )%t") == MATCH_YES)
6259 break;
6261 if (gfc_match_char (',') != MATCH_YES)
6263 gfc_error ("Unexpected characters in PARAMETER statement at %C");
6264 m = MATCH_ERROR;
6265 break;
6269 return m;
6273 /* Save statements have a special syntax. */
6275 match
6276 gfc_match_save (void)
6278 char n[GFC_MAX_SYMBOL_LEN+1];
6279 gfc_common_head *c;
6280 gfc_symbol *sym;
6281 match m;
6283 if (gfc_match_eos () == MATCH_YES)
6285 if (gfc_current_ns->seen_save)
6287 if (gfc_notify_std (GFC_STD_LEGACY, "Blanket SAVE statement at %C "
6288 "follows previous SAVE statement")
6289 == FAILURE)
6290 return MATCH_ERROR;
6293 gfc_current_ns->save_all = gfc_current_ns->seen_save = 1;
6294 return MATCH_YES;
6297 if (gfc_current_ns->save_all)
6299 if (gfc_notify_std (GFC_STD_LEGACY, "SAVE statement at %C follows "
6300 "blanket SAVE statement")
6301 == FAILURE)
6302 return MATCH_ERROR;
6305 gfc_match (" ::");
6307 for (;;)
6309 m = gfc_match_symbol (&sym, 0);
6310 switch (m)
6312 case MATCH_YES:
6313 if (gfc_add_save (&sym->attr, sym->name, &gfc_current_locus)
6314 == FAILURE)
6315 return MATCH_ERROR;
6316 goto next_item;
6318 case MATCH_NO:
6319 break;
6321 case MATCH_ERROR:
6322 return MATCH_ERROR;
6325 m = gfc_match (" / %n /", &n);
6326 if (m == MATCH_ERROR)
6327 return MATCH_ERROR;
6328 if (m == MATCH_NO)
6329 goto syntax;
6331 c = gfc_get_common (n, 0);
6332 c->saved = 1;
6334 gfc_current_ns->seen_save = 1;
6336 next_item:
6337 if (gfc_match_eos () == MATCH_YES)
6338 break;
6339 if (gfc_match_char (',') != MATCH_YES)
6340 goto syntax;
6343 return MATCH_YES;
6345 syntax:
6346 gfc_error ("Syntax error in SAVE statement at %C");
6347 return MATCH_ERROR;
6351 match
6352 gfc_match_value (void)
6354 gfc_symbol *sym;
6355 match m;
6357 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: VALUE statement at %C")
6358 == FAILURE)
6359 return MATCH_ERROR;
6361 if (gfc_match (" ::") == MATCH_NO && gfc_match_space () == MATCH_NO)
6363 return MATCH_ERROR;
6366 if (gfc_match_eos () == MATCH_YES)
6367 goto syntax;
6369 for(;;)
6371 m = gfc_match_symbol (&sym, 0);
6372 switch (m)
6374 case MATCH_YES:
6375 if (gfc_add_value (&sym->attr, sym->name, &gfc_current_locus)
6376 == FAILURE)
6377 return MATCH_ERROR;
6378 goto next_item;
6380 case MATCH_NO:
6381 break;
6383 case MATCH_ERROR:
6384 return MATCH_ERROR;
6387 next_item:
6388 if (gfc_match_eos () == MATCH_YES)
6389 break;
6390 if (gfc_match_char (',') != MATCH_YES)
6391 goto syntax;
6394 return MATCH_YES;
6396 syntax:
6397 gfc_error ("Syntax error in VALUE statement at %C");
6398 return MATCH_ERROR;
6402 match
6403 gfc_match_volatile (void)
6405 gfc_symbol *sym;
6406 match m;
6408 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: VOLATILE statement at %C")
6409 == FAILURE)
6410 return MATCH_ERROR;
6412 if (gfc_match (" ::") == MATCH_NO && gfc_match_space () == MATCH_NO)
6414 return MATCH_ERROR;
6417 if (gfc_match_eos () == MATCH_YES)
6418 goto syntax;
6420 for(;;)
6422 /* VOLATILE is special because it can be added to host-associated
6423 symbols locally. */
6424 m = gfc_match_symbol (&sym, 1);
6425 switch (m)
6427 case MATCH_YES:
6428 if (gfc_add_volatile (&sym->attr, sym->name, &gfc_current_locus)
6429 == FAILURE)
6430 return MATCH_ERROR;
6431 goto next_item;
6433 case MATCH_NO:
6434 break;
6436 case MATCH_ERROR:
6437 return MATCH_ERROR;
6440 next_item:
6441 if (gfc_match_eos () == MATCH_YES)
6442 break;
6443 if (gfc_match_char (',') != MATCH_YES)
6444 goto syntax;
6447 return MATCH_YES;
6449 syntax:
6450 gfc_error ("Syntax error in VOLATILE statement at %C");
6451 return MATCH_ERROR;
6455 /* Match a module procedure statement. Note that we have to modify
6456 symbols in the parent's namespace because the current one was there
6457 to receive symbols that are in an interface's formal argument list. */
6459 match
6460 gfc_match_modproc (void)
6462 char name[GFC_MAX_SYMBOL_LEN + 1];
6463 gfc_symbol *sym;
6464 match m;
6465 gfc_namespace *module_ns;
6466 gfc_interface *old_interface_head, *interface;
6468 if (gfc_state_stack->state != COMP_INTERFACE
6469 || gfc_state_stack->previous == NULL
6470 || current_interface.type == INTERFACE_NAMELESS
6471 || current_interface.type == INTERFACE_ABSTRACT)
6473 gfc_error ("MODULE PROCEDURE at %C must be in a generic module "
6474 "interface");
6475 return MATCH_ERROR;
6478 module_ns = gfc_current_ns->parent;
6479 for (; module_ns; module_ns = module_ns->parent)
6480 if (module_ns->proc_name->attr.flavor == FL_MODULE)
6481 break;
6483 if (module_ns == NULL)
6484 return MATCH_ERROR;
6486 /* Store the current state of the interface. We will need it if we
6487 end up with a syntax error and need to recover. */
6488 old_interface_head = gfc_current_interface_head ();
6490 for (;;)
6492 bool last = false;
6494 m = gfc_match_name (name);
6495 if (m == MATCH_NO)
6496 goto syntax;
6497 if (m != MATCH_YES)
6498 return MATCH_ERROR;
6500 /* Check for syntax error before starting to add symbols to the
6501 current namespace. */
6502 if (gfc_match_eos () == MATCH_YES)
6503 last = true;
6504 if (!last && gfc_match_char (',') != MATCH_YES)
6505 goto syntax;
6507 /* Now we're sure the syntax is valid, we process this item
6508 further. */
6509 if (gfc_get_symbol (name, module_ns, &sym))
6510 return MATCH_ERROR;
6512 if (sym->attr.proc != PROC_MODULE
6513 && gfc_add_procedure (&sym->attr, PROC_MODULE,
6514 sym->name, NULL) == FAILURE)
6515 return MATCH_ERROR;
6517 if (gfc_add_interface (sym) == FAILURE)
6518 return MATCH_ERROR;
6520 sym->attr.mod_proc = 1;
6522 if (last)
6523 break;
6526 return MATCH_YES;
6528 syntax:
6529 /* Restore the previous state of the interface. */
6530 interface = gfc_current_interface_head ();
6531 gfc_set_current_interface_head (old_interface_head);
6533 /* Free the new interfaces. */
6534 while (interface != old_interface_head)
6536 gfc_interface *i = interface->next;
6537 gfc_free (interface);
6538 interface = i;
6541 /* And issue a syntax error. */
6542 gfc_syntax_error (ST_MODULE_PROC);
6543 return MATCH_ERROR;
6547 /* Check a derived type that is being extended. */
6548 static gfc_symbol*
6549 check_extended_derived_type (char *name)
6551 gfc_symbol *extended;
6553 if (gfc_find_symbol (name, gfc_current_ns, 1, &extended))
6555 gfc_error ("Ambiguous symbol in TYPE definition at %C");
6556 return NULL;
6559 if (!extended)
6561 gfc_error ("No such symbol in TYPE definition at %C");
6562 return NULL;
6565 if (extended->attr.flavor != FL_DERIVED)
6567 gfc_error ("'%s' in EXTENDS expression at %C is not a "
6568 "derived type", name);
6569 return NULL;
6572 if (extended->attr.is_bind_c)
6574 gfc_error ("'%s' cannot be extended at %C because it "
6575 "is BIND(C)", extended->name);
6576 return NULL;
6579 if (extended->attr.sequence)
6581 gfc_error ("'%s' cannot be extended at %C because it "
6582 "is a SEQUENCE type", extended->name);
6583 return NULL;
6586 return extended;
6590 /* Match the optional attribute specifiers for a type declaration.
6591 Return MATCH_ERROR if an error is encountered in one of the handled
6592 attributes (public, private, bind(c)), MATCH_NO if what's found is
6593 not a handled attribute, and MATCH_YES otherwise. TODO: More error
6594 checking on attribute conflicts needs to be done. */
6596 match
6597 gfc_get_type_attr_spec (symbol_attribute *attr, char *name)
6599 /* See if the derived type is marked as private. */
6600 if (gfc_match (" , private") == MATCH_YES)
6602 if (gfc_current_state () != COMP_MODULE)
6604 gfc_error ("Derived type at %C can only be PRIVATE in the "
6605 "specification part of a module");
6606 return MATCH_ERROR;
6609 if (gfc_add_access (attr, ACCESS_PRIVATE, NULL, NULL) == FAILURE)
6610 return MATCH_ERROR;
6612 else if (gfc_match (" , public") == MATCH_YES)
6614 if (gfc_current_state () != COMP_MODULE)
6616 gfc_error ("Derived type at %C can only be PUBLIC in the "
6617 "specification part of a module");
6618 return MATCH_ERROR;
6621 if (gfc_add_access (attr, ACCESS_PUBLIC, NULL, NULL) == FAILURE)
6622 return MATCH_ERROR;
6624 else if (gfc_match (" , bind ( c )") == MATCH_YES)
6626 /* If the type is defined to be bind(c) it then needs to make
6627 sure that all fields are interoperable. This will
6628 need to be a semantic check on the finished derived type.
6629 See 15.2.3 (lines 9-12) of F2003 draft. */
6630 if (gfc_add_is_bind_c (attr, NULL, &gfc_current_locus, 0) != SUCCESS)
6631 return MATCH_ERROR;
6633 /* TODO: attr conflicts need to be checked, probably in symbol.c. */
6635 else if (gfc_match (" , abstract") == MATCH_YES)
6637 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: ABSTRACT type at %C")
6638 == FAILURE)
6639 return MATCH_ERROR;
6641 if (gfc_add_abstract (attr, &gfc_current_locus) == FAILURE)
6642 return MATCH_ERROR;
6644 else if (name && gfc_match(" , extends ( %n )", name) == MATCH_YES)
6646 if (gfc_add_extension (attr, &gfc_current_locus) == FAILURE)
6647 return MATCH_ERROR;
6649 else
6650 return MATCH_NO;
6652 /* If we get here, something matched. */
6653 return MATCH_YES;
6657 /* Match the beginning of a derived type declaration. If a type name
6658 was the result of a function, then it is possible to have a symbol
6659 already to be known as a derived type yet have no components. */
6661 match
6662 gfc_match_derived_decl (void)
6664 char name[GFC_MAX_SYMBOL_LEN + 1];
6665 char parent[GFC_MAX_SYMBOL_LEN + 1];
6666 symbol_attribute attr;
6667 gfc_symbol *sym;
6668 gfc_symbol *extended;
6669 match m;
6670 match is_type_attr_spec = MATCH_NO;
6671 bool seen_attr = false;
6673 if (gfc_current_state () == COMP_DERIVED)
6674 return MATCH_NO;
6676 name[0] = '\0';
6677 parent[0] = '\0';
6678 gfc_clear_attr (&attr);
6679 extended = NULL;
6683 is_type_attr_spec = gfc_get_type_attr_spec (&attr, parent);
6684 if (is_type_attr_spec == MATCH_ERROR)
6685 return MATCH_ERROR;
6686 if (is_type_attr_spec == MATCH_YES)
6687 seen_attr = true;
6688 } while (is_type_attr_spec == MATCH_YES);
6690 /* Deal with derived type extensions. The extension attribute has
6691 been added to 'attr' but now the parent type must be found and
6692 checked. */
6693 if (parent[0])
6694 extended = check_extended_derived_type (parent);
6696 if (parent[0] && !extended)
6697 return MATCH_ERROR;
6699 if (gfc_match (" ::") != MATCH_YES && seen_attr)
6701 gfc_error ("Expected :: in TYPE definition at %C");
6702 return MATCH_ERROR;
6705 m = gfc_match (" %n%t", name);
6706 if (m != MATCH_YES)
6707 return m;
6709 /* Make sure the name is not the name of an intrinsic type. */
6710 if (gfc_is_intrinsic_typename (name))
6712 gfc_error ("Type name '%s' at %C cannot be the same as an intrinsic "
6713 "type", name);
6714 return MATCH_ERROR;
6717 if (gfc_get_symbol (name, NULL, &sym))
6718 return MATCH_ERROR;
6720 if (sym->ts.type != BT_UNKNOWN)
6722 gfc_error ("Derived type name '%s' at %C already has a basic type "
6723 "of %s", sym->name, gfc_typename (&sym->ts));
6724 return MATCH_ERROR;
6727 /* The symbol may already have the derived attribute without the
6728 components. The ways this can happen is via a function
6729 definition, an INTRINSIC statement or a subtype in another
6730 derived type that is a pointer. The first part of the AND clause
6731 is true if the symbol is not the return value of a function. */
6732 if (sym->attr.flavor != FL_DERIVED
6733 && gfc_add_flavor (&sym->attr, FL_DERIVED, sym->name, NULL) == FAILURE)
6734 return MATCH_ERROR;
6736 if (sym->components != NULL || sym->attr.zero_comp)
6738 gfc_error ("Derived type definition of '%s' at %C has already been "
6739 "defined", sym->name);
6740 return MATCH_ERROR;
6743 if (attr.access != ACCESS_UNKNOWN
6744 && gfc_add_access (&sym->attr, attr.access, sym->name, NULL) == FAILURE)
6745 return MATCH_ERROR;
6747 /* See if the derived type was labeled as bind(c). */
6748 if (attr.is_bind_c != 0)
6749 sym->attr.is_bind_c = attr.is_bind_c;
6751 /* Construct the f2k_derived namespace if it is not yet there. */
6752 if (!sym->f2k_derived)
6753 sym->f2k_derived = gfc_get_namespace (NULL, 0);
6755 if (extended && !sym->components)
6757 gfc_component *p;
6758 gfc_symtree *st;
6760 /* Add the extended derived type as the first component. */
6761 gfc_add_component (sym, parent, &p);
6762 sym->attr.extension = attr.extension;
6763 extended->refs++;
6764 gfc_set_sym_referenced (extended);
6766 p->ts.type = BT_DERIVED;
6767 p->ts.derived = extended;
6768 p->initializer = gfc_default_initializer (&p->ts);
6770 /* Provide the links between the extended type and its extension. */
6771 if (!extended->f2k_derived)
6772 extended->f2k_derived = gfc_get_namespace (NULL, 0);
6773 st = gfc_new_symtree (&extended->f2k_derived->sym_root, sym->name);
6774 st->n.sym = sym;
6777 /* Take over the ABSTRACT attribute. */
6778 sym->attr.abstract = attr.abstract;
6780 gfc_new_block = sym;
6782 return MATCH_YES;
6786 /* Cray Pointees can be declared as:
6787 pointer (ipt, a (n,m,...,*))
6788 By default, this is treated as an AS_ASSUMED_SIZE array. We'll
6789 cheat and set a constant bound of 1 for the last dimension, if this
6790 is the case. Since there is no bounds-checking for Cray Pointees,
6791 this will be okay. */
6793 match
6794 gfc_mod_pointee_as (gfc_array_spec *as)
6796 as->cray_pointee = true; /* This will be useful to know later. */
6797 if (as->type == AS_ASSUMED_SIZE)
6799 as->type = AS_EXPLICIT;
6800 as->upper[as->rank - 1] = gfc_int_expr (1);
6801 as->cp_was_assumed = true;
6803 else if (as->type == AS_ASSUMED_SHAPE)
6805 gfc_error ("Cray Pointee at %C cannot be assumed shape array");
6806 return MATCH_ERROR;
6808 return MATCH_YES;
6812 /* Match the enum definition statement, here we are trying to match
6813 the first line of enum definition statement.
6814 Returns MATCH_YES if match is found. */
6816 match
6817 gfc_match_enum (void)
6819 match m;
6821 m = gfc_match_eos ();
6822 if (m != MATCH_YES)
6823 return m;
6825 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: ENUM and ENUMERATOR at %C")
6826 == FAILURE)
6827 return MATCH_ERROR;
6829 return MATCH_YES;
6833 /* Returns an initializer whose value is one higher than the value of the
6834 LAST_INITIALIZER argument. If the argument is NULL, the
6835 initializers value will be set to zero. The initializer's kind
6836 will be set to gfc_c_int_kind.
6838 If -fshort-enums is given, the appropriate kind will be selected
6839 later after all enumerators have been parsed. A warning is issued
6840 here if an initializer exceeds gfc_c_int_kind. */
6842 static gfc_expr *
6843 enum_initializer (gfc_expr *last_initializer, locus where)
6845 gfc_expr *result;
6847 result = gfc_get_expr ();
6848 result->expr_type = EXPR_CONSTANT;
6849 result->ts.type = BT_INTEGER;
6850 result->ts.kind = gfc_c_int_kind;
6851 result->where = where;
6853 mpz_init (result->value.integer);
6855 if (last_initializer != NULL)
6857 mpz_add_ui (result->value.integer, last_initializer->value.integer, 1);
6858 result->where = last_initializer->where;
6860 if (gfc_check_integer_range (result->value.integer,
6861 gfc_c_int_kind) != ARITH_OK)
6863 gfc_error ("Enumerator exceeds the C integer type at %C");
6864 return NULL;
6867 else
6869 /* Control comes here, if it's the very first enumerator and no
6870 initializer has been given. It will be initialized to zero. */
6871 mpz_set_si (result->value.integer, 0);
6874 return result;
6878 /* Match a variable name with an optional initializer. When this
6879 subroutine is called, a variable is expected to be parsed next.
6880 Depending on what is happening at the moment, updates either the
6881 symbol table or the current interface. */
6883 static match
6884 enumerator_decl (void)
6886 char name[GFC_MAX_SYMBOL_LEN + 1];
6887 gfc_expr *initializer;
6888 gfc_array_spec *as = NULL;
6889 gfc_symbol *sym;
6890 locus var_locus;
6891 match m;
6892 gfc_try t;
6893 locus old_locus;
6895 initializer = NULL;
6896 old_locus = gfc_current_locus;
6898 /* When we get here, we've just matched a list of attributes and
6899 maybe a type and a double colon. The next thing we expect to see
6900 is the name of the symbol. */
6901 m = gfc_match_name (name);
6902 if (m != MATCH_YES)
6903 goto cleanup;
6905 var_locus = gfc_current_locus;
6907 /* OK, we've successfully matched the declaration. Now put the
6908 symbol in the current namespace. If we fail to create the symbol,
6909 bail out. */
6910 if (build_sym (name, NULL, &as, &var_locus) == FAILURE)
6912 m = MATCH_ERROR;
6913 goto cleanup;
6916 /* The double colon must be present in order to have initializers.
6917 Otherwise the statement is ambiguous with an assignment statement. */
6918 if (colon_seen)
6920 if (gfc_match_char ('=') == MATCH_YES)
6922 m = gfc_match_init_expr (&initializer);
6923 if (m == MATCH_NO)
6925 gfc_error ("Expected an initialization expression at %C");
6926 m = MATCH_ERROR;
6929 if (m != MATCH_YES)
6930 goto cleanup;
6934 /* If we do not have an initializer, the initialization value of the
6935 previous enumerator (stored in last_initializer) is incremented
6936 by 1 and is used to initialize the current enumerator. */
6937 if (initializer == NULL)
6938 initializer = enum_initializer (last_initializer, old_locus);
6940 if (initializer == NULL || initializer->ts.type != BT_INTEGER)
6942 gfc_error("ENUMERATOR %L not initialized with integer expression",
6943 &var_locus);
6944 m = MATCH_ERROR;
6945 gfc_free_enum_history ();
6946 goto cleanup;
6949 /* Store this current initializer, for the next enumerator variable
6950 to be parsed. add_init_expr_to_sym() zeros initializer, so we
6951 use last_initializer below. */
6952 last_initializer = initializer;
6953 t = add_init_expr_to_sym (name, &initializer, &var_locus);
6955 /* Maintain enumerator history. */
6956 gfc_find_symbol (name, NULL, 0, &sym);
6957 create_enum_history (sym, last_initializer);
6959 return (t == SUCCESS) ? MATCH_YES : MATCH_ERROR;
6961 cleanup:
6962 /* Free stuff up and return. */
6963 gfc_free_expr (initializer);
6965 return m;
6969 /* Match the enumerator definition statement. */
6971 match
6972 gfc_match_enumerator_def (void)
6974 match m;
6975 gfc_try t;
6977 gfc_clear_ts (&current_ts);
6979 m = gfc_match (" enumerator");
6980 if (m != MATCH_YES)
6981 return m;
6983 m = gfc_match (" :: ");
6984 if (m == MATCH_ERROR)
6985 return m;
6987 colon_seen = (m == MATCH_YES);
6989 if (gfc_current_state () != COMP_ENUM)
6991 gfc_error ("ENUM definition statement expected before %C");
6992 gfc_free_enum_history ();
6993 return MATCH_ERROR;
6996 (&current_ts)->type = BT_INTEGER;
6997 (&current_ts)->kind = gfc_c_int_kind;
6999 gfc_clear_attr (&current_attr);
7000 t = gfc_add_flavor (&current_attr, FL_PARAMETER, NULL, NULL);
7001 if (t == FAILURE)
7003 m = MATCH_ERROR;
7004 goto cleanup;
7007 for (;;)
7009 m = enumerator_decl ();
7010 if (m == MATCH_ERROR)
7011 goto cleanup;
7012 if (m == MATCH_NO)
7013 break;
7015 if (gfc_match_eos () == MATCH_YES)
7016 goto cleanup;
7017 if (gfc_match_char (',') != MATCH_YES)
7018 break;
7021 if (gfc_current_state () == COMP_ENUM)
7023 gfc_free_enum_history ();
7024 gfc_error ("Syntax error in ENUMERATOR definition at %C");
7025 m = MATCH_ERROR;
7028 cleanup:
7029 gfc_free_array_spec (current_as);
7030 current_as = NULL;
7031 return m;
7036 /* Match binding attributes. */
7038 static match
7039 match_binding_attributes (gfc_typebound_proc* ba, bool generic, bool ppc)
7041 bool found_passing = false;
7042 bool seen_ptr = false;
7043 match m;
7045 /* Intialize to defaults. Do so even before the MATCH_NO check so that in
7046 this case the defaults are in there. */
7047 ba->access = ACCESS_UNKNOWN;
7048 ba->pass_arg = NULL;
7049 ba->pass_arg_num = 0;
7050 ba->nopass = 0;
7051 ba->non_overridable = 0;
7052 ba->deferred = 0;
7054 /* If we find a comma, we believe there are binding attributes. */
7055 if (gfc_match_char (',') == MATCH_NO)
7057 ba->access = gfc_typebound_default_access;
7058 return MATCH_NO;
7063 /* Access specifier. */
7065 m = gfc_match (" public");
7066 if (m == MATCH_ERROR)
7067 goto error;
7068 if (m == MATCH_YES)
7070 if (ba->access != ACCESS_UNKNOWN)
7072 gfc_error ("Duplicate access-specifier at %C");
7073 goto error;
7076 ba->access = ACCESS_PUBLIC;
7077 continue;
7080 m = gfc_match (" private");
7081 if (m == MATCH_ERROR)
7082 goto error;
7083 if (m == MATCH_YES)
7085 if (ba->access != ACCESS_UNKNOWN)
7087 gfc_error ("Duplicate access-specifier at %C");
7088 goto error;
7091 ba->access = ACCESS_PRIVATE;
7092 continue;
7095 /* If inside GENERIC, the following is not allowed. */
7096 if (!generic)
7099 /* NOPASS flag. */
7100 m = gfc_match (" nopass");
7101 if (m == MATCH_ERROR)
7102 goto error;
7103 if (m == MATCH_YES)
7105 if (found_passing)
7107 gfc_error ("Binding attributes already specify passing,"
7108 " illegal NOPASS at %C");
7109 goto error;
7112 found_passing = true;
7113 ba->nopass = 1;
7114 continue;
7117 /* PASS possibly including argument. */
7118 m = gfc_match (" pass");
7119 if (m == MATCH_ERROR)
7120 goto error;
7121 if (m == MATCH_YES)
7123 char arg[GFC_MAX_SYMBOL_LEN + 1];
7125 if (found_passing)
7127 gfc_error ("Binding attributes already specify passing,"
7128 " illegal PASS at %C");
7129 goto error;
7132 m = gfc_match (" ( %n )", arg);
7133 if (m == MATCH_ERROR)
7134 goto error;
7135 if (m == MATCH_YES)
7136 ba->pass_arg = xstrdup (arg);
7137 gcc_assert ((m == MATCH_YES) == (ba->pass_arg != NULL));
7139 found_passing = true;
7140 ba->nopass = 0;
7141 continue;
7144 if (ppc)
7146 /* POINTER flag. */
7147 m = gfc_match (" pointer");
7148 if (m == MATCH_ERROR)
7149 goto error;
7150 if (m == MATCH_YES)
7152 if (seen_ptr)
7154 gfc_error ("Duplicate POINTER attribute at %C");
7155 goto error;
7158 seen_ptr = true;
7159 /*ba->ppc = 1;*/
7160 continue;
7163 else
7165 /* NON_OVERRIDABLE flag. */
7166 m = gfc_match (" non_overridable");
7167 if (m == MATCH_ERROR)
7168 goto error;
7169 if (m == MATCH_YES)
7171 if (ba->non_overridable)
7173 gfc_error ("Duplicate NON_OVERRIDABLE at %C");
7174 goto error;
7177 ba->non_overridable = 1;
7178 continue;
7181 /* DEFERRED flag. */
7182 m = gfc_match (" deferred");
7183 if (m == MATCH_ERROR)
7184 goto error;
7185 if (m == MATCH_YES)
7187 if (ba->deferred)
7189 gfc_error ("Duplicate DEFERRED at %C");
7190 goto error;
7193 ba->deferred = 1;
7194 continue;
7200 /* Nothing matching found. */
7201 if (generic)
7202 gfc_error ("Expected access-specifier at %C");
7203 else
7204 gfc_error ("Expected binding attribute at %C");
7205 goto error;
7207 while (gfc_match_char (',') == MATCH_YES);
7209 /* NON_OVERRIDABLE and DEFERRED exclude themselves. */
7210 if (ba->non_overridable && ba->deferred)
7212 gfc_error ("NON_OVERRIDABLE and DEFERRED can't both appear at %C");
7213 goto error;
7216 if (ba->access == ACCESS_UNKNOWN)
7217 ba->access = gfc_typebound_default_access;
7219 if (ppc && !seen_ptr)
7221 gfc_error ("POINTER attribute is required for procedure pointer component"
7222 " at %C");
7223 goto error;
7226 return MATCH_YES;
7228 error:
7229 gfc_free (ba->pass_arg);
7230 return MATCH_ERROR;
7234 /* Match a PROCEDURE specific binding inside a derived type. */
7236 static match
7237 match_procedure_in_type (void)
7239 char name[GFC_MAX_SYMBOL_LEN + 1];
7240 char target_buf[GFC_MAX_SYMBOL_LEN + 1];
7241 char* target = NULL;
7242 gfc_typebound_proc* tb;
7243 bool seen_colons;
7244 bool seen_attrs;
7245 match m;
7246 gfc_symtree* stree;
7247 gfc_namespace* ns;
7248 gfc_symbol* block;
7250 /* Check current state. */
7251 gcc_assert (gfc_state_stack->state == COMP_DERIVED_CONTAINS);
7252 block = gfc_state_stack->previous->sym;
7253 gcc_assert (block);
7255 /* Try to match PROCEDURE(interface). */
7256 if (gfc_match (" (") == MATCH_YES)
7258 m = gfc_match_name (target_buf);
7259 if (m == MATCH_ERROR)
7260 return m;
7261 if (m != MATCH_YES)
7263 gfc_error ("Interface-name expected after '(' at %C");
7264 return MATCH_ERROR;
7267 if (gfc_match (" )") != MATCH_YES)
7269 gfc_error ("')' expected at %C");
7270 return MATCH_ERROR;
7273 target = target_buf;
7276 /* Construct the data structure. */
7277 tb = gfc_get_typebound_proc ();
7278 tb->where = gfc_current_locus;
7279 tb->is_generic = 0;
7281 /* Match binding attributes. */
7282 m = match_binding_attributes (tb, false, false);
7283 if (m == MATCH_ERROR)
7284 return m;
7285 seen_attrs = (m == MATCH_YES);
7287 /* Check that attribute DEFERRED is given iff an interface is specified, which
7288 means target != NULL. */
7289 if (tb->deferred && !target)
7291 gfc_error ("Interface must be specified for DEFERRED binding at %C");
7292 return MATCH_ERROR;
7294 if (target && !tb->deferred)
7296 gfc_error ("PROCEDURE(interface) at %C should be declared DEFERRED");
7297 return MATCH_ERROR;
7300 /* Match the colons. */
7301 m = gfc_match (" ::");
7302 if (m == MATCH_ERROR)
7303 return m;
7304 seen_colons = (m == MATCH_YES);
7305 if (seen_attrs && !seen_colons)
7307 gfc_error ("Expected '::' after binding-attributes at %C");
7308 return MATCH_ERROR;
7311 /* Match the binding name. */
7312 m = gfc_match_name (name);
7313 if (m == MATCH_ERROR)
7314 return m;
7315 if (m == MATCH_NO)
7317 gfc_error ("Expected binding name at %C");
7318 return MATCH_ERROR;
7321 /* Try to match the '=> target', if it's there. */
7322 m = gfc_match (" =>");
7323 if (m == MATCH_ERROR)
7324 return m;
7325 if (m == MATCH_YES)
7327 if (tb->deferred)
7329 gfc_error ("'=> target' is invalid for DEFERRED binding at %C");
7330 return MATCH_ERROR;
7333 if (!seen_colons)
7335 gfc_error ("'::' needed in PROCEDURE binding with explicit target"
7336 " at %C");
7337 return MATCH_ERROR;
7340 m = gfc_match_name (target_buf);
7341 if (m == MATCH_ERROR)
7342 return m;
7343 if (m == MATCH_NO)
7345 gfc_error ("Expected binding target after '=>' at %C");
7346 return MATCH_ERROR;
7348 target = target_buf;
7351 /* Now we should have the end. */
7352 m = gfc_match_eos ();
7353 if (m == MATCH_ERROR)
7354 return m;
7355 if (m == MATCH_NO)
7357 gfc_error ("Junk after PROCEDURE declaration at %C");
7358 return MATCH_ERROR;
7361 /* If no target was found, it has the same name as the binding. */
7362 if (!target)
7363 target = name;
7365 /* Get the namespace to insert the symbols into. */
7366 ns = block->f2k_derived;
7367 gcc_assert (ns);
7369 /* If the binding is DEFERRED, check that the containing type is ABSTRACT. */
7370 if (tb->deferred && !block->attr.abstract)
7372 gfc_error ("Type '%s' containing DEFERRED binding at %C is not ABSTRACT",
7373 block->name);
7374 return MATCH_ERROR;
7377 /* See if we already have a binding with this name in the symtree which would
7378 be an error. If a GENERIC already targetted this binding, it may be
7379 already there but then typebound is still NULL. */
7380 stree = gfc_find_symtree (ns->tb_sym_root, name);
7381 if (stree && stree->n.tb)
7383 gfc_error ("There's already a procedure with binding name '%s' for the"
7384 " derived type '%s' at %C", name, block->name);
7385 return MATCH_ERROR;
7388 /* Insert it and set attributes. */
7390 if (!stree)
7392 stree = gfc_new_symtree (&ns->tb_sym_root, name);
7393 gcc_assert (stree);
7395 stree->n.tb = tb;
7397 if (gfc_get_sym_tree (target, gfc_current_ns, &tb->u.specific, false))
7398 return MATCH_ERROR;
7399 gfc_set_sym_referenced (tb->u.specific->n.sym);
7401 return MATCH_YES;
7405 /* Match a GENERIC procedure binding inside a derived type. */
7407 match
7408 gfc_match_generic (void)
7410 char name[GFC_MAX_SYMBOL_LEN + 1];
7411 gfc_symbol* block;
7412 gfc_typebound_proc tbattr; /* Used for match_binding_attributes. */
7413 gfc_typebound_proc* tb;
7414 gfc_symtree* st;
7415 gfc_namespace* ns;
7416 match m;
7418 /* Check current state. */
7419 if (gfc_current_state () == COMP_DERIVED)
7421 gfc_error ("GENERIC at %C must be inside a derived-type CONTAINS");
7422 return MATCH_ERROR;
7424 if (gfc_current_state () != COMP_DERIVED_CONTAINS)
7425 return MATCH_NO;
7426 block = gfc_state_stack->previous->sym;
7427 ns = block->f2k_derived;
7428 gcc_assert (block && ns);
7430 /* See if we get an access-specifier. */
7431 m = match_binding_attributes (&tbattr, true, false);
7432 if (m == MATCH_ERROR)
7433 goto error;
7435 /* Now the colons, those are required. */
7436 if (gfc_match (" ::") != MATCH_YES)
7438 gfc_error ("Expected '::' at %C");
7439 goto error;
7442 /* The binding name and =>. */
7443 m = gfc_match (" %n =>", name);
7444 if (m == MATCH_ERROR)
7445 return MATCH_ERROR;
7446 if (m == MATCH_NO)
7448 gfc_error ("Expected generic name at %C");
7449 goto error;
7452 /* If there's already something with this name, check that it is another
7453 GENERIC and then extend that rather than build a new node. */
7454 st = gfc_find_symtree (ns->tb_sym_root, name);
7455 if (st)
7457 gcc_assert (st->n.tb);
7458 tb = st->n.tb;
7460 if (!tb->is_generic)
7462 gfc_error ("There's already a non-generic procedure with binding name"
7463 " '%s' for the derived type '%s' at %C",
7464 name, block->name);
7465 goto error;
7468 if (tb->access != tbattr.access)
7470 gfc_error ("Binding at %C must have the same access as already"
7471 " defined binding '%s'", name);
7472 goto error;
7475 else
7477 st = gfc_new_symtree (&ns->tb_sym_root, name);
7478 gcc_assert (st);
7480 st->n.tb = tb = gfc_get_typebound_proc ();
7481 tb->where = gfc_current_locus;
7482 tb->access = tbattr.access;
7483 tb->is_generic = 1;
7484 tb->u.generic = NULL;
7487 /* Now, match all following names as specific targets. */
7490 gfc_symtree* target_st;
7491 gfc_tbp_generic* target;
7493 m = gfc_match_name (name);
7494 if (m == MATCH_ERROR)
7495 goto error;
7496 if (m == MATCH_NO)
7498 gfc_error ("Expected specific binding name at %C");
7499 goto error;
7502 target_st = gfc_get_tbp_symtree (&ns->tb_sym_root, name);
7504 /* See if this is a duplicate specification. */
7505 for (target = tb->u.generic; target; target = target->next)
7506 if (target_st == target->specific_st)
7508 gfc_error ("'%s' already defined as specific binding for the"
7509 " generic '%s' at %C", name, st->name);
7510 goto error;
7513 target = gfc_get_tbp_generic ();
7514 target->specific_st = target_st;
7515 target->specific = NULL;
7516 target->next = tb->u.generic;
7517 tb->u.generic = target;
7519 while (gfc_match (" ,") == MATCH_YES);
7521 /* Here should be the end. */
7522 if (gfc_match_eos () != MATCH_YES)
7524 gfc_error ("Junk after GENERIC binding at %C");
7525 goto error;
7528 return MATCH_YES;
7530 error:
7531 return MATCH_ERROR;
7535 /* Match a FINAL declaration inside a derived type. */
7537 match
7538 gfc_match_final_decl (void)
7540 char name[GFC_MAX_SYMBOL_LEN + 1];
7541 gfc_symbol* sym;
7542 match m;
7543 gfc_namespace* module_ns;
7544 bool first, last;
7545 gfc_symbol* block;
7547 if (gfc_state_stack->state != COMP_DERIVED_CONTAINS)
7549 gfc_error ("FINAL declaration at %C must be inside a derived type "
7550 "CONTAINS section");
7551 return MATCH_ERROR;
7554 block = gfc_state_stack->previous->sym;
7555 gcc_assert (block);
7557 if (!gfc_state_stack->previous || !gfc_state_stack->previous->previous
7558 || gfc_state_stack->previous->previous->state != COMP_MODULE)
7560 gfc_error ("Derived type declaration with FINAL at %C must be in the"
7561 " specification part of a MODULE");
7562 return MATCH_ERROR;
7565 module_ns = gfc_current_ns;
7566 gcc_assert (module_ns);
7567 gcc_assert (module_ns->proc_name->attr.flavor == FL_MODULE);
7569 /* Match optional ::, don't care about MATCH_YES or MATCH_NO. */
7570 if (gfc_match (" ::") == MATCH_ERROR)
7571 return MATCH_ERROR;
7573 /* Match the sequence of procedure names. */
7574 first = true;
7575 last = false;
7578 gfc_finalizer* f;
7580 if (first && gfc_match_eos () == MATCH_YES)
7582 gfc_error ("Empty FINAL at %C");
7583 return MATCH_ERROR;
7586 m = gfc_match_name (name);
7587 if (m == MATCH_NO)
7589 gfc_error ("Expected module procedure name at %C");
7590 return MATCH_ERROR;
7592 else if (m != MATCH_YES)
7593 return MATCH_ERROR;
7595 if (gfc_match_eos () == MATCH_YES)
7596 last = true;
7597 if (!last && gfc_match_char (',') != MATCH_YES)
7599 gfc_error ("Expected ',' at %C");
7600 return MATCH_ERROR;
7603 if (gfc_get_symbol (name, module_ns, &sym))
7605 gfc_error ("Unknown procedure name \"%s\" at %C", name);
7606 return MATCH_ERROR;
7609 /* Mark the symbol as module procedure. */
7610 if (sym->attr.proc != PROC_MODULE
7611 && gfc_add_procedure (&sym->attr, PROC_MODULE,
7612 sym->name, NULL) == FAILURE)
7613 return MATCH_ERROR;
7615 /* Check if we already have this symbol in the list, this is an error. */
7616 for (f = block->f2k_derived->finalizers; f; f = f->next)
7617 if (f->proc_sym == sym)
7619 gfc_error ("'%s' at %C is already defined as FINAL procedure!",
7620 name);
7621 return MATCH_ERROR;
7624 /* Add this symbol to the list of finalizers. */
7625 gcc_assert (block->f2k_derived);
7626 ++sym->refs;
7627 f = XCNEW (gfc_finalizer);
7628 f->proc_sym = sym;
7629 f->proc_tree = NULL;
7630 f->where = gfc_current_locus;
7631 f->next = block->f2k_derived->finalizers;
7632 block->f2k_derived->finalizers = f;
7634 first = false;
7636 while (!last);
7638 return MATCH_YES;
7642 const ext_attr_t ext_attr_list[] = {
7643 { "dllimport", EXT_ATTR_DLLIMPORT, "dllimport" },
7644 { "dllexport", EXT_ATTR_DLLEXPORT, "dllexport" },
7645 { "cdecl", EXT_ATTR_CDECL, "cdecl" },
7646 { "stdcall", EXT_ATTR_STDCALL, "stdcall" },
7647 { "fastcall", EXT_ATTR_FASTCALL, "fastcall" },
7648 { NULL, EXT_ATTR_LAST, NULL }
7651 /* Match a !GCC$ ATTRIBUTES statement of the form:
7652 !GCC$ ATTRIBUTES attribute-list :: var-name [, var-name] ...
7653 When we come here, we have already matched the !GCC$ ATTRIBUTES string.
7655 TODO: We should support all GCC attributes using the same syntax for
7656 the attribute list, i.e. the list in C
7657 __attributes(( attribute-list ))
7658 matches then
7659 !GCC$ ATTRIBUTES attribute-list ::
7660 Cf. c-parser.c's c_parser_attributes; the data can then directly be
7661 saved into a TREE.
7663 As there is absolutely no risk of confusion, we should never return
7664 MATCH_NO. */
7665 match
7666 gfc_match_gcc_attributes (void)
7668 symbol_attribute attr;
7669 char name[GFC_MAX_SYMBOL_LEN + 1];
7670 unsigned id;
7671 gfc_symbol *sym;
7672 match m;
7674 gfc_clear_attr (&attr);
7675 for(;;)
7677 char ch;
7679 if (gfc_match_name (name) != MATCH_YES)
7680 return MATCH_ERROR;
7682 for (id = 0; id < EXT_ATTR_LAST; id++)
7683 if (strcmp (name, ext_attr_list[id].name) == 0)
7684 break;
7686 if (id == EXT_ATTR_LAST)
7688 gfc_error ("Unknown attribute in !GCC$ ATTRIBUTES statement at %C");
7689 return MATCH_ERROR;
7692 if (gfc_add_ext_attribute (&attr, id, &gfc_current_locus)
7693 == FAILURE)
7694 return MATCH_ERROR;
7696 gfc_gobble_whitespace ();
7697 ch = gfc_next_ascii_char ();
7698 if (ch == ':')
7700 /* This is the successful exit condition for the loop. */
7701 if (gfc_next_ascii_char () == ':')
7702 break;
7705 if (ch == ',')
7706 continue;
7708 goto syntax;
7711 if (gfc_match_eos () == MATCH_YES)
7712 goto syntax;
7714 for(;;)
7716 m = gfc_match_name (name);
7717 if (m != MATCH_YES)
7718 return m;
7720 if (find_special (name, &sym, true))
7721 return MATCH_ERROR;
7723 sym->attr.ext_attr |= attr.ext_attr;
7725 if (gfc_match_eos () == MATCH_YES)
7726 break;
7728 if (gfc_match_char (',') != MATCH_YES)
7729 goto syntax;
7732 return MATCH_YES;
7734 syntax:
7735 gfc_error ("Syntax error in !GCC$ ATTRIBUTES statement at %C");
7736 return MATCH_ERROR;