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
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
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/>. */
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
73 gfc_expr *initializer;
74 struct enumerator_history *next;
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;
98 gfc_in_match_data (void)
100 return in_match_data;
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. */
112 free_variable (gfc_data_variable *p)
114 gfc_data_variable *q;
119 gfc_free_expr (p->expr);
120 gfc_free_iterator (&p->iter, 0);
121 free_variable (p->list);
127 /* Free a gfc_data_value structure and everything beneath it. */
130 free_value (gfc_data_value *p)
137 gfc_free_expr (p->expr);
143 /* Free a list of gfc_data structures. */
146 gfc_free_data (gfc_data *p)
153 free_variable (p->var);
154 free_value (p->value);
160 /* Free all data in a namespace. */
163 gfc_free_data_all (gfc_namespace *ns)
176 static match var_element (gfc_data_variable *);
178 /* Match a list of variables terminated by an iterator and a right
182 var_list (gfc_data_variable *parent)
184 gfc_data_variable *tail, var;
187 m = var_element (&var);
188 if (m == MATCH_ERROR)
193 tail = gfc_get_data_variable ();
200 if (gfc_match_char (',') != MATCH_YES)
203 m = gfc_match_iterator (&parent->iter, 1);
206 if (m == MATCH_ERROR)
209 m = var_element (&var);
210 if (m == MATCH_ERROR)
215 tail->next = gfc_get_data_variable ();
221 if (gfc_match_char (')') != MATCH_YES)
226 gfc_syntax_error (ST_DATA);
231 /* Match a single element in a data variable list, which can be a
232 variable-iterator list. */
235 var_element (gfc_data_variable *new_var)
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);
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)
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);
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)
271 if (gfc_add_data (&sym->attr, sym->name, &new_var->expr->where) == FAILURE)
278 /* Match the top-level list of data variables. */
281 top_var_list (gfc_data *d)
283 gfc_data_variable var, *tail, *new_var;
290 m = var_element (&var);
293 if (m == MATCH_ERROR)
296 new_var = gfc_get_data_variable ();
302 tail->next = new_var;
306 if (gfc_match_char ('/') == MATCH_YES)
308 if (gfc_match_char (',') != MATCH_YES)
315 gfc_syntax_error (ST_DATA);
316 gfc_free_data_all (gfc_current_ns);
322 match_data_constant (gfc_expr **result)
324 char name[GFC_MAX_SYMBOL_LEN + 1];
330 m = gfc_match_literal_constant (&expr, 1);
337 if (m == MATCH_ERROR)
340 m = gfc_match_null (result);
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)
352 if (m == MATCH_YES && (*result)->expr_type == EXPR_STRUCTURE)
354 if (gfc_simplify_expr (*result, 0) == FAILURE)
359 gfc_current_locus = old_loc;
361 m = gfc_match_name (name);
365 if (gfc_find_symbol (name, NULL, 1, &sym))
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",
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)
389 if (gfc_simplify_expr (*result, 0) == FAILURE)
392 if ((*result)->expr_type == EXPR_CONSTANT)
396 gfc_error ("Invalid initializer %s in Data statement at %C", name);
402 *result = gfc_copy_expr (sym->value);
407 /* Match a list of values in a DATA statement. The leading '/' has
408 already been seen at this point. */
411 top_val_list (gfc_data *data)
413 gfc_data_value *new_val, *tail;
421 m = match_data_constant (&expr);
424 if (m == MATCH_ERROR)
427 new_val = gfc_get_data_value ();
428 mpz_init (new_val->repeat);
431 data->value = new_val;
433 tail->next = new_val;
437 if (expr->ts.type != BT_INTEGER || gfc_match_char ('*') != MATCH_YES)
440 mpz_set_ui (tail->repeat, 1);
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);
451 if (m == MATCH_ERROR)
455 if (gfc_match_char ('/') == MATCH_YES)
457 if (gfc_match_char (',') == MATCH_NO)
464 gfc_syntax_error (ST_DATA);
465 gfc_free_data_all (gfc_current_ns);
470 /* Matches an old style initialization. */
473 match_old_style_init (const char *name)
480 /* Set up data structure to hold initializers. */
481 gfc_find_sym_tree (name, NULL, 0, &st);
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);
499 gfc_error ("Initialization at %C is not allowed in a PURE procedure");
504 /* Mark the variable as having appeared in a data statement. */
505 if (gfc_add_data (&sym->attr, sym->name, &sym->declared_at) == FAILURE)
511 /* Chain in namespace list of DATA initializers. */
512 newdata->next = gfc_current_ns->data;
513 gfc_current_ns->data = newdata;
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/. */
525 gfc_match_data (void)
530 set_in_match_data (true);
534 new_data = gfc_get_data ();
535 new_data->where = gfc_current_locus;
537 m = top_var_list (new_data);
541 m = top_val_list (new_data);
545 new_data->next = gfc_current_ns->data;
546 gfc_current_ns->data = new_data;
548 if (gfc_match_eos () == MATCH_YES)
551 gfc_match_char (','); /* Optional comma */
554 set_in_match_data (false);
558 gfc_error ("DATA statement at %C is not allowed in a PURE procedure");
565 set_in_match_data (false);
566 gfc_free_data (new_data);
571 /************************ Declaration statements *********************/
573 /* Match an intent specification. Since this can only happen after an
574 INTENT word, a legal intent-spec must follow. */
577 match_intent_spec (void)
580 if (gfc_match (" ( in out )") == MATCH_YES)
582 if (gfc_match (" ( in )") == MATCH_YES)
584 if (gfc_match (" ( out )") == MATCH_YES)
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 '*'. */
596 char_len_param_value (gfc_expr **expr)
600 if (gfc_match_char ('*') == MATCH_YES)
606 m = gfc_match_expr (expr);
609 && gfc_expr_check_typed (*expr, gfc_current_ns, false) == FAILURE)
612 if (m == MATCH_YES && (*expr)->expr_type == EXPR_FUNCTION)
614 if ((*expr)->value.function.actual
615 && (*expr)->value.function.actual->expr->symtree)
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)
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)
634 gfc_error ("Conflict in attributes of function argument at %C");
639 /* A character length is a '*' followed by a literal integer or a
640 char_len_param_value in parenthesis. */
643 match_char_length (gfc_expr **expr)
648 m = gfc_match_char ('*');
652 m = gfc_match_small_literal_int (&length, NULL);
653 if (m == MATCH_ERROR)
658 if (gfc_notify_std (GFC_STD_F95_OBS, "Obsolescent feature: "
659 "Old-style character length at %C") == FAILURE)
661 *expr = gfc_int_expr (length);
665 if (gfc_match_char ('(') == MATCH_NO)
668 m = char_len_param_value (expr);
669 if (m != MATCH_YES && gfc_matching_function)
675 if (m == MATCH_ERROR)
680 if (gfc_match_char (')') == MATCH_NO)
682 gfc_free_expr (*expr);
690 gfc_error ("Syntax error in character length specification at %C");
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). */
702 find_special (const char *name, gfc_symbol **result, bool allow_subroutine)
708 i = gfc_get_sym_tree (name, NULL, &st, allow_subroutine);
711 *result = st ? st->n.sym : NULL;
715 if (gfc_current_state () != COMP_SUBROUTINE
716 && gfc_current_state () != COMP_FUNCTION)
719 s = gfc_state_stack->previous;
723 if (s->state != COMP_INTERFACE)
726 goto end; /* Nameless interface. */
728 if (strcmp (name, s->sym->name) == 0)
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. */
746 get_proc_name (const char *name, gfc_symbol **result, bool module_fcn_entry)
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);
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
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
785 (*result)->ns = gfc_current_ns;
787 gfc_find_sym_tree (name, gfc_current_ns, 0, &st);
789 st = gfc_get_unique_symtree (gfc_current_ns);
794 rc = gfc_get_symbol (name, gfc_current_ns->parent, 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
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)
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);
849 st = gfc_new_symtree (&gfc_current_ns->parent->sym_root, name);
852 st = gfc_new_symtree (&gfc_current_ns->sym_root, name);
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)
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
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)
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
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));
914 if (sym->attr.is_c_interop == 1)
915 /* We've already checked this procedure; don't check it again. */
918 return verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
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)
929 (verify_c_interop (&(sym->ts))
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);
943 gfc_warning ("Variable '%s' at %L is a parameter to the "
944 "BIND(C) procedure '%s' but may not be C "
946 sym->name, &(sym->declared_at),
947 sym->ns->proc_name->name);
950 /* Character strings are only C interoperable if they have a
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);
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);
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);
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);
997 /* Make sure that if it has the dimension attribute, that it is
998 either assumed size or explicit shape. */
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));
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));
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. */
1034 encapsulate_class_symbol (gfc_typespec *ts, symbol_attribute *attr,
1035 gfc_array_spec **as)
1037 char name[GFC_MAX_SYMBOL_LEN + 5];
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);
1049 sprintf (name, ".class.%s", ts->u.derived->name);
1051 gfc_find_symbol (name, ts->u.derived->ns, 0, &fclass);
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);
1059 gfc_set_sym_referenced (fclass);
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)
1070 /* Add component '$data'. */
1071 if (gfc_add_component (fclass, "$data", &c) == FAILURE)
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;
1081 c->initializer = gfc_get_expr ();
1082 c->initializer->expr_type = EXPR_NULL;
1084 /* Add component '$vindex'. */
1085 if (gfc_add_component (fclass, "$vindex", &c) == FAILURE)
1087 c->ts.type = BT_INTEGER;
1089 c->attr.access = ACCESS_PRIVATE;
1090 c->initializer = gfc_int_expr (0);
1093 fclass->attr.extension = 1;
1094 fclass->attr.is_class = 1;
1095 ts->u.derived = fclass;
1096 attr->allocatable = attr->pointer = attr->dimension = 0;
1097 (*as) = NULL; /* XXX */
1101 /* Function called by variable_decl() that adds a name to the symbol table. */
1104 build_sym (const char *name, gfc_charlen *cl,
1105 gfc_array_spec **as, locus *var_locus)
1107 symbol_attribute attr;
1110 if (gfc_get_symbol (name, NULL, &sym))
1113 /* Start updating the symbol table. Add basic type attribute if present. */
1114 if (current_ts.type != BT_UNKNOWN
1115 && (sym->attr.implicit_type == 0
1116 || !gfc_compare_types (&sym->ts, ¤t_ts))
1117 && gfc_add_type (sym, ¤t_ts, var_locus) == FAILURE)
1120 if (sym->ts.type == BT_CHARACTER)
1123 /* Add dimension attribute if present. */
1124 if (gfc_set_array_spec (sym, *as, var_locus) == FAILURE)
1128 /* Add attribute to symbol. The copy is so that we can reset the
1129 dimension attribute. */
1130 attr = current_attr;
1133 if (gfc_copy_attr (&sym->attr, &attr, var_locus) == FAILURE)
1136 /* Finish any work that may need to be done for the binding label,
1137 if it's a bind(c). The bind(c) attr is found before the symbol
1138 is made, and before the symbol name (for data decls), so the
1139 current_ts is holding the binding label, or nothing if the
1140 name= attr wasn't given. Therefore, test here if we're dealing
1141 with a bind(c) and make sure the binding label is set correctly. */
1142 if (sym->attr.is_bind_c == 1)
1144 if (sym->binding_label[0] == '\0')
1146 /* Set the binding label and verify that if a NAME= was specified
1147 then only one identifier was in the entity-decl-list. */
1148 if (set_binding_label (sym->binding_label, sym->name,
1149 num_idents_on_line) == FAILURE)
1154 /* See if we know we're in a common block, and if it's a bind(c)
1155 common then we need to make sure we're an interoperable type. */
1156 if (sym->attr.in_common == 1)
1158 /* Test the common block object. */
1159 if (sym->common_block != NULL && sym->common_block->is_bind_c == 1
1160 && sym->ts.is_c_interop != 1)
1162 gfc_error_now ("Variable '%s' in common block '%s' at %C "
1163 "must be declared with a C interoperable "
1164 "kind since common block '%s' is BIND(C)",
1165 sym->name, sym->common_block->name,
1166 sym->common_block->name);
1171 sym->attr.implied_index = 0;
1173 if (sym->ts.type == BT_CLASS)
1174 encapsulate_class_symbol (&sym->ts, &sym->attr, &sym->as);
1180 /* Set character constant to the given length. The constant will be padded or
1181 truncated. If we're inside an array constructor without a typespec, we
1182 additionally check that all elements have the same length; check_len -1
1183 means no checking. */
1186 gfc_set_constant_character_len (int len, gfc_expr *expr, int check_len)
1191 gcc_assert (expr->expr_type == EXPR_CONSTANT);
1192 gcc_assert (expr->ts.type == BT_CHARACTER);
1194 slen = expr->value.character.length;
1197 s = gfc_get_wide_string (len + 1);
1198 memcpy (s, expr->value.character.string,
1199 MIN (len, slen) * sizeof (gfc_char_t));
1201 gfc_wide_memset (&s[slen], ' ', len - slen);
1203 if (gfc_option.warn_character_truncation && slen > len)
1204 gfc_warning_now ("CHARACTER expression at %L is being truncated "
1205 "(%d/%d)", &expr->where, slen, len);
1207 /* Apply the standard by 'hand' otherwise it gets cleared for
1209 if (check_len != -1 && slen != check_len
1210 && !(gfc_option.allow_std & GFC_STD_GNU))
1211 gfc_error_now ("The CHARACTER elements of the array constructor "
1212 "at %L must have the same length (%d/%d)",
1213 &expr->where, slen, check_len);
1216 gfc_free (expr->value.character.string);
1217 expr->value.character.string = s;
1218 expr->value.character.length = len;
1223 /* Function to create and update the enumerator history
1224 using the information passed as arguments.
1225 Pointer "max_enum" is also updated, to point to
1226 enum history node containing largest initializer.
1228 SYM points to the symbol node of enumerator.
1229 INIT points to its enumerator value. */
1232 create_enum_history (gfc_symbol *sym, gfc_expr *init)
1234 enumerator_history *new_enum_history;
1235 gcc_assert (sym != NULL && init != NULL);
1237 new_enum_history = XCNEW (enumerator_history);
1239 new_enum_history->sym = sym;
1240 new_enum_history->initializer = init;
1241 new_enum_history->next = NULL;
1243 if (enum_history == NULL)
1245 enum_history = new_enum_history;
1246 max_enum = enum_history;
1250 new_enum_history->next = enum_history;
1251 enum_history = new_enum_history;
1253 if (mpz_cmp (max_enum->initializer->value.integer,
1254 new_enum_history->initializer->value.integer) < 0)
1255 max_enum = new_enum_history;
1260 /* Function to free enum kind history. */
1263 gfc_free_enum_history (void)
1265 enumerator_history *current = enum_history;
1266 enumerator_history *next;
1268 while (current != NULL)
1270 next = current->next;
1275 enum_history = NULL;
1279 /* Function called by variable_decl() that adds an initialization
1280 expression to a symbol. */
1283 add_init_expr_to_sym (const char *name, gfc_expr **initp, locus *var_locus)
1285 symbol_attribute attr;
1290 if (find_special (name, &sym, false))
1295 /* If this symbol is confirming an implicit parameter type,
1296 then an initialization expression is not allowed. */
1297 if (attr.flavor == FL_PARAMETER
1298 && sym->value != NULL
1301 gfc_error ("Initializer not allowed for PARAMETER '%s' at %C",
1308 /* An initializer is required for PARAMETER declarations. */
1309 if (attr.flavor == FL_PARAMETER)
1311 gfc_error ("PARAMETER at %L is missing an initializer", var_locus);
1317 /* If a variable appears in a DATA block, it cannot have an
1321 gfc_error ("Variable '%s' at %C with an initializer already "
1322 "appears in a DATA statement", sym->name);
1326 /* Check if the assignment can happen. This has to be put off
1327 until later for a derived type variable. */
1328 if (sym->ts.type != BT_DERIVED && init->ts.type != BT_DERIVED
1329 && sym->ts.type != BT_CLASS && init->ts.type != BT_CLASS
1330 && gfc_check_assign_symbol (sym, init) == FAILURE)
1333 if (sym->ts.type == BT_CHARACTER && sym->ts.u.cl
1334 && init->ts.type == BT_CHARACTER)
1336 /* Update symbol character length according initializer. */
1337 if (gfc_check_assign_symbol (sym, init) == FAILURE)
1340 if (sym->ts.u.cl->length == NULL)
1343 /* If there are multiple CHARACTER variables declared on the
1344 same line, we don't want them to share the same length. */
1345 sym->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
1347 if (sym->attr.flavor == FL_PARAMETER)
1349 if (init->expr_type == EXPR_CONSTANT)
1351 clen = init->value.character.length;
1352 sym->ts.u.cl->length = gfc_int_expr (clen);
1354 else if (init->expr_type == EXPR_ARRAY)
1356 gfc_expr *p = init->value.constructor->expr;
1357 clen = p->value.character.length;
1358 sym->ts.u.cl->length = gfc_int_expr (clen);
1360 else if (init->ts.u.cl && init->ts.u.cl->length)
1361 sym->ts.u.cl->length =
1362 gfc_copy_expr (sym->value->ts.u.cl->length);
1365 /* Update initializer character length according symbol. */
1366 else if (sym->ts.u.cl->length->expr_type == EXPR_CONSTANT)
1368 int len = mpz_get_si (sym->ts.u.cl->length->value.integer);
1369 gfc_constructor * p;
1371 if (init->expr_type == EXPR_CONSTANT)
1372 gfc_set_constant_character_len (len, init, -1);
1373 else if (init->expr_type == EXPR_ARRAY)
1375 /* Build a new charlen to prevent simplification from
1376 deleting the length before it is resolved. */
1377 init->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
1378 init->ts.u.cl->length = gfc_copy_expr (sym->ts.u.cl->length);
1380 for (p = init->value.constructor; p; p = p->next)
1381 gfc_set_constant_character_len (len, p->expr, -1);
1386 /* Need to check if the expression we initialized this
1387 to was one of the iso_c_binding named constants. If so,
1388 and we're a parameter (constant), let it be iso_c.
1390 integer(c_int), parameter :: my_int = c_int
1391 integer(my_int) :: my_int_2
1392 If we mark my_int as iso_c (since we can see it's value
1393 is equal to one of the named constants), then my_int_2
1394 will be considered C interoperable. */
1395 if (sym->ts.type != BT_CHARACTER && sym->ts.type != BT_DERIVED)
1397 sym->ts.is_iso_c |= init->ts.is_iso_c;
1398 sym->ts.is_c_interop |= init->ts.is_c_interop;
1399 /* attr bits needed for module files. */
1400 sym->attr.is_iso_c |= init->ts.is_iso_c;
1401 sym->attr.is_c_interop |= init->ts.is_c_interop;
1402 if (init->ts.is_iso_c)
1403 sym->ts.f90_type = init->ts.f90_type;
1406 /* Add initializer. Make sure we keep the ranks sane. */
1407 if (sym->attr.dimension && init->rank == 0)
1413 if (sym->attr.flavor == FL_PARAMETER
1414 && init->expr_type == EXPR_CONSTANT
1415 && spec_size (sym->as, &size) == SUCCESS
1416 && mpz_cmp_si (size, 0) > 0)
1418 array = gfc_start_constructor (init->ts.type, init->ts.kind,
1421 array->value.constructor = c = NULL;
1422 for (n = 0; n < (int)mpz_get_si (size); n++)
1424 if (array->value.constructor == NULL)
1426 array->value.constructor = c = gfc_get_constructor ();
1431 c->next = gfc_get_constructor ();
1433 c->expr = gfc_copy_expr (init);
1437 array->shape = gfc_get_shape (sym->as->rank);
1438 for (n = 0; n < sym->as->rank; n++)
1439 spec_dimen_size (sym->as, n, &array->shape[n]);
1444 init->rank = sym->as->rank;
1448 if (sym->attr.save == SAVE_NONE)
1449 sym->attr.save = SAVE_IMPLICIT;
1457 /* Function called by variable_decl() that adds a name to a structure
1461 build_struct (const char *name, gfc_charlen *cl, gfc_expr **init,
1462 gfc_array_spec **as)
1466 /* If the current symbol is of the same derived type that we're
1467 constructing, it must have the pointer attribute. */
1468 if (current_ts.type == BT_DERIVED
1469 && current_ts.u.derived == gfc_current_block ()
1470 && current_attr.pointer == 0)
1472 gfc_error ("Component at %C must have the POINTER attribute");
1476 if (gfc_current_block ()->attr.pointer && (*as)->rank != 0)
1478 if ((*as)->type != AS_DEFERRED && (*as)->type != AS_EXPLICIT)
1480 gfc_error ("Array component of structure at %C must have explicit "
1481 "or deferred shape");
1486 if (gfc_add_component (gfc_current_block (), name, &c) == FAILURE)
1490 if (c->ts.type == BT_CHARACTER)
1492 c->attr = current_attr;
1494 c->initializer = *init;
1499 c->attr.dimension = 1;
1502 /* Should this ever get more complicated, combine with similar section
1503 in add_init_expr_to_sym into a separate function. */
1504 if (c->ts.type == BT_CHARACTER && !c->attr.pointer && c->initializer && c->ts.u.cl
1505 && c->ts.u.cl->length && c->ts.u.cl->length->expr_type == EXPR_CONSTANT)
1509 gcc_assert (c->ts.u.cl && c->ts.u.cl->length);
1510 gcc_assert (c->ts.u.cl->length->expr_type == EXPR_CONSTANT);
1511 gcc_assert (c->ts.u.cl->length->ts.type == BT_INTEGER);
1513 len = mpz_get_si (c->ts.u.cl->length->value.integer);
1515 if (c->initializer->expr_type == EXPR_CONSTANT)
1516 gfc_set_constant_character_len (len, c->initializer, -1);
1517 else if (mpz_cmp (c->ts.u.cl->length->value.integer,
1518 c->initializer->ts.u.cl->length->value.integer))
1521 gfc_constructor *ctor = c->initializer->value.constructor;
1523 has_ts = (c->initializer->ts.u.cl
1524 && c->initializer->ts.u.cl->length_from_typespec);
1530 /* Remember the length of the first element for checking
1531 that all elements *in the constructor* have the same
1532 length. This need not be the length of the LHS! */
1533 gcc_assert (ctor->expr->expr_type == EXPR_CONSTANT);
1534 gcc_assert (ctor->expr->ts.type == BT_CHARACTER);
1535 first_len = ctor->expr->value.character.length;
1537 for (; ctor; ctor = ctor->next)
1539 if (ctor->expr->expr_type == EXPR_CONSTANT)
1540 gfc_set_constant_character_len (len, ctor->expr,
1541 has_ts ? -1 : first_len);
1547 if (c->ts.type == BT_CLASS)
1548 encapsulate_class_symbol (&c->ts, &c->attr, &c->as);
1550 /* Check array components. */
1551 if (!c->attr.dimension)
1554 if (c->attr.pointer)
1556 if (c->as->type != AS_DEFERRED)
1558 gfc_error ("Pointer array component of structure at %C must have a "
1563 else if (c->attr.allocatable)
1565 if (c->as->type != AS_DEFERRED)
1567 gfc_error ("Allocatable component of structure at %C must have a "
1574 if (c->as->type != AS_EXPLICIT)
1576 gfc_error ("Array component of structure at %C must have an "
1586 /* Match a 'NULL()', and possibly take care of some side effects. */
1589 gfc_match_null (gfc_expr **result)
1595 m = gfc_match (" null ( )");
1599 /* The NULL symbol now has to be/become an intrinsic function. */
1600 if (gfc_get_symbol ("null", NULL, &sym))
1602 gfc_error ("NULL() initialization at %C is ambiguous");
1606 gfc_intrinsic_symbol (sym);
1608 if (sym->attr.proc != PROC_INTRINSIC
1609 && (gfc_add_procedure (&sym->attr, PROC_INTRINSIC,
1610 sym->name, NULL) == FAILURE
1611 || gfc_add_function (&sym->attr, sym->name, NULL) == FAILURE))
1614 e = gfc_get_expr ();
1615 e->where = gfc_current_locus;
1616 e->expr_type = EXPR_NULL;
1617 e->ts.type = BT_UNKNOWN;
1625 /* Match a variable name with an optional initializer. When this
1626 subroutine is called, a variable is expected to be parsed next.
1627 Depending on what is happening at the moment, updates either the
1628 symbol table or the current interface. */
1631 variable_decl (int elem)
1633 char name[GFC_MAX_SYMBOL_LEN + 1];
1634 gfc_expr *initializer, *char_len;
1636 gfc_array_spec *cp_as; /* Extra copy for Cray Pointees. */
1647 old_locus = gfc_current_locus;
1649 /* When we get here, we've just matched a list of attributes and
1650 maybe a type and a double colon. The next thing we expect to see
1651 is the name of the symbol. */
1652 m = gfc_match_name (name);
1656 var_locus = gfc_current_locus;
1658 /* Now we could see the optional array spec. or character length. */
1659 m = gfc_match_array_spec (&as);
1660 if (gfc_option.flag_cray_pointer && m == MATCH_YES)
1661 cp_as = gfc_copy_array_spec (as);
1662 else if (m == MATCH_ERROR)
1666 as = gfc_copy_array_spec (current_as);
1671 if (current_ts.type == BT_CHARACTER)
1673 switch (match_char_length (&char_len))
1676 cl = gfc_new_charlen (gfc_current_ns, NULL);
1678 cl->length = char_len;
1681 /* Non-constant lengths need to be copied after the first
1682 element. Also copy assumed lengths. */
1685 && (current_ts.u.cl->length == NULL
1686 || current_ts.u.cl->length->expr_type != EXPR_CONSTANT))
1688 cl = gfc_new_charlen (gfc_current_ns, NULL);
1689 cl->length = gfc_copy_expr (current_ts.u.cl->length);
1692 cl = current_ts.u.cl;
1701 /* If this symbol has already shown up in a Cray Pointer declaration,
1702 then we want to set the type & bail out. */
1703 if (gfc_option.flag_cray_pointer)
1705 gfc_find_symbol (name, gfc_current_ns, 1, &sym);
1706 if (sym != NULL && sym->attr.cray_pointee)
1708 sym->ts.type = current_ts.type;
1709 sym->ts.kind = current_ts.kind;
1711 sym->ts.u.derived = current_ts.u.derived;
1712 sym->ts.is_c_interop = current_ts.is_c_interop;
1713 sym->ts.is_iso_c = current_ts.is_iso_c;
1716 /* Check to see if we have an array specification. */
1719 if (sym->as != NULL)
1721 gfc_error ("Duplicate array spec for Cray pointee at %C");
1722 gfc_free_array_spec (cp_as);
1728 if (gfc_set_array_spec (sym, cp_as, &var_locus) == FAILURE)
1729 gfc_internal_error ("Couldn't set pointee array spec.");
1731 /* Fix the array spec. */
1732 m = gfc_mod_pointee_as (sym->as);
1733 if (m == MATCH_ERROR)
1741 gfc_free_array_spec (cp_as);
1745 /* Procedure pointer as function result. */
1746 if (gfc_current_state () == COMP_FUNCTION
1747 && strcmp ("ppr@", gfc_current_block ()->name) == 0
1748 && strcmp (name, gfc_current_block ()->ns->proc_name->name) == 0)
1749 strcpy (name, "ppr@");
1751 if (gfc_current_state () == COMP_FUNCTION
1752 && strcmp (name, gfc_current_block ()->name) == 0
1753 && gfc_current_block ()->result
1754 && strcmp ("ppr@", gfc_current_block ()->result->name) == 0)
1755 strcpy (name, "ppr@");
1757 /* OK, we've successfully matched the declaration. Now put the
1758 symbol in the current namespace, because it might be used in the
1759 optional initialization expression for this symbol, e.g. this is
1762 integer, parameter :: i = huge(i)
1764 This is only true for parameters or variables of a basic type.
1765 For components of derived types, it is not true, so we don't
1766 create a symbol for those yet. If we fail to create the symbol,
1768 if (gfc_current_state () != COMP_DERIVED
1769 && build_sym (name, cl, &as, &var_locus) == FAILURE)
1775 /* An interface body specifies all of the procedure's
1776 characteristics and these shall be consistent with those
1777 specified in the procedure definition, except that the interface
1778 may specify a procedure that is not pure if the procedure is
1779 defined to be pure(12.3.2). */
1780 if (current_ts.type == BT_DERIVED
1781 && gfc_current_ns->proc_name
1782 && gfc_current_ns->proc_name->attr.if_source == IFSRC_IFBODY
1783 && current_ts.u.derived->ns != gfc_current_ns)
1786 st = gfc_find_symtree (gfc_current_ns->sym_root, current_ts.u.derived->name);
1787 if (!(current_ts.u.derived->attr.imported
1789 && st->n.sym == current_ts.u.derived)
1790 && !gfc_current_ns->has_import_set)
1792 gfc_error ("the type of '%s' at %C has not been declared within the "
1799 /* In functions that have a RESULT variable defined, the function
1800 name always refers to function calls. Therefore, the name is
1801 not allowed to appear in specification statements. */
1802 if (gfc_current_state () == COMP_FUNCTION
1803 && gfc_current_block () != NULL
1804 && gfc_current_block ()->result != NULL
1805 && gfc_current_block ()->result != gfc_current_block ()
1806 && strcmp (gfc_current_block ()->name, name) == 0)
1808 gfc_error ("Function name '%s' not allowed at %C", name);
1813 /* We allow old-style initializations of the form
1814 integer i /2/, j(4) /3*3, 1/
1815 (if no colon has been seen). These are different from data
1816 statements in that initializers are only allowed to apply to the
1817 variable immediately preceding, i.e.
1819 is not allowed. Therefore we have to do some work manually, that
1820 could otherwise be left to the matchers for DATA statements. */
1822 if (!colon_seen && gfc_match (" /") == MATCH_YES)
1824 if (gfc_notify_std (GFC_STD_GNU, "Extension: Old-style "
1825 "initialization at %C") == FAILURE)
1828 return match_old_style_init (name);
1831 /* The double colon must be present in order to have initializers.
1832 Otherwise the statement is ambiguous with an assignment statement. */
1835 if (gfc_match (" =>") == MATCH_YES)
1837 if (!current_attr.pointer)
1839 gfc_error ("Initialization at %C isn't for a pointer variable");
1844 m = gfc_match_null (&initializer);
1847 gfc_error ("Pointer initialization requires a NULL() at %C");
1851 if (gfc_pure (NULL))
1853 gfc_error ("Initialization of pointer at %C is not allowed in "
1854 "a PURE procedure");
1862 else if (gfc_match_char ('=') == MATCH_YES)
1864 if (current_attr.pointer)
1866 gfc_error ("Pointer initialization at %C requires '=>', "
1872 m = gfc_match_init_expr (&initializer);
1875 gfc_error ("Expected an initialization expression at %C");
1879 if (current_attr.flavor != FL_PARAMETER && gfc_pure (NULL))
1881 gfc_error ("Initialization of variable at %C is not allowed in "
1882 "a PURE procedure");
1891 if (initializer != NULL && current_attr.allocatable
1892 && gfc_current_state () == COMP_DERIVED)
1894 gfc_error ("Initialization of allocatable component at %C is not "
1900 /* Add the initializer. Note that it is fine if initializer is
1901 NULL here, because we sometimes also need to check if a
1902 declaration *must* have an initialization expression. */
1903 if (gfc_current_state () != COMP_DERIVED)
1904 t = add_init_expr_to_sym (name, &initializer, &var_locus);
1907 if (current_ts.type == BT_DERIVED
1908 && !current_attr.pointer && !initializer)
1909 initializer = gfc_default_initializer (¤t_ts);
1910 t = build_struct (name, cl, &initializer, &as);
1913 m = (t == SUCCESS) ? MATCH_YES : MATCH_ERROR;
1916 /* Free stuff up and return. */
1917 gfc_free_expr (initializer);
1918 gfc_free_array_spec (as);
1924 /* Match an extended-f77 "TYPESPEC*bytesize"-style kind specification.
1925 This assumes that the byte size is equal to the kind number for
1926 non-COMPLEX types, and equal to twice the kind number for COMPLEX. */
1929 gfc_match_old_kind_spec (gfc_typespec *ts)
1934 if (gfc_match_char ('*') != MATCH_YES)
1937 m = gfc_match_small_literal_int (&ts->kind, NULL);
1941 original_kind = ts->kind;
1943 /* Massage the kind numbers for complex types. */
1944 if (ts->type == BT_COMPLEX)
1948 gfc_error ("Old-style type declaration %s*%d not supported at %C",
1949 gfc_basic_typename (ts->type), original_kind);
1955 if (gfc_validate_kind (ts->type, ts->kind, true) < 0)
1957 gfc_error ("Old-style type declaration %s*%d not supported at %C",
1958 gfc_basic_typename (ts->type), original_kind);
1962 if (gfc_notify_std (GFC_STD_GNU, "Nonstandard type declaration %s*%d at %C",
1963 gfc_basic_typename (ts->type), original_kind) == FAILURE)
1970 /* Match a kind specification. Since kinds are generally optional, we
1971 usually return MATCH_NO if something goes wrong. If a "kind="
1972 string is found, then we know we have an error. */
1975 gfc_match_kind_spec (gfc_typespec *ts, bool kind_expr_only)
1987 where = loc = gfc_current_locus;
1992 if (gfc_match_char ('(') == MATCH_NO)
1995 /* Also gobbles optional text. */
1996 if (gfc_match (" kind = ") == MATCH_YES)
1999 loc = gfc_current_locus;
2002 n = gfc_match_init_expr (&e);
2006 if (gfc_matching_function)
2008 /* The function kind expression might include use associated or
2009 imported parameters and try again after the specification
2011 if (gfc_match_char (')') != MATCH_YES)
2013 gfc_error ("Missing right parenthesis at %C");
2019 gfc_undo_symbols ();
2024 /* ....or else, the match is real. */
2026 gfc_error ("Expected initialization expression at %C");
2034 gfc_error ("Expected scalar initialization expression at %C");
2039 msg = gfc_extract_int (e, &ts->kind);
2048 /* Before throwing away the expression, let's see if we had a
2049 C interoperable kind (and store the fact). */
2050 if (e->ts.is_c_interop == 1)
2052 /* Mark this as c interoperable if being declared with one
2053 of the named constants from iso_c_binding. */
2054 ts->is_c_interop = e->ts.is_iso_c;
2055 ts->f90_type = e->ts.f90_type;
2061 /* Ignore errors to this point, if we've gotten here. This means
2062 we ignore the m=MATCH_ERROR from above. */
2063 if (gfc_validate_kind (ts->type, ts->kind, true) < 0)
2065 gfc_error ("Kind %d not supported for type %s at %C", ts->kind,
2066 gfc_basic_typename (ts->type));
2067 gfc_current_locus = where;
2071 /* Warn if, e.g., c_int is used for a REAL variable, but not
2072 if, e.g., c_double is used for COMPLEX as the standard
2073 explicitly says that the kind type parameter for complex and real
2074 variable is the same, i.e. c_float == c_float_complex. */
2075 if (ts->f90_type != BT_UNKNOWN && ts->f90_type != ts->type
2076 && !((ts->f90_type == BT_REAL && ts->type == BT_COMPLEX)
2077 || (ts->f90_type == BT_COMPLEX && ts->type == BT_REAL)))
2078 gfc_warning_now ("C kind type parameter is for type %s but type at %L "
2079 "is %s", gfc_basic_typename (ts->f90_type), &where,
2080 gfc_basic_typename (ts->type));
2082 gfc_gobble_whitespace ();
2083 if ((c = gfc_next_ascii_char ()) != ')'
2084 && (ts->type != BT_CHARACTER || c != ','))
2086 if (ts->type == BT_CHARACTER)
2087 gfc_error ("Missing right parenthesis or comma at %C");
2089 gfc_error ("Missing right parenthesis at %C");
2093 /* All tests passed. */
2096 if(m == MATCH_ERROR)
2097 gfc_current_locus = where;
2099 /* Return what we know from the test(s). */
2104 gfc_current_locus = where;
2110 match_char_kind (int * kind, int * is_iso_c)
2119 where = gfc_current_locus;
2121 n = gfc_match_init_expr (&e);
2123 if (n != MATCH_YES && gfc_matching_function)
2125 /* The expression might include use-associated or imported
2126 parameters and try again after the specification
2129 gfc_undo_symbols ();
2134 gfc_error ("Expected initialization expression at %C");
2140 gfc_error ("Expected scalar initialization expression at %C");
2145 msg = gfc_extract_int (e, kind);
2146 *is_iso_c = e->ts.is_iso_c;
2156 /* Ignore errors to this point, if we've gotten here. This means
2157 we ignore the m=MATCH_ERROR from above. */
2158 if (gfc_validate_kind (BT_CHARACTER, *kind, true) < 0)
2160 gfc_error ("Kind %d is not supported for CHARACTER at %C", *kind);
2164 /* All tests passed. */
2167 if (m == MATCH_ERROR)
2168 gfc_current_locus = where;
2170 /* Return what we know from the test(s). */
2175 gfc_current_locus = where;
2180 /* Match the various kind/length specifications in a CHARACTER
2181 declaration. We don't return MATCH_NO. */
2184 gfc_match_char_spec (gfc_typespec *ts)
2186 int kind, seen_length, is_iso_c;
2196 /* Try the old-style specification first. */
2197 old_char_selector = 0;
2199 m = match_char_length (&len);
2203 old_char_selector = 1;
2208 m = gfc_match_char ('(');
2211 m = MATCH_YES; /* Character without length is a single char. */
2215 /* Try the weird case: ( KIND = <int> [ , LEN = <len-param> ] ). */
2216 if (gfc_match (" kind =") == MATCH_YES)
2218 m = match_char_kind (&kind, &is_iso_c);
2220 if (m == MATCH_ERROR)
2225 if (gfc_match (" , len =") == MATCH_NO)
2228 m = char_len_param_value (&len);
2231 if (m == MATCH_ERROR)
2238 /* Try to match "LEN = <len-param>" or "LEN = <len-param>, KIND = <int>". */
2239 if (gfc_match (" len =") == MATCH_YES)
2241 m = char_len_param_value (&len);
2244 if (m == MATCH_ERROR)
2248 if (gfc_match_char (')') == MATCH_YES)
2251 if (gfc_match (" , kind =") != MATCH_YES)
2254 if (match_char_kind (&kind, &is_iso_c) == MATCH_ERROR)
2260 /* Try to match ( <len-param> ) or ( <len-param> , [ KIND = ] <int> ). */
2261 m = char_len_param_value (&len);
2264 if (m == MATCH_ERROR)
2268 m = gfc_match_char (')');
2272 if (gfc_match_char (',') != MATCH_YES)
2275 gfc_match (" kind ="); /* Gobble optional text. */
2277 m = match_char_kind (&kind, &is_iso_c);
2278 if (m == MATCH_ERROR)
2284 /* Require a right-paren at this point. */
2285 m = gfc_match_char (')');
2290 gfc_error ("Syntax error in CHARACTER declaration at %C");
2292 gfc_free_expr (len);
2296 /* Deal with character functions after USE and IMPORT statements. */
2297 if (gfc_matching_function)
2299 gfc_free_expr (len);
2300 gfc_undo_symbols ();
2306 gfc_free_expr (len);
2310 /* Do some final massaging of the length values. */
2311 cl = gfc_new_charlen (gfc_current_ns, NULL);
2313 if (seen_length == 0)
2314 cl->length = gfc_int_expr (1);
2319 ts->kind = kind == 0 ? gfc_default_character_kind : kind;
2321 /* We have to know if it was a c interoperable kind so we can
2322 do accurate type checking of bind(c) procs, etc. */
2324 /* Mark this as c interoperable if being declared with one
2325 of the named constants from iso_c_binding. */
2326 ts->is_c_interop = is_iso_c;
2327 else if (len != NULL)
2328 /* Here, we might have parsed something such as: character(c_char)
2329 In this case, the parsing code above grabs the c_char when
2330 looking for the length (line 1690, roughly). it's the last
2331 testcase for parsing the kind params of a character variable.
2332 However, it's not actually the length. this seems like it
2334 To see if the user used a C interop kind, test the expr
2335 of the so called length, and see if it's C interoperable. */
2336 ts->is_c_interop = len->ts.is_iso_c;
2342 /* Matches a declaration-type-spec (F03:R502). If successful, sets the ts
2343 structure to the matched specification. This is necessary for FUNCTION and
2344 IMPLICIT statements.
2346 If implicit_flag is nonzero, then we don't check for the optional
2347 kind specification. Not doing so is needed for matching an IMPLICIT
2348 statement correctly. */
2351 gfc_match_decl_type_spec (gfc_typespec *ts, int implicit_flag)
2353 char name[GFC_MAX_SYMBOL_LEN + 1];
2357 bool seen_deferred_kind;
2359 /* A belt and braces check that the typespec is correctly being treated
2360 as a deferred characteristic association. */
2361 seen_deferred_kind = (gfc_current_state () == COMP_FUNCTION)
2362 && (gfc_current_block ()->result->ts.kind == -1)
2363 && (ts->kind == -1);
2365 if (seen_deferred_kind)
2368 /* Clear the current binding label, in case one is given. */
2369 curr_binding_label[0] = '\0';
2371 if (gfc_match (" byte") == MATCH_YES)
2373 if (gfc_notify_std (GFC_STD_GNU, "Extension: BYTE type at %C")
2377 if (gfc_validate_kind (BT_INTEGER, 1, true) < 0)
2379 gfc_error ("BYTE type used at %C "
2380 "is not available on the target machine");
2384 ts->type = BT_INTEGER;
2389 if (gfc_match (" integer") == MATCH_YES)
2391 ts->type = BT_INTEGER;
2392 ts->kind = gfc_default_integer_kind;
2396 if (gfc_match (" character") == MATCH_YES)
2398 ts->type = BT_CHARACTER;
2399 if (implicit_flag == 0)
2400 return gfc_match_char_spec (ts);
2405 if (gfc_match (" real") == MATCH_YES)
2408 ts->kind = gfc_default_real_kind;
2412 if (gfc_match (" double precision") == MATCH_YES)
2415 ts->kind = gfc_default_double_kind;
2419 if (gfc_match (" complex") == MATCH_YES)
2421 ts->type = BT_COMPLEX;
2422 ts->kind = gfc_default_complex_kind;
2426 if (gfc_match (" double complex") == MATCH_YES)
2428 if (gfc_notify_std (GFC_STD_GNU, "DOUBLE COMPLEX at %C does not "
2429 "conform to the Fortran 95 standard") == FAILURE)
2432 ts->type = BT_COMPLEX;
2433 ts->kind = gfc_default_double_kind;
2437 if (gfc_match (" logical") == MATCH_YES)
2439 ts->type = BT_LOGICAL;
2440 ts->kind = gfc_default_logical_kind;
2444 m = gfc_match (" type ( %n )", name);
2446 ts->type = BT_DERIVED;
2449 m = gfc_match (" class ( %n )", name);
2452 ts->type = BT_CLASS;
2454 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: CLASS statement at %C")
2459 /* Defer association of the derived type until the end of the
2460 specification block. However, if the derived type can be
2461 found, add it to the typespec. */
2462 if (gfc_matching_function)
2464 ts->u.derived = NULL;
2465 if (gfc_current_state () != COMP_INTERFACE
2466 && !gfc_find_symbol (name, NULL, 1, &sym) && sym)
2467 ts->u.derived = sym;
2471 /* Search for the name but allow the components to be defined later. If
2472 type = -1, this typespec has been seen in a function declaration but
2473 the type could not be accessed at that point. */
2475 if (ts->kind != -1 && gfc_get_ha_symbol (name, &sym))
2477 gfc_error ("Type name '%s' at %C is ambiguous", name);
2480 else if (ts->kind == -1)
2482 int iface = gfc_state_stack->previous->state != COMP_INTERFACE
2483 || gfc_current_ns->has_import_set;
2484 if (gfc_find_symbol (name, NULL, iface, &sym))
2486 gfc_error ("Type name '%s' at %C is ambiguous", name);
2495 if (sym->attr.flavor != FL_DERIVED
2496 && gfc_add_flavor (&sym->attr, FL_DERIVED, sym->name, NULL) == FAILURE)
2499 gfc_set_sym_referenced (sym);
2500 ts->u.derived = sym;
2505 /* For all types except double, derived and character, look for an
2506 optional kind specifier. MATCH_NO is actually OK at this point. */
2507 if (implicit_flag == 1)
2510 if (gfc_current_form == FORM_FREE)
2512 c = gfc_peek_ascii_char ();
2513 if (!gfc_is_whitespace (c) && c != '*' && c != '('
2514 && c != ':' && c != ',')
2518 m = gfc_match_kind_spec (ts, false);
2519 if (m == MATCH_NO && ts->type != BT_CHARACTER)
2520 m = gfc_match_old_kind_spec (ts);
2522 /* Defer association of the KIND expression of function results
2523 until after USE and IMPORT statements. */
2524 if ((gfc_current_state () == COMP_NONE && gfc_error_flag_test ())
2525 || gfc_matching_function)
2529 m = MATCH_YES; /* No kind specifier found. */
2535 /* Match an IMPLICIT NONE statement. Actually, this statement is
2536 already matched in parse.c, or we would not end up here in the
2537 first place. So the only thing we need to check, is if there is
2538 trailing garbage. If not, the match is successful. */
2541 gfc_match_implicit_none (void)
2543 return (gfc_match_eos () == MATCH_YES) ? MATCH_YES : MATCH_NO;
2547 /* Match the letter range(s) of an IMPLICIT statement. */
2550 match_implicit_range (void)
2556 cur_loc = gfc_current_locus;
2558 gfc_gobble_whitespace ();
2559 c = gfc_next_ascii_char ();
2562 gfc_error ("Missing character range in IMPLICIT at %C");
2569 gfc_gobble_whitespace ();
2570 c1 = gfc_next_ascii_char ();
2574 gfc_gobble_whitespace ();
2575 c = gfc_next_ascii_char ();
2580 inner = 0; /* Fall through. */
2587 gfc_gobble_whitespace ();
2588 c2 = gfc_next_ascii_char ();
2592 gfc_gobble_whitespace ();
2593 c = gfc_next_ascii_char ();
2595 if ((c != ',') && (c != ')'))
2608 gfc_error ("Letters must be in alphabetic order in "
2609 "IMPLICIT statement at %C");
2613 /* See if we can add the newly matched range to the pending
2614 implicits from this IMPLICIT statement. We do not check for
2615 conflicts with whatever earlier IMPLICIT statements may have
2616 set. This is done when we've successfully finished matching
2618 if (gfc_add_new_implicit_range (c1, c2) != SUCCESS)
2625 gfc_syntax_error (ST_IMPLICIT);
2627 gfc_current_locus = cur_loc;
2632 /* Match an IMPLICIT statement, storing the types for
2633 gfc_set_implicit() if the statement is accepted by the parser.
2634 There is a strange looking, but legal syntactic construction
2635 possible. It looks like:
2637 IMPLICIT INTEGER (a-b) (c-d)
2639 This is legal if "a-b" is a constant expression that happens to
2640 equal one of the legal kinds for integers. The real problem
2641 happens with an implicit specification that looks like:
2643 IMPLICIT INTEGER (a-b)
2645 In this case, a typespec matcher that is "greedy" (as most of the
2646 matchers are) gobbles the character range as a kindspec, leaving
2647 nothing left. We therefore have to go a bit more slowly in the
2648 matching process by inhibiting the kindspec checking during
2649 typespec matching and checking for a kind later. */
2652 gfc_match_implicit (void)
2661 /* We don't allow empty implicit statements. */
2662 if (gfc_match_eos () == MATCH_YES)
2664 gfc_error ("Empty IMPLICIT statement at %C");
2670 /* First cleanup. */
2671 gfc_clear_new_implicit ();
2673 /* A basic type is mandatory here. */
2674 m = gfc_match_decl_type_spec (&ts, 1);
2675 if (m == MATCH_ERROR)
2680 cur_loc = gfc_current_locus;
2681 m = match_implicit_range ();
2685 /* We may have <TYPE> (<RANGE>). */
2686 gfc_gobble_whitespace ();
2687 c = gfc_next_ascii_char ();
2688 if ((c == '\n') || (c == ','))
2690 /* Check for CHARACTER with no length parameter. */
2691 if (ts.type == BT_CHARACTER && !ts.u.cl)
2693 ts.kind = gfc_default_character_kind;
2694 ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
2695 ts.u.cl->length = gfc_int_expr (1);
2698 /* Record the Successful match. */
2699 if (gfc_merge_new_implicit (&ts) != SUCCESS)
2704 gfc_current_locus = cur_loc;
2707 /* Discard the (incorrectly) matched range. */
2708 gfc_clear_new_implicit ();
2710 /* Last chance -- check <TYPE> <SELECTOR> (<RANGE>). */
2711 if (ts.type == BT_CHARACTER)
2712 m = gfc_match_char_spec (&ts);
2715 m = gfc_match_kind_spec (&ts, false);
2718 m = gfc_match_old_kind_spec (&ts);
2719 if (m == MATCH_ERROR)
2725 if (m == MATCH_ERROR)
2728 m = match_implicit_range ();
2729 if (m == MATCH_ERROR)
2734 gfc_gobble_whitespace ();
2735 c = gfc_next_ascii_char ();
2736 if ((c != '\n') && (c != ','))
2739 if (gfc_merge_new_implicit (&ts) != SUCCESS)
2747 gfc_syntax_error (ST_IMPLICIT);
2755 gfc_match_import (void)
2757 char name[GFC_MAX_SYMBOL_LEN + 1];
2762 if (gfc_current_ns->proc_name == NULL
2763 || gfc_current_ns->proc_name->attr.if_source != IFSRC_IFBODY)
2765 gfc_error ("IMPORT statement at %C only permitted in "
2766 "an INTERFACE body");
2770 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: IMPORT statement at %C")
2774 if (gfc_match_eos () == MATCH_YES)
2776 /* All host variables should be imported. */
2777 gfc_current_ns->has_import_set = 1;
2781 if (gfc_match (" ::") == MATCH_YES)
2783 if (gfc_match_eos () == MATCH_YES)
2785 gfc_error ("Expecting list of named entities at %C");
2792 m = gfc_match (" %n", name);
2796 if (gfc_current_ns->parent != NULL
2797 && gfc_find_symbol (name, gfc_current_ns->parent, 1, &sym))
2799 gfc_error ("Type name '%s' at %C is ambiguous", name);
2802 else if (gfc_current_ns->proc_name->ns->parent != NULL
2803 && gfc_find_symbol (name,
2804 gfc_current_ns->proc_name->ns->parent,
2807 gfc_error ("Type name '%s' at %C is ambiguous", name);
2813 gfc_error ("Cannot IMPORT '%s' from host scoping unit "
2814 "at %C - does not exist.", name);
2818 if (gfc_find_symtree (gfc_current_ns->sym_root,name))
2820 gfc_warning ("'%s' is already IMPORTed from host scoping unit "
2825 st = gfc_new_symtree (&gfc_current_ns->sym_root, sym->name);
2828 sym->attr.imported = 1;
2840 if (gfc_match_eos () == MATCH_YES)
2842 if (gfc_match_char (',') != MATCH_YES)
2849 gfc_error ("Syntax error in IMPORT statement at %C");
2854 /* A minimal implementation of gfc_match without whitespace, escape
2855 characters or variable arguments. Returns true if the next
2856 characters match the TARGET template exactly. */
2859 match_string_p (const char *target)
2863 for (p = target; *p; p++)
2864 if ((char) gfc_next_ascii_char () != *p)
2869 /* Matches an attribute specification including array specs. If
2870 successful, leaves the variables current_attr and current_as
2871 holding the specification. Also sets the colon_seen variable for
2872 later use by matchers associated with initializations.
2874 This subroutine is a little tricky in the sense that we don't know
2875 if we really have an attr-spec until we hit the double colon.
2876 Until that time, we can only return MATCH_NO. This forces us to
2877 check for duplicate specification at this level. */
2880 match_attr_spec (void)
2882 /* Modifiers that can exist in a type statement. */
2884 { GFC_DECL_BEGIN = 0,
2885 DECL_ALLOCATABLE = GFC_DECL_BEGIN, DECL_DIMENSION, DECL_EXTERNAL,
2886 DECL_IN, DECL_OUT, DECL_INOUT, DECL_INTRINSIC, DECL_OPTIONAL,
2887 DECL_PARAMETER, DECL_POINTER, DECL_PROTECTED, DECL_PRIVATE,
2888 DECL_PUBLIC, DECL_SAVE, DECL_TARGET, DECL_VALUE, DECL_VOLATILE,
2889 DECL_IS_BIND_C, DECL_NONE,
2890 GFC_DECL_END /* Sentinel */
2894 /* GFC_DECL_END is the sentinel, index starts at 0. */
2895 #define NUM_DECL GFC_DECL_END
2897 locus start, seen_at[NUM_DECL];
2904 gfc_clear_attr (¤t_attr);
2905 start = gfc_current_locus;
2910 /* See if we get all of the keywords up to the final double colon. */
2911 for (d = GFC_DECL_BEGIN; d != GFC_DECL_END; d++)
2919 gfc_gobble_whitespace ();
2921 ch = gfc_next_ascii_char ();
2924 /* This is the successful exit condition for the loop. */
2925 if (gfc_next_ascii_char () == ':')
2930 gfc_gobble_whitespace ();
2931 switch (gfc_peek_ascii_char ())
2934 if (match_string_p ("allocatable"))
2935 d = DECL_ALLOCATABLE;
2939 /* Try and match the bind(c). */
2940 m = gfc_match_bind_c (NULL, true);
2943 else if (m == MATCH_ERROR)
2948 if (match_string_p ("dimension"))
2953 if (match_string_p ("external"))
2958 if (match_string_p ("int"))
2960 ch = gfc_next_ascii_char ();
2963 if (match_string_p ("nt"))
2965 /* Matched "intent". */
2966 /* TODO: Call match_intent_spec from here. */
2967 if (gfc_match (" ( in out )") == MATCH_YES)
2969 else if (gfc_match (" ( in )") == MATCH_YES)
2971 else if (gfc_match (" ( out )") == MATCH_YES)
2977 if (match_string_p ("insic"))
2979 /* Matched "intrinsic". */
2987 if (match_string_p ("optional"))
2992 gfc_next_ascii_char ();
2993 switch (gfc_next_ascii_char ())
2996 if (match_string_p ("rameter"))
2998 /* Matched "parameter". */
3004 if (match_string_p ("inter"))
3006 /* Matched "pointer". */
3012 ch = gfc_next_ascii_char ();
3015 if (match_string_p ("vate"))
3017 /* Matched "private". */
3023 if (match_string_p ("tected"))
3025 /* Matched "protected". */
3032 if (match_string_p ("blic"))
3034 /* Matched "public". */
3042 if (match_string_p ("save"))
3047 if (match_string_p ("target"))
3052 gfc_next_ascii_char ();
3053 ch = gfc_next_ascii_char ();
3056 if (match_string_p ("lue"))
3058 /* Matched "value". */
3064 if (match_string_p ("latile"))
3066 /* Matched "volatile". */
3074 /* No double colon and no recognizable decl_type, so assume that
3075 we've been looking at something else the whole time. */
3082 /* Check to make sure any parens are paired up correctly. */
3083 if (gfc_match_parens () == MATCH_ERROR)
3090 seen_at[d] = gfc_current_locus;
3092 if (d == DECL_DIMENSION)
3094 m = gfc_match_array_spec (¤t_as);
3098 gfc_error ("Missing dimension specification at %C");
3102 if (m == MATCH_ERROR)
3107 /* Since we've seen a double colon, we have to be looking at an
3108 attr-spec. This means that we can now issue errors. */
3109 for (d = GFC_DECL_BEGIN; d != GFC_DECL_END; d++)
3114 case DECL_ALLOCATABLE:
3115 attr = "ALLOCATABLE";
3117 case DECL_DIMENSION:
3124 attr = "INTENT (IN)";
3127 attr = "INTENT (OUT)";
3130 attr = "INTENT (IN OUT)";
3132 case DECL_INTRINSIC:
3138 case DECL_PARAMETER:
3144 case DECL_PROTECTED:
3159 case DECL_IS_BIND_C:
3169 attr = NULL; /* This shouldn't happen. */
3172 gfc_error ("Duplicate %s attribute at %L", attr, &seen_at[d]);
3177 /* Now that we've dealt with duplicate attributes, add the attributes
3178 to the current attribute. */
3179 for (d = GFC_DECL_BEGIN; d != GFC_DECL_END; d++)
3184 if (gfc_current_state () == COMP_DERIVED
3185 && d != DECL_DIMENSION && d != DECL_POINTER
3186 && d != DECL_PRIVATE && d != DECL_PUBLIC
3189 if (d == DECL_ALLOCATABLE)
3191 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: ALLOCATABLE "
3192 "attribute at %C in a TYPE definition")
3201 gfc_error ("Attribute at %L is not allowed in a TYPE definition",
3208 if ((d == DECL_PRIVATE || d == DECL_PUBLIC)
3209 && gfc_current_state () != COMP_MODULE)
3211 if (d == DECL_PRIVATE)
3215 if (gfc_current_state () == COMP_DERIVED
3216 && gfc_state_stack->previous
3217 && gfc_state_stack->previous->state == COMP_MODULE)
3219 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Attribute %s "
3220 "at %L in a TYPE definition", attr,
3230 gfc_error ("%s attribute at %L is not allowed outside of the "
3231 "specification part of a module", attr, &seen_at[d]);
3239 case DECL_ALLOCATABLE:
3240 t = gfc_add_allocatable (¤t_attr, &seen_at[d]);
3243 case DECL_DIMENSION:
3244 t = gfc_add_dimension (¤t_attr, NULL, &seen_at[d]);
3248 t = gfc_add_external (¤t_attr, &seen_at[d]);
3252 t = gfc_add_intent (¤t_attr, INTENT_IN, &seen_at[d]);
3256 t = gfc_add_intent (¤t_attr, INTENT_OUT, &seen_at[d]);
3260 t = gfc_add_intent (¤t_attr, INTENT_INOUT, &seen_at[d]);
3263 case DECL_INTRINSIC:
3264 t = gfc_add_intrinsic (¤t_attr, &seen_at[d]);
3268 t = gfc_add_optional (¤t_attr, &seen_at[d]);
3271 case DECL_PARAMETER:
3272 t = gfc_add_flavor (¤t_attr, FL_PARAMETER, NULL, &seen_at[d]);
3276 t = gfc_add_pointer (¤t_attr, &seen_at[d]);
3279 case DECL_PROTECTED:
3280 if (gfc_current_ns->proc_name->attr.flavor != FL_MODULE)
3282 gfc_error ("PROTECTED at %C only allowed in specification "
3283 "part of a module");
3288 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PROTECTED "
3293 t = gfc_add_protected (¤t_attr, NULL, &seen_at[d]);
3297 t = gfc_add_access (¤t_attr, ACCESS_PRIVATE, NULL,
3302 t = gfc_add_access (¤t_attr, ACCESS_PUBLIC, NULL,
3307 t = gfc_add_save (¤t_attr, NULL, &seen_at[d]);
3311 t = gfc_add_target (¤t_attr, &seen_at[d]);
3314 case DECL_IS_BIND_C:
3315 t = gfc_add_is_bind_c(¤t_attr, NULL, &seen_at[d], 0);
3319 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: VALUE attribute "
3324 t = gfc_add_value (¤t_attr, NULL, &seen_at[d]);
3328 if (gfc_notify_std (GFC_STD_F2003,
3329 "Fortran 2003: VOLATILE attribute at %C")
3333 t = gfc_add_volatile (¤t_attr, NULL, &seen_at[d]);
3337 gfc_internal_error ("match_attr_spec(): Bad attribute");
3351 gfc_current_locus = start;
3352 gfc_free_array_spec (current_as);
3358 /* Set the binding label, dest_label, either with the binding label
3359 stored in the given gfc_typespec, ts, or if none was provided, it
3360 will be the symbol name in all lower case, as required by the draft
3361 (J3/04-007, section 15.4.1). If a binding label was given and
3362 there is more than one argument (num_idents), it is an error. */
3365 set_binding_label (char *dest_label, const char *sym_name, int num_idents)
3367 if (num_idents > 1 && has_name_equals)
3369 gfc_error ("Multiple identifiers provided with "
3370 "single NAME= specifier at %C");
3374 if (curr_binding_label[0] != '\0')
3376 /* Binding label given; store in temp holder til have sym. */
3377 strcpy (dest_label, curr_binding_label);
3381 /* No binding label given, and the NAME= specifier did not exist,
3382 which means there was no NAME="". */
3383 if (sym_name != NULL && has_name_equals == 0)
3384 strcpy (dest_label, sym_name);
3391 /* Set the status of the given common block as being BIND(C) or not,
3392 depending on the given parameter, is_bind_c. */
3395 set_com_block_bind_c (gfc_common_head *com_block, int is_bind_c)
3397 com_block->is_bind_c = is_bind_c;
3402 /* Verify that the given gfc_typespec is for a C interoperable type. */
3405 verify_c_interop (gfc_typespec *ts)
3407 if (ts->type == BT_DERIVED && ts->u.derived != NULL)
3408 return (ts->u.derived->ts.is_c_interop ? SUCCESS : FAILURE);
3409 else if (ts->is_c_interop != 1)
3416 /* Verify that the variables of a given common block, which has been
3417 defined with the attribute specifier bind(c), to be of a C
3418 interoperable type. Errors will be reported here, if
3422 verify_com_block_vars_c_interop (gfc_common_head *com_block)
3424 gfc_symbol *curr_sym = NULL;
3425 gfc_try retval = SUCCESS;
3427 curr_sym = com_block->head;
3429 /* Make sure we have at least one symbol. */
3430 if (curr_sym == NULL)
3433 /* Here we know we have a symbol, so we'll execute this loop
3437 /* The second to last param, 1, says this is in a common block. */
3438 retval = verify_bind_c_sym (curr_sym, &(curr_sym->ts), 1, com_block);
3439 curr_sym = curr_sym->common_next;
3440 } while (curr_sym != NULL);
3446 /* Verify that a given BIND(C) symbol is C interoperable. If it is not,
3447 an appropriate error message is reported. */
3450 verify_bind_c_sym (gfc_symbol *tmp_sym, gfc_typespec *ts,
3451 int is_in_common, gfc_common_head *com_block)
3453 bool bind_c_function = false;
3454 gfc_try retval = SUCCESS;
3456 if (tmp_sym->attr.function && tmp_sym->attr.is_bind_c)
3457 bind_c_function = true;
3459 if (tmp_sym->attr.function && tmp_sym->result != NULL)
3461 tmp_sym = tmp_sym->result;
3462 /* Make sure it wasn't an implicitly typed result. */
3463 if (tmp_sym->attr.implicit_type)
3465 gfc_warning ("Implicitly declared BIND(C) function '%s' at "
3466 "%L may not be C interoperable", tmp_sym->name,
3467 &tmp_sym->declared_at);
3468 tmp_sym->ts.f90_type = tmp_sym->ts.type;
3469 /* Mark it as C interoperable to prevent duplicate warnings. */
3470 tmp_sym->ts.is_c_interop = 1;
3471 tmp_sym->attr.is_c_interop = 1;
3475 /* Here, we know we have the bind(c) attribute, so if we have
3476 enough type info, then verify that it's a C interop kind.
3477 The info could be in the symbol already, or possibly still in
3478 the given ts (current_ts), so look in both. */
3479 if (tmp_sym->ts.type != BT_UNKNOWN || ts->type != BT_UNKNOWN)
3481 if (verify_c_interop (&(tmp_sym->ts)) != SUCCESS)
3483 /* See if we're dealing with a sym in a common block or not. */
3484 if (is_in_common == 1)
3486 gfc_warning ("Variable '%s' in common block '%s' at %L "
3487 "may not be a C interoperable "
3488 "kind though common block '%s' is BIND(C)",
3489 tmp_sym->name, com_block->name,
3490 &(tmp_sym->declared_at), com_block->name);
3494 if (tmp_sym->ts.type == BT_DERIVED || ts->type == BT_DERIVED)
3495 gfc_error ("Type declaration '%s' at %L is not C "
3496 "interoperable but it is BIND(C)",
3497 tmp_sym->name, &(tmp_sym->declared_at));
3499 gfc_warning ("Variable '%s' at %L "
3500 "may not be a C interoperable "
3501 "kind but it is bind(c)",
3502 tmp_sym->name, &(tmp_sym->declared_at));
3506 /* Variables declared w/in a common block can't be bind(c)
3507 since there's no way for C to see these variables, so there's
3508 semantically no reason for the attribute. */
3509 if (is_in_common == 1 && tmp_sym->attr.is_bind_c == 1)
3511 gfc_error ("Variable '%s' in common block '%s' at "
3512 "%L cannot be declared with BIND(C) "
3513 "since it is not a global",
3514 tmp_sym->name, com_block->name,
3515 &(tmp_sym->declared_at));
3519 /* Scalar variables that are bind(c) can not have the pointer
3520 or allocatable attributes. */
3521 if (tmp_sym->attr.is_bind_c == 1)
3523 if (tmp_sym->attr.pointer == 1)
3525 gfc_error ("Variable '%s' at %L cannot have both the "
3526 "POINTER and BIND(C) attributes",
3527 tmp_sym->name, &(tmp_sym->declared_at));
3531 if (tmp_sym->attr.allocatable == 1)
3533 gfc_error ("Variable '%s' at %L cannot have both the "
3534 "ALLOCATABLE and BIND(C) attributes",
3535 tmp_sym->name, &(tmp_sym->declared_at));
3541 /* If it is a BIND(C) function, make sure the return value is a
3542 scalar value. The previous tests in this function made sure
3543 the type is interoperable. */
3544 if (bind_c_function && tmp_sym->as != NULL)
3545 gfc_error ("Return type of BIND(C) function '%s' at %L cannot "
3546 "be an array", tmp_sym->name, &(tmp_sym->declared_at));
3548 /* BIND(C) functions can not return a character string. */
3549 if (bind_c_function && tmp_sym->ts.type == BT_CHARACTER)
3550 if (tmp_sym->ts.u.cl == NULL || tmp_sym->ts.u.cl->length == NULL
3551 || tmp_sym->ts.u.cl->length->expr_type != EXPR_CONSTANT
3552 || mpz_cmp_si (tmp_sym->ts.u.cl->length->value.integer, 1) != 0)
3553 gfc_error ("Return type of BIND(C) function '%s' at %L cannot "
3554 "be a character string", tmp_sym->name,
3555 &(tmp_sym->declared_at));
3558 /* See if the symbol has been marked as private. If it has, make sure
3559 there is no binding label and warn the user if there is one. */
3560 if (tmp_sym->attr.access == ACCESS_PRIVATE
3561 && tmp_sym->binding_label[0] != '\0')
3562 /* Use gfc_warning_now because we won't say that the symbol fails
3563 just because of this. */
3564 gfc_warning_now ("Symbol '%s' at %L is marked PRIVATE but has been "
3565 "given the binding label '%s'", tmp_sym->name,
3566 &(tmp_sym->declared_at), tmp_sym->binding_label);
3572 /* Set the appropriate fields for a symbol that's been declared as
3573 BIND(C) (the is_bind_c flag and the binding label), and verify that
3574 the type is C interoperable. Errors are reported by the functions
3575 used to set/test these fields. */
3578 set_verify_bind_c_sym (gfc_symbol *tmp_sym, int num_idents)
3580 gfc_try retval = SUCCESS;
3582 /* TODO: Do we need to make sure the vars aren't marked private? */
3584 /* Set the is_bind_c bit in symbol_attribute. */
3585 gfc_add_is_bind_c (&(tmp_sym->attr), tmp_sym->name, &gfc_current_locus, 0);
3587 if (set_binding_label (tmp_sym->binding_label, tmp_sym->name,
3588 num_idents) != SUCCESS)
3595 /* Set the fields marking the given common block as BIND(C), including
3596 a binding label, and report any errors encountered. */
3599 set_verify_bind_c_com_block (gfc_common_head *com_block, int num_idents)
3601 gfc_try retval = SUCCESS;
3603 /* destLabel, common name, typespec (which may have binding label). */
3604 if (set_binding_label (com_block->binding_label, com_block->name, num_idents)
3608 /* Set the given common block (com_block) to being bind(c) (1). */
3609 set_com_block_bind_c (com_block, 1);
3615 /* Retrieve the list of one or more identifiers that the given bind(c)
3616 attribute applies to. */
3619 get_bind_c_idents (void)
3621 char name[GFC_MAX_SYMBOL_LEN + 1];
3623 gfc_symbol *tmp_sym = NULL;
3625 gfc_common_head *com_block = NULL;
3627 if (gfc_match_name (name) == MATCH_YES)
3629 found_id = MATCH_YES;
3630 gfc_get_ha_symbol (name, &tmp_sym);
3632 else if (match_common_name (name) == MATCH_YES)
3634 found_id = MATCH_YES;
3635 com_block = gfc_get_common (name, 0);
3639 gfc_error ("Need either entity or common block name for "
3640 "attribute specification statement at %C");
3644 /* Save the current identifier and look for more. */
3647 /* Increment the number of identifiers found for this spec stmt. */
3650 /* Make sure we have a sym or com block, and verify that it can
3651 be bind(c). Set the appropriate field(s) and look for more
3653 if (tmp_sym != NULL || com_block != NULL)
3655 if (tmp_sym != NULL)
3657 if (set_verify_bind_c_sym (tmp_sym, num_idents)
3663 if (set_verify_bind_c_com_block(com_block, num_idents)
3668 /* Look to see if we have another identifier. */
3670 if (gfc_match_eos () == MATCH_YES)
3671 found_id = MATCH_NO;
3672 else if (gfc_match_char (',') != MATCH_YES)
3673 found_id = MATCH_NO;
3674 else if (gfc_match_name (name) == MATCH_YES)
3676 found_id = MATCH_YES;
3677 gfc_get_ha_symbol (name, &tmp_sym);
3679 else if (match_common_name (name) == MATCH_YES)
3681 found_id = MATCH_YES;
3682 com_block = gfc_get_common (name, 0);
3686 gfc_error ("Missing entity or common block name for "
3687 "attribute specification statement at %C");
3693 gfc_internal_error ("Missing symbol");
3695 } while (found_id == MATCH_YES);
3697 /* if we get here we were successful */
3702 /* Try and match a BIND(C) attribute specification statement. */
3705 gfc_match_bind_c_stmt (void)
3707 match found_match = MATCH_NO;
3712 /* This may not be necessary. */
3714 /* Clear the temporary binding label holder. */
3715 curr_binding_label[0] = '\0';
3717 /* Look for the bind(c). */
3718 found_match = gfc_match_bind_c (NULL, true);
3720 if (found_match == MATCH_YES)
3722 /* Look for the :: now, but it is not required. */
3725 /* Get the identifier(s) that needs to be updated. This may need to
3726 change to hand the flag(s) for the attr specified so all identifiers
3727 found can have all appropriate parts updated (assuming that the same
3728 spec stmt can have multiple attrs, such as both bind(c) and
3730 if (get_bind_c_idents () != SUCCESS)
3731 /* Error message should have printed already. */
3739 /* Match a data declaration statement. */
3742 gfc_match_data_decl (void)
3748 num_idents_on_line = 0;
3750 m = gfc_match_decl_type_spec (¤t_ts, 0);
3754 if (current_ts.type == BT_DERIVED && gfc_current_state () != COMP_DERIVED)
3756 sym = gfc_use_derived (current_ts.u.derived);
3764 current_ts.u.derived = sym;
3767 m = match_attr_spec ();
3768 if (m == MATCH_ERROR)
3774 if (current_ts.type == BT_DERIVED && current_ts.u.derived->components == NULL
3775 && !current_ts.u.derived->attr.zero_comp)
3778 if (current_attr.pointer && gfc_current_state () == COMP_DERIVED)
3781 gfc_find_symbol (current_ts.u.derived->name,
3782 current_ts.u.derived->ns->parent, 1, &sym);
3784 /* Any symbol that we find had better be a type definition
3785 which has its components defined. */
3786 if (sym != NULL && sym->attr.flavor == FL_DERIVED
3787 && (current_ts.u.derived->components != NULL
3788 || current_ts.u.derived->attr.zero_comp))
3791 /* Now we have an error, which we signal, and then fix up
3792 because the knock-on is plain and simple confusing. */
3793 gfc_error_now ("Derived type at %C has not been previously defined "
3794 "and so cannot appear in a derived type definition");
3795 current_attr.pointer = 1;
3800 /* If we have an old-style character declaration, and no new-style
3801 attribute specifications, then there a comma is optional between
3802 the type specification and the variable list. */
3803 if (m == MATCH_NO && current_ts.type == BT_CHARACTER && old_char_selector)
3804 gfc_match_char (',');
3806 /* Give the types/attributes to symbols that follow. Give the element
3807 a number so that repeat character length expressions can be copied. */
3811 num_idents_on_line++;
3812 m = variable_decl (elem++);
3813 if (m == MATCH_ERROR)
3818 if (gfc_match_eos () == MATCH_YES)
3820 if (gfc_match_char (',') != MATCH_YES)
3824 if (gfc_error_flag_test () == 0)
3825 gfc_error ("Syntax error in data declaration at %C");
3828 gfc_free_data_all (gfc_current_ns);
3831 gfc_free_array_spec (current_as);
3837 /* Match a prefix associated with a function or subroutine
3838 declaration. If the typespec pointer is nonnull, then a typespec
3839 can be matched. Note that if nothing matches, MATCH_YES is
3840 returned (the null string was matched). */
3843 gfc_match_prefix (gfc_typespec *ts)
3847 gfc_clear_attr (¤t_attr);
3850 gcc_assert (!gfc_matching_prefix);
3851 gfc_matching_prefix = true;
3854 if (!seen_type && ts != NULL
3855 && gfc_match_decl_type_spec (ts, 0) == MATCH_YES
3856 && gfc_match_space () == MATCH_YES)
3863 if (gfc_match ("elemental% ") == MATCH_YES)
3865 if (gfc_add_elemental (¤t_attr, NULL) == FAILURE)
3871 if (gfc_match ("pure% ") == MATCH_YES)
3873 if (gfc_add_pure (¤t_attr, NULL) == FAILURE)
3879 if (gfc_match ("recursive% ") == MATCH_YES)
3881 if (gfc_add_recursive (¤t_attr, NULL) == FAILURE)
3887 /* At this point, the next item is not a prefix. */
3888 gcc_assert (gfc_matching_prefix);
3889 gfc_matching_prefix = false;
3893 gcc_assert (gfc_matching_prefix);
3894 gfc_matching_prefix = false;
3899 /* Copy attributes matched by gfc_match_prefix() to attributes on a symbol. */
3902 copy_prefix (symbol_attribute *dest, locus *where)
3904 if (current_attr.pure && gfc_add_pure (dest, where) == FAILURE)
3907 if (current_attr.elemental && gfc_add_elemental (dest, where) == FAILURE)
3910 if (current_attr.recursive && gfc_add_recursive (dest, where) == FAILURE)
3917 /* Match a formal argument list. */
3920 gfc_match_formal_arglist (gfc_symbol *progname, int st_flag, int null_flag)
3922 gfc_formal_arglist *head, *tail, *p, *q;
3923 char name[GFC_MAX_SYMBOL_LEN + 1];
3929 if (gfc_match_char ('(') != MATCH_YES)
3936 if (gfc_match_char (')') == MATCH_YES)
3941 if (gfc_match_char ('*') == MATCH_YES)
3945 m = gfc_match_name (name);
3949 if (gfc_get_symbol (name, NULL, &sym))
3953 p = gfc_get_formal_arglist ();
3965 /* We don't add the VARIABLE flavor because the name could be a
3966 dummy procedure. We don't apply these attributes to formal
3967 arguments of statement functions. */
3968 if (sym != NULL && !st_flag
3969 && (gfc_add_dummy (&sym->attr, sym->name, NULL) == FAILURE
3970 || gfc_missing_attr (&sym->attr, NULL) == FAILURE))
3976 /* The name of a program unit can be in a different namespace,
3977 so check for it explicitly. After the statement is accepted,
3978 the name is checked for especially in gfc_get_symbol(). */
3979 if (gfc_new_block != NULL && sym != NULL
3980 && strcmp (sym->name, gfc_new_block->name) == 0)
3982 gfc_error ("Name '%s' at %C is the name of the procedure",
3988 if (gfc_match_char (')') == MATCH_YES)
3991 m = gfc_match_char (',');
3994 gfc_error ("Unexpected junk in formal argument list at %C");
4000 /* Check for duplicate symbols in the formal argument list. */
4003 for (p = head; p->next; p = p->next)
4008 for (q = p->next; q; q = q->next)
4009 if (p->sym == q->sym)
4011 gfc_error ("Duplicate symbol '%s' in formal argument list "
4012 "at %C", p->sym->name);
4020 if (gfc_add_explicit_interface (progname, IFSRC_DECL, head, NULL)
4030 gfc_free_formal_arglist (head);
4035 /* Match a RESULT specification following a function declaration or
4036 ENTRY statement. Also matches the end-of-statement. */
4039 match_result (gfc_symbol *function, gfc_symbol **result)
4041 char name[GFC_MAX_SYMBOL_LEN + 1];
4045 if (gfc_match (" result (") != MATCH_YES)
4048 m = gfc_match_name (name);
4052 /* Get the right paren, and that's it because there could be the
4053 bind(c) attribute after the result clause. */
4054 if (gfc_match_char(')') != MATCH_YES)
4056 /* TODO: should report the missing right paren here. */
4060 if (strcmp (function->name, name) == 0)
4062 gfc_error ("RESULT variable at %C must be different than function name");
4066 if (gfc_get_symbol (name, NULL, &r))
4069 if (gfc_add_result (&r->attr, r->name, NULL) == FAILURE)
4078 /* Match a function suffix, which could be a combination of a result
4079 clause and BIND(C), either one, or neither. The draft does not
4080 require them to come in a specific order. */
4083 gfc_match_suffix (gfc_symbol *sym, gfc_symbol **result)
4085 match is_bind_c; /* Found bind(c). */
4086 match is_result; /* Found result clause. */
4087 match found_match; /* Status of whether we've found a good match. */
4088 char peek_char; /* Character we're going to peek at. */
4089 bool allow_binding_name;
4091 /* Initialize to having found nothing. */
4092 found_match = MATCH_NO;
4093 is_bind_c = MATCH_NO;
4094 is_result = MATCH_NO;
4096 /* Get the next char to narrow between result and bind(c). */
4097 gfc_gobble_whitespace ();
4098 peek_char = gfc_peek_ascii_char ();
4100 /* C binding names are not allowed for internal procedures. */
4101 if (gfc_current_state () == COMP_CONTAINS
4102 && sym->ns->proc_name->attr.flavor != FL_MODULE)
4103 allow_binding_name = false;
4105 allow_binding_name = true;
4110 /* Look for result clause. */
4111 is_result = match_result (sym, result);
4112 if (is_result == MATCH_YES)
4114 /* Now see if there is a bind(c) after it. */
4115 is_bind_c = gfc_match_bind_c (sym, allow_binding_name);
4116 /* We've found the result clause and possibly bind(c). */
4117 found_match = MATCH_YES;
4120 /* This should only be MATCH_ERROR. */
4121 found_match = is_result;
4124 /* Look for bind(c) first. */
4125 is_bind_c = gfc_match_bind_c (sym, allow_binding_name);
4126 if (is_bind_c == MATCH_YES)
4128 /* Now see if a result clause followed it. */
4129 is_result = match_result (sym, result);
4130 found_match = MATCH_YES;
4134 /* Should only be a MATCH_ERROR if we get here after seeing 'b'. */
4135 found_match = MATCH_ERROR;
4139 gfc_error ("Unexpected junk after function declaration at %C");
4140 found_match = MATCH_ERROR;
4144 if (is_bind_c == MATCH_YES)
4146 /* Fortran 2008 draft allows BIND(C) for internal procedures. */
4147 if (gfc_current_state () == COMP_CONTAINS
4148 && sym->ns->proc_name->attr.flavor != FL_MODULE
4149 && gfc_notify_std (GFC_STD_F2008, "Fortran 2008: BIND(C) attribute "
4150 "at %L may not be specified for an internal "
4151 "procedure", &gfc_current_locus)
4155 if (gfc_add_is_bind_c (&(sym->attr), sym->name, &gfc_current_locus, 1)