if (Offs >= 256) {
/* Too many local vars */
AddCodeLine (";*** Too many locals");
- Error (ERR_TOO_MANY_LOCALS);
+ Error ("Too many local variables");
}
}
/* Don't accept illegal storage classes */
if (Spec.StorageClass == SC_AUTO || Spec.StorageClass == SC_REGISTER) {
- Error (ERR_ILLEGAL_STORAGE_CLASS);
+ Error ("Illegal storage class");
Spec.StorageClass = SC_EXTERN | SC_STATIC;
}
if (!IsTypeVoid (Decl.Type)) {
if (!IsTypeArray (Decl.Type)) {
/* Size is unknown and not an array */
- Error (ERR_UNKNOWN_SIZE);
+ Error ("Variable `%s' has unknown size", Decl.Ident);
}
} else if (ANSI) {
/* We cannot declare variables of type void */
- Error (ERR_ILLEGAL_TYPE);
+ Error ("Illegal type for variable `%s'", Decl.Ident);
}
}
if (IsTypeVoid (Decl.Type)) {
/* We cannot declare variables of type void */
- Error (ERR_ILLEGAL_TYPE);
+ Error ("Illegal type for variable `%s'", Decl.Ident);
} else if (Size == 0) {
/* Size is unknown */
- Error (ERR_UNKNOWN_SIZE);
+ Error ("Variable `%s' has unknown size", Decl.Ident);
}
/* Switch to the BSS segment */
type* PointerTo (const type* T)
/* Return a type string that is "pointer to T". The type string is allocated
* on the heap and may be freed after use.
- */
+ */
{
/* Get the size of the type string including the terminator */
unsigned Size = TypeLen (T) + 1;
switch (UnqualifiedType (T[0])) {
case T_VOID:
- Error (ERR_ILLEGAL_SIZE);
+ Error ("Variable has unknown size");
return 1; /* Return something that makes sense */
case T_SCHAR:
FuncDesc* F;
switch (UnqualifiedType (T[0])) {
-
+
case T_SCHAR:
return CF_CHAR;
return CF_INT | CF_UNSIGNED;
default:
- Error (ERR_ILLEGAL_TYPE);
+ Error ("Illegal type");
return CF_INT;
}
}
case TOK_CONST:
if (Q & T_QUAL_CONST) {
- Error (ERR_DUPLICATE_QUALIFIER, "const");
- }
+ Error ("Duplicate qualifier: `const'");
+ }
Q |= T_QUAL_CONST;
break;
case TOK_VOLATILE:
if (Q & T_QUAL_VOLATILE) {
- Error (ERR_DUPLICATE_QUALIFIER, "volatile");
+ Error ("Duplicate qualifier: `volatile'");
}
Q |= T_QUAL_VOLATILE;
break;
/* We expect an identifier */
if (curtok != TOK_IDENT) {
- Error (ERR_IDENT_EXPECTED);
+ Error ("Identifier expected");
continue;
}
Entry = AddStructSym (Name, 0, 0);
} else if (SymIsLocal (Entry) && (Entry->Flags & SC_STRUCT) == 0) {
/* Already defined in the level but no struct */
- Error (ERR_SYMBOL_KIND);
+ Error ("Symbol `%s' is already different kind", Name);
}
return Entry;
}
Entry = FindTagSym (CurTok.Ident);
if (Entry) {
if (SymIsLocal (Entry) && (Entry->Flags & SC_ENUM) == 0) {
- Error (ERR_SYMBOL_KIND);
+ Error ("Symbol `%s' is already different kind", Entry->Name);
}
} else {
/* Insert entry into table ### */
/* Skip the identifier */
NextToken ();
} else {
- Error (ERR_IDENT_EXPECTED);
+ Error ("Identifier expected");
}
}
/* Remember we have an extra type decl */
default:
if (Default < 0) {
- Error (ERR_TYPE_EXPECTED);
+ Error ("Type expected");
D->Type[0] = T_INT;
D->Type[1] = T_END;
} else {
/* List of identifiers expected */
if (curtok != TOK_IDENT) {
- Error (ERR_IDENT_EXPECTED);
+ Error ("Identifier expected");
}
/* Create a symbol table entry with type int */
/* An optional list of type specifications follows */
while (curtok != TOK_LCURLY) {
- DeclSpec Spec;
+ DeclSpec Spec;
/* Read the declaration specifier */
ParseDeclSpec (&Spec, SC_AUTO, T_INT);
*/
if ((Spec.StorageClass & SC_AUTO) == 0 &&
(Spec.StorageClass & SC_REGISTER) == 0) {
- Error (ERR_ILLEGAL_STORAGE_CLASS);
+ Error ("Illegal storage class");
}
/* Parse a comma separated variable list */
/* Found it, change the default type to the one given */
ChangeSymType (Sym, ParamTypeCvt (Decl.Type));
} else {
- Error (ERR_UNKNOWN_IDENT, Decl.Ident);
+ Error ("Unknown identifier: `%s'", Decl.Ident);
}
}
*/
if ((Spec.StorageClass & SC_AUTO) == 0 &&
(Spec.StorageClass & SC_REGISTER) == 0) {
- Error (ERR_ILLEGAL_STORAGE_CLASS);
+ Error ("Illegal storage class");
}
Spec.StorageClass = SC_AUTO | SC_PARAM | SC_DEF;
* parameters.
*/
if (ANSI && (F->Flags & FD_UNNAMED_PARAMS) != 0) {
- Error (ERR_MISSING_PARAM_NAME);
+ Error ("Parameter name omitted");
}
}
}
Decl (D, Mode);
/* Set the fastcall flag */
if (!IsTypeFunc (T)) {
- Error (ERR_ILLEGAL_MODIFIER);
+ Error ("__fastcall__ modifier applied to non function");
} else {
FuncDesc* F = DecodePtr (T+1);
F->Flags |= FD_FASTCALL;
NextToken ();
} else {
if (Mode == DM_NEED_IDENT) {
- Error (ERR_IDENT_EXPECTED);
+ Error ("Identifier expected");
}
D->Ident[0] = '\0';
return;
/* Check the size of the generated type */
if (!IsTypeFunc (D->Type) && !IsTypeVoid (D->Type) && SizeOf (D->Type) >= 0x10000) {
- Error (ERR_ILLEGAL_SIZE);
+ if (D->Ident[0] != '\0') {
+ Error ("Size of `%s' is invalid", D->Ident);
+ } else {
+ Error ("Invalid size");
+ }
}
}
break;
default:
- Error (ERR_ILLEGAL_TYPE);
+ Error ("Illegal type in initialization");
break;
}
*/
Tab = Entry->V.S.SymTab;
if (Tab == 0) {
- Error (ERR_INIT_INCOMPLETE_TYPE);
+ Error ("Cannot initialize variables with incomplete type");
/* Returning here will cause lots of errors, but recovery is difficult */
return;
}
Entry = Tab->SymHead;
while (curtok != TOK_RCURLY) {
if (Entry == 0) {
- Error (ERR_TOO_MANY_INITIALIZERS);
+ Error ("Too many initializers");
return;
}
ParseInit (Entry->Type);
} else if (count < sz) {
g_zerobytes ((sz - count) * SizeOf (T + DECODE_SIZE + 1));
} else if (count > sz) {
- Error (ERR_TOO_MANY_INITIALIZERS);
+ Error ("Too many initializers");
}
break;
/* FALLTHROUGH */
default:
- Error (ERR_ILLEGAL_TYPE);
+ Error ("Illegal type");
break;
}
/* The next identifier is the name of the alias symbol */
if (CurTok.Tok != TOK_IDENT) {
- Error (ERR_IDENT_EXPECTED);
+ Error ("Identifier expected");
return;
}
/* Lookup the symbol for this name, it must exist */
Sym = FindSym (CurTok.Ident);
if (Sym == 0) {
- Error (ERR_UNKNOWN_IDENT, CurTok.Ident);
+ Error ("Unknown identifier: `%s'", CurTok.Ident);
NextToken ();
return;
}
/* Check if the types of the symbols are identical */
if (TypeCmp (D->Type, Sym->Type) < TC_EQUAL) {
/* Types are not identical */
- Error (ERR_INCOMPATIBLE_TYPES);
+ Error ("Incompatible types");
return;
}
void ParseAttribute (const Declaration* D, DeclAttr* A)
/* Parse an additional __attribute__ modifier */
{
- attrib_t AttrType;
+ ident AttrName;
+ attrib_t AttrType;
/* Initialize the attribute description with "no attribute" */
A->AttrType = atNone;
/* Identifier follows */
if (CurTok.Tok != TOK_IDENT) {
- Error (ERR_IDENT_EXPECTED);
+ Error ("Identifier expected");
/* We should *really* try to recover here, but for now: */
return;
}
/* Map the attribute name to its id, then skip the identifier */
- AttrType = FindAttribute (CurTok.Ident);
+ strcpy (AttrName, CurTok.Ident);
+ AttrType = FindAttribute (AttrName);
NextToken ();
/* Handle possible attributes */
default:
/* Attribute not known, maybe typo */
- Error (ERR_ILLEGAL_ATTRIBUTE);
+ Error ("Illegal attribute: `%s'", AttrName);
break;
}
/*****************************************************************************/
-/* Data */
+/* Data */
/*****************************************************************************/
-/* Error messages sorted by ErrTypes */
-static char* ErrMsg [ERR_COUNT-1] = {
- "Syntax error",
- "`\"' expected",
- "`:' expected",
- "`;' expected",
- "`,' expected",
- "`(' expected",
- "`)' expected",
- "`[' expected",
- "`]' expected",
- "`{' expected",
- "`}' expected",
- "Identifier expected",
- "Type expected",
- "Incompatible types",
- "Incompatible pointer types",
- "Too many arguments in function call",
- "Too few arguments in function call",
- "Duplicate macro parameter: %s",
- "Variable identifier expected",
- "Integer expression expected",
- "Constant expression expected",
- "No active loop",
- "Redefinition of `%s'",
- "Conflicting types for `%s'",
- "String literal expected",
- "`while' expected",
- "Function must return a value",
- "Function cannot return a value",
- "Unexpected `continue'",
- "Undefined symbol: `%s'",
- "Undefined label: `%s'",
- "Too many local variables",
- "Too many initializers",
- "Cannot initialize incomplete type",
- "Cannot subscript",
- "Operation not allowed with this type of argument",
- "Struct expected",
- "Struct/union has no field named `%s'",
- "Struct pointer expected",
- "lvalue expected",
- "Expression expected",
- "Preprocessor expression expected",
- "Illegal type",
- "Illegal function call",
- "Illegal indirection",
- "Illegal address",
- "Illegal hex digit",
- "Illegal character constant",
- "Illegal modifier",
- "Illegal type qualifier",
- "Illegal storage class",
- "Illegal attribute",
- "Illegal segment name: `%s'",
- "Division by zero",
- "Modulo operation with zero",
- "Range error",
- "Symbol is already different kind",
- "Too many lexical levels",
- "Parameter name omitted",
- "Old style function decl used as prototype",
- "Declaration for parameter `%s' but no such parameter",
- "Cannot take address of a register variable",
- "Illegal size of data type",
- "__fastcall__ is not allowed for C functions",
- "Variable has unknown size",
- "Unknown identifier: `%s'",
- "Duplicate qualifier: `%s'",
- "Assignment to const",
- "Pointer types differ in type qualifiers",
-};
-
-
-
/* Count of errors/warnings */
unsigned ErrorCount = 0;
unsigned WarningCount = 0;
-void Error (unsigned ErrNum, ...)
-/* Print an error message */
-{
- va_list ap;
- va_start (ap, ErrNum);
- IntError (GetCurrentFile(), curpos, ErrMsg [ErrNum-1], ap);
- va_end (ap);
-}
-
-
-
-void MError (const char* Format, ...)
+void Error (const char* Format, ...)
/* Print an error message */
{
va_list ap;
-/* Error numbers */
-enum Errors {
- ERR_NONE, /* No error */
- ERR_SYNTAX,
- ERR_QUOTE_EXPECTED,
- ERR_COLON_EXPECTED,
- ERR_SEMICOLON_EXPECTED,
- ERR_COMMA_EXPECTED,
- ERR_LPAREN_EXPECTED,
- ERR_RPAREN_EXPECTED,
- ERR_LBRACK_EXPECTED,
- ERR_RBRACK_EXPECTED,
- ERR_LCURLY_EXPECTED,
- ERR_RCURLY_EXPECTED,
- ERR_IDENT_EXPECTED,
- ERR_TYPE_EXPECTED,
- ERR_INCOMPATIBLE_TYPES,
- ERR_INCOMPATIBLE_POINTERS,
- ERR_TOO_MANY_FUNC_ARGS,
- ERR_TOO_FEW_FUNC_ARGS,
- ERR_DUPLICATE_MACRO_ARG,
- ERR_VAR_IDENT_EXPECTED,
- ERR_INT_EXPR_EXPECTED,
- ERR_CONST_EXPR_EXPECTED,
- ERR_NO_ACTIVE_LOOP,
- ERR_MULTIPLE_DEFINITION,
- ERR_CONFLICTING_TYPES,
- ERR_STRLIT_EXPECTED,
- ERR_WHILE_EXPECTED,
- ERR_MUST_RETURN_VALUE,
- ERR_CANNOT_RETURN_VALUE,
- ERR_UNEXPECTED_CONTINUE,
- ERR_UNDEFINED_SYMBOL,
- ERR_UNDEFINED_LABEL,
- ERR_TOO_MANY_LOCALS,
- ERR_TOO_MANY_INITIALIZERS,
- ERR_INIT_INCOMPLETE_TYPE,
- ERR_CANNOT_SUBSCRIPT,
- ERR_OP_NOT_ALLOWED,
- ERR_STRUCT_EXPECTED,
- ERR_STRUCT_FIELD_MISMATCH,
- ERR_STRUCT_PTR_EXPECTED,
- ERR_LVALUE_EXPECTED,
- ERR_EXPR_EXPECTED,
- ERR_CPP_EXPR_EXPECTED,
- ERR_ILLEGAL_TYPE,
- ERR_ILLEGAL_FUNC_CALL,
- ERR_ILLEGAL_INDIRECT,
- ERR_ILLEGAL_ADDRESS,
- ERR_ILLEGAL_HEX_DIGIT,
- ERR_ILLEGAL_CHARCONST,
- ERR_ILLEGAL_MODIFIER,
- ERR_ILLEGAL_QUALIFIER,
- ERR_ILLEGAL_STORAGE_CLASS,
- ERR_ILLEGAL_ATTRIBUTE,
- ERR_ILLEGAL_SEG_NAME,
- ERR_DIV_BY_ZERO,
- ERR_MOD_BY_ZERO,
- ERR_RANGE,
- ERR_SYMBOL_KIND,
- ERR_LEVEL_NESTING,
- ERR_MISSING_PARAM_NAME,
- ERR_OLD_STYLE_PROTO,
- ERR_PARAM_DECL,
- ERR_CANNOT_TAKE_ADDR_OF_REG,
- ERR_ILLEGAL_SIZE,
- ERR_FASTCALL,
- ERR_UNKNOWN_SIZE,
- ERR_UNKNOWN_IDENT,
- ERR_DUPLICATE_QUALIFIER,
- ERR_CONST_ASSIGN,
- ERR_QUAL_DIFF,
- ERR_COUNT /* Error count */
-};
-
/* Count of errors/warnings */
extern unsigned ErrorCount;
extern unsigned WarningCount;
void PPWarning (const char* Format, ...) attribute ((format (printf, 1, 2)));
/* Print warning message. For use within the preprocessor. */
-void Error (unsigned ErrNum, ...);
-/* Print an error message */
-
-void MError (const char* Format, ...) attribute ((format (printf, 1, 2)));
+void Error (const char* Format, ...) attribute ((format (printf, 1, 2)));
/* Print an error message */
void PPError (const char* Format, ...) attribute ((format (printf, 1, 2)));
/* If one of the sides are of type void, output a more apropriate
* error message.
*/
- Error (ERR_ILLEGAL_TYPE);
+ Error ("Illegal type");
} else if (IsClassInt (lhst)) {
if (IsClassPtr (rhst)) {
/* Pointer -> int conversion */
Warning ("Converting pointer to integer without a cast");
} else if (!IsClassInt (rhst)) {
- Error (ERR_INCOMPATIBLE_TYPES);
+ Error ("Incompatible types");
} else {
/* Adjust the int types. To avoid manipulation of TOS mark lhs
* as const.
switch (TypeCmp (lhst, rhst)) {
case TC_INCOMPATIBLE:
- Error (ERR_INCOMPATIBLE_POINTERS);
+ Error ("Incompatible pointer types");
break;
case TC_QUAL_DIFF:
- Error (ERR_QUAL_DIFF);
+ Error ("Pointer types differ in type qualifiers");
break;
default:
* that both functions have the same parameter list.
*/
if (TypeCmp (Indirect (lhst), rhst) < TC_EQUAL) {
- Error (ERR_INCOMPATIBLE_TYPES);
+ Error ("Incompatible types");
}
} else {
- Error (ERR_INCOMPATIBLE_TYPES);
+ Error ("Incompatible types");
}
} else {
- Error (ERR_INCOMPATIBLE_TYPES);
+ Error ("Incompatible types");
}
/* Return an int value in all cases where the operands are not both ints */
* allowed.
*/
if (!AllowRegVarAddr) {
- Error (ERR_CANNOT_TAKE_ADDR_OF_REG);
+ Error ("Cannot take the address of a register variable");
}
/* FALLTHROUGH */
* allowed.
*/
if (!AllowRegVarAddr) {
- Error (ERR_CANNOT_TAKE_ADDR_OF_REG);
+ Error ("Cannot take the address of a register variable");
}
/* FALLTHROUGH */
return (val1 * val2);
case TOK_DIV:
if (val2 == 0) {
- Error (ERR_DIV_BY_ZERO);
+ Error ("Division by zero");
return 0x7FFFFFFF;
}
return (val1 / val2);
case TOK_MOD:
if (val2 == 0) {
- Error (ERR_MOD_BY_ZERO);
+ Error ("Modulo operation with zero");
return 0;
}
return (val1 % val2);
/* Too many arguments. Do we have an open param list? */
if ((Func->Flags & FD_ELLIPSIS) == 0) {
/* End of param list reached, no ellipsis */
- Error (ERR_TOO_MANY_FUNC_ARGS);
+ Error ("Too many arguments in function call");
}
/* Assume an ellipsis even in case of errors to avoid an error
* message for each other argument.
/* Check if we had enough parameters */
if (ParamCount < Func->ParamCount) {
- Error (ERR_TOO_FEW_FUNC_ARGS);
+ Error ("Too few arguments in function call");
}
/* */
/* String literal */
if (curtok != TOK_SCONST) {
- Error (ERR_STRLIT_EXPECTED);
+ Error ("String literal expected");
} else {
/* Write the string directly into the output, followed by a newline */
AddCodeLine (GetLiteral (curval));
*/
if (Preprocessing) {
/* Illegal expression in PP mode */
- Error (ERR_CPP_EXPR_EXPECTED);
+ Error ("Preprocessor expression expected");
lval->e_flags = E_MCONST;
lval->e_tptr = type_int;
return 0;
lval->e_tptr = Sym->Type;
/* Check for illegal symbol types */
- if ((Sym->Flags & SC_LABEL) == SC_LABEL) {
- /* Cannot use labels in expressions */
- Error (ERR_SYMBOL_KIND);
- return 1;
- } else if (Sym->Flags & SC_TYPE) {
+ CHECK ((Sym->Flags & SC_LABEL) != SC_LABEL);
+ if (Sym->Flags & SC_TYPE) {
/* Cannot use type symbols */
- Error (ERR_VAR_IDENT_EXPECTED);
+ Error ("Variable identifier expected");
/* Assume an int type to make lval valid */
lval->e_flags = E_MLOCAL | E_TLOFFS;
lval->e_tptr = type_int;
lval->e_flags = E_MLOCAL | E_TLOFFS;
lval->e_tptr = type_int;
lval->e_const = 0;
- Error (ERR_UNDEFINED_SYMBOL, Ident);
+ Error ("Undefined symbol: `%s'", Ident);
return 1;
}
}
/* Illegal primary. */
- Error (ERR_EXPR_EXPECTED);
+ Error ("Expression expected");
lval->e_flags = E_MCONST;
lval->e_tptr = type_int;
return 0;
/* */
lval->e_tptr = lval2.e_tptr;
} else {
- Error (ERR_CANNOT_SUBSCRIPT);
+ Error ("Cannot subscript");
}
/* Add the subscript. Since arrays are indexed by integers,
g_scale (TypeOf (tptr1), SizeOf (lval2.e_tptr));
lval->e_tptr = lval2.e_tptr;
} else {
- Error (ERR_CANNOT_SUBSCRIPT);
+ Error ("Cannot subscript");
}
/* The offset is now in the primary register. It didn't have a
/* Skip the token and check for an identifier */
NextToken ();
if (curtok != TOK_IDENT) {
- Error (ERR_IDENT_EXPECTED);
+ Error ("Identifier expected");
lval->e_tptr = type_int;
return 0;
}
NextToken ();
Field = FindStructField (lval->e_tptr, Ident);
if (Field == 0) {
- Error (ERR_STRUCT_FIELD_MISMATCH, Ident);
+ Error ("Struct/union has no field named `%s'", Ident);
lval->e_tptr = type_int;
return 0;
}
lval->e_flags = E_MEXPR;
lval->e_tptr += DECODE_SIZE + 1; /* Set to result */
} else {
- Error (ERR_ILLEGAL_FUNC_CALL);
+ Error ("Illegal function call");
}
k = 0;
} else if (curtok == TOK_DOT) {
if (!IsClassStruct (lval->e_tptr)) {
- Error (ERR_STRUCT_EXPECTED);
+ Error ("Struct expected");
}
k = structref (0, lval);
tptr = lval->e_tptr;
if (tptr[0] != T_PTR || (tptr[1] & T_STRUCT) == 0) {
- Error (ERR_STRUCT_PTR_EXPECTED);
+ Error ("Struct pointer expected");
}
k = structref (k, lval);
NextToken ();
if ((k = hie10 (lval)) == 0) {
- Error (ERR_LVALUE_EXPECTED);
+ Error ("Invalid lvalue");
return;
}
NextToken ();
if (k == 0) {
- Error (ERR_LVALUE_EXPECTED);
+ Error ("Invalid lvalue");
return;
}
if (IsClassPtr (t)) {
lval->e_tptr = Indirect (t);
} else {
- Error (ERR_ILLEGAL_INDIRECT);
+ Error ("Illegal indirection");
}
return 1;
if (k == 0) {
/* Allow the & operator with an array */
if (!IsTypeArray (lval->e_tptr)) {
- Error (ERR_ILLEGAL_ADDRESS);
+ Error ("Illegal address");
}
} else {
t = TypeAlloc (TypeLen (lval->e_tptr) + 2);
/* All operators that call this function expect an int on the lhs */
if (!IsClassInt (lval->e_tptr)) {
- Error (ERR_INT_EXPR_EXPECTED);
+ Error ("Integer expression expected");
}
/* Remember the operator token, then skip it */
/* Check the type of the rhs */
if (!IsClassInt (lval2.e_tptr)) {
- Error (ERR_INT_EXPR_EXPECTED);
+ Error ("Integer expression expected");
}
/* Check for const operands */
type |= CF_CONST;
rtype |= CF_CONST;
if (tok == TOK_DIV && lval2.e_const == 0) {
- Error (ERR_DIV_BY_ZERO);
+ Error ("Division by zero");
} else if (tok == TOK_MOD && lval2.e_const == 0) {
- Error (ERR_MOD_BY_ZERO);
+ Error ("Modulo operation with zero");
}
if ((Gen->Flags & GEN_NOPUSH) != 0) {
RemoveCode (Mark2);
/* Make sure, the types are compatible */
if (IsClassInt (lval->e_tptr)) {
if (!IsClassInt (lval2.e_tptr) && !(IsClassPtr(lval2.e_tptr) && IsNullPtr(lval))) {
- Error (ERR_INCOMPATIBLE_TYPES);
+ Error ("Incompatible types");
}
} else if (IsClassPtr (lval->e_tptr)) {
if (IsClassPtr (lval2.e_tptr)) {
type* right = Indirect (lval2.e_tptr);
if (TypeCmp (left, right) < TC_EQUAL && *left != T_VOID && *right != T_VOID) {
/* Incomatible pointers */
- Error (ERR_INCOMPATIBLE_TYPES);
+ Error ("Incompatible types");
}
} else if (!IsNullPtr (&lval2)) {
- Error (ERR_INCOMPATIBLE_TYPES);
+ Error ("Incompatible types");
}
}
typeadjust (lval, &lval2, 1);
} else {
/* OOPS */
- Error (ERR_OP_NOT_ALLOWED);
+ Error ("Invalid operands for binary operator `+'");
}
/* Result is constant, condition codes not set */
flags = typeadjust (lval, &lval2, 1);
} else {
/* OOPS */
- Error (ERR_OP_NOT_ALLOWED);
+ Error ("Invalid operands for binary operator `+'");
}
/* Generate code for the add */
flags = typeadjust (lval, &lval2, 1);
} else {
/* OOPS */
- Error (ERR_OP_NOT_ALLOWED);
+ Error ("Invalid operands for binary operator `+'");
}
/* Generate code for the add */
flags = typeadjust (lval, &lval2, 0);
} else {
/* OOPS */
- Error (ERR_OP_NOT_ALLOWED);
+ Error ("Invalid operands for binary operator `+'");
}
/* Generate code for the add */
type* lhst; /* Type of left hand side */
type* rhst; /* Type of right hand side */
CodeMark Mark1; /* Save position of output queue */
- CodeMark Mark2; /* Another position in the queue */
+ CodeMark Mark2; /* Another position in the queue */
int rscale; /* Scale factor for the result */
} else if (IsClassPtr (lhst) && IsClassPtr (rhst)) {
/* Left is pointer, right is pointer, must scale result */
if (TypeCmp (Indirect (lhst), Indirect (rhst)) < TC_EQUAL) {
- Error (ERR_INCOMPATIBLE_POINTERS);
+ Error ("Incompatible pointer types");
} else {
lval->e_const = (lval->e_const - lval2.e_const) / PSizeOf (lhst);
}
lval->e_const -= lval2.e_const;
} else {
/* OOPS */
- Error (ERR_OP_NOT_ALLOWED);
+ Error ("Invalid operands for binary operator `-'");
}
/* Result is constant, condition codes not set */
} else if (IsClassPtr (lhst) && IsClassPtr (rhst)) {
/* Left is pointer, right is pointer, must scale result */
if (TypeCmp (Indirect (lhst), Indirect (rhst)) < TC_EQUAL) {
- Error (ERR_INCOMPATIBLE_POINTERS);
+ Error ("Incompatible pointer types");
} else {
rscale = PSizeOf (lhst);
}
flags = typeadjust (lval, &lval2, 1);
} else {
/* OOPS */
- Error (ERR_OP_NOT_ALLOWED);
+ Error ("Invalid operands for binary operator `-'");
}
/* Do the subtraction */
} else if (IsClassPtr (lhst) && IsClassPtr (rhst)) {
/* Left is pointer, right is pointer, must scale result */
if (TypeCmp (Indirect (lhst), Indirect (rhst)) < TC_EQUAL) {
- Error (ERR_INCOMPATIBLE_POINTERS);
+ Error ("Incompatible pointer types");
} else {
rscale = PSizeOf (lhst);
}
flags = typeadjust (lval, &lval2, 0);
} else {
/* OOPS */
- Error (ERR_OP_NOT_ALLOWED);
+ Error ("Invalid operands for binary operator `-'");
}
/* Generate code for the sub (the & is a hack here) */
} else if (IsClassPtr (type2) && IsClassPtr (type3)) {
/* Must point to same type */
if (TypeCmp (Indirect (type2), Indirect (type3)) < TC_EQUAL) {
- Error (ERR_INCOMPATIBLE_TYPES);
+ Error ("Incompatible pointer types");
}
/* Result has the common type */
rtype = lval2.e_tptr;
/* Result type is pointer, no cast needed */
rtype = lval3.e_tptr;
} else {
- Error (ERR_INCOMPATIBLE_TYPES);
+ Error ("Incompatible types");
rtype = lval2.e_tptr; /* Doesn't matter here */
}
NextToken ();
if (k == 0) {
- Error (ERR_LVALUE_EXPECTED);
+ Error ("Invalid lvalue in assignment");
return;
}
if (k == 0) {
- Error (ERR_LVALUE_EXPECTED);
+ Error ("Invalid lvalue in assignment");
return;
}
/* Check for assignment to const */
if (IsQualConst (ltype)) {
- Error (ERR_CONST_ASSIGN);
+ Error ("Assignment to const");
}
/* cc65 does not have full support for handling structs by value. Since
exprhs (0, 0, &lval2);
} else {
/* We need an lvalue */
- Error (ERR_LVALUE_EXPECTED);
+ Error ("Invalid lvalue in assignment");
}
/* Push the address (or whatever is in ax in case of errors) */
/* Check for equality of the structs */
if (TypeCmp (ltype, lval2.e_tptr) < TC_EQUAL) {
- Error (ERR_INCOMPATIBLE_TYPES);
+ Error ("Incompatible types");
}
/* Load the size of the struct into the primary */
case TOK_ASSIGN:
NextToken ();
if (k == 0) {
- Error (ERR_LVALUE_EXPECTED);
+ Error ("Invalid lvalue in assignment");
} else {
Assignment (lval);
}
{
memset (lval, 0, sizeof (*lval));
if (expr (hie1, lval) != 0 || (lval->e_flags & E_MCONST) == 0) {
- Error (ERR_CONST_EXPR_EXPECTED);
+ Error ("Constant expression expected");
/* To avoid any compiler errors, make the expression a valid const */
lval->e_flags = E_MCONST;
lval->e_tptr = type_int;
{
expression (lval);
if (!IsClassInt (lval->e_tptr)) {
- Error (ERR_INT_EXPR_EXPECTED);
+ Error ("Integer expression expected");
/* To avoid any compiler errors, make the expression a valid int */
lval->e_flags = E_MCONST;
lval->e_tptr = type_int;
expression (lval);
/* If it's an integer, it's ok. If it's not an integer, but a pointer,
- * the pointer used in a boolean context is also ok (Ootherwise check if it's a pointer
- * expression.
+ * the pointer used in a boolean context is also ok
*/
if (!IsClassInt (lval->e_tptr) && !IsClassPtr (lval->e_tptr)) {
- Error (ERR_INT_EXPR_EXPECTED);
+ Error ("Boolean expression expected");
/* To avoid any compiler errors, make the expression a valid int */
lval->e_flags = E_MCONST;
lval->e_tptr = type_int;
/* C functions cannot currently have __fastcall__ calling conventions */
if (IsFastCallFunc (Func->Type)) {
- Error (ERR_FASTCALL);
+ Error ("__fastcall__ is not allowed for C functions");
}
/* Need a starting curly brace */
if (curtok != TOK_LCURLY) {
- Error (ERR_LCURLY_EXPECTED);
+ Error ("`{' expected");
}
/* Setup register variables */
#if 0
/* If the function has a return type, flag an error */
if (!voidfunc) {
- Error (ERR_MUST_RETURN_VALUE);
+ Error ("Function `%s' must return a value", Func->Name);
}
#endif
RestoreRegVars (0);
/* Label name must follow */
if (curtok != TOK_IDENT) {
- Error (ERR_IDENT_EXPECTED);
+ Error ("Identifier expected");
} else {
-/*
- * loop.c
- *
- * Ullrich von Bassewitz, 20.06.1998
- */
+/*****************************************************************************/
+/* */
+/* loop.c */
+/* */
+/* Loop management */
+/* */
+/* */
+/* */
+/* (C) 1998-2000 Ullrich von Bassewitz */
+/* Wacholderweg 14 */
+/* D-70597 Stuttgart */
+/* EMail: uz@musoftware.de */
+/* */
+/* */
+/* This software is provided 'as-is', without any expressed or implied */
+/* warranty. In no event will the authors be held liable for any damages */
+/* arising from the use of this software. */
+/* */
+/* Permission is granted to anyone to use this software for any purpose, */
+/* including commercial applications, and to alter it and redistribute it */
+/* freely, subject to the following restrictions: */
+/* */
+/* 1. The origin of this software must not be misrepresented; you must not */
+/* claim that you wrote the original software. If you use this software */
+/* in a product, an acknowledgment in the product documentation would be */
+/* appreciated but is not required. */
+/* 2. Altered source versions must be plainly marked as such, and must not */
+/* be misrepresented as being the original software. */
+/* 3. This notice may not be removed or altered from any source */
+/* distribution. */
+/* */
+/*****************************************************************************/
-#include "../common/xmalloc.h"
+/* common */
+#include "xmalloc.h"
+/* cc65 */
#include "error.h"
#include "loop.h"
/*****************************************************************************/
-/* data */
+/* Data */
/*****************************************************************************/
/* The root */
-static struct loopdesc* loopstack = 0;
+static LoopDesc* LoopStack = 0;
/*****************************************************************************/
-/* code */
+/* Code */
/*****************************************************************************/
-struct loopdesc* addloop (unsigned sp, unsigned loop, unsigned label,
- unsigned linc, unsigned lstat)
+LoopDesc* AddLoop (unsigned sp, unsigned loop, unsigned label,
+ unsigned linc, unsigned lstat)
/* Create and add a new loop descriptor */
{
- struct loopdesc* l;
+ LoopDesc* L;
/* Allocate a new struct */
- l = xmalloc (sizeof (struct loopdesc));
+ L = xmalloc (sizeof (LoopDesc));
/* Fill in the data */
- l->sp = sp;
- l->loop = loop;
- l->label = label;
- l->linc = linc;
- l->lstat = lstat;
+ L->StackPtr = sp;
+ L->Loop = loop;
+ L->Label = label;
+ L->linc = linc;
+ L->lstat = lstat;
/* Insert it into the list */
- l->next = loopstack;
- loopstack = l;
+ L->Next = LoopStack;
+ LoopStack = L;
/* Return a pointer to the struct */
- return l;
+ return L;
}
-struct loopdesc* currentloop (void)
+LoopDesc* CurrentLoop (void)
/* Return a pointer to the descriptor of the current loop */
{
- if (loopstack == 0) {
- /* Stack is empty */
- Error (ERR_NO_ACTIVE_LOOP);
- }
- return loopstack;
+ return LoopStack;
}
-void delloop (void)
+void DelLoop (void)
/* Remove the current loop */
{
- struct loopdesc* l;
-
- l = loopstack;
- loopstack = loopstack->next;
- xfree (l);
+ LoopDesc* L = LoopStack;
+ LoopStack = LoopStack->Next;
+ xfree (L);
}
-/*
- * loop.h
- *
- * Ullrich von Bassewitz, 20.06.1998
- */
+/*****************************************************************************/
+/* */
+/* loop.h */
+/* */
+/* Loop management */
+/* */
+/* */
+/* */
+/* (C) 1998-2000 Ullrich von Bassewitz */
+/* Wacholderweg 14 */
+/* D-70597 Stuttgart */
+/* EMail: uz@musoftware.de */
+/* */
+/* */
+/* This software is provided 'as-is', without any expressed or implied */
+/* warranty. In no event will the authors be held liable for any damages */
+/* arising from the use of this software. */
+/* */
+/* Permission is granted to anyone to use this software for any purpose, */
+/* including commercial applications, and to alter it and redistribute it */
+/* freely, subject to the following restrictions: */
+/* */
+/* 1. The origin of this software must not be misrepresented; you must not */
+/* claim that you wrote the original software. If you use this software */
+/* in a product, an acknowledgment in the product documentation would be */
+/* appreciated but is not required. */
+/* 2. Altered source versions must be plainly marked as such, and must not */
+/* be misrepresented as being the original software. */
+/* 3. This notice may not be removed or altered from any source */
+/* distribution. */
+/* */
+/*****************************************************************************/
-struct loopdesc {
- struct loopdesc* next;
- unsigned sp;
- unsigned loop;
- unsigned label;
- unsigned linc;
- unsigned lstat;
+typedef struct LoopDesc LoopDesc;
+struct LoopDesc {
+ LoopDesc* Next;
+ unsigned StackPtr;
+ unsigned Loop;
+ unsigned Label;
+ unsigned linc;
+ unsigned lstat;
};
-struct loopdesc* addloop (unsigned sp, unsigned loop, unsigned label,
- unsigned linc, unsigned lstat);
+LoopDesc* AddLoop (unsigned sp, unsigned loop, unsigned label,
+ unsigned linc, unsigned lstat);
/* Create and add a new loop descriptor */
-struct loopdesc* currentloop (void);
+LoopDesc* CurrentLoop (void);
/* Return a pointer to the descriptor of the current loop */
-void delloop (void);
+void DelLoop (void);
/* Remove the current loop */
/* common */
#include "hashstr.h"
#include "xmalloc.h"
-
+
/* cc65 */
#include "error.h"
#include "macrotab.h"
for (I = 0; I < M->ArgCount; ++I) {
if (strcmp (M->FormalArgs[I], Arg) == 0) {
/* Found */
- Error (ERR_DUPLICATE_MACRO_ARG, Arg);
+ Error ("Duplicate macro parameter: `%s'", Arg);
break;
}
}
int MacroCmp (const Macro* M1, const Macro* M2)
/* Compare two macros and return zero if both are identical. */
-{
+{
int I;
/* Argument count must be identical */
/* Handle a pragma that expects a string parameter */
{
if (curtok != TOK_SCONST) {
- Error (ERR_STRLIT_EXPECTED);
+ Error ("String literal expected");
} else {
/* Get the string */
const char* Name = GetLiteral (curval);
/* Handle a pragma that expects a segment name parameter */
{
if (curtok != TOK_SCONST) {
- Error (ERR_STRLIT_EXPECTED);
+ Error ("String literal expected");
} else {
/* Get the segment name */
const char* Name = GetLiteral (curval);
} else {
/* Segment name is invalid */
- Error (ERR_ILLEGAL_SEG_NAME, Name);
+ Error ("Illegal segment name: `%s'", Name);
}
/* Identifier must follow */
if (curtok != TOK_IDENT) {
- Error (ERR_IDENT_EXPECTED);
+ Error ("Identifier expected");
return;
}
static void unknown (char C)
/* Error message for unknown character */
{
- MError ("Invalid input character with code %02X", C & 0xFF);
+ Error ("Invalid input character with code %02X", C & 0xFF);
NextChar (); /* Skip */
}
/* Convert a hex digit into a value */
{
if (!isxdigit (c)) {
- Error (ERR_ILLEGAL_HEX_DIGIT);
+ Error ("Invalid hexadecimal digit: `%c'", c);
}
if (isdigit (c)) {
return c - '0';
}
break;
default:
- Error (ERR_ILLEGAL_CHARCONST);
+ Error ("Illegal character constant");
C = ' ';
break;
}
/* Check for closing quote */
if (CurC != '\'') {
- Error (ERR_QUOTE_EXPECTED);
+ Error ("`\'' expected");
} else {
/* Skip the quote */
NextChar ();
while (CurC != '\"') {
if (CurC == '\0') {
- MError ("Unexpected newline");
+ Error ("Unexpected newline");
break;
}
AddLiteralChar (ParseChar ());
} while (CurC == ' ');
if (!IsSym (token) || strcmp (token, "pragma") != 0) {
/* OOPS - should not happen */
- MError ("Preprocessor directive expected");
+ Error ("Preprocessor directive expected");
}
nxttok = TOK_PRAGMA;
break;
-void Consume (token_t Token, unsigned ErrNum)
+void Consume (token_t Token, const char* ErrorMsg)
/* Eat token if it is the next in the input stream, otherwise print an error
* message.
*/
if (curtok == Token) {
NextToken ();
} else {
- Error (ErrNum);
+ Error (ErrorMsg);
}
}
void ConsumeColon (void)
/* Check for a colon and skip it. */
{
- Consume (TOK_COLON, ERR_COLON_EXPECTED);
+ Consume (TOK_COLON, "`:' expected");
}
if (curtok == TOK_SEMI) {
NextToken ();
} else {
- Error (ERR_SEMICOLON_EXPECTED);
+ Error ("`;' expected");
if (curtok == TOK_COLON || curtok == TOK_COMMA) {
NextToken ();
}
if (CurTok.Tok == TOK_COMMA) {
NextToken ();
} else {
- Error (ERR_COMMA_EXPECTED);
+ Error ("`,' expected");
if (CurTok.Tok == TOK_SEMI) {
NextToken ();
}
void ConsumeLParen (void)
/* Check for a left parenthesis and skip it */
{
- Consume (TOK_LPAREN, ERR_LPAREN_EXPECTED);
+ Consume (TOK_LPAREN, "`(' expected");
}
void ConsumeRParen (void)
/* Check for a right parenthesis and skip it */
{
- Consume (TOK_RPAREN, ERR_RPAREN_EXPECTED);
+ Consume (TOK_RPAREN, "`)' expected");
}
void ConsumeLBrack (void)
/* Check for a left bracket and skip it */
{
- Consume (TOK_LBRACK, ERR_LBRACK_EXPECTED);
+ Consume (TOK_LBRACK, "`[' expected");
}
void ConsumeRBrack (void)
/* Check for a right bracket and skip it */
{
- Consume (TOK_RBRACK, ERR_RBRACK_EXPECTED);
+ Consume (TOK_RBRACK, "`]' expected");
}
void ConsumeLCurly (void)
/* Check for a left curly brace and skip it */
{
- Consume (TOK_LCURLY, ERR_LCURLY_EXPECTED);
+ Consume (TOK_LCURLY, "`{' expected");
}
void ConsumeRCurly (void)
/* Check for a right curly brace and skip it */
{
- Consume (TOK_RCURLY, ERR_RCURLY_EXPECTED);
+ Consume (TOK_RCURLY, "`}' expected");
}
void NextToken (void);
/* Get next token from input stream */
-void Consume (token_t Token, unsigned ErrNum);
+void Consume (token_t Token, const char* ErrorMsg);
/* Eat token if it is the next in the input stream, otherwise print an error
* message.
*/
NextToken ();
loop = GetLabel ();
lab = GetLabel ();
- addloop (oursp, loop, lab, 0, 0);
+ AddLoop (oursp, loop, lab, 0, 0);
g_defloclabel (loop);
if (wtype == 'w') {
/* Do loop */
statement ();
- Consume (TOK_WHILE, ERR_WHILE_EXPECTED);
+ Consume (TOK_WHILE, "`while' expected");
test (loop, 1);
ConsumeSemi ();
g_defloclabel (lab);
}
- delloop ();
+ DelLoop ();
}
NextToken ();
if (curtok != TOK_SEMI) {
if (HasVoidReturn (CurrentFunc)) {
- Error (ERR_CANNOT_RETURN_VALUE);
+ Error ("Returning a value in function with return type void");
}
if (evalexpr (CF_NONE, hie0, &lval) == 0) {
/* Constant value */
etype |= assignadjust (GetReturnType (CurrentFunc), &lval) & ~CF_CONST;
}
} else if (!HasVoidReturn (CurrentFunc)) {
- Error (ERR_MUST_RETURN_VALUE);
+ Error ("Function `%s' must return a value", GetFuncName (CurrentFunc));
}
RestoreRegVars (HaveVal);
g_leave (etype, lval.e_const);
static void dobreak (void)
/* Handle 'break' statement here */
{
- struct loopdesc* l;
+ LoopDesc* L;
+ /* Skip the break */
NextToken ();
- if ((l = currentloop ()) == 0) {
+
+ /* Get the current loop descriptor */
+ L = CurrentLoop ();
+
+ /* Check if we are inside a loop */
+ if (L == 0) {
/* Error: No current loop */
- return;
+ Error ("`break' statement not within loop or switch");
+ return;
}
- g_space (oursp - l->sp);
- g_jump (l->label);
+
+ /* Correct the stack pointer if needed */
+ g_space (oursp - L->StackPtr);
+
+ /* Jump to the exit label of the loop */
+ g_jump (L->Label);
}
static void docontinue (void)
/* Handle 'continue' statement here */
{
- struct loopdesc* l;
+ LoopDesc* L;
+ /* Skip the continue */
NextToken ();
- if ((l = currentloop ()) == 0) {
- /* Error: Not in loop */
- return;
+
+ /* Get the current loop descriptor */
+ L = CurrentLoop ();
+ if (L) {
+ /* Search for the correct loop */
+ do {
+ if (L->Loop) {
+ break;
+ }
+ L = L->Next;
+ } while (L);
}
- do {
- if (l->loop) {
- break;
- }
- l = l->next;
- } while (l);
- if (l == 0) {
- Error (ERR_UNEXPECTED_CONTINUE);
- return;
+
+ /* Did we find it? */
+ if (L == 0) {
+ Error ("`continue' statement not within a loop");
+ return;
}
- g_space (oursp - l->sp);
- if (l->linc) {
- g_jump (l->linc);
+
+ /* Correct the stackpointer if needed */
+ g_space (oursp - L->StackPtr);
+
+ /* Output the loop code */
+ if (L->linc) {
+ g_jump (L->linc);
} else {
- g_jump (l->loop);
+ g_jump (L->Loop);
}
}
/* Create a loop so we may break out, init labels */
exitlab = GetLabel ();
- addloop (oursp, 0, exitlab, 0, 0);
+ AddLoop (oursp, 0, exitlab, 0, 0);
/* Setup some variables needed in the loop below */
flags = TypeOf (eval->e_tptr) | CF_CONST | CF_FORCECHAR;
/* Read the selector expression */
constexpr (&lval);
if (!IsClassInt (lval.e_tptr)) {
- Error (ERR_ILLEGAL_TYPE);
+ Error ("Switch quantity not an integer");
}
/* Check the range of the expression */
case T_SCHAR:
/* Signed char */
if (val < -128 || val > 127) {
- Error (ERR_RANGE);
+ Error ("Range error");
}
break;
case T_UCHAR:
if (val < 0 || val > 255) {
- Error (ERR_RANGE);
+ Error ("Range error");
}
break;
case T_INT:
if (val < -32768 || val > 32767) {
- Error (ERR_RANGE);
+ Error ("Range error");
}
break;
case T_UINT:
if (val < 0 || val > 65535) {
- Error (ERR_RANGE);
- }
+ Error ("Range error");
+ }
break;
default:
g_defloclabel (exitlab);
/* End the loop */
- delloop ();
+ DelLoop ();
}
dlabel = 0; /* init */
lab = GetLabel (); /* get exit */
p = swtab;
- addloop (oursp, 0, lab, 0, 0);
+ AddLoop (oursp, 0, lab, 0, 0);
/* Jump behind the code for the CASE labels */
g_jump (lcase = GetLabel ());
NextToken ();
constexpr (&lval);
if (!IsClassInt (lval.e_tptr)) {
- Error (ERR_ILLEGAL_TYPE);
+ Error ("Switch quantity not an integer");
}
p->sw_const = lval.e_const;
p->sw_lab = label;
g_jump (dlabel);
}
g_defloclabel (lab);
- delloop ();
+ DelLoop ();
/* Free the allocated space for the labels */
xfree (swtab);
lab = GetLabel ();
linc = GetLabel ();
lstat = GetLabel ();
- addloop (oursp, loop, lab, linc, lstat);
+ AddLoop (oursp, loop, lab, linc, lstat);
ConsumeLParen ();
if (curtok != TOK_SEMI) { /* exp1 */
expression (&lval1);
statement ();
g_jump (linc);
g_defloclabel (lab);
- delloop ();
+ DelLoop ();
}
if (Flags & SC_LABEL) {
if ((Flags & SC_DEF) == 0) {
/* Undefined label */
- Error (ERR_UNDEFINED_LABEL, Entry->Name);
+ Error ("Undefined label: `%s'", Entry->Name);
} else if ((Flags & SC_REF) == 0) {
/* Defined but not used */
Warning ("`%s' is defined but never used", Entry->Name);
/* We do have an entry. This may be a forward, so check it. */
if ((Entry->Flags & SC_STRUCT) == 0) {
/* Existing symbol is not a struct */
- Error (ERR_SYMBOL_KIND);
+ Error ("Symbol `%s' is already different kind", Name);
} else if (Size > 0 && Entry->V.S.Size > 0) {
/* Both structs are definitions. */
- Error (ERR_MULTIPLE_DEFINITION, Name);
+ Error ("Multiple definition for `%s'", Name);
} else {
/* Define the struct size if it is given */
if (Size > 0) {
SymEntry* Entry = FindSymInTable (SymTab, Name, HashStr (Name));
if (Entry) {
if (Entry->Flags != SC_ENUM) {
- Error (ERR_SYMBOL_KIND);
+ Error ("Symbol `%s' is already different kind", Name);
} else {
- Error (ERR_MULTIPLE_DEFINITION, Name);
+ Error ("Multiple definition for `%s'", Name);
}
return Entry;
}
if ((Entry->Flags & SC_DEF) != 0 && (Flags & SC_DEF) != 0) {
/* Trying to define the label more than once */
- Error (ERR_MULTIPLE_DEFINITION, Name);
- }
+ Error ("Label `%s' is defined more than once", Name);
+ }
Entry->Flags |= Flags;
} else {
if (Entry) {
/* We have a symbol with this name already */
- Error (ERR_MULTIPLE_DEFINITION, Name);
+ Error ("Multiple definition for `%s'", Name);
} else {
/* We have a symbol with this name already */
if (Entry->Flags & SC_TYPE) {
- Error (ERR_MULTIPLE_DEFINITION, Name);
+ Error ("Multiple definition for `%s'", Name);
return Entry;
}
if ((Size != 0 && ESize != 0) ||
TypeCmp (Type+DECODE_SIZE+1, EType+DECODE_SIZE+1) < TC_EQUAL) {
/* Types not identical: Conflicting types */
- Error (ERR_CONFLICTING_TYPES, Name);
+ Error ("Conflicting types for `%s'", Name);
} else {
/* Check if we have a size in the existing definition */
if (ESize == 0) {
} else {
/* New type must be identical */
if (TypeCmp (EType, Type) < TC_EQUAL) {
- Error (ERR_CONFLICTING_TYPES, Name);
- }
+ Error ("Conflicting types for `%s'", Name);
+ }
/* In case of a function, use the new type descriptor, since it
* contains pointers to the new symbol tables that are needed if
if (Entry) {
Entry->Flags |= SC_ZEROPAGE;
} else {
- Error (ERR_UNDEFINED_SYMBOL, Name);
+ Error ("Undefined symbol: `%s'", Name);
}
}