* target.h (struct gcc_target): Add frame_pointer_required field.
[official-gcc.git] / gcc / fortran / decl.c
blobc3760a81c0b27dda472b5e125409c1783314c310
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 locus old_loc, entry_loc;
4160 old_loc = entry_loc = gfc_current_locus;
4162 gfc_clear_ts (&current_ts);
4164 if (gfc_match (" (") != MATCH_YES)
4166 gfc_current_locus = entry_loc;
4167 return MATCH_NO;
4170 /* Get the type spec. for the procedure interface. */
4171 old_loc = gfc_current_locus;
4172 m = gfc_match_type_spec (&current_ts, 0);
4173 gfc_gobble_whitespace ();
4174 if (m == MATCH_YES || (m == MATCH_NO && gfc_peek_ascii_char () == ')'))
4175 goto got_ts;
4177 if (m == MATCH_ERROR)
4178 return m;
4180 gfc_current_locus = old_loc;
4182 /* Get the name of the procedure or abstract interface
4183 to inherit the interface from. */
4184 m = gfc_match_symbol (proc_if, 1);
4185 if (m != MATCH_YES)
4186 return m;
4188 /* Various interface checks. */
4189 if (*proc_if)
4191 (*proc_if)->refs++;
4192 /* Resolve interface if possible. That way, attr.procedure is only set
4193 if it is declared by a later procedure-declaration-stmt, which is
4194 invalid per C1212. */
4195 while ((*proc_if)->ts.interface)
4196 *proc_if = (*proc_if)->ts.interface;
4198 if ((*proc_if)->generic)
4200 gfc_error ("Interface '%s' at %C may not be generic",
4201 (*proc_if)->name);
4202 return MATCH_ERROR;
4204 if ((*proc_if)->attr.proc == PROC_ST_FUNCTION)
4206 gfc_error ("Interface '%s' at %C may not be a statement function",
4207 (*proc_if)->name);
4208 return MATCH_ERROR;
4210 /* Handle intrinsic procedures. */
4211 if (!((*proc_if)->attr.external || (*proc_if)->attr.use_assoc
4212 || (*proc_if)->attr.if_source == IFSRC_IFBODY)
4213 && (gfc_is_intrinsic ((*proc_if), 0, gfc_current_locus)
4214 || gfc_is_intrinsic ((*proc_if), 1, gfc_current_locus)))
4215 (*proc_if)->attr.intrinsic = 1;
4216 if ((*proc_if)->attr.intrinsic
4217 && !gfc_intrinsic_actual_ok ((*proc_if)->name, 0))
4219 gfc_error ("Intrinsic procedure '%s' not allowed "
4220 "in PROCEDURE statement at %C", (*proc_if)->name);
4221 return MATCH_ERROR;
4225 got_ts:
4226 if (gfc_match (" )") != MATCH_YES)
4228 gfc_current_locus = entry_loc;
4229 return MATCH_NO;
4232 return MATCH_YES;
4236 /* Match a PROCEDURE declaration (R1211). */
4238 static match
4239 match_procedure_decl (void)
4241 match m;
4242 gfc_symbol *sym, *proc_if = NULL;
4243 int num;
4244 gfc_expr *initializer = NULL;
4246 /* Parse interface (with brackets). */
4247 m = match_procedure_interface (&proc_if);
4248 if (m != MATCH_YES)
4249 return m;
4251 /* Parse attributes (with colons). */
4252 m = match_attr_spec();
4253 if (m == MATCH_ERROR)
4254 return MATCH_ERROR;
4256 /* Get procedure symbols. */
4257 for(num=1;;num++)
4259 m = gfc_match_symbol (&sym, 0);
4260 if (m == MATCH_NO)
4261 goto syntax;
4262 else if (m == MATCH_ERROR)
4263 return m;
4265 /* Add current_attr to the symbol attributes. */
4266 if (gfc_copy_attr (&sym->attr, &current_attr, NULL) == FAILURE)
4267 return MATCH_ERROR;
4269 if (sym->attr.is_bind_c)
4271 /* Check for C1218. */
4272 if (!proc_if || !proc_if->attr.is_bind_c)
4274 gfc_error ("BIND(C) attribute at %C requires "
4275 "an interface with BIND(C)");
4276 return MATCH_ERROR;
4278 /* Check for C1217. */
4279 if (has_name_equals && sym->attr.pointer)
4281 gfc_error ("BIND(C) procedure with NAME may not have "
4282 "POINTER attribute at %C");
4283 return MATCH_ERROR;
4285 if (has_name_equals && sym->attr.dummy)
4287 gfc_error ("Dummy procedure at %C may not have "
4288 "BIND(C) attribute with NAME");
4289 return MATCH_ERROR;
4291 /* Set binding label for BIND(C). */
4292 if (set_binding_label (sym->binding_label, sym->name, num) != SUCCESS)
4293 return MATCH_ERROR;
4296 if (gfc_add_external (&sym->attr, NULL) == FAILURE)
4297 return MATCH_ERROR;
4299 if (add_hidden_procptr_result (sym) == SUCCESS)
4300 sym = sym->result;
4302 if (gfc_add_proc (&sym->attr, sym->name, NULL) == FAILURE)
4303 return MATCH_ERROR;
4305 /* Set interface. */
4306 if (proc_if != NULL)
4308 if (sym->ts.type != BT_UNKNOWN)
4310 gfc_error ("Procedure '%s' at %L already has basic type of %s",
4311 sym->name, &gfc_current_locus,
4312 gfc_basic_typename (sym->ts.type));
4313 return MATCH_ERROR;
4315 sym->ts.interface = proc_if;
4316 sym->attr.untyped = 1;
4317 sym->attr.if_source = IFSRC_IFBODY;
4319 else if (current_ts.type != BT_UNKNOWN)
4321 if (gfc_add_type (sym, &current_ts, &gfc_current_locus) == FAILURE)
4322 return MATCH_ERROR;
4323 sym->ts.interface = gfc_new_symbol ("", gfc_current_ns);
4324 sym->ts.interface->ts = current_ts;
4325 sym->ts.interface->attr.function = 1;
4326 sym->attr.function = sym->ts.interface->attr.function;
4327 sym->attr.if_source = IFSRC_UNKNOWN;
4330 if (gfc_match (" =>") == MATCH_YES)
4332 if (!current_attr.pointer)
4334 gfc_error ("Initialization at %C isn't for a pointer variable");
4335 m = MATCH_ERROR;
4336 goto cleanup;
4339 m = gfc_match_null (&initializer);
4340 if (m == MATCH_NO)
4342 gfc_error ("Pointer initialization requires a NULL() at %C");
4343 m = MATCH_ERROR;
4346 if (gfc_pure (NULL))
4348 gfc_error ("Initialization of pointer at %C is not allowed in "
4349 "a PURE procedure");
4350 m = MATCH_ERROR;
4353 if (m != MATCH_YES)
4354 goto cleanup;
4356 if (add_init_expr_to_sym (sym->name, &initializer, &gfc_current_locus)
4357 != SUCCESS)
4358 goto cleanup;
4362 gfc_set_sym_referenced (sym);
4364 if (gfc_match_eos () == MATCH_YES)
4365 return MATCH_YES;
4366 if (gfc_match_char (',') != MATCH_YES)
4367 goto syntax;
4370 syntax:
4371 gfc_error ("Syntax error in PROCEDURE statement at %C");
4372 return MATCH_ERROR;
4374 cleanup:
4375 /* Free stuff up and return. */
4376 gfc_free_expr (initializer);
4377 return m;
4381 static match
4382 match_binding_attributes (gfc_typebound_proc* ba, bool generic, bool ppc);
4385 /* Match a procedure pointer component declaration (R445). */
4387 static match
4388 match_ppc_decl (void)
4390 match m;
4391 gfc_symbol *proc_if = NULL;
4392 gfc_typespec ts;
4393 int num;
4394 gfc_component *c;
4395 gfc_expr *initializer = NULL;
4396 gfc_typebound_proc* tb;
4397 char name[GFC_MAX_SYMBOL_LEN + 1];
4399 /* Parse interface (with brackets). */
4400 m = match_procedure_interface (&proc_if);
4401 if (m != MATCH_YES)
4402 goto syntax;
4404 /* Parse attributes. */
4405 tb = XCNEW (gfc_typebound_proc);
4406 tb->where = gfc_current_locus;
4407 m = match_binding_attributes (tb, false, true);
4408 if (m == MATCH_ERROR)
4409 return m;
4411 /* TODO: Implement PASS. */
4412 if (!tb->nopass)
4414 gfc_error ("Procedure Pointer Component with PASS at %C "
4415 "not yet implemented");
4416 return MATCH_ERROR;
4419 gfc_clear_attr (&current_attr);
4420 current_attr.procedure = 1;
4421 current_attr.proc_pointer = 1;
4422 current_attr.access = tb->access;
4423 current_attr.flavor = FL_PROCEDURE;
4425 /* Match the colons (required). */
4426 if (gfc_match (" ::") != MATCH_YES)
4428 gfc_error ("Expected '::' after binding-attributes at %C");
4429 return MATCH_ERROR;
4432 /* Check for C450. */
4433 if (!tb->nopass && proc_if == NULL)
4435 gfc_error("NOPASS or explicit interface required at %C");
4436 return MATCH_ERROR;
4439 /* Match PPC names. */
4440 ts = current_ts;
4441 for(num=1;;num++)
4443 m = gfc_match_name (name);
4444 if (m == MATCH_NO)
4445 goto syntax;
4446 else if (m == MATCH_ERROR)
4447 return m;
4449 if (gfc_add_component (gfc_current_block (), name, &c) == FAILURE)
4450 return MATCH_ERROR;
4452 /* Add current_attr to the symbol attributes. */
4453 if (gfc_copy_attr (&c->attr, &current_attr, NULL) == FAILURE)
4454 return MATCH_ERROR;
4456 if (gfc_add_external (&c->attr, NULL) == FAILURE)
4457 return MATCH_ERROR;
4459 if (gfc_add_proc (&c->attr, name, NULL) == FAILURE)
4460 return MATCH_ERROR;
4462 /* Set interface. */
4463 if (proc_if != NULL)
4465 c->ts.interface = proc_if;
4466 c->attr.untyped = 1;
4467 c->attr.if_source = IFSRC_IFBODY;
4469 else if (ts.type != BT_UNKNOWN)
4471 c->ts = ts;
4472 c->ts.interface = gfc_new_symbol ("", gfc_current_ns);
4473 c->ts.interface->ts = ts;
4474 c->ts.interface->attr.function = 1;
4475 c->attr.function = c->ts.interface->attr.function;
4476 c->attr.if_source = IFSRC_UNKNOWN;
4479 if (gfc_match (" =>") == MATCH_YES)
4481 m = gfc_match_null (&initializer);
4482 if (m == MATCH_NO)
4484 gfc_error ("Pointer initialization requires a NULL() at %C");
4485 m = MATCH_ERROR;
4487 if (gfc_pure (NULL))
4489 gfc_error ("Initialization of pointer at %C is not allowed in "
4490 "a PURE procedure");
4491 m = MATCH_ERROR;
4493 if (m != MATCH_YES)
4495 gfc_free_expr (initializer);
4496 return m;
4498 c->initializer = initializer;
4501 if (gfc_match_eos () == MATCH_YES)
4502 return MATCH_YES;
4503 if (gfc_match_char (',') != MATCH_YES)
4504 goto syntax;
4507 syntax:
4508 gfc_error ("Syntax error in procedure pointer component at %C");
4509 return MATCH_ERROR;
4513 /* Match a PROCEDURE declaration inside an interface (R1206). */
4515 static match
4516 match_procedure_in_interface (void)
4518 match m;
4519 gfc_symbol *sym;
4520 char name[GFC_MAX_SYMBOL_LEN + 1];
4522 if (current_interface.type == INTERFACE_NAMELESS
4523 || current_interface.type == INTERFACE_ABSTRACT)
4525 gfc_error ("PROCEDURE at %C must be in a generic interface");
4526 return MATCH_ERROR;
4529 for(;;)
4531 m = gfc_match_name (name);
4532 if (m == MATCH_NO)
4533 goto syntax;
4534 else if (m == MATCH_ERROR)
4535 return m;
4536 if (gfc_get_symbol (name, gfc_current_ns->parent, &sym))
4537 return MATCH_ERROR;
4539 if (gfc_add_interface (sym) == FAILURE)
4540 return MATCH_ERROR;
4542 if (gfc_match_eos () == MATCH_YES)
4543 break;
4544 if (gfc_match_char (',') != MATCH_YES)
4545 goto syntax;
4548 return MATCH_YES;
4550 syntax:
4551 gfc_error ("Syntax error in PROCEDURE statement at %C");
4552 return MATCH_ERROR;
4556 /* General matcher for PROCEDURE declarations. */
4558 static match match_procedure_in_type (void);
4560 match
4561 gfc_match_procedure (void)
4563 match m;
4565 switch (gfc_current_state ())
4567 case COMP_NONE:
4568 case COMP_PROGRAM:
4569 case COMP_MODULE:
4570 case COMP_SUBROUTINE:
4571 case COMP_FUNCTION:
4572 m = match_procedure_decl ();
4573 break;
4574 case COMP_INTERFACE:
4575 m = match_procedure_in_interface ();
4576 break;
4577 case COMP_DERIVED:
4578 m = match_ppc_decl ();
4579 break;
4580 case COMP_DERIVED_CONTAINS:
4581 m = match_procedure_in_type ();
4582 break;
4583 default:
4584 return MATCH_NO;
4587 if (m != MATCH_YES)
4588 return m;
4590 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PROCEDURE statement at %C")
4591 == FAILURE)
4592 return MATCH_ERROR;
4594 return m;
4598 /* Warn if a matched procedure has the same name as an intrinsic; this is
4599 simply a wrapper around gfc_warn_intrinsic_shadow that interprets the current
4600 parser-state-stack to find out whether we're in a module. */
4602 static void
4603 warn_intrinsic_shadow (const gfc_symbol* sym, bool func)
4605 bool in_module;
4607 in_module = (gfc_state_stack->previous
4608 && gfc_state_stack->previous->state == COMP_MODULE);
4610 gfc_warn_intrinsic_shadow (sym, in_module, func);
4614 /* Match a function declaration. */
4616 match
4617 gfc_match_function_decl (void)
4619 char name[GFC_MAX_SYMBOL_LEN + 1];
4620 gfc_symbol *sym, *result;
4621 locus old_loc;
4622 match m;
4623 match suffix_match;
4624 match found_match; /* Status returned by match func. */
4626 if (gfc_current_state () != COMP_NONE
4627 && gfc_current_state () != COMP_INTERFACE
4628 && gfc_current_state () != COMP_CONTAINS)
4629 return MATCH_NO;
4631 gfc_clear_ts (&current_ts);
4633 old_loc = gfc_current_locus;
4635 m = gfc_match_prefix (&current_ts);
4636 if (m != MATCH_YES)
4638 gfc_current_locus = old_loc;
4639 return m;
4642 if (gfc_match ("function% %n", name) != MATCH_YES)
4644 gfc_current_locus = old_loc;
4645 return MATCH_NO;
4647 if (get_proc_name (name, &sym, false))
4648 return MATCH_ERROR;
4650 if (add_hidden_procptr_result (sym) == SUCCESS)
4651 sym = sym->result;
4653 gfc_new_block = sym;
4655 m = gfc_match_formal_arglist (sym, 0, 0);
4656 if (m == MATCH_NO)
4658 gfc_error ("Expected formal argument list in function "
4659 "definition at %C");
4660 m = MATCH_ERROR;
4661 goto cleanup;
4663 else if (m == MATCH_ERROR)
4664 goto cleanup;
4666 result = NULL;
4668 /* According to the draft, the bind(c) and result clause can
4669 come in either order after the formal_arg_list (i.e., either
4670 can be first, both can exist together or by themselves or neither
4671 one). Therefore, the match_result can't match the end of the
4672 string, and check for the bind(c) or result clause in either order. */
4673 found_match = gfc_match_eos ();
4675 /* Make sure that it isn't already declared as BIND(C). If it is, it
4676 must have been marked BIND(C) with a BIND(C) attribute and that is
4677 not allowed for procedures. */
4678 if (sym->attr.is_bind_c == 1)
4680 sym->attr.is_bind_c = 0;
4681 if (sym->old_symbol != NULL)
4682 gfc_error_now ("BIND(C) attribute at %L can only be used for "
4683 "variables or common blocks",
4684 &(sym->old_symbol->declared_at));
4685 else
4686 gfc_error_now ("BIND(C) attribute at %L can only be used for "
4687 "variables or common blocks", &gfc_current_locus);
4690 if (found_match != MATCH_YES)
4692 /* If we haven't found the end-of-statement, look for a suffix. */
4693 suffix_match = gfc_match_suffix (sym, &result);
4694 if (suffix_match == MATCH_YES)
4695 /* Need to get the eos now. */
4696 found_match = gfc_match_eos ();
4697 else
4698 found_match = suffix_match;
4701 if(found_match != MATCH_YES)
4702 m = MATCH_ERROR;
4703 else
4705 /* Make changes to the symbol. */
4706 m = MATCH_ERROR;
4708 if (gfc_add_function (&sym->attr, sym->name, NULL) == FAILURE)
4709 goto cleanup;
4711 if (gfc_missing_attr (&sym->attr, NULL) == FAILURE
4712 || copy_prefix (&sym->attr, &sym->declared_at) == FAILURE)
4713 goto cleanup;
4715 /* Delay matching the function characteristics until after the
4716 specification block by signalling kind=-1. */
4717 sym->declared_at = old_loc;
4718 if (current_ts.type != BT_UNKNOWN)
4719 current_ts.kind = -1;
4720 else
4721 current_ts.kind = 0;
4723 if (result == NULL)
4725 if (current_ts.type != BT_UNKNOWN
4726 && gfc_add_type (sym, &current_ts, &gfc_current_locus) == FAILURE)
4727 goto cleanup;
4728 sym->result = sym;
4730 else
4732 if (current_ts.type != BT_UNKNOWN
4733 && gfc_add_type (result, &current_ts, &gfc_current_locus)
4734 == FAILURE)
4735 goto cleanup;
4736 sym->result = result;
4739 /* Warn if this procedure has the same name as an intrinsic. */
4740 warn_intrinsic_shadow (sym, true);
4742 return MATCH_YES;
4745 cleanup:
4746 gfc_current_locus = old_loc;
4747 return m;
4751 /* This is mostly a copy of parse.c(add_global_procedure) but modified to
4752 pass the name of the entry, rather than the gfc_current_block name, and
4753 to return false upon finding an existing global entry. */
4755 static bool
4756 add_global_entry (const char *name, int sub)
4758 gfc_gsymbol *s;
4759 enum gfc_symbol_type type;
4761 s = gfc_get_gsymbol(name);
4762 type = sub ? GSYM_SUBROUTINE : GSYM_FUNCTION;
4764 if (s->defined
4765 || (s->type != GSYM_UNKNOWN
4766 && s->type != type))
4767 gfc_global_used(s, NULL);
4768 else
4770 s->type = type;
4771 s->where = gfc_current_locus;
4772 s->defined = 1;
4773 s->ns = gfc_current_ns;
4774 return true;
4776 return false;
4780 /* Match an ENTRY statement. */
4782 match
4783 gfc_match_entry (void)
4785 gfc_symbol *proc;
4786 gfc_symbol *result;
4787 gfc_symbol *entry;
4788 char name[GFC_MAX_SYMBOL_LEN + 1];
4789 gfc_compile_state state;
4790 match m;
4791 gfc_entry_list *el;
4792 locus old_loc;
4793 bool module_procedure;
4794 char peek_char;
4795 match is_bind_c;
4797 m = gfc_match_name (name);
4798 if (m != MATCH_YES)
4799 return m;
4801 state = gfc_current_state ();
4802 if (state != COMP_SUBROUTINE && state != COMP_FUNCTION)
4804 switch (state)
4806 case COMP_PROGRAM:
4807 gfc_error ("ENTRY statement at %C cannot appear within a PROGRAM");
4808 break;
4809 case COMP_MODULE:
4810 gfc_error ("ENTRY statement at %C cannot appear within a MODULE");
4811 break;
4812 case COMP_BLOCK_DATA:
4813 gfc_error ("ENTRY statement at %C cannot appear within "
4814 "a BLOCK DATA");
4815 break;
4816 case COMP_INTERFACE:
4817 gfc_error ("ENTRY statement at %C cannot appear within "
4818 "an INTERFACE");
4819 break;
4820 case COMP_DERIVED:
4821 gfc_error ("ENTRY statement at %C cannot appear within "
4822 "a DERIVED TYPE block");
4823 break;
4824 case COMP_IF:
4825 gfc_error ("ENTRY statement at %C cannot appear within "
4826 "an IF-THEN block");
4827 break;
4828 case COMP_DO:
4829 gfc_error ("ENTRY statement at %C cannot appear within "
4830 "a DO block");
4831 break;
4832 case COMP_SELECT:
4833 gfc_error ("ENTRY statement at %C cannot appear within "
4834 "a SELECT block");
4835 break;
4836 case COMP_FORALL:
4837 gfc_error ("ENTRY statement at %C cannot appear within "
4838 "a FORALL block");
4839 break;
4840 case COMP_WHERE:
4841 gfc_error ("ENTRY statement at %C cannot appear within "
4842 "a WHERE block");
4843 break;
4844 case COMP_CONTAINS:
4845 gfc_error ("ENTRY statement at %C cannot appear within "
4846 "a contained subprogram");
4847 break;
4848 default:
4849 gfc_internal_error ("gfc_match_entry(): Bad state");
4851 return MATCH_ERROR;
4854 module_procedure = gfc_current_ns->parent != NULL
4855 && gfc_current_ns->parent->proc_name
4856 && gfc_current_ns->parent->proc_name->attr.flavor
4857 == FL_MODULE;
4859 if (gfc_current_ns->parent != NULL
4860 && gfc_current_ns->parent->proc_name
4861 && !module_procedure)
4863 gfc_error("ENTRY statement at %C cannot appear in a "
4864 "contained procedure");
4865 return MATCH_ERROR;
4868 /* Module function entries need special care in get_proc_name
4869 because previous references within the function will have
4870 created symbols attached to the current namespace. */
4871 if (get_proc_name (name, &entry,
4872 gfc_current_ns->parent != NULL
4873 && module_procedure))
4874 return MATCH_ERROR;
4876 proc = gfc_current_block ();
4878 /* Make sure that it isn't already declared as BIND(C). If it is, it
4879 must have been marked BIND(C) with a BIND(C) attribute and that is
4880 not allowed for procedures. */
4881 if (entry->attr.is_bind_c == 1)
4883 entry->attr.is_bind_c = 0;
4884 if (entry->old_symbol != NULL)
4885 gfc_error_now ("BIND(C) attribute at %L can only be used for "
4886 "variables or common blocks",
4887 &(entry->old_symbol->declared_at));
4888 else
4889 gfc_error_now ("BIND(C) attribute at %L can only be used for "
4890 "variables or common blocks", &gfc_current_locus);
4893 /* Check what next non-whitespace character is so we can tell if there
4894 is the required parens if we have a BIND(C). */
4895 gfc_gobble_whitespace ();
4896 peek_char = gfc_peek_ascii_char ();
4898 if (state == COMP_SUBROUTINE)
4900 /* An entry in a subroutine. */
4901 if (!gfc_current_ns->parent && !add_global_entry (name, 1))
4902 return MATCH_ERROR;
4904 m = gfc_match_formal_arglist (entry, 0, 1);
4905 if (m != MATCH_YES)
4906 return MATCH_ERROR;
4908 /* Call gfc_match_bind_c with allow_binding_name = true as ENTRY can
4909 never be an internal procedure. */
4910 is_bind_c = gfc_match_bind_c (entry, true);
4911 if (is_bind_c == MATCH_ERROR)
4912 return MATCH_ERROR;
4913 if (is_bind_c == MATCH_YES)
4915 if (peek_char != '(')
4917 gfc_error ("Missing required parentheses before BIND(C) at %C");
4918 return MATCH_ERROR;
4920 if (gfc_add_is_bind_c (&(entry->attr), entry->name, &(entry->declared_at), 1)
4921 == FAILURE)
4922 return MATCH_ERROR;
4925 if (gfc_add_entry (&entry->attr, entry->name, NULL) == FAILURE
4926 || gfc_add_subroutine (&entry->attr, entry->name, NULL) == FAILURE)
4927 return MATCH_ERROR;
4929 else
4931 /* An entry in a function.
4932 We need to take special care because writing
4933 ENTRY f()
4935 ENTRY f
4936 is allowed, whereas
4937 ENTRY f() RESULT (r)
4938 can't be written as
4939 ENTRY f RESULT (r). */
4940 if (!gfc_current_ns->parent && !add_global_entry (name, 0))
4941 return MATCH_ERROR;
4943 old_loc = gfc_current_locus;
4944 if (gfc_match_eos () == MATCH_YES)
4946 gfc_current_locus = old_loc;
4947 /* Match the empty argument list, and add the interface to
4948 the symbol. */
4949 m = gfc_match_formal_arglist (entry, 0, 1);
4951 else
4952 m = gfc_match_formal_arglist (entry, 0, 0);
4954 if (m != MATCH_YES)
4955 return MATCH_ERROR;
4957 result = NULL;
4959 if (gfc_match_eos () == MATCH_YES)
4961 if (gfc_add_entry (&entry->attr, entry->name, NULL) == FAILURE
4962 || gfc_add_function (&entry->attr, entry->name, NULL) == FAILURE)
4963 return MATCH_ERROR;
4965 entry->result = entry;
4967 else
4969 m = gfc_match_suffix (entry, &result);
4970 if (m == MATCH_NO)
4971 gfc_syntax_error (ST_ENTRY);
4972 if (m != MATCH_YES)
4973 return MATCH_ERROR;
4975 if (result)
4977 if (gfc_add_result (&result->attr, result->name, NULL) == FAILURE
4978 || gfc_add_entry (&entry->attr, result->name, NULL) == FAILURE
4979 || gfc_add_function (&entry->attr, result->name, NULL)
4980 == FAILURE)
4981 return MATCH_ERROR;
4982 entry->result = result;
4984 else
4986 if (gfc_add_entry (&entry->attr, entry->name, NULL) == FAILURE
4987 || gfc_add_function (&entry->attr, entry->name, NULL) == FAILURE)
4988 return MATCH_ERROR;
4989 entry->result = entry;
4994 if (gfc_match_eos () != MATCH_YES)
4996 gfc_syntax_error (ST_ENTRY);
4997 return MATCH_ERROR;
5000 entry->attr.recursive = proc->attr.recursive;
5001 entry->attr.elemental = proc->attr.elemental;
5002 entry->attr.pure = proc->attr.pure;
5004 el = gfc_get_entry_list ();
5005 el->sym = entry;
5006 el->next = gfc_current_ns->entries;
5007 gfc_current_ns->entries = el;
5008 if (el->next)
5009 el->id = el->next->id + 1;
5010 else
5011 el->id = 1;
5013 new_st.op = EXEC_ENTRY;
5014 new_st.ext.entry = el;
5016 return MATCH_YES;
5020 /* Match a subroutine statement, including optional prefixes. */
5022 match
5023 gfc_match_subroutine (void)
5025 char name[GFC_MAX_SYMBOL_LEN + 1];
5026 gfc_symbol *sym;
5027 match m;
5028 match is_bind_c;
5029 char peek_char;
5030 bool allow_binding_name;
5032 if (gfc_current_state () != COMP_NONE
5033 && gfc_current_state () != COMP_INTERFACE
5034 && gfc_current_state () != COMP_CONTAINS)
5035 return MATCH_NO;
5037 m = gfc_match_prefix (NULL);
5038 if (m != MATCH_YES)
5039 return m;
5041 m = gfc_match ("subroutine% %n", name);
5042 if (m != MATCH_YES)
5043 return m;
5045 if (get_proc_name (name, &sym, false))
5046 return MATCH_ERROR;
5048 if (add_hidden_procptr_result (sym) == SUCCESS)
5049 sym = sym->result;
5051 gfc_new_block = sym;
5053 /* Check what next non-whitespace character is so we can tell if there
5054 is the required parens if we have a BIND(C). */
5055 gfc_gobble_whitespace ();
5056 peek_char = gfc_peek_ascii_char ();
5058 if (gfc_add_subroutine (&sym->attr, sym->name, NULL) == FAILURE)
5059 return MATCH_ERROR;
5061 if (gfc_match_formal_arglist (sym, 0, 1) != MATCH_YES)
5062 return MATCH_ERROR;
5064 /* Make sure that it isn't already declared as BIND(C). If it is, it
5065 must have been marked BIND(C) with a BIND(C) attribute and that is
5066 not allowed for procedures. */
5067 if (sym->attr.is_bind_c == 1)
5069 sym->attr.is_bind_c = 0;
5070 if (sym->old_symbol != NULL)
5071 gfc_error_now ("BIND(C) attribute at %L can only be used for "
5072 "variables or common blocks",
5073 &(sym->old_symbol->declared_at));
5074 else
5075 gfc_error_now ("BIND(C) attribute at %L can only be used for "
5076 "variables or common blocks", &gfc_current_locus);
5079 /* C binding names are not allowed for internal procedures. */
5080 if (gfc_current_state () == COMP_CONTAINS
5081 && sym->ns->proc_name->attr.flavor != FL_MODULE)
5082 allow_binding_name = false;
5083 else
5084 allow_binding_name = true;
5086 /* Here, we are just checking if it has the bind(c) attribute, and if
5087 so, then we need to make sure it's all correct. If it doesn't,
5088 we still need to continue matching the rest of the subroutine line. */
5089 is_bind_c = gfc_match_bind_c (sym, allow_binding_name);
5090 if (is_bind_c == MATCH_ERROR)
5092 /* There was an attempt at the bind(c), but it was wrong. An
5093 error message should have been printed w/in the gfc_match_bind_c
5094 so here we'll just return the MATCH_ERROR. */
5095 return MATCH_ERROR;
5098 if (is_bind_c == MATCH_YES)
5100 /* The following is allowed in the Fortran 2008 draft. */
5101 if (gfc_current_state () == COMP_CONTAINS
5102 && sym->ns->proc_name->attr.flavor != FL_MODULE
5103 && gfc_notify_std (GFC_STD_F2008, "Fortran 2008: BIND(C) attribute "
5104 "at %L may not be specified for an internal "
5105 "procedure", &gfc_current_locus)
5106 == FAILURE)
5107 return MATCH_ERROR;
5109 if (peek_char != '(')
5111 gfc_error ("Missing required parentheses before BIND(C) at %C");
5112 return MATCH_ERROR;
5114 if (gfc_add_is_bind_c (&(sym->attr), sym->name, &(sym->declared_at), 1)
5115 == FAILURE)
5116 return MATCH_ERROR;
5119 if (gfc_match_eos () != MATCH_YES)
5121 gfc_syntax_error (ST_SUBROUTINE);
5122 return MATCH_ERROR;
5125 if (copy_prefix (&sym->attr, &sym->declared_at) == FAILURE)
5126 return MATCH_ERROR;
5128 /* Warn if it has the same name as an intrinsic. */
5129 warn_intrinsic_shadow (sym, false);
5131 return MATCH_YES;
5135 /* Match a BIND(C) specifier, with the optional 'name=' specifier if
5136 given, and set the binding label in either the given symbol (if not
5137 NULL), or in the current_ts. The symbol may be NULL because we may
5138 encounter the BIND(C) before the declaration itself. Return
5139 MATCH_NO if what we're looking at isn't a BIND(C) specifier,
5140 MATCH_ERROR if it is a BIND(C) clause but an error was encountered,
5141 or MATCH_YES if the specifier was correct and the binding label and
5142 bind(c) fields were set correctly for the given symbol or the
5143 current_ts. If allow_binding_name is false, no binding name may be
5144 given. */
5146 match
5147 gfc_match_bind_c (gfc_symbol *sym, bool allow_binding_name)
5149 /* binding label, if exists */
5150 char binding_label[GFC_MAX_SYMBOL_LEN + 1];
5151 match double_quote;
5152 match single_quote;
5154 /* Initialize the flag that specifies whether we encountered a NAME=
5155 specifier or not. */
5156 has_name_equals = 0;
5158 /* Init the first char to nil so we can catch if we don't have
5159 the label (name attr) or the symbol name yet. */
5160 binding_label[0] = '\0';
5162 /* This much we have to be able to match, in this order, if
5163 there is a bind(c) label. */
5164 if (gfc_match (" bind ( c ") != MATCH_YES)
5165 return MATCH_NO;
5167 /* Now see if there is a binding label, or if we've reached the
5168 end of the bind(c) attribute without one. */
5169 if (gfc_match_char (',') == MATCH_YES)
5171 if (gfc_match (" name = ") != MATCH_YES)
5173 gfc_error ("Syntax error in NAME= specifier for binding label "
5174 "at %C");
5175 /* should give an error message here */
5176 return MATCH_ERROR;
5179 has_name_equals = 1;
5181 /* Get the opening quote. */
5182 double_quote = MATCH_YES;
5183 single_quote = MATCH_YES;
5184 double_quote = gfc_match_char ('"');
5185 if (double_quote != MATCH_YES)
5186 single_quote = gfc_match_char ('\'');
5187 if (double_quote != MATCH_YES && single_quote != MATCH_YES)
5189 gfc_error ("Syntax error in NAME= specifier for binding label "
5190 "at %C");
5191 return MATCH_ERROR;
5194 /* Grab the binding label, using functions that will not lower
5195 case the names automatically. */
5196 if (gfc_match_name_C (binding_label) != MATCH_YES)
5197 return MATCH_ERROR;
5199 /* Get the closing quotation. */
5200 if (double_quote == MATCH_YES)
5202 if (gfc_match_char ('"') != MATCH_YES)
5204 gfc_error ("Missing closing quote '\"' for binding label at %C");
5205 /* User started string with '"' so looked to match it. */
5206 return MATCH_ERROR;
5209 else
5211 if (gfc_match_char ('\'') != MATCH_YES)
5213 gfc_error ("Missing closing quote '\'' for binding label at %C");
5214 /* User started string with "'" char. */
5215 return MATCH_ERROR;
5220 /* Get the required right paren. */
5221 if (gfc_match_char (')') != MATCH_YES)
5223 gfc_error ("Missing closing paren for binding label at %C");
5224 return MATCH_ERROR;
5227 if (has_name_equals && !allow_binding_name)
5229 gfc_error ("No binding name is allowed in BIND(C) at %C");
5230 return MATCH_ERROR;
5233 if (has_name_equals && sym != NULL && sym->attr.dummy)
5235 gfc_error ("For dummy procedure %s, no binding name is "
5236 "allowed in BIND(C) at %C", sym->name);
5237 return MATCH_ERROR;
5241 /* Save the binding label to the symbol. If sym is null, we're
5242 probably matching the typespec attributes of a declaration and
5243 haven't gotten the name yet, and therefore, no symbol yet. */
5244 if (binding_label[0] != '\0')
5246 if (sym != NULL)
5248 strcpy (sym->binding_label, binding_label);
5250 else
5251 strcpy (curr_binding_label, binding_label);
5253 else if (allow_binding_name)
5255 /* No binding label, but if symbol isn't null, we
5256 can set the label for it here.
5257 If name="" or allow_binding_name is false, no C binding name is
5258 created. */
5259 if (sym != NULL && sym->name != NULL && has_name_equals == 0)
5260 strncpy (sym->binding_label, sym->name, strlen (sym->name) + 1);
5263 if (has_name_equals && gfc_current_state () == COMP_INTERFACE
5264 && current_interface.type == INTERFACE_ABSTRACT)
5266 gfc_error ("NAME not allowed on BIND(C) for ABSTRACT INTERFACE at %C");
5267 return MATCH_ERROR;
5270 return MATCH_YES;
5274 /* Return nonzero if we're currently compiling a contained procedure. */
5276 static int
5277 contained_procedure (void)
5279 gfc_state_data *s = gfc_state_stack;
5281 if ((s->state == COMP_SUBROUTINE || s->state == COMP_FUNCTION)
5282 && s->previous != NULL && s->previous->state == COMP_CONTAINS)
5283 return 1;
5285 return 0;
5288 /* Set the kind of each enumerator. The kind is selected such that it is
5289 interoperable with the corresponding C enumeration type, making
5290 sure that -fshort-enums is honored. */
5292 static void
5293 set_enum_kind(void)
5295 enumerator_history *current_history = NULL;
5296 int kind;
5297 int i;
5299 if (max_enum == NULL || enum_history == NULL)
5300 return;
5302 if (!flag_short_enums)
5303 return;
5305 i = 0;
5308 kind = gfc_integer_kinds[i++].kind;
5310 while (kind < gfc_c_int_kind
5311 && gfc_check_integer_range (max_enum->initializer->value.integer,
5312 kind) != ARITH_OK);
5314 current_history = enum_history;
5315 while (current_history != NULL)
5317 current_history->sym->ts.kind = kind;
5318 current_history = current_history->next;
5323 /* Match any of the various end-block statements. Returns the type of
5324 END to the caller. The END INTERFACE, END IF, END DO and END
5325 SELECT statements cannot be replaced by a single END statement. */
5327 match
5328 gfc_match_end (gfc_statement *st)
5330 char name[GFC_MAX_SYMBOL_LEN + 1];
5331 gfc_compile_state state;
5332 locus old_loc;
5333 const char *block_name;
5334 const char *target;
5335 int eos_ok;
5336 match m;
5338 old_loc = gfc_current_locus;
5339 if (gfc_match ("end") != MATCH_YES)
5340 return MATCH_NO;
5342 state = gfc_current_state ();
5343 block_name = gfc_current_block () == NULL
5344 ? NULL : gfc_current_block ()->name;
5346 if (state == COMP_CONTAINS || state == COMP_DERIVED_CONTAINS)
5348 state = gfc_state_stack->previous->state;
5349 block_name = gfc_state_stack->previous->sym == NULL
5350 ? NULL : gfc_state_stack->previous->sym->name;
5353 switch (state)
5355 case COMP_NONE:
5356 case COMP_PROGRAM:
5357 *st = ST_END_PROGRAM;
5358 target = " program";
5359 eos_ok = 1;
5360 break;
5362 case COMP_SUBROUTINE:
5363 *st = ST_END_SUBROUTINE;
5364 target = " subroutine";
5365 eos_ok = !contained_procedure ();
5366 break;
5368 case COMP_FUNCTION:
5369 *st = ST_END_FUNCTION;
5370 target = " function";
5371 eos_ok = !contained_procedure ();
5372 break;
5374 case COMP_BLOCK_DATA:
5375 *st = ST_END_BLOCK_DATA;
5376 target = " block data";
5377 eos_ok = 1;
5378 break;
5380 case COMP_MODULE:
5381 *st = ST_END_MODULE;
5382 target = " module";
5383 eos_ok = 1;
5384 break;
5386 case COMP_INTERFACE:
5387 *st = ST_END_INTERFACE;
5388 target = " interface";
5389 eos_ok = 0;
5390 break;
5392 case COMP_DERIVED:
5393 case COMP_DERIVED_CONTAINS:
5394 *st = ST_END_TYPE;
5395 target = " type";
5396 eos_ok = 0;
5397 break;
5399 case COMP_IF:
5400 *st = ST_ENDIF;
5401 target = " if";
5402 eos_ok = 0;
5403 break;
5405 case COMP_DO:
5406 *st = ST_ENDDO;
5407 target = " do";
5408 eos_ok = 0;
5409 break;
5411 case COMP_SELECT:
5412 *st = ST_END_SELECT;
5413 target = " select";
5414 eos_ok = 0;
5415 break;
5417 case COMP_FORALL:
5418 *st = ST_END_FORALL;
5419 target = " forall";
5420 eos_ok = 0;
5421 break;
5423 case COMP_WHERE:
5424 *st = ST_END_WHERE;
5425 target = " where";
5426 eos_ok = 0;
5427 break;
5429 case COMP_ENUM:
5430 *st = ST_END_ENUM;
5431 target = " enum";
5432 eos_ok = 0;
5433 last_initializer = NULL;
5434 set_enum_kind ();
5435 gfc_free_enum_history ();
5436 break;
5438 default:
5439 gfc_error ("Unexpected END statement at %C");
5440 goto cleanup;
5443 if (gfc_match_eos () == MATCH_YES)
5445 if (!eos_ok)
5447 /* We would have required END [something]. */
5448 gfc_error ("%s statement expected at %L",
5449 gfc_ascii_statement (*st), &old_loc);
5450 goto cleanup;
5453 return MATCH_YES;
5456 /* Verify that we've got the sort of end-block that we're expecting. */
5457 if (gfc_match (target) != MATCH_YES)
5459 gfc_error ("Expecting %s statement at %C", gfc_ascii_statement (*st));
5460 goto cleanup;
5463 /* If we're at the end, make sure a block name wasn't required. */
5464 if (gfc_match_eos () == MATCH_YES)
5467 if (*st != ST_ENDDO && *st != ST_ENDIF && *st != ST_END_SELECT
5468 && *st != ST_END_FORALL && *st != ST_END_WHERE)
5469 return MATCH_YES;
5471 if (gfc_current_block () == NULL)
5472 return MATCH_YES;
5474 gfc_error ("Expected block name of '%s' in %s statement at %C",
5475 block_name, gfc_ascii_statement (*st));
5477 return MATCH_ERROR;
5480 /* END INTERFACE has a special handler for its several possible endings. */
5481 if (*st == ST_END_INTERFACE)
5482 return gfc_match_end_interface ();
5484 /* We haven't hit the end of statement, so what is left must be an
5485 end-name. */
5486 m = gfc_match_space ();
5487 if (m == MATCH_YES)
5488 m = gfc_match_name (name);
5490 if (m == MATCH_NO)
5491 gfc_error ("Expected terminating name at %C");
5492 if (m != MATCH_YES)
5493 goto cleanup;
5495 if (block_name == NULL)
5496 goto syntax;
5498 if (strcmp (name, block_name) != 0 && strcmp (block_name, "ppr@") != 0)
5500 gfc_error ("Expected label '%s' for %s statement at %C", block_name,
5501 gfc_ascii_statement (*st));
5502 goto cleanup;
5504 /* Procedure pointer as function result. */
5505 else if (strcmp (block_name, "ppr@") == 0
5506 && strcmp (name, gfc_current_block ()->ns->proc_name->name) != 0)
5508 gfc_error ("Expected label '%s' for %s statement at %C",
5509 gfc_current_block ()->ns->proc_name->name,
5510 gfc_ascii_statement (*st));
5511 goto cleanup;
5514 if (gfc_match_eos () == MATCH_YES)
5515 return MATCH_YES;
5517 syntax:
5518 gfc_syntax_error (*st);
5520 cleanup:
5521 gfc_current_locus = old_loc;
5522 return MATCH_ERROR;
5527 /***************** Attribute declaration statements ****************/
5529 /* Set the attribute of a single variable. */
5531 static match
5532 attr_decl1 (void)
5534 char name[GFC_MAX_SYMBOL_LEN + 1];
5535 gfc_array_spec *as;
5536 gfc_symbol *sym;
5537 locus var_locus;
5538 match m;
5540 as = NULL;
5542 m = gfc_match_name (name);
5543 if (m != MATCH_YES)
5544 goto cleanup;
5546 if (find_special (name, &sym, false))
5547 return MATCH_ERROR;
5549 var_locus = gfc_current_locus;
5551 /* Deal with possible array specification for certain attributes. */
5552 if (current_attr.dimension
5553 || current_attr.allocatable
5554 || current_attr.pointer
5555 || current_attr.target)
5557 m = gfc_match_array_spec (&as);
5558 if (m == MATCH_ERROR)
5559 goto cleanup;
5561 if (current_attr.dimension && m == MATCH_NO)
5563 gfc_error ("Missing array specification at %L in DIMENSION "
5564 "statement", &var_locus);
5565 m = MATCH_ERROR;
5566 goto cleanup;
5569 if (current_attr.dimension && sym->value)
5571 gfc_error ("Dimensions specified for %s at %L after its "
5572 "initialisation", sym->name, &var_locus);
5573 m = MATCH_ERROR;
5574 goto cleanup;
5577 if ((current_attr.allocatable || current_attr.pointer)
5578 && (m == MATCH_YES) && (as->type != AS_DEFERRED))
5580 gfc_error ("Array specification must be deferred at %L", &var_locus);
5581 m = MATCH_ERROR;
5582 goto cleanup;
5586 /* Update symbol table. DIMENSION attribute is set
5587 in gfc_set_array_spec(). */
5588 if (current_attr.dimension == 0
5589 && gfc_copy_attr (&sym->attr, &current_attr, &var_locus) == FAILURE)
5591 m = MATCH_ERROR;
5592 goto cleanup;
5595 if (gfc_set_array_spec (sym, as, &var_locus) == FAILURE)
5597 m = MATCH_ERROR;
5598 goto cleanup;
5601 if (sym->attr.cray_pointee && sym->as != NULL)
5603 /* Fix the array spec. */
5604 m = gfc_mod_pointee_as (sym->as);
5605 if (m == MATCH_ERROR)
5606 goto cleanup;
5609 if (gfc_add_attribute (&sym->attr, &var_locus) == FAILURE)
5611 m = MATCH_ERROR;
5612 goto cleanup;
5615 if ((current_attr.external || current_attr.intrinsic)
5616 && sym->attr.flavor != FL_PROCEDURE
5617 && gfc_add_flavor (&sym->attr, FL_PROCEDURE, sym->name, NULL) == FAILURE)
5619 m = MATCH_ERROR;
5620 goto cleanup;
5623 add_hidden_procptr_result (sym);
5625 return MATCH_YES;
5627 cleanup:
5628 gfc_free_array_spec (as);
5629 return m;
5633 /* Generic attribute declaration subroutine. Used for attributes that
5634 just have a list of names. */
5636 static match
5637 attr_decl (void)
5639 match m;
5641 /* Gobble the optional double colon, by simply ignoring the result
5642 of gfc_match(). */
5643 gfc_match (" ::");
5645 for (;;)
5647 m = attr_decl1 ();
5648 if (m != MATCH_YES)
5649 break;
5651 if (gfc_match_eos () == MATCH_YES)
5653 m = MATCH_YES;
5654 break;
5657 if (gfc_match_char (',') != MATCH_YES)
5659 gfc_error ("Unexpected character in variable list at %C");
5660 m = MATCH_ERROR;
5661 break;
5665 return m;
5669 /* This routine matches Cray Pointer declarations of the form:
5670 pointer ( <pointer>, <pointee> )
5672 pointer ( <pointer1>, <pointee1> ), ( <pointer2>, <pointee2> ), ...
5673 The pointer, if already declared, should be an integer. Otherwise, we
5674 set it as BT_INTEGER with kind gfc_index_integer_kind. The pointee may
5675 be either a scalar, or an array declaration. No space is allocated for
5676 the pointee. For the statement
5677 pointer (ipt, ar(10))
5678 any subsequent uses of ar will be translated (in C-notation) as
5679 ar(i) => ((<type> *) ipt)(i)
5680 After gimplification, pointee variable will disappear in the code. */
5682 static match
5683 cray_pointer_decl (void)
5685 match m;
5686 gfc_array_spec *as;
5687 gfc_symbol *cptr; /* Pointer symbol. */
5688 gfc_symbol *cpte; /* Pointee symbol. */
5689 locus var_locus;
5690 bool done = false;
5692 while (!done)
5694 if (gfc_match_char ('(') != MATCH_YES)
5696 gfc_error ("Expected '(' at %C");
5697 return MATCH_ERROR;
5700 /* Match pointer. */
5701 var_locus = gfc_current_locus;
5702 gfc_clear_attr (&current_attr);
5703 gfc_add_cray_pointer (&current_attr, &var_locus);
5704 current_ts.type = BT_INTEGER;
5705 current_ts.kind = gfc_index_integer_kind;
5707 m = gfc_match_symbol (&cptr, 0);
5708 if (m != MATCH_YES)
5710 gfc_error ("Expected variable name at %C");
5711 return m;
5714 if (gfc_add_cray_pointer (&cptr->attr, &var_locus) == FAILURE)
5715 return MATCH_ERROR;
5717 gfc_set_sym_referenced (cptr);
5719 if (cptr->ts.type == BT_UNKNOWN) /* Override the type, if necessary. */
5721 cptr->ts.type = BT_INTEGER;
5722 cptr->ts.kind = gfc_index_integer_kind;
5724 else if (cptr->ts.type != BT_INTEGER)
5726 gfc_error ("Cray pointer at %C must be an integer");
5727 return MATCH_ERROR;
5729 else if (cptr->ts.kind < gfc_index_integer_kind)
5730 gfc_warning ("Cray pointer at %C has %d bytes of precision;"
5731 " memory addresses require %d bytes",
5732 cptr->ts.kind, gfc_index_integer_kind);
5734 if (gfc_match_char (',') != MATCH_YES)
5736 gfc_error ("Expected \",\" at %C");
5737 return MATCH_ERROR;
5740 /* Match Pointee. */
5741 var_locus = gfc_current_locus;
5742 gfc_clear_attr (&current_attr);
5743 gfc_add_cray_pointee (&current_attr, &var_locus);
5744 current_ts.type = BT_UNKNOWN;
5745 current_ts.kind = 0;
5747 m = gfc_match_symbol (&cpte, 0);
5748 if (m != MATCH_YES)
5750 gfc_error ("Expected variable name at %C");
5751 return m;
5754 /* Check for an optional array spec. */
5755 m = gfc_match_array_spec (&as);
5756 if (m == MATCH_ERROR)
5758 gfc_free_array_spec (as);
5759 return m;
5761 else if (m == MATCH_NO)
5763 gfc_free_array_spec (as);
5764 as = NULL;
5767 if (gfc_add_cray_pointee (&cpte->attr, &var_locus) == FAILURE)
5768 return MATCH_ERROR;
5770 gfc_set_sym_referenced (cpte);
5772 if (cpte->as == NULL)
5774 if (gfc_set_array_spec (cpte, as, &var_locus) == FAILURE)
5775 gfc_internal_error ("Couldn't set Cray pointee array spec.");
5777 else if (as != NULL)
5779 gfc_error ("Duplicate array spec for Cray pointee at %C");
5780 gfc_free_array_spec (as);
5781 return MATCH_ERROR;
5784 as = NULL;
5786 if (cpte->as != NULL)
5788 /* Fix array spec. */
5789 m = gfc_mod_pointee_as (cpte->as);
5790 if (m == MATCH_ERROR)
5791 return m;
5794 /* Point the Pointee at the Pointer. */
5795 cpte->cp_pointer = cptr;
5797 if (gfc_match_char (')') != MATCH_YES)
5799 gfc_error ("Expected \")\" at %C");
5800 return MATCH_ERROR;
5802 m = gfc_match_char (',');
5803 if (m != MATCH_YES)
5804 done = true; /* Stop searching for more declarations. */
5808 if (m == MATCH_ERROR /* Failed when trying to find ',' above. */
5809 || gfc_match_eos () != MATCH_YES)
5811 gfc_error ("Expected \",\" or end of statement at %C");
5812 return MATCH_ERROR;
5814 return MATCH_YES;
5818 match
5819 gfc_match_external (void)
5822 gfc_clear_attr (&current_attr);
5823 current_attr.external = 1;
5825 return attr_decl ();
5829 match
5830 gfc_match_intent (void)
5832 sym_intent intent;
5834 intent = match_intent_spec ();
5835 if (intent == INTENT_UNKNOWN)
5836 return MATCH_ERROR;
5838 gfc_clear_attr (&current_attr);
5839 current_attr.intent = intent;
5841 return attr_decl ();
5845 match
5846 gfc_match_intrinsic (void)
5849 gfc_clear_attr (&current_attr);
5850 current_attr.intrinsic = 1;
5852 return attr_decl ();
5856 match
5857 gfc_match_optional (void)
5860 gfc_clear_attr (&current_attr);
5861 current_attr.optional = 1;
5863 return attr_decl ();
5867 match
5868 gfc_match_pointer (void)
5870 gfc_gobble_whitespace ();
5871 if (gfc_peek_ascii_char () == '(')
5873 if (!gfc_option.flag_cray_pointer)
5875 gfc_error ("Cray pointer declaration at %C requires -fcray-pointer "
5876 "flag");
5877 return MATCH_ERROR;
5879 return cray_pointer_decl ();
5881 else
5883 gfc_clear_attr (&current_attr);
5884 current_attr.pointer = 1;
5886 return attr_decl ();
5891 match
5892 gfc_match_allocatable (void)
5894 gfc_clear_attr (&current_attr);
5895 current_attr.allocatable = 1;
5897 return attr_decl ();
5901 match
5902 gfc_match_dimension (void)
5904 gfc_clear_attr (&current_attr);
5905 current_attr.dimension = 1;
5907 return attr_decl ();
5911 match
5912 gfc_match_target (void)
5914 gfc_clear_attr (&current_attr);
5915 current_attr.target = 1;
5917 return attr_decl ();
5921 /* Match the list of entities being specified in a PUBLIC or PRIVATE
5922 statement. */
5924 static match
5925 access_attr_decl (gfc_statement st)
5927 char name[GFC_MAX_SYMBOL_LEN + 1];
5928 interface_type type;
5929 gfc_user_op *uop;
5930 gfc_symbol *sym;
5931 gfc_intrinsic_op op;
5932 match m;
5934 if (gfc_match (" ::") == MATCH_NO && gfc_match_space () == MATCH_NO)
5935 goto done;
5937 for (;;)
5939 m = gfc_match_generic_spec (&type, name, &op);
5940 if (m == MATCH_NO)
5941 goto syntax;
5942 if (m == MATCH_ERROR)
5943 return MATCH_ERROR;
5945 switch (type)
5947 case INTERFACE_NAMELESS:
5948 case INTERFACE_ABSTRACT:
5949 goto syntax;
5951 case INTERFACE_GENERIC:
5952 if (gfc_get_symbol (name, NULL, &sym))
5953 goto done;
5955 if (gfc_add_access (&sym->attr, (st == ST_PUBLIC)
5956 ? ACCESS_PUBLIC : ACCESS_PRIVATE,
5957 sym->name, NULL) == FAILURE)
5958 return MATCH_ERROR;
5960 break;
5962 case INTERFACE_INTRINSIC_OP:
5963 if (gfc_current_ns->operator_access[op] == ACCESS_UNKNOWN)
5965 gfc_current_ns->operator_access[op] =
5966 (st == ST_PUBLIC) ? ACCESS_PUBLIC : ACCESS_PRIVATE;
5968 else
5970 gfc_error ("Access specification of the %s operator at %C has "
5971 "already been specified", gfc_op2string (op));
5972 goto done;
5975 break;
5977 case INTERFACE_USER_OP:
5978 uop = gfc_get_uop (name);
5980 if (uop->access == ACCESS_UNKNOWN)
5982 uop->access = (st == ST_PUBLIC)
5983 ? ACCESS_PUBLIC : ACCESS_PRIVATE;
5985 else
5987 gfc_error ("Access specification of the .%s. operator at %C "
5988 "has already been specified", sym->name);
5989 goto done;
5992 break;
5995 if (gfc_match_char (',') == MATCH_NO)
5996 break;
5999 if (gfc_match_eos () != MATCH_YES)
6000 goto syntax;
6001 return MATCH_YES;
6003 syntax:
6004 gfc_syntax_error (st);
6006 done:
6007 return MATCH_ERROR;
6011 match
6012 gfc_match_protected (void)
6014 gfc_symbol *sym;
6015 match m;
6017 if (gfc_current_ns->proc_name->attr.flavor != FL_MODULE)
6019 gfc_error ("PROTECTED at %C only allowed in specification "
6020 "part of a module");
6021 return MATCH_ERROR;
6025 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PROTECTED statement at %C")
6026 == FAILURE)
6027 return MATCH_ERROR;
6029 if (gfc_match (" ::") == MATCH_NO && gfc_match_space () == MATCH_NO)
6031 return MATCH_ERROR;
6034 if (gfc_match_eos () == MATCH_YES)
6035 goto syntax;
6037 for(;;)
6039 m = gfc_match_symbol (&sym, 0);
6040 switch (m)
6042 case MATCH_YES:
6043 if (gfc_add_protected (&sym->attr, sym->name, &gfc_current_locus)
6044 == FAILURE)
6045 return MATCH_ERROR;
6046 goto next_item;
6048 case MATCH_NO:
6049 break;
6051 case MATCH_ERROR:
6052 return MATCH_ERROR;
6055 next_item:
6056 if (gfc_match_eos () == MATCH_YES)
6057 break;
6058 if (gfc_match_char (',') != MATCH_YES)
6059 goto syntax;
6062 return MATCH_YES;
6064 syntax:
6065 gfc_error ("Syntax error in PROTECTED statement at %C");
6066 return MATCH_ERROR;
6070 /* The PRIVATE statement is a bit weird in that it can be an attribute
6071 declaration, but also works as a standalone statement inside of a
6072 type declaration or a module. */
6074 match
6075 gfc_match_private (gfc_statement *st)
6078 if (gfc_match ("private") != MATCH_YES)
6079 return MATCH_NO;
6081 if (gfc_current_state () != COMP_MODULE
6082 && !(gfc_current_state () == COMP_DERIVED
6083 && gfc_state_stack->previous
6084 && gfc_state_stack->previous->state == COMP_MODULE)
6085 && !(gfc_current_state () == COMP_DERIVED_CONTAINS
6086 && gfc_state_stack->previous && gfc_state_stack->previous->previous
6087 && gfc_state_stack->previous->previous->state == COMP_MODULE))
6089 gfc_error ("PRIVATE statement at %C is only allowed in the "
6090 "specification part of a module");
6091 return MATCH_ERROR;
6094 if (gfc_current_state () == COMP_DERIVED)
6096 if (gfc_match_eos () == MATCH_YES)
6098 *st = ST_PRIVATE;
6099 return MATCH_YES;
6102 gfc_syntax_error (ST_PRIVATE);
6103 return MATCH_ERROR;
6106 if (gfc_match_eos () == MATCH_YES)
6108 *st = ST_PRIVATE;
6109 return MATCH_YES;
6112 *st = ST_ATTR_DECL;
6113 return access_attr_decl (ST_PRIVATE);
6117 match
6118 gfc_match_public (gfc_statement *st)
6121 if (gfc_match ("public") != MATCH_YES)
6122 return MATCH_NO;
6124 if (gfc_current_state () != COMP_MODULE)
6126 gfc_error ("PUBLIC statement at %C is only allowed in the "
6127 "specification part of a module");
6128 return MATCH_ERROR;
6131 if (gfc_match_eos () == MATCH_YES)
6133 *st = ST_PUBLIC;
6134 return MATCH_YES;
6137 *st = ST_ATTR_DECL;
6138 return access_attr_decl (ST_PUBLIC);
6142 /* Workhorse for gfc_match_parameter. */
6144 static match
6145 do_parm (void)
6147 gfc_symbol *sym;
6148 gfc_expr *init;
6149 match m;
6151 m = gfc_match_symbol (&sym, 0);
6152 if (m == MATCH_NO)
6153 gfc_error ("Expected variable name at %C in PARAMETER statement");
6155 if (m != MATCH_YES)
6156 return m;
6158 if (gfc_match_char ('=') == MATCH_NO)
6160 gfc_error ("Expected = sign in PARAMETER statement at %C");
6161 return MATCH_ERROR;
6164 m = gfc_match_init_expr (&init);
6165 if (m == MATCH_NO)
6166 gfc_error ("Expected expression at %C in PARAMETER statement");
6167 if (m != MATCH_YES)
6168 return m;
6170 if (sym->ts.type == BT_UNKNOWN
6171 && gfc_set_default_type (sym, 1, NULL) == FAILURE)
6173 m = MATCH_ERROR;
6174 goto cleanup;
6177 if (gfc_check_assign_symbol (sym, init) == FAILURE
6178 || gfc_add_flavor (&sym->attr, FL_PARAMETER, sym->name, NULL) == FAILURE)
6180 m = MATCH_ERROR;
6181 goto cleanup;
6184 if (sym->value)
6186 gfc_error ("Initializing already initialized variable at %C");
6187 m = MATCH_ERROR;
6188 goto cleanup;
6191 if (sym->ts.type == BT_CHARACTER
6192 && sym->ts.cl != NULL
6193 && sym->ts.cl->length != NULL
6194 && sym->ts.cl->length->expr_type == EXPR_CONSTANT
6195 && init->expr_type == EXPR_CONSTANT
6196 && init->ts.type == BT_CHARACTER)
6197 gfc_set_constant_character_len (
6198 mpz_get_si (sym->ts.cl->length->value.integer), init, -1);
6199 else if (sym->ts.type == BT_CHARACTER && sym->ts.cl != NULL
6200 && sym->ts.cl->length == NULL)
6202 int clen;
6203 if (init->expr_type == EXPR_CONSTANT)
6205 clen = init->value.character.length;
6206 sym->ts.cl->length = gfc_int_expr (clen);
6208 else if (init->expr_type == EXPR_ARRAY)
6210 gfc_expr *p = init->value.constructor->expr;
6211 clen = p->value.character.length;
6212 sym->ts.cl->length = gfc_int_expr (clen);
6214 else if (init->ts.cl && init->ts.cl->length)
6215 sym->ts.cl->length = gfc_copy_expr (sym->value->ts.cl->length);
6218 sym->value = init;
6219 return MATCH_YES;
6221 cleanup:
6222 gfc_free_expr (init);
6223 return m;
6227 /* Match a parameter statement, with the weird syntax that these have. */
6229 match
6230 gfc_match_parameter (void)
6232 match m;
6234 if (gfc_match_char ('(') == MATCH_NO)
6235 return MATCH_NO;
6237 for (;;)
6239 m = do_parm ();
6240 if (m != MATCH_YES)
6241 break;
6243 if (gfc_match (" )%t") == MATCH_YES)
6244 break;
6246 if (gfc_match_char (',') != MATCH_YES)
6248 gfc_error ("Unexpected characters in PARAMETER statement at %C");
6249 m = MATCH_ERROR;
6250 break;
6254 return m;
6258 /* Save statements have a special syntax. */
6260 match
6261 gfc_match_save (void)
6263 char n[GFC_MAX_SYMBOL_LEN+1];
6264 gfc_common_head *c;
6265 gfc_symbol *sym;
6266 match m;
6268 if (gfc_match_eos () == MATCH_YES)
6270 if (gfc_current_ns->seen_save)
6272 if (gfc_notify_std (GFC_STD_LEGACY, "Blanket SAVE statement at %C "
6273 "follows previous SAVE statement")
6274 == FAILURE)
6275 return MATCH_ERROR;
6278 gfc_current_ns->save_all = gfc_current_ns->seen_save = 1;
6279 return MATCH_YES;
6282 if (gfc_current_ns->save_all)
6284 if (gfc_notify_std (GFC_STD_LEGACY, "SAVE statement at %C follows "
6285 "blanket SAVE statement")
6286 == FAILURE)
6287 return MATCH_ERROR;
6290 gfc_match (" ::");
6292 for (;;)
6294 m = gfc_match_symbol (&sym, 0);
6295 switch (m)
6297 case MATCH_YES:
6298 if (gfc_add_save (&sym->attr, sym->name, &gfc_current_locus)
6299 == FAILURE)
6300 return MATCH_ERROR;
6301 goto next_item;
6303 case MATCH_NO:
6304 break;
6306 case MATCH_ERROR:
6307 return MATCH_ERROR;
6310 m = gfc_match (" / %n /", &n);
6311 if (m == MATCH_ERROR)
6312 return MATCH_ERROR;
6313 if (m == MATCH_NO)
6314 goto syntax;
6316 c = gfc_get_common (n, 0);
6317 c->saved = 1;
6319 gfc_current_ns->seen_save = 1;
6321 next_item:
6322 if (gfc_match_eos () == MATCH_YES)
6323 break;
6324 if (gfc_match_char (',') != MATCH_YES)
6325 goto syntax;
6328 return MATCH_YES;
6330 syntax:
6331 gfc_error ("Syntax error in SAVE statement at %C");
6332 return MATCH_ERROR;
6336 match
6337 gfc_match_value (void)
6339 gfc_symbol *sym;
6340 match m;
6342 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: VALUE statement at %C")
6343 == FAILURE)
6344 return MATCH_ERROR;
6346 if (gfc_match (" ::") == MATCH_NO && gfc_match_space () == MATCH_NO)
6348 return MATCH_ERROR;
6351 if (gfc_match_eos () == MATCH_YES)
6352 goto syntax;
6354 for(;;)
6356 m = gfc_match_symbol (&sym, 0);
6357 switch (m)
6359 case MATCH_YES:
6360 if (gfc_add_value (&sym->attr, sym->name, &gfc_current_locus)
6361 == FAILURE)
6362 return MATCH_ERROR;
6363 goto next_item;
6365 case MATCH_NO:
6366 break;
6368 case MATCH_ERROR:
6369 return MATCH_ERROR;
6372 next_item:
6373 if (gfc_match_eos () == MATCH_YES)
6374 break;
6375 if (gfc_match_char (',') != MATCH_YES)
6376 goto syntax;
6379 return MATCH_YES;
6381 syntax:
6382 gfc_error ("Syntax error in VALUE statement at %C");
6383 return MATCH_ERROR;
6387 match
6388 gfc_match_volatile (void)
6390 gfc_symbol *sym;
6391 match m;
6393 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: VOLATILE statement at %C")
6394 == FAILURE)
6395 return MATCH_ERROR;
6397 if (gfc_match (" ::") == MATCH_NO && gfc_match_space () == MATCH_NO)
6399 return MATCH_ERROR;
6402 if (gfc_match_eos () == MATCH_YES)
6403 goto syntax;
6405 for(;;)
6407 /* VOLATILE is special because it can be added to host-associated
6408 symbols locally. */
6409 m = gfc_match_symbol (&sym, 1);
6410 switch (m)
6412 case MATCH_YES:
6413 if (gfc_add_volatile (&sym->attr, sym->name, &gfc_current_locus)
6414 == FAILURE)
6415 return MATCH_ERROR;
6416 goto next_item;
6418 case MATCH_NO:
6419 break;
6421 case MATCH_ERROR:
6422 return MATCH_ERROR;
6425 next_item:
6426 if (gfc_match_eos () == MATCH_YES)
6427 break;
6428 if (gfc_match_char (',') != MATCH_YES)
6429 goto syntax;
6432 return MATCH_YES;
6434 syntax:
6435 gfc_error ("Syntax error in VOLATILE statement at %C");
6436 return MATCH_ERROR;
6440 /* Match a module procedure statement. Note that we have to modify
6441 symbols in the parent's namespace because the current one was there
6442 to receive symbols that are in an interface's formal argument list. */
6444 match
6445 gfc_match_modproc (void)
6447 char name[GFC_MAX_SYMBOL_LEN + 1];
6448 gfc_symbol *sym;
6449 match m;
6450 gfc_namespace *module_ns;
6451 gfc_interface *old_interface_head, *interface;
6453 if (gfc_state_stack->state != COMP_INTERFACE
6454 || gfc_state_stack->previous == NULL
6455 || current_interface.type == INTERFACE_NAMELESS
6456 || current_interface.type == INTERFACE_ABSTRACT)
6458 gfc_error ("MODULE PROCEDURE at %C must be in a generic module "
6459 "interface");
6460 return MATCH_ERROR;
6463 module_ns = gfc_current_ns->parent;
6464 for (; module_ns; module_ns = module_ns->parent)
6465 if (module_ns->proc_name->attr.flavor == FL_MODULE)
6466 break;
6468 if (module_ns == NULL)
6469 return MATCH_ERROR;
6471 /* Store the current state of the interface. We will need it if we
6472 end up with a syntax error and need to recover. */
6473 old_interface_head = gfc_current_interface_head ();
6475 for (;;)
6477 bool last = false;
6479 m = gfc_match_name (name);
6480 if (m == MATCH_NO)
6481 goto syntax;
6482 if (m != MATCH_YES)
6483 return MATCH_ERROR;
6485 /* Check for syntax error before starting to add symbols to the
6486 current namespace. */
6487 if (gfc_match_eos () == MATCH_YES)
6488 last = true;
6489 if (!last && gfc_match_char (',') != MATCH_YES)
6490 goto syntax;
6492 /* Now we're sure the syntax is valid, we process this item
6493 further. */
6494 if (gfc_get_symbol (name, module_ns, &sym))
6495 return MATCH_ERROR;
6497 if (sym->attr.proc != PROC_MODULE
6498 && gfc_add_procedure (&sym->attr, PROC_MODULE,
6499 sym->name, NULL) == FAILURE)
6500 return MATCH_ERROR;
6502 if (gfc_add_interface (sym) == FAILURE)
6503 return MATCH_ERROR;
6505 sym->attr.mod_proc = 1;
6507 if (last)
6508 break;
6511 return MATCH_YES;
6513 syntax:
6514 /* Restore the previous state of the interface. */
6515 interface = gfc_current_interface_head ();
6516 gfc_set_current_interface_head (old_interface_head);
6518 /* Free the new interfaces. */
6519 while (interface != old_interface_head)
6521 gfc_interface *i = interface->next;
6522 gfc_free (interface);
6523 interface = i;
6526 /* And issue a syntax error. */
6527 gfc_syntax_error (ST_MODULE_PROC);
6528 return MATCH_ERROR;
6532 /* Check a derived type that is being extended. */
6533 static gfc_symbol*
6534 check_extended_derived_type (char *name)
6536 gfc_symbol *extended;
6538 if (gfc_find_symbol (name, gfc_current_ns, 1, &extended))
6540 gfc_error ("Ambiguous symbol in TYPE definition at %C");
6541 return NULL;
6544 if (!extended)
6546 gfc_error ("No such symbol in TYPE definition at %C");
6547 return NULL;
6550 if (extended->attr.flavor != FL_DERIVED)
6552 gfc_error ("'%s' in EXTENDS expression at %C is not a "
6553 "derived type", name);
6554 return NULL;
6557 if (extended->attr.is_bind_c)
6559 gfc_error ("'%s' cannot be extended at %C because it "
6560 "is BIND(C)", extended->name);
6561 return NULL;
6564 if (extended->attr.sequence)
6566 gfc_error ("'%s' cannot be extended at %C because it "
6567 "is a SEQUENCE type", extended->name);
6568 return NULL;
6571 return extended;
6575 /* Match the optional attribute specifiers for a type declaration.
6576 Return MATCH_ERROR if an error is encountered in one of the handled
6577 attributes (public, private, bind(c)), MATCH_NO if what's found is
6578 not a handled attribute, and MATCH_YES otherwise. TODO: More error
6579 checking on attribute conflicts needs to be done. */
6581 match
6582 gfc_get_type_attr_spec (symbol_attribute *attr, char *name)
6584 /* See if the derived type is marked as private. */
6585 if (gfc_match (" , private") == MATCH_YES)
6587 if (gfc_current_state () != COMP_MODULE)
6589 gfc_error ("Derived type at %C can only be PRIVATE in the "
6590 "specification part of a module");
6591 return MATCH_ERROR;
6594 if (gfc_add_access (attr, ACCESS_PRIVATE, NULL, NULL) == FAILURE)
6595 return MATCH_ERROR;
6597 else if (gfc_match (" , public") == MATCH_YES)
6599 if (gfc_current_state () != COMP_MODULE)
6601 gfc_error ("Derived type at %C can only be PUBLIC in the "
6602 "specification part of a module");
6603 return MATCH_ERROR;
6606 if (gfc_add_access (attr, ACCESS_PUBLIC, NULL, NULL) == FAILURE)
6607 return MATCH_ERROR;
6609 else if (gfc_match (" , bind ( c )") == MATCH_YES)
6611 /* If the type is defined to be bind(c) it then needs to make
6612 sure that all fields are interoperable. This will
6613 need to be a semantic check on the finished derived type.
6614 See 15.2.3 (lines 9-12) of F2003 draft. */
6615 if (gfc_add_is_bind_c (attr, NULL, &gfc_current_locus, 0) != SUCCESS)
6616 return MATCH_ERROR;
6618 /* TODO: attr conflicts need to be checked, probably in symbol.c. */
6620 else if (gfc_match (" , abstract") == MATCH_YES)
6622 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: ABSTRACT type at %C")
6623 == FAILURE)
6624 return MATCH_ERROR;
6626 if (gfc_add_abstract (attr, &gfc_current_locus) == FAILURE)
6627 return MATCH_ERROR;
6629 else if (name && gfc_match(" , extends ( %n )", name) == MATCH_YES)
6631 if (gfc_add_extension (attr, &gfc_current_locus) == FAILURE)
6632 return MATCH_ERROR;
6634 else
6635 return MATCH_NO;
6637 /* If we get here, something matched. */
6638 return MATCH_YES;
6642 /* Match the beginning of a derived type declaration. If a type name
6643 was the result of a function, then it is possible to have a symbol
6644 already to be known as a derived type yet have no components. */
6646 match
6647 gfc_match_derived_decl (void)
6649 char name[GFC_MAX_SYMBOL_LEN + 1];
6650 char parent[GFC_MAX_SYMBOL_LEN + 1];
6651 symbol_attribute attr;
6652 gfc_symbol *sym;
6653 gfc_symbol *extended;
6654 match m;
6655 match is_type_attr_spec = MATCH_NO;
6656 bool seen_attr = false;
6658 if (gfc_current_state () == COMP_DERIVED)
6659 return MATCH_NO;
6661 name[0] = '\0';
6662 parent[0] = '\0';
6663 gfc_clear_attr (&attr);
6664 extended = NULL;
6668 is_type_attr_spec = gfc_get_type_attr_spec (&attr, parent);
6669 if (is_type_attr_spec == MATCH_ERROR)
6670 return MATCH_ERROR;
6671 if (is_type_attr_spec == MATCH_YES)
6672 seen_attr = true;
6673 } while (is_type_attr_spec == MATCH_YES);
6675 /* Deal with derived type extensions. The extension attribute has
6676 been added to 'attr' but now the parent type must be found and
6677 checked. */
6678 if (parent[0])
6679 extended = check_extended_derived_type (parent);
6681 if (parent[0] && !extended)
6682 return MATCH_ERROR;
6684 if (gfc_match (" ::") != MATCH_YES && seen_attr)
6686 gfc_error ("Expected :: in TYPE definition at %C");
6687 return MATCH_ERROR;
6690 m = gfc_match (" %n%t", name);
6691 if (m != MATCH_YES)
6692 return m;
6694 /* Make sure the name is not the name of an intrinsic type. */
6695 if (gfc_is_intrinsic_typename (name))
6697 gfc_error ("Type name '%s' at %C cannot be the same as an intrinsic "
6698 "type", name);
6699 return MATCH_ERROR;
6702 if (gfc_get_symbol (name, NULL, &sym))
6703 return MATCH_ERROR;
6705 if (sym->ts.type != BT_UNKNOWN)
6707 gfc_error ("Derived type name '%s' at %C already has a basic type "
6708 "of %s", sym->name, gfc_typename (&sym->ts));
6709 return MATCH_ERROR;
6712 /* The symbol may already have the derived attribute without the
6713 components. The ways this can happen is via a function
6714 definition, an INTRINSIC statement or a subtype in another
6715 derived type that is a pointer. The first part of the AND clause
6716 is true if the symbol is not the return value of a function. */
6717 if (sym->attr.flavor != FL_DERIVED
6718 && gfc_add_flavor (&sym->attr, FL_DERIVED, sym->name, NULL) == FAILURE)
6719 return MATCH_ERROR;
6721 if (sym->components != NULL || sym->attr.zero_comp)
6723 gfc_error ("Derived type definition of '%s' at %C has already been "
6724 "defined", sym->name);
6725 return MATCH_ERROR;
6728 if (attr.access != ACCESS_UNKNOWN
6729 && gfc_add_access (&sym->attr, attr.access, sym->name, NULL) == FAILURE)
6730 return MATCH_ERROR;
6732 /* See if the derived type was labeled as bind(c). */
6733 if (attr.is_bind_c != 0)
6734 sym->attr.is_bind_c = attr.is_bind_c;
6736 /* Construct the f2k_derived namespace if it is not yet there. */
6737 if (!sym->f2k_derived)
6738 sym->f2k_derived = gfc_get_namespace (NULL, 0);
6740 if (extended && !sym->components)
6742 gfc_component *p;
6743 gfc_symtree *st;
6745 /* Add the extended derived type as the first component. */
6746 gfc_add_component (sym, parent, &p);
6747 sym->attr.extension = attr.extension;
6748 extended->refs++;
6749 gfc_set_sym_referenced (extended);
6751 p->ts.type = BT_DERIVED;
6752 p->ts.derived = extended;
6753 p->initializer = gfc_default_initializer (&p->ts);
6755 /* Provide the links between the extended type and its extension. */
6756 if (!extended->f2k_derived)
6757 extended->f2k_derived = gfc_get_namespace (NULL, 0);
6758 st = gfc_new_symtree (&extended->f2k_derived->sym_root, sym->name);
6759 st->n.sym = sym;
6762 /* Take over the ABSTRACT attribute. */
6763 sym->attr.abstract = attr.abstract;
6765 gfc_new_block = sym;
6767 return MATCH_YES;
6771 /* Cray Pointees can be declared as:
6772 pointer (ipt, a (n,m,...,*))
6773 By default, this is treated as an AS_ASSUMED_SIZE array. We'll
6774 cheat and set a constant bound of 1 for the last dimension, if this
6775 is the case. Since there is no bounds-checking for Cray Pointees,
6776 this will be okay. */
6778 match
6779 gfc_mod_pointee_as (gfc_array_spec *as)
6781 as->cray_pointee = true; /* This will be useful to know later. */
6782 if (as->type == AS_ASSUMED_SIZE)
6784 as->type = AS_EXPLICIT;
6785 as->upper[as->rank - 1] = gfc_int_expr (1);
6786 as->cp_was_assumed = true;
6788 else if (as->type == AS_ASSUMED_SHAPE)
6790 gfc_error ("Cray Pointee at %C cannot be assumed shape array");
6791 return MATCH_ERROR;
6793 return MATCH_YES;
6797 /* Match the enum definition statement, here we are trying to match
6798 the first line of enum definition statement.
6799 Returns MATCH_YES if match is found. */
6801 match
6802 gfc_match_enum (void)
6804 match m;
6806 m = gfc_match_eos ();
6807 if (m != MATCH_YES)
6808 return m;
6810 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: ENUM and ENUMERATOR at %C")
6811 == FAILURE)
6812 return MATCH_ERROR;
6814 return MATCH_YES;
6818 /* Returns an initializer whose value is one higher than the value of the
6819 LAST_INITIALIZER argument. If the argument is NULL, the
6820 initializers value will be set to zero. The initializer's kind
6821 will be set to gfc_c_int_kind.
6823 If -fshort-enums is given, the appropriate kind will be selected
6824 later after all enumerators have been parsed. A warning is issued
6825 here if an initializer exceeds gfc_c_int_kind. */
6827 static gfc_expr *
6828 enum_initializer (gfc_expr *last_initializer, locus where)
6830 gfc_expr *result;
6832 result = gfc_get_expr ();
6833 result->expr_type = EXPR_CONSTANT;
6834 result->ts.type = BT_INTEGER;
6835 result->ts.kind = gfc_c_int_kind;
6836 result->where = where;
6838 mpz_init (result->value.integer);
6840 if (last_initializer != NULL)
6842 mpz_add_ui (result->value.integer, last_initializer->value.integer, 1);
6843 result->where = last_initializer->where;
6845 if (gfc_check_integer_range (result->value.integer,
6846 gfc_c_int_kind) != ARITH_OK)
6848 gfc_error ("Enumerator exceeds the C integer type at %C");
6849 return NULL;
6852 else
6854 /* Control comes here, if it's the very first enumerator and no
6855 initializer has been given. It will be initialized to zero. */
6856 mpz_set_si (result->value.integer, 0);
6859 return result;
6863 /* Match a variable name with an optional initializer. When this
6864 subroutine is called, a variable is expected to be parsed next.
6865 Depending on what is happening at the moment, updates either the
6866 symbol table or the current interface. */
6868 static match
6869 enumerator_decl (void)
6871 char name[GFC_MAX_SYMBOL_LEN + 1];
6872 gfc_expr *initializer;
6873 gfc_array_spec *as = NULL;
6874 gfc_symbol *sym;
6875 locus var_locus;
6876 match m;
6877 gfc_try t;
6878 locus old_locus;
6880 initializer = NULL;
6881 old_locus = gfc_current_locus;
6883 /* When we get here, we've just matched a list of attributes and
6884 maybe a type and a double colon. The next thing we expect to see
6885 is the name of the symbol. */
6886 m = gfc_match_name (name);
6887 if (m != MATCH_YES)
6888 goto cleanup;
6890 var_locus = gfc_current_locus;
6892 /* OK, we've successfully matched the declaration. Now put the
6893 symbol in the current namespace. If we fail to create the symbol,
6894 bail out. */
6895 if (build_sym (name, NULL, &as, &var_locus) == FAILURE)
6897 m = MATCH_ERROR;
6898 goto cleanup;
6901 /* The double colon must be present in order to have initializers.
6902 Otherwise the statement is ambiguous with an assignment statement. */
6903 if (colon_seen)
6905 if (gfc_match_char ('=') == MATCH_YES)
6907 m = gfc_match_init_expr (&initializer);
6908 if (m == MATCH_NO)
6910 gfc_error ("Expected an initialization expression at %C");
6911 m = MATCH_ERROR;
6914 if (m != MATCH_YES)
6915 goto cleanup;
6919 /* If we do not have an initializer, the initialization value of the
6920 previous enumerator (stored in last_initializer) is incremented
6921 by 1 and is used to initialize the current enumerator. */
6922 if (initializer == NULL)
6923 initializer = enum_initializer (last_initializer, old_locus);
6925 if (initializer == NULL || initializer->ts.type != BT_INTEGER)
6927 gfc_error("ENUMERATOR %L not initialized with integer expression",
6928 &var_locus);
6929 m = MATCH_ERROR;
6930 gfc_free_enum_history ();
6931 goto cleanup;
6934 /* Store this current initializer, for the next enumerator variable
6935 to be parsed. add_init_expr_to_sym() zeros initializer, so we
6936 use last_initializer below. */
6937 last_initializer = initializer;
6938 t = add_init_expr_to_sym (name, &initializer, &var_locus);
6940 /* Maintain enumerator history. */
6941 gfc_find_symbol (name, NULL, 0, &sym);
6942 create_enum_history (sym, last_initializer);
6944 return (t == SUCCESS) ? MATCH_YES : MATCH_ERROR;
6946 cleanup:
6947 /* Free stuff up and return. */
6948 gfc_free_expr (initializer);
6950 return m;
6954 /* Match the enumerator definition statement. */
6956 match
6957 gfc_match_enumerator_def (void)
6959 match m;
6960 gfc_try t;
6962 gfc_clear_ts (&current_ts);
6964 m = gfc_match (" enumerator");
6965 if (m != MATCH_YES)
6966 return m;
6968 m = gfc_match (" :: ");
6969 if (m == MATCH_ERROR)
6970 return m;
6972 colon_seen = (m == MATCH_YES);
6974 if (gfc_current_state () != COMP_ENUM)
6976 gfc_error ("ENUM definition statement expected before %C");
6977 gfc_free_enum_history ();
6978 return MATCH_ERROR;
6981 (&current_ts)->type = BT_INTEGER;
6982 (&current_ts)->kind = gfc_c_int_kind;
6984 gfc_clear_attr (&current_attr);
6985 t = gfc_add_flavor (&current_attr, FL_PARAMETER, NULL, NULL);
6986 if (t == FAILURE)
6988 m = MATCH_ERROR;
6989 goto cleanup;
6992 for (;;)
6994 m = enumerator_decl ();
6995 if (m == MATCH_ERROR)
6996 goto cleanup;
6997 if (m == MATCH_NO)
6998 break;
7000 if (gfc_match_eos () == MATCH_YES)
7001 goto cleanup;
7002 if (gfc_match_char (',') != MATCH_YES)
7003 break;
7006 if (gfc_current_state () == COMP_ENUM)
7008 gfc_free_enum_history ();
7009 gfc_error ("Syntax error in ENUMERATOR definition at %C");
7010 m = MATCH_ERROR;
7013 cleanup:
7014 gfc_free_array_spec (current_as);
7015 current_as = NULL;
7016 return m;
7021 /* Match binding attributes. */
7023 static match
7024 match_binding_attributes (gfc_typebound_proc* ba, bool generic, bool ppc)
7026 bool found_passing = false;
7027 bool seen_ptr = false;
7028 match m;
7030 /* Intialize to defaults. Do so even before the MATCH_NO check so that in
7031 this case the defaults are in there. */
7032 ba->access = ACCESS_UNKNOWN;
7033 ba->pass_arg = NULL;
7034 ba->pass_arg_num = 0;
7035 ba->nopass = 0;
7036 ba->non_overridable = 0;
7037 ba->deferred = 0;
7039 /* If we find a comma, we believe there are binding attributes. */
7040 if (gfc_match_char (',') == MATCH_NO)
7042 ba->access = gfc_typebound_default_access;
7043 return MATCH_NO;
7048 /* Access specifier. */
7050 m = gfc_match (" public");
7051 if (m == MATCH_ERROR)
7052 goto error;
7053 if (m == MATCH_YES)
7055 if (ba->access != ACCESS_UNKNOWN)
7057 gfc_error ("Duplicate access-specifier at %C");
7058 goto error;
7061 ba->access = ACCESS_PUBLIC;
7062 continue;
7065 m = gfc_match (" private");
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_PRIVATE;
7077 continue;
7080 /* If inside GENERIC, the following is not allowed. */
7081 if (!generic)
7084 /* NOPASS flag. */
7085 m = gfc_match (" nopass");
7086 if (m == MATCH_ERROR)
7087 goto error;
7088 if (m == MATCH_YES)
7090 if (found_passing)
7092 gfc_error ("Binding attributes already specify passing,"
7093 " illegal NOPASS at %C");
7094 goto error;
7097 found_passing = true;
7098 ba->nopass = 1;
7099 continue;
7102 /* PASS possibly including argument. */
7103 m = gfc_match (" pass");
7104 if (m == MATCH_ERROR)
7105 goto error;
7106 if (m == MATCH_YES)
7108 char arg[GFC_MAX_SYMBOL_LEN + 1];
7110 if (found_passing)
7112 gfc_error ("Binding attributes already specify passing,"
7113 " illegal PASS at %C");
7114 goto error;
7117 m = gfc_match (" ( %n )", arg);
7118 if (m == MATCH_ERROR)
7119 goto error;
7120 if (m == MATCH_YES)
7121 ba->pass_arg = xstrdup (arg);
7122 gcc_assert ((m == MATCH_YES) == (ba->pass_arg != NULL));
7124 found_passing = true;
7125 ba->nopass = 0;
7126 continue;
7129 if (ppc)
7131 /* POINTER flag. */
7132 m = gfc_match (" pointer");
7133 if (m == MATCH_ERROR)
7134 goto error;
7135 if (m == MATCH_YES)
7137 if (seen_ptr)
7139 gfc_error ("Duplicate POINTER attribute at %C");
7140 goto error;
7143 seen_ptr = true;
7144 /*ba->ppc = 1;*/
7145 continue;
7148 else
7150 /* NON_OVERRIDABLE flag. */
7151 m = gfc_match (" non_overridable");
7152 if (m == MATCH_ERROR)
7153 goto error;
7154 if (m == MATCH_YES)
7156 if (ba->non_overridable)
7158 gfc_error ("Duplicate NON_OVERRIDABLE at %C");
7159 goto error;
7162 ba->non_overridable = 1;
7163 continue;
7166 /* DEFERRED flag. */
7167 m = gfc_match (" deferred");
7168 if (m == MATCH_ERROR)
7169 goto error;
7170 if (m == MATCH_YES)
7172 if (ba->deferred)
7174 gfc_error ("Duplicate DEFERRED at %C");
7175 goto error;
7178 ba->deferred = 1;
7179 continue;
7185 /* Nothing matching found. */
7186 if (generic)
7187 gfc_error ("Expected access-specifier at %C");
7188 else
7189 gfc_error ("Expected binding attribute at %C");
7190 goto error;
7192 while (gfc_match_char (',') == MATCH_YES);
7194 /* NON_OVERRIDABLE and DEFERRED exclude themselves. */
7195 if (ba->non_overridable && ba->deferred)
7197 gfc_error ("NON_OVERRIDABLE and DEFERRED can't both appear at %C");
7198 goto error;
7201 if (ba->access == ACCESS_UNKNOWN)
7202 ba->access = gfc_typebound_default_access;
7204 if (ppc && !seen_ptr)
7206 gfc_error ("POINTER attribute is required for procedure pointer component"
7207 " at %C");
7208 goto error;
7211 return MATCH_YES;
7213 error:
7214 gfc_free (ba->pass_arg);
7215 return MATCH_ERROR;
7219 /* Match a PROCEDURE specific binding inside a derived type. */
7221 static match
7222 match_procedure_in_type (void)
7224 char name[GFC_MAX_SYMBOL_LEN + 1];
7225 char target_buf[GFC_MAX_SYMBOL_LEN + 1];
7226 char* target = NULL;
7227 gfc_typebound_proc* tb;
7228 bool seen_colons;
7229 bool seen_attrs;
7230 match m;
7231 gfc_symtree* stree;
7232 gfc_namespace* ns;
7233 gfc_symbol* block;
7235 /* Check current state. */
7236 gcc_assert (gfc_state_stack->state == COMP_DERIVED_CONTAINS);
7237 block = gfc_state_stack->previous->sym;
7238 gcc_assert (block);
7240 /* Try to match PROCEDURE(interface). */
7241 if (gfc_match (" (") == MATCH_YES)
7243 m = gfc_match_name (target_buf);
7244 if (m == MATCH_ERROR)
7245 return m;
7246 if (m != MATCH_YES)
7248 gfc_error ("Interface-name expected after '(' at %C");
7249 return MATCH_ERROR;
7252 if (gfc_match (" )") != MATCH_YES)
7254 gfc_error ("')' expected at %C");
7255 return MATCH_ERROR;
7258 target = target_buf;
7261 /* Construct the data structure. */
7262 tb = gfc_get_typebound_proc ();
7263 tb->where = gfc_current_locus;
7264 tb->is_generic = 0;
7266 /* Match binding attributes. */
7267 m = match_binding_attributes (tb, false, false);
7268 if (m == MATCH_ERROR)
7269 return m;
7270 seen_attrs = (m == MATCH_YES);
7272 /* Check that attribute DEFERRED is given iff an interface is specified, which
7273 means target != NULL. */
7274 if (tb->deferred && !target)
7276 gfc_error ("Interface must be specified for DEFERRED binding at %C");
7277 return MATCH_ERROR;
7279 if (target && !tb->deferred)
7281 gfc_error ("PROCEDURE(interface) at %C should be declared DEFERRED");
7282 return MATCH_ERROR;
7285 /* Match the colons. */
7286 m = gfc_match (" ::");
7287 if (m == MATCH_ERROR)
7288 return m;
7289 seen_colons = (m == MATCH_YES);
7290 if (seen_attrs && !seen_colons)
7292 gfc_error ("Expected '::' after binding-attributes at %C");
7293 return MATCH_ERROR;
7296 /* Match the binding name. */
7297 m = gfc_match_name (name);
7298 if (m == MATCH_ERROR)
7299 return m;
7300 if (m == MATCH_NO)
7302 gfc_error ("Expected binding name at %C");
7303 return MATCH_ERROR;
7306 /* Try to match the '=> target', if it's there. */
7307 m = gfc_match (" =>");
7308 if (m == MATCH_ERROR)
7309 return m;
7310 if (m == MATCH_YES)
7312 if (tb->deferred)
7314 gfc_error ("'=> target' is invalid for DEFERRED binding at %C");
7315 return MATCH_ERROR;
7318 if (!seen_colons)
7320 gfc_error ("'::' needed in PROCEDURE binding with explicit target"
7321 " at %C");
7322 return MATCH_ERROR;
7325 m = gfc_match_name (target_buf);
7326 if (m == MATCH_ERROR)
7327 return m;
7328 if (m == MATCH_NO)
7330 gfc_error ("Expected binding target after '=>' at %C");
7331 return MATCH_ERROR;
7333 target = target_buf;
7336 /* Now we should have the end. */
7337 m = gfc_match_eos ();
7338 if (m == MATCH_ERROR)
7339 return m;
7340 if (m == MATCH_NO)
7342 gfc_error ("Junk after PROCEDURE declaration at %C");
7343 return MATCH_ERROR;
7346 /* If no target was found, it has the same name as the binding. */
7347 if (!target)
7348 target = name;
7350 /* Get the namespace to insert the symbols into. */
7351 ns = block->f2k_derived;
7352 gcc_assert (ns);
7354 /* If the binding is DEFERRED, check that the containing type is ABSTRACT. */
7355 if (tb->deferred && !block->attr.abstract)
7357 gfc_error ("Type '%s' containing DEFERRED binding at %C is not ABSTRACT",
7358 block->name);
7359 return MATCH_ERROR;
7362 /* See if we already have a binding with this name in the symtree which would
7363 be an error. If a GENERIC already targetted this binding, it may be
7364 already there but then typebound is still NULL. */
7365 stree = gfc_find_symtree (ns->tb_sym_root, name);
7366 if (stree && stree->n.tb)
7368 gfc_error ("There's already a procedure with binding name '%s' for the"
7369 " derived type '%s' at %C", name, block->name);
7370 return MATCH_ERROR;
7373 /* Insert it and set attributes. */
7375 if (!stree)
7377 stree = gfc_new_symtree (&ns->tb_sym_root, name);
7378 gcc_assert (stree);
7380 stree->n.tb = tb;
7382 if (gfc_get_sym_tree (target, gfc_current_ns, &tb->u.specific, false))
7383 return MATCH_ERROR;
7384 gfc_set_sym_referenced (tb->u.specific->n.sym);
7386 return MATCH_YES;
7390 /* Match a GENERIC procedure binding inside a derived type. */
7392 match
7393 gfc_match_generic (void)
7395 char name[GFC_MAX_SYMBOL_LEN + 1];
7396 gfc_symbol* block;
7397 gfc_typebound_proc tbattr; /* Used for match_binding_attributes. */
7398 gfc_typebound_proc* tb;
7399 gfc_symtree* st;
7400 gfc_namespace* ns;
7401 match m;
7403 /* Check current state. */
7404 if (gfc_current_state () == COMP_DERIVED)
7406 gfc_error ("GENERIC at %C must be inside a derived-type CONTAINS");
7407 return MATCH_ERROR;
7409 if (gfc_current_state () != COMP_DERIVED_CONTAINS)
7410 return MATCH_NO;
7411 block = gfc_state_stack->previous->sym;
7412 ns = block->f2k_derived;
7413 gcc_assert (block && ns);
7415 /* See if we get an access-specifier. */
7416 m = match_binding_attributes (&tbattr, true, false);
7417 if (m == MATCH_ERROR)
7418 goto error;
7420 /* Now the colons, those are required. */
7421 if (gfc_match (" ::") != MATCH_YES)
7423 gfc_error ("Expected '::' at %C");
7424 goto error;
7427 /* The binding name and =>. */
7428 m = gfc_match (" %n =>", name);
7429 if (m == MATCH_ERROR)
7430 return MATCH_ERROR;
7431 if (m == MATCH_NO)
7433 gfc_error ("Expected generic name at %C");
7434 goto error;
7437 /* If there's already something with this name, check that it is another
7438 GENERIC and then extend that rather than build a new node. */
7439 st = gfc_find_symtree (ns->tb_sym_root, name);
7440 if (st)
7442 gcc_assert (st->n.tb);
7443 tb = st->n.tb;
7445 if (!tb->is_generic)
7447 gfc_error ("There's already a non-generic procedure with binding name"
7448 " '%s' for the derived type '%s' at %C",
7449 name, block->name);
7450 goto error;
7453 if (tb->access != tbattr.access)
7455 gfc_error ("Binding at %C must have the same access as already"
7456 " defined binding '%s'", name);
7457 goto error;
7460 else
7462 st = gfc_new_symtree (&ns->tb_sym_root, name);
7463 gcc_assert (st);
7465 st->n.tb = tb = gfc_get_typebound_proc ();
7466 tb->where = gfc_current_locus;
7467 tb->access = tbattr.access;
7468 tb->is_generic = 1;
7469 tb->u.generic = NULL;
7472 /* Now, match all following names as specific targets. */
7475 gfc_symtree* target_st;
7476 gfc_tbp_generic* target;
7478 m = gfc_match_name (name);
7479 if (m == MATCH_ERROR)
7480 goto error;
7481 if (m == MATCH_NO)
7483 gfc_error ("Expected specific binding name at %C");
7484 goto error;
7487 target_st = gfc_get_tbp_symtree (&ns->tb_sym_root, name);
7489 /* See if this is a duplicate specification. */
7490 for (target = tb->u.generic; target; target = target->next)
7491 if (target_st == target->specific_st)
7493 gfc_error ("'%s' already defined as specific binding for the"
7494 " generic '%s' at %C", name, st->name);
7495 goto error;
7498 target = gfc_get_tbp_generic ();
7499 target->specific_st = target_st;
7500 target->specific = NULL;
7501 target->next = tb->u.generic;
7502 tb->u.generic = target;
7504 while (gfc_match (" ,") == MATCH_YES);
7506 /* Here should be the end. */
7507 if (gfc_match_eos () != MATCH_YES)
7509 gfc_error ("Junk after GENERIC binding at %C");
7510 goto error;
7513 return MATCH_YES;
7515 error:
7516 return MATCH_ERROR;
7520 /* Match a FINAL declaration inside a derived type. */
7522 match
7523 gfc_match_final_decl (void)
7525 char name[GFC_MAX_SYMBOL_LEN + 1];
7526 gfc_symbol* sym;
7527 match m;
7528 gfc_namespace* module_ns;
7529 bool first, last;
7530 gfc_symbol* block;
7532 if (gfc_state_stack->state != COMP_DERIVED_CONTAINS)
7534 gfc_error ("FINAL declaration at %C must be inside a derived type "
7535 "CONTAINS section");
7536 return MATCH_ERROR;
7539 block = gfc_state_stack->previous->sym;
7540 gcc_assert (block);
7542 if (!gfc_state_stack->previous || !gfc_state_stack->previous->previous
7543 || gfc_state_stack->previous->previous->state != COMP_MODULE)
7545 gfc_error ("Derived type declaration with FINAL at %C must be in the"
7546 " specification part of a MODULE");
7547 return MATCH_ERROR;
7550 module_ns = gfc_current_ns;
7551 gcc_assert (module_ns);
7552 gcc_assert (module_ns->proc_name->attr.flavor == FL_MODULE);
7554 /* Match optional ::, don't care about MATCH_YES or MATCH_NO. */
7555 if (gfc_match (" ::") == MATCH_ERROR)
7556 return MATCH_ERROR;
7558 /* Match the sequence of procedure names. */
7559 first = true;
7560 last = false;
7563 gfc_finalizer* f;
7565 if (first && gfc_match_eos () == MATCH_YES)
7567 gfc_error ("Empty FINAL at %C");
7568 return MATCH_ERROR;
7571 m = gfc_match_name (name);
7572 if (m == MATCH_NO)
7574 gfc_error ("Expected module procedure name at %C");
7575 return MATCH_ERROR;
7577 else if (m != MATCH_YES)
7578 return MATCH_ERROR;
7580 if (gfc_match_eos () == MATCH_YES)
7581 last = true;
7582 if (!last && gfc_match_char (',') != MATCH_YES)
7584 gfc_error ("Expected ',' at %C");
7585 return MATCH_ERROR;
7588 if (gfc_get_symbol (name, module_ns, &sym))
7590 gfc_error ("Unknown procedure name \"%s\" at %C", name);
7591 return MATCH_ERROR;
7594 /* Mark the symbol as module procedure. */
7595 if (sym->attr.proc != PROC_MODULE
7596 && gfc_add_procedure (&sym->attr, PROC_MODULE,
7597 sym->name, NULL) == FAILURE)
7598 return MATCH_ERROR;
7600 /* Check if we already have this symbol in the list, this is an error. */
7601 for (f = block->f2k_derived->finalizers; f; f = f->next)
7602 if (f->proc_sym == sym)
7604 gfc_error ("'%s' at %C is already defined as FINAL procedure!",
7605 name);
7606 return MATCH_ERROR;
7609 /* Add this symbol to the list of finalizers. */
7610 gcc_assert (block->f2k_derived);
7611 ++sym->refs;
7612 f = XCNEW (gfc_finalizer);
7613 f->proc_sym = sym;
7614 f->proc_tree = NULL;
7615 f->where = gfc_current_locus;
7616 f->next = block->f2k_derived->finalizers;
7617 block->f2k_derived->finalizers = f;
7619 first = false;
7621 while (!last);
7623 return MATCH_YES;
7627 const ext_attr_t ext_attr_list[] = {
7628 { "dllimport", EXT_ATTR_DLLIMPORT, "dllimport" },
7629 { "dllexport", EXT_ATTR_DLLEXPORT, "dllexport" },
7630 { "cdecl", EXT_ATTR_CDECL, "cdecl" },
7631 { "stdcall", EXT_ATTR_STDCALL, "stdcall" },
7632 { "fastcall", EXT_ATTR_FASTCALL, "fastcall" },
7633 { NULL, EXT_ATTR_LAST, NULL }
7636 /* Match a !GCC$ ATTRIBUTES statement of the form:
7637 !GCC$ ATTRIBUTES attribute-list :: var-name [, var-name] ...
7638 When we come here, we have already matched the !GCC$ ATTRIBUTES string.
7640 TODO: We should support all GCC attributes using the same syntax for
7641 the attribute list, i.e. the list in C
7642 __attributes(( attribute-list ))
7643 matches then
7644 !GCC$ ATTRIBUTES attribute-list ::
7645 Cf. c-parser.c's c_parser_attributes; the data can then directly be
7646 saved into a TREE.
7648 As there is absolutely no risk of confusion, we should never return
7649 MATCH_NO. */
7650 match
7651 gfc_match_gcc_attributes (void)
7653 symbol_attribute attr;
7654 char name[GFC_MAX_SYMBOL_LEN + 1];
7655 unsigned id;
7656 gfc_symbol *sym;
7657 match m;
7659 gfc_clear_attr (&attr);
7660 for(;;)
7662 char ch;
7664 if (gfc_match_name (name) != MATCH_YES)
7665 return MATCH_ERROR;
7667 for (id = 0; id < EXT_ATTR_LAST; id++)
7668 if (strcmp (name, ext_attr_list[id].name) == 0)
7669 break;
7671 if (id == EXT_ATTR_LAST)
7673 gfc_error ("Unknown attribute in !GCC$ ATTRIBUTES statement at %C");
7674 return MATCH_ERROR;
7677 if (gfc_add_ext_attribute (&attr, id, &gfc_current_locus)
7678 == FAILURE)
7679 return MATCH_ERROR;
7681 gfc_gobble_whitespace ();
7682 ch = gfc_next_ascii_char ();
7683 if (ch == ':')
7685 /* This is the successful exit condition for the loop. */
7686 if (gfc_next_ascii_char () == ':')
7687 break;
7690 if (ch == ',')
7691 continue;
7693 goto syntax;
7696 if (gfc_match_eos () == MATCH_YES)
7697 goto syntax;
7699 for(;;)
7701 m = gfc_match_name (name);
7702 if (m != MATCH_YES)
7703 return m;
7705 if (find_special (name, &sym, true))
7706 return MATCH_ERROR;
7708 sym->attr.ext_attr |= attr.ext_attr;
7710 if (gfc_match_eos () == MATCH_YES)
7711 break;
7713 if (gfc_match_char (',') != MATCH_YES)
7714 goto syntax;
7717 return MATCH_YES;
7719 syntax:
7720 gfc_error ("Syntax error in !GCC$ ATTRIBUTES statement at %C");
7721 return MATCH_ERROR;