diff --git a/gcc/doc/gm2.texi b/gcc/doc/gm2.texi index 9e620c32ae1a3f53fccce83a0ab85dd096ba4a63..0bace308d11274071d08951d66c35e1441464dd2 100644 --- a/gcc/doc/gm2.texi +++ b/gcc/doc/gm2.texi @@ -500,6 +500,10 @@ the previous forms could be: @code{-fm2-dump-filter=m2pim.StrIO.WriteString} and @code{-fm2-dump-filter=StrLib.mod:StrIO.WriteString}. +@item -fm2-file-offset-bits= +force the type @code{SYSTEM.COFF_T} to be built using the specified +number of bits. If this option is not used then default is 64 bits. + @item -fm2-g improve the debugging experience for new programmers at the expense of generating @code{nop} instructions if necessary to ensure single diff --git a/gcc/m2/gm2-compiler/M2GCCDeclare.mod b/gcc/m2/gm2-compiler/M2GCCDeclare.mod index d536ee31452f979174b0992abecd0ec71075df5f..0de9ff7f22147d7c025ec4ce3d13acbf32447e29 100644 --- a/gcc/m2/gm2-compiler/M2GCCDeclare.mod +++ b/gcc/m2/gm2-compiler/M2GCCDeclare.mod @@ -147,7 +147,7 @@ FROM M2Base IMPORT IsPseudoBaseProcedure, IsPseudoBaseFunction, FROM M2System IMPORT IsPseudoSystemFunction, IsSystemType, GetSystemTypeMinMax, Address, Word, Byte, Loc, System, IntegerN, CardinalN, WordN, RealN, SetN, ComplexN, - CSizeT, CSSizeT ; + CSizeT, CSSizeT, COffT ; FROM M2Bitset IMPORT Bitset, Bitnum ; FROM SymbolConversion IMPORT AddModGcc, Mod2Gcc, GccKnowsAbout, Poison, RemoveMod2Gcc ; @@ -185,7 +185,7 @@ FROM m2type IMPORT MarkFunctionReferenced, BuildStartRecord, BuildStartVarient, GetM2Cardinal16, GetM2Cardinal32, GetM2Cardinal64, GetM2Word16, GetM2Word32, GetM2Word64, GetM2Bitset8, GetM2Bitset16, GetM2Bitset32, GetM2Real32, GetM2Real64, GetM2Real96, GetM2Real128, GetM2Complex32, GetM2Complex64, GetM2Complex96, - GetM2Complex128, GetCSizeTType, GetCSSizeTType, + GetM2Complex128, GetCSizeTType, GetCSSizeTType, GetCOffTType, GetPackedBooleanType, BuildConstPointerType, BuildPointerType, BuildEnumerator, BuildStartEnumeration, BuildEndEnumeration, SetAlignment, SetTypePacked, SetDeclPacked, BuildSmallestTypeRange, @@ -3229,6 +3229,7 @@ BEGIN DeclareDefaultType(ShortComplex, "SHORTCOMPLEX", GetM2ShortComplexType()) ; DeclareDefaultType(CSizeT , "CSIZE_T" , GetCSizeTType()) ; DeclareDefaultType(CSSizeT , "CSSIZE_T" , GetCSSizeTType()) ; + DeclareDefaultType(COffT , "COFF_T" , GetCOffTType()) ; DeclareBoolean ; diff --git a/gcc/m2/gm2-compiler/M2GenGCC.mod b/gcc/m2/gm2-compiler/M2GenGCC.mod index 01ceeb61d60b096482ffb80724c61a302ba7b002..7ddcc1622900842ad8850cc1d0088fa54db79ea1 100644 --- a/gcc/m2/gm2-compiler/M2GenGCC.mod +++ b/gcc/m2/gm2-compiler/M2GenGCC.mod @@ -1660,7 +1660,7 @@ BEGIN THEN RETURN GetSizeOfHighFromUnbounded(tokenno, param) ELSE - RETURN BuildSize(tokenno, Mod2Gcc(GetType(param)), FALSE) + RETURN BuildSize (TokenToLocation (tokenno), Mod2Gcc (GetType (param)), FALSE) END END GetParamSize ; diff --git a/gcc/m2/gm2-compiler/M2Options.def b/gcc/m2/gm2-compiler/M2Options.def index 1d14868a353c10f859737cf4d8c9d243a5a43576..2b78add36cd3d97728113735c980b2652a8d0f6c 100644 --- a/gcc/m2/gm2-compiler/M2Options.def +++ b/gcc/m2/gm2-compiler/M2Options.def @@ -1135,6 +1135,20 @@ PROCEDURE GetEnableForward () : BOOLEAN ; PROCEDURE SetEnableForward (value: BOOLEAN) ; +(* + SetFileOffsetBits - set the number of bits used by SYSTEM.COFF_T to bits. +*) + +PROCEDURE SetFileOffsetBits (value: BOOLEAN; bits: CARDINAL) : BOOLEAN ; + + +(* + GetFileOffsetBits - return the number of bits used by SYSTEM.COFF_T. +*) + +PROCEDURE GetFileOffsetBits () : CARDINAL ; + + (* FinaliseOptions - once all options have been parsed we set any inferred values. diff --git a/gcc/m2/gm2-compiler/M2Options.mod b/gcc/m2/gm2-compiler/M2Options.mod index 9a0cf784c9ae81f056fc687d22e94b7541ec978b..4c03dfeddfba49b9252f5a8eb9eb7a6d788b64ec 100644 --- a/gcc/m2/gm2-compiler/M2Options.mod +++ b/gcc/m2/gm2-compiler/M2Options.mod @@ -95,6 +95,7 @@ VAR UselistFlag, CC1Quiet, SeenSources : BOOLEAN ; + OffTBits : CARDINAL ; ForcedLocationValue : location_t ; @@ -2029,6 +2030,30 @@ BEGIN END SetEnableForward ; +(* + SetFileOffsetBits - create SYSTEM.COFF_T as a signed integer of size bits. +*) + +PROCEDURE SetFileOffsetBits (value: BOOLEAN; bits: CARDINAL) : BOOLEAN ; +BEGIN + IF value + THEN + OffTBits := bits + END ; + RETURN TRUE +END SetFileOffsetBits ; + + +(* + GetFileOffsetBits - return the number of bits used to create SYSTEM.COFF_T. +*) + +PROCEDURE GetFileOffsetBits () : CARDINAL ; +BEGIN + RETURN OffTBits +END GetFileOffsetBits ; + + BEGIN cflag := FALSE ; (* -c. *) RuntimeModuleOverride := InitString (DefaultRuntimeModuleOverride) ; @@ -2121,5 +2146,6 @@ BEGIN DumpGimple := FALSE ; M2Dump := NIL ; M2DumpFilter := NIL ; - EnableForward := TRUE + EnableForward := TRUE ; + OffTBits := 64 ; (* Default to 64bit OFF_T. *) END M2Options. diff --git a/gcc/m2/gm2-compiler/M2System.def b/gcc/m2/gm2-compiler/M2System.def index 11b4fdef0bbd385ad55024db61037e035ad2115a..9c91b04e4a8292b20554844e72060a42ad06eaef 100644 --- a/gcc/m2/gm2-compiler/M2System.def +++ b/gcc/m2/gm2-compiler/M2System.def @@ -42,6 +42,7 @@ EXPORT QUALIFIED Address, (* System Type *) CSizeT, (* System Type *) CSSizeT, (* System Type *) + COffT, (* System Type *) Adr, (* System Function *) TSize, (* System Function *) @@ -75,6 +76,7 @@ VAR Word, Byte, Address, CSizeT, CSSizeT, + COffT, Adr, TSize, TBitSize, diff --git a/gcc/m2/gm2-compiler/M2System.mod b/gcc/m2/gm2-compiler/M2System.mod index a1a9f918ebc100910d08a9a74bbf5832075302a1..efd5d1183a3f2264702a9039022f922233ced0be 100644 --- a/gcc/m2/gm2-compiler/M2System.mod +++ b/gcc/m2/gm2-compiler/M2System.mod @@ -86,7 +86,8 @@ FROM m2type IMPORT GetMaxFrom, GetMinFrom, GetM2Real32, GetM2Real64, GetM2Real96, GetM2Real128, GetM2Complex32, GetM2Complex64, GetM2Complex96, GetM2Complex128, GetBitsetType, GetISOByteType, GetISOWordType, - GetCSizeTType, GetCSSizeTType, InitSystemTypes ; + GetCSizeTType, GetCSSizeTType, GetCOffTType, + InitSystemTypes ; FROM m2expr IMPORT BuildSize, GetSizeOf, AreConstantsEqual ; @@ -327,7 +328,8 @@ END InitISOTypes ; PROCEDURE MakeExtraSystemTypes ; BEGIN CSizeT := CreateType ('CSIZE_T' , '', '', TRUE, GetCSizeTType ()) ; - CSSizeT := CreateType ('CSSIZE_T', '', '', TRUE, GetCSSizeTType ()) + CSSizeT := CreateType ('CSSIZE_T', '', '', TRUE, GetCSSizeTType ()) ; + COffT := CreateType ('COFF_T', '', '', TRUE, GetCOffTType ()) ; END MakeExtraSystemTypes ; diff --git a/gcc/m2/gm2-compiler/P1SymBuild.mod b/gcc/m2/gm2-compiler/P1SymBuild.mod index e9fda9f4d980bb075fa9eb58b51f88f314b88681..02d4ac7f75147d97268fa6161b8c8d68b30f22e6 100644 --- a/gcc/m2/gm2-compiler/P1SymBuild.mod +++ b/gcc/m2/gm2-compiler/P1SymBuild.mod @@ -1042,7 +1042,8 @@ BEGIN 'first proper declaration of procedure {%1Ea}', ProcSym) ; MetaErrorT1 (tok, 'procedure {%1Ea} has already been declared', ProcSym) ELSE - PutProcedureDeclaredTok (ProcSym, ProperProcedure, tok) + PutProcedureDeclaredTok (ProcSym, ProperProcedure, tok) ; + PutProcedureDefined (ProcSym, ProperProcedure) END ; Assert (NOT CompilingDefinitionModule()) ; LeaveBlock diff --git a/gcc/m2/gm2-compiler/P2SymBuild.mod b/gcc/m2/gm2-compiler/P2SymBuild.mod index 0bce78fc0d4f72a57f2988bc9cc1e341feee4352..a625e7dd95d75d1d89b9e54b7adb8d6d87810d37 100644 --- a/gcc/m2/gm2-compiler/P2SymBuild.mod +++ b/gcc/m2/gm2-compiler/P2SymBuild.mod @@ -182,12 +182,13 @@ PROCEDURE stop ; BEGIN END stop ; Debug - call stop if symbol name is name. *) -PROCEDURE Debug (sym: CARDINAL; name: ARRAY OF CHAR) ; +PROCEDURE Debug (tok: CARDINAL; sym: CARDINAL; name: ARRAY OF CHAR) ; BEGIN IF MakeKey (name) = GetSymName (sym) THEN stop - END + END ; + MetaErrorT1 (tok, 'procedure {%1Wa}', sym) END Debug ; @@ -1503,7 +1504,7 @@ BEGIN PopT (ParamTotal) ; ProcSym := CARDINAL (OperandT (3 + CARDINAL (OperandT (3)) + 2)) ; tok := CARDINAL (OperandTok (3 + CARDINAL (OperandT (3)) + 2)) ; - Debug (ProcSym, 'foo') ; + (* Debug (tok, ProcSym, 'foo') ; *) curkind := GetProcedureKind (ProcSym, tok) ; PushT (ParamTotal) ; Annotate ("%1d||running total of no. of parameters") ; diff --git a/gcc/m2/gm2-compiler/SymbolTable.mod b/gcc/m2/gm2-compiler/SymbolTable.mod index 3d6584d38c9adacdb72775d217652952462ea3a4..826d2d39de10fae42d7c4f1e1c66512fd13cac9e 100644 --- a/gcc/m2/gm2-compiler/SymbolTable.mod +++ b/gcc/m2/gm2-compiler/SymbolTable.mod @@ -3940,7 +3940,8 @@ BEGIN HasVarArgs := FALSE ; (* Does the procedure use ... ? *) HasOptArg := FALSE ; (* Does this procedure use [ ] ? *) IsNoReturn := FALSE ; (* Declared attribute noreturn ? *) - ReturnOptional := FALSE (* Is the return value optional? *) + ReturnOptional := FALSE ; (* Is the return value optional? *) + ProcedureTok := UnknownTokenNo END END InitProcedureDeclaration ; diff --git a/gcc/m2/gm2-gcc/gcctypes.def b/gcc/m2/gm2-gcc/gcctypes.def index 097a40ae68f778ecaaf850c38874ccbf7d7661a9..f30a269ef16d5d531b686fc44a1cf552d757aa5e 100644 --- a/gcc/m2/gm2-gcc/gcctypes.def +++ b/gcc/m2/gm2-gcc/gcctypes.def @@ -21,7 +21,7 @@ along with GNU Modula-2; see the file COPYING3. If not see DEFINITION MODULE gcctypes ; -FROM SYSTEM IMPORT ADDRESS ; +FROM SYSTEM IMPORT ADDRESS, CARDINAL64 ; EXPORT UNQUALIFIED location_t, tree ; @@ -29,7 +29,7 @@ EXPORT UNQUALIFIED location_t, tree ; TYPE (* Not declared here by the bootstrap tool mc when --gcc-config-system is used. *) - location_t = CARDINAL ; + location_t = CARDINAL64 ; tree = ADDRESS ; diff --git a/gcc/m2/gm2-gcc/m2linemap.cc b/gcc/m2/gm2-gcc/m2linemap.cc index 338d691e8e28ac7d8f1b7d5138d9114086d719cb..feb62b3ed4d84af29fac7679bf22ce36ef4c7c8c 100644 --- a/gcc/m2/gm2-gcc/m2linemap.cc +++ b/gcc/m2/gm2-gcc/m2linemap.cc @@ -126,6 +126,7 @@ m2linemap_GetLocationBinary (location_t caret, location_t start, location_t fini linemap_add (line_table, LC_ENTER, false, xstrdup (m2linemap_GetFilenameFromLocation (start)), 1); gcc_assert (inFile); location_t location = make_location (caret, start, finish); + linemap_add (line_table, LC_LEAVE, false, NULL, 0); return location; } return caret; diff --git a/gcc/m2/gm2-gcc/m2options.h b/gcc/m2/gm2-gcc/m2options.h index ab1a2281e6675374400a0e43e84205350c6a3052..d60b510de34ff713526bec9e196516fb635e62f3 100644 --- a/gcc/m2/gm2-gcc/m2options.h +++ b/gcc/m2/gm2-gcc/m2options.h @@ -99,6 +99,8 @@ EXTERN void M2Options_SetSwig (bool value); EXTERN void M2Options_SetForcedLocation (location_t location); EXTERN location_t M2Options_OverrideLocation (location_t location); EXTERN void M2Options_SetStatistics (bool on); +EXTERN bool M2Options_SetFileOffsetBits (bool value, unsigned int bits); +EXTERN unsigned int M2Options_GetFileOffsetBits (void); EXTERN void M2Options_CppProg (const char *program); EXTERN void M2Options_CppArg (const char *opt, const char *arg, bool joined); EXTERN void M2Options_SetWholeProgram (bool value); diff --git a/gcc/m2/gm2-gcc/m2type.cc b/gcc/m2/gm2-gcc/m2type.cc index 1a489274e4a24adbb78a41d8341db34a5d43a924..9f7a433e98061d844fc7ba0bf744215c1a3fcd66 100644 --- a/gcc/m2/gm2-gcc/m2type.cc +++ b/gcc/m2/gm2-gcc/m2type.cc @@ -119,6 +119,7 @@ static GTY (()) tree m2_complex96_type_node; static GTY (()) tree m2_complex128_type_node; static GTY (()) tree m2_packed_boolean_type_node; static GTY (()) tree m2_cardinal_address_type_node; +static GTY (()) tree m2_offt_type_node; /* gm2_canonicalize_array - returns a unique array node based on index_type and type. */ @@ -824,7 +825,7 @@ m2type_GetIntegerType (void) return integer_type_node; } -/* GetCSizeTType return a type representing, size_t on this system. */ +/* GetCSizeTType return a type representing size_t. */ tree m2type_GetCSizeTType (void) @@ -832,8 +833,7 @@ m2type_GetCSizeTType (void) return sizetype; } -/* GetCSSizeTType return a type representing, size_t on this - system. */ +/* GetCSSizeTType return a type representing size_t. */ tree m2type_GetCSSizeTType (void) @@ -841,6 +841,14 @@ m2type_GetCSSizeTType (void) return ssizetype; } +/* GetCSSizeTType return a type representing off_t. */ + +tree +m2type_GetCOffTType (void) +{ + return m2_offt_type_node; +} + /* GetPackedBooleanType return the packed boolean data type node. */ tree @@ -1373,6 +1381,14 @@ build_m2_iso_byte_node (location_t location, int loc) return c; } +static tree +build_m2_offt_type_node (location_t location) +{ + m2assert_AssertLocation (location); + return build_m2_specific_size_type (location, INTEGER_TYPE, + M2Options_GetFileOffsetBits (), true); +} + /* m2type_InitSystemTypes initialise loc and word derivatives. */ void @@ -1386,6 +1402,7 @@ m2type_InitSystemTypes (location_t location, int loc) m2_word16_type_node = build_m2_word16_type_node (location, loc); m2_word32_type_node = build_m2_word32_type_node (location, loc); m2_word64_type_node = build_m2_word64_type_node (location, loc); + m2_offt_type_node = build_m2_offt_type_node (location); } static tree diff --git a/gcc/m2/gm2-gcc/m2type.def b/gcc/m2/gm2-gcc/m2type.def index eea623ccf9c461c770f8481b4c03076e85a61cfa..797335e00704b35501925607a802651a654f385e 100644 --- a/gcc/m2/gm2-gcc/m2type.def +++ b/gcc/m2/gm2-gcc/m2type.def @@ -766,19 +766,26 @@ PROCEDURE GetM2CharType () : tree ; (* - GetCSizeTType - return a type representing, size_t on this system. + GetCSizeTType - return a type representing size_t. *) PROCEDURE GetCSizeTType () : tree ; (* - GetCSSizeTType - return a type representing, ssize_t on this system. + GetCSSizeTType - return a type representing ssize_t. *) PROCEDURE GetCSSizeTType () : tree ; +(* + GetCOffTType - return a type representing OFF_T. +*) + +PROCEDURE GetCOffTType () : tree ; + + (* BuildArrayStringConstructor - creates an array constructor for, arrayType, consisting of the character elements diff --git a/gcc/m2/gm2-gcc/m2type.h b/gcc/m2/gm2-gcc/m2type.h index f1da0f6993834e5db27566f19fa7b200f7b831a6..04370d63e2bd8b91c15924231221a4ffcc271e3c 100644 --- a/gcc/m2/gm2-gcc/m2type.h +++ b/gcc/m2/gm2-gcc/m2type.h @@ -130,7 +130,7 @@ EXTERN tree m2type_GetShortCardType (void); EXTERN tree m2type_GetProcType (void); EXTERN tree m2type_GetCSizeTType (void); EXTERN tree m2type_GetCSSizeTType (void); - +EXTERN tree m2type_GetCOffTType (void); EXTERN tree m2type_GetM2CType (void); EXTERN tree m2type_GetBitsetType (void); diff --git a/gcc/m2/gm2-lang.cc b/gcc/m2/gm2-lang.cc index 0ee0e54336a6e01a7e1473f76ae15746e31c41d2..e8820daf4745a675d71330e803cc952a5b3ac0d5 100644 --- a/gcc/m2/gm2-lang.cc +++ b/gcc/m2/gm2-lang.cc @@ -512,6 +512,16 @@ gm2_langhook_handle_option ( return M2Options_SetUninitVariableChecking (value, "known"); case OPT_Wuninit_variable_checking_: return M2Options_SetUninitVariableChecking (value, arg); + case OPT_fm2_file_offset_bits_: + { + if (arg != NULL) + { + unsigned int bits = atoi (arg); + if (bits > 0) + return M2Options_SetFileOffsetBits (value, bits); + } + return 0; + } case OPT_fm2_strict_type: M2Options_SetStrictTypeChecking (value); return 1; diff --git a/gcc/m2/gm2-libs-coroutines/SYSTEM.def b/gcc/m2/gm2-libs-coroutines/SYSTEM.def index a186f8b4a323dcf97e425a80781453f22a1e1ddf..ea982e8ffa712acb9e615a5f47b35a96fe6d61ee 100644 --- a/gcc/m2/gm2-libs-coroutines/SYSTEM.def +++ b/gcc/m2/gm2-libs-coroutines/SYSTEM.def @@ -34,7 +34,7 @@ DEFINITION MODULE SYSTEM ; FROM COROUTINES IMPORT PROTECTION ; EXPORT QUALIFIED (* the following are built into the compiler: *) - ADDRESS, WORD, BYTE, CSIZE_T, CSSIZE_T, (* @SYSTEM_DATATYPES@ *) + ADDRESS, WORD, BYTE, CSIZE_T, CSSIZE_T, COFF_T, (* @SYSTEM_DATATYPES@ *) ADR, TSIZE, ROTATE, SHIFT, THROW, TBITSIZE, (* SIZE is exported depending upon -fpim2 and -fpedantic. *) diff --git a/gcc/m2/gm2-libs-iso/SYSTEM.def b/gcc/m2/gm2-libs-iso/SYSTEM.def index f25fc6ff3a297cf446397fee383c34a1d9c6c731..b99b2afdccce50cc4668d9fc08ef4c4aea75b816 100644 --- a/gcc/m2/gm2-libs-iso/SYSTEM.def +++ b/gcc/m2/gm2-libs-iso/SYSTEM.def @@ -17,7 +17,7 @@ DEFINITION MODULE SYSTEM; (* The constants and types define underlying properties of storage *) EXPORT QUALIFIED BITSPERLOC, LOCSPERWORD, - LOC, BYTE, WORD, ADDRESS, CSIZE_T, CSSIZE_T, (* @SYSTEM_DATATYPES@ *) + LOC, BYTE, WORD, ADDRESS, CSIZE_T, CSSIZE_T, COFF_T, (* @SYSTEM_DATATYPES@ *) ADDADR, SUBADR, DIFADR, MAKEADR, ADR, ROTATE, SHIFT, CAST, TSIZE, diff --git a/gcc/m2/gm2-libs-min/SYSTEM.def b/gcc/m2/gm2-libs-min/SYSTEM.def index 72543052a56216b79609cf281e7e11d0d73220cc..77ea228e5ec4958e0b914965e3679f59d0955710 100644 --- a/gcc/m2/gm2-libs-min/SYSTEM.def +++ b/gcc/m2/gm2-libs-min/SYSTEM.def @@ -27,7 +27,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see DEFINITION MODULE SYSTEM ; EXPORT QUALIFIED BITSPERBYTE, BYTESPERWORD, - ADDRESS, WORD, BYTE, CSIZE_T, CSSIZE_T, (* @SYSTEM_DATATYPES@ *) + ADDRESS, WORD, BYTE, CSIZE_T, CSSIZE_T, COFF_T, (* @SYSTEM_DATATYPES@ *) ADR, TSIZE ; (* SIZE is also exported if -fpim2 is used *) diff --git a/gcc/m2/gm2-libs/SYSTEM.def b/gcc/m2/gm2-libs/SYSTEM.def index fafd97dbc07bd154722298c4293a87d11a90d24b..1b2949eebb0b8a88d2cfc365bfdf16821166ad01 100644 --- a/gcc/m2/gm2-libs/SYSTEM.def +++ b/gcc/m2/gm2-libs/SYSTEM.def @@ -27,7 +27,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see DEFINITION MODULE SYSTEM ; EXPORT QUALIFIED BITSPERBYTE, BYTESPERWORD, - ADDRESS, WORD, BYTE, CSIZE_T, CSSIZE_T, (* @SYSTEM_DATATYPES@ *) + ADDRESS, WORD, BYTE, CSIZE_T, CSSIZE_T, COFF_T, CARDINAL64, (* @SYSTEM_DATATYPES@ *) ADR, TSIZE, ROTATE, SHIFT, THROW, TBITSIZE ; (* SIZE is also exported if -fpim2 is used. *) diff --git a/gcc/m2/gm2-libs/libc.def b/gcc/m2/gm2-libs/libc.def index 3c43f165eb07312df43cda936e29557fb1b46f55..f1f13ddd9aebb6ace9f9f02d409b502788dd57c7 100644 --- a/gcc/m2/gm2-libs/libc.def +++ b/gcc/m2/gm2-libs/libc.def @@ -26,7 +26,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see DEFINITION MODULE FOR "C" libc ; -FROM SYSTEM IMPORT ADDRESS, CSIZE_T, CSSIZE_T ; +FROM SYSTEM IMPORT ADDRESS, CSIZE_T, CSSIZE_T, COFF_T ; EXPORT UNQUALIFIED time_t, timeb, tm, ptrToTM, atof, atoi, atol, atoll, @@ -311,7 +311,7 @@ PROCEDURE creat (filename: ADDRESS; mode: CARDINAL) : INTEGER; off_t lseek(int fildes, off_t offset, int whence); *) -PROCEDURE lseek (fd: INTEGER; offset: CSSIZE_T; whence: INTEGER) : [ CSSIZE_T ] ; +PROCEDURE lseek (fd: INTEGER; offset: CSSIZE_T; whence: INTEGER) : [ COFF_T ] ; (* diff --git a/gcc/m2/lang.opt b/gcc/m2/lang.opt index 655ff9173e4f5aa6ec6bd2109e6b196f4709d39e..1ea55f21e4c774d62e168847cd76fb1583003580 100644 --- a/gcc/m2/lang.opt +++ b/gcc/m2/lang.opt @@ -154,6 +154,10 @@ fm2-dump-filter= Modula-2 Joined filter the language dump using a comma separated list of procedures and modules +fm2-file-offset-bits= +Modula-2 Joined +override the default 64 bit definition of SYSTEM.COFF_T with the argument specified + fm2-g Modula-2 generate extra nops to improve debugging, producing an instruction for every code related keyword diff --git a/gcc/m2/mc-boot-ch/Glibc.c b/gcc/m2/mc-boot-ch/Glibc.c index e4c910b168a9b4eb38f95477f210b18d0d75428f..1709ccf3a3625ec12cb243612d2f680f8a7050af 100644 --- a/gcc/m2/mc-boot-ch/Glibc.c +++ b/gcc/m2/mc-boot-ch/Glibc.c @@ -356,7 +356,7 @@ off_t libc_lseek (int fd, off_t offset, int whence) { tracedb ("libc_lseek (%s, %p, %d)\n", fd, offset, whence); - int result = lseek (fd, offset, whence); + off_t result = lseek (fd, offset, whence); tracedb_result (result); return result; } diff --git a/gcc/m2/mc-boot/GASCII.cc b/gcc/m2/mc-boot/GASCII.cc index 35e77522b701580b8af480ec1b2f1d961bd9f94f..72cc6b251330454430898935fe1ceeec97c9f88a 100644 --- a/gcc/m2/mc-boot/GASCII.cc +++ b/gcc/m2/mc-boot/GASCII.cc @@ -25,6 +25,7 @@ a copy of the GCC Runtime Library Exception along with this program; see the files COPYING3 and COPYING.RUNTIME respectively. If not, see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GASCII.h b/gcc/m2/mc-boot/GASCII.h index 18c2725057842062c139f68af4b48b19f4dc28ce..c5a38b227c99262329e4897111047cb115b75256 100644 --- a/gcc/m2/mc-boot/GASCII.h +++ b/gcc/m2/mc-boot/GASCII.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_ASCII_H) # define _ASCII_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GArgs.cc b/gcc/m2/mc-boot/GArgs.cc index c87c35e73b6901985728df9933521e3e21361a2c..2aafca77a3b6d64a142c5f2fc8c71ea6240d1f15 100644 --- a/gcc/m2/mc-boot/GArgs.cc +++ b/gcc/m2/mc-boot/GArgs.cc @@ -25,6 +25,7 @@ a copy of the GCC Runtime Library Exception along with this program; see the files COPYING3 and COPYING.RUNTIME respectively. If not, see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GArgs.h b/gcc/m2/mc-boot/GArgs.h index 4a7b4f9c886c872a704bff13ca0e370b90d0cffc..8de0d0f52f0f7335fd5b8a23dcb4394baa064ff7 100644 --- a/gcc/m2/mc-boot/GArgs.h +++ b/gcc/m2/mc-boot/GArgs.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_Args_H) # define _Args_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GAssertion.cc b/gcc/m2/mc-boot/GAssertion.cc index 18d693185f7fbe9712c815e90da9ed01be57611b..f4185f91cacc064ca3de21ed53dc76412c93adf2 100644 --- a/gcc/m2/mc-boot/GAssertion.cc +++ b/gcc/m2/mc-boot/GAssertion.cc @@ -25,6 +25,7 @@ a copy of the GCC Runtime Library Exception along with this program; see the files COPYING3 and COPYING.RUNTIME respectively. If not, see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GAssertion.h b/gcc/m2/mc-boot/GAssertion.h index 94ca402a2152a4db31c6bb772119fb03cb80dce5..0ea29e4f406f1cab5f52cf527516ad88d9736ce2 100644 --- a/gcc/m2/mc-boot/GAssertion.h +++ b/gcc/m2/mc-boot/GAssertion.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_Assertion_H) # define _Assertion_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GBreak.cc b/gcc/m2/mc-boot/GBreak.cc index f31d4a82b5ada9f1a9347c4751b3e8422e42fec2..e8b5d053ac69af272275c54675392457c32020d9 100644 --- a/gcc/m2/mc-boot/GBreak.cc +++ b/gcc/m2/mc-boot/GBreak.cc @@ -25,6 +25,7 @@ a copy of the GCC Runtime Library Exception along with this program; see the files COPYING3 and COPYING.RUNTIME respectively. If not, see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GBreak.h b/gcc/m2/mc-boot/GBreak.h index 14bd68e1ee9016997935d2fef994e918e3c1729b..c29c8b9d3e066c9ba17234b884b42836f5499acb 100644 --- a/gcc/m2/mc-boot/GBreak.h +++ b/gcc/m2/mc-boot/GBreak.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_Break_H) # define _Break_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GCOROUTINES.h b/gcc/m2/mc-boot/GCOROUTINES.h index 7543c7e4969cf0d12de8300642adbb4bf59f3de5..678a8742248419302d0cd9bb8ea51ee2850da5c5 100644 --- a/gcc/m2/mc-boot/GCOROUTINES.h +++ b/gcc/m2/mc-boot/GCOROUTINES.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_COROUTINES_H) # define _COROUTINES_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GCmdArgs.cc b/gcc/m2/mc-boot/GCmdArgs.cc index 9c0da752714b1d9ac6c13b91ff7e157cc9c7e214..220fd0c3a8a9a4bbf2f1fc48608a54d19884d6e7 100644 --- a/gcc/m2/mc-boot/GCmdArgs.cc +++ b/gcc/m2/mc-boot/GCmdArgs.cc @@ -25,6 +25,7 @@ a copy of the GCC Runtime Library Exception along with this program; see the files COPYING3 and COPYING.RUNTIME respectively. If not, see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GCmdArgs.h b/gcc/m2/mc-boot/GCmdArgs.h index b29a52acc0d04751f665f48c6c9fca534bb01e71..a078d64a06d70fca04f29fddbb115fd21c20f862 100644 --- a/gcc/m2/mc-boot/GCmdArgs.h +++ b/gcc/m2/mc-boot/GCmdArgs.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_CmdArgs_H) # define _CmdArgs_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GDebug.cc b/gcc/m2/mc-boot/GDebug.cc index 4e25f76428020c008b8f46b3cc85f164c668e533..1aa02a60e59150775e2f264de0486a577fc6c030 100644 --- a/gcc/m2/mc-boot/GDebug.cc +++ b/gcc/m2/mc-boot/GDebug.cc @@ -25,6 +25,7 @@ a copy of the GCC Runtime Library Exception along with this program; see the files COPYING3 and COPYING.RUNTIME respectively. If not, see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GDebug.h b/gcc/m2/mc-boot/GDebug.h index b7530ea4d988d72ce29d79c44e45001d1dc0d4aa..c43e363fe14ede45b9c39d055a347ec750f77d9f 100644 --- a/gcc/m2/mc-boot/GDebug.h +++ b/gcc/m2/mc-boot/GDebug.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_Debug_H) # define _Debug_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GDynamicStrings.cc b/gcc/m2/mc-boot/GDynamicStrings.cc index 55d2ae8038bc4fef3394a8c79366cb0a11315fa9..a409ce79b1b4fb92895d2a31cf208021c839eaf5 100644 --- a/gcc/m2/mc-boot/GDynamicStrings.cc +++ b/gcc/m2/mc-boot/GDynamicStrings.cc @@ -25,6 +25,7 @@ a copy of the GCC Runtime Library Exception along with this program; see the files COPYING3 and COPYING.RUNTIME respectively. If not, see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GDynamicStrings.h b/gcc/m2/mc-boot/GDynamicStrings.h index 1939b73037ae1665d5a79a700df9a3d31f97b90c..1860701b310b424f9a492590aa0b724af2803eb5 100644 --- a/gcc/m2/mc-boot/GDynamicStrings.h +++ b/gcc/m2/mc-boot/GDynamicStrings.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_DynamicStrings_H) # define _DynamicStrings_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GEnvironment.cc b/gcc/m2/mc-boot/GEnvironment.cc index 044fba1079756e3a67e9035c0575a29ca9d0125b..5a2ad756a05349be85f963afd6110f277d30fc25 100644 --- a/gcc/m2/mc-boot/GEnvironment.cc +++ b/gcc/m2/mc-boot/GEnvironment.cc @@ -25,6 +25,7 @@ a copy of the GCC Runtime Library Exception along with this program; see the files COPYING3 and COPYING.RUNTIME respectively. If not, see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GEnvironment.h b/gcc/m2/mc-boot/GEnvironment.h index 3bfadaaebed2be15ecc159fe491f23a190699542..cf58be08b5fb85e5440ae163cadde21b38f3104c 100644 --- a/gcc/m2/mc-boot/GEnvironment.h +++ b/gcc/m2/mc-boot/GEnvironment.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_Environment_H) # define _Environment_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GFIO.cc b/gcc/m2/mc-boot/GFIO.cc index c7f857b265a0254ce44d61482819179df65c9318..440919af533811ed531f3194959ceff7712116a4 100644 --- a/gcc/m2/mc-boot/GFIO.cc +++ b/gcc/m2/mc-boot/GFIO.cc @@ -25,6 +25,7 @@ a copy of the GCC Runtime Library Exception along with this program; see the files COPYING3 and COPYING.RUNTIME respectively. If not, see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GFIO.h b/gcc/m2/mc-boot/GFIO.h index 8b69241f1751e1a91756b06a21ce3e835847d5f1..3ab2c518da4a8263ad71de0218711b1ab67f0ccd 100644 --- a/gcc/m2/mc-boot/GFIO.h +++ b/gcc/m2/mc-boot/GFIO.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_FIO_H) # define _FIO_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GFormatStrings.cc b/gcc/m2/mc-boot/GFormatStrings.cc index f4c4fd6f8c102be75d6b4ec081a20451f9189311..e2ea1954d191b3988cf33ffa351588f670adf08b 100644 --- a/gcc/m2/mc-boot/GFormatStrings.cc +++ b/gcc/m2/mc-boot/GFormatStrings.cc @@ -25,6 +25,7 @@ a copy of the GCC Runtime Library Exception along with this program; see the files COPYING3 and COPYING.RUNTIME respectively. If not, see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GFormatStrings.h b/gcc/m2/mc-boot/GFormatStrings.h index 6ab12c4ef02bbad7bed02fe961494d1ab8473b5b..61e84541e51321acd29dfe11d091566bb6f68f7a 100644 --- a/gcc/m2/mc-boot/GFormatStrings.h +++ b/gcc/m2/mc-boot/GFormatStrings.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_FormatStrings_H) # define _FormatStrings_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GFpuIO.cc b/gcc/m2/mc-boot/GFpuIO.cc index 6bd6a6bc59fd7c288e0d8fafad68e72ff2d0641d..3fdd5fd2925db7b85dbcc81348c1cacaa7db61f8 100644 --- a/gcc/m2/mc-boot/GFpuIO.cc +++ b/gcc/m2/mc-boot/GFpuIO.cc @@ -25,6 +25,7 @@ a copy of the GCC Runtime Library Exception along with this program; see the files COPYING3 and COPYING.RUNTIME respectively. If not, see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GFpuIO.h b/gcc/m2/mc-boot/GFpuIO.h index 1c6670d6c82ba1ee7d582b93703fb4f5816a73a3..1b6f9573ebc139ad9769e21db7a609428c1bca4f 100644 --- a/gcc/m2/mc-boot/GFpuIO.h +++ b/gcc/m2/mc-boot/GFpuIO.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_FpuIO_H) # define _FpuIO_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GIO.cc b/gcc/m2/mc-boot/GIO.cc index 6e0ae3150a3491f3a27e8aaa4ca2c79e440d1a87..a64f401a71619a6048e5cee0598b3d5716a26162 100644 --- a/gcc/m2/mc-boot/GIO.cc +++ b/gcc/m2/mc-boot/GIO.cc @@ -25,6 +25,7 @@ a copy of the GCC Runtime Library Exception along with this program; see the files COPYING3 and COPYING.RUNTIME respectively. If not, see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GIO.h b/gcc/m2/mc-boot/GIO.h index d01d69a65168b0278220e7feffb09a22d22cbc8f..4037cfdef4c793267b08b90b9526852ab262ef74 100644 --- a/gcc/m2/mc-boot/GIO.h +++ b/gcc/m2/mc-boot/GIO.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_IO_H) # define _IO_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GIndexing.cc b/gcc/m2/mc-boot/GIndexing.cc index 5ab0c4296aaf23aeb7fb85d002f9961c07a7a5c3..a38a4776c8c43916ff597714812ba7dad8589872 100644 --- a/gcc/m2/mc-boot/GIndexing.cc +++ b/gcc/m2/mc-boot/GIndexing.cc @@ -18,6 +18,7 @@ You should have received a copy of the GNU General Public License along with GCC; see the file COPYING3. If not see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GIndexing.h b/gcc/m2/mc-boot/GIndexing.h index e1054b026fd8bec507ea4d4180aad7fefcc33fe7..f6a58cf9b5472723d1418b8b246578c8e24ce17c 100644 --- a/gcc/m2/mc-boot/GIndexing.h +++ b/gcc/m2/mc-boot/GIndexing.h @@ -24,6 +24,7 @@ along with GNU Modula-2; see the file COPYING3. If not see #if !defined (_Indexing_H) # define _Indexing_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GM2Dependent.cc b/gcc/m2/mc-boot/GM2Dependent.cc index e8ade8773a14d0f3f9982cdca7a28b2a0e088b36..32f204fbbbceb08899ab4613045ef7988a965bbd 100644 --- a/gcc/m2/mc-boot/GM2Dependent.cc +++ b/gcc/m2/mc-boot/GM2Dependent.cc @@ -25,6 +25,7 @@ a copy of the GCC Runtime Library Exception along with this program; see the files COPYING3 and COPYING.RUNTIME respectively. If not, see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GM2Dependent.h b/gcc/m2/mc-boot/GM2Dependent.h index b9ad0c780b8c1c72cc44fddeeb0765709a865ecd..f95d585ed96a682c9d5a17042305294b9a1ba4df 100644 --- a/gcc/m2/mc-boot/GM2Dependent.h +++ b/gcc/m2/mc-boot/GM2Dependent.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_M2Dependent_H) # define _M2Dependent_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GM2EXCEPTION.cc b/gcc/m2/mc-boot/GM2EXCEPTION.cc index 62d47f08b5b532d0ebbe6ee941ebc3852d869ba9..e2d89e0cb3742179b49fb752e66c8caecf52a3e7 100644 --- a/gcc/m2/mc-boot/GM2EXCEPTION.cc +++ b/gcc/m2/mc-boot/GM2EXCEPTION.cc @@ -25,6 +25,7 @@ a copy of the GCC Runtime Library Exception along with this program; see the files COPYING3 and COPYING.RUNTIME respectively. If not, see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GM2EXCEPTION.h b/gcc/m2/mc-boot/GM2EXCEPTION.h index 6f6b2f6712b6c02c01d9666ab6a4e408e7df1e16..66eb23ab12f001b796146eb09fa657e594525cfc 100644 --- a/gcc/m2/mc-boot/GM2EXCEPTION.h +++ b/gcc/m2/mc-boot/GM2EXCEPTION.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_M2EXCEPTION_H) # define _M2EXCEPTION_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GM2RTS.cc b/gcc/m2/mc-boot/GM2RTS.cc index b2361270e645765c2ccacb7d00fd3c298a46a39f..7149c1865dcddcedeeb4c7ecdcf67a10f39efe92 100644 --- a/gcc/m2/mc-boot/GM2RTS.cc +++ b/gcc/m2/mc-boot/GM2RTS.cc @@ -25,6 +25,7 @@ a copy of the GCC Runtime Library Exception along with this program; see the files COPYING3 and COPYING.RUNTIME respectively. If not, see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> @@ -496,6 +497,7 @@ extern "C" void M2RTS_Halt (const char *description_, unsigned int _description_ memcpy (function, function_, _function_high+1); M2RTS_ErrorMessage ((const char *) description, _description_high, (const char *) filename, _filename_high, line, (const char *) function, _function_high); + libc_exit (1); } @@ -508,6 +510,7 @@ extern "C" void M2RTS_Halt (const char *description_, unsigned int _description_ extern "C" void M2RTS_HaltC (void * description, void * filename, void * function, unsigned int line) { ErrorMessageC (description, filename, line, function); + libc_exit (1); } diff --git a/gcc/m2/mc-boot/GM2RTS.h b/gcc/m2/mc-boot/GM2RTS.h index ea6eabae97142ff22bcbb8ebd30975d47a1b0f7f..a1dbf88e2b63a1b2ed5677fd9aee72e32b8e62aa 100644 --- a/gcc/m2/mc-boot/GM2RTS.h +++ b/gcc/m2/mc-boot/GM2RTS.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_M2RTS_H) # define _M2RTS_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GMemUtils.cc b/gcc/m2/mc-boot/GMemUtils.cc index 828144fb02356a352c95627d37cbba7c2306d414..4bdbe3e8344887a25d2b50149e6920adc952b654 100644 --- a/gcc/m2/mc-boot/GMemUtils.cc +++ b/gcc/m2/mc-boot/GMemUtils.cc @@ -25,6 +25,7 @@ a copy of the GCC Runtime Library Exception along with this program; see the files COPYING3 and COPYING.RUNTIME respectively. If not, see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GMemUtils.h b/gcc/m2/mc-boot/GMemUtils.h index 38a843417d96f17214f5d96efbc1b5aaf12bb284..9fd5e46e790269bcf7f62cd59595889dc02b48fe 100644 --- a/gcc/m2/mc-boot/GMemUtils.h +++ b/gcc/m2/mc-boot/GMemUtils.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_MemUtils_H) # define _MemUtils_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GNumberIO.cc b/gcc/m2/mc-boot/GNumberIO.cc index 8a04cbff7e63bb5d7136f8ab690769069d200edb..9de7a51353af3e63c8a94170f27ca37e7abc1832 100644 --- a/gcc/m2/mc-boot/GNumberIO.cc +++ b/gcc/m2/mc-boot/GNumberIO.cc @@ -25,6 +25,7 @@ a copy of the GCC Runtime Library Exception along with this program; see the files COPYING3 and COPYING.RUNTIME respectively. If not, see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GNumberIO.h b/gcc/m2/mc-boot/GNumberIO.h index 13960e9660750ddcf6b5db6eed5f1b99272335a2..b40c33d0316eaab495828d979cbd73a546bdbf34 100644 --- a/gcc/m2/mc-boot/GNumberIO.h +++ b/gcc/m2/mc-boot/GNumberIO.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_NumberIO_H) # define _NumberIO_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GPushBackInput.cc b/gcc/m2/mc-boot/GPushBackInput.cc index 60fb12ef898e86c461cb86521b0daff36960a90b..e526bf7438e50fe0fefdbc24b5a5769a547f33e3 100644 --- a/gcc/m2/mc-boot/GPushBackInput.cc +++ b/gcc/m2/mc-boot/GPushBackInput.cc @@ -25,6 +25,7 @@ a copy of the GCC Runtime Library Exception along with this program; see the files COPYING3 and COPYING.RUNTIME respectively. If not, see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GPushBackInput.h b/gcc/m2/mc-boot/GPushBackInput.h index c2e034429481146a730958e7233794e260925d93..b747e50baa4c677098ab6642db628aa62e6d1f7f 100644 --- a/gcc/m2/mc-boot/GPushBackInput.h +++ b/gcc/m2/mc-boot/GPushBackInput.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_PushBackInput_H) # define _PushBackInput_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GRTExceptions.cc b/gcc/m2/mc-boot/GRTExceptions.cc index 2f84fa638c30a1a5f1248de91e4be259f269abee..881d97de1ec601859ec09d13ecdc7b0e9f020935 100644 --- a/gcc/m2/mc-boot/GRTExceptions.cc +++ b/gcc/m2/mc-boot/GRTExceptions.cc @@ -25,6 +25,7 @@ a copy of the GCC Runtime Library Exception along with this program; see the files COPYING3 and COPYING.RUNTIME respectively. If not, see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GRTExceptions.h b/gcc/m2/mc-boot/GRTExceptions.h index 24f3da38d6c301858600ddfbcd33413083dc8d02..3d70cb3594676f3145f9acde593b56669aaf3889 100644 --- a/gcc/m2/mc-boot/GRTExceptions.h +++ b/gcc/m2/mc-boot/GRTExceptions.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_RTExceptions_H) # define _RTExceptions_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GRTco.h b/gcc/m2/mc-boot/GRTco.h index 86c5b0316b1791d8fcc4742518cbeceb4d664eca..aa6e928363545ee4e1be65174049cc2261e6e781 100644 --- a/gcc/m2/mc-boot/GRTco.h +++ b/gcc/m2/mc-boot/GRTco.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_RTco_H) # define _RTco_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GRTentity.h b/gcc/m2/mc-boot/GRTentity.h index 381ba680b634d52f62e187f7c7456946236b4847..6f54002aa31157e37f12d0ba84795a58fe7335e3 100644 --- a/gcc/m2/mc-boot/GRTentity.h +++ b/gcc/m2/mc-boot/GRTentity.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_RTentity_H) # define _RTentity_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GRTint.cc b/gcc/m2/mc-boot/GRTint.cc index 188b6e0a9a24d799e9410457a507f55900606710..8f0f81036c32c5d10c0de2ad2ca32eba64ec0d71 100644 --- a/gcc/m2/mc-boot/GRTint.cc +++ b/gcc/m2/mc-boot/GRTint.cc @@ -25,6 +25,7 @@ a copy of the GCC Runtime Library Exception along with this program; see the files COPYING3 and COPYING.RUNTIME respectively. If not, see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GRTint.h b/gcc/m2/mc-boot/GRTint.h index daf64ecaae62050aa0c43646777d4ad2bee7e28d..703dfb4c04ea556d0b16349369ece9d140545c26 100644 --- a/gcc/m2/mc-boot/GRTint.h +++ b/gcc/m2/mc-boot/GRTint.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_RTint_H) # define _RTint_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GSArgs.cc b/gcc/m2/mc-boot/GSArgs.cc index 414ea1f004e25bc19bd04643a80a42319a809b8a..cd4514ef8ddd865006b6db685f0244354cfab73a 100644 --- a/gcc/m2/mc-boot/GSArgs.cc +++ b/gcc/m2/mc-boot/GSArgs.cc @@ -25,6 +25,7 @@ a copy of the GCC Runtime Library Exception along with this program; see the files COPYING3 and COPYING.RUNTIME respectively. If not, see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GSArgs.h b/gcc/m2/mc-boot/GSArgs.h index 5164cca0bff8a6e44fe86762ef3ec89d3b42149a..70cab3886989bfc851fac56a07a5901972606d28 100644 --- a/gcc/m2/mc-boot/GSArgs.h +++ b/gcc/m2/mc-boot/GSArgs.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_SArgs_H) # define _SArgs_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GSFIO.cc b/gcc/m2/mc-boot/GSFIO.cc index 6ae0d5e048554fbe90e86b0f0663f986ca53602f..06fabab34f42195f927416e61f2cc7de8f2a1797 100644 --- a/gcc/m2/mc-boot/GSFIO.cc +++ b/gcc/m2/mc-boot/GSFIO.cc @@ -25,6 +25,7 @@ a copy of the GCC Runtime Library Exception along with this program; see the files COPYING3 and COPYING.RUNTIME respectively. If not, see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GSFIO.h b/gcc/m2/mc-boot/GSFIO.h index 42ffc48782a6b33bb74f03c240322c57b3d205b4..e7fba7ebf7c8afec5b8c61f2d3a24def5b4917b5 100644 --- a/gcc/m2/mc-boot/GSFIO.h +++ b/gcc/m2/mc-boot/GSFIO.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_SFIO_H) # define _SFIO_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GSYSTEM.h b/gcc/m2/mc-boot/GSYSTEM.h index e3d51ab97d58066ac301f9010827afad12ab0f58..125787f008a76792a16db8f22f4791c27c8a9706 100644 --- a/gcc/m2/mc-boot/GSYSTEM.h +++ b/gcc/m2/mc-boot/GSYSTEM.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_SYSTEM_H) # define _SYSTEM_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GSelective.h b/gcc/m2/mc-boot/GSelective.h index af2e9c31feaa97e38c65eb291633c6bb7c0a9de7..31f5932fedbb4160c422e8e9c84d87461943cafa 100644 --- a/gcc/m2/mc-boot/GSelective.h +++ b/gcc/m2/mc-boot/GSelective.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_Selective_H) # define _Selective_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GStdIO.cc b/gcc/m2/mc-boot/GStdIO.cc index e485eeb25752c7b39a65146bae71edf224a4336a..85eebf4c8349b86a927dc3bff53d305034f811a8 100644 --- a/gcc/m2/mc-boot/GStdIO.cc +++ b/gcc/m2/mc-boot/GStdIO.cc @@ -25,6 +25,7 @@ a copy of the GCC Runtime Library Exception along with this program; see the files COPYING3 and COPYING.RUNTIME respectively. If not, see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GStdIO.h b/gcc/m2/mc-boot/GStdIO.h index b01480ac33a9eb753d8a34180de502035a83a28f..0418234bbb2fba759ca99b9c72250e1d81c013d6 100644 --- a/gcc/m2/mc-boot/GStdIO.h +++ b/gcc/m2/mc-boot/GStdIO.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_StdIO_H) # define _StdIO_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GStorage.cc b/gcc/m2/mc-boot/GStorage.cc index f668201059f5fccc0c5264995289e5ee0c19014e..b19616f4ab556d8fa12f49f0112865160be6757c 100644 --- a/gcc/m2/mc-boot/GStorage.cc +++ b/gcc/m2/mc-boot/GStorage.cc @@ -25,6 +25,7 @@ a copy of the GCC Runtime Library Exception along with this program; see the files COPYING3 and COPYING.RUNTIME respectively. If not, see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GStorage.h b/gcc/m2/mc-boot/GStorage.h index f352d19f964438c9fe0a32a65e4dff83741be7d3..e85fd7aeefa7a29012492224b0ba94fd69e4b3c8 100644 --- a/gcc/m2/mc-boot/GStorage.h +++ b/gcc/m2/mc-boot/GStorage.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_Storage_H) # define _Storage_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GStrCase.cc b/gcc/m2/mc-boot/GStrCase.cc index 40323ca949f77346e7cbd2a73a245f34304c4dd3..f33f5a52ac90d5b4e362958b47f022d4c7feacf6 100644 --- a/gcc/m2/mc-boot/GStrCase.cc +++ b/gcc/m2/mc-boot/GStrCase.cc @@ -25,6 +25,7 @@ a copy of the GCC Runtime Library Exception along with this program; see the files COPYING3 and COPYING.RUNTIME respectively. If not, see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GStrCase.h b/gcc/m2/mc-boot/GStrCase.h index 3762f57acac0ed88dfd73d3ecc8d59bfd82c2821..66b4f689fd09132a7de12584a8c2bb0550da0a7e 100644 --- a/gcc/m2/mc-boot/GStrCase.h +++ b/gcc/m2/mc-boot/GStrCase.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_StrCase_H) # define _StrCase_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GStrIO.cc b/gcc/m2/mc-boot/GStrIO.cc index 533460b63f706d01d60955d6c95eadc42e2b07fc..46c392bb8a26acc0ca2ac836dc2544ad6492d07e 100644 --- a/gcc/m2/mc-boot/GStrIO.cc +++ b/gcc/m2/mc-boot/GStrIO.cc @@ -25,6 +25,7 @@ a copy of the GCC Runtime Library Exception along with this program; see the files COPYING3 and COPYING.RUNTIME respectively. If not, see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GStrIO.h b/gcc/m2/mc-boot/GStrIO.h index 24b31a992d5d2fcf02ac90047aba9cb13765ab7f..66ef3d4331c779e0385732726e4449b03a336274 100644 --- a/gcc/m2/mc-boot/GStrIO.h +++ b/gcc/m2/mc-boot/GStrIO.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_StrIO_H) # define _StrIO_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GStrLib.cc b/gcc/m2/mc-boot/GStrLib.cc index dbde45c912262b939526da0fda106fcef310b976..bc3c5e8c38810051ed82c44cc25164fd067bb8cc 100644 --- a/gcc/m2/mc-boot/GStrLib.cc +++ b/gcc/m2/mc-boot/GStrLib.cc @@ -25,6 +25,7 @@ a copy of the GCC Runtime Library Exception along with this program; see the files COPYING3 and COPYING.RUNTIME respectively. If not, see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GStrLib.h b/gcc/m2/mc-boot/GStrLib.h index e79eb709845672c615c83fb93e2571ddfff682b7..2b11e84ca448568f086c379ee413ccfbe5f789e0 100644 --- a/gcc/m2/mc-boot/GStrLib.h +++ b/gcc/m2/mc-boot/GStrLib.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_StrLib_H) # define _StrLib_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GStringConvert.cc b/gcc/m2/mc-boot/GStringConvert.cc index e552244fec553831f2c81a90e04042a14e0efd28..ae50e99c2ab9b26c19e00ad9210e6dad60791c00 100644 --- a/gcc/m2/mc-boot/GStringConvert.cc +++ b/gcc/m2/mc-boot/GStringConvert.cc @@ -25,6 +25,7 @@ a copy of the GCC Runtime Library Exception along with this program; see the files COPYING3 and COPYING.RUNTIME respectively. If not, see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GStringConvert.h b/gcc/m2/mc-boot/GStringConvert.h index 95f1bc1b52928d17626ccf404632dae72207d9f0..035ad56a52ad33d1524ad28e3745e19e462aa467 100644 --- a/gcc/m2/mc-boot/GStringConvert.h +++ b/gcc/m2/mc-boot/GStringConvert.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_StringConvert_H) # define _StringConvert_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GSysExceptions.h b/gcc/m2/mc-boot/GSysExceptions.h index 928a0c1667de2f0827fcb66550d0af6701fe53e3..ef9a6a0f2d9d9bc8cdc02551a6dd433599fd03c2 100644 --- a/gcc/m2/mc-boot/GSysExceptions.h +++ b/gcc/m2/mc-boot/GSysExceptions.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_SysExceptions_H) # define _SysExceptions_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GSysStorage.cc b/gcc/m2/mc-boot/GSysStorage.cc index 1c0cb839ef4178ef73904ea8fcd61cf869eb6f24..906910bf3d8b8d805cdf7133943bfdd5f28aa3fe 100644 --- a/gcc/m2/mc-boot/GSysStorage.cc +++ b/gcc/m2/mc-boot/GSysStorage.cc @@ -25,6 +25,7 @@ a copy of the GCC Runtime Library Exception along with this program; see the files COPYING3 and COPYING.RUNTIME respectively. If not, see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GSysStorage.h b/gcc/m2/mc-boot/GSysStorage.h index 3c1f310ff0ebf35b1ffe6020d2eeba531dbc3e81..930b3bae6cc26685c81bcfcdaa3f124001d7e3b0 100644 --- a/gcc/m2/mc-boot/GSysStorage.h +++ b/gcc/m2/mc-boot/GSysStorage.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_SysStorage_H) # define _SysStorage_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GTimeString.cc b/gcc/m2/mc-boot/GTimeString.cc index b1d6e6e1e508c7df619996e800a8fc6404c5f715..fc9b8ada831b75c0212749a72c3cbc0f47f0dd21 100644 --- a/gcc/m2/mc-boot/GTimeString.cc +++ b/gcc/m2/mc-boot/GTimeString.cc @@ -25,6 +25,7 @@ a copy of the GCC Runtime Library Exception along with this program; see the files COPYING3 and COPYING.RUNTIME respectively. If not, see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GTimeString.h b/gcc/m2/mc-boot/GTimeString.h index c442abb2c22ff1eb97b4c29f8f1905d728a2b212..6323436d70c23161897b77c95e7724bd6dc82885 100644 --- a/gcc/m2/mc-boot/GTimeString.h +++ b/gcc/m2/mc-boot/GTimeString.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_TimeString_H) # define _TimeString_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GUnixArgs.h b/gcc/m2/mc-boot/GUnixArgs.h index 59ba2ac123ec7b5fbcf621b41a3c26d84edf681f..79a1ea948d3a738183a101675161be3e6615d0e7 100644 --- a/gcc/m2/mc-boot/GUnixArgs.h +++ b/gcc/m2/mc-boot/GUnixArgs.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_UnixArgs_H) # define _UnixArgs_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/Galists.cc b/gcc/m2/mc-boot/Galists.cc index 7c42dd45625fbea0d3e35942fda0cc8184349f0c..09bfdccc49f868d5b0fdcd8d9cec2746d187de3d 100644 --- a/gcc/m2/mc-boot/Galists.cc +++ b/gcc/m2/mc-boot/Galists.cc @@ -20,6 +20,7 @@ You should have received a copy of the GNU General Public License along with GNU Modula-2; see the file COPYING3. If not see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/Galists.h b/gcc/m2/mc-boot/Galists.h index bda3ac6bf1f5139e77889c93b491ef382660b0ce..fdacd985785b0d738190e75a123760d2923834f3 100644 --- a/gcc/m2/mc-boot/Galists.h +++ b/gcc/m2/mc-boot/Galists.h @@ -24,6 +24,7 @@ along with GNU Modula-2; see the file COPYING3. If not see #if !defined (_alists_H) # define _alists_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/Gdecl.cc b/gcc/m2/mc-boot/Gdecl.cc index ea22d064f6885cf3f0347f98f439a8b481ba4ea1..292c654fa66b915780412fb5c7deff9b758cc547 100644 --- a/gcc/m2/mc-boot/Gdecl.cc +++ b/gcc/m2/mc-boot/Gdecl.cc @@ -20,6 +20,7 @@ You should have received a copy of the GNU General Public License along with GNU Modula-2; see the file COPYING3. If not see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> @@ -210,7 +211,7 @@ typedef struct decl__T1_r decl__T1; typedef decl__T1 *decl_group; -typedef enum {decl_explist, decl_funccall, decl_exit, decl_return, decl_stmtseq, decl_comment, decl_halt, decl_new, decl_dispose, decl_inc, decl_dec, decl_incl, decl_excl, decl_length, decl_nil, decl_true, decl_false, decl_address, decl_loc, decl_byte, decl_word, decl_csizet, decl_cssizet, decl_char, decl_cardinal, decl_longcard, decl_shortcard, decl_integer, decl_longint, decl_shortint, decl_real, decl_longreal, decl_shortreal, decl_bitset, decl_boolean, decl_proc, decl_ztype, decl_rtype, decl_complex, decl_longcomplex, decl_shortcomplex, decl_type, decl_record, decl_varient, decl_var, decl_enumeration, decl_subrange, decl_array, decl_subscript, decl_string, decl_const, decl_literal, decl_varparam, decl_param, decl_varargs, decl_optarg, decl_pointer, decl_recordfield, decl_varientfield, decl_enumerationfield, decl_set, decl_proctype, decl_procedure, decl_def, decl_imp, decl_module, decl_loop, decl_while, decl_for, decl_repeat, decl_case, decl_caselabellist, decl_caselist, decl_range, decl_assignment, decl_if, decl_elsif, decl_constexp, decl_neg, decl_cast, decl_val, decl_plus, decl_sub, decl_div, decl_mod, decl_mult, decl_divide, decl_in, decl_adr, decl_size, decl_tsize, decl_ord, decl_float, decl_trunc, decl_chr, decl_abs, decl_cap, decl_high, decl_throw, decl_unreachable, decl_cmplx, decl_re, decl_im, decl_min, decl_max, decl_componentref, decl_pointerref, decl_arrayref, decl_deref, decl_equal, decl_notequal, decl_less, decl_greater, decl_greequal, decl_lessequal, decl_lsl, decl_lsr, decl_lor, decl_land, decl_lnot, decl_lxor, decl_and, decl_or, decl_not, decl_identlist, decl_vardecl, decl_setvalue, decl_opaquecast} decl_nodeT; +typedef enum {decl_explist, decl_funccall, decl_exit, decl_return, decl_stmtseq, decl_comment, decl_halt, decl_new, decl_dispose, decl_inc, decl_dec, decl_incl, decl_excl, decl_length, decl_nil, decl_true, decl_false, decl_address, decl_loc, decl_byte, decl_word, decl_csizet, decl_cssizet, decl_cofft, decl_cardinal64, decl_char, decl_cardinal, decl_longcard, decl_shortcard, decl_integer, decl_longint, decl_shortint, decl_real, decl_longreal, decl_shortreal, decl_bitset, decl_boolean, decl_proc, decl_ztype, decl_rtype, decl_complex, decl_longcomplex, decl_shortcomplex, decl_type, decl_record, decl_varient, decl_var, decl_enumeration, decl_subrange, decl_array, decl_subscript, decl_string, decl_const, decl_literal, decl_varparam, decl_param, decl_varargs, decl_optarg, decl_pointer, decl_recordfield, decl_varientfield, decl_enumerationfield, decl_set, decl_proctype, decl_procedure, decl_def, decl_imp, decl_module, decl_loop, decl_while, decl_for, decl_repeat, decl_case, decl_caselabellist, decl_caselist, decl_range, decl_assignment, decl_if, decl_elsif, decl_constexp, decl_neg, decl_cast, decl_val, decl_plus, decl_sub, decl_div, decl_mod, decl_mult, decl_divide, decl_in, decl_adr, decl_size, decl_tsize, decl_ord, decl_float, decl_trunc, decl_chr, decl_abs, decl_cap, decl_high, decl_throw, decl_unreachable, decl_cmplx, decl_re, decl_im, decl_min, decl_max, decl_componentref, decl_pointerref, decl_arrayref, decl_deref, decl_equal, decl_notequal, decl_less, decl_greater, decl_greequal, decl_lessequal, decl_lsl, decl_lsr, decl_lor, decl_land, decl_lnot, decl_lxor, decl_and, decl_or, decl_not, decl_identlist, decl_vardecl, decl_setvalue, decl_opaquecast} decl_nodeT; typedef enum {decl_ansiC, decl_ansiCP, decl_pim4} decl_language; @@ -744,6 +745,8 @@ static decl_node__opaque byteN; static decl_node__opaque wordN; static decl_node__opaque csizetN; static decl_node__opaque cssizetN; +static decl_node__opaque cofftN; +static decl_node__opaque cardinal64N; static decl_node__opaque adrN; static decl_node__opaque sizeN; static decl_node__opaque tsizeN; @@ -1155,7 +1158,7 @@ extern "C" bool decl_isProcType (decl_node n); extern "C" bool decl_isPointer (decl_node n); /* - isProcedure - returns TRUE if, n, is a procedure. + isProcedure - returns TRUE if node, n, is a procedure. */ extern "C" bool decl_isProcedure (decl_node n); @@ -7847,6 +7850,8 @@ static decl_node__opaque makeBase (decl_nodeT k) case decl_word: case decl_csizet: case decl_cssizet: + case decl_cofft: + case decl_cardinal64: case decl_char: case decl_cardinal: case decl_longcard: @@ -7910,6 +7915,8 @@ static bool isOrdinal (decl_node__opaque n) case decl_word: case decl_csizet: case decl_cssizet: + case decl_cofft: + case decl_cardinal64: case decl_char: case decl_integer: case decl_longint: @@ -8077,6 +8084,14 @@ static decl_node__opaque doGetExprType (decl_node__opaque n) return n; break; + case decl_cofft: + return n; + break; + + case decl_cardinal64: + return n; + break; + case decl_boolean: /* base types. */ return n; @@ -9890,6 +9905,8 @@ static void doExprC (mcPretty_pretty p, decl_node__opaque n) case decl_word: case decl_csizet: case decl_cssizet: + case decl_cofft: + case decl_cardinal64: doSystemC (p, n); break; @@ -12971,26 +12988,13 @@ static bool isSystem (decl_node__opaque n) switch (n->kind) { case decl_address: - return true; - break; - case decl_loc: - return true; - break; - case decl_byte: - return true; - break; - case decl_word: - return true; - break; - case decl_csizet: - return true; - break; - case decl_cssizet: + case decl_cofft: + case decl_cardinal64: return true; break; @@ -13043,6 +13047,16 @@ static void doSystemC (mcPretty_pretty p, decl_node__opaque n) keyc_useSSize_t (); break; + case decl_cofft: + outText (p, (const char *) "off_t", 5); + mcPretty_setNeedSpace (p); + break; + + case decl_cardinal64: + outText (p, (const char *) "uint64_t", 8); + mcPretty_setNeedSpace (p); + break; + default: CaseException ("../../gcc/m2/mc/decl.def", 20, 1); @@ -18846,6 +18860,8 @@ static decl_dependentState doDependants (alists_alist l, decl_node__opaque n) case decl_word: case decl_csizet: case decl_cssizet: + case decl_cofft: + case decl_cardinal64: case decl_boolean: case decl_char: case decl_cardinal: @@ -19850,6 +19866,8 @@ static void visitDependants (alists_alist v, decl_node__opaque n, decl_nodeProce case decl_word: case decl_csizet: case decl_cssizet: + case decl_cofft: + case decl_cardinal64: case decl_char: case decl_cardinal: case decl_longcard: @@ -20168,6 +20186,8 @@ static DynamicStrings_String genKind (decl_node__opaque n) case decl_word: case decl_csizet: case decl_cssizet: + case decl_cofft: + case decl_cardinal64: case decl_char: case decl_cardinal: case decl_longcard: @@ -21676,6 +21696,8 @@ static void doSystemM2 (mcPretty_pretty p, decl_node__opaque n) case decl_word: case decl_csizet: case decl_cssizet: + case decl_cofft: + case decl_cardinal64: doNameM2 (p, n); break; @@ -22781,6 +22803,8 @@ static decl_node__opaque doDupExpr (decl_node__opaque n) case decl_word: case decl_csizet: case decl_cssizet: + case decl_cofft: + case decl_cardinal64: case decl_boolean: case decl_proc: case decl_char: @@ -22945,6 +22969,8 @@ static void makeSystem (void) wordN = makeBase (decl_word); csizetN = makeBase (decl_csizet); cssizetN = makeBase (decl_cssizet); + cofftN = makeBase (decl_cofft); + cardinal64N = makeBase (decl_cardinal64); adrN = makeBase (decl_adr); tsizeN = makeBase (decl_tsize); throwN = makeBase (decl_throw); @@ -22955,6 +22981,8 @@ static void makeSystem (void) wordN = addToScope (wordN); csizetN = addToScope (csizetN); cssizetN = addToScope (cssizetN); + cofftN = addToScope (cofftN); + cardinal64N = addToScope (cardinal64N); adrN = addToScope (adrN); tsizeN = addToScope (tsizeN); throwN = addToScope (throwN); @@ -22967,6 +22995,8 @@ static void makeSystem (void) addDone (wordN); addDone (csizetN); addDone (cssizetN); + addDone (cofftN); + addDone (cardinal64N); } @@ -23741,6 +23771,14 @@ extern "C" decl_node decl_getType (decl_node n) return n; break; + case decl_cofft: + return n; + break; + + case decl_cardinal64: + return n; + break; + case decl_boolean: /* base types. */ return n; @@ -24222,6 +24260,8 @@ extern "C" decl_node decl_getScope (decl_node n) case decl_word: case decl_csizet: case decl_cssizet: + case decl_cofft: + case decl_cardinal64: return static_cast<decl_node> (systemN); break; @@ -24685,7 +24725,7 @@ extern "C" bool decl_isPointer (decl_node n) /* - isProcedure - returns TRUE if, n, is a procedure. + isProcedure - returns TRUE if node, n, is a procedure. */ extern "C" bool decl_isProcedure (decl_node n) @@ -25281,6 +25321,14 @@ extern "C" nameKey_Name decl_getSymName (decl_node n) return nameKey_makeKey ((const char *) "CSSIZE_T", 8); break; + case decl_cofft: + return nameKey_makeKey ((const char *) "COFF_T", 6); + break; + + case decl_cardinal64: + return nameKey_makeKey ((const char *) "CARDINAL64", 10); + break; + case decl_boolean: /* base types. */ return nameKey_makeKey ((const char *) "BOOLEAN", 7); diff --git a/gcc/m2/mc-boot/Gdecl.h b/gcc/m2/mc-boot/Gdecl.h index a979c52f09593ce947b719262caacf15801c707e..30e02f0a1e84b13ec6b821faea3e5b62d49e914e 100644 --- a/gcc/m2/mc-boot/Gdecl.h +++ b/gcc/m2/mc-boot/Gdecl.h @@ -24,6 +24,7 @@ along with GNU Modula-2; see the file COPYING3. If not see #if !defined (_decl_H) # define _decl_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/Gdtoa.h b/gcc/m2/mc-boot/Gdtoa.h index d371aeb78511f8ab1ff77758bde2f04c39364076..e58489e01e6d5e993558214c499e9215abfeea70 100644 --- a/gcc/m2/mc-boot/Gdtoa.h +++ b/gcc/m2/mc-boot/Gdtoa.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_dtoa_H) # define _dtoa_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/Gerrno.h b/gcc/m2/mc-boot/Gerrno.h index 256317afc8847c88da955849c8cd7e59986c0f9d..1f8c83a252da79fb379ed9961086d928e9deb843 100644 --- a/gcc/m2/mc-boot/Gerrno.h +++ b/gcc/m2/mc-boot/Gerrno.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_errno_H) # define _errno_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/Gkeyc.cc b/gcc/m2/mc-boot/Gkeyc.cc index 132c2fc7283c6aa3390e876eececf8acffdcad89..9a35e953d18cebb8143e33372b7e17326655d9eb 100644 --- a/gcc/m2/mc-boot/Gkeyc.cc +++ b/gcc/m2/mc-boot/Gkeyc.cc @@ -18,6 +18,7 @@ You should have received a copy of the GNU General Public License along with GCC; see the file COPYING3. If not see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> @@ -575,6 +576,7 @@ static void checkGccConfigSystem (mcPretty_pretty p) if (! initializedGCC) { initializedGCC = true; + mcPretty_print (p, (const char *) "#define INCLUDE_MEMORY\\n", 24); mcPretty_print (p, (const char *) "#include \"config.h\"\\n", 21); mcPretty_print (p, (const char *) "#include \"system.h\"\\n", 21); checkGccTypes (p); diff --git a/gcc/m2/mc-boot/Gkeyc.h b/gcc/m2/mc-boot/Gkeyc.h index 9a15c93d10f04329f621b0131c57c48c0c185209..8537fbcc86b7bbb1dbb94af8ef6776645daed286 100644 --- a/gcc/m2/mc-boot/Gkeyc.h +++ b/gcc/m2/mc-boot/Gkeyc.h @@ -24,6 +24,7 @@ along with GNU Modula-2; see the file COPYING3. If not see #if !defined (_keyc_H) # define _keyc_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/Gldtoa.h b/gcc/m2/mc-boot/Gldtoa.h index 6ae682ee13c5d522f2569462ac55ad12790a72f6..f24ab408bb0c23755ab4e0bc21dda0a4bdb5df5a 100644 --- a/gcc/m2/mc-boot/Gldtoa.h +++ b/gcc/m2/mc-boot/Gldtoa.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_ldtoa_H) # define _ldtoa_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/Glibc.h b/gcc/m2/mc-boot/Glibc.h index 9987d0ea01ddd180ecfe54034b8f567ca40cd8d4..cdf441f07741bbb72919b977ae494b79622abcc8 100644 --- a/gcc/m2/mc-boot/Glibc.h +++ b/gcc/m2/mc-boot/Glibc.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_libc_H) # define _libc_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/Glibm.h b/gcc/m2/mc-boot/Glibm.h index 344ac623f0ed31afaacb0bc5302d61cda83b26cb..2c5a177735f445d47def168a7f8b93027fbf10fc 100644 --- a/gcc/m2/mc-boot/Glibm.h +++ b/gcc/m2/mc-boot/Glibm.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_libm_H) # define _libm_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/Glists.cc b/gcc/m2/mc-boot/Glists.cc index f29edec1a140b6e9bb223cb37b4eca5cf977d5a8..2e459ca910dfbb806086ff6eabfa161b1fb56614 100644 --- a/gcc/m2/mc-boot/Glists.cc +++ b/gcc/m2/mc-boot/Glists.cc @@ -18,6 +18,7 @@ You should have received a copy of the GNU General Public License along with GCC; see the file COPYING3. If not see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/Glists.h b/gcc/m2/mc-boot/Glists.h index 84537a1ffc5740c6458d1c600172e5ab4c117e6c..e89a42a4006f406f4b76d4e9d754ea0bf52facb7 100644 --- a/gcc/m2/mc-boot/Glists.h +++ b/gcc/m2/mc-boot/Glists.h @@ -24,6 +24,7 @@ along with GNU Modula-2; see the file COPYING3. If not see #if !defined (_lists_H) # define _lists_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GmcComment.cc b/gcc/m2/mc-boot/GmcComment.cc index d5f741e047b77ac288fe32560c8aae4071798a8a..320c512628902e2fe3f89d6ae23d0dca034a04ff 100644 --- a/gcc/m2/mc-boot/GmcComment.cc +++ b/gcc/m2/mc-boot/GmcComment.cc @@ -20,6 +20,7 @@ You should have received a copy of the GNU General Public License along with GNU Modula-2; see the file COPYING3. If not see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GmcComment.h b/gcc/m2/mc-boot/GmcComment.h index 10dd5c2781c9cab030caf124d4fb49ebcc73a6b3..bbb7d2fbb726a393c02e6400abf1360bb30c98a6 100644 --- a/gcc/m2/mc-boot/GmcComment.h +++ b/gcc/m2/mc-boot/GmcComment.h @@ -24,6 +24,7 @@ along with GNU Modula-2; see the file COPYING3. If not see #if !defined (_mcComment_H) # define _mcComment_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GmcComp.cc b/gcc/m2/mc-boot/GmcComp.cc index e36fa638c9e737096fcb52537df31840ffe8de7f..72c277d203ab2bed6b7d2eda626f89e2481fb0a0 100644 --- a/gcc/m2/mc-boot/GmcComp.cc +++ b/gcc/m2/mc-boot/GmcComp.cc @@ -16,6 +16,7 @@ You should have received a copy of the GNU General Public License along with GCC; see the file COPYING3. If not see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GmcComp.h b/gcc/m2/mc-boot/GmcComp.h index 17e2080d780de64b56d27adb73dd85162e613a22..a4e302f6af9310bc84b08822854185bc44870f69 100644 --- a/gcc/m2/mc-boot/GmcComp.h +++ b/gcc/m2/mc-boot/GmcComp.h @@ -24,6 +24,7 @@ along with GNU Modula-2; see the file COPYING3. If not see #if !defined (_mcComp_H) # define _mcComp_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GmcDebug.cc b/gcc/m2/mc-boot/GmcDebug.cc index 0085384f2c98262114519c041d6e43cf589d5039..7ded4aee139fcc593988f7a5ea58676e51c2b63d 100644 --- a/gcc/m2/mc-boot/GmcDebug.cc +++ b/gcc/m2/mc-boot/GmcDebug.cc @@ -15,6 +15,7 @@ You should have received a copy of the GNU General Public License along with GCC; see the file COPYING3. If not see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GmcDebug.h b/gcc/m2/mc-boot/GmcDebug.h index a46fa13eeb0aa2087e3ff7f5d59c7e77ff009655..e4ac762d64864699827f36fc5076297eab500fad 100644 --- a/gcc/m2/mc-boot/GmcDebug.h +++ b/gcc/m2/mc-boot/GmcDebug.h @@ -24,6 +24,7 @@ along with GNU Modula-2; see the file COPYING3. If not see #if !defined (_mcDebug_H) # define _mcDebug_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GmcError.cc b/gcc/m2/mc-boot/GmcError.cc index a3df34e77996825f219c6b121017f3ca2cad0505..4e29211845590e4e7ce548ef717a13d213e0492c 100644 --- a/gcc/m2/mc-boot/GmcError.cc +++ b/gcc/m2/mc-boot/GmcError.cc @@ -20,6 +20,7 @@ You should have received a copy of the GNU General Public License along with GNU Modula-2; see the file COPYING3. If not see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GmcError.h b/gcc/m2/mc-boot/GmcError.h index 054a4780a728cf7cf9383ca26524f7cc20a09234..951f6ae3bbe6ea9c16ab774b5c0427266dbfb875 100644 --- a/gcc/m2/mc-boot/GmcError.h +++ b/gcc/m2/mc-boot/GmcError.h @@ -24,6 +24,7 @@ along with GNU Modula-2; see the file COPYING3. If not see #if !defined (_mcError_H) # define _mcError_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GmcFileName.cc b/gcc/m2/mc-boot/GmcFileName.cc index 3b516594c595e447de748ae00876a68b32b43364..f0f69129e06cf86a623308906bc413b0002e5281 100644 --- a/gcc/m2/mc-boot/GmcFileName.cc +++ b/gcc/m2/mc-boot/GmcFileName.cc @@ -15,6 +15,7 @@ You should have received a copy of the GNU General Public License along with GCC; see the file COPYING3. If not see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GmcFileName.h b/gcc/m2/mc-boot/GmcFileName.h index 11f1512dbe81ccf3c17b13b46646a16358c4a6a8..04e08ec8e9a2f5bc25d1f79728e31492023fd271 100644 --- a/gcc/m2/mc-boot/GmcFileName.h +++ b/gcc/m2/mc-boot/GmcFileName.h @@ -24,6 +24,7 @@ along with GNU Modula-2; see the file COPYING3. If not see #if !defined (_mcFileName_H) # define _mcFileName_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GmcLexBuf.cc b/gcc/m2/mc-boot/GmcLexBuf.cc index 4f2293165aea49d692f6a43b22d03d29daf895b4..dd6b87e5a211900862cb7f82853c6ca49fa29ecd 100644 --- a/gcc/m2/mc-boot/GmcLexBuf.cc +++ b/gcc/m2/mc-boot/GmcLexBuf.cc @@ -20,6 +20,7 @@ You should have received a copy of the GNU General Public License along with GNU Modula-2; see the file COPYING3. If not see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GmcLexBuf.h b/gcc/m2/mc-boot/GmcLexBuf.h index ca22526c0a43055b739ca6321a319fb2572fb42a..bb552aee3fa653808b4e472908c4c5cdc26b9eb8 100644 --- a/gcc/m2/mc-boot/GmcLexBuf.h +++ b/gcc/m2/mc-boot/GmcLexBuf.h @@ -24,6 +24,7 @@ along with GNU Modula-2; see the file COPYING3. If not see #if !defined (_mcLexBuf_H) # define _mcLexBuf_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GmcMetaError.cc b/gcc/m2/mc-boot/GmcMetaError.cc index af64604534e2f189df03a43405ba166b9862c42b..9298d0e4192721d32a6d1447ab80007307aa5099 100644 --- a/gcc/m2/mc-boot/GmcMetaError.cc +++ b/gcc/m2/mc-boot/GmcMetaError.cc @@ -15,6 +15,7 @@ You should have received a copy of the GNU General Public License along with GCC; see the file COPYING3. If not see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GmcMetaError.h b/gcc/m2/mc-boot/GmcMetaError.h index de244c186fffb52477c8f109d1cdebe413a13d35..ce5e8e1b7952cb9ac6baa017c8dd48f3b5815ee3 100644 --- a/gcc/m2/mc-boot/GmcMetaError.h +++ b/gcc/m2/mc-boot/GmcMetaError.h @@ -24,6 +24,7 @@ along with GNU Modula-2; see the file COPYING3. If not see #if !defined (_mcMetaError_H) # define _mcMetaError_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GmcOptions.cc b/gcc/m2/mc-boot/GmcOptions.cc index 5a0606047092a46b3dbf6eaf62b7adc0355e469f..f6e4417b6593929b83ed18b8cf8a089029456f00 100644 --- a/gcc/m2/mc-boot/GmcOptions.cc +++ b/gcc/m2/mc-boot/GmcOptions.cc @@ -15,6 +15,7 @@ You should have received a copy of the GNU General Public License along with GCC; see the file COPYING3. If not see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GmcOptions.h b/gcc/m2/mc-boot/GmcOptions.h index aab560038e22e4317df4171a04f47f41e88eae62..2db8bcb998a043876cb861d2d972e02c7a4417d7 100644 --- a/gcc/m2/mc-boot/GmcOptions.h +++ b/gcc/m2/mc-boot/GmcOptions.h @@ -24,6 +24,7 @@ along with GNU Modula-2; see the file COPYING3. If not see #if !defined (_mcOptions_H) # define _mcOptions_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GmcPreprocess.cc b/gcc/m2/mc-boot/GmcPreprocess.cc index 741109ad7fbf40fd4dfe0fd035671a763807537a..54d89bf33e75ac3931f13571832b1568e06c6485 100644 --- a/gcc/m2/mc-boot/GmcPreprocess.cc +++ b/gcc/m2/mc-boot/GmcPreprocess.cc @@ -15,6 +15,7 @@ You should have received a copy of the GNU General Public License along with GCC; see the file COPYING3. If not see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GmcPreprocess.h b/gcc/m2/mc-boot/GmcPreprocess.h index 21b4fd458a4ffb2763d274702af36d16b6625180..05e8122a332a50abd8a5d01269ba29ad03453b81 100644 --- a/gcc/m2/mc-boot/GmcPreprocess.h +++ b/gcc/m2/mc-boot/GmcPreprocess.h @@ -24,6 +24,7 @@ along with GNU Modula-2; see the file COPYING3. If not see #if !defined (_mcPreprocess_H) # define _mcPreprocess_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GmcPretty.cc b/gcc/m2/mc-boot/GmcPretty.cc index 0bffa1ff6feb4025432e5dc2e01a4b550207c48c..c0be8c1e49915f0dd5c080573d5e35bed4b7d0bb 100644 --- a/gcc/m2/mc-boot/GmcPretty.cc +++ b/gcc/m2/mc-boot/GmcPretty.cc @@ -15,6 +15,7 @@ You should have received a copy of the GNU General Public License along with GCC; see the file COPYING3. If not see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GmcPretty.h b/gcc/m2/mc-boot/GmcPretty.h index d6834e2f9004b466b1dd8a284cb872159b02d273..95d7a0b13ae2ab90fd8f9a0fdcc6cb7b6093b5c4 100644 --- a/gcc/m2/mc-boot/GmcPretty.h +++ b/gcc/m2/mc-boot/GmcPretty.h @@ -24,6 +24,7 @@ along with GNU Modula-2; see the file COPYING3. If not see #if !defined (_mcPretty_H) # define _mcPretty_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GmcPrintf.cc b/gcc/m2/mc-boot/GmcPrintf.cc index e91e55acc14c73501b25126b86c113da004dec81..dafa728437fdcd5c57c4677a5a680b43c85b9fbf 100644 --- a/gcc/m2/mc-boot/GmcPrintf.cc +++ b/gcc/m2/mc-boot/GmcPrintf.cc @@ -15,6 +15,7 @@ You should have received a copy of the GNU General Public License along with GCC; see the file COPYING3. If not see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GmcPrintf.h b/gcc/m2/mc-boot/GmcPrintf.h index ca1129a26ef739e2219e747a03d59e78a474a976..6d70a6db6a5ee0e91cb3da841aa265bb6b460a5c 100644 --- a/gcc/m2/mc-boot/GmcPrintf.h +++ b/gcc/m2/mc-boot/GmcPrintf.h @@ -24,6 +24,7 @@ along with GNU Modula-2; see the file COPYING3. If not see #if !defined (_mcPrintf_H) # define _mcPrintf_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GmcQuiet.cc b/gcc/m2/mc-boot/GmcQuiet.cc index d0f2f009b2a86ece8f6228f039d49ff60a524835..3309f13d736c9ee5c3f9a0ed486328fc390e9021 100644 --- a/gcc/m2/mc-boot/GmcQuiet.cc +++ b/gcc/m2/mc-boot/GmcQuiet.cc @@ -15,6 +15,7 @@ You should have received a copy of the GNU General Public License along with GCC; see the file COPYING3. If not see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GmcQuiet.h b/gcc/m2/mc-boot/GmcQuiet.h index b84144c9f30b11d190ab49be7b9bbc5c13f582a0..6eebb3b69cdbd6ae82e2073435094835adbbd64e 100644 --- a/gcc/m2/mc-boot/GmcQuiet.h +++ b/gcc/m2/mc-boot/GmcQuiet.h @@ -24,6 +24,7 @@ along with GNU Modula-2; see the file COPYING3. If not see #if !defined (_mcQuiet_H) # define _mcQuiet_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GmcReserved.cc b/gcc/m2/mc-boot/GmcReserved.cc index a42f1b1b0acb7a3b6124f98d418af8a43ea422e5..02132e48b4b8fbb007c12fc0880312f5c586cdc3 100644 --- a/gcc/m2/mc-boot/GmcReserved.cc +++ b/gcc/m2/mc-boot/GmcReserved.cc @@ -15,6 +15,7 @@ You should have received a copy of the GNU General Public License along with GCC; see the file COPYING3. If not see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GmcReserved.h b/gcc/m2/mc-boot/GmcReserved.h index 8c5adca465a8e0a6ac05633f0422a7c15cbb4893..18e15f6247eeba0de2934ae4139bec0167938215 100644 --- a/gcc/m2/mc-boot/GmcReserved.h +++ b/gcc/m2/mc-boot/GmcReserved.h @@ -24,6 +24,7 @@ along with GNU Modula-2; see the file COPYING3. If not see #if !defined (_mcReserved_H) # define _mcReserved_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GmcSearch.cc b/gcc/m2/mc-boot/GmcSearch.cc index e1a2aa63e29d99ff6df0db90998a1a3cb6b895f1..14d3e3fe0abd69b667377483be490cd447f828ae 100644 --- a/gcc/m2/mc-boot/GmcSearch.cc +++ b/gcc/m2/mc-boot/GmcSearch.cc @@ -15,6 +15,7 @@ You should have received a copy of the GNU General Public License along with GCC; see the file COPYING3. If not see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GmcSearch.h b/gcc/m2/mc-boot/GmcSearch.h index 277f55858496f67a7040b0edb3e3c3b869210f1e..4ea92e0c0fa7b3b9f093915ed52833008ca44392 100644 --- a/gcc/m2/mc-boot/GmcSearch.h +++ b/gcc/m2/mc-boot/GmcSearch.h @@ -24,6 +24,7 @@ along with GNU Modula-2; see the file COPYING3. If not see #if !defined (_mcSearch_H) # define _mcSearch_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GmcStack.cc b/gcc/m2/mc-boot/GmcStack.cc index 70f937b4299161810300f776a152506e5631e875..8edae475e6de4d6afd9dba22bb47fbde547005ed 100644 --- a/gcc/m2/mc-boot/GmcStack.cc +++ b/gcc/m2/mc-boot/GmcStack.cc @@ -15,6 +15,7 @@ You should have received a copy of the GNU General Public License along with GCC; see the file COPYING3. If not see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GmcStack.h b/gcc/m2/mc-boot/GmcStack.h index fe790ced893383f3917e613462de6e902cad7bc0..ee1fad402fc79fb86fbbc3ab271ea045d8ed33e3 100644 --- a/gcc/m2/mc-boot/GmcStack.h +++ b/gcc/m2/mc-boot/GmcStack.h @@ -24,6 +24,7 @@ along with GNU Modula-2; see the file COPYING3. If not see #if !defined (_mcStack_H) # define _mcStack_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GmcStream.cc b/gcc/m2/mc-boot/GmcStream.cc index f970dd61c2e5b6d333a15e48cfcd2c7c5af4b436..a35ee25294f1215374efd311e523d64d17095fd2 100644 --- a/gcc/m2/mc-boot/GmcStream.cc +++ b/gcc/m2/mc-boot/GmcStream.cc @@ -20,6 +20,7 @@ You should have received a copy of the GNU General Public License along with GNU Modula-2; see the file COPYING3. If not see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GmcStream.h b/gcc/m2/mc-boot/GmcStream.h index 6fef979e5fb77ac29b4d6c31f09a90bba1b27737..0584dd743c3ade64f62477836e667dc1b2e7609b 100644 --- a/gcc/m2/mc-boot/GmcStream.h +++ b/gcc/m2/mc-boot/GmcStream.h @@ -24,6 +24,7 @@ along with GNU Modula-2; see the file COPYING3. If not see #if !defined (_mcStream_H) # define _mcStream_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/Gmcflex.h b/gcc/m2/mc-boot/Gmcflex.h index b6a3d0a03d7a2079b7ea524a7471c0fb8d07c7fb..739c99267e9313cced874e32ba878a30d4c3e79e 100644 --- a/gcc/m2/mc-boot/Gmcflex.h +++ b/gcc/m2/mc-boot/Gmcflex.h @@ -24,6 +24,7 @@ along with GNU Modula-2; see the file COPYING3. If not see #if !defined (_mcflex_H) # define _mcflex_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/Gmcp1.cc b/gcc/m2/mc-boot/Gmcp1.cc index 389c1381bf356259f3d1b1d955d526840e5d7aca..cb0d1ad1698d7e7493af17f965c1d4f7f69df934 100644 --- a/gcc/m2/mc-boot/Gmcp1.cc +++ b/gcc/m2/mc-boot/Gmcp1.cc @@ -20,6 +20,7 @@ You should have received a copy of the GNU General Public License along with GNU Modula-2; see the file COPYING. If not, see <https://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/Gmcp1.h b/gcc/m2/mc-boot/Gmcp1.h index 2bc44047820ed44c4c68d2338c5a33349980dec9..428f312a6d62c5a77863c4beb6ee32c4488acaa9 100644 --- a/gcc/m2/mc-boot/Gmcp1.h +++ b/gcc/m2/mc-boot/Gmcp1.h @@ -24,6 +24,7 @@ along with GNU Modula-2; see the file COPYING3. If not see #if !defined (_mcp1_H) # define _mcp1_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/Gmcp2.cc b/gcc/m2/mc-boot/Gmcp2.cc index 88ff478ce70dfc3cee73813910a4b575b5792357..bfd3e0c5b62b6952d1f68ee9a56c11e12932c99c 100644 --- a/gcc/m2/mc-boot/Gmcp2.cc +++ b/gcc/m2/mc-boot/Gmcp2.cc @@ -20,6 +20,7 @@ You should have received a copy of the GNU General Public License along with GNU Modula-2; see the file COPYING. If not, see <https://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/Gmcp2.h b/gcc/m2/mc-boot/Gmcp2.h index 080c4fae962510c3682532320e205d1961c8ab9b..8fc92ea91122546ba350f688c8381ce0fd163e00 100644 --- a/gcc/m2/mc-boot/Gmcp2.h +++ b/gcc/m2/mc-boot/Gmcp2.h @@ -24,6 +24,7 @@ along with GNU Modula-2; see the file COPYING3. If not see #if !defined (_mcp2_H) # define _mcp2_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/Gmcp3.cc b/gcc/m2/mc-boot/Gmcp3.cc index aa8b7338d13a68e20f52cda99ce78902ae527cd8..f345cf666fb21655b0bf589bfc12ccba6177a619 100644 --- a/gcc/m2/mc-boot/Gmcp3.cc +++ b/gcc/m2/mc-boot/Gmcp3.cc @@ -20,6 +20,7 @@ You should have received a copy of the GNU General Public License along with GNU Modula-2; see the file COPYING. If not, see <https://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/Gmcp3.h b/gcc/m2/mc-boot/Gmcp3.h index 231e6f0cc7a0cc6793c2fde77f3fdf8e5dfd0cf1..d58349f1998d68462ee82c35a15647c1c10c9464 100644 --- a/gcc/m2/mc-boot/Gmcp3.h +++ b/gcc/m2/mc-boot/Gmcp3.h @@ -24,6 +24,7 @@ along with GNU Modula-2; see the file COPYING3. If not see #if !defined (_mcp3_H) # define _mcp3_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/Gmcp4.cc b/gcc/m2/mc-boot/Gmcp4.cc index 5cf2ec15de3a12d001ecefaaedb3242763b28794..872b7b102c58e0e1f3e556002e96303e32ce2a11 100644 --- a/gcc/m2/mc-boot/Gmcp4.cc +++ b/gcc/m2/mc-boot/Gmcp4.cc @@ -20,6 +20,7 @@ You should have received a copy of the GNU General Public License along with GNU Modula-2; see the file COPYING. If not, see <https://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/Gmcp4.h b/gcc/m2/mc-boot/Gmcp4.h index 826cba6809e51be97d5b004f8c38944826257d27..c374b34bf777a210bee4ebbdbc0d6ed154db4437 100644 --- a/gcc/m2/mc-boot/Gmcp4.h +++ b/gcc/m2/mc-boot/Gmcp4.h @@ -24,6 +24,7 @@ along with GNU Modula-2; see the file COPYING3. If not see #if !defined (_mcp4_H) # define _mcp4_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/Gmcp5.cc b/gcc/m2/mc-boot/Gmcp5.cc index 20b006cab71bc71270d1ca096f8b439eded93bd1..0fa727a7fc3594bc2e611e7c71102fb518483ed5 100644 --- a/gcc/m2/mc-boot/Gmcp5.cc +++ b/gcc/m2/mc-boot/Gmcp5.cc @@ -20,6 +20,7 @@ You should have received a copy of the GNU General Public License along with GNU Modula-2; see the file COPYING. If not, see <https://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/Gmcp5.h b/gcc/m2/mc-boot/Gmcp5.h index 001f08436691e1bab6fb6a97807628eade6b688c..44cb6ce2b50a88d78d151a5360621c2ed968b4e7 100644 --- a/gcc/m2/mc-boot/Gmcp5.h +++ b/gcc/m2/mc-boot/Gmcp5.h @@ -24,6 +24,7 @@ along with GNU Modula-2; see the file COPYING3. If not see #if !defined (_mcp5_H) # define _mcp5_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GnameKey.cc b/gcc/m2/mc-boot/GnameKey.cc index ea52ccbc3fe39cd0342a386a3ea21d05f04776e5..128ac93c9bcdb7ab8f99dbdb857e5a314723bf71 100644 --- a/gcc/m2/mc-boot/GnameKey.cc +++ b/gcc/m2/mc-boot/GnameKey.cc @@ -20,6 +20,7 @@ You should have received a copy of the GNU General Public License along with GNU Modula-2; see the file COPYING3. If not see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GnameKey.h b/gcc/m2/mc-boot/GnameKey.h index 8204133d61f515218676d5fcfd56e6230c2d26d5..1ef63030a95606d03a647d8c4f90b092d522dd75 100644 --- a/gcc/m2/mc-boot/GnameKey.h +++ b/gcc/m2/mc-boot/GnameKey.h @@ -24,6 +24,7 @@ along with GNU Modula-2; see the file COPYING3. If not see #if !defined (_nameKey_H) # define _nameKey_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/GsymbolKey.cc b/gcc/m2/mc-boot/GsymbolKey.cc index 61232975187976c5f8e4d6aac6ac49264e4f3ccf..c9848d54307413b522edb69526ca1391aa6cda11 100644 --- a/gcc/m2/mc-boot/GsymbolKey.cc +++ b/gcc/m2/mc-boot/GsymbolKey.cc @@ -20,6 +20,7 @@ You should have received a copy of the GNU General Public License along with GNU Modula-2; see the file COPYING3. If not see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/GsymbolKey.h b/gcc/m2/mc-boot/GsymbolKey.h index be8d8ed9f76452405e4c2c849d70b97b244bf4ac..82c2fe114224e8d33cbac602317b78f9cd00ba07 100644 --- a/gcc/m2/mc-boot/GsymbolKey.h +++ b/gcc/m2/mc-boot/GsymbolKey.h @@ -24,6 +24,7 @@ along with GNU Modula-2; see the file COPYING3. If not see #if !defined (_symbolKey_H) # define _symbolKey_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/Gtermios.h b/gcc/m2/mc-boot/Gtermios.h index fc6cf989f7ea7f1a42d5b776211a34b5ce8c8e92..a95e43fa3373f43dcb030d6edf79cf77db0f4cea 100644 --- a/gcc/m2/mc-boot/Gtermios.h +++ b/gcc/m2/mc-boot/Gtermios.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_termios_H) # define _termios_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/Gtop.cc b/gcc/m2/mc-boot/Gtop.cc index 34c5b27edd2ca021f16a8dc18e5f0d7610421dfe..ba492e5acbf565c604da507c8adb2687ac626ee9 100644 --- a/gcc/m2/mc-boot/Gtop.cc +++ b/gcc/m2/mc-boot/Gtop.cc @@ -20,6 +20,7 @@ You should have received a copy of the GNU General Public License along with GNU Modula-2; see the file COPYING3. If not see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/Gvarargs.cc b/gcc/m2/mc-boot/Gvarargs.cc index c9ba44d3439b08d122b02018abbbfd9e2aadc214..0f517c4d9d63dec2b12755c94ca056c30e2192a6 100644 --- a/gcc/m2/mc-boot/Gvarargs.cc +++ b/gcc/m2/mc-boot/Gvarargs.cc @@ -20,6 +20,7 @@ You should have received a copy of the GNU General Public License along with GNU Modula-2; see the file COPYING3. If not see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/Gvarargs.h b/gcc/m2/mc-boot/Gvarargs.h index b68ca9fad56848abf34117c49d9373b065cf9b85..9ac674ca5d65a65e1275a929eada6582878709e5 100644 --- a/gcc/m2/mc-boot/Gvarargs.h +++ b/gcc/m2/mc-boot/Gvarargs.h @@ -24,6 +24,7 @@ along with GNU Modula-2; see the file COPYING3. If not see #if !defined (_varargs_H) # define _varargs_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/Gwlists.cc b/gcc/m2/mc-boot/Gwlists.cc index 68482482ae1538d9ae2ce35e27e3a82222016e91..adf86f80dd83b673000444d771ba1256153a0b08 100644 --- a/gcc/m2/mc-boot/Gwlists.cc +++ b/gcc/m2/mc-boot/Gwlists.cc @@ -20,6 +20,7 @@ You should have received a copy of the GNU General Public License along with GNU Modula-2; see the file COPYING3. If not see <http://www.gnu.org/licenses/>. */ +#define INCLUDE_MEMORY #include "config.h" #include "system.h" #include <stdbool.h> diff --git a/gcc/m2/mc-boot/Gwlists.h b/gcc/m2/mc-boot/Gwlists.h index fe07de5e5d96c7a30e1bc256ac08cf06e7476bfd..424cdfb57ed834f75a2c05958f83461ae5ae4309 100644 --- a/gcc/m2/mc-boot/Gwlists.h +++ b/gcc/m2/mc-boot/Gwlists.h @@ -24,6 +24,7 @@ along with GNU Modula-2; see the file COPYING3. If not see #if !defined (_wlists_H) # define _wlists_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc-boot/Gwrapc.h b/gcc/m2/mc-boot/Gwrapc.h index 4d77e274c3c0592ea0292a95c332065df824df30..d36d74ccd4a95ddf8ccb97ed6fc33eec74f3717a 100644 --- a/gcc/m2/mc-boot/Gwrapc.h +++ b/gcc/m2/mc-boot/Gwrapc.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_wrapc_H) # define _wrapc_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/mc/decl.mod b/gcc/m2/mc/decl.mod index 2617cf6e59575dbd1897305d2386d6c096c6fe89..342487e398dbed5cce6e89e8d5f83a7d337cb320 100644 --- a/gcc/m2/mc/decl.mod +++ b/gcc/m2/mc/decl.mod @@ -94,7 +94,8 @@ TYPE nil, true, false, (* system types. *) address, loc, byte, word, - csizet, cssizet, + csizet, cssizet, cofft, + cardinal64, (* base types. *) char, cardinal, longcard, shortcard, @@ -159,7 +160,9 @@ TYPE byte, word, csizet, - cssizet : | + cssizet, + cofft, + cardinal64 : | (* base types. *) boolean, proc, @@ -738,6 +741,8 @@ VAR wordN, csizetN, cssizetN, + cofftN, + cardinal64N, adrN, sizeN, tsizeN, @@ -1460,17 +1465,6 @@ BEGIN END isAProcType ; -(* - isProcedure - returns TRUE if, n, is a procedure. -*) - -PROCEDURE isProcedure (n: node) : BOOLEAN ; -BEGIN - assert (n # NIL) ; - RETURN n^.kind = procedure -END isProcedure ; - - (* isPointer - returns TRUE if, n, is a pointer. *) @@ -4378,6 +4372,9 @@ BEGIN word : RETURN makeKey ('WORD') | csizet : RETURN makeKey ('CSIZE_T') | cssizet : RETURN makeKey ('CSSIZE_T') | + cofft : RETURN makeKey ('COFF_T') | + cardinal64 : RETURN makeKey ('CARDINAL64') | + (* base types. *) boolean : RETURN makeKey ('BOOLEAN') | proc : RETURN makeKey ('PROC') | @@ -4988,6 +4985,8 @@ BEGIN word, csizet, cssizet, + cofft, + cardinal64, char, cardinal, longcard, @@ -5126,6 +5125,8 @@ BEGIN word, csizet, cssizet, + cofft, + cardinal64, char, integer, longint, @@ -5166,6 +5167,8 @@ BEGIN word : RETURN n | csizet : RETURN n | cssizet : RETURN n | + cofft : RETURN n | + cardinal64 : RETURN n | (* base types. *) boolean : RETURN n | proc : RETURN n | @@ -5367,6 +5370,8 @@ BEGIN word : RETURN n | csizet : RETURN n | cssizet : RETURN n | + cofft : RETURN n | + cardinal64 : RETURN n | (* base types. *) boolean : RETURN n | proc : RETURN n | @@ -5538,7 +5543,9 @@ BEGIN byte, word, csizet, - cssizet : RETURN systemN | + cssizet, + cofft, + cardinal64 : RETURN systemN | (* base types. *) boolean, proc, @@ -6672,7 +6679,9 @@ BEGIN byte, word, csizet, - cssizet : doSystemC (p, n) | + cssizet, + cofft, + cardinal64 : doSystemC (p, n) | type : doTypeNameC (p, n) | pointer : doTypeNameC (p, n) @@ -8974,12 +8983,14 @@ PROCEDURE isSystem (n: node) : BOOLEAN ; BEGIN CASE n^.kind OF - address: RETURN TRUE | - loc : RETURN TRUE | - byte : RETURN TRUE | - word : RETURN TRUE | - csizet : RETURN TRUE | - cssizet: RETURN TRUE + address, + loc, + byte, + word, + csizet, + cssizet, + cofft, + cardinal64: RETURN TRUE ELSE RETURN FALSE @@ -9000,7 +9011,9 @@ BEGIN byte : outText (p, 'unsigned char') ; setNeedSpace (p) | word : outText (p, 'unsigned int') ; setNeedSpace (p) | csizet : outText (p, 'size_t') ; setNeedSpace (p) ; keyc.useSize_t | - cssizet: outText (p, 'ssize_t') ; setNeedSpace (p) ; keyc.useSSize_t + cssizet : outText (p, 'ssize_t') ; setNeedSpace (p) ; keyc.useSSize_t | + cofft : outText (p, 'off_t') ; setNeedSpace (p) | + cardinal64: outText (p, 'uint64_t') ; setNeedSpace (p) END END doSystemC ; @@ -14084,6 +14097,8 @@ BEGIN word, csizet, cssizet, + cofft, + cardinal64, (* base types. *) boolean, char, @@ -14951,6 +14966,8 @@ BEGIN word, csizet, cssizet, + cofft, + cardinal64, (* base types. *) char, cardinal, @@ -15089,6 +15106,8 @@ BEGIN word, csizet, cssizet, + cofft, + cardinal64, char, cardinal, longcard, @@ -16318,10 +16337,12 @@ BEGIN address, loc, - byte , - word , - csizet , - cssizet: doNameM2 (p, n) + byte, + word, + csizet, + cssizet, + cofft, + cardinal64: doNameM2 (p, n) END END doSystemM2 ; @@ -18084,6 +18105,8 @@ BEGIN word, csizet, cssizet, + cofft, + cardinal64, (* base types. *) boolean, proc, @@ -18222,6 +18245,8 @@ BEGIN wordN := makeBase (word) ; csizetN := makeBase (csizet) ; cssizetN := makeBase (cssizet) ; + cofftN := makeBase (cofft) ; + cardinal64N := makeBase (cardinal64) ; adrN := makeBase (adr) ; tsizeN := makeBase (tsize) ; @@ -18234,6 +18259,8 @@ BEGIN wordN := addToScope (wordN) ; csizetN := addToScope (csizetN) ; cssizetN := addToScope (cssizetN) ; + cofftN := addToScope (cofftN) ; + cardinal64N := addToScope (cardinal64N) ; adrN := addToScope (adrN) ; tsizeN := addToScope (tsizeN) ; throwN := addToScope (throwN) ; @@ -18247,7 +18274,9 @@ BEGIN addDone (byteN) ; addDone (wordN) ; addDone (csizetN) ; - addDone (cssizetN) + addDone (cssizetN) ; + addDone (cofftN) ; + addDone (cardinal64N) END makeSystem ; diff --git a/gcc/m2/mc/keyc.mod b/gcc/m2/mc/keyc.mod index 24ef6926d287226a96b2326b39c6d44eb78d3e48..857dffc6ab0dce67c480731bfc2a8d39c4894694 100644 --- a/gcc/m2/mc/keyc.mod +++ b/gcc/m2/mc/keyc.mod @@ -264,16 +264,6 @@ BEGIN END useUCharMin ; -(* - useUIntMin - indicate we have used UINT_MIN. -*) - -PROCEDURE useUIntMin ; -BEGIN - seenUIntMin := TRUE -END useUIntMin ; - - (* useIntMax - indicate we have used INT_MAX. *) @@ -334,16 +324,6 @@ BEGIN END useUCharMax ; -(* - useUIntMax - indicate we have used UINT_MAX. -*) - -PROCEDURE useUIntMax ; -BEGIN - seenUIntMax := TRUE -END useUIntMax ; - - (* useSize_t - indicate we have used size_t. *) diff --git a/gcc/m2/pge-boot/GIndexing.h b/gcc/m2/pge-boot/GIndexing.h index bb307ffc860c81812096d68a50e3091afeefedf0..4227866039a52f8b273c62e7b38b1aaeecd9f7c5 100644 --- a/gcc/m2/pge-boot/GIndexing.h +++ b/gcc/m2/pge-boot/GIndexing.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_Indexing_H) # define _Indexing_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/pge-boot/GSEnvironment.h b/gcc/m2/pge-boot/GSEnvironment.h index 01850abfd0f0d7d2fce151315040db0f6615c2ec..8429c3e87d9b7d2e4c0aec373602cfffbdfdfffe 100644 --- a/gcc/m2/pge-boot/GSEnvironment.h +++ b/gcc/m2/pge-boot/GSEnvironment.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_SEnvironment_H) # define _SEnvironment_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/pge-boot/GScan.h b/gcc/m2/pge-boot/GScan.h index d4b901744f7e0db54497b2171064ad10b18c86c1..04b7490476edce798bd3deb741ade102b6c0de74 100644 --- a/gcc/m2/pge-boot/GScan.h +++ b/gcc/m2/pge-boot/GScan.h @@ -29,6 +29,7 @@ see the files COPYING3 and COPYING.RUNTIME respectively. If not, see #if !defined (_Scan_H) # define _Scan_H +#define INCLUDE_MEMORY #include "config.h" #include "system.h" # ifdef __cplusplus diff --git a/gcc/m2/pge-boot/Glibc.h b/gcc/m2/pge-boot/Glibc.h index 8e68c768db356fce9286c7298bbbdbb36d84e801..ad7deb54d5300e5b0b6d0f991eee82b7d52aa4e1 100644 --- a/gcc/m2/pge-boot/Glibc.h +++ b/gcc/m2/pge-boot/Glibc.h @@ -203,7 +203,7 @@ EXTERN int libc_creat (void * filename, unsigned int mode); off_t lseek(int fildes, off_t offset, int whence); */ -EXTERN ssize_t libc_lseek (int fd, ssize_t offset, int whence); +EXTERN off_t libc_lseek (int fd, ssize_t offset, int whence); /* perror - writes errno and string. (ARRAY OF CHAR is translated onto ADDRESS).