2009-10-11 Paul Thomas <pault@gcc.gnu.org>
[official-gcc.git] / gcc / fortran / decl.c
blob69449a32ce989ee6b87800c92f434ee13adbaa01
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.u.cl
626 && e->symtree->n.sym->ts.u.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 if (gfc_notify_std (GFC_STD_F95_OBS, "Obsolescent feature: "
659 "Old-style character length at %C") == FAILURE)
660 return MATCH_ERROR;
661 *expr = gfc_int_expr (length);
662 return m;
665 if (gfc_match_char ('(') == MATCH_NO)
666 goto syntax;
668 m = char_len_param_value (expr);
669 if (m != MATCH_YES && gfc_matching_function)
671 gfc_undo_symbols ();
672 m = MATCH_YES;
675 if (m == MATCH_ERROR)
676 return m;
677 if (m == MATCH_NO)
678 goto syntax;
680 if (gfc_match_char (')') == MATCH_NO)
682 gfc_free_expr (*expr);
683 *expr = NULL;
684 goto syntax;
687 return MATCH_YES;
689 syntax:
690 gfc_error ("Syntax error in character length specification at %C");
691 return MATCH_ERROR;
695 /* Special subroutine for finding a symbol. Check if the name is found
696 in the current name space. If not, and we're compiling a function or
697 subroutine and the parent compilation unit is an interface, then check
698 to see if the name we've been given is the name of the interface
699 (located in another namespace). */
701 static int
702 find_special (const char *name, gfc_symbol **result, bool allow_subroutine)
704 gfc_state_data *s;
705 gfc_symtree *st;
706 int i;
708 i = gfc_get_sym_tree (name, NULL, &st, allow_subroutine);
709 if (i == 0)
711 *result = st ? st->n.sym : NULL;
712 goto end;
715 if (gfc_current_state () != COMP_SUBROUTINE
716 && gfc_current_state () != COMP_FUNCTION)
717 goto end;
719 s = gfc_state_stack->previous;
720 if (s == NULL)
721 goto end;
723 if (s->state != COMP_INTERFACE)
724 goto end;
725 if (s->sym == NULL)
726 goto end; /* Nameless interface. */
728 if (strcmp (name, s->sym->name) == 0)
730 *result = s->sym;
731 return 0;
734 end:
735 return i;
739 /* Special subroutine for getting a symbol node associated with a
740 procedure name, used in SUBROUTINE and FUNCTION statements. The
741 symbol is created in the parent using with symtree node in the
742 child unit pointing to the symbol. If the current namespace has no
743 parent, then the symbol is just created in the current unit. */
745 static int
746 get_proc_name (const char *name, gfc_symbol **result, bool module_fcn_entry)
748 gfc_symtree *st;
749 gfc_symbol *sym;
750 int rc = 0;
752 /* Module functions have to be left in their own namespace because
753 they have potentially (almost certainly!) already been referenced.
754 In this sense, they are rather like external functions. This is
755 fixed up in resolve.c(resolve_entries), where the symbol name-
756 space is set to point to the master function, so that the fake
757 result mechanism can work. */
758 if (module_fcn_entry)
760 /* Present if entry is declared to be a module procedure. */
761 rc = gfc_find_symbol (name, gfc_current_ns->parent, 0, result);
763 if (*result == NULL)
764 rc = gfc_get_symbol (name, NULL, result);
765 else if (!gfc_get_symbol (name, NULL, &sym) && sym
766 && (*result)->ts.type == BT_UNKNOWN
767 && sym->attr.flavor == FL_UNKNOWN)
768 /* Pick up the typespec for the entry, if declared in the function
769 body. Note that this symbol is FL_UNKNOWN because it will
770 only have appeared in a type declaration. The local symtree
771 is set to point to the module symbol and a unique symtree
772 to the local version. This latter ensures a correct clearing
773 of the symbols. */
775 /* If the ENTRY proceeds its specification, we need to ensure
776 that this does not raise a "has no IMPLICIT type" error. */
777 if (sym->ts.type == BT_UNKNOWN)
778 sym->attr.untyped = 1;
780 (*result)->ts = sym->ts;
782 /* Put the symbol in the procedure namespace so that, should
783 the ENTRY precede its specification, the specification
784 can be applied. */
785 (*result)->ns = gfc_current_ns;
787 gfc_find_sym_tree (name, gfc_current_ns, 0, &st);
788 st->n.sym = *result;
789 st = gfc_get_unique_symtree (gfc_current_ns);
790 st->n.sym = sym;
793 else
794 rc = gfc_get_symbol (name, gfc_current_ns->parent, result);
796 if (rc)
797 return rc;
799 sym = *result;
800 gfc_current_ns->refs++;
802 if (sym && !sym->gfc_new && gfc_current_state () != COMP_INTERFACE)
804 /* Trap another encompassed procedure with the same name. All
805 these conditions are necessary to avoid picking up an entry
806 whose name clashes with that of the encompassing procedure;
807 this is handled using gsymbols to register unique,globally
808 accessible names. */
809 if (sym->attr.flavor != 0
810 && sym->attr.proc != 0
811 && (sym->attr.subroutine || sym->attr.function)
812 && sym->attr.if_source != IFSRC_UNKNOWN)
813 gfc_error_now ("Procedure '%s' at %C is already defined at %L",
814 name, &sym->declared_at);
816 /* Trap a procedure with a name the same as interface in the
817 encompassing scope. */
818 if (sym->attr.generic != 0
819 && (sym->attr.subroutine || sym->attr.function)
820 && !sym->attr.mod_proc)
821 gfc_error_now ("Name '%s' at %C is already defined"
822 " as a generic interface at %L",
823 name, &sym->declared_at);
825 /* Trap declarations of attributes in encompassing scope. The
826 signature for this is that ts.kind is set. Legitimate
827 references only set ts.type. */
828 if (sym->ts.kind != 0
829 && !sym->attr.implicit_type
830 && sym->attr.proc == 0
831 && gfc_current_ns->parent != NULL
832 && sym->attr.access == 0
833 && !module_fcn_entry)
834 gfc_error_now ("Procedure '%s' at %C has an explicit interface "
835 "and must not have attributes declared at %L",
836 name, &sym->declared_at);
839 if (gfc_current_ns->parent == NULL || *result == NULL)
840 return rc;
842 /* Module function entries will already have a symtree in
843 the current namespace but will need one at module level. */
844 if (module_fcn_entry)
846 /* Present if entry is declared to be a module procedure. */
847 rc = gfc_find_sym_tree (name, gfc_current_ns->parent, 0, &st);
848 if (st == NULL)
849 st = gfc_new_symtree (&gfc_current_ns->parent->sym_root, name);
851 else
852 st = gfc_new_symtree (&gfc_current_ns->sym_root, name);
854 st->n.sym = sym;
855 sym->refs++;
857 /* See if the procedure should be a module procedure. */
859 if (((sym->ns->proc_name != NULL
860 && sym->ns->proc_name->attr.flavor == FL_MODULE
861 && sym->attr.proc != PROC_MODULE)
862 || (module_fcn_entry && sym->attr.proc != PROC_MODULE))
863 && gfc_add_procedure (&sym->attr, PROC_MODULE,
864 sym->name, NULL) == FAILURE)
865 rc = 2;
867 return rc;
871 /* Verify that the given symbol representing a parameter is C
872 interoperable, by checking to see if it was marked as such after
873 its declaration. If the given symbol is not interoperable, a
874 warning is reported, thus removing the need to return the status to
875 the calling function. The standard does not require the user use
876 one of the iso_c_binding named constants to declare an
877 interoperable parameter, but we can't be sure if the param is C
878 interop or not if the user doesn't. For example, integer(4) may be
879 legal Fortran, but doesn't have meaning in C. It may interop with
880 a number of the C types, which causes a problem because the
881 compiler can't know which one. This code is almost certainly not
882 portable, and the user will get what they deserve if the C type
883 across platforms isn't always interoperable with integer(4). If
884 the user had used something like integer(c_int) or integer(c_long),
885 the compiler could have automatically handled the varying sizes
886 across platforms. */
888 gfc_try
889 verify_c_interop_param (gfc_symbol *sym)
891 int is_c_interop = 0;
892 gfc_try retval = SUCCESS;
894 /* We check implicitly typed variables in symbol.c:gfc_set_default_type().
895 Don't repeat the checks here. */
896 if (sym->attr.implicit_type)
897 return SUCCESS;
899 /* For subroutines or functions that are passed to a BIND(C) procedure,
900 they're interoperable if they're BIND(C) and their params are all
901 interoperable. */
902 if (sym->attr.flavor == FL_PROCEDURE)
904 if (sym->attr.is_bind_c == 0)
906 gfc_error_now ("Procedure '%s' at %L must have the BIND(C) "
907 "attribute to be C interoperable", sym->name,
908 &(sym->declared_at));
910 return FAILURE;
912 else
914 if (sym->attr.is_c_interop == 1)
915 /* We've already checked this procedure; don't check it again. */
916 return SUCCESS;
917 else
918 return verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
919 sym->common_block);
923 /* See if we've stored a reference to a procedure that owns sym. */
924 if (sym->ns != NULL && sym->ns->proc_name != NULL)
926 if (sym->ns->proc_name->attr.is_bind_c == 1)
928 is_c_interop =
929 (verify_c_interop (&(sym->ts))
930 == SUCCESS ? 1 : 0);
932 if (is_c_interop != 1)
934 /* Make personalized messages to give better feedback. */
935 if (sym->ts.type == BT_DERIVED)
936 gfc_error ("Type '%s' at %L is a parameter to the BIND(C) "
937 " procedure '%s' but is not C interoperable "
938 "because derived type '%s' is not C interoperable",
939 sym->name, &(sym->declared_at),
940 sym->ns->proc_name->name,
941 sym->ts.u.derived->name);
942 else
943 gfc_warning ("Variable '%s' at %L is a parameter to the "
944 "BIND(C) procedure '%s' but may not be C "
945 "interoperable",
946 sym->name, &(sym->declared_at),
947 sym->ns->proc_name->name);
950 /* Character strings are only C interoperable if they have a
951 length of 1. */
952 if (sym->ts.type == BT_CHARACTER)
954 gfc_charlen *cl = sym->ts.u.cl;
955 if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT
956 || mpz_cmp_si (cl->length->value.integer, 1) != 0)
958 gfc_error ("Character argument '%s' at %L "
959 "must be length 1 because "
960 "procedure '%s' is BIND(C)",
961 sym->name, &sym->declared_at,
962 sym->ns->proc_name->name);
963 retval = FAILURE;
967 /* We have to make sure that any param to a bind(c) routine does
968 not have the allocatable, pointer, or optional attributes,
969 according to J3/04-007, section 5.1. */
970 if (sym->attr.allocatable == 1)
972 gfc_error ("Variable '%s' at %L cannot have the "
973 "ALLOCATABLE attribute because procedure '%s'"
974 " is BIND(C)", sym->name, &(sym->declared_at),
975 sym->ns->proc_name->name);
976 retval = FAILURE;
979 if (sym->attr.pointer == 1)
981 gfc_error ("Variable '%s' at %L cannot have the "
982 "POINTER attribute because procedure '%s'"
983 " is BIND(C)", sym->name, &(sym->declared_at),
984 sym->ns->proc_name->name);
985 retval = FAILURE;
988 if (sym->attr.optional == 1)
990 gfc_error ("Variable '%s' at %L cannot have the "
991 "OPTIONAL attribute because procedure '%s'"
992 " is BIND(C)", sym->name, &(sym->declared_at),
993 sym->ns->proc_name->name);
994 retval = FAILURE;
997 /* Make sure that if it has the dimension attribute, that it is
998 either assumed size or explicit shape. */
999 if (sym->as != NULL)
1001 if (sym->as->type == AS_ASSUMED_SHAPE)
1003 gfc_error ("Assumed-shape array '%s' at %L cannot be an "
1004 "argument to the procedure '%s' at %L because "
1005 "the procedure is BIND(C)", sym->name,
1006 &(sym->declared_at), sym->ns->proc_name->name,
1007 &(sym->ns->proc_name->declared_at));
1008 retval = FAILURE;
1011 if (sym->as->type == AS_DEFERRED)
1013 gfc_error ("Deferred-shape array '%s' at %L cannot be an "
1014 "argument to the procedure '%s' at %L because "
1015 "the procedure is BIND(C)", sym->name,
1016 &(sym->declared_at), sym->ns->proc_name->name,
1017 &(sym->ns->proc_name->declared_at));
1018 retval = FAILURE;
1024 return retval;
1028 /* Build a polymorphic CLASS entity, using the symbol that comes from build_sym.
1029 A CLASS entity is represented by an encapsulating type, which contains the
1030 declared type as '$data' component, plus an integer component '$vindex'
1031 which determines the dynamic type. */
1033 static gfc_try
1034 encapsulate_class_symbol (gfc_typespec *ts, symbol_attribute *attr,
1035 gfc_array_spec **as)
1037 char name[GFC_MAX_SYMBOL_LEN + 5];
1038 gfc_symbol *fclass;
1039 gfc_component *c;
1041 /* Determine the name of the encapsulating type. */
1042 if ((*as) && (*as)->rank && attr->allocatable)
1043 sprintf (name, ".class.%s.%d.a", ts->u.derived->name, (*as)->rank);
1044 else if ((*as) && (*as)->rank)
1045 sprintf (name, ".class.%s.%d", ts->u.derived->name, (*as)->rank);
1046 else if (attr->allocatable)
1047 sprintf (name, ".class.%s.a", ts->u.derived->name);
1048 else
1049 sprintf (name, ".class.%s", ts->u.derived->name);
1051 gfc_find_symbol (name, ts->u.derived->ns, 0, &fclass);
1052 if (fclass == NULL)
1054 gfc_symtree *st;
1055 /* If not there, create a new symbol. */
1056 fclass = gfc_new_symbol (name, ts->u.derived->ns);
1057 st = gfc_new_symtree (&ts->u.derived->ns->sym_root, name);
1058 st->n.sym = fclass;
1059 gfc_set_sym_referenced (fclass);
1060 fclass->refs++;
1061 fclass->ts.type = BT_UNKNOWN;
1062 fclass->vindex = ts->u.derived->vindex;
1063 fclass->attr.abstract = ts->u.derived->attr.abstract;
1064 if (ts->u.derived->f2k_derived)
1065 fclass->f2k_derived = gfc_get_namespace (NULL, 0);
1066 if (gfc_add_flavor (&fclass->attr, FL_DERIVED,
1067 NULL, &gfc_current_locus) == FAILURE)
1068 return FAILURE;
1070 /* Add component '$data'. */
1071 if (gfc_add_component (fclass, "$data", &c) == FAILURE)
1072 return FAILURE;
1073 c->ts = *ts;
1074 c->ts.type = BT_DERIVED;
1075 c->attr.access = ACCESS_PRIVATE;
1076 c->ts.u.derived = ts->u.derived;
1077 c->attr.pointer = attr->pointer || attr->dummy;
1078 c->attr.allocatable = attr->allocatable;
1079 c->attr.dimension = attr->dimension;
1080 c->attr.abstract = ts->u.derived->attr.abstract;
1081 c->as = (*as);
1082 c->initializer = gfc_get_expr ();
1083 c->initializer->expr_type = EXPR_NULL;
1085 /* Add component '$vindex'. */
1086 if (gfc_add_component (fclass, "$vindex", &c) == FAILURE)
1087 return FAILURE;
1088 c->ts.type = BT_INTEGER;
1089 c->ts.kind = 4;
1090 c->attr.access = ACCESS_PRIVATE;
1091 c->initializer = gfc_int_expr (0);
1094 fclass->attr.extension = 1;
1095 fclass->attr.is_class = 1;
1096 ts->u.derived = fclass;
1097 attr->allocatable = attr->pointer = attr->dimension = 0;
1098 (*as) = NULL; /* XXX */
1099 return SUCCESS;
1102 /* Function called by variable_decl() that adds a name to the symbol table. */
1104 static gfc_try
1105 build_sym (const char *name, gfc_charlen *cl,
1106 gfc_array_spec **as, locus *var_locus)
1108 symbol_attribute attr;
1109 gfc_symbol *sym;
1111 if (gfc_get_symbol (name, NULL, &sym))
1112 return FAILURE;
1114 /* Start updating the symbol table. Add basic type attribute if present. */
1115 if (current_ts.type != BT_UNKNOWN
1116 && (sym->attr.implicit_type == 0
1117 || !gfc_compare_types (&sym->ts, &current_ts))
1118 && gfc_add_type (sym, &current_ts, var_locus) == FAILURE)
1119 return FAILURE;
1121 if (sym->ts.type == BT_CHARACTER)
1122 sym->ts.u.cl = cl;
1124 /* Add dimension attribute if present. */
1125 if (gfc_set_array_spec (sym, *as, var_locus) == FAILURE)
1126 return FAILURE;
1127 *as = NULL;
1129 /* Add attribute to symbol. The copy is so that we can reset the
1130 dimension attribute. */
1131 attr = current_attr;
1132 attr.dimension = 0;
1134 if (gfc_copy_attr (&sym->attr, &attr, var_locus) == FAILURE)
1135 return FAILURE;
1137 /* Finish any work that may need to be done for the binding label,
1138 if it's a bind(c). The bind(c) attr is found before the symbol
1139 is made, and before the symbol name (for data decls), so the
1140 current_ts is holding the binding label, or nothing if the
1141 name= attr wasn't given. Therefore, test here if we're dealing
1142 with a bind(c) and make sure the binding label is set correctly. */
1143 if (sym->attr.is_bind_c == 1)
1145 if (sym->binding_label[0] == '\0')
1147 /* Set the binding label and verify that if a NAME= was specified
1148 then only one identifier was in the entity-decl-list. */
1149 if (set_binding_label (sym->binding_label, sym->name,
1150 num_idents_on_line) == FAILURE)
1151 return FAILURE;
1155 /* See if we know we're in a common block, and if it's a bind(c)
1156 common then we need to make sure we're an interoperable type. */
1157 if (sym->attr.in_common == 1)
1159 /* Test the common block object. */
1160 if (sym->common_block != NULL && sym->common_block->is_bind_c == 1
1161 && sym->ts.is_c_interop != 1)
1163 gfc_error_now ("Variable '%s' in common block '%s' at %C "
1164 "must be declared with a C interoperable "
1165 "kind since common block '%s' is BIND(C)",
1166 sym->name, sym->common_block->name,
1167 sym->common_block->name);
1168 gfc_clear_error ();
1172 sym->attr.implied_index = 0;
1174 if (sym->ts.type == BT_CLASS)
1175 encapsulate_class_symbol (&sym->ts, &sym->attr, &sym->as);
1177 return SUCCESS;
1181 /* Set character constant to the given length. The constant will be padded or
1182 truncated. If we're inside an array constructor without a typespec, we
1183 additionally check that all elements have the same length; check_len -1
1184 means no checking. */
1186 void
1187 gfc_set_constant_character_len (int len, gfc_expr *expr, int check_len)
1189 gfc_char_t *s;
1190 int slen;
1192 gcc_assert (expr->expr_type == EXPR_CONSTANT);
1193 gcc_assert (expr->ts.type == BT_CHARACTER);
1195 slen = expr->value.character.length;
1196 if (len != slen)
1198 s = gfc_get_wide_string (len + 1);
1199 memcpy (s, expr->value.character.string,
1200 MIN (len, slen) * sizeof (gfc_char_t));
1201 if (len > slen)
1202 gfc_wide_memset (&s[slen], ' ', len - slen);
1204 if (gfc_option.warn_character_truncation && slen > len)
1205 gfc_warning_now ("CHARACTER expression at %L is being truncated "
1206 "(%d/%d)", &expr->where, slen, len);
1208 /* Apply the standard by 'hand' otherwise it gets cleared for
1209 initializers. */
1210 if (check_len != -1 && slen != check_len
1211 && !(gfc_option.allow_std & GFC_STD_GNU))
1212 gfc_error_now ("The CHARACTER elements of the array constructor "
1213 "at %L must have the same length (%d/%d)",
1214 &expr->where, slen, check_len);
1216 s[len] = '\0';
1217 gfc_free (expr->value.character.string);
1218 expr->value.character.string = s;
1219 expr->value.character.length = len;
1224 /* Function to create and update the enumerator history
1225 using the information passed as arguments.
1226 Pointer "max_enum" is also updated, to point to
1227 enum history node containing largest initializer.
1229 SYM points to the symbol node of enumerator.
1230 INIT points to its enumerator value. */
1232 static void
1233 create_enum_history (gfc_symbol *sym, gfc_expr *init)
1235 enumerator_history *new_enum_history;
1236 gcc_assert (sym != NULL && init != NULL);
1238 new_enum_history = XCNEW (enumerator_history);
1240 new_enum_history->sym = sym;
1241 new_enum_history->initializer = init;
1242 new_enum_history->next = NULL;
1244 if (enum_history == NULL)
1246 enum_history = new_enum_history;
1247 max_enum = enum_history;
1249 else
1251 new_enum_history->next = enum_history;
1252 enum_history = new_enum_history;
1254 if (mpz_cmp (max_enum->initializer->value.integer,
1255 new_enum_history->initializer->value.integer) < 0)
1256 max_enum = new_enum_history;
1261 /* Function to free enum kind history. */
1263 void
1264 gfc_free_enum_history (void)
1266 enumerator_history *current = enum_history;
1267 enumerator_history *next;
1269 while (current != NULL)
1271 next = current->next;
1272 gfc_free (current);
1273 current = next;
1275 max_enum = NULL;
1276 enum_history = NULL;
1280 /* Function called by variable_decl() that adds an initialization
1281 expression to a symbol. */
1283 static gfc_try
1284 add_init_expr_to_sym (const char *name, gfc_expr **initp, locus *var_locus)
1286 symbol_attribute attr;
1287 gfc_symbol *sym;
1288 gfc_expr *init;
1290 init = *initp;
1291 if (find_special (name, &sym, false))
1292 return FAILURE;
1294 attr = sym->attr;
1296 /* If this symbol is confirming an implicit parameter type,
1297 then an initialization expression is not allowed. */
1298 if (attr.flavor == FL_PARAMETER
1299 && sym->value != NULL
1300 && *initp != NULL)
1302 gfc_error ("Initializer not allowed for PARAMETER '%s' at %C",
1303 sym->name);
1304 return FAILURE;
1307 if (init == NULL)
1309 /* An initializer is required for PARAMETER declarations. */
1310 if (attr.flavor == FL_PARAMETER)
1312 gfc_error ("PARAMETER at %L is missing an initializer", var_locus);
1313 return FAILURE;
1316 else
1318 /* If a variable appears in a DATA block, it cannot have an
1319 initializer. */
1320 if (sym->attr.data)
1322 gfc_error ("Variable '%s' at %C with an initializer already "
1323 "appears in a DATA statement", sym->name);
1324 return FAILURE;
1327 /* Check if the assignment can happen. This has to be put off
1328 until later for a derived type variable. */
1329 if (sym->ts.type != BT_DERIVED && init->ts.type != BT_DERIVED
1330 && sym->ts.type != BT_CLASS && init->ts.type != BT_CLASS
1331 && gfc_check_assign_symbol (sym, init) == FAILURE)
1332 return FAILURE;
1334 if (sym->ts.type == BT_CHARACTER && sym->ts.u.cl
1335 && init->ts.type == BT_CHARACTER)
1337 /* Update symbol character length according initializer. */
1338 if (gfc_check_assign_symbol (sym, init) == FAILURE)
1339 return FAILURE;
1341 if (sym->ts.u.cl->length == NULL)
1343 int clen;
1344 /* If there are multiple CHARACTER variables declared on the
1345 same line, we don't want them to share the same length. */
1346 sym->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
1348 if (sym->attr.flavor == FL_PARAMETER)
1350 if (init->expr_type == EXPR_CONSTANT)
1352 clen = init->value.character.length;
1353 sym->ts.u.cl->length = gfc_int_expr (clen);
1355 else if (init->expr_type == EXPR_ARRAY)
1357 gfc_expr *p = init->value.constructor->expr;
1358 clen = p->value.character.length;
1359 sym->ts.u.cl->length = gfc_int_expr (clen);
1361 else if (init->ts.u.cl && init->ts.u.cl->length)
1362 sym->ts.u.cl->length =
1363 gfc_copy_expr (sym->value->ts.u.cl->length);
1366 /* Update initializer character length according symbol. */
1367 else if (sym->ts.u.cl->length->expr_type == EXPR_CONSTANT)
1369 int len = mpz_get_si (sym->ts.u.cl->length->value.integer);
1370 gfc_constructor * p;
1372 if (init->expr_type == EXPR_CONSTANT)
1373 gfc_set_constant_character_len (len, init, -1);
1374 else if (init->expr_type == EXPR_ARRAY)
1376 /* Build a new charlen to prevent simplification from
1377 deleting the length before it is resolved. */
1378 init->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
1379 init->ts.u.cl->length = gfc_copy_expr (sym->ts.u.cl->length);
1381 for (p = init->value.constructor; p; p = p->next)
1382 gfc_set_constant_character_len (len, p->expr, -1);
1387 /* Need to check if the expression we initialized this
1388 to was one of the iso_c_binding named constants. If so,
1389 and we're a parameter (constant), let it be iso_c.
1390 For example:
1391 integer(c_int), parameter :: my_int = c_int
1392 integer(my_int) :: my_int_2
1393 If we mark my_int as iso_c (since we can see it's value
1394 is equal to one of the named constants), then my_int_2
1395 will be considered C interoperable. */
1396 if (sym->ts.type != BT_CHARACTER && sym->ts.type != BT_DERIVED)
1398 sym->ts.is_iso_c |= init->ts.is_iso_c;
1399 sym->ts.is_c_interop |= init->ts.is_c_interop;
1400 /* attr bits needed for module files. */
1401 sym->attr.is_iso_c |= init->ts.is_iso_c;
1402 sym->attr.is_c_interop |= init->ts.is_c_interop;
1403 if (init->ts.is_iso_c)
1404 sym->ts.f90_type = init->ts.f90_type;
1407 /* Add initializer. Make sure we keep the ranks sane. */
1408 if (sym->attr.dimension && init->rank == 0)
1410 mpz_t size;
1411 gfc_expr *array;
1412 gfc_constructor *c;
1413 int n;
1414 if (sym->attr.flavor == FL_PARAMETER
1415 && init->expr_type == EXPR_CONSTANT
1416 && spec_size (sym->as, &size) == SUCCESS
1417 && mpz_cmp_si (size, 0) > 0)
1419 array = gfc_start_constructor (init->ts.type, init->ts.kind,
1420 &init->where);
1422 array->value.constructor = c = NULL;
1423 for (n = 0; n < (int)mpz_get_si (size); n++)
1425 if (array->value.constructor == NULL)
1427 array->value.constructor = c = gfc_get_constructor ();
1428 c->expr = init;
1430 else
1432 c->next = gfc_get_constructor ();
1433 c = c->next;
1434 c->expr = gfc_copy_expr (init);
1438 array->shape = gfc_get_shape (sym->as->rank);
1439 for (n = 0; n < sym->as->rank; n++)
1440 spec_dimen_size (sym->as, n, &array->shape[n]);
1442 init = array;
1443 mpz_clear (size);
1445 init->rank = sym->as->rank;
1448 sym->value = init;
1449 if (sym->attr.save == SAVE_NONE)
1450 sym->attr.save = SAVE_IMPLICIT;
1451 *initp = NULL;
1454 return SUCCESS;
1458 /* Function called by variable_decl() that adds a name to a structure
1459 being built. */
1461 static gfc_try
1462 build_struct (const char *name, gfc_charlen *cl, gfc_expr **init,
1463 gfc_array_spec **as)
1465 gfc_component *c;
1467 /* F03:C438/C439. If the current symbol is of the same derived type that we're
1468 constructing, it must have the pointer attribute. */
1469 if ((current_ts.type == BT_DERIVED || current_ts.type == BT_CLASS)
1470 && current_ts.u.derived == gfc_current_block ()
1471 && current_attr.pointer == 0)
1473 gfc_error ("Component at %C must have the POINTER attribute");
1474 return FAILURE;
1477 if (gfc_current_block ()->attr.pointer && (*as)->rank != 0)
1479 if ((*as)->type != AS_DEFERRED && (*as)->type != AS_EXPLICIT)
1481 gfc_error ("Array component of structure at %C must have explicit "
1482 "or deferred shape");
1483 return FAILURE;
1487 if (gfc_add_component (gfc_current_block (), name, &c) == FAILURE)
1488 return FAILURE;
1490 c->ts = current_ts;
1491 if (c->ts.type == BT_CHARACTER)
1492 c->ts.u.cl = cl;
1493 c->attr = current_attr;
1495 c->initializer = *init;
1496 *init = NULL;
1498 c->as = *as;
1499 if (c->as != NULL)
1500 c->attr.dimension = 1;
1501 *as = NULL;
1503 /* Should this ever get more complicated, combine with similar section
1504 in add_init_expr_to_sym into a separate function. */
1505 if (c->ts.type == BT_CHARACTER && !c->attr.pointer && c->initializer && c->ts.u.cl
1506 && c->ts.u.cl->length && c->ts.u.cl->length->expr_type == EXPR_CONSTANT)
1508 int len;
1510 gcc_assert (c->ts.u.cl && c->ts.u.cl->length);
1511 gcc_assert (c->ts.u.cl->length->expr_type == EXPR_CONSTANT);
1512 gcc_assert (c->ts.u.cl->length->ts.type == BT_INTEGER);
1514 len = mpz_get_si (c->ts.u.cl->length->value.integer);
1516 if (c->initializer->expr_type == EXPR_CONSTANT)
1517 gfc_set_constant_character_len (len, c->initializer, -1);
1518 else if (mpz_cmp (c->ts.u.cl->length->value.integer,
1519 c->initializer->ts.u.cl->length->value.integer))
1521 bool has_ts;
1522 gfc_constructor *ctor = c->initializer->value.constructor;
1524 has_ts = (c->initializer->ts.u.cl
1525 && c->initializer->ts.u.cl->length_from_typespec);
1527 if (ctor)
1529 int first_len;
1531 /* Remember the length of the first element for checking
1532 that all elements *in the constructor* have the same
1533 length. This need not be the length of the LHS! */
1534 gcc_assert (ctor->expr->expr_type == EXPR_CONSTANT);
1535 gcc_assert (ctor->expr->ts.type == BT_CHARACTER);
1536 first_len = ctor->expr->value.character.length;
1538 for (; ctor; ctor = ctor->next)
1540 if (ctor->expr->expr_type == EXPR_CONSTANT)
1541 gfc_set_constant_character_len (len, ctor->expr,
1542 has_ts ? -1 : first_len);
1548 if (c->ts.type == BT_CLASS)
1549 encapsulate_class_symbol (&c->ts, &c->attr, &c->as);
1551 /* Check array components. */
1552 if (!c->attr.dimension)
1553 return SUCCESS;
1555 if (c->attr.pointer)
1557 if (c->as->type != AS_DEFERRED)
1559 gfc_error ("Pointer array component of structure at %C must have a "
1560 "deferred shape");
1561 return FAILURE;
1564 else if (c->attr.allocatable)
1566 if (c->as->type != AS_DEFERRED)
1568 gfc_error ("Allocatable component of structure at %C must have a "
1569 "deferred shape");
1570 return FAILURE;
1573 else
1575 if (c->as->type != AS_EXPLICIT)
1577 gfc_error ("Array component of structure at %C must have an "
1578 "explicit shape");
1579 return FAILURE;
1583 return SUCCESS;
1587 /* Match a 'NULL()', and possibly take care of some side effects. */
1589 match
1590 gfc_match_null (gfc_expr **result)
1592 gfc_symbol *sym;
1593 gfc_expr *e;
1594 match m;
1596 m = gfc_match (" null ( )");
1597 if (m != MATCH_YES)
1598 return m;
1600 /* The NULL symbol now has to be/become an intrinsic function. */
1601 if (gfc_get_symbol ("null", NULL, &sym))
1603 gfc_error ("NULL() initialization at %C is ambiguous");
1604 return MATCH_ERROR;
1607 gfc_intrinsic_symbol (sym);
1609 if (sym->attr.proc != PROC_INTRINSIC
1610 && (gfc_add_procedure (&sym->attr, PROC_INTRINSIC,
1611 sym->name, NULL) == FAILURE
1612 || gfc_add_function (&sym->attr, sym->name, NULL) == FAILURE))
1613 return MATCH_ERROR;
1615 e = gfc_get_expr ();
1616 e->where = gfc_current_locus;
1617 e->expr_type = EXPR_NULL;
1618 e->ts.type = BT_UNKNOWN;
1620 *result = e;
1622 return MATCH_YES;
1626 /* Match a variable name with an optional initializer. When this
1627 subroutine is called, a variable is expected to be parsed next.
1628 Depending on what is happening at the moment, updates either the
1629 symbol table or the current interface. */
1631 static match
1632 variable_decl (int elem)
1634 char name[GFC_MAX_SYMBOL_LEN + 1];
1635 gfc_expr *initializer, *char_len;
1636 gfc_array_spec *as;
1637 gfc_array_spec *cp_as; /* Extra copy for Cray Pointees. */
1638 gfc_charlen *cl;
1639 locus var_locus;
1640 match m;
1641 gfc_try t;
1642 gfc_symbol *sym;
1643 locus old_locus;
1645 initializer = NULL;
1646 as = NULL;
1647 cp_as = NULL;
1648 old_locus = gfc_current_locus;
1650 /* When we get here, we've just matched a list of attributes and
1651 maybe a type and a double colon. The next thing we expect to see
1652 is the name of the symbol. */
1653 m = gfc_match_name (name);
1654 if (m != MATCH_YES)
1655 goto cleanup;
1657 var_locus = gfc_current_locus;
1659 /* Now we could see the optional array spec. or character length. */
1660 m = gfc_match_array_spec (&as);
1661 if (gfc_option.flag_cray_pointer && m == MATCH_YES)
1662 cp_as = gfc_copy_array_spec (as);
1663 else if (m == MATCH_ERROR)
1664 goto cleanup;
1666 if (m == MATCH_NO)
1667 as = gfc_copy_array_spec (current_as);
1669 char_len = NULL;
1670 cl = NULL;
1672 if (current_ts.type == BT_CHARACTER)
1674 switch (match_char_length (&char_len))
1676 case MATCH_YES:
1677 cl = gfc_new_charlen (gfc_current_ns, NULL);
1679 cl->length = char_len;
1680 break;
1682 /* Non-constant lengths need to be copied after the first
1683 element. Also copy assumed lengths. */
1684 case MATCH_NO:
1685 if (elem > 1
1686 && (current_ts.u.cl->length == NULL
1687 || current_ts.u.cl->length->expr_type != EXPR_CONSTANT))
1689 cl = gfc_new_charlen (gfc_current_ns, NULL);
1690 cl->length = gfc_copy_expr (current_ts.u.cl->length);
1692 else
1693 cl = current_ts.u.cl;
1695 break;
1697 case MATCH_ERROR:
1698 goto cleanup;
1702 /* If this symbol has already shown up in a Cray Pointer declaration,
1703 then we want to set the type & bail out. */
1704 if (gfc_option.flag_cray_pointer)
1706 gfc_find_symbol (name, gfc_current_ns, 1, &sym);
1707 if (sym != NULL && sym->attr.cray_pointee)
1709 sym->ts.type = current_ts.type;
1710 sym->ts.kind = current_ts.kind;
1711 sym->ts.u.cl = cl;
1712 sym->ts.u.derived = current_ts.u.derived;
1713 sym->ts.is_c_interop = current_ts.is_c_interop;
1714 sym->ts.is_iso_c = current_ts.is_iso_c;
1715 m = MATCH_YES;
1717 /* Check to see if we have an array specification. */
1718 if (cp_as != NULL)
1720 if (sym->as != NULL)
1722 gfc_error ("Duplicate array spec for Cray pointee at %C");
1723 gfc_free_array_spec (cp_as);
1724 m = MATCH_ERROR;
1725 goto cleanup;
1727 else
1729 if (gfc_set_array_spec (sym, cp_as, &var_locus) == FAILURE)
1730 gfc_internal_error ("Couldn't set pointee array spec.");
1732 /* Fix the array spec. */
1733 m = gfc_mod_pointee_as (sym->as);
1734 if (m == MATCH_ERROR)
1735 goto cleanup;
1738 goto cleanup;
1740 else
1742 gfc_free_array_spec (cp_as);
1746 /* Procedure pointer as function result. */
1747 if (gfc_current_state () == COMP_FUNCTION
1748 && strcmp ("ppr@", gfc_current_block ()->name) == 0
1749 && strcmp (name, gfc_current_block ()->ns->proc_name->name) == 0)
1750 strcpy (name, "ppr@");
1752 if (gfc_current_state () == COMP_FUNCTION
1753 && strcmp (name, gfc_current_block ()->name) == 0
1754 && gfc_current_block ()->result
1755 && strcmp ("ppr@", gfc_current_block ()->result->name) == 0)
1756 strcpy (name, "ppr@");
1758 /* OK, we've successfully matched the declaration. Now put the
1759 symbol in the current namespace, because it might be used in the
1760 optional initialization expression for this symbol, e.g. this is
1761 perfectly legal:
1763 integer, parameter :: i = huge(i)
1765 This is only true for parameters or variables of a basic type.
1766 For components of derived types, it is not true, so we don't
1767 create a symbol for those yet. If we fail to create the symbol,
1768 bail out. */
1769 if (gfc_current_state () != COMP_DERIVED
1770 && build_sym (name, cl, &as, &var_locus) == FAILURE)
1772 m = MATCH_ERROR;
1773 goto cleanup;
1776 /* An interface body specifies all of the procedure's
1777 characteristics and these shall be consistent with those
1778 specified in the procedure definition, except that the interface
1779 may specify a procedure that is not pure if the procedure is
1780 defined to be pure(12.3.2). */
1781 if (current_ts.type == BT_DERIVED
1782 && gfc_current_ns->proc_name
1783 && gfc_current_ns->proc_name->attr.if_source == IFSRC_IFBODY
1784 && current_ts.u.derived->ns != gfc_current_ns)
1786 gfc_symtree *st;
1787 st = gfc_find_symtree (gfc_current_ns->sym_root, current_ts.u.derived->name);
1788 if (!(current_ts.u.derived->attr.imported
1789 && st != NULL
1790 && st->n.sym == current_ts.u.derived)
1791 && !gfc_current_ns->has_import_set)
1793 gfc_error ("the type of '%s' at %C has not been declared within the "
1794 "interface", name);
1795 m = MATCH_ERROR;
1796 goto cleanup;
1800 /* In functions that have a RESULT variable defined, the function
1801 name always refers to function calls. Therefore, the name is
1802 not allowed to appear in specification statements. */
1803 if (gfc_current_state () == COMP_FUNCTION
1804 && gfc_current_block () != NULL
1805 && gfc_current_block ()->result != NULL
1806 && gfc_current_block ()->result != gfc_current_block ()
1807 && strcmp (gfc_current_block ()->name, name) == 0)
1809 gfc_error ("Function name '%s' not allowed at %C", name);
1810 m = MATCH_ERROR;
1811 goto cleanup;
1814 /* We allow old-style initializations of the form
1815 integer i /2/, j(4) /3*3, 1/
1816 (if no colon has been seen). These are different from data
1817 statements in that initializers are only allowed to apply to the
1818 variable immediately preceding, i.e.
1819 integer i, j /1, 2/
1820 is not allowed. Therefore we have to do some work manually, that
1821 could otherwise be left to the matchers for DATA statements. */
1823 if (!colon_seen && gfc_match (" /") == MATCH_YES)
1825 if (gfc_notify_std (GFC_STD_GNU, "Extension: Old-style "
1826 "initialization at %C") == FAILURE)
1827 return MATCH_ERROR;
1829 return match_old_style_init (name);
1832 /* The double colon must be present in order to have initializers.
1833 Otherwise the statement is ambiguous with an assignment statement. */
1834 if (colon_seen)
1836 if (gfc_match (" =>") == MATCH_YES)
1838 if (!current_attr.pointer)
1840 gfc_error ("Initialization at %C isn't for a pointer variable");
1841 m = MATCH_ERROR;
1842 goto cleanup;
1845 m = gfc_match_null (&initializer);
1846 if (m == MATCH_NO)
1848 gfc_error ("Pointer initialization requires a NULL() at %C");
1849 m = MATCH_ERROR;
1852 if (gfc_pure (NULL))
1854 gfc_error ("Initialization of pointer at %C is not allowed in "
1855 "a PURE procedure");
1856 m = MATCH_ERROR;
1859 if (m != MATCH_YES)
1860 goto cleanup;
1863 else if (gfc_match_char ('=') == MATCH_YES)
1865 if (current_attr.pointer)
1867 gfc_error ("Pointer initialization at %C requires '=>', "
1868 "not '='");
1869 m = MATCH_ERROR;
1870 goto cleanup;
1873 m = gfc_match_init_expr (&initializer);
1874 if (m == MATCH_NO)
1876 gfc_error ("Expected an initialization expression at %C");
1877 m = MATCH_ERROR;
1880 if (current_attr.flavor != FL_PARAMETER && gfc_pure (NULL))
1882 gfc_error ("Initialization of variable at %C is not allowed in "
1883 "a PURE procedure");
1884 m = MATCH_ERROR;
1887 if (m != MATCH_YES)
1888 goto cleanup;
1892 if (initializer != NULL && current_attr.allocatable
1893 && gfc_current_state () == COMP_DERIVED)
1895 gfc_error ("Initialization of allocatable component at %C is not "
1896 "allowed");
1897 m = MATCH_ERROR;
1898 goto cleanup;
1901 /* Add the initializer. Note that it is fine if initializer is
1902 NULL here, because we sometimes also need to check if a
1903 declaration *must* have an initialization expression. */
1904 if (gfc_current_state () != COMP_DERIVED)
1905 t = add_init_expr_to_sym (name, &initializer, &var_locus);
1906 else
1908 if (current_ts.type == BT_DERIVED
1909 && !current_attr.pointer && !initializer)
1910 initializer = gfc_default_initializer (&current_ts);
1911 t = build_struct (name, cl, &initializer, &as);
1914 m = (t == SUCCESS) ? MATCH_YES : MATCH_ERROR;
1916 cleanup:
1917 /* Free stuff up and return. */
1918 gfc_free_expr (initializer);
1919 gfc_free_array_spec (as);
1921 return m;
1925 /* Match an extended-f77 "TYPESPEC*bytesize"-style kind specification.
1926 This assumes that the byte size is equal to the kind number for
1927 non-COMPLEX types, and equal to twice the kind number for COMPLEX. */
1929 match
1930 gfc_match_old_kind_spec (gfc_typespec *ts)
1932 match m;
1933 int original_kind;
1935 if (gfc_match_char ('*') != MATCH_YES)
1936 return MATCH_NO;
1938 m = gfc_match_small_literal_int (&ts->kind, NULL);
1939 if (m != MATCH_YES)
1940 return MATCH_ERROR;
1942 original_kind = ts->kind;
1944 /* Massage the kind numbers for complex types. */
1945 if (ts->type == BT_COMPLEX)
1947 if (ts->kind % 2)
1949 gfc_error ("Old-style type declaration %s*%d not supported at %C",
1950 gfc_basic_typename (ts->type), original_kind);
1951 return MATCH_ERROR;
1953 ts->kind /= 2;
1956 if (gfc_validate_kind (ts->type, ts->kind, true) < 0)
1958 gfc_error ("Old-style type declaration %s*%d not supported at %C",
1959 gfc_basic_typename (ts->type), original_kind);
1960 return MATCH_ERROR;
1963 if (gfc_notify_std (GFC_STD_GNU, "Nonstandard type declaration %s*%d at %C",
1964 gfc_basic_typename (ts->type), original_kind) == FAILURE)
1965 return MATCH_ERROR;
1967 return MATCH_YES;
1971 /* Match a kind specification. Since kinds are generally optional, we
1972 usually return MATCH_NO if something goes wrong. If a "kind="
1973 string is found, then we know we have an error. */
1975 match
1976 gfc_match_kind_spec (gfc_typespec *ts, bool kind_expr_only)
1978 locus where, loc;
1979 gfc_expr *e;
1980 match m, n;
1981 char c;
1982 const char *msg;
1984 m = MATCH_NO;
1985 n = MATCH_YES;
1986 e = NULL;
1988 where = loc = gfc_current_locus;
1990 if (kind_expr_only)
1991 goto kind_expr;
1993 if (gfc_match_char ('(') == MATCH_NO)
1994 return MATCH_NO;
1996 /* Also gobbles optional text. */
1997 if (gfc_match (" kind = ") == MATCH_YES)
1998 m = MATCH_ERROR;
2000 loc = gfc_current_locus;
2002 kind_expr:
2003 n = gfc_match_init_expr (&e);
2005 if (n != MATCH_YES)
2007 if (gfc_matching_function)
2009 /* The function kind expression might include use associated or
2010 imported parameters and try again after the specification
2011 expressions..... */
2012 if (gfc_match_char (')') != MATCH_YES)
2014 gfc_error ("Missing right parenthesis at %C");
2015 m = MATCH_ERROR;
2016 goto no_match;
2019 gfc_free_expr (e);
2020 gfc_undo_symbols ();
2021 return MATCH_YES;
2023 else
2025 /* ....or else, the match is real. */
2026 if (n == MATCH_NO)
2027 gfc_error ("Expected initialization expression at %C");
2028 if (n != MATCH_YES)
2029 return MATCH_ERROR;
2033 if (e->rank != 0)
2035 gfc_error ("Expected scalar initialization expression at %C");
2036 m = MATCH_ERROR;
2037 goto no_match;
2040 msg = gfc_extract_int (e, &ts->kind);
2042 if (msg != NULL)
2044 gfc_error (msg);
2045 m = MATCH_ERROR;
2046 goto no_match;
2049 /* Before throwing away the expression, let's see if we had a
2050 C interoperable kind (and store the fact). */
2051 if (e->ts.is_c_interop == 1)
2053 /* Mark this as c interoperable if being declared with one
2054 of the named constants from iso_c_binding. */
2055 ts->is_c_interop = e->ts.is_iso_c;
2056 ts->f90_type = e->ts.f90_type;
2059 gfc_free_expr (e);
2060 e = NULL;
2062 /* Ignore errors to this point, if we've gotten here. This means
2063 we ignore the m=MATCH_ERROR from above. */
2064 if (gfc_validate_kind (ts->type, ts->kind, true) < 0)
2066 gfc_error ("Kind %d not supported for type %s at %C", ts->kind,
2067 gfc_basic_typename (ts->type));
2068 gfc_current_locus = where;
2069 return MATCH_ERROR;
2072 /* Warn if, e.g., c_int is used for a REAL variable, but not
2073 if, e.g., c_double is used for COMPLEX as the standard
2074 explicitly says that the kind type parameter for complex and real
2075 variable is the same, i.e. c_float == c_float_complex. */
2076 if (ts->f90_type != BT_UNKNOWN && ts->f90_type != ts->type
2077 && !((ts->f90_type == BT_REAL && ts->type == BT_COMPLEX)
2078 || (ts->f90_type == BT_COMPLEX && ts->type == BT_REAL)))
2079 gfc_warning_now ("C kind type parameter is for type %s but type at %L "
2080 "is %s", gfc_basic_typename (ts->f90_type), &where,
2081 gfc_basic_typename (ts->type));
2083 gfc_gobble_whitespace ();
2084 if ((c = gfc_next_ascii_char ()) != ')'
2085 && (ts->type != BT_CHARACTER || c != ','))
2087 if (ts->type == BT_CHARACTER)
2088 gfc_error ("Missing right parenthesis or comma at %C");
2089 else
2090 gfc_error ("Missing right parenthesis at %C");
2091 m = MATCH_ERROR;
2093 else
2094 /* All tests passed. */
2095 m = MATCH_YES;
2097 if(m == MATCH_ERROR)
2098 gfc_current_locus = where;
2100 /* Return what we know from the test(s). */
2101 return m;
2103 no_match:
2104 gfc_free_expr (e);
2105 gfc_current_locus = where;
2106 return m;
2110 static match
2111 match_char_kind (int * kind, int * is_iso_c)
2113 locus where;
2114 gfc_expr *e;
2115 match m, n;
2116 const char *msg;
2118 m = MATCH_NO;
2119 e = NULL;
2120 where = gfc_current_locus;
2122 n = gfc_match_init_expr (&e);
2124 if (n != MATCH_YES && gfc_matching_function)
2126 /* The expression might include use-associated or imported
2127 parameters and try again after the specification
2128 expressions. */
2129 gfc_free_expr (e);
2130 gfc_undo_symbols ();
2131 return MATCH_YES;
2134 if (n == MATCH_NO)
2135 gfc_error ("Expected initialization expression at %C");
2136 if (n != MATCH_YES)
2137 return MATCH_ERROR;
2139 if (e->rank != 0)
2141 gfc_error ("Expected scalar initialization expression at %C");
2142 m = MATCH_ERROR;
2143 goto no_match;
2146 msg = gfc_extract_int (e, kind);
2147 *is_iso_c = e->ts.is_iso_c;
2148 if (msg != NULL)
2150 gfc_error (msg);
2151 m = MATCH_ERROR;
2152 goto no_match;
2155 gfc_free_expr (e);
2157 /* Ignore errors to this point, if we've gotten here. This means
2158 we ignore the m=MATCH_ERROR from above. */
2159 if (gfc_validate_kind (BT_CHARACTER, *kind, true) < 0)
2161 gfc_error ("Kind %d is not supported for CHARACTER at %C", *kind);
2162 m = MATCH_ERROR;
2164 else
2165 /* All tests passed. */
2166 m = MATCH_YES;
2168 if (m == MATCH_ERROR)
2169 gfc_current_locus = where;
2171 /* Return what we know from the test(s). */
2172 return m;
2174 no_match:
2175 gfc_free_expr (e);
2176 gfc_current_locus = where;
2177 return m;
2181 /* Match the various kind/length specifications in a CHARACTER
2182 declaration. We don't return MATCH_NO. */
2184 match
2185 gfc_match_char_spec (gfc_typespec *ts)
2187 int kind, seen_length, is_iso_c;
2188 gfc_charlen *cl;
2189 gfc_expr *len;
2190 match m;
2192 len = NULL;
2193 seen_length = 0;
2194 kind = 0;
2195 is_iso_c = 0;
2197 /* Try the old-style specification first. */
2198 old_char_selector = 0;
2200 m = match_char_length (&len);
2201 if (m != MATCH_NO)
2203 if (m == MATCH_YES)
2204 old_char_selector = 1;
2205 seen_length = 1;
2206 goto done;
2209 m = gfc_match_char ('(');
2210 if (m != MATCH_YES)
2212 m = MATCH_YES; /* Character without length is a single char. */
2213 goto done;
2216 /* Try the weird case: ( KIND = <int> [ , LEN = <len-param> ] ). */
2217 if (gfc_match (" kind =") == MATCH_YES)
2219 m = match_char_kind (&kind, &is_iso_c);
2221 if (m == MATCH_ERROR)
2222 goto done;
2223 if (m == MATCH_NO)
2224 goto syntax;
2226 if (gfc_match (" , len =") == MATCH_NO)
2227 goto rparen;
2229 m = char_len_param_value (&len);
2230 if (m == MATCH_NO)
2231 goto syntax;
2232 if (m == MATCH_ERROR)
2233 goto done;
2234 seen_length = 1;
2236 goto rparen;
2239 /* Try to match "LEN = <len-param>" or "LEN = <len-param>, KIND = <int>". */
2240 if (gfc_match (" len =") == MATCH_YES)
2242 m = char_len_param_value (&len);
2243 if (m == MATCH_NO)
2244 goto syntax;
2245 if (m == MATCH_ERROR)
2246 goto done;
2247 seen_length = 1;
2249 if (gfc_match_char (')') == MATCH_YES)
2250 goto done;
2252 if (gfc_match (" , kind =") != MATCH_YES)
2253 goto syntax;
2255 if (match_char_kind (&kind, &is_iso_c) == MATCH_ERROR)
2256 goto done;
2258 goto rparen;
2261 /* Try to match ( <len-param> ) or ( <len-param> , [ KIND = ] <int> ). */
2262 m = char_len_param_value (&len);
2263 if (m == MATCH_NO)
2264 goto syntax;
2265 if (m == MATCH_ERROR)
2266 goto done;
2267 seen_length = 1;
2269 m = gfc_match_char (')');
2270 if (m == MATCH_YES)
2271 goto done;
2273 if (gfc_match_char (',') != MATCH_YES)
2274 goto syntax;
2276 gfc_match (" kind ="); /* Gobble optional text. */
2278 m = match_char_kind (&kind, &is_iso_c);
2279 if (m == MATCH_ERROR)
2280 goto done;
2281 if (m == MATCH_NO)
2282 goto syntax;
2284 rparen:
2285 /* Require a right-paren at this point. */
2286 m = gfc_match_char (')');
2287 if (m == MATCH_YES)
2288 goto done;
2290 syntax:
2291 gfc_error ("Syntax error in CHARACTER declaration at %C");
2292 m = MATCH_ERROR;
2293 gfc_free_expr (len);
2294 return m;
2296 done:
2297 /* Deal with character functions after USE and IMPORT statements. */
2298 if (gfc_matching_function)
2300 gfc_free_expr (len);
2301 gfc_undo_symbols ();
2302 return MATCH_YES;
2305 if (m != MATCH_YES)
2307 gfc_free_expr (len);
2308 return m;
2311 /* Do some final massaging of the length values. */
2312 cl = gfc_new_charlen (gfc_current_ns, NULL);
2314 if (seen_length == 0)
2315 cl->length = gfc_int_expr (1);
2316 else
2317 cl->length = len;
2319 ts->u.cl = cl;
2320 ts->kind = kind == 0 ? gfc_default_character_kind : kind;
2322 /* We have to know if it was a c interoperable kind so we can
2323 do accurate type checking of bind(c) procs, etc. */
2324 if (kind != 0)
2325 /* Mark this as c interoperable if being declared with one
2326 of the named constants from iso_c_binding. */
2327 ts->is_c_interop = is_iso_c;
2328 else if (len != NULL)
2329 /* Here, we might have parsed something such as: character(c_char)
2330 In this case, the parsing code above grabs the c_char when
2331 looking for the length (line 1690, roughly). it's the last
2332 testcase for parsing the kind params of a character variable.
2333 However, it's not actually the length. this seems like it
2334 could be an error.
2335 To see if the user used a C interop kind, test the expr
2336 of the so called length, and see if it's C interoperable. */
2337 ts->is_c_interop = len->ts.is_iso_c;
2339 return MATCH_YES;
2343 /* Matches a declaration-type-spec (F03:R502). If successful, sets the ts
2344 structure to the matched specification. This is necessary for FUNCTION and
2345 IMPLICIT statements.
2347 If implicit_flag is nonzero, then we don't check for the optional
2348 kind specification. Not doing so is needed for matching an IMPLICIT
2349 statement correctly. */
2351 match
2352 gfc_match_decl_type_spec (gfc_typespec *ts, int implicit_flag)
2354 char name[GFC_MAX_SYMBOL_LEN + 1];
2355 gfc_symbol *sym;
2356 match m;
2357 char c;
2358 bool seen_deferred_kind;
2360 /* A belt and braces check that the typespec is correctly being treated
2361 as a deferred characteristic association. */
2362 seen_deferred_kind = (gfc_current_state () == COMP_FUNCTION)
2363 && (gfc_current_block ()->result->ts.kind == -1)
2364 && (ts->kind == -1);
2365 gfc_clear_ts (ts);
2366 if (seen_deferred_kind)
2367 ts->kind = -1;
2369 /* Clear the current binding label, in case one is given. */
2370 curr_binding_label[0] = '\0';
2372 if (gfc_match (" byte") == MATCH_YES)
2374 if (gfc_notify_std (GFC_STD_GNU, "Extension: BYTE type at %C")
2375 == FAILURE)
2376 return MATCH_ERROR;
2378 if (gfc_validate_kind (BT_INTEGER, 1, true) < 0)
2380 gfc_error ("BYTE type used at %C "
2381 "is not available on the target machine");
2382 return MATCH_ERROR;
2385 ts->type = BT_INTEGER;
2386 ts->kind = 1;
2387 return MATCH_YES;
2390 if (gfc_match (" integer") == MATCH_YES)
2392 ts->type = BT_INTEGER;
2393 ts->kind = gfc_default_integer_kind;
2394 goto get_kind;
2397 if (gfc_match (" character") == MATCH_YES)
2399 ts->type = BT_CHARACTER;
2400 if (implicit_flag == 0)
2401 return gfc_match_char_spec (ts);
2402 else
2403 return MATCH_YES;
2406 if (gfc_match (" real") == MATCH_YES)
2408 ts->type = BT_REAL;
2409 ts->kind = gfc_default_real_kind;
2410 goto get_kind;
2413 if (gfc_match (" double precision") == MATCH_YES)
2415 ts->type = BT_REAL;
2416 ts->kind = gfc_default_double_kind;
2417 return MATCH_YES;
2420 if (gfc_match (" complex") == MATCH_YES)
2422 ts->type = BT_COMPLEX;
2423 ts->kind = gfc_default_complex_kind;
2424 goto get_kind;
2427 if (gfc_match (" double complex") == MATCH_YES)
2429 if (gfc_notify_std (GFC_STD_GNU, "DOUBLE COMPLEX at %C does not "
2430 "conform to the Fortran 95 standard") == FAILURE)
2431 return MATCH_ERROR;
2433 ts->type = BT_COMPLEX;
2434 ts->kind = gfc_default_double_kind;
2435 return MATCH_YES;
2438 if (gfc_match (" logical") == MATCH_YES)
2440 ts->type = BT_LOGICAL;
2441 ts->kind = gfc_default_logical_kind;
2442 goto get_kind;
2445 m = gfc_match (" type ( %n )", name);
2446 if (m == MATCH_YES)
2447 ts->type = BT_DERIVED;
2448 else
2450 m = gfc_match (" class ( %n )", name);
2451 if (m != MATCH_YES)
2452 return m;
2453 ts->type = BT_CLASS;
2455 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: CLASS statement at %C")
2456 == FAILURE)
2457 return MATCH_ERROR;
2460 /* Defer association of the derived type until the end of the
2461 specification block. However, if the derived type can be
2462 found, add it to the typespec. */
2463 if (gfc_matching_function)
2465 ts->u.derived = NULL;
2466 if (gfc_current_state () != COMP_INTERFACE
2467 && !gfc_find_symbol (name, NULL, 1, &sym) && sym)
2468 ts->u.derived = sym;
2469 return MATCH_YES;
2472 /* Search for the name but allow the components to be defined later. If
2473 type = -1, this typespec has been seen in a function declaration but
2474 the type could not be accessed at that point. */
2475 sym = NULL;
2476 if (ts->kind != -1 && gfc_get_ha_symbol (name, &sym))
2478 gfc_error ("Type name '%s' at %C is ambiguous", name);
2479 return MATCH_ERROR;
2481 else if (ts->kind == -1)
2483 int iface = gfc_state_stack->previous->state != COMP_INTERFACE
2484 || gfc_current_ns->has_import_set;
2485 if (gfc_find_symbol (name, NULL, iface, &sym))
2487 gfc_error ("Type name '%s' at %C is ambiguous", name);
2488 return MATCH_ERROR;
2491 ts->kind = 0;
2492 if (sym == NULL)
2493 return MATCH_NO;
2496 if (sym->attr.flavor != FL_DERIVED
2497 && gfc_add_flavor (&sym->attr, FL_DERIVED, sym->name, NULL) == FAILURE)
2498 return MATCH_ERROR;
2500 gfc_set_sym_referenced (sym);
2501 ts->u.derived = sym;
2503 return MATCH_YES;
2505 get_kind:
2506 /* For all types except double, derived and character, look for an
2507 optional kind specifier. MATCH_NO is actually OK at this point. */
2508 if (implicit_flag == 1)
2509 return MATCH_YES;
2511 if (gfc_current_form == FORM_FREE)
2513 c = gfc_peek_ascii_char ();
2514 if (!gfc_is_whitespace (c) && c != '*' && c != '('
2515 && c != ':' && c != ',')
2516 return MATCH_NO;
2519 m = gfc_match_kind_spec (ts, false);
2520 if (m == MATCH_NO && ts->type != BT_CHARACTER)
2521 m = gfc_match_old_kind_spec (ts);
2523 /* Defer association of the KIND expression of function results
2524 until after USE and IMPORT statements. */
2525 if ((gfc_current_state () == COMP_NONE && gfc_error_flag_test ())
2526 || gfc_matching_function)
2527 return MATCH_YES;
2529 if (m == MATCH_NO)
2530 m = MATCH_YES; /* No kind specifier found. */
2532 return m;
2536 /* Match an IMPLICIT NONE statement. Actually, this statement is
2537 already matched in parse.c, or we would not end up here in the
2538 first place. So the only thing we need to check, is if there is
2539 trailing garbage. If not, the match is successful. */
2541 match
2542 gfc_match_implicit_none (void)
2544 return (gfc_match_eos () == MATCH_YES) ? MATCH_YES : MATCH_NO;
2548 /* Match the letter range(s) of an IMPLICIT statement. */
2550 static match
2551 match_implicit_range (void)
2553 char c, c1, c2;
2554 int inner;
2555 locus cur_loc;
2557 cur_loc = gfc_current_locus;
2559 gfc_gobble_whitespace ();
2560 c = gfc_next_ascii_char ();
2561 if (c != '(')
2563 gfc_error ("Missing character range in IMPLICIT at %C");
2564 goto bad;
2567 inner = 1;
2568 while (inner)
2570 gfc_gobble_whitespace ();
2571 c1 = gfc_next_ascii_char ();
2572 if (!ISALPHA (c1))
2573 goto bad;
2575 gfc_gobble_whitespace ();
2576 c = gfc_next_ascii_char ();
2578 switch (c)
2580 case ')':
2581 inner = 0; /* Fall through. */
2583 case ',':
2584 c2 = c1;
2585 break;
2587 case '-':
2588 gfc_gobble_whitespace ();
2589 c2 = gfc_next_ascii_char ();
2590 if (!ISALPHA (c2))
2591 goto bad;
2593 gfc_gobble_whitespace ();
2594 c = gfc_next_ascii_char ();
2596 if ((c != ',') && (c != ')'))
2597 goto bad;
2598 if (c == ')')
2599 inner = 0;
2601 break;
2603 default:
2604 goto bad;
2607 if (c1 > c2)
2609 gfc_error ("Letters must be in alphabetic order in "
2610 "IMPLICIT statement at %C");
2611 goto bad;
2614 /* See if we can add the newly matched range to the pending
2615 implicits from this IMPLICIT statement. We do not check for
2616 conflicts with whatever earlier IMPLICIT statements may have
2617 set. This is done when we've successfully finished matching
2618 the current one. */
2619 if (gfc_add_new_implicit_range (c1, c2) != SUCCESS)
2620 goto bad;
2623 return MATCH_YES;
2625 bad:
2626 gfc_syntax_error (ST_IMPLICIT);
2628 gfc_current_locus = cur_loc;
2629 return MATCH_ERROR;
2633 /* Match an IMPLICIT statement, storing the types for
2634 gfc_set_implicit() if the statement is accepted by the parser.
2635 There is a strange looking, but legal syntactic construction
2636 possible. It looks like:
2638 IMPLICIT INTEGER (a-b) (c-d)
2640 This is legal if "a-b" is a constant expression that happens to
2641 equal one of the legal kinds for integers. The real problem
2642 happens with an implicit specification that looks like:
2644 IMPLICIT INTEGER (a-b)
2646 In this case, a typespec matcher that is "greedy" (as most of the
2647 matchers are) gobbles the character range as a kindspec, leaving
2648 nothing left. We therefore have to go a bit more slowly in the
2649 matching process by inhibiting the kindspec checking during
2650 typespec matching and checking for a kind later. */
2652 match
2653 gfc_match_implicit (void)
2655 gfc_typespec ts;
2656 locus cur_loc;
2657 char c;
2658 match m;
2660 gfc_clear_ts (&ts);
2662 /* We don't allow empty implicit statements. */
2663 if (gfc_match_eos () == MATCH_YES)
2665 gfc_error ("Empty IMPLICIT statement at %C");
2666 return MATCH_ERROR;
2671 /* First cleanup. */
2672 gfc_clear_new_implicit ();
2674 /* A basic type is mandatory here. */
2675 m = gfc_match_decl_type_spec (&ts, 1);
2676 if (m == MATCH_ERROR)
2677 goto error;
2678 if (m == MATCH_NO)
2679 goto syntax;
2681 cur_loc = gfc_current_locus;
2682 m = match_implicit_range ();
2684 if (m == MATCH_YES)
2686 /* We may have <TYPE> (<RANGE>). */
2687 gfc_gobble_whitespace ();
2688 c = gfc_next_ascii_char ();
2689 if ((c == '\n') || (c == ','))
2691 /* Check for CHARACTER with no length parameter. */
2692 if (ts.type == BT_CHARACTER && !ts.u.cl)
2694 ts.kind = gfc_default_character_kind;
2695 ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
2696 ts.u.cl->length = gfc_int_expr (1);
2699 /* Record the Successful match. */
2700 if (gfc_merge_new_implicit (&ts) != SUCCESS)
2701 return MATCH_ERROR;
2702 continue;
2705 gfc_current_locus = cur_loc;
2708 /* Discard the (incorrectly) matched range. */
2709 gfc_clear_new_implicit ();
2711 /* Last chance -- check <TYPE> <SELECTOR> (<RANGE>). */
2712 if (ts.type == BT_CHARACTER)
2713 m = gfc_match_char_spec (&ts);
2714 else
2716 m = gfc_match_kind_spec (&ts, false);
2717 if (m == MATCH_NO)
2719 m = gfc_match_old_kind_spec (&ts);
2720 if (m == MATCH_ERROR)
2721 goto error;
2722 if (m == MATCH_NO)
2723 goto syntax;
2726 if (m == MATCH_ERROR)
2727 goto error;
2729 m = match_implicit_range ();
2730 if (m == MATCH_ERROR)
2731 goto error;
2732 if (m == MATCH_NO)
2733 goto syntax;
2735 gfc_gobble_whitespace ();
2736 c = gfc_next_ascii_char ();
2737 if ((c != '\n') && (c != ','))
2738 goto syntax;
2740 if (gfc_merge_new_implicit (&ts) != SUCCESS)
2741 return MATCH_ERROR;
2743 while (c == ',');
2745 return MATCH_YES;
2747 syntax:
2748 gfc_syntax_error (ST_IMPLICIT);
2750 error:
2751 return MATCH_ERROR;
2755 match
2756 gfc_match_import (void)
2758 char name[GFC_MAX_SYMBOL_LEN + 1];
2759 match m;
2760 gfc_symbol *sym;
2761 gfc_symtree *st;
2763 if (gfc_current_ns->proc_name == NULL
2764 || gfc_current_ns->proc_name->attr.if_source != IFSRC_IFBODY)
2766 gfc_error ("IMPORT statement at %C only permitted in "
2767 "an INTERFACE body");
2768 return MATCH_ERROR;
2771 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: IMPORT statement at %C")
2772 == FAILURE)
2773 return MATCH_ERROR;
2775 if (gfc_match_eos () == MATCH_YES)
2777 /* All host variables should be imported. */
2778 gfc_current_ns->has_import_set = 1;
2779 return MATCH_YES;
2782 if (gfc_match (" ::") == MATCH_YES)
2784 if (gfc_match_eos () == MATCH_YES)
2786 gfc_error ("Expecting list of named entities at %C");
2787 return MATCH_ERROR;
2791 for(;;)
2793 m = gfc_match (" %n", name);
2794 switch (m)
2796 case MATCH_YES:
2797 if (gfc_current_ns->parent != NULL
2798 && gfc_find_symbol (name, gfc_current_ns->parent, 1, &sym))
2800 gfc_error ("Type name '%s' at %C is ambiguous", name);
2801 return MATCH_ERROR;
2803 else if (gfc_current_ns->proc_name->ns->parent != NULL
2804 && gfc_find_symbol (name,
2805 gfc_current_ns->proc_name->ns->parent,
2806 1, &sym))
2808 gfc_error ("Type name '%s' at %C is ambiguous", name);
2809 return MATCH_ERROR;
2812 if (sym == NULL)
2814 gfc_error ("Cannot IMPORT '%s' from host scoping unit "
2815 "at %C - does not exist.", name);
2816 return MATCH_ERROR;
2819 if (gfc_find_symtree (gfc_current_ns->sym_root,name))
2821 gfc_warning ("'%s' is already IMPORTed from host scoping unit "
2822 "at %C.", name);
2823 goto next_item;
2826 st = gfc_new_symtree (&gfc_current_ns->sym_root, sym->name);
2827 st->n.sym = sym;
2828 sym->refs++;
2829 sym->attr.imported = 1;
2831 goto next_item;
2833 case MATCH_NO:
2834 break;
2836 case MATCH_ERROR:
2837 return MATCH_ERROR;
2840 next_item:
2841 if (gfc_match_eos () == MATCH_YES)
2842 break;
2843 if (gfc_match_char (',') != MATCH_YES)
2844 goto syntax;
2847 return MATCH_YES;
2849 syntax:
2850 gfc_error ("Syntax error in IMPORT statement at %C");
2851 return MATCH_ERROR;
2855 /* A minimal implementation of gfc_match without whitespace, escape
2856 characters or variable arguments. Returns true if the next
2857 characters match the TARGET template exactly. */
2859 static bool
2860 match_string_p (const char *target)
2862 const char *p;
2864 for (p = target; *p; p++)
2865 if ((char) gfc_next_ascii_char () != *p)
2866 return false;
2867 return true;
2870 /* Matches an attribute specification including array specs. If
2871 successful, leaves the variables current_attr and current_as
2872 holding the specification. Also sets the colon_seen variable for
2873 later use by matchers associated with initializations.
2875 This subroutine is a little tricky in the sense that we don't know
2876 if we really have an attr-spec until we hit the double colon.
2877 Until that time, we can only return MATCH_NO. This forces us to
2878 check for duplicate specification at this level. */
2880 static match
2881 match_attr_spec (void)
2883 /* Modifiers that can exist in a type statement. */
2884 typedef enum
2885 { GFC_DECL_BEGIN = 0,
2886 DECL_ALLOCATABLE = GFC_DECL_BEGIN, DECL_DIMENSION, DECL_EXTERNAL,
2887 DECL_IN, DECL_OUT, DECL_INOUT, DECL_INTRINSIC, DECL_OPTIONAL,
2888 DECL_PARAMETER, DECL_POINTER, DECL_PROTECTED, DECL_PRIVATE,
2889 DECL_PUBLIC, DECL_SAVE, DECL_TARGET, DECL_VALUE, DECL_VOLATILE,
2890 DECL_IS_BIND_C, DECL_NONE,
2891 GFC_DECL_END /* Sentinel */
2893 decl_types;
2895 /* GFC_DECL_END is the sentinel, index starts at 0. */
2896 #define NUM_DECL GFC_DECL_END
2898 locus start, seen_at[NUM_DECL];
2899 int seen[NUM_DECL];
2900 unsigned int d;
2901 const char *attr;
2902 match m;
2903 gfc_try t;
2905 gfc_clear_attr (&current_attr);
2906 start = gfc_current_locus;
2908 current_as = NULL;
2909 colon_seen = 0;
2911 /* See if we get all of the keywords up to the final double colon. */
2912 for (d = GFC_DECL_BEGIN; d != GFC_DECL_END; d++)
2913 seen[d] = 0;
2915 for (;;)
2917 char ch;
2919 d = DECL_NONE;
2920 gfc_gobble_whitespace ();
2922 ch = gfc_next_ascii_char ();
2923 if (ch == ':')
2925 /* This is the successful exit condition for the loop. */
2926 if (gfc_next_ascii_char () == ':')
2927 break;
2929 else if (ch == ',')
2931 gfc_gobble_whitespace ();
2932 switch (gfc_peek_ascii_char ())
2934 case 'a':
2935 if (match_string_p ("allocatable"))
2936 d = DECL_ALLOCATABLE;
2937 break;
2939 case 'b':
2940 /* Try and match the bind(c). */
2941 m = gfc_match_bind_c (NULL, true);
2942 if (m == MATCH_YES)
2943 d = DECL_IS_BIND_C;
2944 else if (m == MATCH_ERROR)
2945 goto cleanup;
2946 break;
2948 case 'd':
2949 if (match_string_p ("dimension"))
2950 d = DECL_DIMENSION;
2951 break;
2953 case 'e':
2954 if (match_string_p ("external"))
2955 d = DECL_EXTERNAL;
2956 break;
2958 case 'i':
2959 if (match_string_p ("int"))
2961 ch = gfc_next_ascii_char ();
2962 if (ch == 'e')
2964 if (match_string_p ("nt"))
2966 /* Matched "intent". */
2967 /* TODO: Call match_intent_spec from here. */
2968 if (gfc_match (" ( in out )") == MATCH_YES)
2969 d = DECL_INOUT;
2970 else if (gfc_match (" ( in )") == MATCH_YES)
2971 d = DECL_IN;
2972 else if (gfc_match (" ( out )") == MATCH_YES)
2973 d = DECL_OUT;
2976 else if (ch == 'r')
2978 if (match_string_p ("insic"))
2980 /* Matched "intrinsic". */
2981 d = DECL_INTRINSIC;
2985 break;
2987 case 'o':
2988 if (match_string_p ("optional"))
2989 d = DECL_OPTIONAL;
2990 break;
2992 case 'p':
2993 gfc_next_ascii_char ();
2994 switch (gfc_next_ascii_char ())
2996 case 'a':
2997 if (match_string_p ("rameter"))
2999 /* Matched "parameter". */
3000 d = DECL_PARAMETER;
3002 break;
3004 case 'o':
3005 if (match_string_p ("inter"))
3007 /* Matched "pointer". */
3008 d = DECL_POINTER;
3010 break;
3012 case 'r':
3013 ch = gfc_next_ascii_char ();
3014 if (ch == 'i')
3016 if (match_string_p ("vate"))
3018 /* Matched "private". */
3019 d = DECL_PRIVATE;
3022 else if (ch == 'o')
3024 if (match_string_p ("tected"))
3026 /* Matched "protected". */
3027 d = DECL_PROTECTED;
3030 break;
3032 case 'u':
3033 if (match_string_p ("blic"))
3035 /* Matched "public". */
3036 d = DECL_PUBLIC;
3038 break;
3040 break;
3042 case 's':
3043 if (match_string_p ("save"))
3044 d = DECL_SAVE;
3045 break;
3047 case 't':
3048 if (match_string_p ("target"))
3049 d = DECL_TARGET;
3050 break;
3052 case 'v':
3053 gfc_next_ascii_char ();
3054 ch = gfc_next_ascii_char ();
3055 if (ch == 'a')
3057 if (match_string_p ("lue"))
3059 /* Matched "value". */
3060 d = DECL_VALUE;
3063 else if (ch == 'o')
3065 if (match_string_p ("latile"))
3067 /* Matched "volatile". */
3068 d = DECL_VOLATILE;
3071 break;
3075 /* No double colon and no recognizable decl_type, so assume that
3076 we've been looking at something else the whole time. */
3077 if (d == DECL_NONE)
3079 m = MATCH_NO;
3080 goto cleanup;
3083 /* Check to make sure any parens are paired up correctly. */
3084 if (gfc_match_parens () == MATCH_ERROR)
3086 m = MATCH_ERROR;
3087 goto cleanup;
3090 seen[d]++;
3091 seen_at[d] = gfc_current_locus;
3093 if (d == DECL_DIMENSION)
3095 m = gfc_match_array_spec (&current_as);
3097 if (m == MATCH_NO)
3099 gfc_error ("Missing dimension specification at %C");
3100 m = MATCH_ERROR;
3103 if (m == MATCH_ERROR)
3104 goto cleanup;
3108 /* Since we've seen a double colon, we have to be looking at an
3109 attr-spec. This means that we can now issue errors. */
3110 for (d = GFC_DECL_BEGIN; d != GFC_DECL_END; d++)
3111 if (seen[d] > 1)
3113 switch (d)
3115 case DECL_ALLOCATABLE:
3116 attr = "ALLOCATABLE";
3117 break;
3118 case DECL_DIMENSION:
3119 attr = "DIMENSION";
3120 break;
3121 case DECL_EXTERNAL:
3122 attr = "EXTERNAL";
3123 break;
3124 case DECL_IN:
3125 attr = "INTENT (IN)";
3126 break;
3127 case DECL_OUT:
3128 attr = "INTENT (OUT)";
3129 break;
3130 case DECL_INOUT:
3131 attr = "INTENT (IN OUT)";
3132 break;
3133 case DECL_INTRINSIC:
3134 attr = "INTRINSIC";
3135 break;
3136 case DECL_OPTIONAL:
3137 attr = "OPTIONAL";
3138 break;
3139 case DECL_PARAMETER:
3140 attr = "PARAMETER";
3141 break;
3142 case DECL_POINTER:
3143 attr = "POINTER";
3144 break;
3145 case DECL_PROTECTED:
3146 attr = "PROTECTED";
3147 break;
3148 case DECL_PRIVATE:
3149 attr = "PRIVATE";
3150 break;
3151 case DECL_PUBLIC:
3152 attr = "PUBLIC";
3153 break;
3154 case DECL_SAVE:
3155 attr = "SAVE";
3156 break;
3157 case DECL_TARGET:
3158 attr = "TARGET";
3159 break;
3160 case DECL_IS_BIND_C:
3161 attr = "IS_BIND_C";
3162 break;
3163 case DECL_VALUE:
3164 attr = "VALUE";
3165 break;
3166 case DECL_VOLATILE:
3167 attr = "VOLATILE";
3168 break;
3169 default:
3170 attr = NULL; /* This shouldn't happen. */
3173 gfc_error ("Duplicate %s attribute at %L", attr, &seen_at[d]);
3174 m = MATCH_ERROR;
3175 goto cleanup;
3178 /* Now that we've dealt with duplicate attributes, add the attributes
3179 to the current attribute. */
3180 for (d = GFC_DECL_BEGIN; d != GFC_DECL_END; d++)
3182 if (seen[d] == 0)
3183 continue;
3185 if (gfc_current_state () == COMP_DERIVED
3186 && d != DECL_DIMENSION && d != DECL_POINTER
3187 && d != DECL_PRIVATE && d != DECL_PUBLIC
3188 && d != DECL_NONE)
3190 if (d == DECL_ALLOCATABLE)
3192 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: ALLOCATABLE "
3193 "attribute at %C in a TYPE definition")
3194 == FAILURE)
3196 m = MATCH_ERROR;
3197 goto cleanup;
3200 else
3202 gfc_error ("Attribute at %L is not allowed in a TYPE definition",
3203 &seen_at[d]);
3204 m = MATCH_ERROR;
3205 goto cleanup;
3209 if ((d == DECL_PRIVATE || d == DECL_PUBLIC)
3210 && gfc_current_state () != COMP_MODULE)
3212 if (d == DECL_PRIVATE)
3213 attr = "PRIVATE";
3214 else
3215 attr = "PUBLIC";
3216 if (gfc_current_state () == COMP_DERIVED
3217 && gfc_state_stack->previous
3218 && gfc_state_stack->previous->state == COMP_MODULE)
3220 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Attribute %s "
3221 "at %L in a TYPE definition", attr,
3222 &seen_at[d])
3223 == FAILURE)
3225 m = MATCH_ERROR;
3226 goto cleanup;
3229 else
3231 gfc_error ("%s attribute at %L is not allowed outside of the "
3232 "specification part of a module", attr, &seen_at[d]);
3233 m = MATCH_ERROR;
3234 goto cleanup;
3238 switch (d)
3240 case DECL_ALLOCATABLE:
3241 t = gfc_add_allocatable (&current_attr, &seen_at[d]);
3242 break;
3244 case DECL_DIMENSION:
3245 t = gfc_add_dimension (&current_attr, NULL, &seen_at[d]);
3246 break;
3248 case DECL_EXTERNAL:
3249 t = gfc_add_external (&current_attr, &seen_at[d]);
3250 break;
3252 case DECL_IN:
3253 t = gfc_add_intent (&current_attr, INTENT_IN, &seen_at[d]);
3254 break;
3256 case DECL_OUT:
3257 t = gfc_add_intent (&current_attr, INTENT_OUT, &seen_at[d]);
3258 break;
3260 case DECL_INOUT:
3261 t = gfc_add_intent (&current_attr, INTENT_INOUT, &seen_at[d]);
3262 break;
3264 case DECL_INTRINSIC:
3265 t = gfc_add_intrinsic (&current_attr, &seen_at[d]);
3266 break;
3268 case DECL_OPTIONAL:
3269 t = gfc_add_optional (&current_attr, &seen_at[d]);
3270 break;
3272 case DECL_PARAMETER:
3273 t = gfc_add_flavor (&current_attr, FL_PARAMETER, NULL, &seen_at[d]);
3274 break;
3276 case DECL_POINTER:
3277 t = gfc_add_pointer (&current_attr, &seen_at[d]);
3278 break;
3280 case DECL_PROTECTED:
3281 if (gfc_current_ns->proc_name->attr.flavor != FL_MODULE)
3283 gfc_error ("PROTECTED at %C only allowed in specification "
3284 "part of a module");
3285 t = FAILURE;
3286 break;
3289 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PROTECTED "
3290 "attribute at %C")
3291 == FAILURE)
3292 t = FAILURE;
3293 else
3294 t = gfc_add_protected (&current_attr, NULL, &seen_at[d]);
3295 break;
3297 case DECL_PRIVATE:
3298 t = gfc_add_access (&current_attr, ACCESS_PRIVATE, NULL,
3299 &seen_at[d]);
3300 break;
3302 case DECL_PUBLIC:
3303 t = gfc_add_access (&current_attr, ACCESS_PUBLIC, NULL,
3304 &seen_at[d]);
3305 break;
3307 case DECL_SAVE:
3308 t = gfc_add_save (&current_attr, NULL, &seen_at[d]);
3309 break;
3311 case DECL_TARGET:
3312 t = gfc_add_target (&current_attr, &seen_at[d]);
3313 break;
3315 case DECL_IS_BIND_C:
3316 t = gfc_add_is_bind_c(&current_attr, NULL, &seen_at[d], 0);
3317 break;
3319 case DECL_VALUE:
3320 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: VALUE attribute "
3321 "at %C")
3322 == FAILURE)
3323 t = FAILURE;
3324 else
3325 t = gfc_add_value (&current_attr, NULL, &seen_at[d]);
3326 break;
3328 case DECL_VOLATILE:
3329 if (gfc_notify_std (GFC_STD_F2003,
3330 "Fortran 2003: VOLATILE attribute at %C")
3331 == FAILURE)
3332 t = FAILURE;
3333 else
3334 t = gfc_add_volatile (&current_attr, NULL, &seen_at[d]);
3335 break;
3337 default:
3338 gfc_internal_error ("match_attr_spec(): Bad attribute");
3341 if (t == FAILURE)
3343 m = MATCH_ERROR;
3344 goto cleanup;
3348 colon_seen = 1;
3349 return MATCH_YES;
3351 cleanup:
3352 gfc_current_locus = start;
3353 gfc_free_array_spec (current_as);
3354 current_as = NULL;
3355 return m;
3359 /* Set the binding label, dest_label, either with the binding label
3360 stored in the given gfc_typespec, ts, or if none was provided, it
3361 will be the symbol name in all lower case, as required by the draft
3362 (J3/04-007, section 15.4.1). If a binding label was given and
3363 there is more than one argument (num_idents), it is an error. */
3365 gfc_try
3366 set_binding_label (char *dest_label, const char *sym_name, int num_idents)
3368 if (num_idents > 1 && has_name_equals)
3370 gfc_error ("Multiple identifiers provided with "
3371 "single NAME= specifier at %C");
3372 return FAILURE;
3375 if (curr_binding_label[0] != '\0')
3377 /* Binding label given; store in temp holder til have sym. */
3378 strcpy (dest_label, curr_binding_label);
3380 else
3382 /* No binding label given, and the NAME= specifier did not exist,
3383 which means there was no NAME="". */
3384 if (sym_name != NULL && has_name_equals == 0)
3385 strcpy (dest_label, sym_name);
3388 return SUCCESS;
3392 /* Set the status of the given common block as being BIND(C) or not,
3393 depending on the given parameter, is_bind_c. */
3395 void
3396 set_com_block_bind_c (gfc_common_head *com_block, int is_bind_c)
3398 com_block->is_bind_c = is_bind_c;
3399 return;
3403 /* Verify that the given gfc_typespec is for a C interoperable type. */
3405 gfc_try
3406 verify_c_interop (gfc_typespec *ts)
3408 if (ts->type == BT_DERIVED && ts->u.derived != NULL)
3409 return (ts->u.derived->ts.is_c_interop ? SUCCESS : FAILURE);
3410 else if (ts->is_c_interop != 1)
3411 return FAILURE;
3413 return SUCCESS;
3417 /* Verify that the variables of a given common block, which has been
3418 defined with the attribute specifier bind(c), to be of a C
3419 interoperable type. Errors will be reported here, if
3420 encountered. */
3422 gfc_try
3423 verify_com_block_vars_c_interop (gfc_common_head *com_block)
3425 gfc_symbol *curr_sym = NULL;
3426 gfc_try retval = SUCCESS;
3428 curr_sym = com_block->head;
3430 /* Make sure we have at least one symbol. */
3431 if (curr_sym == NULL)
3432 return retval;
3434 /* Here we know we have a symbol, so we'll execute this loop
3435 at least once. */
3438 /* The second to last param, 1, says this is in a common block. */
3439 retval = verify_bind_c_sym (curr_sym, &(curr_sym->ts), 1, com_block);
3440 curr_sym = curr_sym->common_next;
3441 } while (curr_sym != NULL);
3443 return retval;
3447 /* Verify that a given BIND(C) symbol is C interoperable. If it is not,
3448 an appropriate error message is reported. */
3450 gfc_try
3451 verify_bind_c_sym (gfc_symbol *tmp_sym, gfc_typespec *ts,
3452 int is_in_common, gfc_common_head *com_block)
3454 bool bind_c_function = false;
3455 gfc_try retval = SUCCESS;
3457 if (tmp_sym->attr.function && tmp_sym->attr.is_bind_c)
3458 bind_c_function = true;
3460 if (tmp_sym->attr.function && tmp_sym->result != NULL)
3462 tmp_sym = tmp_sym->result;
3463 /* Make sure it wasn't an implicitly typed result. */
3464 if (tmp_sym->attr.implicit_type)
3466 gfc_warning ("Implicitly declared BIND(C) function '%s' at "
3467 "%L may not be C interoperable", tmp_sym->name,
3468 &tmp_sym->declared_at);
3469 tmp_sym->ts.f90_type = tmp_sym->ts.type;
3470 /* Mark it as C interoperable to prevent duplicate warnings. */
3471 tmp_sym->ts.is_c_interop = 1;
3472 tmp_sym->attr.is_c_interop = 1;
3476 /* Here, we know we have the bind(c) attribute, so if we have
3477 enough type info, then verify that it's a C interop kind.
3478 The info could be in the symbol already, or possibly still in
3479 the given ts (current_ts), so look in both. */
3480 if (tmp_sym->ts.type != BT_UNKNOWN || ts->type != BT_UNKNOWN)
3482 if (verify_c_interop (&(tmp_sym->ts)) != SUCCESS)
3484 /* See if we're dealing with a sym in a common block or not. */
3485 if (is_in_common == 1)
3487 gfc_warning ("Variable '%s' in common block '%s' at %L "
3488 "may not be a C interoperable "
3489 "kind though common block '%s' is BIND(C)",
3490 tmp_sym->name, com_block->name,
3491 &(tmp_sym->declared_at), com_block->name);
3493 else
3495 if (tmp_sym->ts.type == BT_DERIVED || ts->type == BT_DERIVED)
3496 gfc_error ("Type declaration '%s' at %L is not C "
3497 "interoperable but it is BIND(C)",
3498 tmp_sym->name, &(tmp_sym->declared_at));
3499 else
3500 gfc_warning ("Variable '%s' at %L "
3501 "may not be a C interoperable "
3502 "kind but it is bind(c)",
3503 tmp_sym->name, &(tmp_sym->declared_at));
3507 /* Variables declared w/in a common block can't be bind(c)
3508 since there's no way for C to see these variables, so there's
3509 semantically no reason for the attribute. */
3510 if (is_in_common == 1 && tmp_sym->attr.is_bind_c == 1)
3512 gfc_error ("Variable '%s' in common block '%s' at "
3513 "%L cannot be declared with BIND(C) "
3514 "since it is not a global",
3515 tmp_sym->name, com_block->name,
3516 &(tmp_sym->declared_at));
3517 retval = FAILURE;
3520 /* Scalar variables that are bind(c) can not have the pointer
3521 or allocatable attributes. */
3522 if (tmp_sym->attr.is_bind_c == 1)
3524 if (tmp_sym->attr.pointer == 1)
3526 gfc_error ("Variable '%s' at %L cannot have both the "
3527 "POINTER and BIND(C) attributes",
3528 tmp_sym->name, &(tmp_sym->declared_at));
3529 retval = FAILURE;
3532 if (tmp_sym->attr.allocatable == 1)
3534 gfc_error ("Variable '%s' at %L cannot have both the "
3535 "ALLOCATABLE and BIND(C) attributes",
3536 tmp_sym->name, &(tmp_sym->declared_at));
3537 retval = FAILURE;
3542 /* If it is a BIND(C) function, make sure the return value is a
3543 scalar value. The previous tests in this function made sure
3544 the type is interoperable. */
3545 if (bind_c_function && tmp_sym->as != NULL)
3546 gfc_error ("Return type of BIND(C) function '%s' at %L cannot "
3547 "be an array", tmp_sym->name, &(tmp_sym->declared_at));
3549 /* BIND(C) functions can not return a character string. */
3550 if (bind_c_function && tmp_sym->ts.type == BT_CHARACTER)
3551 if (tmp_sym->ts.u.cl == NULL || tmp_sym->ts.u.cl->length == NULL
3552 || tmp_sym->ts.u.cl->length->expr_type != EXPR_CONSTANT
3553 || mpz_cmp_si (tmp_sym->ts.u.cl->length->value.integer, 1) != 0)
3554 gfc_error ("Return type of BIND(C) function '%s' at %L cannot "
3555 "be a character string", tmp_sym->name,
3556 &(tmp_sym->declared_at));
3559 /* See if the symbol has been marked as private. If it has, make sure
3560 there is no binding label and warn the user if there is one. */
3561 if (tmp_sym->attr.access == ACCESS_PRIVATE
3562 && tmp_sym->binding_label[0] != '\0')
3563 /* Use gfc_warning_now because we won't say that the symbol fails
3564 just because of this. */
3565 gfc_warning_now ("Symbol '%s' at %L is marked PRIVATE but has been "
3566 "given the binding label '%s'", tmp_sym->name,
3567 &(tmp_sym->declared_at), tmp_sym->binding_label);
3569 return retval;
3573 /* Set the appropriate fields for a symbol that's been declared as
3574 BIND(C) (the is_bind_c flag and the binding label), and verify that
3575 the type is C interoperable. Errors are reported by the functions
3576 used to set/test these fields. */
3578 gfc_try
3579 set_verify_bind_c_sym (gfc_symbol *tmp_sym, int num_idents)
3581 gfc_try retval = SUCCESS;
3583 /* TODO: Do we need to make sure the vars aren't marked private? */
3585 /* Set the is_bind_c bit in symbol_attribute. */
3586 gfc_add_is_bind_c (&(tmp_sym->attr), tmp_sym->name, &gfc_current_locus, 0);
3588 if (set_binding_label (tmp_sym->binding_label, tmp_sym->name,
3589 num_idents) != SUCCESS)
3590 return FAILURE;
3592 return retval;
3596 /* Set the fields marking the given common block as BIND(C), including
3597 a binding label, and report any errors encountered. */
3599 gfc_try
3600 set_verify_bind_c_com_block (gfc_common_head *com_block, int num_idents)
3602 gfc_try retval = SUCCESS;
3604 /* destLabel, common name, typespec (which may have binding label). */
3605 if (set_binding_label (com_block->binding_label, com_block->name, num_idents)
3606 != SUCCESS)
3607 return FAILURE;
3609 /* Set the given common block (com_block) to being bind(c) (1). */
3610 set_com_block_bind_c (com_block, 1);
3612 return retval;
3616 /* Retrieve the list of one or more identifiers that the given bind(c)
3617 attribute applies to. */
3619 gfc_try
3620 get_bind_c_idents (void)
3622 char name[GFC_MAX_SYMBOL_LEN + 1];
3623 int num_idents = 0;
3624 gfc_symbol *tmp_sym = NULL;
3625 match found_id;
3626 gfc_common_head *com_block = NULL;
3628 if (gfc_match_name (name) == MATCH_YES)
3630 found_id = MATCH_YES;
3631 gfc_get_ha_symbol (name, &tmp_sym);
3633 else if (match_common_name (name) == MATCH_YES)
3635 found_id = MATCH_YES;
3636 com_block = gfc_get_common (name, 0);
3638 else
3640 gfc_error ("Need either entity or common block name for "
3641 "attribute specification statement at %C");
3642 return FAILURE;
3645 /* Save the current identifier and look for more. */
3648 /* Increment the number of identifiers found for this spec stmt. */
3649 num_idents++;
3651 /* Make sure we have a sym or com block, and verify that it can
3652 be bind(c). Set the appropriate field(s) and look for more
3653 identifiers. */
3654 if (tmp_sym != NULL || com_block != NULL)
3656 if (tmp_sym != NULL)
3658 if (set_verify_bind_c_sym (tmp_sym, num_idents)
3659 != SUCCESS)
3660 return FAILURE;
3662 else
3664 if (set_verify_bind_c_com_block(com_block, num_idents)
3665 != SUCCESS)
3666 return FAILURE;
3669 /* Look to see if we have another identifier. */
3670 tmp_sym = NULL;
3671 if (gfc_match_eos () == MATCH_YES)
3672 found_id = MATCH_NO;
3673 else if (gfc_match_char (',') != MATCH_YES)
3674 found_id = MATCH_NO;
3675 else if (gfc_match_name (name) == MATCH_YES)
3677 found_id = MATCH_YES;
3678 gfc_get_ha_symbol (name, &tmp_sym);
3680 else if (match_common_name (name) == MATCH_YES)
3682 found_id = MATCH_YES;
3683 com_block = gfc_get_common (name, 0);
3685 else
3687 gfc_error ("Missing entity or common block name for "
3688 "attribute specification statement at %C");
3689 return FAILURE;
3692 else
3694 gfc_internal_error ("Missing symbol");
3696 } while (found_id == MATCH_YES);
3698 /* if we get here we were successful */
3699 return SUCCESS;
3703 /* Try and match a BIND(C) attribute specification statement. */
3705 match
3706 gfc_match_bind_c_stmt (void)
3708 match found_match = MATCH_NO;
3709 gfc_typespec *ts;
3711 ts = &current_ts;
3713 /* This may not be necessary. */
3714 gfc_clear_ts (ts);
3715 /* Clear the temporary binding label holder. */
3716 curr_binding_label[0] = '\0';
3718 /* Look for the bind(c). */
3719 found_match = gfc_match_bind_c (NULL, true);
3721 if (found_match == MATCH_YES)
3723 /* Look for the :: now, but it is not required. */
3724 gfc_match (" :: ");
3726 /* Get the identifier(s) that needs to be updated. This may need to
3727 change to hand the flag(s) for the attr specified so all identifiers
3728 found can have all appropriate parts updated (assuming that the same
3729 spec stmt can have multiple attrs, such as both bind(c) and
3730 allocatable...). */
3731 if (get_bind_c_idents () != SUCCESS)
3732 /* Error message should have printed already. */
3733 return MATCH_ERROR;
3736 return found_match;
3740 /* Match a data declaration statement. */
3742 match
3743 gfc_match_data_decl (void)
3745 gfc_symbol *sym;
3746 match m;
3747 int elem;
3749 num_idents_on_line = 0;
3751 m = gfc_match_decl_type_spec (&current_ts, 0);
3752 if (m != MATCH_YES)
3753 return m;
3755 if (current_ts.type == BT_DERIVED && gfc_current_state () != COMP_DERIVED)
3757 sym = gfc_use_derived (current_ts.u.derived);
3759 if (sym == NULL)
3761 m = MATCH_ERROR;
3762 goto cleanup;
3765 current_ts.u.derived = sym;
3768 m = match_attr_spec ();
3769 if (m == MATCH_ERROR)
3771 m = MATCH_NO;
3772 goto cleanup;
3775 if (current_ts.type == BT_DERIVED && current_ts.u.derived->components == NULL
3776 && !current_ts.u.derived->attr.zero_comp)
3779 if (current_attr.pointer && gfc_current_state () == COMP_DERIVED)
3780 goto ok;
3782 gfc_find_symbol (current_ts.u.derived->name,
3783 current_ts.u.derived->ns->parent, 1, &sym);
3785 /* Any symbol that we find had better be a type definition
3786 which has its components defined. */
3787 if (sym != NULL && sym->attr.flavor == FL_DERIVED
3788 && (current_ts.u.derived->components != NULL
3789 || current_ts.u.derived->attr.zero_comp))
3790 goto ok;
3792 /* Now we have an error, which we signal, and then fix up
3793 because the knock-on is plain and simple confusing. */
3794 gfc_error_now ("Derived type at %C has not been previously defined "
3795 "and so cannot appear in a derived type definition");
3796 current_attr.pointer = 1;
3797 goto ok;
3801 /* If we have an old-style character declaration, and no new-style
3802 attribute specifications, then there a comma is optional between
3803 the type specification and the variable list. */
3804 if (m == MATCH_NO && current_ts.type == BT_CHARACTER && old_char_selector)
3805 gfc_match_char (',');
3807 /* Give the types/attributes to symbols that follow. Give the element
3808 a number so that repeat character length expressions can be copied. */
3809 elem = 1;
3810 for (;;)
3812 num_idents_on_line++;
3813 m = variable_decl (elem++);
3814 if (m == MATCH_ERROR)
3815 goto cleanup;
3816 if (m == MATCH_NO)
3817 break;
3819 if (gfc_match_eos () == MATCH_YES)
3820 goto cleanup;
3821 if (gfc_match_char (',') != MATCH_YES)
3822 break;
3825 if (gfc_error_flag_test () == 0)
3826 gfc_error ("Syntax error in data declaration at %C");
3827 m = MATCH_ERROR;
3829 gfc_free_data_all (gfc_current_ns);
3831 cleanup:
3832 gfc_free_array_spec (current_as);
3833 current_as = NULL;
3834 return m;
3838 /* Match a prefix associated with a function or subroutine
3839 declaration. If the typespec pointer is nonnull, then a typespec
3840 can be matched. Note that if nothing matches, MATCH_YES is
3841 returned (the null string was matched). */
3843 match
3844 gfc_match_prefix (gfc_typespec *ts)
3846 bool seen_type;
3848 gfc_clear_attr (&current_attr);
3849 seen_type = 0;
3851 gcc_assert (!gfc_matching_prefix);
3852 gfc_matching_prefix = true;
3854 loop:
3855 if (!seen_type && ts != NULL
3856 && gfc_match_decl_type_spec (ts, 0) == MATCH_YES
3857 && gfc_match_space () == MATCH_YES)
3860 seen_type = 1;
3861 goto loop;
3864 if (gfc_match ("elemental% ") == MATCH_YES)
3866 if (gfc_add_elemental (&current_attr, NULL) == FAILURE)
3867 goto error;
3869 goto loop;
3872 if (gfc_match ("pure% ") == MATCH_YES)
3874 if (gfc_add_pure (&current_attr, NULL) == FAILURE)
3875 goto error;
3877 goto loop;
3880 if (gfc_match ("recursive% ") == MATCH_YES)
3882 if (gfc_add_recursive (&current_attr, NULL) == FAILURE)
3883 goto error;
3885 goto loop;
3888 /* At this point, the next item is not a prefix. */
3889 gcc_assert (gfc_matching_prefix);
3890 gfc_matching_prefix = false;
3891 return MATCH_YES;
3893 error:
3894 gcc_assert (gfc_matching_prefix);
3895 gfc_matching_prefix = false;
3896 return MATCH_ERROR;
3900 /* Copy attributes matched by gfc_match_prefix() to attributes on a symbol. */
3902 static gfc_try
3903 copy_prefix (symbol_attribute *dest, locus *where)
3905 if (current_attr.pure && gfc_add_pure (dest, where) == FAILURE)
3906 return FAILURE;
3908 if (current_attr.elemental && gfc_add_elemental (dest, where) == FAILURE)
3909 return FAILURE;
3911 if (current_attr.recursive && gfc_add_recursive (dest, where) == FAILURE)
3912 return FAILURE;
3914 return SUCCESS;
3918 /* Match a formal argument list. */
3920 match
3921 gfc_match_formal_arglist (gfc_symbol *progname, int st_flag, int null_flag)
3923 gfc_formal_arglist *head, *tail, *p, *q;
3924 char name[GFC_MAX_SYMBOL_LEN + 1];
3925 gfc_symbol *sym;
3926 match m;
3928 head = tail = NULL;
3930 if (gfc_match_char ('(') != MATCH_YES)
3932 if (null_flag)
3933 goto ok;
3934 return MATCH_NO;
3937 if (gfc_match_char (')') == MATCH_YES)
3938 goto ok;
3940 for (;;)
3942 if (gfc_match_char ('*') == MATCH_YES)
3943 sym = NULL;
3944 else
3946 m = gfc_match_name (name);
3947 if (m != MATCH_YES)
3948 goto cleanup;
3950 if (gfc_get_symbol (name, NULL, &sym))
3951 goto cleanup;
3954 p = gfc_get_formal_arglist ();
3956 if (head == NULL)
3957 head = tail = p;
3958 else
3960 tail->next = p;
3961 tail = p;
3964 tail->sym = sym;
3966 /* We don't add the VARIABLE flavor because the name could be a
3967 dummy procedure. We don't apply these attributes to formal
3968 arguments of statement functions. */
3969 if (sym != NULL && !st_flag
3970 && (gfc_add_dummy (&sym->attr, sym->name, NULL) == FAILURE
3971 || gfc_missing_attr (&sym->attr, NULL) == FAILURE))
3973 m = MATCH_ERROR;
3974 goto cleanup;
3977 /* The name of a program unit can be in a different namespace,
3978 so check for it explicitly. After the statement is accepted,
3979 the name is checked for especially in gfc_get_symbol(). */
3980 if (gfc_new_block != NULL && sym != NULL
3981 && strcmp (sym->name, gfc_new_block->name) == 0)
3983 gfc_error ("Name '%s' at %C is the name of the procedure",
3984 sym->name);
3985 m = MATCH_ERROR;
3986 goto cleanup;
3989 if (gfc_match_char (')') == MATCH_YES)
3990 goto ok;
3992 m = gfc_match_char (',');
3993 if (m != MATCH_YES)
3995 gfc_error ("Unexpected junk in formal argument list at %C");
3996 goto cleanup;
4001 /* Check for duplicate symbols in the formal argument list. */
4002 if (head != NULL)
4004 for (p = head; p->next; p = p->next)
4006 if (p->sym == NULL)
4007 continue;
4009 for (q = p->next; q; q = q->next)
4010 if (p->sym == q->sym)
4012 gfc_error ("Duplicate symbol '%s' in formal argument list "
4013 "at %C", p->sym->name);
4015 m = MATCH_ERROR;
4016 goto cleanup;
4021 if (gfc_add_explicit_interface (progname, IFSRC_DECL, head, NULL)
4022 == FAILURE)
4024 m = MATCH_ERROR;
4025 goto cleanup;
4028 return MATCH_YES;
4030 cleanup:
4031 gfc_free_formal_arglist (head);
4032 return m;
4036 /* Match a RESULT specification following a function declaration or
4037 ENTRY statement. Also matches the end-of-statement. */
4039 static match
4040 match_result (gfc_symbol *function, gfc_symbol **result)
4042 char name[GFC_MAX_SYMBOL_LEN + 1];
4043 gfc_symbol *r;
4044 match m;
4046 if (gfc_match (" result (") != MATCH_YES)
4047 return MATCH_NO;
4049 m = gfc_match_name (name);
4050 if (m != MATCH_YES)
4051 return m;
4053 /* Get the right paren, and that's it because there could be the
4054 bind(c) attribute after the result clause. */
4055 if (gfc_match_char(')') != MATCH_YES)
4057 /* TODO: should report the missing right paren here. */
4058 return MATCH_ERROR;
4061 if (strcmp (function->name, name) == 0)
4063 gfc_error ("RESULT variable at %C must be different than function name");
4064 return MATCH_ERROR;
4067 if (gfc_get_symbol (name, NULL, &r))
4068 return MATCH_ERROR;
4070 if (gfc_add_result (&r->attr, r->name, NULL) == FAILURE)
4071 return MATCH_ERROR;
4073 *result = r;
4075 return MATCH_YES;
4079 /* Match a function suffix, which could be a combination of a result
4080 clause and BIND(C), either one, or neither. The draft does not
4081 require them to come in a specific order. */
4083 match
4084 gfc_match_suffix (gfc_symbol *sym, gfc_symbol **result)
4086 match is_bind_c; /* Found bind(c). */
4087 match is_result; /* Found result clause. */
4088 match found_match; /* Status of whether we've found a good match. */
4089 char peek_char; /* Character we're going to peek at. */
4090 bool allow_binding_name;
4092 /* Initialize to having found nothing. */
4093 found_match = MATCH_NO;
4094 is_bind_c = MATCH_NO;
4095 is_result = MATCH_NO;
4097 /* Get the next char to narrow between result and bind(c). */
4098 gfc_gobble_whitespace ();
4099 peek_char = gfc_peek_ascii_char ();
4101 /* C binding names are not allowed for internal procedures. */
4102 if (gfc_current_state () == COMP_CONTAINS
4103 && sym->ns->proc_name->attr.flavor != FL_MODULE)
4104 allow_binding_name = false;
4105 else
4106 allow_binding_name = true;
4108 switch (peek_char)
4110 case 'r':
4111 /* Look for result clause. */
4112 is_result = match_result (sym, result);
4113 if (is_result == MATCH_YES)
4115 /* Now see if there is a bind(c) after it. */
4116 is_bind_c = gfc_match_bind_c (sym, allow_binding_name);
4117 /* We've found the result clause and possibly bind(c). */
4118 found_match = MATCH_YES;
4120 else
4121 /* This should only be MATCH_ERROR. */
4122 found_match = is_result;
4123 break;
4124 case 'b':
4125 /* Look for bind(c) first. */
4126 is_bind_c = gfc_match_bind_c (sym, allow_binding_name);
4127 if (is_bind_c == MATCH_YES)
4129 /* Now see if a result clause followed it. */
4130 is_result = match_result (sym, result);
4131 found_match = MATCH_YES;
4133 else
4135 /* Should only be a MATCH_ERROR if we get here after seeing 'b'. */
4136 found_match = MATCH_ERROR;
4138 break;
4139 default:
4140 gfc_error ("Unexpected junk after function declaration at %C");
4141 found_match = MATCH_ERROR;
4142 break;
4145 if (is_bind_c == MATCH_YES)
4147 /* Fortran 2008 draft allows BIND(C) for internal procedures. */
4148 if (gfc_current_state () == COMP_CONTAINS
4149 && sym->ns->proc_name->attr.flavor != FL_MODULE
4150 && gfc_notify_std (GFC_STD_F2008, "Fortran 2008: BIND(C) attribute "
4151 "at %L may not be specified for an internal "
4152 "procedure", &gfc_current_locus)
4153 == FAILURE)
4154 return MATCH_ERROR;
4156 if (gfc_add_is_bind_c (&(sym->attr), sym->name, &gfc_current_locus, 1)
4157 == FAILURE)
4158 return MATCH_ERROR;
4161 return found_match;
4165 /* Procedure pointer return value without RESULT statement:
4166 Add "hidden" result variable named "ppr@". */
4168 static gfc_try
4169 add_hidden_procptr_result (gfc_symbol *sym)
4171 bool case1,case2;
4173 if (gfc_notification_std (GFC_STD_F2003) == ERROR)
4174 return FAILURE;
4176 /* First usage case: PROCEDURE and EXTERNAL statements. */
4177 case1 = gfc_current_state () == COMP_FUNCTION && gfc_current_block ()
4178 && strcmp (gfc_current_block ()->name, sym->name) == 0
4179 && sym->attr.external;
4180 /* Second usage case: INTERFACE statements. */
4181 case2 = gfc_current_state () == COMP_INTERFACE && gfc_state_stack->previous
4182 && gfc_state_stack->previous->state == COMP_FUNCTION
4183 && strcmp (gfc_state_stack->previous->sym->name, sym->name) == 0;
4185 if (case1 || case2)
4187 gfc_symtree *stree;
4188 if (case1)
4189 gfc_get_sym_tree ("ppr@", gfc_current_ns, &stree, false);
4190 else if (case2)
4192 gfc_symtree *st2;
4193 gfc_get_sym_tree ("ppr@", gfc_current_ns->parent, &stree, false);
4194 st2 = gfc_new_symtree (&gfc_current_ns->sym_root, "ppr@");
4195 st2->n.sym = stree->n.sym;
4197 sym->result = stree->n.sym;
4199 sym->result->attr.proc_pointer = sym->attr.proc_pointer;
4200 sym->result->attr.pointer = sym->attr.pointer;
4201 sym->result->attr.external = sym->attr.external;
4202 sym->result->attr.referenced = sym->attr.referenced;
4203 sym->result->ts = sym->ts;
4204 sym->attr.proc_pointer = 0;
4205 sym->attr.pointer = 0;
4206 sym->attr.external = 0;
4207 if (sym->result->attr.external && sym->result->attr.pointer)
4209 sym->result->attr.pointer = 0;
4210 sym->result->attr.proc_pointer = 1;
4213 return gfc_add_result (&sym->result->attr, sym->result->name, NULL);
4215 /* POINTER after PROCEDURE/EXTERNAL/INTERFACE statement. */
4216 else if (sym->attr.function && !sym->attr.external && sym->attr.pointer
4217 && sym->result && sym->result != sym && sym->result->attr.external
4218 && sym == gfc_current_ns->proc_name
4219 && sym == sym->result->ns->proc_name
4220 && strcmp ("ppr@", sym->result->name) == 0)
4222 sym->result->attr.proc_pointer = 1;
4223 sym->attr.pointer = 0;
4224 return SUCCESS;
4226 else
4227 return FAILURE;
4231 /* Match the interface for a PROCEDURE declaration,
4232 including brackets (R1212). */
4234 static match
4235 match_procedure_interface (gfc_symbol **proc_if)
4237 match m;
4238 gfc_symtree *st;
4239 locus old_loc, entry_loc;
4240 gfc_namespace *old_ns = gfc_current_ns;
4241 char name[GFC_MAX_SYMBOL_LEN + 1];
4243 old_loc = entry_loc = gfc_current_locus;
4244 gfc_clear_ts (&current_ts);
4246 if (gfc_match (" (") != MATCH_YES)
4248 gfc_current_locus = entry_loc;
4249 return MATCH_NO;
4252 /* Get the type spec. for the procedure interface. */
4253 old_loc = gfc_current_locus;
4254 m = gfc_match_decl_type_spec (&current_ts, 0);
4255 gfc_gobble_whitespace ();
4256 if (m == MATCH_YES || (m == MATCH_NO && gfc_peek_ascii_char () == ')'))
4257 goto got_ts;
4259 if (m == MATCH_ERROR)
4260 return m;
4262 /* Procedure interface is itself a procedure. */
4263 gfc_current_locus = old_loc;
4264 m = gfc_match_name (name);
4266 /* First look to see if it is already accessible in the current
4267 namespace because it is use associated or contained. */
4268 st = NULL;
4269 if (gfc_find_sym_tree (name, NULL, 0, &st))
4270 return MATCH_ERROR;
4272 /* If it is still not found, then try the parent namespace, if it
4273 exists and create the symbol there if it is still not found. */
4274 if (gfc_current_ns->parent)
4275 gfc_current_ns = gfc_current_ns->parent;
4276 if (st == NULL && gfc_get_ha_sym_tree (name, &st))
4277 return MATCH_ERROR;
4279 gfc_current_ns = old_ns;
4280 *proc_if = st->n.sym;
4282 /* Various interface checks. */
4283 if (*proc_if)
4285 (*proc_if)->refs++;
4286 /* Resolve interface if possible. That way, attr.procedure is only set
4287 if it is declared by a later procedure-declaration-stmt, which is
4288 invalid per C1212. */
4289 while ((*proc_if)->ts.interface)
4290 *proc_if = (*proc_if)->ts.interface;
4292 if ((*proc_if)->generic)
4294 gfc_error ("Interface '%s' at %C may not be generic",
4295 (*proc_if)->name);
4296 return MATCH_ERROR;
4298 if ((*proc_if)->attr.proc == PROC_ST_FUNCTION)
4300 gfc_error ("Interface '%s' at %C may not be a statement function",
4301 (*proc_if)->name);
4302 return MATCH_ERROR;
4304 /* Handle intrinsic procedures. */
4305 if (!((*proc_if)->attr.external || (*proc_if)->attr.use_assoc
4306 || (*proc_if)->attr.if_source == IFSRC_IFBODY)
4307 && (gfc_is_intrinsic ((*proc_if), 0, gfc_current_locus)
4308 || gfc_is_intrinsic ((*proc_if), 1, gfc_current_locus)))
4309 (*proc_if)->attr.intrinsic = 1;
4310 if ((*proc_if)->attr.intrinsic
4311 && !gfc_intrinsic_actual_ok ((*proc_if)->name, 0))
4313 gfc_error ("Intrinsic procedure '%s' not allowed "
4314 "in PROCEDURE statement at %C", (*proc_if)->name);
4315 return MATCH_ERROR;
4319 got_ts:
4320 if (gfc_match (" )") != MATCH_YES)
4322 gfc_current_locus = entry_loc;
4323 return MATCH_NO;
4326 return MATCH_YES;
4330 /* Match a PROCEDURE declaration (R1211). */
4332 static match
4333 match_procedure_decl (void)
4335 match m;
4336 gfc_symbol *sym, *proc_if = NULL;
4337 int num;
4338 gfc_expr *initializer = NULL;
4340 /* Parse interface (with brackets). */
4341 m = match_procedure_interface (&proc_if);
4342 if (m != MATCH_YES)
4343 return m;
4345 /* Parse attributes (with colons). */
4346 m = match_attr_spec();
4347 if (m == MATCH_ERROR)
4348 return MATCH_ERROR;
4350 /* Get procedure symbols. */
4351 for(num=1;;num++)
4353 m = gfc_match_symbol (&sym, 0);
4354 if (m == MATCH_NO)
4355 goto syntax;
4356 else if (m == MATCH_ERROR)
4357 return m;
4359 /* Add current_attr to the symbol attributes. */
4360 if (gfc_copy_attr (&sym->attr, &current_attr, NULL) == FAILURE)
4361 return MATCH_ERROR;
4363 if (sym->attr.is_bind_c)
4365 /* Check for C1218. */
4366 if (!proc_if || !proc_if->attr.is_bind_c)
4368 gfc_error ("BIND(C) attribute at %C requires "
4369 "an interface with BIND(C)");
4370 return MATCH_ERROR;
4372 /* Check for C1217. */
4373 if (has_name_equals && sym->attr.pointer)
4375 gfc_error ("BIND(C) procedure with NAME may not have "
4376 "POINTER attribute at %C");
4377 return MATCH_ERROR;
4379 if (has_name_equals && sym->attr.dummy)
4381 gfc_error ("Dummy procedure at %C may not have "
4382 "BIND(C) attribute with NAME");
4383 return MATCH_ERROR;
4385 /* Set binding label for BIND(C). */
4386 if (set_binding_label (sym->binding_label, sym->name, num) != SUCCESS)
4387 return MATCH_ERROR;
4390 if (gfc_add_external (&sym->attr, NULL) == FAILURE)
4391 return MATCH_ERROR;
4393 if (add_hidden_procptr_result (sym) == SUCCESS)
4394 sym = sym->result;
4396 if (gfc_add_proc (&sym->attr, sym->name, NULL) == FAILURE)
4397 return MATCH_ERROR;
4399 /* Set interface. */
4400 if (proc_if != NULL)
4402 if (sym->ts.type != BT_UNKNOWN)
4404 gfc_error ("Procedure '%s' at %L already has basic type of %s",
4405 sym->name, &gfc_current_locus,
4406 gfc_basic_typename (sym->ts.type));
4407 return MATCH_ERROR;
4409 sym->ts.interface = proc_if;
4410 sym->attr.untyped = 1;
4411 sym->attr.if_source = IFSRC_IFBODY;
4413 else if (current_ts.type != BT_UNKNOWN)
4415 if (gfc_add_type (sym, &current_ts, &gfc_current_locus) == FAILURE)
4416 return MATCH_ERROR;
4417 sym->ts.interface = gfc_new_symbol ("", gfc_current_ns);
4418 sym->ts.interface->ts = current_ts;
4419 sym->ts.interface->attr.function = 1;
4420 sym->attr.function = sym->ts.interface->attr.function;
4421 sym->attr.if_source = IFSRC_UNKNOWN;
4424 if (gfc_match (" =>") == MATCH_YES)
4426 if (!current_attr.pointer)
4428 gfc_error ("Initialization at %C isn't for a pointer variable");
4429 m = MATCH_ERROR;
4430 goto cleanup;
4433 m = gfc_match_null (&initializer);
4434 if (m == MATCH_NO)
4436 gfc_error ("Pointer initialization requires a NULL() at %C");
4437 m = MATCH_ERROR;
4440 if (gfc_pure (NULL))
4442 gfc_error ("Initialization of pointer at %C is not allowed in "
4443 "a PURE procedure");
4444 m = MATCH_ERROR;
4447 if (m != MATCH_YES)
4448 goto cleanup;
4450 if (add_init_expr_to_sym (sym->name, &initializer, &gfc_current_locus)
4451 != SUCCESS)
4452 goto cleanup;
4456 gfc_set_sym_referenced (sym);
4458 if (gfc_match_eos () == MATCH_YES)
4459 return MATCH_YES;
4460 if (gfc_match_char (',') != MATCH_YES)
4461 goto syntax;
4464 syntax:
4465 gfc_error ("Syntax error in PROCEDURE statement at %C");
4466 return MATCH_ERROR;
4468 cleanup:
4469 /* Free stuff up and return. */
4470 gfc_free_expr (initializer);
4471 return m;
4475 static match
4476 match_binding_attributes (gfc_typebound_proc* ba, bool generic, bool ppc);
4479 /* Match a procedure pointer component declaration (R445). */
4481 static match
4482 match_ppc_decl (void)
4484 match m;
4485 gfc_symbol *proc_if = NULL;
4486 gfc_typespec ts;
4487 int num;
4488 gfc_component *c;
4489 gfc_expr *initializer = NULL;
4490 gfc_typebound_proc* tb;
4491 char name[GFC_MAX_SYMBOL_LEN + 1];
4493 /* Parse interface (with brackets). */
4494 m = match_procedure_interface (&proc_if);
4495 if (m != MATCH_YES)
4496 goto syntax;
4498 /* Parse attributes. */
4499 tb = XCNEW (gfc_typebound_proc);
4500 tb->where = gfc_current_locus;
4501 m = match_binding_attributes (tb, false, true);
4502 if (m == MATCH_ERROR)
4503 return m;
4505 gfc_clear_attr (&current_attr);
4506 current_attr.procedure = 1;
4507 current_attr.proc_pointer = 1;
4508 current_attr.access = tb->access;
4509 current_attr.flavor = FL_PROCEDURE;
4511 /* Match the colons (required). */
4512 if (gfc_match (" ::") != MATCH_YES)
4514 gfc_error ("Expected '::' after binding-attributes at %C");
4515 return MATCH_ERROR;
4518 /* Check for C450. */
4519 if (!tb->nopass && proc_if == NULL)
4521 gfc_error("NOPASS or explicit interface required at %C");
4522 return MATCH_ERROR;
4525 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure pointer "
4526 "component at %C") == FAILURE)
4527 return MATCH_ERROR;
4529 /* Match PPC names. */
4530 ts = current_ts;
4531 for(num=1;;num++)
4533 m = gfc_match_name (name);
4534 if (m == MATCH_NO)
4535 goto syntax;
4536 else if (m == MATCH_ERROR)
4537 return m;
4539 if (gfc_add_component (gfc_current_block (), name, &c) == FAILURE)
4540 return MATCH_ERROR;
4542 /* Add current_attr to the symbol attributes. */
4543 if (gfc_copy_attr (&c->attr, &current_attr, NULL) == FAILURE)
4544 return MATCH_ERROR;
4546 if (gfc_add_external (&c->attr, NULL) == FAILURE)
4547 return MATCH_ERROR;
4549 if (gfc_add_proc (&c->attr, name, NULL) == FAILURE)
4550 return MATCH_ERROR;
4552 c->tb = tb;
4554 /* Set interface. */
4555 if (proc_if != NULL)
4557 c->ts.interface = proc_if;
4558 c->attr.untyped = 1;
4559 c->attr.if_source = IFSRC_IFBODY;
4561 else if (ts.type != BT_UNKNOWN)
4563 c->ts = ts;
4564 c->ts.interface = gfc_new_symbol ("", gfc_current_ns);
4565 c->ts.interface->ts = ts;
4566 c->ts.interface->attr.function = 1;
4567 c->attr.function = c->ts.interface->attr.function;
4568 c->attr.if_source = IFSRC_UNKNOWN;
4571 if (gfc_match (" =>") == MATCH_YES)
4573 m = gfc_match_null (&initializer);
4574 if (m == MATCH_NO)
4576 gfc_error ("Pointer initialization requires a NULL() at %C");
4577 m = MATCH_ERROR;
4579 if (gfc_pure (NULL))
4581 gfc_error ("Initialization of pointer at %C is not allowed in "
4582 "a PURE procedure");
4583 m = MATCH_ERROR;
4585 if (m != MATCH_YES)
4587 gfc_free_expr (initializer);
4588 return m;
4590 c->initializer = initializer;
4593 if (gfc_match_eos () == MATCH_YES)
4594 return MATCH_YES;
4595 if (gfc_match_char (',') != MATCH_YES)
4596 goto syntax;
4599 syntax:
4600 gfc_error ("Syntax error in procedure pointer component at %C");
4601 return MATCH_ERROR;
4605 /* Match a PROCEDURE declaration inside an interface (R1206). */
4607 static match
4608 match_procedure_in_interface (void)
4610 match m;
4611 gfc_symbol *sym;
4612 char name[GFC_MAX_SYMBOL_LEN + 1];
4614 if (current_interface.type == INTERFACE_NAMELESS
4615 || current_interface.type == INTERFACE_ABSTRACT)
4617 gfc_error ("PROCEDURE at %C must be in a generic interface");
4618 return MATCH_ERROR;
4621 for(;;)
4623 m = gfc_match_name (name);
4624 if (m == MATCH_NO)
4625 goto syntax;
4626 else if (m == MATCH_ERROR)
4627 return m;
4628 if (gfc_get_symbol (name, gfc_current_ns->parent, &sym))
4629 return MATCH_ERROR;
4631 if (gfc_add_interface (sym) == FAILURE)
4632 return MATCH_ERROR;
4634 if (gfc_match_eos () == MATCH_YES)
4635 break;
4636 if (gfc_match_char (',') != MATCH_YES)
4637 goto syntax;
4640 return MATCH_YES;
4642 syntax:
4643 gfc_error ("Syntax error in PROCEDURE statement at %C");
4644 return MATCH_ERROR;
4648 /* General matcher for PROCEDURE declarations. */
4650 static match match_procedure_in_type (void);
4652 match
4653 gfc_match_procedure (void)
4655 match m;
4657 switch (gfc_current_state ())
4659 case COMP_NONE:
4660 case COMP_PROGRAM:
4661 case COMP_MODULE:
4662 case COMP_SUBROUTINE:
4663 case COMP_FUNCTION:
4664 m = match_procedure_decl ();
4665 break;
4666 case COMP_INTERFACE:
4667 m = match_procedure_in_interface ();
4668 break;
4669 case COMP_DERIVED:
4670 m = match_ppc_decl ();
4671 break;
4672 case COMP_DERIVED_CONTAINS:
4673 m = match_procedure_in_type ();
4674 break;
4675 default:
4676 return MATCH_NO;
4679 if (m != MATCH_YES)
4680 return m;
4682 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PROCEDURE statement at %C")
4683 == FAILURE)
4684 return MATCH_ERROR;
4686 return m;
4690 /* Warn if a matched procedure has the same name as an intrinsic; this is
4691 simply a wrapper around gfc_warn_intrinsic_shadow that interprets the current
4692 parser-state-stack to find out whether we're in a module. */
4694 static void
4695 warn_intrinsic_shadow (const gfc_symbol* sym, bool func)
4697 bool in_module;
4699 in_module = (gfc_state_stack->previous
4700 && gfc_state_stack->previous->state == COMP_MODULE);
4702 gfc_warn_intrinsic_shadow (sym, in_module, func);
4706 /* Match a function declaration. */
4708 match
4709 gfc_match_function_decl (void)
4711 char name[GFC_MAX_SYMBOL_LEN + 1];
4712 gfc_symbol *sym, *result;
4713 locus old_loc;
4714 match m;
4715 match suffix_match;
4716 match found_match; /* Status returned by match func. */
4718 if (gfc_current_state () != COMP_NONE
4719 && gfc_current_state () != COMP_INTERFACE
4720 && gfc_current_state () != COMP_CONTAINS)
4721 return MATCH_NO;
4723 gfc_clear_ts (&current_ts);
4725 old_loc = gfc_current_locus;
4727 m = gfc_match_prefix (&current_ts);
4728 if (m != MATCH_YES)
4730 gfc_current_locus = old_loc;
4731 return m;
4734 if (gfc_match ("function% %n", name) != MATCH_YES)
4736 gfc_current_locus = old_loc;
4737 return MATCH_NO;
4739 if (get_proc_name (name, &sym, false))
4740 return MATCH_ERROR;
4742 if (add_hidden_procptr_result (sym) == SUCCESS)
4743 sym = sym->result;
4745 gfc_new_block = sym;
4747 m = gfc_match_formal_arglist (sym, 0, 0);
4748 if (m == MATCH_NO)
4750 gfc_error ("Expected formal argument list in function "
4751 "definition at %C");
4752 m = MATCH_ERROR;
4753 goto cleanup;
4755 else if (m == MATCH_ERROR)
4756 goto cleanup;
4758 result = NULL;
4760 /* According to the draft, the bind(c) and result clause can
4761 come in either order after the formal_arg_list (i.e., either
4762 can be first, both can exist together or by themselves or neither
4763 one). Therefore, the match_result can't match the end of the
4764 string, and check for the bind(c) or result clause in either order. */
4765 found_match = gfc_match_eos ();
4767 /* Make sure that it isn't already declared as BIND(C). If it is, it
4768 must have been marked BIND(C) with a BIND(C) attribute and that is
4769 not allowed for procedures. */
4770 if (sym->attr.is_bind_c == 1)
4772 sym->attr.is_bind_c = 0;
4773 if (sym->old_symbol != NULL)
4774 gfc_error_now ("BIND(C) attribute at %L can only be used for "
4775 "variables or common blocks",
4776 &(sym->old_symbol->declared_at));
4777 else
4778 gfc_error_now ("BIND(C) attribute at %L can only be used for "
4779 "variables or common blocks", &gfc_current_locus);
4782 if (found_match != MATCH_YES)
4784 /* If we haven't found the end-of-statement, look for a suffix. */
4785 suffix_match = gfc_match_suffix (sym, &result);
4786 if (suffix_match == MATCH_YES)
4787 /* Need to get the eos now. */
4788 found_match = gfc_match_eos ();
4789 else
4790 found_match = suffix_match;
4793 if(found_match != MATCH_YES)
4794 m = MATCH_ERROR;
4795 else
4797 /* Make changes to the symbol. */
4798 m = MATCH_ERROR;
4800 if (gfc_add_function (&sym->attr, sym->name, NULL) == FAILURE)
4801 goto cleanup;
4803 if (gfc_missing_attr (&sym->attr, NULL) == FAILURE
4804 || copy_prefix (&sym->attr, &sym->declared_at) == FAILURE)
4805 goto cleanup;
4807 /* Delay matching the function characteristics until after the
4808 specification block by signalling kind=-1. */
4809 sym->declared_at = old_loc;
4810 if (current_ts.type != BT_UNKNOWN)
4811 current_ts.kind = -1;
4812 else
4813 current_ts.kind = 0;
4815 if (result == NULL)
4817 if (current_ts.type != BT_UNKNOWN
4818 && gfc_add_type (sym, &current_ts, &gfc_current_locus) == FAILURE)
4819 goto cleanup;
4820 sym->result = sym;
4822 else
4824 if (current_ts.type != BT_UNKNOWN
4825 && gfc_add_type (result, &current_ts, &gfc_current_locus)
4826 == FAILURE)
4827 goto cleanup;
4828 sym->result = result;
4831 /* Warn if this procedure has the same name as an intrinsic. */
4832 warn_intrinsic_shadow (sym, true);
4834 return MATCH_YES;
4837 cleanup:
4838 gfc_current_locus = old_loc;
4839 return m;
4843 /* This is mostly a copy of parse.c(add_global_procedure) but modified to
4844 pass the name of the entry, rather than the gfc_current_block name, and
4845 to return false upon finding an existing global entry. */
4847 static bool
4848 add_global_entry (const char *name, int sub)
4850 gfc_gsymbol *s;
4851 enum gfc_symbol_type type;
4853 s = gfc_get_gsymbol(name);
4854 type = sub ? GSYM_SUBROUTINE : GSYM_FUNCTION;
4856 if (s->defined
4857 || (s->type != GSYM_UNKNOWN
4858 && s->type != type))
4859 gfc_global_used(s, NULL);
4860 else
4862 s->type = type;
4863 s->where = gfc_current_locus;
4864 s->defined = 1;
4865 s->ns = gfc_current_ns;
4866 return true;
4868 return false;
4872 /* Match an ENTRY statement. */
4874 match
4875 gfc_match_entry (void)
4877 gfc_symbol *proc;
4878 gfc_symbol *result;
4879 gfc_symbol *entry;
4880 char name[GFC_MAX_SYMBOL_LEN + 1];
4881 gfc_compile_state state;
4882 match m;
4883 gfc_entry_list *el;
4884 locus old_loc;
4885 bool module_procedure;
4886 char peek_char;
4887 match is_bind_c;
4889 m = gfc_match_name (name);
4890 if (m != MATCH_YES)
4891 return m;
4893 state = gfc_current_state ();
4894 if (state != COMP_SUBROUTINE && state != COMP_FUNCTION)
4896 switch (state)
4898 case COMP_PROGRAM:
4899 gfc_error ("ENTRY statement at %C cannot appear within a PROGRAM");
4900 break;
4901 case COMP_MODULE:
4902 gfc_error ("ENTRY statement at %C cannot appear within a MODULE");
4903 break;
4904 case COMP_BLOCK_DATA:
4905 gfc_error ("ENTRY statement at %C cannot appear within "
4906 "a BLOCK DATA");
4907 break;
4908 case COMP_INTERFACE:
4909 gfc_error ("ENTRY statement at %C cannot appear within "
4910 "an INTERFACE");
4911 break;
4912 case COMP_DERIVED:
4913 gfc_error ("ENTRY statement at %C cannot appear within "
4914 "a DERIVED TYPE block");
4915 break;
4916 case COMP_IF:
4917 gfc_error ("ENTRY statement at %C cannot appear within "
4918 "an IF-THEN block");
4919 break;
4920 case COMP_DO:
4921 gfc_error ("ENTRY statement at %C cannot appear within "
4922 "a DO block");
4923 break;
4924 case COMP_SELECT:
4925 gfc_error ("ENTRY statement at %C cannot appear within "
4926 "a SELECT block");
4927 break;
4928 case COMP_FORALL:
4929 gfc_error ("ENTRY statement at %C cannot appear within "
4930 "a FORALL block");
4931 break;
4932 case COMP_WHERE:
4933 gfc_error ("ENTRY statement at %C cannot appear within "
4934 "a WHERE block");
4935 break;
4936 case COMP_CONTAINS:
4937 gfc_error ("ENTRY statement at %C cannot appear within "
4938 "a contained subprogram");
4939 break;
4940 default:
4941 gfc_internal_error ("gfc_match_entry(): Bad state");
4943 return MATCH_ERROR;
4946 module_procedure = gfc_current_ns->parent != NULL
4947 && gfc_current_ns->parent->proc_name
4948 && gfc_current_ns->parent->proc_name->attr.flavor
4949 == FL_MODULE;
4951 if (gfc_current_ns->parent != NULL
4952 && gfc_current_ns->parent->proc_name
4953 && !module_procedure)
4955 gfc_error("ENTRY statement at %C cannot appear in a "
4956 "contained procedure");
4957 return MATCH_ERROR;
4960 /* Module function entries need special care in get_proc_name
4961 because previous references within the function will have
4962 created symbols attached to the current namespace. */
4963 if (get_proc_name (name, &entry,
4964 gfc_current_ns->parent != NULL
4965 && module_procedure))
4966 return MATCH_ERROR;
4968 proc = gfc_current_block ();
4970 /* Make sure that it isn't already declared as BIND(C). If it is, it
4971 must have been marked BIND(C) with a BIND(C) attribute and that is
4972 not allowed for procedures. */
4973 if (entry->attr.is_bind_c == 1)
4975 entry->attr.is_bind_c = 0;
4976 if (entry->old_symbol != NULL)
4977 gfc_error_now ("BIND(C) attribute at %L can only be used for "
4978 "variables or common blocks",
4979 &(entry->old_symbol->declared_at));
4980 else
4981 gfc_error_now ("BIND(C) attribute at %L can only be used for "
4982 "variables or common blocks", &gfc_current_locus);
4985 /* Check what next non-whitespace character is so we can tell if there
4986 is the required parens if we have a BIND(C). */
4987 gfc_gobble_whitespace ();
4988 peek_char = gfc_peek_ascii_char ();
4990 if (state == COMP_SUBROUTINE)
4992 /* An entry in a subroutine. */
4993 if (!gfc_current_ns->parent && !add_global_entry (name, 1))
4994 return MATCH_ERROR;
4996 m = gfc_match_formal_arglist (entry, 0, 1);
4997 if (m != MATCH_YES)
4998 return MATCH_ERROR;
5000 /* Call gfc_match_bind_c with allow_binding_name = true as ENTRY can
5001 never be an internal procedure. */
5002 is_bind_c = gfc_match_bind_c (entry, true);
5003 if (is_bind_c == MATCH_ERROR)
5004 return MATCH_ERROR;
5005 if (is_bind_c == MATCH_YES)
5007 if (peek_char != '(')
5009 gfc_error ("Missing required parentheses before BIND(C) at %C");
5010 return MATCH_ERROR;
5012 if (gfc_add_is_bind_c (&(entry->attr), entry->name, &(entry->declared_at), 1)
5013 == FAILURE)
5014 return MATCH_ERROR;
5017 if (gfc_add_entry (&entry->attr, entry->name, NULL) == FAILURE
5018 || gfc_add_subroutine (&entry->attr, entry->name, NULL) == FAILURE)
5019 return MATCH_ERROR;
5021 else
5023 /* An entry in a function.
5024 We need to take special care because writing
5025 ENTRY f()
5027 ENTRY f
5028 is allowed, whereas
5029 ENTRY f() RESULT (r)
5030 can't be written as
5031 ENTRY f RESULT (r). */
5032 if (!gfc_current_ns->parent && !add_global_entry (name, 0))
5033 return MATCH_ERROR;
5035 old_loc = gfc_current_locus;
5036 if (gfc_match_eos () == MATCH_YES)
5038 gfc_current_locus = old_loc;
5039 /* Match the empty argument list, and add the interface to
5040 the symbol. */
5041 m = gfc_match_formal_arglist (entry, 0, 1);
5043 else
5044 m = gfc_match_formal_arglist (entry, 0, 0);
5046 if (m != MATCH_YES)
5047 return MATCH_ERROR;
5049 result = NULL;
5051 if (gfc_match_eos () == MATCH_YES)
5053 if (gfc_add_entry (&entry->attr, entry->name, NULL) == FAILURE
5054 || gfc_add_function (&entry->attr, entry->name, NULL) == FAILURE)
5055 return MATCH_ERROR;
5057 entry->result = entry;
5059 else
5061 m = gfc_match_suffix (entry, &result);
5062 if (m == MATCH_NO)
5063 gfc_syntax_error (ST_ENTRY);
5064 if (m != MATCH_YES)
5065 return MATCH_ERROR;
5067 if (result)
5069 if (gfc_add_result (&result->attr, result->name, NULL) == FAILURE
5070 || gfc_add_entry (&entry->attr, result->name, NULL) == FAILURE
5071 || gfc_add_function (&entry->attr, result->name, NULL)
5072 == FAILURE)
5073 return MATCH_ERROR;
5074 entry->result = result;
5076 else
5078 if (gfc_add_entry (&entry->attr, entry->name, NULL) == FAILURE
5079 || gfc_add_function (&entry->attr, entry->name, NULL) == FAILURE)
5080 return MATCH_ERROR;
5081 entry->result = entry;
5086 if (gfc_match_eos () != MATCH_YES)
5088 gfc_syntax_error (ST_ENTRY);
5089 return MATCH_ERROR;
5092 entry->attr.recursive = proc->attr.recursive;
5093 entry->attr.elemental = proc->attr.elemental;
5094 entry->attr.pure = proc->attr.pure;
5096 el = gfc_get_entry_list ();
5097 el->sym = entry;
5098 el->next = gfc_current_ns->entries;
5099 gfc_current_ns->entries = el;
5100 if (el->next)
5101 el->id = el->next->id + 1;
5102 else
5103 el->id = 1;
5105 new_st.op = EXEC_ENTRY;
5106 new_st.ext.entry = el;
5108 return MATCH_YES;
5112 /* Match a subroutine statement, including optional prefixes. */
5114 match
5115 gfc_match_subroutine (void)
5117 char name[GFC_MAX_SYMBOL_LEN + 1];
5118 gfc_symbol *sym;
5119 match m;
5120 match is_bind_c;
5121 char peek_char;
5122 bool allow_binding_name;
5124 if (gfc_current_state () != COMP_NONE
5125 && gfc_current_state () != COMP_INTERFACE
5126 && gfc_current_state () != COMP_CONTAINS)
5127 return MATCH_NO;
5129 m = gfc_match_prefix (NULL);
5130 if (m != MATCH_YES)
5131 return m;
5133 m = gfc_match ("subroutine% %n", name);
5134 if (m != MATCH_YES)
5135 return m;
5137 if (get_proc_name (name, &sym, false))
5138 return MATCH_ERROR;
5140 if (add_hidden_procptr_result (sym) == SUCCESS)
5141 sym = sym->result;
5143 gfc_new_block = sym;
5145 /* Check what next non-whitespace character is so we can tell if there
5146 is the required parens if we have a BIND(C). */
5147 gfc_gobble_whitespace ();
5148 peek_char = gfc_peek_ascii_char ();
5150 if (gfc_add_subroutine (&sym->attr, sym->name, NULL) == FAILURE)
5151 return MATCH_ERROR;
5153 if (gfc_match_formal_arglist (sym, 0, 1) != MATCH_YES)
5154 return MATCH_ERROR;
5156 /* Make sure that it isn't already declared as BIND(C). If it is, it
5157 must have been marked BIND(C) with a BIND(C) attribute and that is
5158 not allowed for procedures. */
5159 if (sym->attr.is_bind_c == 1)
5161 sym->attr.is_bind_c = 0;
5162 if (sym->old_symbol != NULL)
5163 gfc_error_now ("BIND(C) attribute at %L can only be used for "
5164 "variables or common blocks",
5165 &(sym->old_symbol->declared_at));
5166 else
5167 gfc_error_now ("BIND(C) attribute at %L can only be used for "
5168 "variables or common blocks", &gfc_current_locus);
5171 /* C binding names are not allowed for internal procedures. */
5172 if (gfc_current_state () == COMP_CONTAINS
5173 && sym->ns->proc_name->attr.flavor != FL_MODULE)
5174 allow_binding_name = false;
5175 else
5176 allow_binding_name = true;
5178 /* Here, we are just checking if it has the bind(c) attribute, and if
5179 so, then we need to make sure it's all correct. If it doesn't,
5180 we still need to continue matching the rest of the subroutine line. */
5181 is_bind_c = gfc_match_bind_c (sym, allow_binding_name);
5182 if (is_bind_c == MATCH_ERROR)
5184 /* There was an attempt at the bind(c), but it was wrong. An
5185 error message should have been printed w/in the gfc_match_bind_c
5186 so here we'll just return the MATCH_ERROR. */
5187 return MATCH_ERROR;
5190 if (is_bind_c == MATCH_YES)
5192 /* The following is allowed in the Fortran 2008 draft. */
5193 if (gfc_current_state () == COMP_CONTAINS
5194 && sym->ns->proc_name->attr.flavor != FL_MODULE
5195 && gfc_notify_std (GFC_STD_F2008, "Fortran 2008: BIND(C) attribute "
5196 "at %L may not be specified for an internal "
5197 "procedure", &gfc_current_locus)
5198 == FAILURE)
5199 return MATCH_ERROR;
5201 if (peek_char != '(')
5203 gfc_error ("Missing required parentheses before BIND(C) at %C");
5204 return MATCH_ERROR;
5206 if (gfc_add_is_bind_c (&(sym->attr), sym->name, &(sym->declared_at), 1)
5207 == FAILURE)
5208 return MATCH_ERROR;
5211 if (gfc_match_eos () != MATCH_YES)
5213 gfc_syntax_error (ST_SUBROUTINE);
5214 return MATCH_ERROR;
5217 if (copy_prefix (&sym->attr, &sym->declared_at) == FAILURE)
5218 return MATCH_ERROR;
5220 /* Warn if it has the same name as an intrinsic. */
5221 warn_intrinsic_shadow (sym, false);
5223 return MATCH_YES;
5227 /* Match a BIND(C) specifier, with the optional 'name=' specifier if
5228 given, and set the binding label in either the given symbol (if not
5229 NULL), or in the current_ts. The symbol may be NULL because we may
5230 encounter the BIND(C) before the declaration itself. Return
5231 MATCH_NO if what we're looking at isn't a BIND(C) specifier,
5232 MATCH_ERROR if it is a BIND(C) clause but an error was encountered,
5233 or MATCH_YES if the specifier was correct and the binding label and
5234 bind(c) fields were set correctly for the given symbol or the
5235 current_ts. If allow_binding_name is false, no binding name may be
5236 given. */
5238 match
5239 gfc_match_bind_c (gfc_symbol *sym, bool allow_binding_name)
5241 /* binding label, if exists */
5242 char binding_label[GFC_MAX_SYMBOL_LEN + 1];
5243 match double_quote;
5244 match single_quote;
5246 /* Initialize the flag that specifies whether we encountered a NAME=
5247 specifier or not. */
5248 has_name_equals = 0;
5250 /* Init the first char to nil so we can catch if we don't have
5251 the label (name attr) or the symbol name yet. */
5252 binding_label[0] = '\0';
5254 /* This much we have to be able to match, in this order, if
5255 there is a bind(c) label. */
5256 if (gfc_match (" bind ( c ") != MATCH_YES)
5257 return MATCH_NO;
5259 /* Now see if there is a binding label, or if we've reached the
5260 end of the bind(c) attribute without one. */
5261 if (gfc_match_char (',') == MATCH_YES)
5263 if (gfc_match (" name = ") != MATCH_YES)
5265 gfc_error ("Syntax error in NAME= specifier for binding label "
5266 "at %C");
5267 /* should give an error message here */
5268 return MATCH_ERROR;
5271 has_name_equals = 1;
5273 /* Get the opening quote. */
5274 double_quote = MATCH_YES;
5275 single_quote = MATCH_YES;
5276 double_quote = gfc_match_char ('"');
5277 if (double_quote != MATCH_YES)
5278 single_quote = gfc_match_char ('\'');
5279 if (double_quote != MATCH_YES && single_quote != MATCH_YES)
5281 gfc_error ("Syntax error in NAME= specifier for binding label "
5282 "at %C");
5283 return MATCH_ERROR;
5286 /* Grab the binding label, using functions that will not lower
5287 case the names automatically. */
5288 if (gfc_match_name_C (binding_label) != MATCH_YES)
5289 return MATCH_ERROR;
5291 /* Get the closing quotation. */
5292 if (double_quote == MATCH_YES)
5294 if (gfc_match_char ('"') != MATCH_YES)
5296 gfc_error ("Missing closing quote '\"' for binding label at %C");
5297 /* User started string with '"' so looked to match it. */
5298 return MATCH_ERROR;
5301 else
5303 if (gfc_match_char ('\'') != MATCH_YES)
5305 gfc_error ("Missing closing quote '\'' for binding label at %C");
5306 /* User started string with "'" char. */
5307 return MATCH_ERROR;
5312 /* Get the required right paren. */
5313 if (gfc_match_char (')') != MATCH_YES)
5315 gfc_error ("Missing closing paren for binding label at %C");
5316 return MATCH_ERROR;
5319 if (has_name_equals && !allow_binding_name)
5321 gfc_error ("No binding name is allowed in BIND(C) at %C");
5322 return MATCH_ERROR;
5325 if (has_name_equals && sym != NULL && sym->attr.dummy)
5327 gfc_error ("For dummy procedure %s, no binding name is "
5328 "allowed in BIND(C) at %C", sym->name);
5329 return MATCH_ERROR;
5333 /* Save the binding label to the symbol. If sym is null, we're
5334 probably matching the typespec attributes of a declaration and
5335 haven't gotten the name yet, and therefore, no symbol yet. */
5336 if (binding_label[0] != '\0')
5338 if (sym != NULL)
5340 strcpy (sym->binding_label, binding_label);
5342 else
5343 strcpy (curr_binding_label, binding_label);
5345 else if (allow_binding_name)
5347 /* No binding label, but if symbol isn't null, we
5348 can set the label for it here.
5349 If name="" or allow_binding_name is false, no C binding name is
5350 created. */
5351 if (sym != NULL && sym->name != NULL && has_name_equals == 0)
5352 strncpy (sym->binding_label, sym->name, strlen (sym->name) + 1);
5355 if (has_name_equals && gfc_current_state () == COMP_INTERFACE
5356 && current_interface.type == INTERFACE_ABSTRACT)
5358 gfc_error ("NAME not allowed on BIND(C) for ABSTRACT INTERFACE at %C");
5359 return MATCH_ERROR;
5362 return MATCH_YES;
5366 /* Return nonzero if we're currently compiling a contained procedure. */
5368 static int
5369 contained_procedure (void)
5371 gfc_state_data *s = gfc_state_stack;
5373 if ((s->state == COMP_SUBROUTINE || s->state == COMP_FUNCTION)
5374 && s->previous != NULL && s->previous->state == COMP_CONTAINS)
5375 return 1;
5377 return 0;
5380 /* Set the kind of each enumerator. The kind is selected such that it is
5381 interoperable with the corresponding C enumeration type, making
5382 sure that -fshort-enums is honored. */
5384 static void
5385 set_enum_kind(void)
5387 enumerator_history *current_history = NULL;
5388 int kind;
5389 int i;
5391 if (max_enum == NULL || enum_history == NULL)
5392 return;
5394 if (!flag_short_enums)
5395 return;
5397 i = 0;
5400 kind = gfc_integer_kinds[i++].kind;
5402 while (kind < gfc_c_int_kind
5403 && gfc_check_integer_range (max_enum->initializer->value.integer,
5404 kind) != ARITH_OK);
5406 current_history = enum_history;
5407 while (current_history != NULL)
5409 current_history->sym->ts.kind = kind;
5410 current_history = current_history->next;
5415 /* Match any of the various end-block statements. Returns the type of
5416 END to the caller. The END INTERFACE, END IF, END DO, END SELECT
5417 and END BLOCK statements cannot be replaced by a single END statement. */
5419 match
5420 gfc_match_end (gfc_statement *st)
5422 char name[GFC_MAX_SYMBOL_LEN + 1];
5423 gfc_compile_state state;
5424 locus old_loc;
5425 const char *block_name;
5426 const char *target;
5427 int eos_ok;
5428 match m;
5430 old_loc = gfc_current_locus;
5431 if (gfc_match ("end") != MATCH_YES)
5432 return MATCH_NO;
5434 state = gfc_current_state ();
5435 block_name = gfc_current_block () == NULL
5436 ? NULL : gfc_current_block ()->name;
5438 if (state == COMP_BLOCK && !strcmp (block_name, "block@"))
5439 block_name = NULL;
5441 if (state == COMP_CONTAINS || state == COMP_DERIVED_CONTAINS)
5443 state = gfc_state_stack->previous->state;
5444 block_name = gfc_state_stack->previous->sym == NULL
5445 ? NULL : gfc_state_stack->previous->sym->name;
5448 switch (state)
5450 case COMP_NONE:
5451 case COMP_PROGRAM:
5452 *st = ST_END_PROGRAM;
5453 target = " program";
5454 eos_ok = 1;
5455 break;
5457 case COMP_SUBROUTINE:
5458 *st = ST_END_SUBROUTINE;
5459 target = " subroutine";
5460 eos_ok = !contained_procedure ();
5461 break;
5463 case COMP_FUNCTION:
5464 *st = ST_END_FUNCTION;
5465 target = " function";
5466 eos_ok = !contained_procedure ();
5467 break;
5469 case COMP_BLOCK_DATA:
5470 *st = ST_END_BLOCK_DATA;
5471 target = " block data";
5472 eos_ok = 1;
5473 break;
5475 case COMP_MODULE:
5476 *st = ST_END_MODULE;
5477 target = " module";
5478 eos_ok = 1;
5479 break;
5481 case COMP_INTERFACE:
5482 *st = ST_END_INTERFACE;
5483 target = " interface";
5484 eos_ok = 0;
5485 break;
5487 case COMP_DERIVED:
5488 case COMP_DERIVED_CONTAINS:
5489 *st = ST_END_TYPE;
5490 target = " type";
5491 eos_ok = 0;
5492 break;
5494 case COMP_BLOCK:
5495 *st = ST_END_BLOCK;
5496 target = " block";
5497 eos_ok = 0;
5498 break;
5500 case COMP_IF:
5501 *st = ST_ENDIF;
5502 target = " if";
5503 eos_ok = 0;
5504 break;
5506 case COMP_DO:
5507 *st = ST_ENDDO;
5508 target = " do";
5509 eos_ok = 0;
5510 break;
5512 case COMP_SELECT:
5513 case COMP_SELECT_TYPE:
5514 *st = ST_END_SELECT;
5515 target = " select";
5516 eos_ok = 0;
5517 break;
5519 case COMP_FORALL:
5520 *st = ST_END_FORALL;
5521 target = " forall";
5522 eos_ok = 0;
5523 break;
5525 case COMP_WHERE:
5526 *st = ST_END_WHERE;
5527 target = " where";
5528 eos_ok = 0;
5529 break;
5531 case COMP_ENUM:
5532 *st = ST_END_ENUM;
5533 target = " enum";
5534 eos_ok = 0;
5535 last_initializer = NULL;
5536 set_enum_kind ();
5537 gfc_free_enum_history ();
5538 break;
5540 default:
5541 gfc_error ("Unexpected END statement at %C");
5542 goto cleanup;
5545 if (gfc_match_eos () == MATCH_YES)
5547 if (!eos_ok)
5549 /* We would have required END [something]. */
5550 gfc_error ("%s statement expected at %L",
5551 gfc_ascii_statement (*st), &old_loc);
5552 goto cleanup;
5555 return MATCH_YES;
5558 /* Verify that we've got the sort of end-block that we're expecting. */
5559 if (gfc_match (target) != MATCH_YES)
5561 gfc_error ("Expecting %s statement at %C", gfc_ascii_statement (*st));
5562 goto cleanup;
5565 /* If we're at the end, make sure a block name wasn't required. */
5566 if (gfc_match_eos () == MATCH_YES)
5569 if (*st != ST_ENDDO && *st != ST_ENDIF && *st != ST_END_SELECT
5570 && *st != ST_END_FORALL && *st != ST_END_WHERE && *st != ST_END_BLOCK)
5571 return MATCH_YES;
5573 if (!block_name)
5574 return MATCH_YES;
5576 gfc_error ("Expected block name of '%s' in %s statement at %C",
5577 block_name, gfc_ascii_statement (*st));
5579 return MATCH_ERROR;
5582 /* END INTERFACE has a special handler for its several possible endings. */
5583 if (*st == ST_END_INTERFACE)
5584 return gfc_match_end_interface ();
5586 /* We haven't hit the end of statement, so what is left must be an
5587 end-name. */
5588 m = gfc_match_space ();
5589 if (m == MATCH_YES)
5590 m = gfc_match_name (name);
5592 if (m == MATCH_NO)
5593 gfc_error ("Expected terminating name at %C");
5594 if (m != MATCH_YES)
5595 goto cleanup;
5597 if (block_name == NULL)
5598 goto syntax;
5600 if (strcmp (name, block_name) != 0 && strcmp (block_name, "ppr@") != 0)
5602 gfc_error ("Expected label '%s' for %s statement at %C", block_name,
5603 gfc_ascii_statement (*st));
5604 goto cleanup;
5606 /* Procedure pointer as function result. */
5607 else if (strcmp (block_name, "ppr@") == 0
5608 && strcmp (name, gfc_current_block ()->ns->proc_name->name) != 0)
5610 gfc_error ("Expected label '%s' for %s statement at %C",
5611 gfc_current_block ()->ns->proc_name->name,
5612 gfc_ascii_statement (*st));
5613 goto cleanup;
5616 if (gfc_match_eos () == MATCH_YES)
5617 return MATCH_YES;
5619 syntax:
5620 gfc_syntax_error (*st);
5622 cleanup:
5623 gfc_current_locus = old_loc;
5624 return MATCH_ERROR;
5629 /***************** Attribute declaration statements ****************/
5631 /* Set the attribute of a single variable. */
5633 static match
5634 attr_decl1 (void)
5636 char name[GFC_MAX_SYMBOL_LEN + 1];
5637 gfc_array_spec *as;
5638 gfc_symbol *sym;
5639 locus var_locus;
5640 match m;
5642 as = NULL;
5644 m = gfc_match_name (name);
5645 if (m != MATCH_YES)
5646 goto cleanup;
5648 if (find_special (name, &sym, false))
5649 return MATCH_ERROR;
5651 var_locus = gfc_current_locus;
5653 /* Deal with possible array specification for certain attributes. */
5654 if (current_attr.dimension
5655 || current_attr.allocatable
5656 || current_attr.pointer
5657 || current_attr.target)
5659 m = gfc_match_array_spec (&as);
5660 if (m == MATCH_ERROR)
5661 goto cleanup;
5663 if (current_attr.dimension && m == MATCH_NO)
5665 gfc_error ("Missing array specification at %L in DIMENSION "
5666 "statement", &var_locus);
5667 m = MATCH_ERROR;
5668 goto cleanup;
5671 if (current_attr.dimension && sym->value)
5673 gfc_error ("Dimensions specified for %s at %L after its "
5674 "initialisation", sym->name, &var_locus);
5675 m = MATCH_ERROR;
5676 goto cleanup;
5679 if ((current_attr.allocatable || current_attr.pointer)
5680 && (m == MATCH_YES) && (as->type != AS_DEFERRED))
5682 gfc_error ("Array specification must be deferred at %L", &var_locus);
5683 m = MATCH_ERROR;
5684 goto cleanup;
5688 /* Update symbol table. DIMENSION attribute is set
5689 in gfc_set_array_spec(). */
5690 if (current_attr.dimension == 0
5691 && gfc_copy_attr (&sym->attr, &current_attr, &var_locus) == FAILURE)
5693 m = MATCH_ERROR;
5694 goto cleanup;
5697 if (gfc_set_array_spec (sym, as, &var_locus) == FAILURE)
5699 m = MATCH_ERROR;
5700 goto cleanup;
5703 if (sym->attr.cray_pointee && sym->as != NULL)
5705 /* Fix the array spec. */
5706 m = gfc_mod_pointee_as (sym->as);
5707 if (m == MATCH_ERROR)
5708 goto cleanup;
5711 if (gfc_add_attribute (&sym->attr, &var_locus) == FAILURE)
5713 m = MATCH_ERROR;
5714 goto cleanup;
5717 if ((current_attr.external || current_attr.intrinsic)
5718 && sym->attr.flavor != FL_PROCEDURE
5719 && gfc_add_flavor (&sym->attr, FL_PROCEDURE, sym->name, NULL) == FAILURE)
5721 m = MATCH_ERROR;
5722 goto cleanup;
5725 add_hidden_procptr_result (sym);
5727 return MATCH_YES;
5729 cleanup:
5730 gfc_free_array_spec (as);
5731 return m;
5735 /* Generic attribute declaration subroutine. Used for attributes that
5736 just have a list of names. */
5738 static match
5739 attr_decl (void)
5741 match m;
5743 /* Gobble the optional double colon, by simply ignoring the result
5744 of gfc_match(). */
5745 gfc_match (" ::");
5747 for (;;)
5749 m = attr_decl1 ();
5750 if (m != MATCH_YES)
5751 break;
5753 if (gfc_match_eos () == MATCH_YES)
5755 m = MATCH_YES;
5756 break;
5759 if (gfc_match_char (',') != MATCH_YES)
5761 gfc_error ("Unexpected character in variable list at %C");
5762 m = MATCH_ERROR;
5763 break;
5767 return m;
5771 /* This routine matches Cray Pointer declarations of the form:
5772 pointer ( <pointer>, <pointee> )
5774 pointer ( <pointer1>, <pointee1> ), ( <pointer2>, <pointee2> ), ...
5775 The pointer, if already declared, should be an integer. Otherwise, we
5776 set it as BT_INTEGER with kind gfc_index_integer_kind. The pointee may
5777 be either a scalar, or an array declaration. No space is allocated for
5778 the pointee. For the statement
5779 pointer (ipt, ar(10))
5780 any subsequent uses of ar will be translated (in C-notation) as
5781 ar(i) => ((<type> *) ipt)(i)
5782 After gimplification, pointee variable will disappear in the code. */
5784 static match
5785 cray_pointer_decl (void)
5787 match m;
5788 gfc_array_spec *as;
5789 gfc_symbol *cptr; /* Pointer symbol. */
5790 gfc_symbol *cpte; /* Pointee symbol. */
5791 locus var_locus;
5792 bool done = false;
5794 while (!done)
5796 if (gfc_match_char ('(') != MATCH_YES)
5798 gfc_error ("Expected '(' at %C");
5799 return MATCH_ERROR;
5802 /* Match pointer. */
5803 var_locus = gfc_current_locus;
5804 gfc_clear_attr (&current_attr);
5805 gfc_add_cray_pointer (&current_attr, &var_locus);
5806 current_ts.type = BT_INTEGER;
5807 current_ts.kind = gfc_index_integer_kind;
5809 m = gfc_match_symbol (&cptr, 0);
5810 if (m != MATCH_YES)
5812 gfc_error ("Expected variable name at %C");
5813 return m;
5816 if (gfc_add_cray_pointer (&cptr->attr, &var_locus) == FAILURE)
5817 return MATCH_ERROR;
5819 gfc_set_sym_referenced (cptr);
5821 if (cptr->ts.type == BT_UNKNOWN) /* Override the type, if necessary. */
5823 cptr->ts.type = BT_INTEGER;
5824 cptr->ts.kind = gfc_index_integer_kind;
5826 else if (cptr->ts.type != BT_INTEGER)
5828 gfc_error ("Cray pointer at %C must be an integer");
5829 return MATCH_ERROR;
5831 else if (cptr->ts.kind < gfc_index_integer_kind)
5832 gfc_warning ("Cray pointer at %C has %d bytes of precision;"
5833 " memory addresses require %d bytes",
5834 cptr->ts.kind, gfc_index_integer_kind);
5836 if (gfc_match_char (',') != MATCH_YES)
5838 gfc_error ("Expected \",\" at %C");
5839 return MATCH_ERROR;
5842 /* Match Pointee. */
5843 var_locus = gfc_current_locus;
5844 gfc_clear_attr (&current_attr);
5845 gfc_add_cray_pointee (&current_attr, &var_locus);
5846 current_ts.type = BT_UNKNOWN;
5847 current_ts.kind = 0;
5849 m = gfc_match_symbol (&cpte, 0);
5850 if (m != MATCH_YES)
5852 gfc_error ("Expected variable name at %C");
5853 return m;
5856 /* Check for an optional array spec. */
5857 m = gfc_match_array_spec (&as);
5858 if (m == MATCH_ERROR)
5860 gfc_free_array_spec (as);
5861 return m;
5863 else if (m == MATCH_NO)
5865 gfc_free_array_spec (as);
5866 as = NULL;
5869 if (gfc_add_cray_pointee (&cpte->attr, &var_locus) == FAILURE)
5870 return MATCH_ERROR;
5872 gfc_set_sym_referenced (cpte);
5874 if (cpte->as == NULL)
5876 if (gfc_set_array_spec (cpte, as, &var_locus) == FAILURE)
5877 gfc_internal_error ("Couldn't set Cray pointee array spec.");
5879 else if (as != NULL)
5881 gfc_error ("Duplicate array spec for Cray pointee at %C");
5882 gfc_free_array_spec (as);
5883 return MATCH_ERROR;
5886 as = NULL;
5888 if (cpte->as != NULL)
5890 /* Fix array spec. */
5891 m = gfc_mod_pointee_as (cpte->as);
5892 if (m == MATCH_ERROR)
5893 return m;
5896 /* Point the Pointee at the Pointer. */
5897 cpte->cp_pointer = cptr;
5899 if (gfc_match_char (')') != MATCH_YES)
5901 gfc_error ("Expected \")\" at %C");
5902 return MATCH_ERROR;
5904 m = gfc_match_char (',');
5905 if (m != MATCH_YES)
5906 done = true; /* Stop searching for more declarations. */
5910 if (m == MATCH_ERROR /* Failed when trying to find ',' above. */
5911 || gfc_match_eos () != MATCH_YES)
5913 gfc_error ("Expected \",\" or end of statement at %C");
5914 return MATCH_ERROR;
5916 return MATCH_YES;
5920 match
5921 gfc_match_external (void)
5924 gfc_clear_attr (&current_attr);
5925 current_attr.external = 1;
5927 return attr_decl ();
5931 match
5932 gfc_match_intent (void)
5934 sym_intent intent;
5936 /* This is not allowed within a BLOCK construct! */
5937 if (gfc_current_state () == COMP_BLOCK)
5939 gfc_error ("INTENT is not allowed inside of BLOCK at %C");
5940 return MATCH_ERROR;
5943 intent = match_intent_spec ();
5944 if (intent == INTENT_UNKNOWN)
5945 return MATCH_ERROR;
5947 gfc_clear_attr (&current_attr);
5948 current_attr.intent = intent;
5950 return attr_decl ();
5954 match
5955 gfc_match_intrinsic (void)
5958 gfc_clear_attr (&current_attr);
5959 current_attr.intrinsic = 1;
5961 return attr_decl ();
5965 match
5966 gfc_match_optional (void)
5968 /* This is not allowed within a BLOCK construct! */
5969 if (gfc_current_state () == COMP_BLOCK)
5971 gfc_error ("OPTIONAL is not allowed inside of BLOCK at %C");
5972 return MATCH_ERROR;
5975 gfc_clear_attr (&current_attr);
5976 current_attr.optional = 1;
5978 return attr_decl ();
5982 match
5983 gfc_match_pointer (void)
5985 gfc_gobble_whitespace ();
5986 if (gfc_peek_ascii_char () == '(')
5988 if (!gfc_option.flag_cray_pointer)
5990 gfc_error ("Cray pointer declaration at %C requires -fcray-pointer "
5991 "flag");
5992 return MATCH_ERROR;
5994 return cray_pointer_decl ();
5996 else
5998 gfc_clear_attr (&current_attr);
5999 current_attr.pointer = 1;
6001 return attr_decl ();
6006 match
6007 gfc_match_allocatable (void)
6009 gfc_clear_attr (&current_attr);
6010 current_attr.allocatable = 1;
6012 return attr_decl ();
6016 match
6017 gfc_match_dimension (void)
6019 gfc_clear_attr (&current_attr);
6020 current_attr.dimension = 1;
6022 return attr_decl ();
6026 match
6027 gfc_match_target (void)
6029 gfc_clear_attr (&current_attr);
6030 current_attr.target = 1;
6032 return attr_decl ();
6036 /* Match the list of entities being specified in a PUBLIC or PRIVATE
6037 statement. */
6039 static match
6040 access_attr_decl (gfc_statement st)
6042 char name[GFC_MAX_SYMBOL_LEN + 1];
6043 interface_type type;
6044 gfc_user_op *uop;
6045 gfc_symbol *sym;
6046 gfc_intrinsic_op op;
6047 match m;
6049 if (gfc_match (" ::") == MATCH_NO && gfc_match_space () == MATCH_NO)
6050 goto done;
6052 for (;;)
6054 m = gfc_match_generic_spec (&type, name, &op);
6055 if (m == MATCH_NO)
6056 goto syntax;
6057 if (m == MATCH_ERROR)
6058 return MATCH_ERROR;
6060 switch (type)
6062 case INTERFACE_NAMELESS:
6063 case INTERFACE_ABSTRACT:
6064 goto syntax;
6066 case INTERFACE_GENERIC:
6067 if (gfc_get_symbol (name, NULL, &sym))
6068 goto done;
6070 if (gfc_add_access (&sym->attr, (st == ST_PUBLIC)
6071 ? ACCESS_PUBLIC : ACCESS_PRIVATE,
6072 sym->name, NULL) == FAILURE)
6073 return MATCH_ERROR;
6075 break;
6077 case INTERFACE_INTRINSIC_OP:
6078 if (gfc_current_ns->operator_access[op] == ACCESS_UNKNOWN)
6080 gfc_current_ns->operator_access[op] =
6081 (st == ST_PUBLIC) ? ACCESS_PUBLIC : ACCESS_PRIVATE;
6083 else
6085 gfc_error ("Access specification of the %s operator at %C has "
6086 "already been specified", gfc_op2string (op));
6087 goto done;
6090 break;
6092 case INTERFACE_USER_OP:
6093 uop = gfc_get_uop (name);
6095 if (uop->access == ACCESS_UNKNOWN)
6097 uop->access = (st == ST_PUBLIC)
6098 ? ACCESS_PUBLIC : ACCESS_PRIVATE;
6100 else
6102 gfc_error ("Access specification of the .%s. operator at %C "
6103 "has already been specified", sym->name);
6104 goto done;
6107 break;
6110 if (gfc_match_char (',') == MATCH_NO)
6111 break;
6114 if (gfc_match_eos () != MATCH_YES)
6115 goto syntax;
6116 return MATCH_YES;
6118 syntax:
6119 gfc_syntax_error (st);
6121 done:
6122 return MATCH_ERROR;
6126 match
6127 gfc_match_protected (void)
6129 gfc_symbol *sym;
6130 match m;
6132 if (gfc_current_ns->proc_name->attr.flavor != FL_MODULE)
6134 gfc_error ("PROTECTED at %C only allowed in specification "
6135 "part of a module");
6136 return MATCH_ERROR;
6140 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PROTECTED statement at %C")
6141 == FAILURE)
6142 return MATCH_ERROR;
6144 if (gfc_match (" ::") == MATCH_NO && gfc_match_space () == MATCH_NO)
6146 return MATCH_ERROR;
6149 if (gfc_match_eos () == MATCH_YES)
6150 goto syntax;
6152 for(;;)
6154 m = gfc_match_symbol (&sym, 0);
6155 switch (m)
6157 case MATCH_YES:
6158 if (gfc_add_protected (&sym->attr, sym->name, &gfc_current_locus)
6159 == FAILURE)
6160 return MATCH_ERROR;
6161 goto next_item;
6163 case MATCH_NO:
6164 break;
6166 case MATCH_ERROR:
6167 return MATCH_ERROR;
6170 next_item:
6171 if (gfc_match_eos () == MATCH_YES)
6172 break;
6173 if (gfc_match_char (',') != MATCH_YES)
6174 goto syntax;
6177 return MATCH_YES;
6179 syntax:
6180 gfc_error ("Syntax error in PROTECTED statement at %C");
6181 return MATCH_ERROR;
6185 /* The PRIVATE statement is a bit weird in that it can be an attribute
6186 declaration, but also works as a standalone statement inside of a
6187 type declaration or a module. */
6189 match
6190 gfc_match_private (gfc_statement *st)
6193 if (gfc_match ("private") != MATCH_YES)
6194 return MATCH_NO;
6196 if (gfc_current_state () != COMP_MODULE
6197 && !(gfc_current_state () == COMP_DERIVED
6198 && gfc_state_stack->previous
6199 && gfc_state_stack->previous->state == COMP_MODULE)
6200 && !(gfc_current_state () == COMP_DERIVED_CONTAINS
6201 && gfc_state_stack->previous && gfc_state_stack->previous->previous
6202 && gfc_state_stack->previous->previous->state == COMP_MODULE))
6204 gfc_error ("PRIVATE statement at %C is only allowed in the "
6205 "specification part of a module");
6206 return MATCH_ERROR;
6209 if (gfc_current_state () == COMP_DERIVED)
6211 if (gfc_match_eos () == MATCH_YES)
6213 *st = ST_PRIVATE;
6214 return MATCH_YES;
6217 gfc_syntax_error (ST_PRIVATE);
6218 return MATCH_ERROR;
6221 if (gfc_match_eos () == MATCH_YES)
6223 *st = ST_PRIVATE;
6224 return MATCH_YES;
6227 *st = ST_ATTR_DECL;
6228 return access_attr_decl (ST_PRIVATE);
6232 match
6233 gfc_match_public (gfc_statement *st)
6236 if (gfc_match ("public") != MATCH_YES)
6237 return MATCH_NO;
6239 if (gfc_current_state () != COMP_MODULE)
6241 gfc_error ("PUBLIC statement at %C is only allowed in the "
6242 "specification part of a module");
6243 return MATCH_ERROR;
6246 if (gfc_match_eos () == MATCH_YES)
6248 *st = ST_PUBLIC;
6249 return MATCH_YES;
6252 *st = ST_ATTR_DECL;
6253 return access_attr_decl (ST_PUBLIC);
6257 /* Workhorse for gfc_match_parameter. */
6259 static match
6260 do_parm (void)
6262 gfc_symbol *sym;
6263 gfc_expr *init;
6264 match m;
6265 gfc_try t;
6267 m = gfc_match_symbol (&sym, 0);
6268 if (m == MATCH_NO)
6269 gfc_error ("Expected variable name at %C in PARAMETER statement");
6271 if (m != MATCH_YES)
6272 return m;
6274 if (gfc_match_char ('=') == MATCH_NO)
6276 gfc_error ("Expected = sign in PARAMETER statement at %C");
6277 return MATCH_ERROR;
6280 m = gfc_match_init_expr (&init);
6281 if (m == MATCH_NO)
6282 gfc_error ("Expected expression at %C in PARAMETER statement");
6283 if (m != MATCH_YES)
6284 return m;
6286 if (sym->ts.type == BT_UNKNOWN
6287 && gfc_set_default_type (sym, 1, NULL) == FAILURE)
6289 m = MATCH_ERROR;
6290 goto cleanup;
6293 if (gfc_check_assign_symbol (sym, init) == FAILURE
6294 || gfc_add_flavor (&sym->attr, FL_PARAMETER, sym->name, NULL) == FAILURE)
6296 m = MATCH_ERROR;
6297 goto cleanup;
6300 if (sym->value)
6302 gfc_error ("Initializing already initialized variable at %C");
6303 m = MATCH_ERROR;
6304 goto cleanup;
6307 t = add_init_expr_to_sym (sym->name, &init, &gfc_current_locus);
6308 return (t == SUCCESS) ? MATCH_YES : MATCH_ERROR;
6310 cleanup:
6311 gfc_free_expr (init);
6312 return m;
6316 /* Match a parameter statement, with the weird syntax that these have. */
6318 match
6319 gfc_match_parameter (void)
6321 match m;
6323 if (gfc_match_char ('(') == MATCH_NO)
6324 return MATCH_NO;
6326 for (;;)
6328 m = do_parm ();
6329 if (m != MATCH_YES)
6330 break;
6332 if (gfc_match (" )%t") == MATCH_YES)
6333 break;
6335 if (gfc_match_char (',') != MATCH_YES)
6337 gfc_error ("Unexpected characters in PARAMETER statement at %C");
6338 m = MATCH_ERROR;
6339 break;
6343 return m;
6347 /* Save statements have a special syntax. */
6349 match
6350 gfc_match_save (void)
6352 char n[GFC_MAX_SYMBOL_LEN+1];
6353 gfc_common_head *c;
6354 gfc_symbol *sym;
6355 match m;
6357 if (gfc_match_eos () == MATCH_YES)
6359 if (gfc_current_ns->seen_save)
6361 if (gfc_notify_std (GFC_STD_LEGACY, "Blanket SAVE statement at %C "
6362 "follows previous SAVE statement")
6363 == FAILURE)
6364 return MATCH_ERROR;
6367 gfc_current_ns->save_all = gfc_current_ns->seen_save = 1;
6368 return MATCH_YES;
6371 if (gfc_current_ns->save_all)
6373 if (gfc_notify_std (GFC_STD_LEGACY, "SAVE statement at %C follows "
6374 "blanket SAVE statement")
6375 == FAILURE)
6376 return MATCH_ERROR;
6379 gfc_match (" ::");
6381 for (;;)
6383 m = gfc_match_symbol (&sym, 0);
6384 switch (m)
6386 case MATCH_YES:
6387 if (gfc_add_save (&sym->attr, sym->name, &gfc_current_locus)
6388 == FAILURE)
6389 return MATCH_ERROR;
6390 goto next_item;
6392 case MATCH_NO:
6393 break;
6395 case MATCH_ERROR:
6396 return MATCH_ERROR;
6399 m = gfc_match (" / %n /", &n);
6400 if (m == MATCH_ERROR)
6401 return MATCH_ERROR;
6402 if (m == MATCH_NO)
6403 goto syntax;
6405 c = gfc_get_common (n, 0);
6406 c->saved = 1;
6408 gfc_current_ns->seen_save = 1;
6410 next_item:
6411 if (gfc_match_eos () == MATCH_YES)
6412 break;
6413 if (gfc_match_char (',') != MATCH_YES)
6414 goto syntax;
6417 return MATCH_YES;
6419 syntax:
6420 gfc_error ("Syntax error in SAVE statement at %C");
6421 return MATCH_ERROR;
6425 match
6426 gfc_match_value (void)
6428 gfc_symbol *sym;
6429 match m;
6431 /* This is not allowed within a BLOCK construct! */
6432 if (gfc_current_state () == COMP_BLOCK)
6434 gfc_error ("VALUE is not allowed inside of BLOCK at %C");
6435 return MATCH_ERROR;
6438 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: VALUE statement at %C")
6439 == FAILURE)
6440 return MATCH_ERROR;
6442 if (gfc_match (" ::") == MATCH_NO && gfc_match_space () == MATCH_NO)
6444 return MATCH_ERROR;
6447 if (gfc_match_eos () == MATCH_YES)
6448 goto syntax;
6450 for(;;)
6452 m = gfc_match_symbol (&sym, 0);
6453 switch (m)
6455 case MATCH_YES:
6456 if (gfc_add_value (&sym->attr, sym->name, &gfc_current_locus)
6457 == FAILURE)
6458 return MATCH_ERROR;
6459 goto next_item;
6461 case MATCH_NO:
6462 break;
6464 case MATCH_ERROR:
6465 return MATCH_ERROR;
6468 next_item:
6469 if (gfc_match_eos () == MATCH_YES)
6470 break;
6471 if (gfc_match_char (',') != MATCH_YES)
6472 goto syntax;
6475 return MATCH_YES;
6477 syntax:
6478 gfc_error ("Syntax error in VALUE statement at %C");
6479 return MATCH_ERROR;
6483 match
6484 gfc_match_volatile (void)
6486 gfc_symbol *sym;
6487 match m;
6489 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: VOLATILE statement at %C")
6490 == FAILURE)
6491 return MATCH_ERROR;
6493 if (gfc_match (" ::") == MATCH_NO && gfc_match_space () == MATCH_NO)
6495 return MATCH_ERROR;
6498 if (gfc_match_eos () == MATCH_YES)
6499 goto syntax;
6501 for(;;)
6503 /* VOLATILE is special because it can be added to host-associated
6504 symbols locally. */
6505 m = gfc_match_symbol (&sym, 1);
6506 switch (m)
6508 case MATCH_YES:
6509 if (gfc_add_volatile (&sym->attr, sym->name, &gfc_current_locus)
6510 == FAILURE)
6511 return MATCH_ERROR;
6512 goto next_item;
6514 case MATCH_NO:
6515 break;
6517 case MATCH_ERROR:
6518 return MATCH_ERROR;
6521 next_item:
6522 if (gfc_match_eos () == MATCH_YES)
6523 break;
6524 if (gfc_match_char (',') != MATCH_YES)
6525 goto syntax;
6528 return MATCH_YES;
6530 syntax:
6531 gfc_error ("Syntax error in VOLATILE statement at %C");
6532 return MATCH_ERROR;
6536 /* Match a module procedure statement. Note that we have to modify
6537 symbols in the parent's namespace because the current one was there
6538 to receive symbols that are in an interface's formal argument list. */
6540 match
6541 gfc_match_modproc (void)
6543 char name[GFC_MAX_SYMBOL_LEN + 1];
6544 gfc_symbol *sym;
6545 match m;
6546 gfc_namespace *module_ns;
6547 gfc_interface *old_interface_head, *interface;
6549 if (gfc_state_stack->state != COMP_INTERFACE
6550 || gfc_state_stack->previous == NULL
6551 || current_interface.type == INTERFACE_NAMELESS
6552 || current_interface.type == INTERFACE_ABSTRACT)
6554 gfc_error ("MODULE PROCEDURE at %C must be in a generic module "
6555 "interface");
6556 return MATCH_ERROR;
6559 module_ns = gfc_current_ns->parent;
6560 for (; module_ns; module_ns = module_ns->parent)
6561 if (module_ns->proc_name->attr.flavor == FL_MODULE
6562 || module_ns->proc_name->attr.flavor == FL_PROGRAM
6563 || (module_ns->proc_name->attr.flavor == FL_PROCEDURE
6564 && !module_ns->proc_name->attr.contained))
6565 break;
6567 if (module_ns == NULL)
6568 return MATCH_ERROR;
6570 /* Store the current state of the interface. We will need it if we
6571 end up with a syntax error and need to recover. */
6572 old_interface_head = gfc_current_interface_head ();
6574 for (;;)
6576 locus old_locus = gfc_current_locus;
6577 bool last = false;
6579 m = gfc_match_name (name);
6580 if (m == MATCH_NO)
6581 goto syntax;
6582 if (m != MATCH_YES)
6583 return MATCH_ERROR;
6585 /* Check for syntax error before starting to add symbols to the
6586 current namespace. */
6587 if (gfc_match_eos () == MATCH_YES)
6588 last = true;
6589 if (!last && gfc_match_char (',') != MATCH_YES)
6590 goto syntax;
6592 /* Now we're sure the syntax is valid, we process this item
6593 further. */
6594 if (gfc_get_symbol (name, module_ns, &sym))
6595 return MATCH_ERROR;
6597 if (sym->attr.intrinsic)
6599 gfc_error ("Intrinsic procedure at %L cannot be a MODULE "
6600 "PROCEDURE", &old_locus);
6601 return MATCH_ERROR;
6604 if (sym->attr.proc != PROC_MODULE
6605 && gfc_add_procedure (&sym->attr, PROC_MODULE,
6606 sym->name, NULL) == FAILURE)
6607 return MATCH_ERROR;
6609 if (gfc_add_interface (sym) == FAILURE)
6610 return MATCH_ERROR;
6612 sym->attr.mod_proc = 1;
6613 sym->declared_at = old_locus;
6615 if (last)
6616 break;
6619 return MATCH_YES;
6621 syntax:
6622 /* Restore the previous state of the interface. */
6623 interface = gfc_current_interface_head ();
6624 gfc_set_current_interface_head (old_interface_head);
6626 /* Free the new interfaces. */
6627 while (interface != old_interface_head)
6629 gfc_interface *i = interface->next;
6630 gfc_free (interface);
6631 interface = i;
6634 /* And issue a syntax error. */
6635 gfc_syntax_error (ST_MODULE_PROC);
6636 return MATCH_ERROR;
6640 /* Check a derived type that is being extended. */
6641 static gfc_symbol*
6642 check_extended_derived_type (char *name)
6644 gfc_symbol *extended;
6646 if (gfc_find_symbol (name, gfc_current_ns, 1, &extended))
6648 gfc_error ("Ambiguous symbol in TYPE definition at %C");
6649 return NULL;
6652 if (!extended)
6654 gfc_error ("No such symbol in TYPE definition at %C");
6655 return NULL;
6658 if (extended->attr.flavor != FL_DERIVED)
6660 gfc_error ("'%s' in EXTENDS expression at %C is not a "
6661 "derived type", name);
6662 return NULL;
6665 if (extended->attr.is_bind_c)
6667 gfc_error ("'%s' cannot be extended at %C because it "
6668 "is BIND(C)", extended->name);
6669 return NULL;
6672 if (extended->attr.sequence)
6674 gfc_error ("'%s' cannot be extended at %C because it "
6675 "is a SEQUENCE type", extended->name);
6676 return NULL;
6679 return extended;
6683 /* Match the optional attribute specifiers for a type declaration.
6684 Return MATCH_ERROR if an error is encountered in one of the handled
6685 attributes (public, private, bind(c)), MATCH_NO if what's found is
6686 not a handled attribute, and MATCH_YES otherwise. TODO: More error
6687 checking on attribute conflicts needs to be done. */
6689 match
6690 gfc_get_type_attr_spec (symbol_attribute *attr, char *name)
6692 /* See if the derived type is marked as private. */
6693 if (gfc_match (" , private") == MATCH_YES)
6695 if (gfc_current_state () != COMP_MODULE)
6697 gfc_error ("Derived type at %C can only be PRIVATE in the "
6698 "specification part of a module");
6699 return MATCH_ERROR;
6702 if (gfc_add_access (attr, ACCESS_PRIVATE, NULL, NULL) == FAILURE)
6703 return MATCH_ERROR;
6705 else if (gfc_match (" , public") == MATCH_YES)
6707 if (gfc_current_state () != COMP_MODULE)
6709 gfc_error ("Derived type at %C can only be PUBLIC in the "
6710 "specification part of a module");
6711 return MATCH_ERROR;
6714 if (gfc_add_access (attr, ACCESS_PUBLIC, NULL, NULL) == FAILURE)
6715 return MATCH_ERROR;
6717 else if (gfc_match (" , bind ( c )") == MATCH_YES)
6719 /* If the type is defined to be bind(c) it then needs to make
6720 sure that all fields are interoperable. This will
6721 need to be a semantic check on the finished derived type.
6722 See 15.2.3 (lines 9-12) of F2003 draft. */
6723 if (gfc_add_is_bind_c (attr, NULL, &gfc_current_locus, 0) != SUCCESS)
6724 return MATCH_ERROR;
6726 /* TODO: attr conflicts need to be checked, probably in symbol.c. */
6728 else if (gfc_match (" , abstract") == MATCH_YES)
6730 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: ABSTRACT type at %C")
6731 == FAILURE)
6732 return MATCH_ERROR;
6734 if (gfc_add_abstract (attr, &gfc_current_locus) == FAILURE)
6735 return MATCH_ERROR;
6737 else if (name && gfc_match(" , extends ( %n )", name) == MATCH_YES)
6739 if (gfc_add_extension (attr, &gfc_current_locus) == FAILURE)
6740 return MATCH_ERROR;
6742 else
6743 return MATCH_NO;
6745 /* If we get here, something matched. */
6746 return MATCH_YES;
6750 /* Assign a hash value for a derived type. The algorithm is that of
6751 SDBM. The hashed string is '[module_name #] derived_name'. */
6752 static unsigned int
6753 hash_value (gfc_symbol *sym)
6755 unsigned int hash = 0;
6756 const char *c;
6757 int i, len;
6759 /* Hash of the module or procedure name. */
6760 if (sym->module != NULL)
6761 c = sym->module;
6762 else if (sym->ns && sym->ns->proc_name
6763 && sym->ns->proc_name->attr.flavor == FL_MODULE)
6764 c = sym->ns->proc_name->name;
6765 else
6766 c = NULL;
6768 if (c)
6770 len = strlen (c);
6771 for (i = 0; i < len; i++, c++)
6772 hash = (hash << 6) + (hash << 16) - hash + (*c);
6774 /* Disambiguate between 'a' in 'aa' and 'aa' in 'a'. */
6775 hash = (hash << 6) + (hash << 16) - hash + '#';
6778 /* Hash of the derived type name. */
6779 len = strlen (sym->name);
6780 c = sym->name;
6781 for (i = 0; i < len; i++, c++)
6782 hash = (hash << 6) + (hash << 16) - hash + (*c);
6784 /* Return the hash but take the modulus for the sake of module read,
6785 even though this slightly increases the chance of collision. */
6786 return (hash % 100000000);
6790 /* Match the beginning of a derived type declaration. If a type name
6791 was the result of a function, then it is possible to have a symbol
6792 already to be known as a derived type yet have no components. */
6794 match
6795 gfc_match_derived_decl (void)
6797 char name[GFC_MAX_SYMBOL_LEN + 1];
6798 char parent[GFC_MAX_SYMBOL_LEN + 1];
6799 symbol_attribute attr;
6800 gfc_symbol *sym;
6801 gfc_symbol *extended;
6802 match m;
6803 match is_type_attr_spec = MATCH_NO;
6804 bool seen_attr = false;
6806 if (gfc_current_state () == COMP_DERIVED)
6807 return MATCH_NO;
6809 name[0] = '\0';
6810 parent[0] = '\0';
6811 gfc_clear_attr (&attr);
6812 extended = NULL;
6816 is_type_attr_spec = gfc_get_type_attr_spec (&attr, parent);
6817 if (is_type_attr_spec == MATCH_ERROR)
6818 return MATCH_ERROR;
6819 if (is_type_attr_spec == MATCH_YES)
6820 seen_attr = true;
6821 } while (is_type_attr_spec == MATCH_YES);
6823 /* Deal with derived type extensions. The extension attribute has
6824 been added to 'attr' but now the parent type must be found and
6825 checked. */
6826 if (parent[0])
6827 extended = check_extended_derived_type (parent);
6829 if (parent[0] && !extended)
6830 return MATCH_ERROR;
6832 if (gfc_match (" ::") != MATCH_YES && seen_attr)
6834 gfc_error ("Expected :: in TYPE definition at %C");
6835 return MATCH_ERROR;
6838 m = gfc_match (" %n%t", name);
6839 if (m != MATCH_YES)
6840 return m;
6842 /* Make sure the name is not the name of an intrinsic type. */
6843 if (gfc_is_intrinsic_typename (name))
6845 gfc_error ("Type name '%s' at %C cannot be the same as an intrinsic "
6846 "type", name);
6847 return MATCH_ERROR;
6850 if (gfc_get_symbol (name, NULL, &sym))
6851 return MATCH_ERROR;
6853 if (sym->ts.type != BT_UNKNOWN)
6855 gfc_error ("Derived type name '%s' at %C already has a basic type "
6856 "of %s", sym->name, gfc_typename (&sym->ts));
6857 return MATCH_ERROR;
6860 /* The symbol may already have the derived attribute without the
6861 components. The ways this can happen is via a function
6862 definition, an INTRINSIC statement or a subtype in another
6863 derived type that is a pointer. The first part of the AND clause
6864 is true if the symbol is not the return value of a function. */
6865 if (sym->attr.flavor != FL_DERIVED
6866 && gfc_add_flavor (&sym->attr, FL_DERIVED, sym->name, NULL) == FAILURE)
6867 return MATCH_ERROR;
6869 if (sym->components != NULL || sym->attr.zero_comp)
6871 gfc_error ("Derived type definition of '%s' at %C has already been "
6872 "defined", sym->name);
6873 return MATCH_ERROR;
6876 if (attr.access != ACCESS_UNKNOWN
6877 && gfc_add_access (&sym->attr, attr.access, sym->name, NULL) == FAILURE)
6878 return MATCH_ERROR;
6880 /* See if the derived type was labeled as bind(c). */
6881 if (attr.is_bind_c != 0)
6882 sym->attr.is_bind_c = attr.is_bind_c;
6884 /* Construct the f2k_derived namespace if it is not yet there. */
6885 if (!sym->f2k_derived)
6886 sym->f2k_derived = gfc_get_namespace (NULL, 0);
6888 if (extended && !sym->components)
6890 gfc_component *p;
6891 gfc_symtree *st;
6893 /* Add the extended derived type as the first component. */
6894 gfc_add_component (sym, parent, &p);
6895 sym->attr.extension = attr.extension;
6896 extended->refs++;
6897 gfc_set_sym_referenced (extended);
6899 p->ts.type = BT_DERIVED;
6900 p->ts.u.derived = extended;
6901 p->initializer = gfc_default_initializer (&p->ts);
6903 /* Provide the links between the extended type and its extension. */
6904 if (!extended->f2k_derived)
6905 extended->f2k_derived = gfc_get_namespace (NULL, 0);
6906 st = gfc_new_symtree (&extended->f2k_derived->sym_root, sym->name);
6907 st->n.sym = sym;
6910 if (!sym->vindex)
6911 /* Set the vindex for this type. */
6912 sym->vindex = hash_value (sym);
6914 /* Take over the ABSTRACT attribute. */
6915 sym->attr.abstract = attr.abstract;
6917 gfc_new_block = sym;
6919 return MATCH_YES;
6923 /* Cray Pointees can be declared as:
6924 pointer (ipt, a (n,m,...,*))
6925 By default, this is treated as an AS_ASSUMED_SIZE array. We'll
6926 cheat and set a constant bound of 1 for the last dimension, if this
6927 is the case. Since there is no bounds-checking for Cray Pointees,
6928 this will be okay. */
6930 match
6931 gfc_mod_pointee_as (gfc_array_spec *as)
6933 as->cray_pointee = true; /* This will be useful to know later. */
6934 if (as->type == AS_ASSUMED_SIZE)
6936 as->type = AS_EXPLICIT;
6937 as->upper[as->rank - 1] = gfc_int_expr (1);
6938 as->cp_was_assumed = true;
6940 else if (as->type == AS_ASSUMED_SHAPE)
6942 gfc_error ("Cray Pointee at %C cannot be assumed shape array");
6943 return MATCH_ERROR;
6945 return MATCH_YES;
6949 /* Match the enum definition statement, here we are trying to match
6950 the first line of enum definition statement.
6951 Returns MATCH_YES if match is found. */
6953 match
6954 gfc_match_enum (void)
6956 match m;
6958 m = gfc_match_eos ();
6959 if (m != MATCH_YES)
6960 return m;
6962 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: ENUM and ENUMERATOR at %C")
6963 == FAILURE)
6964 return MATCH_ERROR;
6966 return MATCH_YES;
6970 /* Returns an initializer whose value is one higher than the value of the
6971 LAST_INITIALIZER argument. If the argument is NULL, the
6972 initializers value will be set to zero. The initializer's kind
6973 will be set to gfc_c_int_kind.
6975 If -fshort-enums is given, the appropriate kind will be selected
6976 later after all enumerators have been parsed. A warning is issued
6977 here if an initializer exceeds gfc_c_int_kind. */
6979 static gfc_expr *
6980 enum_initializer (gfc_expr *last_initializer, locus where)
6982 gfc_expr *result;
6984 result = gfc_get_expr ();
6985 result->expr_type = EXPR_CONSTANT;
6986 result->ts.type = BT_INTEGER;
6987 result->ts.kind = gfc_c_int_kind;
6988 result->where = where;
6990 mpz_init (result->value.integer);
6992 if (last_initializer != NULL)
6994 mpz_add_ui (result->value.integer, last_initializer->value.integer, 1);
6995 result->where = last_initializer->where;
6997 if (gfc_check_integer_range (result->value.integer,
6998 gfc_c_int_kind) != ARITH_OK)
7000 gfc_error ("Enumerator exceeds the C integer type at %C");
7001 return NULL;
7004 else
7006 /* Control comes here, if it's the very first enumerator and no
7007 initializer has been given. It will be initialized to zero. */
7008 mpz_set_si (result->value.integer, 0);
7011 return result;
7015 /* Match a variable name with an optional initializer. When this
7016 subroutine is called, a variable is expected to be parsed next.
7017 Depending on what is happening at the moment, updates either the
7018 symbol table or the current interface. */
7020 static match
7021 enumerator_decl (void)
7023 char name[GFC_MAX_SYMBOL_LEN + 1];
7024 gfc_expr *initializer;
7025 gfc_array_spec *as = NULL;
7026 gfc_symbol *sym;
7027 locus var_locus;
7028 match m;
7029 gfc_try t;
7030 locus old_locus;
7032 initializer = NULL;
7033 old_locus = gfc_current_locus;
7035 /* When we get here, we've just matched a list of attributes and
7036 maybe a type and a double colon. The next thing we expect to see
7037 is the name of the symbol. */
7038 m = gfc_match_name (name);
7039 if (m != MATCH_YES)
7040 goto cleanup;
7042 var_locus = gfc_current_locus;
7044 /* OK, we've successfully matched the declaration. Now put the
7045 symbol in the current namespace. If we fail to create the symbol,
7046 bail out. */
7047 if (build_sym (name, NULL, &as, &var_locus) == FAILURE)
7049 m = MATCH_ERROR;
7050 goto cleanup;
7053 /* The double colon must be present in order to have initializers.
7054 Otherwise the statement is ambiguous with an assignment statement. */
7055 if (colon_seen)
7057 if (gfc_match_char ('=') == MATCH_YES)
7059 m = gfc_match_init_expr (&initializer);
7060 if (m == MATCH_NO)
7062 gfc_error ("Expected an initialization expression at %C");
7063 m = MATCH_ERROR;
7066 if (m != MATCH_YES)
7067 goto cleanup;
7071 /* If we do not have an initializer, the initialization value of the
7072 previous enumerator (stored in last_initializer) is incremented
7073 by 1 and is used to initialize the current enumerator. */
7074 if (initializer == NULL)
7075 initializer = enum_initializer (last_initializer, old_locus);
7077 if (initializer == NULL || initializer->ts.type != BT_INTEGER)
7079 gfc_error("ENUMERATOR %L not initialized with integer expression",
7080 &var_locus);
7081 m = MATCH_ERROR;
7082 gfc_free_enum_history ();
7083 goto cleanup;
7086 /* Store this current initializer, for the next enumerator variable
7087 to be parsed. add_init_expr_to_sym() zeros initializer, so we
7088 use last_initializer below. */
7089 last_initializer = initializer;
7090 t = add_init_expr_to_sym (name, &initializer, &var_locus);
7092 /* Maintain enumerator history. */
7093 gfc_find_symbol (name, NULL, 0, &sym);
7094 create_enum_history (sym, last_initializer);
7096 return (t == SUCCESS) ? MATCH_YES : MATCH_ERROR;
7098 cleanup:
7099 /* Free stuff up and return. */
7100 gfc_free_expr (initializer);
7102 return m;
7106 /* Match the enumerator definition statement. */
7108 match
7109 gfc_match_enumerator_def (void)
7111 match m;
7112 gfc_try t;
7114 gfc_clear_ts (&current_ts);
7116 m = gfc_match (" enumerator");
7117 if (m != MATCH_YES)
7118 return m;
7120 m = gfc_match (" :: ");
7121 if (m == MATCH_ERROR)
7122 return m;
7124 colon_seen = (m == MATCH_YES);
7126 if (gfc_current_state () != COMP_ENUM)
7128 gfc_error ("ENUM definition statement expected before %C");
7129 gfc_free_enum_history ();
7130 return MATCH_ERROR;
7133 (&current_ts)->type = BT_INTEGER;
7134 (&current_ts)->kind = gfc_c_int_kind;
7136 gfc_clear_attr (&current_attr);
7137 t = gfc_add_flavor (&current_attr, FL_PARAMETER, NULL, NULL);
7138 if (t == FAILURE)
7140 m = MATCH_ERROR;
7141 goto cleanup;
7144 for (;;)
7146 m = enumerator_decl ();
7147 if (m == MATCH_ERROR)
7148 goto cleanup;
7149 if (m == MATCH_NO)
7150 break;
7152 if (gfc_match_eos () == MATCH_YES)
7153 goto cleanup;
7154 if (gfc_match_char (',') != MATCH_YES)
7155 break;
7158 if (gfc_current_state () == COMP_ENUM)
7160 gfc_free_enum_history ();
7161 gfc_error ("Syntax error in ENUMERATOR definition at %C");
7162 m = MATCH_ERROR;
7165 cleanup:
7166 gfc_free_array_spec (current_as);
7167 current_as = NULL;
7168 return m;
7173 /* Match binding attributes. */
7175 static match
7176 match_binding_attributes (gfc_typebound_proc* ba, bool generic, bool ppc)
7178 bool found_passing = false;
7179 bool seen_ptr = false;
7180 match m = MATCH_YES;
7182 /* Intialize to defaults. Do so even before the MATCH_NO check so that in
7183 this case the defaults are in there. */
7184 ba->access = ACCESS_UNKNOWN;
7185 ba->pass_arg = NULL;
7186 ba->pass_arg_num = 0;
7187 ba->nopass = 0;
7188 ba->non_overridable = 0;
7189 ba->deferred = 0;
7190 ba->ppc = ppc;
7192 /* If we find a comma, we believe there are binding attributes. */
7193 m = gfc_match_char (',');
7194 if (m == MATCH_NO)
7195 goto done;
7199 /* Access specifier. */
7201 m = gfc_match (" public");
7202 if (m == MATCH_ERROR)
7203 goto error;
7204 if (m == MATCH_YES)
7206 if (ba->access != ACCESS_UNKNOWN)
7208 gfc_error ("Duplicate access-specifier at %C");
7209 goto error;
7212 ba->access = ACCESS_PUBLIC;
7213 continue;
7216 m = gfc_match (" private");
7217 if (m == MATCH_ERROR)
7218 goto error;
7219 if (m == MATCH_YES)
7221 if (ba->access != ACCESS_UNKNOWN)
7223 gfc_error ("Duplicate access-specifier at %C");
7224 goto error;
7227 ba->access = ACCESS_PRIVATE;
7228 continue;
7231 /* If inside GENERIC, the following is not allowed. */
7232 if (!generic)
7235 /* NOPASS flag. */
7236 m = gfc_match (" nopass");
7237 if (m == MATCH_ERROR)
7238 goto error;
7239 if (m == MATCH_YES)
7241 if (found_passing)
7243 gfc_error ("Binding attributes already specify passing,"
7244 " illegal NOPASS at %C");
7245 goto error;
7248 found_passing = true;
7249 ba->nopass = 1;
7250 continue;
7253 /* PASS possibly including argument. */
7254 m = gfc_match (" pass");
7255 if (m == MATCH_ERROR)
7256 goto error;
7257 if (m == MATCH_YES)
7259 char arg[GFC_MAX_SYMBOL_LEN + 1];
7261 if (found_passing)
7263 gfc_error ("Binding attributes already specify passing,"
7264 " illegal PASS at %C");
7265 goto error;
7268 m = gfc_match (" ( %n )", arg);
7269 if (m == MATCH_ERROR)
7270 goto error;
7271 if (m == MATCH_YES)
7272 ba->pass_arg = gfc_get_string (arg);
7273 gcc_assert ((m == MATCH_YES) == (ba->pass_arg != NULL));
7275 found_passing = true;
7276 ba->nopass = 0;
7277 continue;
7280 if (ppc)
7282 /* POINTER flag. */
7283 m = gfc_match (" pointer");
7284 if (m == MATCH_ERROR)
7285 goto error;
7286 if (m == MATCH_YES)
7288 if (seen_ptr)
7290 gfc_error ("Duplicate POINTER attribute at %C");
7291 goto error;
7294 seen_ptr = true;
7295 continue;
7298 else
7300 /* NON_OVERRIDABLE flag. */
7301 m = gfc_match (" non_overridable");
7302 if (m == MATCH_ERROR)
7303 goto error;
7304 if (m == MATCH_YES)
7306 if (ba->non_overridable)
7308 gfc_error ("Duplicate NON_OVERRIDABLE at %C");
7309 goto error;
7312 ba->non_overridable = 1;
7313 continue;
7316 /* DEFERRED flag. */
7317 m = gfc_match (" deferred");
7318 if (m == MATCH_ERROR)
7319 goto error;
7320 if (m == MATCH_YES)
7322 if (ba->deferred)
7324 gfc_error ("Duplicate DEFERRED at %C");
7325 goto error;
7328 ba->deferred = 1;
7329 continue;
7335 /* Nothing matching found. */
7336 if (generic)
7337 gfc_error ("Expected access-specifier at %C");
7338 else
7339 gfc_error ("Expected binding attribute at %C");
7340 goto error;
7342 while (gfc_match_char (',') == MATCH_YES);
7344 /* NON_OVERRIDABLE and DEFERRED exclude themselves. */
7345 if (ba->non_overridable && ba->deferred)
7347 gfc_error ("NON_OVERRIDABLE and DEFERRED can't both appear at %C");
7348 goto error;
7351 m = MATCH_YES;
7353 done:
7354 if (ba->access == ACCESS_UNKNOWN)
7355 ba->access = gfc_typebound_default_access;
7357 if (ppc && !seen_ptr)
7359 gfc_error ("POINTER attribute is required for procedure pointer component"
7360 " at %C");
7361 goto error;
7364 return m;
7366 error:
7367 return MATCH_ERROR;
7371 /* Match a PROCEDURE specific binding inside a derived type. */
7373 static match
7374 match_procedure_in_type (void)
7376 char name[GFC_MAX_SYMBOL_LEN + 1];
7377 char target_buf[GFC_MAX_SYMBOL_LEN + 1];
7378 char* target = NULL;
7379 gfc_typebound_proc* tb;
7380 bool seen_colons;
7381 bool seen_attrs;
7382 match m;
7383 gfc_symtree* stree;
7384 gfc_namespace* ns;
7385 gfc_symbol* block;
7387 /* Check current state. */
7388 gcc_assert (gfc_state_stack->state == COMP_DERIVED_CONTAINS);
7389 block = gfc_state_stack->previous->sym;
7390 gcc_assert (block);
7392 /* Try to match PROCEDURE(interface). */
7393 if (gfc_match (" (") == MATCH_YES)
7395 m = gfc_match_name (target_buf);
7396 if (m == MATCH_ERROR)
7397 return m;
7398 if (m != MATCH_YES)
7400 gfc_error ("Interface-name expected after '(' at %C");
7401 return MATCH_ERROR;
7404 if (gfc_match (" )") != MATCH_YES)
7406 gfc_error ("')' expected at %C");
7407 return MATCH_ERROR;
7410 target = target_buf;
7413 /* Construct the data structure. */
7414 tb = gfc_get_typebound_proc ();
7415 tb->where = gfc_current_locus;
7416 tb->is_generic = 0;
7418 /* Match binding attributes. */
7419 m = match_binding_attributes (tb, false, false);
7420 if (m == MATCH_ERROR)
7421 return m;
7422 seen_attrs = (m == MATCH_YES);
7424 /* Check that attribute DEFERRED is given iff an interface is specified, which
7425 means target != NULL. */
7426 if (tb->deferred && !target)
7428 gfc_error ("Interface must be specified for DEFERRED binding at %C");
7429 return MATCH_ERROR;
7431 if (target && !tb->deferred)
7433 gfc_error ("PROCEDURE(interface) at %C should be declared DEFERRED");
7434 return MATCH_ERROR;
7437 /* Match the colons. */
7438 m = gfc_match (" ::");
7439 if (m == MATCH_ERROR)
7440 return m;
7441 seen_colons = (m == MATCH_YES);
7442 if (seen_attrs && !seen_colons)
7444 gfc_error ("Expected '::' after binding-attributes at %C");
7445 return MATCH_ERROR;
7448 /* Match the binding name. */
7449 m = gfc_match_name (name);
7450 if (m == MATCH_ERROR)
7451 return m;
7452 if (m == MATCH_NO)
7454 gfc_error ("Expected binding name at %C");
7455 return MATCH_ERROR;
7458 /* Try to match the '=> target', if it's there. */
7459 m = gfc_match (" =>");
7460 if (m == MATCH_ERROR)
7461 return m;
7462 if (m == MATCH_YES)
7464 if (tb->deferred)
7466 gfc_error ("'=> target' is invalid for DEFERRED binding at %C");
7467 return MATCH_ERROR;
7470 if (!seen_colons)
7472 gfc_error ("'::' needed in PROCEDURE binding with explicit target"
7473 " at %C");
7474 return MATCH_ERROR;
7477 m = gfc_match_name (target_buf);
7478 if (m == MATCH_ERROR)
7479 return m;
7480 if (m == MATCH_NO)
7482 gfc_error ("Expected binding target after '=>' at %C");
7483 return MATCH_ERROR;
7485 target = target_buf;
7488 /* Now we should have the end. */
7489 m = gfc_match_eos ();
7490 if (m == MATCH_ERROR)
7491 return m;
7492 if (m == MATCH_NO)
7494 gfc_error ("Junk after PROCEDURE declaration at %C");
7495 return MATCH_ERROR;
7498 /* If no target was found, it has the same name as the binding. */
7499 if (!target)
7500 target = name;
7502 /* Get the namespace to insert the symbols into. */
7503 ns = block->f2k_derived;
7504 gcc_assert (ns);
7506 /* If the binding is DEFERRED, check that the containing type is ABSTRACT. */
7507 if (tb->deferred && !block->attr.abstract)
7509 gfc_error ("Type '%s' containing DEFERRED binding at %C is not ABSTRACT",
7510 block->name);
7511 return MATCH_ERROR;
7514 /* See if we already have a binding with this name in the symtree which would
7515 be an error. If a GENERIC already targetted this binding, it may be
7516 already there but then typebound is still NULL. */
7517 stree = gfc_find_symtree (ns->tb_sym_root, name);
7518 if (stree && stree->n.tb)
7520 gfc_error ("There's already a procedure with binding name '%s' for the"
7521 " derived type '%s' at %C", name, block->name);
7522 return MATCH_ERROR;
7525 /* Insert it and set attributes. */
7527 if (!stree)
7529 stree = gfc_new_symtree (&ns->tb_sym_root, name);
7530 gcc_assert (stree);
7532 stree->n.tb = tb;
7534 if (gfc_get_sym_tree (target, gfc_current_ns, &tb->u.specific, false))
7535 return MATCH_ERROR;
7536 gfc_set_sym_referenced (tb->u.specific->n.sym);
7538 return MATCH_YES;
7542 /* Match a GENERIC procedure binding inside a derived type. */
7544 match
7545 gfc_match_generic (void)
7547 char name[GFC_MAX_SYMBOL_LEN + 1];
7548 char bind_name[GFC_MAX_SYMBOL_LEN + 16]; /* Allow space for OPERATOR(...). */
7549 gfc_symbol* block;
7550 gfc_typebound_proc tbattr; /* Used for match_binding_attributes. */
7551 gfc_typebound_proc* tb;
7552 gfc_namespace* ns;
7553 interface_type op_type;
7554 gfc_intrinsic_op op;
7555 match m;
7557 /* Check current state. */
7558 if (gfc_current_state () == COMP_DERIVED)
7560 gfc_error ("GENERIC at %C must be inside a derived-type CONTAINS");
7561 return MATCH_ERROR;
7563 if (gfc_current_state () != COMP_DERIVED_CONTAINS)
7564 return MATCH_NO;
7565 block = gfc_state_stack->previous->sym;
7566 ns = block->f2k_derived;
7567 gcc_assert (block && ns);
7569 /* See if we get an access-specifier. */
7570 m = match_binding_attributes (&tbattr, true, false);
7571 if (m == MATCH_ERROR)
7572 goto error;
7574 /* Now the colons, those are required. */
7575 if (gfc_match (" ::") != MATCH_YES)
7577 gfc_error ("Expected '::' at %C");
7578 goto error;
7581 /* Match the binding name; depending on type (operator / generic) format
7582 it for future error messages into bind_name. */
7584 m = gfc_match_generic_spec (&op_type, name, &op);
7585 if (m == MATCH_ERROR)
7586 return MATCH_ERROR;
7587 if (m == MATCH_NO)
7589 gfc_error ("Expected generic name or operator descriptor at %C");
7590 goto error;
7593 switch (op_type)
7595 case INTERFACE_GENERIC:
7596 snprintf (bind_name, sizeof (bind_name), "%s", name);
7597 break;
7599 case INTERFACE_USER_OP:
7600 snprintf (bind_name, sizeof (bind_name), "OPERATOR(.%s.)", name);
7601 break;
7603 case INTERFACE_INTRINSIC_OP:
7604 snprintf (bind_name, sizeof (bind_name), "OPERATOR(%s)",
7605 gfc_op2string (op));
7606 break;
7608 default:
7609 gcc_unreachable ();
7612 /* Match the required =>. */
7613 if (gfc_match (" =>") != MATCH_YES)
7615 gfc_error ("Expected '=>' at %C");
7616 goto error;
7619 /* Try to find existing GENERIC binding with this name / for this operator;
7620 if there is something, check that it is another GENERIC and then extend
7621 it rather than building a new node. Otherwise, create it and put it
7622 at the right position. */
7624 switch (op_type)
7626 case INTERFACE_USER_OP:
7627 case INTERFACE_GENERIC:
7629 const bool is_op = (op_type == INTERFACE_USER_OP);
7630 gfc_symtree* st;
7632 st = gfc_find_symtree (is_op ? ns->tb_uop_root : ns->tb_sym_root, name);
7633 if (st)
7635 tb = st->n.tb;
7636 gcc_assert (tb);
7638 else
7639 tb = NULL;
7641 break;
7644 case INTERFACE_INTRINSIC_OP:
7645 tb = ns->tb_op[op];
7646 break;
7648 default:
7649 gcc_unreachable ();
7652 if (tb)
7654 if (!tb->is_generic)
7656 gcc_assert (op_type == INTERFACE_GENERIC);
7657 gfc_error ("There's already a non-generic procedure with binding name"
7658 " '%s' for the derived type '%s' at %C",
7659 bind_name, block->name);
7660 goto error;
7663 if (tb->access != tbattr.access)
7665 gfc_error ("Binding at %C must have the same access as already"
7666 " defined binding '%s'", bind_name);
7667 goto error;
7670 else
7672 tb = gfc_get_typebound_proc ();
7673 tb->where = gfc_current_locus;
7674 tb->access = tbattr.access;
7675 tb->is_generic = 1;
7676 tb->u.generic = NULL;
7678 switch (op_type)
7680 case INTERFACE_GENERIC:
7681 case INTERFACE_USER_OP:
7683 const bool is_op = (op_type == INTERFACE_USER_OP);
7684 gfc_symtree* st;
7686 st = gfc_new_symtree (is_op ? &ns->tb_uop_root : &ns->tb_sym_root,
7687 name);
7688 gcc_assert (st);
7689 st->n.tb = tb;
7691 break;
7694 case INTERFACE_INTRINSIC_OP:
7695 ns->tb_op[op] = tb;
7696 break;
7698 default:
7699 gcc_unreachable ();
7703 /* Now, match all following names as specific targets. */
7706 gfc_symtree* target_st;
7707 gfc_tbp_generic* target;
7709 m = gfc_match_name (name);
7710 if (m == MATCH_ERROR)
7711 goto error;
7712 if (m == MATCH_NO)
7714 gfc_error ("Expected specific binding name at %C");
7715 goto error;
7718 target_st = gfc_get_tbp_symtree (&ns->tb_sym_root, name);
7720 /* See if this is a duplicate specification. */
7721 for (target = tb->u.generic; target; target = target->next)
7722 if (target_st == target->specific_st)
7724 gfc_error ("'%s' already defined as specific binding for the"
7725 " generic '%s' at %C", name, bind_name);
7726 goto error;
7729 target = gfc_get_tbp_generic ();
7730 target->specific_st = target_st;
7731 target->specific = NULL;
7732 target->next = tb->u.generic;
7733 tb->u.generic = target;
7735 while (gfc_match (" ,") == MATCH_YES);
7737 /* Here should be the end. */
7738 if (gfc_match_eos () != MATCH_YES)
7740 gfc_error ("Junk after GENERIC binding at %C");
7741 goto error;
7744 return MATCH_YES;
7746 error:
7747 return MATCH_ERROR;
7751 /* Match a FINAL declaration inside a derived type. */
7753 match
7754 gfc_match_final_decl (void)
7756 char name[GFC_MAX_SYMBOL_LEN + 1];
7757 gfc_symbol* sym;
7758 match m;
7759 gfc_namespace* module_ns;
7760 bool first, last;
7761 gfc_symbol* block;
7763 if (gfc_state_stack->state != COMP_DERIVED_CONTAINS)
7765 gfc_error ("FINAL declaration at %C must be inside a derived type "
7766 "CONTAINS section");
7767 return MATCH_ERROR;
7770 block = gfc_state_stack->previous->sym;
7771 gcc_assert (block);
7773 if (!gfc_state_stack->previous || !gfc_state_stack->previous->previous
7774 || gfc_state_stack->previous->previous->state != COMP_MODULE)
7776 gfc_error ("Derived type declaration with FINAL at %C must be in the"
7777 " specification part of a MODULE");
7778 return MATCH_ERROR;
7781 module_ns = gfc_current_ns;
7782 gcc_assert (module_ns);
7783 gcc_assert (module_ns->proc_name->attr.flavor == FL_MODULE);
7785 /* Match optional ::, don't care about MATCH_YES or MATCH_NO. */
7786 if (gfc_match (" ::") == MATCH_ERROR)
7787 return MATCH_ERROR;
7789 /* Match the sequence of procedure names. */
7790 first = true;
7791 last = false;
7794 gfc_finalizer* f;
7796 if (first && gfc_match_eos () == MATCH_YES)
7798 gfc_error ("Empty FINAL at %C");
7799 return MATCH_ERROR;
7802 m = gfc_match_name (name);
7803 if (m == MATCH_NO)
7805 gfc_error ("Expected module procedure name at %C");
7806 return MATCH_ERROR;
7808 else if (m != MATCH_YES)
7809 return MATCH_ERROR;
7811 if (gfc_match_eos () == MATCH_YES)
7812 last = true;
7813 if (!last && gfc_match_char (',') != MATCH_YES)
7815 gfc_error ("Expected ',' at %C");
7816 return MATCH_ERROR;
7819 if (gfc_get_symbol (name, module_ns, &sym))
7821 gfc_error ("Unknown procedure name \"%s\" at %C", name);
7822 return MATCH_ERROR;
7825 /* Mark the symbol as module procedure. */
7826 if (sym->attr.proc != PROC_MODULE
7827 && gfc_add_procedure (&sym->attr, PROC_MODULE,
7828 sym->name, NULL) == FAILURE)
7829 return MATCH_ERROR;
7831 /* Check if we already have this symbol in the list, this is an error. */
7832 for (f = block->f2k_derived->finalizers; f; f = f->next)
7833 if (f->proc_sym == sym)
7835 gfc_error ("'%s' at %C is already defined as FINAL procedure!",
7836 name);
7837 return MATCH_ERROR;
7840 /* Add this symbol to the list of finalizers. */
7841 gcc_assert (block->f2k_derived);
7842 ++sym->refs;
7843 f = XCNEW (gfc_finalizer);
7844 f->proc_sym = sym;
7845 f->proc_tree = NULL;
7846 f->where = gfc_current_locus;
7847 f->next = block->f2k_derived->finalizers;
7848 block->f2k_derived->finalizers = f;
7850 first = false;
7852 while (!last);
7854 return MATCH_YES;
7858 const ext_attr_t ext_attr_list[] = {
7859 { "dllimport", EXT_ATTR_DLLIMPORT, "dllimport" },
7860 { "dllexport", EXT_ATTR_DLLEXPORT, "dllexport" },
7861 { "cdecl", EXT_ATTR_CDECL, "cdecl" },
7862 { "stdcall", EXT_ATTR_STDCALL, "stdcall" },
7863 { "fastcall", EXT_ATTR_FASTCALL, "fastcall" },
7864 { NULL, EXT_ATTR_LAST, NULL }
7867 /* Match a !GCC$ ATTRIBUTES statement of the form:
7868 !GCC$ ATTRIBUTES attribute-list :: var-name [, var-name] ...
7869 When we come here, we have already matched the !GCC$ ATTRIBUTES string.
7871 TODO: We should support all GCC attributes using the same syntax for
7872 the attribute list, i.e. the list in C
7873 __attributes(( attribute-list ))
7874 matches then
7875 !GCC$ ATTRIBUTES attribute-list ::
7876 Cf. c-parser.c's c_parser_attributes; the data can then directly be
7877 saved into a TREE.
7879 As there is absolutely no risk of confusion, we should never return
7880 MATCH_NO. */
7881 match
7882 gfc_match_gcc_attributes (void)
7884 symbol_attribute attr;
7885 char name[GFC_MAX_SYMBOL_LEN + 1];
7886 unsigned id;
7887 gfc_symbol *sym;
7888 match m;
7890 gfc_clear_attr (&attr);
7891 for(;;)
7893 char ch;
7895 if (gfc_match_name (name) != MATCH_YES)
7896 return MATCH_ERROR;
7898 for (id = 0; id < EXT_ATTR_LAST; id++)
7899 if (strcmp (name, ext_attr_list[id].name) == 0)
7900 break;
7902 if (id == EXT_ATTR_LAST)
7904 gfc_error ("Unknown attribute in !GCC$ ATTRIBUTES statement at %C");
7905 return MATCH_ERROR;
7908 if (gfc_add_ext_attribute (&attr, (ext_attr_id_t) id, &gfc_current_locus)
7909 == FAILURE)
7910 return MATCH_ERROR;
7912 gfc_gobble_whitespace ();
7913 ch = gfc_next_ascii_char ();
7914 if (ch == ':')
7916 /* This is the successful exit condition for the loop. */
7917 if (gfc_next_ascii_char () == ':')
7918 break;
7921 if (ch == ',')
7922 continue;
7924 goto syntax;
7927 if (gfc_match_eos () == MATCH_YES)
7928 goto syntax;
7930 for(;;)
7932 m = gfc_match_name (name);
7933 if (m != MATCH_YES)
7934 return m;
7936 if (find_special (name, &sym, true))
7937 return MATCH_ERROR;
7939 sym->attr.ext_attr |= attr.ext_attr;
7941 if (gfc_match_eos () == MATCH_YES)
7942 break;
7944 if (gfc_match_char (',') != MATCH_YES)
7945 goto syntax;
7948 return MATCH_YES;
7950 syntax:
7951 gfc_error ("Syntax error in !GCC$ ATTRIBUTES statement at %C");
7952 return MATCH_ERROR;