1 /* Declaration statement matcher
2 Copyright (C) 2002, 2004, 2005, 2006, 2007, 2008, 2009, 2010
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/>. */
28 #include "constructor.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
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 mpz_clear (p->repeat);
138 gfc_free_expr (p->expr);
144 /* Free a list of gfc_data structures. */
147 gfc_free_data (gfc_data *p)
154 free_variable (p->var);
155 free_value (p->value);
161 /* Free all data in a namespace. */
164 gfc_free_data_all (gfc_namespace *ns)
177 static match var_element (gfc_data_variable *);
179 /* Match a list of variables terminated by an iterator and a right
183 var_list (gfc_data_variable *parent)
185 gfc_data_variable *tail, var;
188 m = var_element (&var);
189 if (m == MATCH_ERROR)
194 tail = gfc_get_data_variable ();
201 if (gfc_match_char (',') != MATCH_YES)
204 m = gfc_match_iterator (&parent->iter, 1);
207 if (m == MATCH_ERROR)
210 m = var_element (&var);
211 if (m == MATCH_ERROR)
216 tail->next = gfc_get_data_variable ();
222 if (gfc_match_char (')') != MATCH_YES)
227 gfc_syntax_error (ST_DATA);
232 /* Match a single element in a data variable list, which can be a
233 variable-iterator list. */
236 var_element (gfc_data_variable *new_var)
241 memset (new_var, 0, sizeof (gfc_data_variable));
243 if (gfc_match_char ('(') == MATCH_YES)
244 return var_list (new_var);
246 m = gfc_match_variable (&new_var->expr, 0);
250 sym = new_var->expr->symtree->n.sym;
252 /* Symbol should already have an associated type. */
253 if (gfc_check_symbol_typed (sym, gfc_current_ns,
254 false, gfc_current_locus) == FAILURE)
257 if (!sym->attr.function && gfc_current_ns->parent
258 && gfc_current_ns->parent == sym->ns)
260 gfc_error ("Host associated variable '%s' may not be in the DATA "
261 "statement at %C", sym->name);
265 if (gfc_current_state () != COMP_BLOCK_DATA
266 && sym->attr.in_common
267 && gfc_notify_std (GFC_STD_GNU, "Extension: initialization of "
268 "common block variable '%s' in DATA statement at %C",
269 sym->name) == FAILURE)
272 if (gfc_add_data (&sym->attr, sym->name, &new_var->expr->where) == FAILURE)
279 /* Match the top-level list of data variables. */
282 top_var_list (gfc_data *d)
284 gfc_data_variable var, *tail, *new_var;
291 m = var_element (&var);
294 if (m == MATCH_ERROR)
297 new_var = gfc_get_data_variable ();
303 tail->next = new_var;
307 if (gfc_match_char ('/') == MATCH_YES)
309 if (gfc_match_char (',') != MATCH_YES)
316 gfc_syntax_error (ST_DATA);
317 gfc_free_data_all (gfc_current_ns);
323 match_data_constant (gfc_expr **result)
325 char name[GFC_MAX_SYMBOL_LEN + 1];
331 m = gfc_match_literal_constant (&expr, 1);
338 if (m == MATCH_ERROR)
341 m = gfc_match_null (result);
345 old_loc = gfc_current_locus;
347 /* Should this be a structure component, try to match it
348 before matching a name. */
349 m = gfc_match_rvalue (result);
350 if (m == MATCH_ERROR)
353 if (m == MATCH_YES && (*result)->expr_type == EXPR_STRUCTURE)
355 if (gfc_simplify_expr (*result, 0) == FAILURE)
360 gfc_current_locus = old_loc;
362 m = gfc_match_name (name);
366 if (gfc_find_symbol (name, NULL, 1, &sym))
370 || (sym->attr.flavor != FL_PARAMETER && sym->attr.flavor != FL_DERIVED))
372 gfc_error ("Symbol '%s' must be a PARAMETER in DATA statement at %C",
376 else if (sym->attr.flavor == FL_DERIVED)
377 return gfc_match_structure_constructor (sym, result, false);
379 /* Check to see if the value is an initialization array expression. */
380 if (sym->value->expr_type == EXPR_ARRAY)
382 gfc_current_locus = old_loc;
384 m = gfc_match_init_expr (result);
385 if (m == MATCH_ERROR)
390 if (gfc_simplify_expr (*result, 0) == FAILURE)
393 if ((*result)->expr_type == EXPR_CONSTANT)
397 gfc_error ("Invalid initializer %s in Data statement at %C", name);
403 *result = gfc_copy_expr (sym->value);
408 /* Match a list of values in a DATA statement. The leading '/' has
409 already been seen at this point. */
412 top_val_list (gfc_data *data)
414 gfc_data_value *new_val, *tail;
422 m = match_data_constant (&expr);
425 if (m == MATCH_ERROR)
428 new_val = gfc_get_data_value ();
429 mpz_init (new_val->repeat);
432 data->value = new_val;
434 tail->next = new_val;
438 if (expr->ts.type != BT_INTEGER || gfc_match_char ('*') != MATCH_YES)
441 mpz_set_ui (tail->repeat, 1);
445 if (expr->ts.type == BT_INTEGER)
446 mpz_set (tail->repeat, expr->value.integer);
447 gfc_free_expr (expr);
449 m = match_data_constant (&tail->expr);
452 if (m == MATCH_ERROR)
456 if (gfc_match_char ('/') == MATCH_YES)
458 if (gfc_match_char (',') == MATCH_NO)
465 gfc_syntax_error (ST_DATA);
466 gfc_free_data_all (gfc_current_ns);
471 /* Matches an old style initialization. */
474 match_old_style_init (const char *name)
481 /* Set up data structure to hold initializers. */
482 gfc_find_sym_tree (name, NULL, 0, &st);
485 newdata = gfc_get_data ();
486 newdata->var = gfc_get_data_variable ();
487 newdata->var->expr = gfc_get_variable_expr (st);
488 newdata->where = gfc_current_locus;
490 /* Match initial value list. This also eats the terminal '/'. */
491 m = top_val_list (newdata);
500 gfc_error ("Initialization at %C is not allowed in a PURE procedure");
505 /* Mark the variable as having appeared in a data statement. */
506 if (gfc_add_data (&sym->attr, sym->name, &sym->declared_at) == FAILURE)
512 /* Chain in namespace list of DATA initializers. */
513 newdata->next = gfc_current_ns->data;
514 gfc_current_ns->data = newdata;
520 /* Match the stuff following a DATA statement. If ERROR_FLAG is set,
521 we are matching a DATA statement and are therefore issuing an error
522 if we encounter something unexpected, if not, we're trying to match
523 an old-style initialization expression of the form INTEGER I /2/. */
526 gfc_match_data (void)
531 set_in_match_data (true);
535 new_data = gfc_get_data ();
536 new_data->where = gfc_current_locus;
538 m = top_var_list (new_data);
542 m = top_val_list (new_data);
546 new_data->next = gfc_current_ns->data;
547 gfc_current_ns->data = new_data;
549 if (gfc_match_eos () == MATCH_YES)
552 gfc_match_char (','); /* Optional comma */
555 set_in_match_data (false);
559 gfc_error ("DATA statement at %C is not allowed in a PURE procedure");
566 set_in_match_data (false);
567 gfc_free_data (new_data);
572 /************************ Declaration statements *********************/
575 /* Auxilliary function to merge DIMENSION and CODIMENSION array specs. */
578 merge_array_spec (gfc_array_spec *from, gfc_array_spec *to, bool copy)
582 if (to->rank == 0 && from->rank > 0)
584 to->rank = from->rank;
585 to->type = from->type;
586 to->cray_pointee = from->cray_pointee;
587 to->cp_was_assumed = from->cp_was_assumed;
589 for (i = 0; i < to->corank; i++)
591 to->lower[from->rank + i] = to->lower[i];
592 to->upper[from->rank + i] = to->upper[i];
594 for (i = 0; i < from->rank; i++)
598 to->lower[i] = gfc_copy_expr (from->lower[i]);
599 to->upper[i] = gfc_copy_expr (from->upper[i]);
603 to->lower[i] = from->lower[i];
604 to->upper[i] = from->upper[i];
608 else if (to->corank == 0 && from->corank > 0)
610 to->corank = from->corank;
611 to->cotype = from->cotype;
613 for (i = 0; i < from->corank; i++)
617 to->lower[to->rank + i] = gfc_copy_expr (from->lower[i]);
618 to->upper[to->rank + i] = gfc_copy_expr (from->upper[i]);
622 to->lower[to->rank + i] = from->lower[i];
623 to->upper[to->rank + i] = from->upper[i];
630 /* Match an intent specification. Since this can only happen after an
631 INTENT word, a legal intent-spec must follow. */
634 match_intent_spec (void)
637 if (gfc_match (" ( in out )") == MATCH_YES)
639 if (gfc_match (" ( in )") == MATCH_YES)
641 if (gfc_match (" ( out )") == MATCH_YES)
644 gfc_error ("Bad INTENT specification at %C");
645 return INTENT_UNKNOWN;
649 /* Matches a character length specification, which is either a
650 specification expression or a '*'. */
653 char_len_param_value (gfc_expr **expr)
657 if (gfc_match_char ('*') == MATCH_YES)
663 m = gfc_match_expr (expr);
666 && gfc_expr_check_typed (*expr, gfc_current_ns, false) == FAILURE)
669 if (m == MATCH_YES && (*expr)->expr_type == EXPR_FUNCTION)
671 if ((*expr)->value.function.actual
672 && (*expr)->value.function.actual->expr->symtree)
675 e = (*expr)->value.function.actual->expr;
676 if (e->symtree->n.sym->attr.flavor == FL_PROCEDURE
677 && e->expr_type == EXPR_VARIABLE)
679 if (e->symtree->n.sym->ts.type == BT_UNKNOWN)
681 if (e->symtree->n.sym->ts.type == BT_CHARACTER
682 && e->symtree->n.sym->ts.u.cl
683 && e->symtree->n.sym->ts.u.cl->length->ts.type == BT_UNKNOWN)
691 gfc_error ("Conflict in attributes of function argument at %C");
696 /* A character length is a '*' followed by a literal integer or a
697 char_len_param_value in parenthesis. */
700 match_char_length (gfc_expr **expr)
705 m = gfc_match_char ('*');
709 m = gfc_match_small_literal_int (&length, NULL);
710 if (m == MATCH_ERROR)
715 if (gfc_notify_std (GFC_STD_F95_OBS, "Obsolescent feature: "
716 "Old-style character length at %C") == FAILURE)
718 *expr = gfc_get_int_expr (gfc_default_integer_kind, NULL, length);
722 if (gfc_match_char ('(') == MATCH_NO)
725 m = char_len_param_value (expr);
726 if (m != MATCH_YES && gfc_matching_function)
732 if (m == MATCH_ERROR)
737 if (gfc_match_char (')') == MATCH_NO)
739 gfc_free_expr (*expr);
747 gfc_error ("Syntax error in character length specification at %C");
752 /* Special subroutine for finding a symbol. Check if the name is found
753 in the current name space. If not, and we're compiling a function or
754 subroutine and the parent compilation unit is an interface, then check
755 to see if the name we've been given is the name of the interface
756 (located in another namespace). */
759 find_special (const char *name, gfc_symbol **result, bool allow_subroutine)
765 i = gfc_get_sym_tree (name, NULL, &st, allow_subroutine);
768 *result = st ? st->n.sym : NULL;
772 if (gfc_current_state () != COMP_SUBROUTINE
773 && gfc_current_state () != COMP_FUNCTION)
776 s = gfc_state_stack->previous;
780 if (s->state != COMP_INTERFACE)
783 goto end; /* Nameless interface. */
785 if (strcmp (name, s->sym->name) == 0)
796 /* Special subroutine for getting a symbol node associated with a
797 procedure name, used in SUBROUTINE and FUNCTION statements. The
798 symbol is created in the parent using with symtree node in the
799 child unit pointing to the symbol. If the current namespace has no
800 parent, then the symbol is just created in the current unit. */
803 get_proc_name (const char *name, gfc_symbol **result, bool module_fcn_entry)
809 /* Module functions have to be left in their own namespace because
810 they have potentially (almost certainly!) already been referenced.
811 In this sense, they are rather like external functions. This is
812 fixed up in resolve.c(resolve_entries), where the symbol name-
813 space is set to point to the master function, so that the fake
814 result mechanism can work. */
815 if (module_fcn_entry)
817 /* Present if entry is declared to be a module procedure. */
818 rc = gfc_find_symbol (name, gfc_current_ns->parent, 0, result);
821 rc = gfc_get_symbol (name, NULL, result);
822 else if (!gfc_get_symbol (name, NULL, &sym) && sym
823 && (*result)->ts.type == BT_UNKNOWN
824 && sym->attr.flavor == FL_UNKNOWN)
825 /* Pick up the typespec for the entry, if declared in the function
826 body. Note that this symbol is FL_UNKNOWN because it will
827 only have appeared in a type declaration. The local symtree
828 is set to point to the module symbol and a unique symtree
829 to the local version. This latter ensures a correct clearing
832 /* If the ENTRY proceeds its specification, we need to ensure
833 that this does not raise a "has no IMPLICIT type" error. */
834 if (sym->ts.type == BT_UNKNOWN)
835 sym->attr.untyped = 1;
837 (*result)->ts = sym->ts;
839 /* Put the symbol in the procedure namespace so that, should
840 the ENTRY precede its specification, the specification
842 (*result)->ns = gfc_current_ns;
844 gfc_find_sym_tree (name, gfc_current_ns, 0, &st);
846 st = gfc_get_unique_symtree (gfc_current_ns);
851 rc = gfc_get_symbol (name, gfc_current_ns->parent, result);
857 gfc_current_ns->refs++;
859 if (sym && !sym->gfc_new && gfc_current_state () != COMP_INTERFACE)
861 /* Trap another encompassed procedure with the same name. All
862 these conditions are necessary to avoid picking up an entry
863 whose name clashes with that of the encompassing procedure;
864 this is handled using gsymbols to register unique,globally
866 if (sym->attr.flavor != 0
867 && sym->attr.proc != 0
868 && (sym->attr.subroutine || sym->attr.function)
869 && sym->attr.if_source != IFSRC_UNKNOWN)
870 gfc_error_now ("Procedure '%s' at %C is already defined at %L",
871 name, &sym->declared_at);
873 /* Trap a procedure with a name the same as interface in the
874 encompassing scope. */
875 if (sym->attr.generic != 0
876 && (sym->attr.subroutine || sym->attr.function)
877 && !sym->attr.mod_proc)
878 gfc_error_now ("Name '%s' at %C is already defined"
879 " as a generic interface at %L",
880 name, &sym->declared_at);
882 /* Trap declarations of attributes in encompassing scope. The
883 signature for this is that ts.kind is set. Legitimate
884 references only set ts.type. */
885 if (sym->ts.kind != 0
886 && !sym->attr.implicit_type
887 && sym->attr.proc == 0
888 && gfc_current_ns->parent != NULL
889 && sym->attr.access == 0
890 && !module_fcn_entry)
891 gfc_error_now ("Procedure '%s' at %C has an explicit interface "
892 "and must not have attributes declared at %L",
893 name, &sym->declared_at);
896 if (gfc_current_ns->parent == NULL || *result == NULL)
899 /* Module function entries will already have a symtree in
900 the current namespace but will need one at module level. */
901 if (module_fcn_entry)
903 /* Present if entry is declared to be a module procedure. */
904 rc = gfc_find_sym_tree (name, gfc_current_ns->parent, 0, &st);
906 st = gfc_new_symtree (&gfc_current_ns->parent->sym_root, name);
909 st = gfc_new_symtree (&gfc_current_ns->sym_root, name);
914 /* See if the procedure should be a module procedure. */
916 if (((sym->ns->proc_name != NULL
917 && sym->ns->proc_name->attr.flavor == FL_MODULE
918 && sym->attr.proc != PROC_MODULE)
919 || (module_fcn_entry && sym->attr.proc != PROC_MODULE))
920 && gfc_add_procedure (&sym->attr, PROC_MODULE,
921 sym->name, NULL) == FAILURE)
928 /* Verify that the given symbol representing a parameter is C
929 interoperable, by checking to see if it was marked as such after
930 its declaration. If the given symbol is not interoperable, a
931 warning is reported, thus removing the need to return the status to
932 the calling function. The standard does not require the user use
933 one of the iso_c_binding named constants to declare an
934 interoperable parameter, but we can't be sure if the param is C
935 interop or not if the user doesn't. For example, integer(4) may be
936 legal Fortran, but doesn't have meaning in C. It may interop with
937 a number of the C types, which causes a problem because the
938 compiler can't know which one. This code is almost certainly not
939 portable, and the user will get what they deserve if the C type
940 across platforms isn't always interoperable with integer(4). If
941 the user had used something like integer(c_int) or integer(c_long),
942 the compiler could have automatically handled the varying sizes
946 verify_c_interop_param (gfc_symbol *sym)
948 int is_c_interop = 0;
949 gfc_try retval = SUCCESS;
951 /* We check implicitly typed variables in symbol.c:gfc_set_default_type().
952 Don't repeat the checks here. */
953 if (sym->attr.implicit_type)
956 /* For subroutines or functions that are passed to a BIND(C) procedure,
957 they're interoperable if they're BIND(C) and their params are all
959 if (sym->attr.flavor == FL_PROCEDURE)
961 if (sym->attr.is_bind_c == 0)
963 gfc_error_now ("Procedure '%s' at %L must have the BIND(C) "
964 "attribute to be C interoperable", sym->name,
965 &(sym->declared_at));
971 if (sym->attr.is_c_interop == 1)
972 /* We've already checked this procedure; don't check it again. */
975 return verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
980 /* See if we've stored a reference to a procedure that owns sym. */
981 if (sym->ns != NULL && sym->ns->proc_name != NULL)
983 if (sym->ns->proc_name->attr.is_bind_c == 1)
986 (verify_c_interop (&(sym->ts))
989 if (is_c_interop != 1)
991 /* Make personalized messages to give better feedback. */
992 if (sym->ts.type == BT_DERIVED)
993 gfc_error ("Type '%s' at %L is a parameter to the BIND(C) "
994 "procedure '%s' but is not C interoperable "
995 "because derived type '%s' is not C interoperable",
996 sym->name, &(sym->declared_at),
997 sym->ns->proc_name->name,
998 sym->ts.u.derived->name);
1000 gfc_warning ("Variable '%s' at %L is a parameter to the "
1001 "BIND(C) procedure '%s' but may not be C "
1003 sym->name, &(sym->declared_at),
1004 sym->ns->proc_name->name);
1007 /* Character strings are only C interoperable if they have a
1009 if (sym->ts.type == BT_CHARACTER)
1011 gfc_charlen *cl = sym->ts.u.cl;
1012 if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT
1013 || mpz_cmp_si (cl->length->value.integer, 1) != 0)
1015 gfc_error ("Character argument '%s' at %L "
1016 "must be length 1 because "
1017 "procedure '%s' is BIND(C)",
1018 sym->name, &sym->declared_at,
1019 sym->ns->proc_name->name);
1024 /* We have to make sure that any param to a bind(c) routine does
1025 not have the allocatable, pointer, or optional attributes,
1026 according to J3/04-007, section 5.1. */
1027 if (sym->attr.allocatable == 1)
1029 gfc_error ("Variable '%s' at %L cannot have the "
1030 "ALLOCATABLE attribute because procedure '%s'"
1031 " is BIND(C)", sym->name, &(sym->declared_at),
1032 sym->ns->proc_name->name);
1036 if (sym->attr.pointer == 1)
1038 gfc_error ("Variable '%s' at %L cannot have the "
1039 "POINTER attribute because procedure '%s'"
1040 " is BIND(C)", sym->name, &(sym->declared_at),
1041 sym->ns->proc_name->name);
1045 if (sym->attr.optional == 1)
1047 gfc_error ("Variable '%s' at %L cannot have the "
1048 "OPTIONAL attribute because procedure '%s'"
1049 " is BIND(C)", sym->name, &(sym->declared_at),
1050 sym->ns->proc_name->name);
1054 /* Make sure that if it has the dimension attribute, that it is
1055 either assumed size or explicit shape. */
1056 if (sym->as != NULL)
1058 if (sym->as->type == AS_ASSUMED_SHAPE)
1060 gfc_error ("Assumed-shape array '%s' at %L cannot be an "
1061 "argument to the procedure '%s' at %L because "
1062 "the procedure is BIND(C)", sym->name,
1063 &(sym->declared_at), sym->ns->proc_name->name,
1064 &(sym->ns->proc_name->declared_at));
1068 if (sym->as->type == AS_DEFERRED)
1070 gfc_error ("Deferred-shape array '%s' at %L cannot be an "
1071 "argument to the procedure '%s' at %L because "
1072 "the procedure is BIND(C)", sym->name,
1073 &(sym->declared_at), sym->ns->proc_name->name,
1074 &(sym->ns->proc_name->declared_at));
1086 /* Function called by variable_decl() that adds a name to the symbol table. */
1089 build_sym (const char *name, gfc_charlen *cl,
1090 gfc_array_spec **as, locus *var_locus)
1092 symbol_attribute attr;
1095 if (gfc_get_symbol (name, NULL, &sym))
1098 /* Start updating the symbol table. Add basic type attribute if present. */
1099 if (current_ts.type != BT_UNKNOWN
1100 && (sym->attr.implicit_type == 0
1101 || !gfc_compare_types (&sym->ts, ¤t_ts))
1102 && gfc_add_type (sym, ¤t_ts, var_locus) == FAILURE)
1105 if (sym->ts.type == BT_CHARACTER)
1108 /* Add dimension attribute if present. */
1109 if (gfc_set_array_spec (sym, *as, var_locus) == FAILURE)
1113 /* Add attribute to symbol. The copy is so that we can reset the
1114 dimension attribute. */
1115 attr = current_attr;
1117 attr.codimension = 0;
1119 if (gfc_copy_attr (&sym->attr, &attr, var_locus) == FAILURE)
1122 /* Finish any work that may need to be done for the binding label,
1123 if it's a bind(c). The bind(c) attr is found before the symbol
1124 is made, and before the symbol name (for data decls), so the
1125 current_ts is holding the binding label, or nothing if the
1126 name= attr wasn't given. Therefore, test here if we're dealing
1127 with a bind(c) and make sure the binding label is set correctly. */
1128 if (sym->attr.is_bind_c == 1)
1130 if (sym->binding_label[0] == '\0')
1132 /* Set the binding label and verify that if a NAME= was specified
1133 then only one identifier was in the entity-decl-list. */
1134 if (set_binding_label (sym->binding_label, sym->name,
1135 num_idents_on_line) == FAILURE)
1140 /* See if we know we're in a common block, and if it's a bind(c)
1141 common then we need to make sure we're an interoperable type. */
1142 if (sym->attr.in_common == 1)
1144 /* Test the common block object. */
1145 if (sym->common_block != NULL && sym->common_block->is_bind_c == 1
1146 && sym->ts.is_c_interop != 1)
1148 gfc_error_now ("Variable '%s' in common block '%s' at %C "
1149 "must be declared with a C interoperable "
1150 "kind since common block '%s' is BIND(C)",
1151 sym->name, sym->common_block->name,
1152 sym->common_block->name);
1157 sym->attr.implied_index = 0;
1159 if (sym->ts.type == BT_CLASS
1160 && (sym->attr.class_ok = sym->attr.dummy || sym->attr.pointer
1161 || sym->attr.allocatable))
1162 gfc_build_class_symbol (&sym->ts, &sym->attr, &sym->as, false);
1168 /* Set character constant to the given length. The constant will be padded or
1169 truncated. If we're inside an array constructor without a typespec, we
1170 additionally check that all elements have the same length; check_len -1
1171 means no checking. */
1174 gfc_set_constant_character_len (int len, gfc_expr *expr, int check_len)
1179 gcc_assert (expr->expr_type == EXPR_CONSTANT);
1180 gcc_assert (expr->ts.type == BT_CHARACTER);
1182 slen = expr->value.character.length;
1185 s = gfc_get_wide_string (len + 1);
1186 memcpy (s, expr->value.character.string,
1187 MIN (len, slen) * sizeof (gfc_char_t));
1189 gfc_wide_memset (&s[slen], ' ', len - slen);
1191 if (gfc_option.warn_character_truncation && slen > len)
1192 gfc_warning_now ("CHARACTER expression at %L is being truncated "
1193 "(%d/%d)", &expr->where, slen, len);
1195 /* Apply the standard by 'hand' otherwise it gets cleared for
1197 if (check_len != -1 && slen != check_len
1198 && !(gfc_option.allow_std & GFC_STD_GNU))
1199 gfc_error_now ("The CHARACTER elements of the array constructor "
1200 "at %L must have the same length (%d/%d)",
1201 &expr->where, slen, check_len);
1204 gfc_free (expr->value.character.string);
1205 expr->value.character.string = s;
1206 expr->value.character.length = len;
1211 /* Function to create and update the enumerator history
1212 using the information passed as arguments.
1213 Pointer "max_enum" is also updated, to point to
1214 enum history node containing largest initializer.
1216 SYM points to the symbol node of enumerator.
1217 INIT points to its enumerator value. */
1220 create_enum_history (gfc_symbol *sym, gfc_expr *init)
1222 enumerator_history *new_enum_history;
1223 gcc_assert (sym != NULL && init != NULL);
1225 new_enum_history = XCNEW (enumerator_history);
1227 new_enum_history->sym = sym;
1228 new_enum_history->initializer = init;
1229 new_enum_history->next = NULL;
1231 if (enum_history == NULL)
1233 enum_history = new_enum_history;
1234 max_enum = enum_history;
1238 new_enum_history->next = enum_history;
1239 enum_history = new_enum_history;
1241 if (mpz_cmp (max_enum->initializer->value.integer,
1242 new_enum_history->initializer->value.integer) < 0)
1243 max_enum = new_enum_history;
1248 /* Function to free enum kind history. */
1251 gfc_free_enum_history (void)
1253 enumerator_history *current = enum_history;
1254 enumerator_history *next;
1256 while (current != NULL)
1258 next = current->next;
1263 enum_history = NULL;
1267 /* Function called by variable_decl() that adds an initialization
1268 expression to a symbol. */
1271 add_init_expr_to_sym (const char *name, gfc_expr **initp, locus *var_locus)
1273 symbol_attribute attr;
1278 if (find_special (name, &sym, false))
1283 /* If this symbol is confirming an implicit parameter type,
1284 then an initialization expression is not allowed. */
1285 if (attr.flavor == FL_PARAMETER
1286 && sym->value != NULL
1289 gfc_error ("Initializer not allowed for PARAMETER '%s' at %C",
1296 /* An initializer is required for PARAMETER declarations. */
1297 if (attr.flavor == FL_PARAMETER)
1299 gfc_error ("PARAMETER at %L is missing an initializer", var_locus);
1305 /* If a variable appears in a DATA block, it cannot have an
1309 gfc_error ("Variable '%s' at %C with an initializer already "
1310 "appears in a DATA statement", sym->name);
1314 /* Check if the assignment can happen. This has to be put off
1315 until later for derived type variables and procedure pointers. */
1316 if (sym->ts.type != BT_DERIVED && init->ts.type != BT_DERIVED
1317 && sym->ts.type != BT_CLASS && init->ts.type != BT_CLASS
1318 && !sym->attr.proc_pointer
1319 && gfc_check_assign_symbol (sym, init) == FAILURE)
1322 if (sym->ts.type == BT_CHARACTER && sym->ts.u.cl
1323 && init->ts.type == BT_CHARACTER)
1325 /* Update symbol character length according initializer. */
1326 if (gfc_check_assign_symbol (sym, init) == FAILURE)
1329 if (sym->ts.u.cl->length == NULL)
1332 /* If there are multiple CHARACTER variables declared on the
1333 same line, we don't want them to share the same length. */
1334 sym->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
1336 if (sym->attr.flavor == FL_PARAMETER)
1338 if (init->expr_type == EXPR_CONSTANT)
1340 clen = init->value.character.length;
1341 sym->ts.u.cl->length
1342 = gfc_get_int_expr (gfc_default_integer_kind,
1345 else if (init->expr_type == EXPR_ARRAY)
1348 c = gfc_constructor_first (init->value.constructor);
1349 clen = c->expr->value.character.length;
1350 sym->ts.u.cl->length
1351 = gfc_get_int_expr (gfc_default_integer_kind,
1354 else if (init->ts.u.cl && init->ts.u.cl->length)
1355 sym->ts.u.cl->length =
1356 gfc_copy_expr (sym->value->ts.u.cl->length);
1359 /* Update initializer character length according symbol. */
1360 else if (sym->ts.u.cl->length->expr_type == EXPR_CONSTANT)
1362 int len = mpz_get_si (sym->ts.u.cl->length->value.integer);
1364 if (init->expr_type == EXPR_CONSTANT)
1365 gfc_set_constant_character_len (len, init, -1);
1366 else if (init->expr_type == EXPR_ARRAY)
1370 /* Build a new charlen to prevent simplification from
1371 deleting the length before it is resolved. */
1372 init->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
1373 init->ts.u.cl->length = gfc_copy_expr (sym->ts.u.cl->length);
1375 for (c = gfc_constructor_first (init->value.constructor);
1376 c; c = gfc_constructor_next (c))
1377 gfc_set_constant_character_len (len, c->expr, -1);
1382 /* If sym is implied-shape, set its upper bounds from init. */
1383 if (sym->attr.flavor == FL_PARAMETER && sym->attr.dimension
1384 && sym->as->type == AS_IMPLIED_SHAPE)
1388 if (init->rank == 0)
1390 gfc_error ("Can't initialize implied-shape array at %L"
1391 " with scalar", &sym->declared_at);
1394 gcc_assert (sym->as->rank == init->rank);
1396 /* Shape should be present, we get an initialization expression. */
1397 gcc_assert (init->shape);
1399 for (dim = 0; dim < sym->as->rank; ++dim)
1405 lower = sym->as->lower[dim];
1406 if (lower->expr_type != EXPR_CONSTANT)
1408 gfc_error ("Non-constant lower bound in implied-shape"
1409 " declaration at %L", &lower->where);
1413 /* All dimensions must be without upper bound. */
1414 gcc_assert (!sym->as->upper[dim]);
1417 e = gfc_get_constant_expr (BT_INTEGER, k, &sym->declared_at);
1418 mpz_add (e->value.integer,
1419 lower->value.integer, init->shape[dim]);
1420 mpz_sub_ui (e->value.integer, e->value.integer, 1);
1421 sym->as->upper[dim] = e;
1424 sym->as->type = AS_EXPLICIT;
1427 /* Need to check if the expression we initialized this
1428 to was one of the iso_c_binding named constants. If so,
1429 and we're a parameter (constant), let it be iso_c.
1431 integer(c_int), parameter :: my_int = c_int
1432 integer(my_int) :: my_int_2
1433 If we mark my_int as iso_c (since we can see it's value
1434 is equal to one of the named constants), then my_int_2
1435 will be considered C interoperable. */
1436 if (sym->ts.type != BT_CHARACTER && sym->ts.type != BT_DERIVED)
1438 sym->ts.is_iso_c |= init->ts.is_iso_c;
1439 sym->ts.is_c_interop |= init->ts.is_c_interop;
1440 /* attr bits needed for module files. */
1441 sym->attr.is_iso_c |= init->ts.is_iso_c;
1442 sym->attr.is_c_interop |= init->ts.is_c_interop;
1443 if (init->ts.is_iso_c)
1444 sym->ts.f90_type = init->ts.f90_type;
1447 /* Add initializer. Make sure we keep the ranks sane. */
1448 if (sym->attr.dimension && init->rank == 0)
1453 if (sym->attr.flavor == FL_PARAMETER
1454 && init->expr_type == EXPR_CONSTANT
1455 && spec_size (sym->as, &size) == SUCCESS
1456 && mpz_cmp_si (size, 0) > 0)
1458 array = gfc_get_array_expr (init->ts.type, init->ts.kind,
1460 for (n = 0; n < (int)mpz_get_si (size); n++)
1461 gfc_constructor_append_expr (&array->value.constructor,
1464 : gfc_copy_expr (init),
1467 array->shape = gfc_get_shape (sym->as->rank);
1468 for (n = 0; n < sym->as->rank; n++)
1469 spec_dimen_size (sym->as, n, &array->shape[n]);
1474 init->rank = sym->as->rank;
1478 if (sym->attr.save == SAVE_NONE)
1479 sym->attr.save = SAVE_IMPLICIT;
1487 /* Function called by variable_decl() that adds a name to a structure
1491 build_struct (const char *name, gfc_charlen *cl, gfc_expr **init,
1492 gfc_array_spec **as)
1495 gfc_try t = SUCCESS;
1497 /* F03:C438/C439. If the current symbol is of the same derived type that we're
1498 constructing, it must have the pointer attribute. */
1499 if ((current_ts.type == BT_DERIVED || current_ts.type == BT_CLASS)
1500 && current_ts.u.derived == gfc_current_block ()
1501 && current_attr.pointer == 0)
1503 gfc_error ("Component at %C must have the POINTER attribute");
1507 if (gfc_current_block ()->attr.pointer && (*as)->rank != 0)
1509 if ((*as)->type != AS_DEFERRED && (*as)->type != AS_EXPLICIT)
1511 gfc_error ("Array component of structure at %C must have explicit "
1512 "or deferred shape");
1517 if (gfc_add_component (gfc_current_block (), name, &c) == FAILURE)
1521 if (c->ts.type == BT_CHARACTER)
1523 c->attr = current_attr;
1525 c->initializer = *init;
1532 c->attr.codimension = 1;
1534 c->attr.dimension = 1;
1538 /* Should this ever get more complicated, combine with similar section
1539 in add_init_expr_to_sym into a separate function. */
1540 if (c->ts.type == BT_CHARACTER && !c->attr.pointer && c->initializer && c->ts.u.cl
1541 && c->ts.u.cl->length && c->ts.u.cl->length->expr_type == EXPR_CONSTANT)
1545 gcc_assert (c->ts.u.cl && c->ts.u.cl->length);
1546 gcc_assert (c->ts.u.cl->length->expr_type == EXPR_CONSTANT);
1547 gcc_assert (c->ts.u.cl->length->ts.type == BT_INTEGER);
1549 len = mpz_get_si (c->ts.u.cl->length->value.integer);
1551 if (c->initializer->expr_type == EXPR_CONSTANT)
1552 gfc_set_constant_character_len (len, c->initializer, -1);
1553 else if (mpz_cmp (c->ts.u.cl->length->value.integer,
1554 c->initializer->ts.u.cl->length->value.integer))
1556 gfc_constructor *ctor;
1557 ctor = gfc_constructor_first (c->initializer->value.constructor);
1562 bool has_ts = (c->initializer->ts.u.cl
1563 && c->initializer->ts.u.cl->length_from_typespec);
1565 /* Remember the length of the first element for checking
1566 that all elements *in the constructor* have the same
1567 length. This need not be the length of the LHS! */
1568 gcc_assert (ctor->expr->expr_type == EXPR_CONSTANT);
1569 gcc_assert (ctor->expr->ts.type == BT_CHARACTER);
1570 first_len = ctor->expr->value.character.length;
1572 for ( ; ctor; ctor = gfc_constructor_next (ctor))
1573 if (ctor->expr->expr_type == EXPR_CONSTANT)
1575 gfc_set_constant_character_len (len, ctor->expr,
1576 has_ts ? -1 : first_len);
1577 ctor->expr->ts.u.cl->length = gfc_copy_expr (c->ts.u.cl->length);
1583 /* Check array components. */
1584 if (!c->attr.dimension)
1587 if (c->attr.pointer)
1589 if (c->as->type != AS_DEFERRED)
1591 gfc_error ("Pointer array component of structure at %C must have a "
1596 else if (c->attr.allocatable)
1598 if (c->as->type != AS_DEFERRED)
1600 gfc_error ("Allocatable component of structure at %C must have a "
1607 if (c->as->type != AS_EXPLICIT)
1609 gfc_error ("Array component of structure at %C must have an "
1616 if (c->ts.type == BT_CLASS)
1617 gfc_build_class_symbol (&c->ts, &c->attr, &c->as, true);
1623 /* Match a 'NULL()', and possibly take care of some side effects. */
1626 gfc_match_null (gfc_expr **result)
1631 m = gfc_match (" null ( )");
1635 /* The NULL symbol now has to be/become an intrinsic function. */
1636 if (gfc_get_symbol ("null", NULL, &sym))
1638 gfc_error ("NULL() initialization at %C is ambiguous");
1642 gfc_intrinsic_symbol (sym);
1644 if (sym->attr.proc != PROC_INTRINSIC
1645 && (gfc_add_procedure (&sym->attr, PROC_INTRINSIC,
1646 sym->name, NULL) == FAILURE
1647 || gfc_add_function (&sym->attr, sym->name, NULL) == FAILURE))
1650 *result = gfc_get_null_expr (&gfc_current_locus);
1656 /* Match the initialization expr for a data pointer or procedure pointer. */
1659 match_pointer_init (gfc_expr **init, int procptr)
1663 if (gfc_pure (NULL) && gfc_state_stack->state != COMP_DERIVED)
1665 gfc_error ("Initialization of pointer at %C is not allowed in "
1666 "a PURE procedure");
1670 /* Match NULL() initilization. */
1671 m = gfc_match_null (init);
1675 /* Match non-NULL initialization. */
1676 gfc_matching_ptr_assignment = !procptr;
1677 gfc_matching_procptr_assignment = procptr;
1678 m = gfc_match_rvalue (init);
1679 gfc_matching_ptr_assignment = 0;
1680 gfc_matching_procptr_assignment = 0;
1681 if (m == MATCH_ERROR)
1683 else if (m == MATCH_NO)
1685 gfc_error ("Error in pointer initialization at %C");
1690 gfc_resolve_expr (*init);
1692 if (gfc_notify_std (GFC_STD_F2008, "Fortran 2008: non-NULL pointer "
1693 "initialization at %C") == FAILURE)
1700 /* Match a variable name with an optional initializer. When this
1701 subroutine is called, a variable is expected to be parsed next.
1702 Depending on what is happening at the moment, updates either the
1703 symbol table or the current interface. */
1706 variable_decl (int elem)
1708 char name[GFC_MAX_SYMBOL_LEN + 1];
1709 gfc_expr *initializer, *char_len;
1711 gfc_array_spec *cp_as; /* Extra copy for Cray Pointees. */
1722 /* When we get here, we've just matched a list of attributes and
1723 maybe a type and a double colon. The next thing we expect to see
1724 is the name of the symbol. */
1725 m = gfc_match_name (name);
1729 var_locus = gfc_current_locus;
1731 /* Now we could see the optional array spec. or character length. */
1732 m = gfc_match_array_spec (&as, true, true);
1733 if (gfc_option.flag_cray_pointer && m == MATCH_YES)
1734 cp_as = gfc_copy_array_spec (as);
1735 else if (m == MATCH_ERROR)
1739 as = gfc_copy_array_spec (current_as);
1740 else if (current_as)
1741 merge_array_spec (current_as, as, true);
1743 /* At this point, we know for sure if the symbol is PARAMETER and can thus
1744 determine (and check) whether it can be implied-shape. If it
1745 was parsed as assumed-size, change it because PARAMETERs can not
1749 if (as->type == AS_IMPLIED_SHAPE && current_attr.flavor != FL_PARAMETER)
1752 gfc_error ("Non-PARAMETER symbol '%s' at %L can't be implied-shape",
1757 if (as->type == AS_ASSUMED_SIZE && as->rank == 1
1758 && current_attr.flavor == FL_PARAMETER)
1759 as->type = AS_IMPLIED_SHAPE;
1761 if (as->type == AS_IMPLIED_SHAPE
1762 && gfc_notify_std (GFC_STD_F2008,
1763 "Fortran 2008: Implied-shape array at %L",
1764 &var_locus) == FAILURE)
1774 if (current_ts.type == BT_CHARACTER)
1776 switch (match_char_length (&char_len))
1779 cl = gfc_new_charlen (gfc_current_ns, NULL);
1781 cl->length = char_len;
1784 /* Non-constant lengths need to be copied after the first
1785 element. Also copy assumed lengths. */
1788 && (current_ts.u.cl->length == NULL
1789 || current_ts.u.cl->length->expr_type != EXPR_CONSTANT))
1791 cl = gfc_new_charlen (gfc_current_ns, NULL);
1792 cl->length = gfc_copy_expr (current_ts.u.cl->length);
1795 cl = current_ts.u.cl;
1804 /* If this symbol has already shown up in a Cray Pointer declaration,
1805 then we want to set the type & bail out. */
1806 if (gfc_option.flag_cray_pointer)
1808 gfc_find_symbol (name, gfc_current_ns, 1, &sym);
1809 if (sym != NULL && sym->attr.cray_pointee)
1811 sym->ts.type = current_ts.type;
1812 sym->ts.kind = current_ts.kind;
1814 sym->ts.u.derived = current_ts.u.derived;
1815 sym->ts.is_c_interop = current_ts.is_c_interop;
1816 sym->ts.is_iso_c = current_ts.is_iso_c;
1819 /* Check to see if we have an array specification. */
1822 if (sym->as != NULL)
1824 gfc_error ("Duplicate array spec for Cray pointee at %C");
1825 gfc_free_array_spec (cp_as);
1831 if (gfc_set_array_spec (sym, cp_as, &var_locus) == FAILURE)
1832 gfc_internal_error ("Couldn't set pointee array spec.");
1834 /* Fix the array spec. */
1835 m = gfc_mod_pointee_as (sym->as);
1836 if (m == MATCH_ERROR)
1844 gfc_free_array_spec (cp_as);
1848 /* Procedure pointer as function result. */
1849 if (gfc_current_state () == COMP_FUNCTION
1850 && strcmp ("ppr@", gfc_current_block ()->name) == 0
1851 && strcmp (name, gfc_current_block ()->ns->proc_name->name) == 0)
1852 strcpy (name, "ppr@");
1854 if (gfc_current_state () == COMP_FUNCTION
1855 && strcmp (name, gfc_current_block ()->name) == 0
1856 && gfc_current_block ()->result
1857 && strcmp ("ppr@", gfc_current_block ()->result->name) == 0)
1858 strcpy (name, "ppr@");
1860 /* OK, we've successfully matched the declaration. Now put the
1861 symbol in the current namespace, because it might be used in the
1862 optional initialization expression for this symbol, e.g. this is
1865 integer, parameter :: i = huge(i)
1867 This is only true for parameters or variables of a basic type.
1868 For components of derived types, it is not true, so we don't
1869 create a symbol for those yet. If we fail to create the symbol,
1871 if (gfc_current_state () != COMP_DERIVED
1872 && build_sym (name, cl, &as, &var_locus) == FAILURE)
1878 /* An interface body specifies all of the procedure's
1879 characteristics and these shall be consistent with those
1880 specified in the procedure definition, except that the interface
1881 may specify a procedure that is not pure if the procedure is
1882 defined to be pure(12.3.2). */
1883 if ((current_ts.type == BT_DERIVED || current_ts.type == BT_CLASS)
1884 && gfc_current_ns->proc_name
1885 && gfc_current_ns->proc_name->attr.if_source == IFSRC_IFBODY
1886 && current_ts.u.derived->ns != gfc_current_ns)
1889 st = gfc_find_symtree (gfc_current_ns->sym_root, current_ts.u.derived->name);
1890 if (!(current_ts.u.derived->attr.imported
1892 && st->n.sym == current_ts.u.derived)
1893 && !gfc_current_ns->has_import_set)
1895 gfc_error ("the type of '%s' at %C has not been declared within the "
1902 /* In functions that have a RESULT variable defined, the function
1903 name always refers to function calls. Therefore, the name is
1904 not allowed to appear in specification statements. */
1905 if (gfc_current_state () == COMP_FUNCTION
1906 && gfc_current_block () != NULL
1907 && gfc_current_block ()->result != NULL
1908 && gfc_current_block ()->result != gfc_current_block ()
1909 && strcmp (gfc_current_block ()->name, name) == 0)
1911 gfc_error ("Function name '%s' not allowed at %C", name);
1916 /* We allow old-style initializations of the form
1917 integer i /2/, j(4) /3*3, 1/
1918 (if no colon has been seen). These are different from data
1919 statements in that initializers are only allowed to apply to the
1920 variable immediately preceding, i.e.
1922 is not allowed. Therefore we have to do some work manually, that
1923 could otherwise be left to the matchers for DATA statements. */
1925 if (!colon_seen && gfc_match (" /") == MATCH_YES)
1927 if (gfc_notify_std (GFC_STD_GNU, "Extension: Old-style "
1928 "initialization at %C") == FAILURE)
1931 return match_old_style_init (name);
1934 /* The double colon must be present in order to have initializers.
1935 Otherwise the statement is ambiguous with an assignment statement. */
1938 if (gfc_match (" =>") == MATCH_YES)
1940 if (!current_attr.pointer)
1942 gfc_error ("Initialization at %C isn't for a pointer variable");
1947 m = match_pointer_init (&initializer, 0);
1951 else if (gfc_match_char ('=') == MATCH_YES)
1953 if (current_attr.pointer)
1955 gfc_error ("Pointer initialization at %C requires '=>', "
1961 m = gfc_match_init_expr (&initializer);
1964 gfc_error ("Expected an initialization expression at %C");
1968 if (current_attr.flavor != FL_PARAMETER && gfc_pure (NULL)
1969 && gfc_state_stack->state != COMP_DERIVED)
1971 gfc_error ("Initialization of variable at %C is not allowed in "
1972 "a PURE procedure");
1981 if (initializer != NULL && current_attr.allocatable
1982 && gfc_current_state () == COMP_DERIVED)
1984 gfc_error ("Initialization of allocatable component at %C is not "
1990 /* Add the initializer. Note that it is fine if initializer is
1991 NULL here, because we sometimes also need to check if a
1992 declaration *must* have an initialization expression. */
1993 if (gfc_current_state () != COMP_DERIVED)
1994 t = add_init_expr_to_sym (name, &initializer, &var_locus);
1997 if (current_ts.type == BT_DERIVED
1998 && !current_attr.pointer && !initializer)
1999 initializer = gfc_default_initializer (¤t_ts);
2000 t = build_struct (name, cl, &initializer, &as);
2003 m = (t == SUCCESS) ? MATCH_YES : MATCH_ERROR;
2006 /* Free stuff up and return. */
2007 gfc_free_expr (initializer);
2008 gfc_free_array_spec (as);
2014 /* Match an extended-f77 "TYPESPEC*bytesize"-style kind specification.
2015 This assumes that the byte size is equal to the kind number for
2016 non-COMPLEX types, and equal to twice the kind number for COMPLEX. */
2019 gfc_match_old_kind_spec (gfc_typespec *ts)
2024 if (gfc_match_char ('*') != MATCH_YES)
2027 m = gfc_match_small_literal_int (&ts->kind, NULL);
2031 original_kind = ts->kind;
2033 /* Massage the kind numbers for complex types. */
2034 if (ts->type == BT_COMPLEX)
2038 gfc_error ("Old-style type declaration %s*%d not supported at %C",
2039 gfc_basic_typename (ts->type), original_kind);
2045 if (gfc_validate_kind (ts->type, ts->kind, true) < 0)
2047 gfc_error ("Old-style type declaration %s*%d not supported at %C",
2048 gfc_basic_typename (ts->type), original_kind);
2052 if (gfc_notify_std (GFC_STD_GNU, "Nonstandard type declaration %s*%d at %C",
2053 gfc_basic_typename (ts->type), original_kind) == FAILURE)
2060 /* Match a kind specification. Since kinds are generally optional, we
2061 usually return MATCH_NO if something goes wrong. If a "kind="
2062 string is found, then we know we have an error. */
2065 gfc_match_kind_spec (gfc_typespec *ts, bool kind_expr_only)
2077 where = loc = gfc_current_locus;
2082 if (gfc_match_char ('(') == MATCH_NO)
2085 /* Also gobbles optional text. */
2086 if (gfc_match (" kind = ") == MATCH_YES)
2089 loc = gfc_current_locus;
2092 n = gfc_match_init_expr (&e);
2096 if (gfc_matching_function)
2098 /* The function kind expression might include use associated or
2099 imported parameters and try again after the specification
2101 if (gfc_match_char (')') != MATCH_YES)
2103 gfc_error ("Missing right parenthesis at %C");
2109 gfc_undo_symbols ();
2114 /* ....or else, the match is real. */
2116 gfc_error ("Expected initialization expression at %C");
2124 gfc_error ("Expected scalar initialization expression at %C");
2129 msg = gfc_extract_int (e, &ts->kind);
2138 /* Before throwing away the expression, let's see if we had a
2139 C interoperable kind (and store the fact). */
2140 if (e->ts.is_c_interop == 1)
2142 /* Mark this as c interoperable if being declared with one
2143 of the named constants from iso_c_binding. */
2144 ts->is_c_interop = e->ts.is_iso_c;
2145 ts->f90_type = e->ts.f90_type;
2151 /* Ignore errors to this point, if we've gotten here. This means
2152 we ignore the m=MATCH_ERROR from above. */
2153 if (gfc_validate_kind (ts->type, ts->kind, true) < 0)
2155 gfc_error ("Kind %d not supported for type %s at %C", ts->kind,
2156 gfc_basic_typename (ts->type));
2157 gfc_current_locus = where;
2161 /* Warn if, e.g., c_int is used for a REAL variable, but not
2162 if, e.g., c_double is used for COMPLEX as the standard
2163 explicitly says that the kind type parameter for complex and real
2164 variable is the same, i.e. c_float == c_float_complex. */
2165 if (ts->f90_type != BT_UNKNOWN && ts->f90_type != ts->type
2166 && !((ts->f90_type == BT_REAL && ts->type == BT_COMPLEX)
2167 || (ts->f90_type == BT_COMPLEX && ts->type == BT_REAL)))
2168 gfc_warning_now ("C kind type parameter is for type %s but type at %L "
2169 "is %s", gfc_basic_typename (ts->f90_type), &where,
2170 gfc_basic_typename (ts->type));
2172 gfc_gobble_whitespace ();
2173 if ((c = gfc_next_ascii_char ()) != ')'
2174 && (ts->type != BT_CHARACTER || c != ','))
2176 if (ts->type == BT_CHARACTER)
2177 gfc_error ("Missing right parenthesis or comma at %C");
2179 gfc_error ("Missing right parenthesis at %C");
2183 /* All tests passed. */
2186 if(m == MATCH_ERROR)
2187 gfc_current_locus = where;
2189 /* Return what we know from the test(s). */
2194 gfc_current_locus = where;
2200 match_char_kind (int * kind, int * is_iso_c)
2209 where = gfc_current_locus;
2211 n = gfc_match_init_expr (&e);
2213 if (n != MATCH_YES && gfc_matching_function)
2215 /* The expression might include use-associated or imported
2216 parameters and try again after the specification
2219 gfc_undo_symbols ();
2224 gfc_error ("Expected initialization expression at %C");
2230 gfc_error ("Expected scalar initialization expression at %C");
2235 msg = gfc_extract_int (e, kind);
2236 *is_iso_c = e->ts.is_iso_c;
2246 /* Ignore errors to this point, if we've gotten here. This means
2247 we ignore the m=MATCH_ERROR from above. */
2248 if (gfc_validate_kind (BT_CHARACTER, *kind, true) < 0)
2250 gfc_error ("Kind %d is not supported for CHARACTER at %C", *kind);
2254 /* All tests passed. */
2257 if (m == MATCH_ERROR)
2258 gfc_current_locus = where;
2260 /* Return what we know from the test(s). */
2265 gfc_current_locus = where;
2270 /* Match the various kind/length specifications in a CHARACTER
2271 declaration. We don't return MATCH_NO. */
2274 gfc_match_char_spec (gfc_typespec *ts)
2276 int kind, seen_length, is_iso_c;
2286 /* Try the old-style specification first. */
2287 old_char_selector = 0;
2289 m = match_char_length (&len);
2293 old_char_selector = 1;
2298 m = gfc_match_char ('(');
2301 m = MATCH_YES; /* Character without length is a single char. */
2305 /* Try the weird case: ( KIND = <int> [ , LEN = <len-param> ] ). */
2306 if (gfc_match (" kind =") == MATCH_YES)
2308 m = match_char_kind (&kind, &is_iso_c);
2310 if (m == MATCH_ERROR)
2315 if (gfc_match (" , len =") == MATCH_NO)
2318 m = char_len_param_value (&len);
2321 if (m == MATCH_ERROR)
2328 /* Try to match "LEN = <len-param>" or "LEN = <len-param>, KIND = <int>". */
2329 if (gfc_match (" len =") == MATCH_YES)
2331 m = char_len_param_value (&len);
2334 if (m == MATCH_ERROR)
2338 if (gfc_match_char (')') == MATCH_YES)
2341 if (gfc_match (" , kind =") != MATCH_YES)
2344 if (match_char_kind (&kind, &is_iso_c) == MATCH_ERROR)
2350 /* Try to match ( <len-param> ) or ( <len-param> , [ KIND = ] <int> ). */
2351 m = char_len_param_value (&len);
2354 if (m == MATCH_ERROR)
2358 m = gfc_match_char (')');
2362 if (gfc_match_char (',') != MATCH_YES)
2365 gfc_match (" kind ="); /* Gobble optional text. */
2367 m = match_char_kind (&kind, &is_iso_c);
2368 if (m == MATCH_ERROR)
2374 /* Require a right-paren at this point. */
2375 m = gfc_match_char (')');
2380 gfc_error ("Syntax error in CHARACTER declaration at %C");
2382 gfc_free_expr (len);
2386 /* Deal with character functions after USE and IMPORT statements. */
2387 if (gfc_matching_function)
2389 gfc_free_expr (len);
2390 gfc_undo_symbols ();
2396 gfc_free_expr (len);
2400 /* Do some final massaging of the length values. */
2401 cl = gfc_new_charlen (gfc_current_ns, NULL);
2403 if (seen_length == 0)
2404 cl->length = gfc_get_int_expr (gfc_default_integer_kind, NULL, 1);
2409 ts->kind = kind == 0 ? gfc_default_character_kind : kind;
2411 /* We have to know if it was a c interoperable kind so we can
2412 do accurate type checking of bind(c) procs, etc. */
2414 /* Mark this as c interoperable if being declared with one
2415 of the named constants from iso_c_binding. */
2416 ts->is_c_interop = is_iso_c;
2417 else if (len != NULL)
2418 /* Here, we might have parsed something such as: character(c_char)
2419 In this case, the parsing code above grabs the c_char when
2420 looking for the length (line 1690, roughly). it's the last
2421 testcase for parsing the kind params of a character variable.
2422 However, it's not actually the length. this seems like it
2424 To see if the user used a C interop kind, test the expr
2425 of the so called length, and see if it's C interoperable. */
2426 ts->is_c_interop = len->ts.is_iso_c;
2432 /* Matches a declaration-type-spec (F03:R502). If successful, sets the ts
2433 structure to the matched specification. This is necessary for FUNCTION and
2434 IMPLICIT statements.
2436 If implicit_flag is nonzero, then we don't check for the optional
2437 kind specification. Not doing so is needed for matching an IMPLICIT
2438 statement correctly. */
2441 gfc_match_decl_type_spec (gfc_typespec *ts, int implicit_flag)
2443 char name[GFC_MAX_SYMBOL_LEN + 1];
2447 bool seen_deferred_kind, matched_type;
2449 /* A belt and braces check that the typespec is correctly being treated
2450 as a deferred characteristic association. */
2451 seen_deferred_kind = (gfc_current_state () == COMP_FUNCTION)
2452 && (gfc_current_block ()->result->ts.kind == -1)
2453 && (ts->kind == -1);
2455 if (seen_deferred_kind)
2458 /* Clear the current binding label, in case one is given. */
2459 curr_binding_label[0] = '\0';
2461 if (gfc_match (" byte") == MATCH_YES)
2463 if (gfc_notify_std (GFC_STD_GNU, "Extension: BYTE type at %C")
2467 if (gfc_validate_kind (BT_INTEGER, 1, true) < 0)
2469 gfc_error ("BYTE type used at %C "
2470 "is not available on the target machine");
2474 ts->type = BT_INTEGER;
2480 m = gfc_match (" type ( %n", name);
2481 matched_type = (m == MATCH_YES);
2483 if ((matched_type && strcmp ("integer", name) == 0)
2484 || (!matched_type && gfc_match (" integer") == MATCH_YES))
2486 ts->type = BT_INTEGER;
2487 ts->kind = gfc_default_integer_kind;
2491 if ((matched_type && strcmp ("character", name) == 0)
2492 || (!matched_type && gfc_match (" character") == MATCH_YES))
2495 && gfc_notify_std (GFC_STD_F2008, "Fortran 2008: TYPE with "
2496 "intrinsic-type-spec at %C") == FAILURE)
2499 ts->type = BT_CHARACTER;
2500 if (implicit_flag == 0)
2501 m = gfc_match_char_spec (ts);
2505 if (matched_type && m == MATCH_YES && gfc_match_char (')') != MATCH_YES)
2511 if ((matched_type && strcmp ("real", name) == 0)
2512 || (!matched_type && gfc_match (" real") == MATCH_YES))
2515 ts->kind = gfc_default_real_kind;
2520 && (strcmp ("doubleprecision", name) == 0
2521 || (strcmp ("double", name) == 0
2522 && gfc_match (" precision") == MATCH_YES)))
2523 || (!matched_type && gfc_match (" double precision") == MATCH_YES))
2526 && gfc_notify_std (GFC_STD_F2008, "Fortran 2008: TYPE with "
2527 "intrinsic-type-spec at %C") == FAILURE)
2529 if (matched_type && gfc_match_char (')') != MATCH_YES)
2533 ts->kind = gfc_default_double_kind;
2537 if ((matched_type && strcmp ("complex", name) == 0)
2538 || (!matched_type && gfc_match (" complex") == MATCH_YES))
2540 ts->type = BT_COMPLEX;
2541 ts->kind = gfc_default_complex_kind;
2546 && (strcmp ("doublecomplex", name) == 0
2547 || (strcmp ("double", name) == 0
2548 && gfc_match (" complex") == MATCH_YES)))
2549 || (!matched_type && gfc_match (" double complex") == MATCH_YES))
2551 if (gfc_notify_std (GFC_STD_GNU, "Extension: DOUBLE COMPLEX at %C")
2556 && gfc_notify_std (GFC_STD_F2008, "Fortran 2008: TYPE with "
2557 "intrinsic-type-spec at %C") == FAILURE)
2560 if (matched_type && gfc_match_char (')') != MATCH_YES)
2563 ts->type = BT_COMPLEX;
2564 ts->kind = gfc_default_double_kind;
2568 if ((matched_type && strcmp ("logical", name) == 0)
2569 || (!matched_type && gfc_match (" logical") == MATCH_YES))
2571 ts->type = BT_LOGICAL;
2572 ts->kind = gfc_default_logical_kind;
2577 m = gfc_match_char (')');
2580 ts->type = BT_DERIVED;
2583 m = gfc_match (" class ( %n )", name);
2586 ts->type = BT_CLASS;
2588 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: CLASS statement at %C")
2593 /* Defer association of the derived type until the end of the
2594 specification block. However, if the derived type can be
2595 found, add it to the typespec. */
2596 if (gfc_matching_function)
2598 ts->u.derived = NULL;
2599 if (gfc_current_state () != COMP_INTERFACE
2600 && !gfc_find_symbol (name, NULL, 1, &sym) && sym)
2601 ts->u.derived = sym;
2605 /* Search for the name but allow the components to be defined later. If
2606 type = -1, this typespec has been seen in a function declaration but
2607 the type could not be accessed at that point. */
2609 if (ts->kind != -1 && gfc_get_ha_symbol (name, &sym))
2611 gfc_error ("Type name '%s' at %C is ambiguous", name);
2614 else if (ts->kind == -1)
2616 int iface = gfc_state_stack->previous->state != COMP_INTERFACE
2617 || gfc_current_ns->has_import_set;
2618 if (gfc_find_symbol (name, NULL, iface, &sym))
2620 gfc_error ("Type name '%s' at %C is ambiguous", name);
2629 if (sym->attr.flavor != FL_DERIVED
2630 && gfc_add_flavor (&sym->attr, FL_DERIVED, sym->name, NULL) == FAILURE)
2633 gfc_set_sym_referenced (sym);
2634 ts->u.derived = sym;
2640 && gfc_notify_std (GFC_STD_F2008, "Fortran 2008: TYPE with "
2641 "intrinsic-type-spec at %C") == FAILURE)
2644 /* For all types except double, derived and character, look for an
2645 optional kind specifier. MATCH_NO is actually OK at this point. */
2646 if (implicit_flag == 1)
2648 if (matched_type && gfc_match_char (')') != MATCH_YES)
2654 if (gfc_current_form == FORM_FREE)
2656 c = gfc_peek_ascii_char ();
2657 if (!gfc_is_whitespace (c) && c != '*' && c != '('
2658 && c != ':' && c != ',')
2660 if (matched_type && c == ')')
2662 gfc_next_ascii_char ();
2669 m = gfc_match_kind_spec (ts, false);
2670 if (m == MATCH_NO && ts->type != BT_CHARACTER)
2671 m = gfc_match_old_kind_spec (ts);
2673 if (matched_type && gfc_match_char (')') != MATCH_YES)
2676 /* Defer association of the KIND expression of function results
2677 until after USE and IMPORT statements. */
2678 if ((gfc_current_state () == COMP_NONE && gfc_error_flag_test ())
2679 || gfc_matching_function)
2683 m = MATCH_YES; /* No kind specifier found. */
2689 /* Match an IMPLICIT NONE statement. Actually, this statement is
2690 already matched in parse.c, or we would not end up here in the
2691 first place. So the only thing we need to check, is if there is
2692 trailing garbage. If not, the match is successful. */
2695 gfc_match_implicit_none (void)
2697 return (gfc_match_eos () == MATCH_YES) ? MATCH_YES : MATCH_NO;
2701 /* Match the letter range(s) of an IMPLICIT statement. */
2704 match_implicit_range (void)
2710 cur_loc = gfc_current_locus;
2712 gfc_gobble_whitespace ();
2713 c = gfc_next_ascii_char ();
2716 gfc_error ("Missing character range in IMPLICIT at %C");
2723 gfc_gobble_whitespace ();
2724 c1 = gfc_next_ascii_char ();
2728 gfc_gobble_whitespace ();
2729 c = gfc_next_ascii_char ();
2734 inner = 0; /* Fall through. */
2741 gfc_gobble_whitespace ();
2742 c2 = gfc_next_ascii_char ();
2746 gfc_gobble_whitespace ();
2747 c = gfc_next_ascii_char ();
2749 if ((c != ',') && (c != ')'))
2762 gfc_error ("Letters must be in alphabetic order in "
2763 "IMPLICIT statement at %C");
2767 /* See if we can add the newly matched range to the pending
2768 implicits from this IMPLICIT statement. We do not check for
2769 conflicts with whatever earlier IMPLICIT statements may have
2770 set. This is done when we've successfully finished matching
2772 if (gfc_add_new_implicit_range (c1, c2) != SUCCESS)
2779 gfc_syntax_error (ST_IMPLICIT);
2781 gfc_current_locus = cur_loc;
2786 /* Match an IMPLICIT statement, storing the types for
2787 gfc_set_implicit() if the statement is accepted by the parser.
2788 There is a strange looking, but legal syntactic construction
2789 possible. It looks like:
2791 IMPLICIT INTEGER (a-b) (c-d)
2793 This is legal if "a-b" is a constant expression that happens to
2794 equal one of the legal kinds for integers. The real problem
2795 happens with an implicit specification that looks like:
2797 IMPLICIT INTEGER (a-b)
2799 In this case, a typespec matcher that is "greedy" (as most of the
2800 matchers are) gobbles the character range as a kindspec, leaving
2801 nothing left. We therefore have to go a bit more slowly in the
2802 matching process by inhibiting the kindspec checking during
2803 typespec matching and checking for a kind later. */
2806 gfc_match_implicit (void)
2815 /* We don't allow empty implicit statements. */
2816 if (gfc_match_eos () == MATCH_YES)
2818 gfc_error ("Empty IMPLICIT statement at %C");
2824 /* First cleanup. */
2825 gfc_clear_new_implicit ();
2827 /* A basic type is mandatory here. */
2828 m = gfc_match_decl_type_spec (&ts, 1);
2829 if (m == MATCH_ERROR)
2834 cur_loc = gfc_current_locus;
2835 m = match_implicit_range ();
2839 /* We may have <TYPE> (<RANGE>). */
2840 gfc_gobble_whitespace ();
2841 c = gfc_next_ascii_char ();
2842 if ((c == '\n') || (c == ','))
2844 /* Check for CHARACTER with no length parameter. */
2845 if (ts.type == BT_CHARACTER && !ts.u.cl)
2847 ts.kind = gfc_default_character_kind;
2848 ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
2849 ts.u.cl->length = gfc_get_int_expr (gfc_default_integer_kind,
2853 /* Record the Successful match. */
2854 if (gfc_merge_new_implicit (&ts) != SUCCESS)
2859 gfc_current_locus = cur_loc;
2862 /* Discard the (incorrectly) matched range. */
2863 gfc_clear_new_implicit ();
2865 /* Last chance -- check <TYPE> <SELECTOR> (<RANGE>). */
2866 if (ts.type == BT_CHARACTER)
2867 m = gfc_match_char_spec (&ts);
2870 m = gfc_match_kind_spec (&ts, false);
2873 m = gfc_match_old_kind_spec (&ts);
2874 if (m == MATCH_ERROR)
2880 if (m == MATCH_ERROR)
2883 m = match_implicit_range ();
2884 if (m == MATCH_ERROR)
2889 gfc_gobble_whitespace ();
2890 c = gfc_next_ascii_char ();
2891 if ((c != '\n') && (c != ','))
2894 if (gfc_merge_new_implicit (&ts) != SUCCESS)
2902 gfc_syntax_error (ST_IMPLICIT);
2910 gfc_match_import (void)
2912 char name[GFC_MAX_SYMBOL_LEN + 1];
2917 if (gfc_current_ns->proc_name == NULL
2918 || gfc_current_ns->proc_name->attr.if_source != IFSRC_IFBODY)
2920 gfc_error ("IMPORT statement at %C only permitted in "
2921 "an INTERFACE body");
2925 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: IMPORT statement at %C")
2929 if (gfc_match_eos () == MATCH_YES)
2931 /* All host variables should be imported. */
2932 gfc_current_ns->has_import_set = 1;
2936 if (gfc_match (" ::") == MATCH_YES)
2938 if (gfc_match_eos () == MATCH_YES)
2940 gfc_error ("Expecting list of named entities at %C");
2947 m = gfc_match (" %n", name);
2951 if (gfc_current_ns->parent != NULL
2952 && gfc_find_symbol (name, gfc_current_ns->parent, 1, &sym))
2954 gfc_error ("Type name '%s' at %C is ambiguous", name);
2957 else if (gfc_current_ns->proc_name->ns->parent != NULL
2958 && gfc_find_symbol (name,
2959 gfc_current_ns->proc_name->ns->parent,
2962 gfc_error ("Type name '%s' at %C is ambiguous", name);
2968 gfc_error ("Cannot IMPORT '%s' from host scoping unit "
2969 "at %C - does not exist.", name);
2973 if (gfc_find_symtree (gfc_current_ns->sym_root,name))
2975 gfc_warning ("'%s' is already IMPORTed from host scoping unit "
2980 st = gfc_new_symtree (&gfc_current_ns->sym_root, sym->name);
2983 sym->attr.imported = 1;
2995 if (gfc_match_eos () == MATCH_YES)
2997 if (gfc_match_char (',') != MATCH_YES)
3004 gfc_error ("Syntax error in IMPORT statement at %C");
3009 /* A minimal implementation of gfc_match without whitespace, escape
3010 characters or variable arguments. Returns true if the next
3011 characters match the TARGET template exactly. */
3014 match_string_p (const char *target)
3018 for (p = target; *p; p++)
3019 if ((char) gfc_next_ascii_char () != *p)
3024 /* Matches an attribute specification including array specs. If
3025 successful, leaves the variables current_attr and current_as
3026 holding the specification. Also sets the colon_seen variable for
3027 later use by matchers associated with initializations.
3029 This subroutine is a little tricky in the sense that we don't know
3030 if we really have an attr-spec until we hit the double colon.
3031 Until that time, we can only return MATCH_NO. This forces us to
3032 check for duplicate specification at this level. */
3035 match_attr_spec (void)
3037 /* Modifiers that can exist in a type statement. */
3039 { GFC_DECL_BEGIN = 0,
3040 DECL_ALLOCATABLE = GFC_DECL_BEGIN, DECL_DIMENSION, DECL_EXTERNAL,
3041 DECL_IN, DECL_OUT, DECL_INOUT, DECL_INTRINSIC, DECL_OPTIONAL,
3042 DECL_PARAMETER, DECL_POINTER, DECL_PROTECTED, DECL_PRIVATE,
3043 DECL_PUBLIC, DECL_SAVE, DECL_TARGET, DECL_VALUE, DECL_VOLATILE,
3044 DECL_IS_BIND_C, DECL_CODIMENSION, DECL_ASYNCHRONOUS, DECL_CONTIGUOUS,
3045 DECL_NONE, GFC_DECL_END /* Sentinel */
3049 /* GFC_DECL_END is the sentinel, index starts at 0. */
3050 #define NUM_DECL GFC_DECL_END
3052 locus start, seen_at[NUM_DECL];
3059 gfc_clear_attr (¤t_attr);
3060 start = gfc_current_locus;
3065 /* See if we get all of the keywords up to the final double colon. */
3066 for (d = GFC_DECL_BEGIN; d != GFC_DECL_END; d++)
3074 gfc_gobble_whitespace ();
3076 ch = gfc_next_ascii_char ();
3079 /* This is the successful exit condition for the loop. */
3080 if (gfc_next_ascii_char () == ':')
3085 gfc_gobble_whitespace ();
3086 switch (gfc_peek_ascii_char ())
3089 gfc_next_ascii_char ();
3090 switch (gfc_next_ascii_char ())
3093 if (match_string_p ("locatable"))
3095 /* Matched "allocatable". */
3096 d = DECL_ALLOCATABLE;
3101 if (match_string_p ("ynchronous"))
3103 /* Matched "asynchronous". */
3104 d = DECL_ASYNCHRONOUS;
3111 /* Try and match the bind(c). */
3112 m = gfc_match_bind_c (NULL, true);
3115 else if (m == MATCH_ERROR)
3120 gfc_next_ascii_char ();
3121 if ('o' != gfc_next_ascii_char ())
3123 switch (gfc_next_ascii_char ())
3126 if (match_string_p ("imension"))
3128 d = DECL_CODIMENSION;
3132 if (match_string_p ("tiguous"))
3134 d = DECL_CONTIGUOUS;
3141 if (match_string_p ("dimension"))
3146 if (match_string_p ("external"))
3151 if (match_string_p ("int"))
3153 ch = gfc_next_ascii_char ();
3156 if (match_string_p ("nt"))
3158 /* Matched "intent". */
3159 /* TODO: Call match_intent_spec from here. */
3160 if (gfc_match (" ( in out )") == MATCH_YES)
3162 else if (gfc_match (" ( in )") == MATCH_YES)
3164 else if (gfc_match (" ( out )") == MATCH_YES)
3170 if (match_string_p ("insic"))
3172 /* Matched "intrinsic". */
3180 if (match_string_p ("optional"))
3185 gfc_next_ascii_char ();
3186 switch (gfc_next_ascii_char ())
3189 if (match_string_p ("rameter"))
3191 /* Matched "parameter". */
3197 if (match_string_p ("inter"))
3199 /* Matched "pointer". */
3205 ch = gfc_next_ascii_char ();
3208 if (match_string_p ("vate"))
3210 /* Matched "private". */
3216 if (match_string_p ("tected"))
3218 /* Matched "protected". */
3225 if (match_string_p ("blic"))
3227 /* Matched "public". */
3235 if (match_string_p ("save"))
3240 if (match_string_p ("target"))
3245 gfc_next_ascii_char ();
3246 ch = gfc_next_ascii_char ();
3249 if (match_string_p ("lue"))
3251 /* Matched "value". */
3257 if (match_string_p ("latile"))
3259 /* Matched "volatile". */
3267 /* No double colon and no recognizable decl_type, so assume that
3268 we've been looking at something else the whole time. */
3275 /* Check to make sure any parens are paired up correctly. */
3276 if (gfc_match_parens () == MATCH_ERROR)
3283 seen_at[d] = gfc_current_locus;
3285 if (d == DECL_DIMENSION || d == DECL_CODIMENSION)
3287 gfc_array_spec *as = NULL;
3289 m = gfc_match_array_spec (&as, d == DECL_DIMENSION,
3290 d == DECL_CODIMENSION);
3292 if (current_as == NULL)
3294 else if (m == MATCH_YES)
3296 merge_array_spec (as, current_as, false);
3302 if (d == DECL_CODIMENSION)
3303 gfc_error ("Missing codimension specification at %C");
3305 gfc_error ("Missing dimension specification at %C");
3309 if (m == MATCH_ERROR)
3314 /* Since we've seen a double colon, we have to be looking at an
3315 attr-spec. This means that we can now issue errors. */
3316 for (d = GFC_DECL_BEGIN; d != GFC_DECL_END; d++)
3321 case DECL_ALLOCATABLE:
3322 attr = "ALLOCATABLE";
3324 case DECL_ASYNCHRONOUS:
3325 attr = "ASYNCHRONOUS";
3327 case DECL_CODIMENSION:
3328 attr = "CODIMENSION";
3330 case DECL_CONTIGUOUS:
3331 attr = "CONTIGUOUS";
3333 case DECL_DIMENSION:
3340 attr = "INTENT (IN)";
3343 attr = "INTENT (OUT)";
3346 attr = "INTENT (IN OUT)";
3348 case DECL_INTRINSIC:
3354 case DECL_PARAMETER:
3360 case DECL_PROTECTED:
3375 case DECL_IS_BIND_C:
3385 attr = NULL; /* This shouldn't happen. */
3388 gfc_error ("Duplicate %s attribute at %L", attr, &seen_at[d]);
3393 /* Now that we've dealt with duplicate attributes, add the attributes
3394 to the current attribute. */
3395 for (d = GFC_DECL_BEGIN; d != GFC_DECL_END; d++)
3400 if (gfc_current_state () == COMP_DERIVED
3401 && d != DECL_DIMENSION && d != DECL_CODIMENSION
3402 && d != DECL_POINTER && d != DECL_PRIVATE
3403 && d != DECL_PUBLIC && d != DECL_CONTIGUOUS && d != DECL_NONE)
3405 if (d == DECL_ALLOCATABLE)
3407 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: ALLOCATABLE "
3408 "attribute at %C in a TYPE definition")
3417 gfc_error ("Attribute at %L is not allowed in a TYPE definition",
3424 if ((d == DECL_PRIVATE || d == DECL_PUBLIC)
3425 && gfc_current_state () != COMP_MODULE)
3427 if (d == DECL_PRIVATE)
3431 if (gfc_current_state () == COMP_DERIVED
3432 && gfc_state_stack->previous
3433 && gfc_state_stack->previous->state == COMP_MODULE)
3435 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Attribute %s "
3436 "at %L in a TYPE definition", attr,
3446 gfc_error ("%s attribute at %L is not allowed outside of the "
3447 "specification part of a module", attr, &seen_at[d]);
3455 case DECL_ALLOCATABLE:
3456 t = gfc_add_allocatable (¤t_attr, &seen_at[d]);
3459 case DECL_ASYNCHRONOUS:
3460 if (gfc_notify_std (GFC_STD_F2003,
3461 "Fortran 2003: ASYNCHRONOUS attribute at %C")
3465 t = gfc_add_asynchronous (¤t_attr, NULL, &seen_at[d]);
3468 case DECL_CODIMENSION:
3469 t = gfc_add_codimension (¤t_attr, NULL, &seen_at[d]);
3472 case DECL_CONTIGUOUS:
3473 if (gfc_notify_std (GFC_STD_F2008,
3474 "Fortran 2008: CONTIGUOUS attribute at %C")
3478 t = gfc_add_contiguous (¤t_attr, NULL, &seen_at[d]);
3481 case DECL_DIMENSION:
3482 t = gfc_add_dimension (¤t_attr, NULL, &seen_at[d]);
3486 t = gfc_add_external (¤t_attr, &seen_at[d]);
3490 t = gfc_add_intent (¤t_attr, INTENT_IN, &seen_at[d]);
3494 t = gfc_add_intent (¤t_attr, INTENT_OUT, &seen_at[d]);
3498 t = gfc_add_intent (¤t_attr, INTENT_INOUT, &seen_at[d]);
3501 case DECL_INTRINSIC:
3502 t = gfc_add_intrinsic (¤t_attr, &seen_at[d]);
3506 t = gfc_add_optional (¤t_attr, &seen_at[d]);
3509 case DECL_PARAMETER:
3510 t = gfc_add_flavor (¤t_attr, FL_PARAMETER, NULL, &seen_at[d]);
3514 t = gfc_add_pointer (¤t_attr, &seen_at[d]);
3517 case DECL_PROTECTED:
3518 if (gfc_current_ns->proc_name->attr.flavor != FL_MODULE)
3520 gfc_error ("PROTECTED at %C only allowed in specification "
3521 "part of a module");
3526 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PROTECTED "
3531 t = gfc_add_protected (¤t_attr, NULL, &seen_at[d]);
3535 t = gfc_add_access (¤t_attr, ACCESS_PRIVATE, NULL,
3540 t = gfc_add_access (¤t_attr, ACCESS_PUBLIC, NULL,
3545 t = gfc_add_save (¤t_attr, SAVE_EXPLICIT, NULL, &seen_at[d]);
3549 t = gfc_add_target (¤t_attr, &seen_at[d]);
3552 case DECL_IS_BIND_C:
3553 t = gfc_add_is_bind_c(¤t_attr, NULL, &seen_at[d], 0);
3557 if (gfc_notify_std (GFC_STD_F2003, "Fortran 2003: VALUE attribute "
3562 t = gfc_add_value (¤t_attr, NULL, &seen_at[d]);
3566 if (gfc_notify_std (GFC_STD_F2003,
3567 "Fortran 2003: VOLATILE attribute at %C")
3571 t = gfc_add_volatile (¤t_attr, NULL, &seen_at[d]);
3575 gfc_internal_error ("match_attr_spec(): Bad attribute");
3585 /* Module variables implicitly have the SAVE attribute. */
3586 if (gfc_current_state () == COMP_MODULE && !current_attr.save)
3587 current_attr.save = SAVE_IMPLICIT;
3593 gfc_current_locus = start;
3594 gfc_free_array_spec (current_as);
3600 /* Set the binding label, dest_label, either with the binding label
3601 stored in the given gfc_typespec, ts, or if none was provided, it
3602 will be the symbol name in all lower case, as required by the draft
3603 (J3/04-007, section 15.4.1). If a binding label was given and
3604 there is more than one argument (num_idents), it is an error. */
3607 set_binding_label (char *dest_label, const char *sym_name, int num_idents)
3609 if (num_idents > 1 && has_name_equals)
3611 gfc_error ("Multiple identifiers provided with "
3612 "single NAME= specifier at %C");
3616 if (curr_binding_label[0] != '\0')
3618 /* Binding label given; store in temp holder til have sym. */
3619 strcpy (dest_label, curr_binding_label);
3623 /* No binding label given, and the NAME= specifier did not exist,
3624 which means there was no NAME="". */
3625 if (sym_name != NULL && has_name_equals == 0)
3626 strcpy (dest_label, sym_name);
3633 /* Set the status of the given common block as being BIND(C) or not,
3634 depending on the given parameter, is_bind_c. */
3637 set_com_block_bind_c (gfc_common_head *com_block, int is_bind_c)
3639 com_block->is_bind_c = is_bind_c;
3644 /* Verify that the given gfc_typespec is for a C interoperable type. */
3647 verify_c_interop (gfc_typespec *ts)
3649 if (ts->type == BT_DERIVED && ts->u.derived != NULL)
3650 return (ts->u.derived->ts.is_c_interop || ts->u.derived->attr.is_bind_c)
3651 ? SUCCESS : FAILURE;
3652 else if (ts->is_c_interop != 1)
3659 /* Verify that the variables of a given common block, which has been
3660 defined with the attribute specifier bind(c), to be of a C
3661 interoperable type. Errors will be reported here, if
3665 verify_com_block_vars_c_interop (gfc_common_head *com_block)
3667 gfc_symbol *curr_sym = NULL;
3668 gfc_try retval = SUCCESS;
3670 curr_sym = com_block->head;
3672 /* Make sure we have at least one symbol. */
3673 if (curr_sym == NULL)
3676 /* Here we know we have a symbol, so we'll execute this loop
3680 /* The second to last param, 1, says this is in a common block. */
3681 retval = verify_bind_c_sym (curr_sym, &(curr_sym->ts), 1, com_block);
3682 curr_sym = curr_sym->common_next;
3683 } while (curr_sym != NULL);
3689 /* Verify that a given BIND(C) symbol is C interoperable. If it is not,
3690 an appropriate error message is reported. */
3693 verify_bind_c_sym (gfc_symbol *tmp_sym, gfc_typespec *ts,
3694 int is_in_common, gfc_common_head *com_block)
3696 bool bind_c_function = false;
3697 gfc_try retval = SUCCESS;
3699 if (tmp_sym->attr.function && tmp_sym->attr.is_bind_c)
3700 bind_c_function = true;
3702 if (tmp_sym->attr.function && tmp_sym->result != NULL)
3704 tmp_sym = tmp_sym->result;
3705 /* Make sure it wasn't an implicitly typed result. */
3706 if (tmp_sym->attr.implicit_type)
3708 gfc_warning ("Implicitly declared BIND(C) function '%s' at "
3709 "%L may not be C interoperable", tmp_sym->name,
3710 &tmp_sym->declared_at);
3711 tmp_sym->ts.f90_type = tmp_sym->ts.type;
3712 /* Mark it as C interoperable to prevent duplicate warnings. */
3713 tmp_sym->ts.is_c_interop = 1;
3714 tmp_sym->attr.is_c_interop = 1;
3718 /* Here, we know we have the bind(c) attribute, so if we have
3719 enough type info, then verify that it's a C interop kind.
3720 The info could be in the symbol already, or possibly still in
3721 the given ts (current_ts), so look in both. */
3722 if (tmp_sym->ts.type != BT_UNKNOWN || ts->type != BT_UNKNOWN)
3724 if (verify_c_interop (&(tmp_sym->ts)) != SUCCESS)
3726 /* See if we're dealing with a sym in a common block or not. */
3727 if (is_in_common == 1)
3729 gfc_warning ("Variable '%s' in common block '%s' at %L "
3730 "may not be a C interoperable "
3731 "kind though common block '%s' is BIND(C)",
3732 tmp_sym->name, com_block->name,
3733 &(tmp_sym->declared_at), com_block->name);
3737 if (tmp_sym->ts.type == BT_DERIVED || ts->type == BT_DERIVED)
3738 gfc_error ("Type declaration '%s' at %L is not C "
3739 "interoperable but it is BIND(C)",
3740 tmp_sym->name, &(tmp_sym->declared_at));
3742 gfc_warning ("Variable '%s' at %L "
3743 "may not be a C interoperable "
3744 "kind but it is bind(c)",
3745 tmp_sym->name, &(tmp_sym->declared_at));
3749 /* Variables declared w/in a common block can't be bind(c)
3750 since there's no way for C to see these variables, so there's
3751 semantically no reason for the attribute. */
3752 if (is_in_common == 1 && tmp_sym->attr.is_bind_c == 1)
3754 gfc_error ("Variable '%s' in common block '%s' at "
3755 "%L cannot be declared with BIND(C) "
3756 "since it is not a global",
3757 tmp_sym->name, com_block->name,
3758 &(tmp_sym->declared_at));
3762 /* Scalar variables that are bind(c) can not have the pointer
3763 or allocatable attributes. */
3764 if (tmp_sym->attr.is_bind_c == 1)
3766 if (tmp_sym->attr.pointer == 1)
3768 gfc_error ("Variable '%s' at %L cannot have both the "
3769 "POINTER and BIND(C) attributes",
3770 tmp_sym->name, &(tmp_sym->declared_at));
3774 if (tmp_sym->attr.allocatable == 1)
3776 gfc_error ("Variable '%s' at %L cannot have both the "
3777 "ALLOCATABLE and BIND(C) attributes",
3778 tmp_sym->name, &(tmp_sym->declared_at));
3784 /* If it is a BIND(C) function, make sure the return value is a
3785 scalar value. The previous tests in this function made sure
3786 the type is interoperable. */
3787 if (bind_c_function && tmp_sym->as != NULL)
3788 gfc_error ("Return type of BIND(C) function '%s' at %L cannot "
3789 "be an array", tmp_sym->name, &(tmp_sym->declared_at));
3791 /* BIND(C) functions can not return a character string. */
3792 if (bind_c_function && tmp_sym->ts.type == BT_CHARACTER)
3793 if (tmp_sym->ts.u.cl == NULL || tmp_sym->ts.u.cl->length == NULL
3794 || tmp_sym->ts.u.cl->length->expr_type != EXPR_CONSTANT
3795 || mpz_cmp_si (tmp_sym->ts.u.cl->length->value.integer, 1) != 0)
3796 gfc_error ("Return type of BIND(C) function '%s' at %L cannot "
3797 "be a character string", tmp_sym->name,
3798 &(tmp_sym->declared_at));
3801 /* See if the symbol has been marked as private. If it has, make sure
3802 there is no binding label and warn the user if there is one. */
3803 if (tmp_sym->attr.access == ACCESS_PRIVATE
3804 && tmp_sym->binding_label[0] != '\0')
3805 /* Use gfc_warning_now because we won't say that the symbol fails
3806 just because of this. */
3807 gfc_warning_now ("Symbol '%s' at %L is marked PRIVATE but has been "
3808 "given the binding label '%s'", tmp_sym->name,
3809 &(tmp_sym->declared_at), tmp_sym->binding_label);
3815 /* Set the appropriate fields for a symbol that's been declared as
3816 BIND(C) (the is_bind_c flag and the binding label), and verify that
3817 the type is C interoperable. Errors are reported by the functions
3818 used to set/test these fields. */
3821 set_verify_bind_c_sym (gfc_symbol *tmp_sym, int num_idents)
3823 gfc_try retval = SUCCESS;
3825 /* TODO: Do we need to make sure the vars aren't marked private? */
3827 /* Set the is_bind_c bit in symbol_attribute. */
3828 gfc_add_is_bind_c (&(tmp_sym->attr), tmp_sym->name, &gfc_current_locus, 0);
3830 if (set_binding_label (tmp_sym->binding_label, tmp_sym->name,
3831 num_idents) != SUCCESS)
3838 /* Set the fields marking the given common block as BIND(C), including
3839 a binding label, and report any errors encountered. */
3842 set_verify_bind_c_com_block (gfc_common_head *com_block, int num_idents)
3844 gfc_try retval = SUCCESS;
3846 /* destLabel, common name, typespec (which may have binding label). */
3847 if (set_binding_label (com_block->binding_label, com_block->name, num_idents)
3851 /* Set the given common block (com_block) to being bind(c) (1). */
3852 set_com_block_bind_c (com_block, 1);
3858 /* Retrieve the list of one or more identifiers that the given bind(c)
3859 attribute applies to. */
3862 get_bind_c_idents (void)
3864 char name[GFC_MAX_SYMBOL_LEN + 1];
3866 gfc_symbol *tmp_sym = NULL;
3868 gfc_common_head *com_block = NULL;
3870 if (gfc_match_name (name) == MATCH_YES)
3872 found_id = MATCH_YES;
3873 gfc_get_ha_symbol (name, &tmp_sym);
3875 else if (match_common_name (name) == MATCH_YES)
3877 found_id = MATCH_YES;
3878 com_block = gfc_get_common (name, 0);
3882 gfc_error ("Need either entity or common block name for "
3883 "attribute specification statement at %C");
3887 /* Save the current identifier and look for more. */
3890 /* Increment the number of identifiers found for this spec stmt. */
3893 /* Make sure we have a sym or com block, and verify that it can
3894 be bind(c). Set the appropriate field(s) and look for more
3896 if (tmp_sym != NULL || com_block != NULL)
3898 if (tmp_sym != NULL)
3900 if (set_verify_bind_c_sym (tmp_sym, num_idents)
3906 if (set_verify_bind_c_com_block(com_block, num_idents)
3911 /* Look to see if we have another identifier. */
3913 if (gfc_match_eos () == MATCH_YES)
3914 found_id = MATCH_NO;
3915 else if (gfc_match_char (',') != MATCH_YES)
3916 found_id = MATCH_NO;
3917 else if (gfc_match_name (name) == MATCH_YES)
3919 found_id = MATCH_YES;
3920 gfc_get_ha_symbol (name, &tmp_sym);
3922 else if (match_common_name (name) == MATCH_YES)
3924 found_id = MATCH_YES;
3925 com_block = gfc_get_common (name, 0);
3929 gfc_error ("Missing entity or common block name for "
3930 "attribute specification statement at %C");
3936 gfc_internal_error ("Missing symbol");
3938 } while (found_id == MATCH_YES);
3940 /* if we get here we were successful */
3945 /* Try and match a BIND(C) attribute specification statement. */
3948 gfc_match_bind_c_stmt (void)
3950 match found_match = MATCH_NO;
3955 /* This may not be necessary. */
3957 /* Clear the temporary binding label holder. */
3958 curr_binding_label[0] = '\0';
3960 /* Look for the bind(c). */
3961 found_match = gfc_match_bind_c (NULL, true);
3963 if (found_match == MATCH_YES)
3965 /* Look for the :: now, but it is not required. */
3968 /* Get the identifier(s) that needs to be updated. This may need to
3969 change to hand the flag(s) for the attr specified so all identifiers
3970 found can have all appropriate parts updated (assuming that the same
3971 spec stmt can have multiple attrs, such as both bind(c) and
3973 if (get_bind_c_idents () != SUCCESS)
3974 /* Error message should have printed already. */
3982 /* Match a data declaration statement. */
3985 gfc_match_data_decl (void)
3991 num_idents_on_line = 0;
3993 m = gfc_match_decl_type_spec (¤t_ts, 0);
3997 if ((current_ts.type == BT_DERIVED || current_ts.type == BT_CLASS)
3998 && gfc_current_state () != COMP_DERIVED)
4000 sym = gfc_use_derived (current_ts.u.derived);
4008 current_ts.u.derived = sym;
4011 m = match_attr_spec ();
4012 if (m == MATCH_ERROR)
4018 if ((current_ts.type == BT_DERIVED || current_ts.type == BT_CLASS)
4019 && current_ts.u.derived->components == NULL
4020 && !current_ts.u.derived->attr.zero_comp)
4023 if (current_attr.pointer && gfc_current_state () == COMP_DERIVED)
4026 gfc_find_symbol (current_ts.u.derived->name,
4027 current_ts.u.derived->ns->parent, 1, &sym);
4029 /* Any symbol that we find had better be a type definition
4030 which has its components defined. */
4031 if (sym != NULL && sym->attr.flavor == FL_DERIVED
4032 && (current_ts.u.derived->components != NULL
4033 || current_ts.u.derived->attr.zero_comp))
4036 /* Now we have an error, which we signal, and then fix up
4037 because the knock-on is plain and simple confusing. */
4038 gfc_error_now ("Derived type at %C has not been previously defined "
4039 "and so cannot appear in a derived type definition");
4040 current_attr.pointer = 1;
4045 /* If we have an old-style character declaration, and no new-style
4046 attribute specifications, then there a comma is optional between
4047 the type specification and the variable list. */
4048 if (m == MATCH_NO && current_ts.type == BT_CHARACTER && old_char_selector)
4049 gfc_match_char (',');
4051 /* Give the types/attributes to symbols that follow. Give the element
4052 a number so that repeat character length expressions can be copied. */
4056 num_idents_on_line++;
4057 m = variable_decl (elem++);
4058 if (m == MATCH_ERROR)
4063 if (gfc_match_eos () == MATCH_YES)
4065 if (gfc_match_char (',') != MATCH_YES)
4069 if (gfc_error_flag_test () == 0)
4070 gfc_error ("Syntax error in data declaration at %C");
4073 gfc_free_data_all (gfc_current_ns);
4076 gfc_free_array_spec (current_as);
4082 /* Match a prefix associated with a function or subroutine
4083 declaration. If the typespec pointer is nonnull, then a typespec
4084 can be matched. Note that if nothing matches, MATCH_YES is
4085 returned (the null string was matched). */
4088 gfc_match_prefix (gfc_typespec *ts)
4094 gfc_clear_attr (¤t_attr);
4096 seen_impure = false;
4098 gcc_assert (!gfc_matching_prefix);
4099 gfc_matching_prefix = true;
4103 found_prefix = false;
4105 if (!seen_type && ts != NULL
4106 && gfc_match_decl_type_spec (ts, 0) == MATCH_YES
4107 && gfc_match_space () == MATCH_YES)
4111 found_prefix = true;
4114 if (gfc_match ("elemental% ") == MATCH_YES)
4116 if (gfc_add_elemental (¤t_attr, NULL) == FAILURE)