From f1685b7c17cfa9d0a74d2e75f63d42ae61c29f74 Mon Sep 17 00:00:00 2001 From: Zack Weinberg <zack@gcc.gnu.org> Date: Wed, 23 Jan 2002 03:01:53 +0000 Subject: [PATCH] bad.c: Include intl.h. * bad.c: Include intl.h. (FFEBAD_MSGS1, FFEBAD_MSGS2): Replace by FFEBAD_MSG, SHORT, LONG. Adjust definitions to work with exgettext. (ffebad_start_): Translate all error messages. (ffebad_finish): Mark constant strings for translation. * bad.h: Use FFEBAD_MSG. Adjust prototype of ffebad_start_ and definitions of ffebad_start_msg, ffebad_start_msg_lex to work with exgettext. * bad.def: Use FFEBAD_MSG, SHORT, LONG throughout. * com.c: Include intl.h. (lang_print_error_function): Always use ffeinfo_kind_message to get the kind label for a non-nested construct. Translate it. Translate constant strings. * info.c (FFEINFO_KIND): Adjust definition to work with exgettext. * info-k.def: Block xgettext from slurping copyright notice into gcc.pot. Adjust strings for their sole use, in com.c. * Make-lang.in (f/bad.o, f/com.o): Depend on intl.h. From-SVN: r49123 --- gcc/f/ChangeLog | 34 +- gcc/f/Make-lang.in | 4 +- gcc/f/bad.c | 38 +- gcc/f/bad.def | 990 ++++++++++++++++++++++----------------------- gcc/f/bad.h | 14 +- gcc/f/com.c | 30 +- gcc/f/info-k.def | 26 +- gcc/f/info.c | 4 +- 8 files changed, 574 insertions(+), 566 deletions(-) diff --git a/gcc/f/ChangeLog b/gcc/f/ChangeLog index b3a9d4acb322..939b2676fd60 100644 --- a/gcc/f/ChangeLog +++ b/gcc/f/ChangeLog @@ -1,8 +1,30 @@ -2001-01-14 David Billinghurst <David.Billinghurst@riotinto.com> - - PR fortran/3807 - * f/intrin.c (ffeintrin_check_): Allow for case of intrinsic - control string have COL-spec an integer > 0. +2002-01-22 Zack Weinberg <zack@codesourcery.com> + + * bad.c: Include intl.h. + (FFEBAD_MSGS1, FFEBAD_MSGS2): Replace by FFEBAD_MSG, SHORT, + LONG. Adjust definitions to work with exgettext. + (ffebad_start_): Translate all error messages. + (ffebad_finish): Mark constant strings for translation. + * bad.h: Use FFEBAD_MSG. Adjust prototype of ffebad_start_ + and definitions of ffebad_start_msg, ffebad_start_msg_lex to + work with exgettext. + * bad.def: Use FFEBAD_MSG, SHORT, LONG throughout. + + * com.c: Include intl.h. + (lang_print_error_function): Always use ffeinfo_kind_message + to get the kind label for a non-nested construct. Translate + it. Translate constant strings. + * info.c (FFEINFO_KIND): Adjust definition to work with exgettext. + * info-k.def: Block xgettext from slurping copyright notice + into gcc.pot. Adjust strings for their sole use, in com.c. + + * Make-lang.in (f/bad.o, f/com.o): Depend on intl.h. + +2002-01-14 David Billinghurst <David.Billinghurst@riotinto.com> + + PR fortran/3807 + * f/intrin.c (ffeintrin_check_): Allow for case of intrinsic + control string have COL-spec an integer > 0. 2002-01-08 Joseph S. Myers <jsm28@cam.ac.uk> @@ -46,7 +68,7 @@ Sun Dec 16 16:08:57 2001 Joseph S. Myers <jsm28@cam.ac.uk> Sun Dec 16 10:36:51 2001 Kaveh R. Ghazi <ghazi@caip.rutgers.edu> * Make-lang.in (f/version.o): Depend on f/version.h. - * version.c: Include ansidecl.h and f/version.h. + * version.c: Include ansidecl.h and f/version.h. Sun Dec 16 08:52:48 2001 Kaveh R. Ghazi <ghazi@caip.rutgers.edu> diff --git a/gcc/f/Make-lang.in b/gcc/f/Make-lang.in index 7cd232b8e970..f9744d7ed155 100644 --- a/gcc/f/Make-lang.in +++ b/gcc/f/Make-lang.in @@ -350,7 +350,7 @@ f/bad.o: f/bad.c f/proj.h $(CONFIG_H) $(SYSTEM_H) f/bad.h f/bad.def f/where.h \ glimits.h f/top.h f/malloc.h flags.h f/com.h f/com-rt.def $(TREE_H) f/bld.h \ f/bld-op.def f/bit.h f/info.h f/info-b.def f/info-k.def f/info-w.def \ f/target.h f/lex.h f/type.h f/intrin.h f/intrin.def f/lab.h f/symbol.h \ - f/symbol.def f/equiv.h f/storag.h f/global.h f/name.h toplev.h + f/symbol.def f/equiv.h f/storag.h f/global.h f/name.h toplev.h intl.h f/bit.o: f/bit.c f/proj.h $(CONFIG_H) $(SYSTEM_H) glimits.h f/bit.h \ f/malloc.h f/bld.o: f/bld.c f/proj.h $(CONFIG_H) $(SYSTEM_H) f/bld.h f/bld-op.def f/bit.h \ @@ -364,7 +364,7 @@ f/com.o: f/com.c f/proj.h $(CONFIG_H) $(SYSTEM_H) flags.h $(RTL_H) $(TREE_H) \ f/bad.def f/where.h glimits.h f/top.h f/lex.h f/type.h f/intrin.h \ f/intrin.def f/lab.h f/symbol.h f/symbol.def f/equiv.h f/storag.h f/global.h \ f/name.h f/expr.h f/implic.h f/src.h f/st.h $(GGC_H) toplev.h diagnostic.h \ - langhooks.h langhooks-def.h + langhooks.h langhooks-def.h intl.h f/data.o: f/data.c f/proj.h $(CONFIG_H) $(SYSTEM_H) f/data.h f/bld.h f/bld-op.def \ f/bit.h f/malloc.h f/com.h f/com-rt.def $(TREE_H) f/info.h f/info-b.def \ f/info-k.def f/info-w.def f/target.h f/bad.h f/bad.def f/where.h glimits.h \ diff --git a/gcc/f/bad.c b/gcc/f/bad.c index d258648e543b..4de713c03d37 100644 --- a/gcc/f/bad.c +++ b/gcc/f/bad.c @@ -1,5 +1,5 @@ /* bad.c -- Implementation File (module.c template V1.0) - Copyright (C) 1995 Free Software Foundation, Inc. + Copyright (C) 1995, 2002 Free Software Foundation, Inc. Contributed by James Craig Burley. This file is part of GNU Fortran. @@ -42,6 +42,7 @@ the Free Software Foundation, 59 Temple Place - Suite 330, Boston, MA #include "com.h" #include "toplev.h" #include "where.h" +#include "intl.h" /* Externals defined here. */ @@ -70,15 +71,18 @@ struct _ffebad_message_ static const struct _ffebad_message_ ffebad_messages_[] = { -#define FFEBAD_MSGS1(KWD,SEV,MSG) { SEV, MSG }, +#define FFEBAD_MSG(kwd,sev,msgid) { sev, msgid }, #if FFEBAD_LONG_MSGS_ == 0 -#define FFEBAD_MSGS2(KWD,SEV,LMSG,SMSG) { SEV, SMSG }, +#define LONG(m) +#define SHORT(m) m #else -#define FFEBAD_MSGS2(KWD,SEV,LMSG,SMSG) { SEV, LMSG }, +#define LONG(m) m +#define SHORT(m) #endif #include "bad.def" -#undef FFEBAD_MSGS1 -#undef FFEBAD_MSGS2 +#undef FFEBAD_MSG +#undef LONG +#undef SHORT }; static struct @@ -161,7 +165,7 @@ ffebad_severity (ffebad errnum) bool ffebad_start_ (bool lex_override, ffebad errnum, ffebadSeverity sev, - const char *message) + const char *msgid) { unsigned char i; @@ -174,12 +178,12 @@ ffebad_start_ (bool lex_override, ffebad errnum, ffebadSeverity sev, if (errnum != FFEBAD) { ffebad_severity_ = ffebad_messages_[errnum].severity; - ffebad_message_ = ffebad_messages_[errnum].message; + ffebad_message_ = gettext (ffebad_messages_[errnum].message); } else { ffebad_severity_ = sev; - ffebad_message_ = message; + ffebad_message_ = gettext (msgid); } switch (ffebad_severity_) @@ -379,15 +383,15 @@ ffebad_finish () switch (ffebad_severity_) { case FFEBAD_severityINFORMATIONAL: - s = "note:"; + s = _("note:"); break; case FFEBAD_severityWARNING: - s = "warning:"; + s = _("warning:"); break; case FFEBAD_severitySEVERE: - s = "fatal:"; + s = _("fatal:"); break; default: @@ -429,7 +433,7 @@ ffebad_finish () pointer); last_line_num = ln; last_col_num = cn; - s = "(continued):"; + s = _("(continued):"); } else { @@ -479,14 +483,14 @@ ffebad_finish () if ((index < 0) || (index >= FFEBAD_MAX_)) { - bufi = ffebad_bufputs_ (buf, bufi, "[REPORT BUG!!] %"); + bufi = ffebad_bufputs_ (buf, bufi, _("[REPORT BUG!!] %")); bufi = ffebad_bufputc_ (buf, bufi, c); } else { s = ffebad_string_[index]; if (s == NULL) - bufi = ffebad_bufputs_ (buf, bufi, "[REPORT BUG!!]"); + bufi = ffebad_bufputs_ (buf, bufi, _("[REPORT BUG!!]")); else bufi = ffebad_bufputs_ (buf, bufi, s); } @@ -497,7 +501,7 @@ ffebad_finish () if ((index < 0) || (index >= FFEBAD_MAX_)) { - bufi = ffebad_bufputs_ (buf, bufi, "[REPORT BUG!!] %"); + bufi = ffebad_bufputs_ (buf, bufi, _("[REPORT BUG!!] %")); bufi = ffebad_bufputc_ (buf, bufi, c); } else @@ -518,7 +522,7 @@ ffebad_finish () bufi = ffebad_bufputc_ (buf, bufi, '%'); else { - bufi = ffebad_bufputs_ (buf, bufi, "[REPORT BUG!!]"); + bufi = ffebad_bufputs_ (buf, bufi, _("[REPORT BUG!!]")); bufi = ffebad_bufputc_ (buf, bufi, '%'); bufi = ffebad_bufputc_ (buf, bufi, c); } diff --git a/gcc/f/bad.def b/gcc/f/bad.def index fbc237b2a668..165a5a38fd10 100644 --- a/gcc/f/bad.def +++ b/gcc/f/bad.def @@ -1,5 +1,5 @@ /* bad.def -- Public #include File (module.h template V1.0) - Copyright (C) 1995, 1996, 1997 Free Software Foundation, Inc. + Copyright (C) 1995, 1996, 1997, 2002 Free Software Foundation, Inc. Contributed by James Craig Burley. This file is part of GNU Fortran. @@ -34,675 +34,675 @@ the Free Software Foundation, 59 Temple Place - Suite 330, Boston, MA #define SEVERE FFEBAD_severitySEVERE #define DISASTER FFEBAD_severityDISASTER -FFEBAD_MSGS1 (FFEBAD_MISSING_FIRST_BINARY_OPERAND, FATAL, +FFEBAD_MSG (FFEBAD_MISSING_FIRST_BINARY_OPERAND, FATAL, "Missing first operand for binary operator at %0") -FFEBAD_MSGS1 (FFEBAD_NULL_CHAR_CONST, WARN, +FFEBAD_MSG (FFEBAD_NULL_CHAR_CONST, WARN, "Zero-length character constant at %0") -FFEBAD_MSGS1 (FFEBAD_INVALID_TOKEN_IN_EXPRESSION, FATAL, +FFEBAD_MSG (FFEBAD_INVALID_TOKEN_IN_EXPRESSION, FATAL, "Invalid token at %0 in expression or subexpression at %1") -FFEBAD_MSGS1 (FFEBAD_MISSING_OPERAND_FOR_OPERATOR, FATAL, +FFEBAD_MSG (FFEBAD_MISSING_OPERAND_FOR_OPERATOR, FATAL, "Missing operand for operator at %1 at end of expression at %0") -FFEBAD_MSGS1 (FFEBAD_LABEL_ALREADY_DEFINED, FATAL, +FFEBAD_MSG (FFEBAD_LABEL_ALREADY_DEFINED, FATAL, "Label %A already defined at %1 when redefined at %0") -FFEBAD_MSGS1 (FFEBAD_UNRECOGNIZED_CHARACTER, FATAL, +FFEBAD_MSG (FFEBAD_UNRECOGNIZED_CHARACTER, FATAL, "Unrecognized character at %0 [info -f g77 M LEX]") -FFEBAD_MSGS1 (FFEBAD_LABEL_WITHOUT_STMT, WARN, +FFEBAD_MSG (FFEBAD_LABEL_WITHOUT_STMT, WARN, "Label definition %A at %0 on empty statement (as of %1)") -FFEBAD_MSGS2 (FFEBAD_EXTRA_LABEL_DEF, FATAL, -"Extra label definition %A at %0 -- perhaps previous label definition %B at %1 should have CONTINUE statement?", -"Extra label definition %A at %0 following label definition %B at %1") -FFEBAD_MSGS1 (FFEBAD_FIRST_CHAR_INVALID, FATAL, +FFEBAD_MSG (FFEBAD_EXTRA_LABEL_DEF, FATAL, +LONG("Extra label definition %A at %0 -- perhaps previous label definition %B at %1 should have CONTINUE statement?") +SHORT("Extra label definition %A at %0 following label definition %B at %1")) +FFEBAD_MSG (FFEBAD_FIRST_CHAR_INVALID, FATAL, "Invalid first character at %0 [info -f g77 M LEX]") -FFEBAD_MSGS1 (FFEBAD_LINE_TOO_LONG, FATAL, +FFEBAD_MSG (FFEBAD_LINE_TOO_LONG, FATAL, "Line too long as of %0 [info -f g77 M LEX]") -FFEBAD_MSGS1 (FFEBAD_LABEL_FIELD_NOT_NUMERIC, FATAL, +FFEBAD_MSG (FFEBAD_LABEL_FIELD_NOT_NUMERIC, FATAL, "Non-numeric character at %0 in label field [info -f g77 M LEX]") -FFEBAD_MSGS1 (FFEBAD_LABEL_NUMBER_INVALID, FATAL, +FFEBAD_MSG (FFEBAD_LABEL_NUMBER_INVALID, FATAL, "Label number at %0 not in range 1-99999") -FFEBAD_MSGS1 (FFEBAD_NON_ANSI_COMMENT, WARN, +FFEBAD_MSG (FFEBAD_NON_ANSI_COMMENT, WARN, "At %0, '!' and '/*' are not valid comment delimiters") -FFEBAD_MSGS1 (FFEBAD_NON_ANSI_CONTINUATION_COLUMN, WARN, +FFEBAD_MSG (FFEBAD_NON_ANSI_CONTINUATION_COLUMN, WARN, "Continuation indicator at %0 must appear in column 6 [info -f g77 M LEX]") -FFEBAD_MSGS1 (FFEBAD_LABEL_ON_CONTINUATION, FATAL, +FFEBAD_MSG (FFEBAD_LABEL_ON_CONTINUATION, FATAL, "Label at %0 invalid with continuation line indicator at %1 [info -f g77 M LEX]") -FFEBAD_MSGS2 (FFEBAD_INVALID_CONTINUATION, FATAL, -"Continuation indicator at %0 invalid on first non-comment line of file or following END or INCLUDE [info -f g77 M LEX]", -"Continuation indicator at %0 invalid here [info -f g77 M LEX]") -FFEBAD_MSGS1 (FFEBAD_NO_CLOSING_APOSTROPHE, FATAL, +FFEBAD_MSG (FFEBAD_INVALID_CONTINUATION, FATAL, +LONG("Continuation indicator at %0 invalid on first non-comment line of file or following END or INCLUDE [info -f g77 M LEX]") +SHORT("Continuation indicator at %0 invalid here [info -f g77 M LEX]")) +FFEBAD_MSG (FFEBAD_NO_CLOSING_APOSTROPHE, FATAL, "Character constant at %0 has no closing apostrophe at %1") -FFEBAD_MSGS1 (FFEBAD_NOT_ENOUGH_HOLLERITH_CHARS, FATAL, +FFEBAD_MSG (FFEBAD_NOT_ENOUGH_HOLLERITH_CHARS, FATAL, "Hollerith constant at %0 specified %A more characters than are present as of %1") -FFEBAD_MSGS1 (FFEBAD_MISSING_CLOSE_PAREN, FATAL, +FFEBAD_MSG (FFEBAD_MISSING_CLOSE_PAREN, FATAL, "Missing close parenthese at %0 needed to match open parenthese at %1") -FFEBAD_MSGS1 (FFEBAD_INTEGER_TOO_LARGE, FATAL, +FFEBAD_MSG (FFEBAD_INTEGER_TOO_LARGE, FATAL, "Integer at %0 too large") -FFEBAD_MSGS2 (FFEBAD_BAD_MAGICAL, WARN, -"Integer at %0 too large except as negative number (preceded by unary minus sign)", -"Non-negative integer at %0 too large") -FFEBAD_MSGS2 (FFEBAD_BAD_MAGICAL_PRECEDENCE, WARN, -"Integer at %0 too large; even though preceded by unary minus sign at %1, subsequent operator at %2 has precedence over unary minus -- enclose unary minus sign and integer in parentheses to force precedence", -"Integer at %0 too large (%2 has precedence over %1)") -FFEBAD_MSGS2 (FFEBAD_BAD_MAGICAL_BINARY, WARN, -"Integer at %0 too large; even though preceded by minus sign at %1, because minus sign is a binary, not unary, operator -- insert plus sign before minus sign to change it to a unary minus sign", -"Integer at %0 too large (needs unary, not binary, minus at %1)") -FFEBAD_MSGS2 (FFEBAD_BAD_MAGICAL_PRECEDENCE_BINARY, WARN, -"Integer at %0 too large; even though preceded by minus sign at %1, subsequent operator at %2 has precedence over minus, and that minus sign should be a unary minus rather than a binary minus -- insert plus sign before minus sign to change it to a unary minus sign, and enclose unary minus sign and integer in parentheses to force precedence", -"Integer at %0 too large (%2 has precedence over %1, which needs to be unary, not binary, minus)") -FFEBAD_MSGS1 (FFEBAD_IGNORING_PERIOD, FATAL, +FFEBAD_MSG (FFEBAD_BAD_MAGICAL, WARN, +LONG("Integer at %0 too large except as negative number (preceded by unary minus sign)") +SHORT("Non-negative integer at %0 too large")) +FFEBAD_MSG (FFEBAD_BAD_MAGICAL_PRECEDENCE, WARN, +LONG("Integer at %0 too large; even though preceded by unary minus sign at %1, subsequent operator at %2 has precedence over unary minus -- enclose unary minus sign and integer in parentheses to force precedence") +SHORT("Integer at %0 too large (%2 has precedence over %1)")) +FFEBAD_MSG (FFEBAD_BAD_MAGICAL_BINARY, WARN, +LONG("Integer at %0 too large; even though preceded by minus sign at %1, because minus sign is a binary, not unary, operator -- insert plus sign before minus sign to change it to a unary minus sign") +SHORT("Integer at %0 too large (needs unary, not binary, minus at %1)")) +FFEBAD_MSG (FFEBAD_BAD_MAGICAL_PRECEDENCE_BINARY, WARN, +LONG("Integer at %0 too large; even though preceded by minus sign at %1, subsequent operator at %2 has precedence over minus, and that minus sign should be a unary minus rather than a binary minus -- insert plus sign before minus sign to change it to a unary minus sign, and enclose unary minus sign and integer in parentheses to force precedence") +SHORT("Integer at %0 too large (%2 has precedence over %1, which needs to be unary, not binary, minus)")) +FFEBAD_MSG (FFEBAD_IGNORING_PERIOD, FATAL, "Period at %0 not followed by digits for floating-point number or by `NOT.', `TRUE.', or `FALSE.'") -FFEBAD_MSGS1 (FFEBAD_INSERTING_PERIOD, FATAL, +FFEBAD_MSG (FFEBAD_INSERTING_PERIOD, FATAL, "Missing close-period between `.%A' at %0 and %1") -FFEBAD_MSGS1 (FFEBAD_INVALID_EXPONENT, FATAL, +FFEBAD_MSG (FFEBAD_INVALID_EXPONENT, FATAL, "Invalid exponent at %0 for real constant at %1; nondigit `%A' in exponent field") -FFEBAD_MSGS1 (FFEBAD_MISSING_EXPONENT_VALUE, FATAL, +FFEBAD_MSG (FFEBAD_MISSING_EXPONENT_VALUE, FATAL, "Missing value at %1 for real-number exponent at %0") -FFEBAD_MSGS1 (FFEBAD_MISSING_BINARY_OPERATOR, FATAL, +FFEBAD_MSG (FFEBAD_MISSING_BINARY_OPERATOR, FATAL, "Expected binary operator between expressions at %0 and at %1") -FFEBAD_MSGS2 (FFEBAD_INVALID_DOTDOT, FATAL, -"Period at %0 not followed by valid keyword forming a valid binary operator; `.%A.' is not a valid binary operator", -"`.%A.' at %0 not a binary operator") -FFEBAD_MSGS2 (FFEBAD_QUOTE_MISSES_DIGITS, FATAL, -"Double-quote at %0 not followed by a string of valid octal digits at %1", -"Invalid octal constant at %0") -FFEBAD_MSGS2 (FFEBAD_INVALID_BINARY_DIGIT, FATAL, -"Invalid binary digit(s) found in string of digits at %0", -"Invalid binary constant at %0") -FFEBAD_MSGS2 (FFEBAD_INVALID_HEX_DIGIT, FATAL, -"Invalid hexadecimal digit(s) found in string of digits at %0", -"Invalid hexadecimal constant at %0") -FFEBAD_MSGS2 (FFEBAD_INVALID_OCTAL_DIGIT, FATAL, -"Invalid octal digit(s) found in string of digits at %0", -"Invalid octal constant at %0") -FFEBAD_MSGS2 (FFEBAD_INVALID_RADIX_SPECIFIER, FATAL, -"Invalid radix specifier `%A' at %0 for typeless constant at %1", -"Invalid typeless constant at %1") -FFEBAD_MSGS2 (FFEBAD_INVALID_TYPELESS_BINARY_DIGIT, FATAL, -"Invalid binary digit(s) found in string of digits at %0", -"Invalid binary constant at %0") -FFEBAD_MSGS2 (FFEBAD_INVALID_TYPELESS_OCTAL_DIGIT, FATAL, -"Invalid octal digit(s) found in string of digits at %0", -"Invalid octal constant at %0") -FFEBAD_MSGS2 (FFEBAD_INVALID_TYPELESS_HEX_DIGIT, FATAL, -"Invalid hexadecimal digit(s) found in string of digits at %0", -"Invalid hexadecimal constant at %0") -FFEBAD_MSGS2 (FFEBAD_INVALID_COMPLEX_PART, FATAL, -"%A part of complex constant at %0 must be a real or integer constant -- otherwise use CMPLX() or COMPLEX() in place of ()", -"%A part of complex constant at %0 not a real or integer constant") -FFEBAD_MSGS2 (FFEBAD_INVALID_PERCENT, FATAL, -"Invalid keyword `%%%A' at %0 in this context", -"Invalid keyword `%%%A' at %0") -FFEBAD_MSGS2 (FFEBAD_NULL_EXPRESSION, FATAL, -"Null expression between %0 and %1 invalid in this context", -"Invalid null expression between %0 and %1") -FFEBAD_MSGS2 (FFEBAD_CONCAT_ARGS_TYPE, FATAL, -"Concatenation operator at %0 must operate on two subexpressions of character type, but neither subexpression at %1 or %2 is of character type", -"Invalid operands at %1 and %2 for concatenation operator at %0") -FFEBAD_MSGS2 (FFEBAD_CONCAT_ARG_TYPE, FATAL, -"Concatenation operator at %0 must operate on two subexpressions of character type, but the subexpression at %1 is not of character type", -"Invalid operand at %1 for concatenation operator at %0") -FFEBAD_MSGS2 (FFEBAD_CONCAT_ARG_KIND, FATAL, -"Concatenation operator at %0 must operate on two scalar (not array) subexpressions, two function invocations returning character scalars, or a combination of both -- but the subexpression at %1 is %A", -"Invalid operand (is %A) at %1 for concatenation operator at %0") -FFEBAD_MSGS2 (FFEBAD_MATH_ARGS_TYPE, FATAL, -"Arithmetic operator at %0 must operate on two subexpressions of arithmetic type, but neither subexpression at %1 or %2 is of arithmetic type", -"Invalid operands at %1 and %2 for arithmetic operator at %0") -FFEBAD_MSGS2 (FFEBAD_MATH_ARG_TYPE, FATAL, -"Arithmetic operator at %0 must operate on two subexpressions of arithmetic type, but the subexpression at %1 is not of arithmetic type", -"Invalid operand at %1 for arithmetic operator at %0") -FFEBAD_MSGS2 (FFEBAD_MATH_ARG_KIND, FATAL, -"Arithmetic operator at %0 must operate on two scalar (not array) subexpressions, two function invocations returning arithmetic scalars, or a combination of both -- but the subexpression at %1 is %A", -"Invalid operand (is %A) at %1 for arithmetic operator at %0") -FFEBAD_MSGS2 (FFEBAD_NO_CLOSING_QUOTE, FATAL, -"Character constant at %0 has no closing quote at %1 [info -f g77 M LEX]", -"Unterminated character constant at %0 [info -f g77 M LEX]") -FFEBAD_MSGS2 (FFEBAD_BAD_CHAR_CONTINUE, FATAL, -"Continuation line at %0 must have initial `&' since it continues a character context [info -f g77 M LEX]", -"Missing initial `&' on continuation line at %0 [info -f g77 M LEX]") -FFEBAD_MSGS2 (FFEBAD_BAD_LEXTOK_CONTINUE, FATAL, -"Continuation line at %0 must have initial `&' since it continues a split lexical token [info -f g77 M LEX]", -"Missing initial `&' on continuation line at %0 [info -f g77 M LEX]") -FFEBAD_MSGS2 (FFEBAD_BAD_FREE_CONTINUE, FATAL, -"Continuation line at %0 invalid because it consists only of a single `&' as the only nonblank character", -"Invalid continuation line at %0") -FFEBAD_MSGS2 (FFEBAD_STMT_BEGINS_BAD, FATAL, -"Statement at %0 begins with invalid token [info -f g77 M LEX]", -"Invalid statement at %0 [info -f g77 M LEX]") -FFEBAD_MSGS1 (FFEBAD_SEMICOLON, FATAL, +FFEBAD_MSG (FFEBAD_INVALID_DOTDOT, FATAL, +LONG("Period at %0 not followed by valid keyword forming a valid binary operator; `.%A.' is not a valid binary operator") +SHORT("`.%A.' at %0 not a binary operator")) +FFEBAD_MSG (FFEBAD_QUOTE_MISSES_DIGITS, FATAL, +LONG("Double-quote at %0 not followed by a string of valid octal digits at %1") +SHORT("Invalid octal constant at %0")) +FFEBAD_MSG (FFEBAD_INVALID_BINARY_DIGIT, FATAL, +LONG("Invalid binary digit(s) found in string of digits at %0") +SHORT("Invalid binary constant at %0")) +FFEBAD_MSG (FFEBAD_INVALID_HEX_DIGIT, FATAL, +LONG("Invalid hexadecimal digit(s) found in string of digits at %0") +SHORT("Invalid hexadecimal constant at %0")) +FFEBAD_MSG (FFEBAD_INVALID_OCTAL_DIGIT, FATAL, +LONG("Invalid octal digit(s) found in string of digits at %0") +SHORT("Invalid octal constant at %0")) +FFEBAD_MSG (FFEBAD_INVALID_RADIX_SPECIFIER, FATAL, +LONG("Invalid radix specifier `%A' at %0 for typeless constant at %1") +SHORT("Invalid typeless constant at %1")) +FFEBAD_MSG (FFEBAD_INVALID_TYPELESS_BINARY_DIGIT, FATAL, +LONG("Invalid binary digit(s) found in string of digits at %0") +SHORT("Invalid binary constant at %0")) +FFEBAD_MSG (FFEBAD_INVALID_TYPELESS_OCTAL_DIGIT, FATAL, +LONG("Invalid octal digit(s) found in string of digits at %0") +SHORT("Invalid octal constant at %0")) +FFEBAD_MSG (FFEBAD_INVALID_TYPELESS_HEX_DIGIT, FATAL, +LONG("Invalid hexadecimal digit(s) found in string of digits at %0") +SHORT("Invalid hexadecimal constant at %0")) +FFEBAD_MSG (FFEBAD_INVALID_COMPLEX_PART, FATAL, +LONG("%A part of complex constant at %0 must be a real or integer constant -- otherwise use CMPLX() or COMPLEX() in place of ()") +SHORT("%A part of complex constant at %0 not a real or integer constant")) +FFEBAD_MSG (FFEBAD_INVALID_PERCENT, FATAL, +LONG("Invalid keyword `%%%A' at %0 in this context") +SHORT("Invalid keyword `%%%A' at %0")) +FFEBAD_MSG (FFEBAD_NULL_EXPRESSION, FATAL, +LONG("Null expression between %0 and %1 invalid in this context") +SHORT("Invalid null expression between %0 and %1")) +FFEBAD_MSG (FFEBAD_CONCAT_ARGS_TYPE, FATAL, +LONG("Concatenation operator at %0 must operate on two subexpressions of character type, but neither subexpression at %1 or %2 is of character type") +SHORT("Invalid operands at %1 and %2 for concatenation operator at %0")) +FFEBAD_MSG (FFEBAD_CONCAT_ARG_TYPE, FATAL, +LONG("Concatenation operator at %0 must operate on two subexpressions of character type, but the subexpression at %1 is not of character type") +SHORT("Invalid operand at %1 for concatenation operator at %0")) +FFEBAD_MSG (FFEBAD_CONCAT_ARG_KIND, FATAL, +LONG("Concatenation operator at %0 must operate on two scalar (not array) subexpressions, two function invocations returning character scalars, or a combination of both -- but the subexpression at %1 is %A") +SHORT("Invalid operand (is %A) at %1 for concatenation operator at %0")) +FFEBAD_MSG (FFEBAD_MATH_ARGS_TYPE, FATAL, +LONG("Arithmetic operator at %0 must operate on two subexpressions of arithmetic type, but neither subexpression at %1 or %2 is of arithmetic type") +SHORT("Invalid operands at %1 and %2 for arithmetic operator at %0")) +FFEBAD_MSG (FFEBAD_MATH_ARG_TYPE, FATAL, +LONG("Arithmetic operator at %0 must operate on two subexpressions of arithmetic type, but the subexpression at %1 is not of arithmetic type") +SHORT("Invalid operand at %1 for arithmetic operator at %0")) +FFEBAD_MSG (FFEBAD_MATH_ARG_KIND, FATAL, +LONG("Arithmetic operator at %0 must operate on two scalar (not array) subexpressions, two function invocations returning arithmetic scalars, or a combination of both -- but the subexpression at %1 is %A") +SHORT("Invalid operand (is %A) at %1 for arithmetic operator at %0")) +FFEBAD_MSG (FFEBAD_NO_CLOSING_QUOTE, FATAL, +LONG("Character constant at %0 has no closing quote at %1 [info -f g77 M LEX]") +SHORT("Unterminated character constant at %0 [info -f g77 M LEX]")) +FFEBAD_MSG (FFEBAD_BAD_CHAR_CONTINUE, FATAL, +LONG("Continuation line at %0 must have initial `&' since it continues a character context [info -f g77 M LEX]") +SHORT("Missing initial `&' on continuation line at %0 [info -f g77 M LEX]")) +FFEBAD_MSG (FFEBAD_BAD_LEXTOK_CONTINUE, FATAL, +LONG("Continuation line at %0 must have initial `&' since it continues a split lexical token [info -f g77 M LEX]") +SHORT("Missing initial `&' on continuation line at %0 [info -f g77 M LEX]")) +FFEBAD_MSG (FFEBAD_BAD_FREE_CONTINUE, FATAL, +LONG("Continuation line at %0 invalid because it consists only of a single `&' as the only nonblank character") +SHORT("Invalid continuation line at %0")) +FFEBAD_MSG (FFEBAD_STMT_BEGINS_BAD, FATAL, +LONG("Statement at %0 begins with invalid token [info -f g77 M LEX]") +SHORT("Invalid statement at %0 [info -f g77 M LEX]")) +FFEBAD_MSG (FFEBAD_SEMICOLON, FATAL, "Semicolon at %0 is an invalid token") -FFEBAD_MSGS2 (FFEBAD_UNREC_STMT, FATAL, -"Unrecognized statement name at %0 and invalid form for assignment or statement-function definition at %1", -"Invalid statement at %0") -FFEBAD_MSGS2 (FFEBAD_INVALID_STMT_FORM, FATAL, -"Invalid form for %A statement at %0", -"Invalid %A statement at %0") -FFEBAD_MSGS2 (FFEBAD_INVALID_HOLL_IN_STMT, FATAL, -"Invalid use of hollerith constant in statement at %0 -- enclose the constant in parentheses (for example, change BACKSPACE 2HAB to BACKSPACE (2HAB))", -"Enclose hollerith constant in statement at %0 in parentheses") -FFEBAD_MSGS1 (FFEBAD_FORMAT_EXTRA_COMMA, FATAL, +FFEBAD_MSG (FFEBAD_UNREC_STMT, FATAL, +LONG("Unrecognized statement name at %0 and invalid form for assignment or statement-function definition at %1") +SHORT("Invalid statement at %0")) +FFEBAD_MSG (FFEBAD_INVALID_STMT_FORM, FATAL, +LONG("Invalid form for %A statement at %0") +SHORT("Invalid %A statement at %0")) +FFEBAD_MSG (FFEBAD_INVALID_HOLL_IN_STMT, FATAL, +LONG("Invalid use of hollerith constant in statement at %0 -- enclose the constant in parentheses (for example, change BACKSPACE 2HAB to BACKSPACE (2HAB))") +SHORT("Enclose hollerith constant in statement at %0 in parentheses")) +FFEBAD_MSG (FFEBAD_FORMAT_EXTRA_COMMA, FATAL, "Extraneous comma in FORMAT statement at %0") -FFEBAD_MSGS1 (FFEBAD_FORMAT_MISSING_COMMA, WARN, +FFEBAD_MSG (FFEBAD_FORMAT_MISSING_COMMA, WARN, "Missing comma in FORMAT statement at %0") -FFEBAD_MSGS1 (FFEBAD_FORMAT_SPURIOUS_SIGN, FATAL, +FFEBAD_MSG (FFEBAD_FORMAT_SPURIOUS_SIGN, FATAL, "Spurious sign in FORMAT statement at %0") -FFEBAD_MSGS1 (FFEBAD_FORMAT_SPURIOUS_NUMBER, FATAL, +FFEBAD_MSG (FFEBAD_FORMAT_SPURIOUS_NUMBER, FATAL, "Spurious number in FORMAT statement at %0") -FFEBAD_MSGS1 (FFEBAD_FORMAT_TEXT_IN_NUMBER, FATAL, +FFEBAD_MSG (FFEBAD_FORMAT_TEXT_IN_NUMBER, FATAL, "Spurious text trailing number in FORMAT statement at %0") -FFEBAD_MSGS2 (FFEBAD_FORMAT_P_NOCOMMA, FATAL, -"nP control edit descriptor not followed by comma but followed by edit descriptor at %0 other than D, E, EN, F, or G", -"Invalid edit descriptor at %0 following nP control edit descriptor") -FFEBAD_MSGS1 (FFEBAD_FORMAT_BAD_SPEC, FATAL, +FFEBAD_MSG (FFEBAD_FORMAT_P_NOCOMMA, FATAL, +LONG("nP control edit descriptor not followed by comma but followed by edit descriptor at %0 other than D, E, EN, F, or G") +SHORT("Invalid edit descriptor at %0 following nP control edit descriptor")) +FFEBAD_MSG (FFEBAD_FORMAT_BAD_SPEC, FATAL, "Unrecognized FORMAT specifier at %0") -FFEBAD_MSGS2 (FFEBAD_FORMAT_BAD_I_SPEC, FATAL, -"Invalid I specifier in FORMAT statement at %0 -- correct form: [r]Iw.[m]", -"Invalid I specifier in FORMAT statement at %0") -FFEBAD_MSGS2 (FFEBAD_FORMAT_BAD_B_SPEC, FATAL, -"Invalid B specifier in FORMAT statement at %0 -- correct form: [r]Bw.[m]", -"Invalid B specifier in FORMAT statement at %0") -FFEBAD_MSGS2 (FFEBAD_FORMAT_BAD_O_SPEC, FATAL, -"Invalid O specifier in FORMAT statement at %0 -- correct form: [r]Ow.[m]", -"Invalid O specifier in FORMAT statement at %0") -FFEBAD_MSGS2 (FFEBAD_FORMAT_BAD_Z_SPEC, FATAL, -"Invalid Z specifier in FORMAT statement at %0 -- correct form: [r]Zw.[m]", -"Invalid Z specifier in FORMAT statement at %0") -FFEBAD_MSGS2 (FFEBAD_FORMAT_BAD_F_SPEC, FATAL, -"Invalid F specifier in FORMAT statement at %0 -- correct form: [r]Fw.d", -"Invalid F specifier in FORMAT statement at %0") -FFEBAD_MSGS2 (FFEBAD_FORMAT_BAD_E_SPEC, FATAL, -"Invalid E specifier in FORMAT statement at %0 -- correct form: [r]Ew.d[Ee]", -"Invalid E specifier in FORMAT statement at %0") -FFEBAD_MSGS2 (FFEBAD_FORMAT_BAD_EN_SPEC, FATAL, -"Invalid EN specifier in FORMAT statement at %0 -- correct form: [r]ENw.d[Ee]", -"Invalid EN specifier in FORMAT statement at %0") -FFEBAD_MSGS2 (FFEBAD_FORMAT_BAD_G_SPEC, FATAL, -"Invalid G specifier in FORMAT statement at %0 -- correct form: [r]Gw.d[Ee]", -"Invalid G specifier in FORMAT statement at %0") -FFEBAD_MSGS2 (FFEBAD_FORMAT_BAD_L_SPEC, FATAL, -"Invalid L specifier in FORMAT statement at %0 -- correct form: [r]Lw", -"Invalid L specifier in FORMAT statement at %0") -FFEBAD_MSGS2 (FFEBAD_FORMAT_BAD_A_SPEC, FATAL, -"Invalid A specifier in FORMAT statement at %0 -- correct form: [r]A[w]", -"Invalid A specifier in FORMAT statement at %0") -FFEBAD_MSGS2 (FFEBAD_FORMAT_BAD_D_SPEC, FATAL, -"Invalid D specifier in FORMAT statement at %0 -- correct form: [r]Dw.d", -"Invalid D specifier in FORMAT statement at %0") -FFEBAD_MSGS2 (FFEBAD_FORMAT_BAD_Q_SPEC, FATAL, -"Invalid Q specifier in FORMAT statement at %0 -- correct form: Q", -"Invalid Q specifier in FORMAT statement at %0") -FFEBAD_MSGS2 (FFEBAD_FORMAT_BAD_DOLLAR_SPEC, FATAL, -"Invalid $ specifier in FORMAT statement at %0 -- correct form: $", -"Invalid $ specifier in FORMAT statement at %0") -FFEBAD_MSGS2 (FFEBAD_FORMAT_BAD_P_SPEC, FATAL, -"Invalid P specifier in FORMAT statement at %0 -- correct form: kP", -"Invalid P specifier in FORMAT statement at %0") -FFEBAD_MSGS2 (FFEBAD_FORMAT_BAD_T_SPEC, FATAL, -"Invalid T specifier in FORMAT statement at %0 -- correct form: Tn", -"Invalid T specifier in FORMAT statement at %0") -FFEBAD_MSGS2 (FFEBAD_FORMAT_BAD_TL_SPEC, FATAL, -"Invalid TL specifier in FORMAT statement at %0 -- correct form: TLn", -"Invalid TL specifier in FORMAT statement at %0") -FFEBAD_MSGS2 (FFEBAD_FORMAT_BAD_TR_SPEC, FATAL, -"Invalid TR specifier in FORMAT statement at %0 -- correct form: TRn", -"Invalid TR specifier in FORMAT statement at %0") -FFEBAD_MSGS2 (FFEBAD_FORMAT_BAD_X_SPEC, FATAL, -"Invalid X specifier in FORMAT statement at %0 -- correct form: nX", -"Invalid X specifier in FORMAT statement at %0") -FFEBAD_MSGS2 (FFEBAD_FORMAT_BAD_S_SPEC, FATAL, -"Invalid S specifier in FORMAT statement at %0 -- correct form: S", -"Invalid S specifier in FORMAT statement at %0") -FFEBAD_MSGS2 (FFEBAD_FORMAT_BAD_SP_SPEC, FATAL, -"Invalid SP specifier in FORMAT statement at %0 -- correct form: SP", -"Invalid SP specifier in FORMAT statement at %0") -FFEBAD_MSGS2 (FFEBAD_FORMAT_BAD_SS_SPEC, FATAL, -"Invalid SS specifier in FORMAT statement at %0 -- correct form: SS", -"Invalid SS specifier in FORMAT statement at %0") -FFEBAD_MSGS2 (FFEBAD_FORMAT_BAD_BN_SPEC, FATAL, -"Invalid BN specifier in FORMAT statement at %0 -- correct form: BN", -"Invalid BN specifier in FORMAT statement at %0") -FFEBAD_MSGS2 (FFEBAD_FORMAT_BAD_BZ_SPEC, FATAL, -"Invalid BZ specifier in FORMAT statement at %0 -- correct form: BZ", -"Invalid BZ specifier in FORMAT statement at %0") -FFEBAD_MSGS2 (FFEBAD_FORMAT_BAD_COLON_SPEC, FATAL, -"Invalid : specifier in FORMAT statement at %0 -- correct form: :", -"Invalid : specifier in FORMAT statement at %0") -FFEBAD_MSGS2 (FFEBAD_FORMAT_BAD_H_SPEC, FATAL, -"Invalid H specifier in FORMAT statement at %0 -- correct form: nHcharacters !where n is an unsigned decimal constant, and characters !contains exactly n characters (including spaces)", -"Invalid H specifier in FORMAT statement at %0") -FFEBAD_MSGS1 (FFEBAD_FORMAT_MISSING_PAREN, FATAL, +FFEBAD_MSG (FFEBAD_FORMAT_BAD_I_SPEC, FATAL, +LONG("Invalid I specifier in FORMAT statement at %0 -- correct form: [r]Iw.[m]") +SHORT("Invalid I specifier in FORMAT statement at %0")) +FFEBAD_MSG (FFEBAD_FORMAT_BAD_B_SPEC, FATAL, +LONG("Invalid B specifier in FORMAT statement at %0 -- correct form: [r]Bw.[m]") +SHORT("Invalid B specifier in FORMAT statement at %0")) +FFEBAD_MSG (FFEBAD_FORMAT_BAD_O_SPEC, FATAL, +LONG("Invalid O specifier in FORMAT statement at %0 -- correct form: [r]Ow.[m]") +SHORT("Invalid O specifier in FORMAT statement at %0")) +FFEBAD_MSG (FFEBAD_FORMAT_BAD_Z_SPEC, FATAL, +LONG("Invalid Z specifier in FORMAT statement at %0 -- correct form: [r]Zw.[m]") +SHORT("Invalid Z specifier in FORMAT statement at %0")) +FFEBAD_MSG (FFEBAD_FORMAT_BAD_F_SPEC, FATAL, +LONG("Invalid F specifier in FORMAT statement at %0 -- correct form: [r]Fw.d") +SHORT("Invalid F specifier in FORMAT statement at %0")) +FFEBAD_MSG (FFEBAD_FORMAT_BAD_E_SPEC, FATAL, +LONG("Invalid E specifier in FORMAT statement at %0 -- correct form: [r]Ew.d[Ee]") +SHORT("Invalid E specifier in FORMAT statement at %0")) +FFEBAD_MSG (FFEBAD_FORMAT_BAD_EN_SPEC, FATAL, +LONG("Invalid EN specifier in FORMAT statement at %0 -- correct form: [r]ENw.d[Ee]") +SHORT("Invalid EN specifier in FORMAT statement at %0")) +FFEBAD_MSG (FFEBAD_FORMAT_BAD_G_SPEC, FATAL, +LONG("Invalid G specifier in FORMAT statement at %0 -- correct form: [r]Gw.d[Ee]") +SHORT("Invalid G specifier in FORMAT statement at %0")) +FFEBAD_MSG (FFEBAD_FORMAT_BAD_L_SPEC, FATAL, +LONG("Invalid L specifier in FORMAT statement at %0 -- correct form: [r]Lw") +SHORT("Invalid L specifier in FORMAT statement at %0")) +FFEBAD_MSG (FFEBAD_FORMAT_BAD_A_SPEC, FATAL, +LONG("Invalid A specifier in FORMAT statement at %0 -- correct form: [r]A[w]") +SHORT("Invalid A specifier in FORMAT statement at %0")) +FFEBAD_MSG (FFEBAD_FORMAT_BAD_D_SPEC, FATAL, +LONG("Invalid D specifier in FORMAT statement at %0 -- correct form: [r]Dw.d") +SHORT("Invalid D specifier in FORMAT statement at %0")) +FFEBAD_MSG (FFEBAD_FORMAT_BAD_Q_SPEC, FATAL, +LONG("Invalid Q specifier in FORMAT statement at %0 -- correct form: Q") +SHORT("Invalid Q specifier in FORMAT statement at %0")) +FFEBAD_MSG (FFEBAD_FORMAT_BAD_DOLLAR_SPEC, FATAL, +LONG("Invalid $ specifier in FORMAT statement at %0 -- correct form: $") +SHORT("Invalid $ specifier in FORMAT statement at %0")) +FFEBAD_MSG (FFEBAD_FORMAT_BAD_P_SPEC, FATAL, +LONG("Invalid P specifier in FORMAT statement at %0 -- correct form: kP") +SHORT("Invalid P specifier in FORMAT statement at %0")) +FFEBAD_MSG (FFEBAD_FORMAT_BAD_T_SPEC, FATAL, +LONG("Invalid T specifier in FORMAT statement at %0 -- correct form: Tn") +SHORT("Invalid T specifier in FORMAT statement at %0")) +FFEBAD_MSG (FFEBAD_FORMAT_BAD_TL_SPEC, FATAL, +LONG("Invalid TL specifier in FORMAT statement at %0 -- correct form: TLn") +SHORT("Invalid TL specifier in FORMAT statement at %0")) +FFEBAD_MSG (FFEBAD_FORMAT_BAD_TR_SPEC, FATAL, +LONG("Invalid TR specifier in FORMAT statement at %0 -- correct form: TRn") +SHORT("Invalid TR specifier in FORMAT statement at %0")) +FFEBAD_MSG (FFEBAD_FORMAT_BAD_X_SPEC, FATAL, +LONG("Invalid X specifier in FORMAT statement at %0 -- correct form: nX") +SHORT("Invalid X specifier in FORMAT statement at %0")) +FFEBAD_MSG (FFEBAD_FORMAT_BAD_S_SPEC, FATAL, +LONG("Invalid S specifier in FORMAT statement at %0 -- correct form: S") +SHORT("Invalid S specifier in FORMAT statement at %0")) +FFEBAD_MSG (FFEBAD_FORMAT_BAD_SP_SPEC, FATAL, +LONG("Invalid SP specifier in FORMAT statement at %0 -- correct form: SP") +SHORT("Invalid SP specifier in FORMAT statement at %0")) +FFEBAD_MSG (FFEBAD_FORMAT_BAD_SS_SPEC, FATAL, +LONG("Invalid SS specifier in FORMAT statement at %0 -- correct form: SS") +SHORT("Invalid SS specifier in FORMAT statement at %0")) +FFEBAD_MSG (FFEBAD_FORMAT_BAD_BN_SPEC, FATAL, +LONG("Invalid BN specifier in FORMAT statement at %0 -- correct form: BN") +SHORT("Invalid BN specifier in FORMAT statement at %0")) +FFEBAD_MSG (FFEBAD_FORMAT_BAD_BZ_SPEC, FATAL, +LONG("Invalid BZ specifier in FORMAT statement at %0 -- correct form: BZ") +SHORT("Invalid BZ specifier in FORMAT statement at %0")) +FFEBAD_MSG (FFEBAD_FORMAT_BAD_COLON_SPEC, FATAL, +LONG("Invalid : specifier in FORMAT statement at %0 -- correct form: :") +SHORT("Invalid : specifier in FORMAT statement at %0")) +FFEBAD_MSG (FFEBAD_FORMAT_BAD_H_SPEC, FATAL, +LONG("Invalid H specifier in FORMAT statement at %0 -- correct form: nHcharacters !where n is an unsigned decimal constant, and characters !contains exactly n characters (including spaces)") +SHORT("Invalid H specifier in FORMAT statement at %0")) +FFEBAD_MSG (FFEBAD_FORMAT_MISSING_PAREN, FATAL, "Missing close-parenthese(s) in FORMAT statement at %0") -FFEBAD_MSGS1 (FFEBAD_FORMAT_MISSING_DOT, FATAL, +FFEBAD_MSG (FFEBAD_FORMAT_MISSING_DOT, FATAL, "Missing number following period in FORMAT statement at %0") -FFEBAD_MSGS1 (FFEBAD_FORMAT_MISSING_EXP, FATAL, +FFEBAD_MSG (FFEBAD_FORMAT_MISSING_EXP, FATAL, "Missing number following `E' in FORMAT statement at %0") -FFEBAD_MSGS2 (FFEBAD_FORMAT_EXPR_TOKEN, FATAL, -"Invalid token with FORMAT run-time expression at %0 -- use the traditional operators .LT., .LE., .GT., .GE., .EQ., and .NE. in place of the newer tokens <, <=, >, >=, ==, and !=, because > ends an expression within a FORMAT statement", -"Invalid token with FORMAT run-time expression at %0") -FFEBAD_MSGS1 (FFEBAD_TRAILING_COMMA, WARN, +FFEBAD_MSG (FFEBAD_FORMAT_EXPR_TOKEN, FATAL, +LONG("Invalid token with FORMAT run-time expression at %0 -- use the traditional operators .LT., .LE., .GT., .GE., .EQ., and .NE. in place of the newer tokens <, <=, >, >=, ==, and !=, because > ends an expression within a FORMAT statement") +SHORT("Invalid token with FORMAT run-time expression at %0")) +FFEBAD_MSG (FFEBAD_TRAILING_COMMA, WARN, "Spurious trailing comma preceding terminator at %0") -FFEBAD_MSGS1 (FFEBAD_INTERFACE_ASSIGNMENT, WARN, +FFEBAD_MSG (FFEBAD_INTERFACE_ASSIGNMENT, WARN, "At %0, specify OPERATOR instead of ASSIGNMENT for INTERFACE statement not specifying the assignment operator (=)") -FFEBAD_MSGS1 (FFEBAD_INTERFACE_OPERATOR, WARN, +FFEBAD_MSG (FFEBAD_INTERFACE_OPERATOR, WARN, "At %0, specify ASSIGNMENT instead of OPERATOR for INTERFACE statement specifying the assignment operator (=)") -FFEBAD_MSGS2 (FFEBAD_INTERFACE_NONLETTER, FATAL, -"Defined operator at %0 contains a nonletter -- must contain only letters A-Z (or a-z)", -"Nonletter in defined operator at %0") -FFEBAD_MSGS2 (FFEBAD_INVALID_TYPEDECL_ATTR, FATAL, -"Invalid type-declaration attribute at %0 -- must be one of: DIMENSION(array-spec), EXTERNAL, INTRINSIC, PARAMETER, or SAVE", -"Invalid type-declaration attribute at %0") -FFEBAD_MSGS1 (FFEBAD_INVALID_TYPEDECL_INIT, FATAL, +FFEBAD_MSG (FFEBAD_INTERFACE_NONLETTER, FATAL, +LONG("Defined operator at %0 contains a nonletter -- must contain only letters A-Z (or a-z)") +SHORT("Nonletter in defined operator at %0")) +FFEBAD_MSG (FFEBAD_INVALID_TYPEDECL_ATTR, FATAL, +LONG("Invalid type-declaration attribute at %0 -- must be one of: DIMENSION(array-spec), EXTERNAL, INTRINSIC, PARAMETER, or SAVE") +SHORT("Invalid type-declaration attribute at %0")) +FFEBAD_MSG (FFEBAD_INVALID_TYPEDECL_INIT, FATAL, "Cannot specify =initialization-expr at %0 unless `::' appears before list of objects") -FFEBAD_MSGS1 (FFEBAD_LABEL_USE_DEF, FATAL, +FFEBAD_MSG (FFEBAD_LABEL_USE_DEF, FATAL, "Reference to label at %1 inconsistent with its definition at %0") -FFEBAD_MSGS1 (FFEBAD_LABEL_USE_USE, FATAL, +FFEBAD_MSG (FFEBAD_LABEL_USE_USE, FATAL, "Reference to label at %1 inconsistent with earlier reference at %0") -FFEBAD_MSGS1 (FFEBAD_LABEL_DEF_DO, FATAL, +FFEBAD_MSG (FFEBAD_LABEL_DEF_DO, FATAL, "DO-statement reference to label at %1 follows its definition at %0") -FFEBAD_MSGS1 (FFEBAD_LABEL_BLOCK, WARN, +FFEBAD_MSG (FFEBAD_LABEL_BLOCK, WARN, "Reference to label at %1 is outside block containing definition at %0") -FFEBAD_MSGS1 (FFEBAD_LABEL_DO_BLOCK_DO, FATAL, +FFEBAD_MSG (FFEBAD_LABEL_DO_BLOCK_DO, FATAL, "DO-statement references to label at %0 and %2 separated by unterminated block starting at %1") -FFEBAD_MSGS1 (FFEBAD_LABEL_DO_BLOCK_END, FATAL, +FFEBAD_MSG (FFEBAD_LABEL_DO_BLOCK_END, FATAL, "DO-statement reference to label at %0 and label definition at %2 separated by unterminated block starting at %1") -FFEBAD_MSGS1 (FFEBAD_INVALID_LABEL_DEF, FATAL, +FFEBAD_MSG (FFEBAD_INVALID_LABEL_DEF, FATAL, "Label definition at %0 invalid on this kind of statement") -FFEBAD_MSGS1 (FFEBAD_ORDER_1, FATAL, +FFEBAD_MSG (FFEBAD_ORDER_1, FATAL, "Statement at %0 invalid in this context") -FFEBAD_MSGS1 (FFEBAD_ORDER_2, FATAL, +FFEBAD_MSG (FFEBAD_ORDER_2, FATAL, "Statement at %0 invalid in context established by statement at %1") -FFEBAD_MSGS1 (FFEBAD_CONSTRUCT_NAMED, FATAL, +FFEBAD_MSG (FFEBAD_CONSTRUCT_NAMED, FATAL, "Statement at %0 must specify construct name specified at %1") -FFEBAD_MSGS1 (FFEBAD_CONSTRUCT_NOT_NAMED, FATAL, +FFEBAD_MSG (FFEBAD_CONSTRUCT_NOT_NAMED, FATAL, "Construct name at %0 superfluous, no construct name specified at %1") -FFEBAD_MSGS1 (FFEBAD_CONSTRUCT_WRONG_NAME, FATAL, +FFEBAD_MSG (FFEBAD_CONSTRUCT_WRONG_NAME, FATAL, "Construct name at %0 not the same as construct name at %1") -FFEBAD_MSGS1 (FFEBAD_CONSTRUCT_NO_DO_NAME, FATAL, +FFEBAD_MSG (FFEBAD_CONSTRUCT_NO_DO_NAME, FATAL, "Construct name at %0 does not match construct name for any containing DO constructs") -FFEBAD_MSGS1 (FFEBAD_DO_HAD_LABEL, FATAL, +FFEBAD_MSG (FFEBAD_DO_HAD_LABEL, FATAL, "Label definition missing at %0 for DO construct specifying label at %1") -FFEBAD_MSGS1 (FFEBAD_AFTER_ELSE, FATAL, +FFEBAD_MSG (FFEBAD_AFTER_ELSE, FATAL, "Statement at %0 follows ELSE block for IF construct at %1") -FFEBAD_MSGS1 (FFEBAD_FORMAT_NO_LABEL_DEF, FATAL, +FFEBAD_MSG (FFEBAD_FORMAT_NO_LABEL_DEF, FATAL, "No label definition for FORMAT statement at %0") -FFEBAD_MSGS1 (FFEBAD_SECOND_ELSE_WHERE, FATAL, +FFEBAD_MSG (FFEBAD_SECOND_ELSE_WHERE, FATAL, "Second occurrence of ELSE WHERE at %0 within WHERE at %1") -FFEBAD_MSGS1 (FFEBAD_END_WO, WARN, +FFEBAD_MSG (FFEBAD_END_WO, WARN, "END statement at %0 missing `%A' keyword required for internal or module procedure(s) bounded by %1") -FFEBAD_MSGS1 (FFEBAD_INVALID_MODULE_PROCEDURE, FATAL, +FFEBAD_MSG (FFEBAD_INVALID_MODULE_PROCEDURE, FATAL, "MODULE PROCEDURE statement at %0 disallowed because INTERFACE at %1 specifies no generic name, operator, or assignment") -FFEBAD_MSGS1 (FFEBAD_BLOCKDATA_NOT_NAMED, FATAL, +FFEBAD_MSG (FFEBAD_BLOCKDATA_NOT_NAMED, FATAL, "BLOCK DATA name at %0 superfluous, no name specified at %1") -FFEBAD_MSGS1 (FFEBAD_PROGRAM_NOT_NAMED, FATAL, +FFEBAD_MSG (FFEBAD_PROGRAM_NOT_NAMED, FATAL, "Program name at %0 superfluous, no PROGRAM statement specified at %1") -FFEBAD_MSGS1 (FFEBAD_UNIT_WRONG_NAME, FATAL, +FFEBAD_MSG (FFEBAD_UNIT_WRONG_NAME, FATAL, "Program unit name at %0 not the same as name at %1") -FFEBAD_MSGS1 (FFEBAD_TYPE_WRONG_NAME, FATAL, +FFEBAD_MSG (FFEBAD_TYPE_WRONG_NAME, FATAL, "Type name at %0 not the same as name at %1") -FFEBAD_MSGS1 (FFEBAD_EOF_BEFORE_BLOCK_END, FATAL, +FFEBAD_MSG (FFEBAD_EOF_BEFORE_BLOCK_END, FATAL, "End of source file before end of block started at %0") -FFEBAD_MSGS1 (FFEBAD_UNDEF_LABEL, FATAL, +FFEBAD_MSG (FFEBAD_UNDEF_LABEL, FATAL, "Undefined label, first referenced at %0") -FFEBAD_MSGS1 (FFEBAD_CONFLICTING_SAVES, WARN, +FFEBAD_MSG (FFEBAD_CONFLICTING_SAVES, WARN, "SAVE statement or attribute at %1 cannot be specified along with SAVE statement or attribute at %0") -FFEBAD_MSGS1 (FFEBAD_CONFLICTING_ACCESSES, FATAL, +FFEBAD_MSG (FFEBAD_CONFLICTING_ACCESSES, FATAL, "PUBLIC or PRIVATE statement at %1 cannot be specified along with PUBLIC or PRIVATE statement at %0") -FFEBAD_MSGS1 (FFEBAD_RETURN_IN_MAIN, WARN, +FFEBAD_MSG (FFEBAD_RETURN_IN_MAIN, WARN, "RETURN statement at %0 invalid within a main program unit") -FFEBAD_MSGS1 (FFEBAD_ALTRETURN_IN_PROGRAM, FATAL, +FFEBAD_MSG (FFEBAD_ALTRETURN_IN_PROGRAM, FATAL, "Alternate return specifier at %0 invalid within a main program unit") -FFEBAD_MSGS1 (FFEBAD_ALTRETURN_IN_FUNCTION, FATAL, +FFEBAD_MSG (FFEBAD_ALTRETURN_IN_FUNCTION, FATAL, "Alternate return specifier at %0 invalid within a function") -FFEBAD_MSGS1 (FFEBAD_DERIVTYP_ACCESS, FATAL, +FFEBAD_MSG (FFEBAD_DERIVTYP_ACCESS, FATAL, "Access specifier or PRIVATE statement at %0 invalid for derived-type definition within other than the specification part of a module") -FFEBAD_MSGS1 (FFEBAD_DERIVTYP_ACCESS_FIRST, FATAL, +FFEBAD_MSG (FFEBAD_DERIVTYP_ACCESS_FIRST, FATAL, "Access specifier at %0 must immediately follow derived-type statement at %1 with no intervening statements") -FFEBAD_MSGS1 (FFEBAD_DERIVTYP_NO_COMPONENTS, FATAL, +FFEBAD_MSG (FFEBAD_DERIVTYP_NO_COMPONENTS, FATAL, "No components specified as of %0 for derived-type definition beginning at %1") -FFEBAD_MSGS1 (FFEBAD_STRUCT_NO_COMPONENTS, FATAL, +FFEBAD_MSG (FFEBAD_STRUCT_NO_COMPONENTS, FATAL, "No components specified as of %0 for structure definition beginning at %1") -FFEBAD_MSGS1 (FFEBAD_STRUCT_MISSING_NAME, FATAL, +FFEBAD_MSG (FFEBAD_STRUCT_MISSING_NAME, FATAL, "Missing structure name for outer structure definition at %0") -FFEBAD_MSGS1 (FFEBAD_STRUCT_IGNORING_FIELD, FATAL, +FFEBAD_MSG (FFEBAD_STRUCT_IGNORING_FIELD, FATAL, "Field names at %0 for outer structure definition -- specify them in a subsequent RECORD statement instead") -FFEBAD_MSGS1 (FFEBAD_STRUCT_MISSING_FIELD, FATAL, +FFEBAD_MSG (FFEBAD_STRUCT_MISSING_FIELD, FATAL, "Missing field name(s) for structure definition at %0 within structure definition at %1") -FFEBAD_MSGS1 (FFEBAD_MAP_NO_COMPONENTS, FATAL, +FFEBAD_MSG (FFEBAD_MAP_NO_COMPONENTS, FATAL, "No components specified as of %0 for map beginning at %1") -FFEBAD_MSGS1 (FFEBAD_UNION_NO_TWO_MAPS, FATAL, +FFEBAD_MSG (FFEBAD_UNION_NO_TWO_MAPS, FATAL, "Zero or one maps specified as of %0 for union beginning at %1 -- at least two are required") -FFEBAD_MSGS1 (FFEBAD_MISSING_SPECIFIER, FATAL, +FFEBAD_MSG (FFEBAD_MISSING_SPECIFIER, FATAL, "Missing %A specifier in statement at %0") -FFEBAD_MSGS1 (FFEBAD_NAMELIST_ITEMS, FATAL, +FFEBAD_MSG (FFEBAD_NAMELIST_ITEMS, FATAL, "Items in I/O list starting at %0 invalid for namelist-directed I/O") -FFEBAD_MSGS1 (FFEBAD_CONFLICTING_SPECS, FATAL, +FFEBAD_MSG (FFEBAD_CONFLICTING_SPECS, FATAL, "Conflicting I/O control specifications at %0 and %1") -FFEBAD_MSGS1 (FFEBAD_NO_UNIT_SPEC, FATAL, +FFEBAD_MSG (FFEBAD_NO_UNIT_SPEC, FATAL, "No UNIT= specifier in I/O control list at %0") -FFEBAD_MSGS1 (FFEBAD_MISSING_ADVANCE_SPEC, FATAL, +FFEBAD_MSG (FFEBAD_MISSING_ADVANCE_SPEC, FATAL, "Specification at %0 requires ADVANCE=`NO' specification in same I/O control list") -FFEBAD_MSGS1 (FFEBAD_MISSING_FORMAT_SPEC, FATAL, +FFEBAD_MSG (FFEBAD_MISSING_FORMAT_SPEC, FATAL, "Specification at %0 requires explicit FMT= specification in same I/O control list") -FFEBAD_MSGS2 (FFEBAD_SPEC_VALUE, FATAL, -"Unrecognized value for character constant at %0 -- expecting %A", -"Unrecognized value for character constant at %0") -FFEBAD_MSGS1 (FFEBAD_CASE_SECOND_DEFAULT, FATAL, +FFEBAD_MSG (FFEBAD_SPEC_VALUE, FATAL, +LONG("Unrecognized value for character constant at %0 -- expecting %A") +SHORT("Unrecognized value for character constant at %0")) +FFEBAD_MSG (FFEBAD_CASE_SECOND_DEFAULT, FATAL, "Second occurrence of CASE DEFAULT at %0 within SELECT CASE at %1") -FFEBAD_MSGS1 (FFEBAD_CASE_DUPLICATE, FATAL, +FFEBAD_MSG (FFEBAD_CASE_DUPLICATE, FATAL, "Duplicate or overlapping case values/ranges at %0 and %1") -FFEBAD_MSGS1 (FFEBAD_CASE_TYPE_DISAGREE, FATAL, +FFEBAD_MSG (FFEBAD_CASE_TYPE_DISAGREE, FATAL, "Type and/or kind-type parameter disagreement between CASE value or value within range at %0 and SELECT CASE at %1") -FFEBAD_MSGS1 (FFEBAD_CASE_LOGICAL_RANGE, FATAL, +FFEBAD_MSG (FFEBAD_CASE_LOGICAL_RANGE, FATAL, "Range specification at %0 invalid for CASE statement within logical-type SELECT CASE statement") -FFEBAD_MSGS2 (FFEBAD_CASE_BAD_RANGE, FATAL, -"Range specification at %0 invalid -- at least one expression must be specified, or use CASE DEFAULT", -"Range specification at %0 invalid") -FFEBAD_MSGS2 (FFEBAD_CASE_RANGE_USELESS, INFORM, -"Range specification at %0 useless; first expression greater than second expression in range, so range can never be matched by any selection expression", -"Useless range at %0") -FFEBAD_MSGS1 (FFEBAD_F90, FATAL, +FFEBAD_MSG (FFEBAD_CASE_BAD_RANGE, FATAL, +LONG("Range specification at %0 invalid -- at least one expression must be specified, or use CASE DEFAULT") +SHORT("Range specification at %0 invalid")) +FFEBAD_MSG (FFEBAD_CASE_RANGE_USELESS, INFORM, +LONG("Range specification at %0 useless; first expression greater than second expression in range, so range can never be matched by any selection expression") +SHORT("Useless range at %0")) +FFEBAD_MSG (FFEBAD_F90, FATAL, "Fortran 90 feature at %0 unsupported") -FFEBAD_MSGS2 (FFEBAD_KINDTYPE, FATAL, -"Invalid kind at %0 for type at %1 -- unsupported or not permitted", -"Invalid kind at %0 for type at %1") -FFEBAD_MSGS2 (FFEBAD_BAD_IMPLICIT, FATAL, -"Cannot establish implicit type for initial letter `%A' at %0 -- already explicitly established or used to set implicit type of some name, or backwards order of letters in letter range", -"Cannot establish implicit type for initial letter `%A' at %0") -FFEBAD_MSGS1 (FFEBAD_SYMERR, FATAL, +FFEBAD_MSG (FFEBAD_KINDTYPE, FATAL, +LONG("Invalid kind at %0 for type at %1 -- unsupported or not permitted") +SHORT("Invalid kind at %0 for type at %1")) +FFEBAD_MSG (FFEBAD_BAD_IMPLICIT, FATAL, +LONG("Cannot establish implicit type for initial letter `%A' at %0 -- already explicitly established or used to set implicit type of some name, or backwards order of letters in letter range") +SHORT("Cannot establish implicit type for initial letter `%A' at %0")) +FFEBAD_MSG (FFEBAD_SYMERR, FATAL, "Invalid declaration of or reference to symbol `%A' at %0 [initially seen at %1]") -FFEBAD_MSGS2 (FFEBAD_LABEL_WRONG_PLACE, FATAL, -"Label definition %A (at %0) invalid -- must be in columns 1-5", -"Invalid label definition %A (at %0)") -FFEBAD_MSGS1 (FFEBAD_NULL_ELEMENT, FATAL, +FFEBAD_MSG (FFEBAD_LABEL_WRONG_PLACE, FATAL, +LONG("Label definition %A (at %0) invalid -- must be in columns 1-5") +SHORT("Invalid label definition %A (at %0)")) +FFEBAD_MSG (FFEBAD_NULL_ELEMENT, FATAL, "Null element at %0 for array reference at %1") -FFEBAD_MSGS1 (FFEBAD_TOO_FEW_ELEMENTS, FATAL, +FFEBAD_MSG (FFEBAD_TOO_FEW_ELEMENTS, FATAL, "Too few elements (%A missing) as of %0 for array reference at %1") -FFEBAD_MSGS1 (FFEBAD_TOO_MANY_ELEMENTS, FATAL, +FFEBAD_MSG (FFEBAD_TOO_MANY_ELEMENTS, FATAL, "Too many elements as of %0 for array reference at %1") -FFEBAD_MSGS1 (FFEBAD_MISSING_COLON_IN_SUBSTR, FATAL, +FFEBAD_MSG (FFEBAD_MISSING_COLON_IN_SUBSTR, FATAL, "Missing colon as of %0 in substring reference for %1") -FFEBAD_MSGS1 (FFEBAD_BAD_SUBSTR, FATAL, +FFEBAD_MSG (FFEBAD_BAD_SUBSTR, FATAL, "Invalid use at %0 of substring operator on %1") -FFEBAD_MSGS1 (FFEBAD_RANGE_SUBSTR, WARN, +FFEBAD_MSG (FFEBAD_RANGE_SUBSTR, WARN, "Substring begin/end point at %0 out of defined range") -FFEBAD_MSGS1 (FFEBAD_RANGE_ARRAY, WARN, +FFEBAD_MSG (FFEBAD_RANGE_ARRAY, WARN, "Array element value at %0 out of defined range") -FFEBAD_MSGS1 (FFEBAD_EXPR_WRONG, FATAL, +FFEBAD_MSG (FFEBAD_EXPR_WRONG, FATAL, "Expression at %0 has incorrect data type or rank for its context") -FFEBAD_MSGS1 (FFEBAD_DIV_BY_ZERO, WARN, +FFEBAD_MSG (FFEBAD_DIV_BY_ZERO, WARN, "Division by 0 (zero) at %0 (IEEE not yet supported)") -FFEBAD_MSGS1 (FFEBAD_DO_STEP_ZERO, FATAL, +FFEBAD_MSG (FFEBAD_DO_STEP_ZERO, FATAL, "%A step count known to be 0 (zero) at %0") -FFEBAD_MSGS1 (FFEBAD_DO_END_OVERFLOW, WARN, +FFEBAD_MSG (FFEBAD_DO_END_OVERFLOW, WARN, "%A end value plus step count known to overflow at %0") -FFEBAD_MSGS1 (FFEBAD_DO_IMP_OVERFLOW, WARN, +FFEBAD_MSG (FFEBAD_DO_IMP_OVERFLOW, WARN, "%A begin, end, and step-count values known to result in implementation-dependent behavior due to overflow(s) in intermediate calculations at %0") -FFEBAD_MSGS1 (FFEBAD_DO_NULL, WARN, +FFEBAD_MSG (FFEBAD_DO_NULL, WARN, "%A begin, end, and step-count values known to result in no iterations at %0") -FFEBAD_MSGS1 (FFEBAD_BAD_TYPES, FATAL, +FFEBAD_MSG (FFEBAD_BAD_TYPES, FATAL, "Type disagreement between expressions at %0 and %1") -FFEBAD_MSGS2 (FFEBAD_FORMAT_EXPR_SPEC, FATAL, -"Run-time expression at %0 in FORMAT statement that does not follow the first executable statement in the program unit -- move the statement", -"FORMAT at %0 with run-time expression must follow first executable statement") -FFEBAD_MSGS2 (FFEBAD_BAD_IMPDO, FATAL, -"Unexpected token at %0 in implied-DO construct at %1 -- form of implied-DO is `(item-list,do-var=start,end[,incr])'", -"Unexpected token at %0 in implied-DO construct at %1") -FFEBAD_MSGS1 (FFEBAD_BAD_IMPDCL, FATAL, +FFEBAD_MSG (FFEBAD_FORMAT_EXPR_SPEC, FATAL, +LONG("Run-time expression at %0 in FORMAT statement that does not follow the first executable statement in the program unit -- move the statement") +SHORT("FORMAT at %0 with run-time expression must follow first executable statement")) +FFEBAD_MSG (FFEBAD_BAD_IMPDO, FATAL, +LONG("Unexpected token at %0 in implied-DO construct at %1 -- form of implied-DO is `(item-list,do-var=start,end[,incr])'") +SHORT("Unexpected token at %0 in implied-DO construct at %1")) +FFEBAD_MSG (FFEBAD_BAD_IMPDCL, FATAL, "No specification for implied-DO iterator `%A' at %0") -FFEBAD_MSGS1 (FFEBAD_IMPDO_PAREN, WARN, +FFEBAD_MSG (FFEBAD_IMPDO_PAREN, WARN, "Gratuitous parentheses surround implied-DO construct at %0") -FFEBAD_MSGS1 (FFEBAD_ZERO_SIZE, FATAL, +FFEBAD_MSG (FFEBAD_ZERO_SIZE, FATAL, "Zero-size specification invalid at %0") -FFEBAD_MSGS1 (FFEBAD_ZERO_ARRAY, FATAL, +FFEBAD_MSG (FFEBAD_ZERO_ARRAY, FATAL, "Zero-size array at %0") -FFEBAD_MSGS1 (FFEBAD_BAD_COMPLEX, FATAL, +FFEBAD_MSG (FFEBAD_BAD_COMPLEX, FATAL, "Target machine does not support complex entity of kind specified at %0") -FFEBAD_MSGS1 (FFEBAD_BAD_DBLCMPLX, FATAL, +FFEBAD_MSG (FFEBAD_BAD_DBLCMPLX, FATAL, "Target machine does not support DOUBLE COMPLEX, specified at %0") -FFEBAD_MSGS1 (FFEBAD_BAD_POWER, WARN, +FFEBAD_MSG (FFEBAD_BAD_POWER, WARN, "Attempt to raise constant zero to a power at %0") -FFEBAD_MSGS2 (FFEBAD_BOOL_ARGS_TYPE, FATAL, -"Boolean/logical operator at %0 must operate on two subexpressions of logical type, but neither subexpression at %1 or %2 is of logical type", -"Invalid operands at %1 and %2 for boolean operator at %0") -FFEBAD_MSGS2 (FFEBAD_BOOL_ARG_TYPE, FATAL, -"Boolean/logical operator at %0 must operate on two subexpressions of logical type, but the subexpression at %1 is not of logical type", -"Invalid operand at %1 for boolean operator at %0") -FFEBAD_MSGS2 (FFEBAD_BOOL_ARG_KIND, FATAL, -"Boolean/logical operator at %0 must operate on two scalar (not array) subexpressions, two function invocations returning logical scalars, or a combination of both -- but the subexpression at %1 is %A", -"Invalid operand (is %A) at %1 for boolean operator at %0") -FFEBAD_MSGS2 (FFEBAD_NOT_ARG_TYPE, FATAL, -".NOT. operator at %0 must operate on subexpression of logical type, but the subexpression at %1 is not of logical type", -"Invalid operand at %1 for .NOT. operator at %0") -FFEBAD_MSGS2 (FFEBAD_NOT_ARG_KIND, FATAL, -".NOT. operator at %0 must operate on scalar subexpressions -- but the subexpression at %1 is %A", -"Invalid operand (is %A) at %1 for .NOT. operator at %0") -FFEBAD_MSGS2 (FFEBAD_EQOP_ARGS_TYPE, FATAL, -"Equality operator at %0 must operate on two subexpressions of arithmetic or character type, but neither subexpression at %1 or %2 is of arithmetic or character type", -"Invalid operands at %1 and %2 for equality operator at %0") -FFEBAD_MSGS2 (FFEBAD_EQOP_ARG_TYPE, FATAL, -"Equality operator at %0 must operate on two subexpressions of arithmetic or character type, but the subexpression at %1 is not of arithmetic or character type", -"Invalid operand at %1 for equality operator at %0") -FFEBAD_MSGS2 (FFEBAD_EQOP_ARG_KIND, FATAL, -"Equality operator at %0 must operate on two scalar (not array) subexpressions, two function invocations returning arithmetic or character scalars, or a combination of both -- but the subexpression at %1 is %A", -"Invalid operand (is %A) at %1 for equality operator at %0") -FFEBAD_MSGS2 (FFEBAD_RELOP_ARGS_TYPE, FATAL, -"Relational operator at %0 must operate on two subexpressions of integer, real, or character type, but neither subexpression at %1 or %2 is of integer, real, or character type", -"Invalid operands at %1 and %2 for relational operator at %0") -FFEBAD_MSGS2 (FFEBAD_RELOP_ARG_TYPE, FATAL, -"Relational operator at %0 must operate on two subexpressions of integer, real, or character type, but the subexpression at %1 is not of integer, real, or character type", -"Invalid operand at %1 for relational operator at %0") -FFEBAD_MSGS2 (FFEBAD_RELOP_ARG_KIND, FATAL, -"Relational operator at %0 must operate on two scalar (not array) subexpressions, two function invocations returning integer, real, or character scalars, or a combination of both -- but the subexpression at %1 is %A", -"Invalid operand (is %A) at %1 for relational operator at %0") -FFEBAD_MSGS2 (FFEBAD_INTRINSIC_REF, FATAL, -"Reference to intrinsic `%A' at %0 invalid -- one or more arguments have incorrect type", -"Invalid reference to intrinsic `%A' at %0") -FFEBAD_MSGS2 (FFEBAD_INTRINSIC_TOOFEW, FATAL, -"Too few arguments passed to intrinsic `%A' at %0", -"Too few arguments for intrinsic `%A' at %0") -FFEBAD_MSGS2 (FFEBAD_INTRINSIC_TOOMANY, FATAL, -"Too many arguments passed to intrinsic `%A' at %0", -"Too many arguments for intrinsic `%A' at %0") -FFEBAD_MSGS2 (FFEBAD_INTRINSIC_DISABLED, FATAL, -"Reference to disabled intrinsic `%A' at %0", -"Disabled intrinsic `%A' at %0") -FFEBAD_MSGS2 (FFEBAD_INTRINSIC_IS_SUBR, FATAL, -"Reference to intrinsic subroutine `%A' as if it were a function at %0", -"Function reference to intrinsic subroutine `%A' at %0") -FFEBAD_MSGS2 (FFEBAD_INTRINSIC_IS_FUNC, FATAL, -"Reference to intrinsic function `%A' as if it were a subroutine at %0", -"Subroutine reference to intrinsic function `%A' at %0") -FFEBAD_MSGS2 (FFEBAD_INTRINSIC_UNIMPL, FATAL, -"Reference to unimplemented intrinsic `%A' at %0 -- use EXTERNAL to reference user-written procedure with this name", -"Unimplemented intrinsic `%A' at %0") -FFEBAD_MSGS2 (FFEBAD_INTRINSIC_UNIMPLW, WARN, -"Reference to unimplemented intrinsic `%A' at %0 (assumed EXTERNAL)", -"Unimplemented intrinsic `%A' at %0 (assumed EXTERNAL)") -FFEBAD_MSGS1 (FFEBAD_INTRINSIC_AMBIG, FATAL, +FFEBAD_MSG (FFEBAD_BOOL_ARGS_TYPE, FATAL, +LONG("Boolean/logical operator at %0 must operate on two subexpressions of logical type, but neither subexpression at %1 or %2 is of logical type") +SHORT("Invalid operands at %1 and %2 for boolean operator at %0")) +FFEBAD_MSG (FFEBAD_BOOL_ARG_TYPE, FATAL, +LONG("Boolean/logical operator at %0 must operate on two subexpressions of logical type, but the subexpression at %1 is not of logical type") +SHORT("Invalid operand at %1 for boolean operator at %0")) +FFEBAD_MSG (FFEBAD_BOOL_ARG_KIND, FATAL, +LONG("Boolean/logical operator at %0 must operate on two scalar (not array) subexpressions, two function invocations returning logical scalars, or a combination of both -- but the subexpression at %1 is %A") +SHORT("Invalid operand (is %A) at %1 for boolean operator at %0")) +FFEBAD_MSG (FFEBAD_NOT_ARG_TYPE, FATAL, +LONG(".NOT. operator at %0 must operate on subexpression of logical type, but the subexpression at %1 is not of logical type") +SHORT("Invalid operand at %1 for .NOT. operator at %0")) +FFEBAD_MSG (FFEBAD_NOT_ARG_KIND, FATAL, +LONG(".NOT. operator at %0 must operate on scalar subexpressions -- but the subexpression at %1 is %A") +SHORT("Invalid operand (is %A) at %1 for .NOT. operator at %0")) +FFEBAD_MSG (FFEBAD_EQOP_ARGS_TYPE, FATAL, +LONG("Equality operator at %0 must operate on two subexpressions of arithmetic or character type, but neither subexpression at %1 or %2 is of arithmetic or character type") +SHORT("Invalid operands at %1 and %2 for equality operator at %0")) +FFEBAD_MSG (FFEBAD_EQOP_ARG_TYPE, FATAL, +LONG("Equality operator at %0 must operate on two subexpressions of arithmetic or character type, but the subexpression at %1 is not of arithmetic or character type") +SHORT("Invalid operand at %1 for equality operator at %0")) +FFEBAD_MSG (FFEBAD_EQOP_ARG_KIND, FATAL, +LONG("Equality operator at %0 must operate on two scalar (not array) subexpressions, two function invocations returning arithmetic or character scalars, or a combination of both -- but the subexpression at %1 is %A") +SHORT("Invalid operand (is %A) at %1 for equality operator at %0")) +FFEBAD_MSG (FFEBAD_RELOP_ARGS_TYPE, FATAL, +LONG("Relational operator at %0 must operate on two subexpressions of integer, real, or character type, but neither subexpression at %1 or %2 is of integer, real, or character type") +SHORT("Invalid operands at %1 and %2 for relational operator at %0")) +FFEBAD_MSG (FFEBAD_RELOP_ARG_TYPE, FATAL, +LONG("Relational operator at %0 must operate on two subexpressions of integer, real, or character type, but the subexpression at %1 is not of integer, real, or character type") +SHORT("Invalid operand at %1 for relational operator at %0")) +FFEBAD_MSG (FFEBAD_RELOP_ARG_KIND, FATAL, +LONG("Relational operator at %0 must operate on two scalar (not array) subexpressions, two function invocations returning integer, real, or character scalars, or a combination of both -- but the subexpression at %1 is %A") +SHORT("Invalid operand (is %A) at %1 for relational operator at %0")) +FFEBAD_MSG (FFEBAD_INTRINSIC_REF, FATAL, +LONG("Reference to intrinsic `%A' at %0 invalid -- one or more arguments have incorrect type") +SHORT("Invalid reference to intrinsic `%A' at %0")) +FFEBAD_MSG (FFEBAD_INTRINSIC_TOOFEW, FATAL, +LONG("Too few arguments passed to intrinsic `%A' at %0") +SHORT("Too few arguments for intrinsic `%A' at %0")) +FFEBAD_MSG (FFEBAD_INTRINSIC_TOOMANY, FATAL, +LONG("Too many arguments passed to intrinsic `%A' at %0") +SHORT("Too many arguments for intrinsic `%A' at %0")) +FFEBAD_MSG (FFEBAD_INTRINSIC_DISABLED, FATAL, +LONG("Reference to disabled intrinsic `%A' at %0") +SHORT("Disabled intrinsic `%A' at %0")) +FFEBAD_MSG (FFEBAD_INTRINSIC_IS_SUBR, FATAL, +LONG("Reference to intrinsic subroutine `%A' as if it were a function at %0") +SHORT("Function reference to intrinsic subroutine `%A' at %0")) +FFEBAD_MSG (FFEBAD_INTRINSIC_IS_FUNC, FATAL, +LONG("Reference to intrinsic function `%A' as if it were a subroutine at %0") +SHORT("Subroutine reference to intrinsic function `%A' at %0")) +FFEBAD_MSG (FFEBAD_INTRINSIC_UNIMPL, FATAL, +LONG("Reference to unimplemented intrinsic `%A' at %0 -- use EXTERNAL to reference user-written procedure with this name") +SHORT("Unimplemented intrinsic `%A' at %0")) +FFEBAD_MSG (FFEBAD_INTRINSIC_UNIMPLW, WARN, +LONG("Reference to unimplemented intrinsic `%A' at %0 (assumed EXTERNAL)") +SHORT("Unimplemented intrinsic `%A' at %0 (assumed EXTERNAL)")) +FFEBAD_MSG (FFEBAD_INTRINSIC_AMBIG, FATAL, "Reference to generic intrinsic `%A' at %0 could be to form %B or %C") -FFEBAD_MSGS1 (FFEBAD_INTRINSIC_CMPAMBIG, FATAL, +FFEBAD_MSG (FFEBAD_INTRINSIC_CMPAMBIG, FATAL, "Ambiguous use of intrinsic `%A' at %0 [info -f g77 M CMPAMBIG]") -FFEBAD_MSGS1 (FFEBAD_INTRINSIC_EXPIMP, WARN, +FFEBAD_MSG (FFEBAD_INTRINSIC_EXPIMP, WARN, "Intrinsic `%A' referenced %Bly at %0, %Cly at %1 [info -f g77 M EXPIMP]") -FFEBAD_MSGS1 (FFEBAD_INTRINSIC_GLOBAL, WARN, +FFEBAD_MSG (FFEBAD_INTRINSIC_GLOBAL, WARN, "Same name `%A' used for %B at %0 and %C at %1 [info -f g77 M INTGLOB]") -FFEBAD_MSGS1 (FFEBAD_INTRINSIC_TYPE, WARN, +FFEBAD_MSG (FFEBAD_INTRINSIC_TYPE, WARN, "Explicit type declaration for intrinsic `%A' disagrees with invocation at %0") -FFEBAD_MSGS1 (FFEBAD_OPEN_INCLUDE, FATAL, +FFEBAD_MSG (FFEBAD_OPEN_INCLUDE, FATAL, "Unable to open INCLUDE file `%A' at %0") -FFEBAD_MSGS2 (FFEBAD_DOITER, FATAL, -"Attempt to modify variable `%A' at %0 while it serves as DO-loop iterator at %1", -"Modification of DO-loop iterator `%A' at %0") -FFEBAD_MSGS2 (FFEBAD_DOITER_IMPDO, FATAL, -"Attempt to modify variable `%A' via item #%B in list at %0 while it serves as implied-DO iterator at %1", -"Modification of DO-loop iterator `%A' at %0") -FFEBAD_MSGS2 (FFEBAD_TOO_MANY_DIMS, FATAL, -"Array has too many dimensions, as of dimension specifier at %0", -"Too many dimensions at %0") -FFEBAD_MSGS1 (FFEBAD_NULL_ARGUMENT, FATAL, +FFEBAD_MSG (FFEBAD_DOITER, FATAL, +LONG("Attempt to modify variable `%A' at %0 while it serves as DO-loop iterator at %1") +SHORT("Modification of DO-loop iterator `%A' at %0")) +FFEBAD_MSG (FFEBAD_DOITER_IMPDO, FATAL, +LONG("Attempt to modify variable `%A' via item #%B in list at %0 while it serves as implied-DO iterator at %1") +SHORT("Modification of DO-loop iterator `%A' at %0")) +FFEBAD_MSG (FFEBAD_TOO_MANY_DIMS, FATAL, +LONG("Array has too many dimensions, as of dimension specifier at %0") +SHORT("Too many dimensions at %0")) +FFEBAD_MSG (FFEBAD_NULL_ARGUMENT, FATAL, "Null argument at %0 for statement function reference at %1") -FFEBAD_MSGS1 (FFEBAD_NULL_ARGUMENT_W, WARN, +FFEBAD_MSG (FFEBAD_NULL_ARGUMENT_W, WARN, "Null argument at %0 for procedure invocation at %1") -FFEBAD_MSGS1 (FFEBAD_TOO_FEW_ARGUMENTS, FATAL, +FFEBAD_MSG (FFEBAD_TOO_FEW_ARGUMENTS, FATAL, "%A too few arguments (starting with dummy argument `%B') as of %0 for statement function reference at %1") -FFEBAD_MSGS1 (FFEBAD_TOO_MANY_ARGUMENTS, FATAL, +FFEBAD_MSG (FFEBAD_TOO_MANY_ARGUMENTS, FATAL, "%A too many arguments as of %0 for statement function reference at %1") -FFEBAD_MSGS1 (FFEBAD_ARRAY_AS_SFARG, FATAL, +FFEBAD_MSG (FFEBAD_ARRAY_AS_SFARG, FATAL, "Array supplied at %1 for dummy argument `%A' in statement function reference at %0") -FFEBAD_MSGS1 (FFEBAD_FORMAT_UNSUPPORTED, FATAL, +FFEBAD_MSG (FFEBAD_FORMAT_UNSUPPORTED, FATAL, "Unsupported FORMAT specifier at %0") -FFEBAD_MSGS1 (FFEBAD_FORMAT_VARIABLE, FATAL, +FFEBAD_MSG (FFEBAD_FORMAT_VARIABLE, FATAL, "Variable-expression FORMAT specifier at %0 -- unsupported") -FFEBAD_MSGS2 (FFEBAD_OPEN_UNSUPPORTED, FATAL, -"Unsupported OPEN control item at %0 -- ACTION=, ASSOCIATEVARIABLE=, BLOCKSIZE=, BUFFERCOUNT=, CARRIAGECONTROL=, DEFAULTFILE=, DELIM=, DISPOSE=, EXTENDSIZE=, INITIALSIZE=, KEY=, MAXREC=, NOSPANBLOCKS, ORGANIZATION=, PAD=, POSITION=, READONLY=, RECORDTYPE=, SHARED=, and USEROPEN= are not supported", -"Unsupported OPEN control item at %0") -FFEBAD_MSGS2 (FFEBAD_INQUIRE_UNSUPPORTED, FATAL, -"Unsupported INQUIRE control item at %0 -- ACTION=, CARRIAGECONTROL=, DEFAULTFILE=, DELIM=, KEYED=, ORGANIZATION=, PAD=, POSITION=, READ=, READWRITE=, RECORDTYPE=, and WRITE= are not supported", -"Unsupported INQUIRE control item at %0") -FFEBAD_MSGS2 (FFEBAD_READ_UNSUPPORTED, FATAL, -"Unsupported READ control item at %0 -- ADVANCE=, EOR=, KEYEQ=, KEYGE=, KEYGT=, KEYID=, NULLS=, and SIZE= are not supported", -"Unsupported READ control item at %0") -FFEBAD_MSGS2 (FFEBAD_WRITE_UNSUPPORTED, FATAL, -"Unsupported WRITE control item at %0 -- ADVANCE= and EOR= are not supported", -"Unsupported WRITE control item at %0") -FFEBAD_MSGS1 (FFEBAD_VXT_UNSUPPORTED, FATAL, +FFEBAD_MSG (FFEBAD_OPEN_UNSUPPORTED, FATAL, +LONG("Unsupported OPEN control item at %0 -- ACTION=, ASSOCIATEVARIABLE=, BLOCKSIZE=, BUFFERCOUNT=, CARRIAGECONTROL=, DEFAULTFILE=, DELIM=, DISPOSE=, EXTENDSIZE=, INITIALSIZE=, KEY=, MAXREC=, NOSPANBLOCKS, ORGANIZATION=, PAD=, POSITION=, READONLY=, RECORDTYPE=, SHARED=, and USEROPEN= are not supported") +SHORT("Unsupported OPEN control item at %0")) +FFEBAD_MSG (FFEBAD_INQUIRE_UNSUPPORTED, FATAL, +LONG("Unsupported INQUIRE control item at %0 -- ACTION=, CARRIAGECONTROL=, DEFAULTFILE=, DELIM=, KEYED=, ORGANIZATION=, PAD=, POSITION=, READ=, READWRITE=, RECORDTYPE=, and WRITE= are not supported") +SHORT("Unsupported INQUIRE control item at %0")) +FFEBAD_MSG (FFEBAD_READ_UNSUPPORTED, FATAL, +LONG("Unsupported READ control item at %0 -- ADVANCE=, EOR=, KEYEQ=, KEYGE=, KEYGT=, KEYID=, NULLS=, and SIZE= are not supported") +SHORT("Unsupported READ control item at %0")) +FFEBAD_MSG (FFEBAD_WRITE_UNSUPPORTED, FATAL, +LONG("Unsupported WRITE control item at %0 -- ADVANCE= and EOR= are not supported") +SHORT("Unsupported WRITE control item at %0")) +FFEBAD_MSG (FFEBAD_VXT_UNSUPPORTED, FATAL, "Unsupported VXT statement at %0") -FFEBAD_MSGS1 (FFEBAD_DATA_REINIT, FATAL, +FFEBAD_MSG (FFEBAD_DATA_REINIT, FATAL, "Attempt to specify second initial value for `%A' at %0") -FFEBAD_MSGS1 (FFEBAD_DATA_TOOFEW, FATAL, +FFEBAD_MSG (FFEBAD_DATA_TOOFEW, FATAL, "Too few initial values in list of initializers for `%A' at %0") -FFEBAD_MSGS1 (FFEBAD_DATA_TOOMANY, FATAL, +FFEBAD_MSG (FFEBAD_DATA_TOOMANY, FATAL, "Too many initial values in list of initializers starting at %0") -FFEBAD_MSGS1 (FFEBAD_DATA_RANGE, FATAL, +FFEBAD_MSG (FFEBAD_DATA_RANGE, FATAL, "Array or substring specification for `%A' out of range in statement at %0") -FFEBAD_MSGS1 (FFEBAD_DATA_SUBSCRIPT, FATAL, +FFEBAD_MSG (FFEBAD_DATA_SUBSCRIPT, FATAL, "Array subscript #%B out of range for initialization of `%A' in statement at %0") -FFEBAD_MSGS1 (FFEBAD_DATA_ZERO, FATAL, +FFEBAD_MSG (FFEBAD_DATA_ZERO, FATAL, "Implied do-loop step count of 0 (zero) for iteration variable `%A' in statement at %0") -FFEBAD_MSGS1 (FFEBAD_DATA_EMPTY, FATAL, +FFEBAD_MSG (FFEBAD_DATA_EMPTY, FATAL, "Implied do-loop iteration count of 0 (zero) for iteration variable `%A' in statement at %0") -FFEBAD_MSGS1 (FFEBAD_DATA_EVAL, FATAL, +FFEBAD_MSG (FFEBAD_DATA_EVAL, FATAL, "Not an integer constant expression in implied do-loop in statement at %0") -FFEBAD_MSGS1 (FFEBAD_DATA_MULTIPLE, FATAL, +FFEBAD_MSG (FFEBAD_DATA_MULTIPLE, FATAL, "Attempt to specify second initial value for element of `%A' at %0") -FFEBAD_MSGS1 (FFEBAD_EQUIV_COMMON, FATAL, +FFEBAD_MSG (FFEBAD_EQUIV_COMMON, FATAL, "Attempt to EQUIVALENCE common areas `%A' and `%B' at %0") -FFEBAD_MSGS1 (FFEBAD_EQUIV_ALIGN, FATAL, +FFEBAD_MSG (FFEBAD_EQUIV_ALIGN, FATAL, "Can't place `%A' as directed by EQUIVALENCE due to alignment restrictions") -FFEBAD_MSGS1 (FFEBAD_EQUIV_MISMATCH, FATAL, +FFEBAD_MSG (FFEBAD_EQUIV_MISMATCH, FATAL, "Mismatched EQUIVALENCE requirements for placement of `%A' at both %C and %D bytes offset from `%B'") -FFEBAD_MSGS1 (FFEBAD_EQUIV_RANGE, FATAL, +FFEBAD_MSG (FFEBAD_EQUIV_RANGE, FATAL, "Array or substring specification for `%A' out of range in EQUIVALENCE statement") -FFEBAD_MSGS1 (FFEBAD_EQUIV_SUBSTR, FATAL, +FFEBAD_MSG (FFEBAD_EQUIV_SUBSTR, FATAL, "Substring of non-CHARACTER entity `%A' in EQUIVALENCE statement") -FFEBAD_MSGS1 (FFEBAD_EQUIV_ARRAY, FATAL, +FFEBAD_MSG (FFEBAD_EQUIV_ARRAY, FATAL, "Array reference to scalar variable `%A' in EQUIVALENCE statement") -FFEBAD_MSGS1 (FFEBAD_EQUIV_SUBSCRIPT, WARN, +FFEBAD_MSG (FFEBAD_EQUIV_SUBSCRIPT, WARN, "Array subscript #%B out of range for EQUIVALENCE of `%A'") -FFEBAD_MSGS2 (FFEBAD_COMMON_PAD, WARN, -"Padding of %A %D required before `%B' in common block `%C' at %0 -- consider reordering members, largest-type-size first", -"Padding of %A %D required before `%B' in common block `%C' at %0") -FFEBAD_MSGS1 (FFEBAD_COMMON_NEG, FATAL, +FFEBAD_MSG (FFEBAD_COMMON_PAD, WARN, +LONG("Padding of %A %D required before `%B' in common block `%C' at %0 -- consider reordering members, largest-type-size first") +SHORT("Padding of %A %D required before `%B' in common block `%C' at %0")) +FFEBAD_MSG (FFEBAD_COMMON_NEG, FATAL, "Attempt to extend COMMON area beyond its starting point via EQUIVALENCE of `%A'") -FFEBAD_MSGS1 (FFEBAD_EQUIV_FEW, FATAL, +FFEBAD_MSG (FFEBAD_EQUIV_FEW, FATAL, "Too few elements in reference to array `%A' in EQUIVALENCE statement") -FFEBAD_MSGS1 (FFEBAD_EQUIV_MANY, FATAL, +FFEBAD_MSG (FFEBAD_EQUIV_MANY, FATAL, "Too many elements in reference to array `%A' in EQUIVALENCE statement") -FFEBAD_MSGS1 (FFEBAD_MIXED_TYPES, WARN, +FFEBAD_MSG (FFEBAD_MIXED_TYPES, WARN, "Mixed CHARACTER and non-CHARACTER types via COMMON/EQUIVALENCE -- for example, `%A' and `%B'") -FFEBAD_MSGS2 (FFEBAD_IMPLICIT_ADJLEN, FATAL, -"Invalid length specification at %0 for IMPLICIT statement -- must be integer constant expression", -"Invalid length specification at %0") -FFEBAD_MSGS2 (FFEBAD_ENTRY_CONFLICTS, FATAL, -"Type of ENTRY point at %0 to function conflicts with type(s) of previous entrypoint(s) -- must all be identical-length CHARACTER or none be CHARACTER type", -"Type of ENTRY point at %0 to function conflicts with type(s) of previous entrypoint(s)") -FFEBAD_MSGS1 (FFEBAD_RETURN_VALUE_UNSET, WARN, +FFEBAD_MSG (FFEBAD_IMPLICIT_ADJLEN, FATAL, +LONG("Invalid length specification at %0 for IMPLICIT statement -- must be integer constant expression") +SHORT("Invalid length specification at %0")) +FFEBAD_MSG (FFEBAD_ENTRY_CONFLICTS, FATAL, +LONG("Type of ENTRY point at %0 to function conflicts with type(s) of previous entrypoint(s) -- must all be identical-length CHARACTER or none be CHARACTER type") +SHORT("Type of ENTRY point at %0 to function conflicts with type(s) of previous entrypoint(s)")) +FFEBAD_MSG (FFEBAD_RETURN_VALUE_UNSET, WARN, "Return value `%A' for FUNCTION at %0 not referenced in subprogram") -FFEBAD_MSGS2 (FFEBAD_COMMON_ALREADY_INIT, FATAL, -"Common block `%A' initialized at %0 already initialized at %1 -- only one program unit may specify initial values for a particular common block", -"Common block `%A' initialized at %0 already initialized at %1") -FFEBAD_MSGS2 (FFEBAD_COMMON_INIT_PAD, WARN, -"Initial padding for common block `%A' is %B %C at %0 -- consider reordering members, largest-type-size first", -"Initial padding for common block `%A' is %B %C at %0") -FFEBAD_MSGS2 (FFEBAD_COMMON_DIFF_PAD, FATAL, -"Initial padding for common block `%A' is %B %D at %0 but %C %E at %1 -- consider reordering members, largest-type-size first", -"Initial padding for common block `%A' is %B %D at %0 but %C %E at %1") -FFEBAD_MSGS1 (FFEBAD_COMMON_DIFF_SAVE, WARN, +FFEBAD_MSG (FFEBAD_COMMON_ALREADY_INIT, FATAL, +LONG("Common block `%A' initialized at %0 already initialized at %1 -- only one program unit may specify initial values for a particular common block") +SHORT("Common block `%A' initialized at %0 already initialized at %1")) +FFEBAD_MSG (FFEBAD_COMMON_INIT_PAD, WARN, +LONG("Initial padding for common block `%A' is %B %C at %0 -- consider reordering members, largest-type-size first") +SHORT("Initial padding for common block `%A' is %B %C at %0")) +FFEBAD_MSG (FFEBAD_COMMON_DIFF_PAD, FATAL, +LONG("Initial padding for common block `%A' is %B %D at %0 but %C %E at %1 -- consider reordering members, largest-type-size first") +SHORT("Initial padding for common block `%A' is %B %D at %0 but %C %E at %1")) +FFEBAD_MSG (FFEBAD_COMMON_DIFF_SAVE, WARN, "Common block `%A' is SAVEd, explicitly or implicitly, at %0 but not SAVEd at %1") -FFEBAD_MSGS1 (FFEBAD_COMMON_DIFF_SIZE, WARN, +FFEBAD_MSG (FFEBAD_COMMON_DIFF_SIZE, WARN, "Common block `%A' is %B %D in length at %0 but %C %E at %1") -FFEBAD_MSGS2 (FFEBAD_COMMON_ENLARGED, FATAL, -"Common block `%A' is initialized to %B %D long at %0 but enlarged to %C %E at %1 -- use consistent definitions or reorder program units in source file", -"Common block `%A' is initialized to %B %D long at %0 but enlarged to %C %E at %1") -FFEBAD_MSGS1 (FFEBAD_COMMON_BLANK_INIT, WARN, +FFEBAD_MSG (FFEBAD_COMMON_ENLARGED, FATAL, +LONG("Common block `%A' is initialized to %B %D long at %0 but enlarged to %C %E at %1 -- use consistent definitions or reorder program units in source file") +SHORT("Common block `%A' is initialized to %B %D long at %0 but enlarged to %C %E at %1")) +FFEBAD_MSG (FFEBAD_COMMON_BLANK_INIT, WARN, "Blank common initialized at %0") -FFEBAD_MSGS1 (FFEBAD_NEED_INTRINSIC, WARN, +FFEBAD_MSG (FFEBAD_NEED_INTRINSIC, WARN, "Intrinsic `%A' is passed as actual argument at %0 but not explicitly declared INTRINSIC") -FFEBAD_MSGS1 (FFEBAD_NEED_EXTERNAL, WARN, +FFEBAD_MSG (FFEBAD_NEED_EXTERNAL, WARN, "External procedure `%A' is passed as actual argument at %0 but not explicitly declared EXTERNAL") -FFEBAD_MSGS1 (FFEBAD_SYMBOL_UPPER_CASE, WARN, +FFEBAD_MSG (FFEBAD_SYMBOL_UPPER_CASE, WARN, "Character `%A' (for example) is upper-case in symbol name at %0") -FFEBAD_MSGS1 (FFEBAD_SYMBOL_LOWER_CASE, WARN, +FFEBAD_MSG (FFEBAD_SYMBOL_LOWER_CASE, WARN, "Character `%A' (for example) is lower-case in symbol name at %0") -FFEBAD_MSGS1 (FFEBAD_SYMBOL_NOLOWER_INITCAP, WARN, +FFEBAD_MSG (FFEBAD_SYMBOL_NOLOWER_INITCAP, WARN, "Character `%A' not followed at some point by lower-case character in symbol name at %0") -FFEBAD_MSGS1 (FFEBAD_SYMBOL_LOWER_INITCAP, WARN, +FFEBAD_MSG (FFEBAD_SYMBOL_LOWER_INITCAP, WARN, "Initial character `%A' is lower-case in symbol name at %0") -FFEBAD_MSGS2 (FFEBAD_DO_REAL, WARN, -"DO-variable `%A' is type REAL or DOUBLE PRECISION at %0 -- unexpected behavior likely", -"DO-variable `%A' is type REAL or DOUBLE PRECISION at %0") -FFEBAD_MSGS1 (FFEBAD_NAMELIST_CASE, WARN, +FFEBAD_MSG (FFEBAD_DO_REAL, WARN, +LONG("DO-variable `%A' is type REAL or DOUBLE PRECISION at %0 -- unexpected behavior likely") +SHORT("DO-variable `%A' is type REAL or DOUBLE PRECISION at %0")) +FFEBAD_MSG (FFEBAD_NAMELIST_CASE, WARN, "NAMELIST not adequately supported by run-time library for source files with case preserved") -FFEBAD_MSGS1 (FFEBAD_NESTED_PERCENT, WARN, +FFEBAD_MSG (FFEBAD_NESTED_PERCENT, WARN, "Nested %% construct (%%VAL, %%REF, or %%DESCR) at %0") -FFEBAD_MSGS2 (FFEBAD_ACTUALARG, WARN, -"Invalid actual argument at %0 -- replace hollerith constants with %%REF('string') and typeless constants with INTEGER constant equivalents, or use -fugly-args or -fugly", -"Invalid actual argument at %0") -FFEBAD_MSGS2 (FFEBAD_QUAD_UNSUPPORTED, FATAL, -"Quadruple-precision floating-point unsupported -- treating constant at %0 as double-precision", -"Quadruple-precision floating-point unsupported") -FFEBAD_MSGS2 (FFEBAD_TOO_BIG_INIT, WARN, -"Initialization of large (%B-unit) aggregate area `%A' at %0 currently very slow and takes lots of memory during g77 compile -- to be improved in 0.6", -"This could take a while (initializing `%A' at %0)...") -FFEBAD_MSGS1 (FFEBAD_BLOCKDATA_STMT, FATAL, +FFEBAD_MSG (FFEBAD_ACTUALARG, WARN, +LONG("Invalid actual argument at %0 -- replace hollerith constants with %%REF('string') and typeless constants with INTEGER constant equivalents, or use -fugly-args or -fugly") +SHORT("Invalid actual argument at %0")) +FFEBAD_MSG (FFEBAD_QUAD_UNSUPPORTED, FATAL, +LONG("Quadruple-precision floating-point unsupported -- treating constant at %0 as double-precision") +SHORT("Quadruple-precision floating-point unsupported")) +FFEBAD_MSG (FFEBAD_TOO_BIG_INIT, WARN, +LONG("Initialization of large (%B-unit) aggregate area `%A' at %0 currently very slow and takes lots of memory during g77 compile -- to be improved in 0.6") +SHORT("This could take a while (initializing `%A' at %0)...")) +FFEBAD_MSG (FFEBAD_BLOCKDATA_STMT, FATAL, "Statement at %0 invalid in BLOCK DATA program unit at %1") -FFEBAD_MSGS1 (FFEBAD_TRUNCATING_CHARACTER, FATAL, +FFEBAD_MSG (FFEBAD_TRUNCATING_CHARACTER, FATAL, "Truncating characters on right side of character constant at %0") -FFEBAD_MSGS1 (FFEBAD_TRUNCATING_HOLLERITH, FATAL, +FFEBAD_MSG (FFEBAD_TRUNCATING_HOLLERITH, FATAL, "Truncating characters on right side of hollerith constant at %0") -FFEBAD_MSGS1 (FFEBAD_TRUNCATING_NUMERIC, FATAL, +FFEBAD_MSG (FFEBAD_TRUNCATING_NUMERIC, FATAL, "Truncating non-zero data on left side of numeric constant at %0") -FFEBAD_MSGS1 (FFEBAD_TRUNCATING_TYPELESS, FATAL, +FFEBAD_MSG (FFEBAD_TRUNCATING_TYPELESS, FATAL, "Truncating non-zero data on left side of typeless constant at %0") -FFEBAD_MSGS1 (FFEBAD_TYPELESS_OVERFLOW, FATAL, +FFEBAD_MSG (FFEBAD_TYPELESS_OVERFLOW, FATAL, "Typeless constant at %0 too large") -FFEBAD_MSGS1 (FFEBAD_AMPERSAND, WARN, +FFEBAD_MSG (FFEBAD_AMPERSAND, WARN, "First-column ampersand continuation at %0") -FFEBAD_MSGS1 (FFEBAD_FILEWIDE_ALREADY_SEEN, FATAL, +FFEBAD_MSG (FFEBAD_FILEWIDE_ALREADY_SEEN, FATAL, "Global name `%A' defined at %0 already defined at %1 [info -f g77 M GLOBALS]") -FFEBAD_MSGS1 (FFEBAD_FILEWIDE_ALREADY_SEEN_W, WARN, +FFEBAD_MSG (FFEBAD_FILEWIDE_ALREADY_SEEN_W, WARN, "Global name `%A' defined at %0 already defined at %1 [info -f g77 M GLOBALS]") -FFEBAD_MSGS1 (FFEBAD_FILEWIDE_DISAGREEMENT, FATAL, +FFEBAD_MSG (FFEBAD_FILEWIDE_DISAGREEMENT, FATAL, "Global name `%A' is %B at %0 but is %C at %1 [info -f g77 M GLOBALS]") -FFEBAD_MSGS1 (FFEBAD_FILEWIDE_DISAGREEMENT_W, WARN, +FFEBAD_MSG (FFEBAD_FILEWIDE_DISAGREEMENT_W, WARN, "Global name `%A' is %B at %0 but is %C at %1 [info -f g77 M GLOBALS]") -FFEBAD_MSGS1 (FFEBAD_FILEWIDE_TYPE_MISMATCH, FATAL, +FFEBAD_MSG (FFEBAD_FILEWIDE_TYPE_MISMATCH, FATAL, "Global name `%A' at %0 has different type at %1 [info -f g77 M GLOBALS]") -FFEBAD_MSGS1 (FFEBAD_FILEWIDE_TYPE_MISMATCH_W, WARN, +FFEBAD_MSG (FFEBAD_FILEWIDE_TYPE_MISMATCH_W, WARN, "Global name `%A' at %0 has different type at %1 [info -f g77 M GLOBALS]") -FFEBAD_MSGS1 (FFEBAD_FILEWIDE_NARGS, FATAL, +FFEBAD_MSG (FFEBAD_FILEWIDE_NARGS, FATAL, "Too %B arguments passed to `%A' at %0 versus definition at %1 [info -f g77 M GLOBALS]") -FFEBAD_MSGS1 (FFEBAD_FILEWIDE_NARGS_W, WARN, +FFEBAD_MSG (FFEBAD_FILEWIDE_NARGS_W, WARN, "Too %B arguments for `%A' at %0 versus invocation at %1 [info -f g77 M GLOBALS]") -FFEBAD_MSGS1 (FFEBAD_FILEWIDE_ARG, FATAL, +FFEBAD_MSG (FFEBAD_FILEWIDE_ARG, FATAL, "Argument #%B of `%A' is %C at %0 but is %D at %1 [info -f g77 M GLOBALS]") -FFEBAD_MSGS1 (FFEBAD_FILEWIDE_ARG_W, WARN, +FFEBAD_MSG (FFEBAD_FILEWIDE_ARG_W, WARN, "Argument #%B of `%A' is %C at %0 but is %D at %1 [info -f g77 M GLOBALS]") -FFEBAD_MSGS1 (FFEBAD_ARRAY_LARGE, FATAL, +FFEBAD_MSG (FFEBAD_ARRAY_LARGE, FATAL, "Array `%A' at %0 is too large to handle") -FFEBAD_MSGS1 (FFEBAD_SFUNC_UNUSED, WARN, +FFEBAD_MSG (FFEBAD_SFUNC_UNUSED, WARN, "Statement function `%A' defined at %0 is not used") -FFEBAD_MSGS1 (FFEBAD_INTRINSIC_Y2KBAD, WARN, +FFEBAD_MSG (FFEBAD_INTRINSIC_Y2KBAD, WARN, "Intrinsic `%A', invoked at %0, known to be non-Y2K-compliant [info -f g77 M Y2KBAD]") -FFEBAD_MSGS1 (FFEBAD_NOCANDO, DISASTER, +FFEBAD_MSG (FFEBAD_NOCANDO, DISASTER, "Internal compiler error -- cannot perform operation") #undef INFORM diff --git a/gcc/f/bad.h b/gcc/f/bad.h index 8589943cc460..bd7581e50d95 100644 --- a/gcc/f/bad.h +++ b/gcc/f/bad.h @@ -1,5 +1,5 @@ /* bad.h -- Public #include File (module.h template V1.0) - Copyright (C) 1995 Free Software Foundation, Inc. + Copyright (C) 1995, 2002 Free Software Foundation, Inc. Contributed by James Craig Burley. This file is part of GNU Fortran. @@ -34,11 +34,9 @@ the Free Software Foundation, 59 Temple Place - Suite 330, Boston, MA typedef enum { -#define FFEBAD_MSGS1(KWD,SEV,MSG) KWD, -#define FFEBAD_MSGS2(KWD,SEV,LMSG,SMSG) KWD, +#define FFEBAD_MSG(KWD,SEV,MSG) KWD, #include "bad.def" -#undef FFEBAD_MSGS1 -#undef FFEBAD_MSGS2 +#undef FFEBAD_MSG FFEBAD } ffebad; @@ -82,7 +80,7 @@ void ffebad_init_0 (void); bool ffebad_is_fatal (ffebad errnum); ffebadSeverity ffebad_severity (ffebad errnum); bool ffebad_start_ (bool lex_override, ffebad errnum, ffebadSeverity sev, - const char *message); + const char *msgid); void ffebad_string (const char *string); /* Define macros. */ @@ -95,8 +93,8 @@ void ffebad_string (const char *string); #define ffebad_set_inhibit(f) (ffebad_is_inhibited_ = (f)) #define ffebad_start(e) ffebad_start_ (FALSE, (e), FFEBAD_severity, NULL) #define ffebad_start_lex(e) ffebad_start_ (TRUE, (e), FFEBAD_severity, NULL) -#define ffebad_start_msg(m,s) ffebad_start_ (FALSE, FFEBAD, (s), (m)) -#define ffebad_start_msg_lex(m,s) ffebad_start_ (TRUE, FFEBAD, (s), (m)) +#define ffebad_start_msg(msgid,s) ffebad_start_ (FALSE, FFEBAD, (s), (msgid)) +#define ffebad_start_msg_lex(msgid,s) ffebad_start_ (TRUE, FFEBAD, (s), (msgid)) #define ffebad_terminate_0() #define ffebad_terminate_1() #define ffebad_terminate_2() diff --git a/gcc/f/com.c b/gcc/f/com.c index 9abab693235d..979d7351642d 100644 --- a/gcc/f/com.c +++ b/gcc/f/com.c @@ -89,6 +89,7 @@ the Free Software Foundation, 59 Temple Place - Suite 330, Boston, MA #include "convert.h" #include "ggc.h" #include "diagnostic.h" +#include "intl.h" #include "langhooks.h" #include "langhooks-def.h" @@ -13669,33 +13670,12 @@ lang_print_error_function (diagnostic_context *context __attribute__((unused)), if (ffecom_nested_entry_ == NULL) { s = ffecom_primary_entry_; - switch (ffesymbol_kind (s)) - { - case FFEINFO_kindFUNCTION: - kind = "function"; - break; - - case FFEINFO_kindSUBROUTINE: - kind = "subroutine"; - break; - - case FFEINFO_kindPROGRAM: - kind = "program"; - break; - - case FFEINFO_kindBLOCKDATA: - kind = "block-data"; - break; - - default: - kind = ffeinfo_kind_message (ffesymbol_kind (s)); - break; - } + kind = _(ffeinfo_kind_message (ffesymbol_kind (s))); } else { s = ffecom_nested_entry_; - kind = "statement function"; + kind = _("In statement function"); } } @@ -13705,12 +13685,12 @@ lang_print_error_function (diagnostic_context *context __attribute__((unused)), fprintf (stderr, "%s: ", file); if (s == NULL) - fprintf (stderr, "Outside of any program unit:\n"); + fprintf (stderr, _("Outside of any program unit:\n")); else { const char *name = ffesymbol_text (s); - fprintf (stderr, "In %s `%s':\n", kind, name); + fprintf (stderr, "%s `%s':\n", kind, name); } last_g = g; diff --git a/gcc/f/info-k.def b/gcc/f/info-k.def index 30fb382c45aa..9e6052d61502 100644 --- a/gcc/f/info-k.def +++ b/gcc/f/info-k.def @@ -1,5 +1,5 @@ /* info-k.def -- Public #include File (module.h template V1.0) - Copyright (C) 1995 Free Software Foundation, Inc. + Copyright (C) 1995, 2002 Free Software Foundation, Inc. Contributed by James Craig Burley. This file is part of GNU Fortran. @@ -25,13 +25,17 @@ the Free Software Foundation, 59 Temple Place - Suite 330, Boston, MA Modifications: */ -FFEINFO_KIND (FFEINFO_kindNONE, "an unknown kind", "") -FFEINFO_KIND (FFEINFO_kindENTITY, "an entity", "e") -FFEINFO_KIND (FFEINFO_kindFUNCTION, "a function", "f") -FFEINFO_KIND (FFEINFO_kindSUBROUTINE, "a subroutine", "u") -FFEINFO_KIND (FFEINFO_kindPROGRAM, "a program", "p") -FFEINFO_KIND (FFEINFO_kindBLOCKDATA, "a block-data unit", "b") -FFEINFO_KIND (FFEINFO_kindCOMMON, "a common block", "c") -FFEINFO_KIND (FFEINFO_kindCONSTRUCT, "a construct", ":") -FFEINFO_KIND (FFEINFO_kindNAMELIST, "a namelist", "n") -FFEINFO_KIND (FFEINFO_kindANY, "anything", "~") +# +/* Kind messages are used in diagnostic location reports of the + form "<file>: In function `foo': <error message>". */ + +FFEINFO_KIND (FFEINFO_kindNONE, "In unknown kind", "") +FFEINFO_KIND (FFEINFO_kindENTITY, "In entity", "e") +FFEINFO_KIND (FFEINFO_kindFUNCTION, "In function", "f") +FFEINFO_KIND (FFEINFO_kindSUBROUTINE, "In subroutine", "u") +FFEINFO_KIND (FFEINFO_kindPROGRAM, "In program", "p") +FFEINFO_KIND (FFEINFO_kindBLOCKDATA, "In block-data unit", "b") +FFEINFO_KIND (FFEINFO_kindCOMMON, "In common block", "c") +FFEINFO_KIND (FFEINFO_kindCONSTRUCT, "In construct", ":") +FFEINFO_KIND (FFEINFO_kindNAMELIST, "In namelist", "n") +FFEINFO_KIND (FFEINFO_kindANY, "In anything", "~") diff --git a/gcc/f/info.c b/gcc/f/info.c index b632f41592f1..1bedaa0772dd 100644 --- a/gcc/f/info.c +++ b/gcc/f/info.c @@ -1,5 +1,5 @@ /* info.c -- Implementation File (module.c template V1.0) - Copyright (C) 1995 Free Software Foundation, Inc. + Copyright (C) 1995, 2002 Free Software Foundation, Inc. Contributed by James Craig Burley. This file is part of GNU Fortran. @@ -65,7 +65,7 @@ static const char *const ffeinfo_basictype_string_[] static const char *const ffeinfo_kind_message_[] = { -#define FFEINFO_KIND(KWD,LNAM,SNAM) LNAM, +#define FFEINFO_KIND(kwd,msgid,snam) msgid, #include "info-k.def" #undef FFEINFO_KIND }; -- GitLab