[Vm-dev] [commit] r2390 - OSCog source as per VMMaker.oscog-eem.70. Add Newspeak VM generation to VMMaker

commits at squeakvm.org commits at squeakvm.org
Thu Jun 2 20:37:13 UTC 2011


Author: eliot
Date: 2011-06-02 13:37:13 -0700 (Thu, 02 Jun 2011)
New Revision: 2390

Added:
   branches/Cog/cygwinbuild/Pharo.def.in
   branches/Cog/cygwinbuild/Pharo.ico
   branches/Cog/cygwinbuild/Pharo.rc
Modified:
   branches/Cog/image/VMMaker-Squeak4.1.changes
   branches/Cog/image/VMMaker-Squeak4.1.image
   branches/Cog/image/Workspace.text
   branches/Cog/image/Workspace2.text
   branches/Cog/macbuild/plugins.int
   branches/Cog/nssrc/vm/gcc3x-interp.c
   branches/Cog/nssrc/vm/interp.c
   branches/Cog/nssrc/vm/interp.h
   branches/Cog/nssrc/vm/vmCallback.h
   branches/Cog/scripts/mkvmarchives
   branches/Cog/scripts/uploadvms
   branches/Cog/src/vm/cointerp.c
   branches/Cog/src/vm/cointerp.h
   branches/Cog/src/vm/gcc3x-cointerp.c
   branches/Cog/src/vm/interp.h
   branches/Cog/src/vm/vmCallback.h
   branches/Cog/stacksrc/vm/gcc3x-interp.c
   branches/Cog/stacksrc/vm/interp.c
   branches/Cog/stacksrc/vm/interp.h
   branches/Cog/stacksrc/vm/vmCallback.h
Log:
OSCog source as per VMMaker.oscog-eem.70.  Add Newspeak VM generation to VMMaker
image.  Add Pharo icons to win build.  Generate VMs using transitive pruneUnr-
eachableMethods.  Rename QVMProfileMacSupportPlugin to VMProfileMacSupportPlugin


Added: branches/Cog/cygwinbuild/Pharo.def.in
===================================================================
--- branches/Cog/cygwinbuild/Pharo.def.in	                        (rev 0)
+++ branches/Cog/cygwinbuild/Pharo.def.in	2011-06-02 20:37:13 UTC (rev 2390)
@@ -0,0 +1,3 @@
+; Set the total stack size to 4 megabytes (0x400000), reserving 4Mb and
+; committing 64k (0x10000)
+STACKSIZE 0x400000,0x10000

Added: branches/Cog/cygwinbuild/Pharo.ico
===================================================================
(Binary files differ)


Property changes on: branches/Cog/cygwinbuild/Pharo.ico
___________________________________________________________________
Added: svn:mime-type
   + application/octet-stream

Added: branches/Cog/cygwinbuild/Pharo.rc
===================================================================
--- branches/Cog/cygwinbuild/Pharo.rc	                        (rev 0)
+++ branches/Cog/cygwinbuild/Pharo.rc	2011-06-02 20:37:13 UTC (rev 2390)
@@ -0,0 +1,37 @@
+#ifdef _WIN32
+1                       ICON    DISCARDABLE     "Pharo.ico"
+2                       ICON    DISCARDABLE     "Pharo.ico"
+3                       ICON    DISCARDABLE     "Pharo.ico"
+
+/////////////////////////////////////////////////////////////////////////////
+//
+// Version
+//
+
+1 VERSIONINFO
+ FILEVERSION 1,0,15,0
+ PRODUCTVERSION 1,0,0,0
+ FILEFLAGSMASK 0x3fL
+ FILEFLAGS 0xaL
+ FILEOS 0x10001L
+ FILETYPE 0x1L
+ FILESUBTYPE 0x0L
+BEGIN
+    BLOCK "StringFileInfo"
+    BEGIN
+        BLOCK "040904E4"    // Lang=US English, CharSet=Windows Multilin
+        BEGIN
+            VALUE "CompanyName", "pharo-project.org\0"
+            VALUE "FileDescription", "Pharo Cog Virtual Machine 1.0.15\0"
+            VALUE "FileVersion", "3.11.3\0"
+            VALUE "LegalCopyright", "Copyright \251 1996-2010. All Rights Reserved.\0"
+            VALUE "ProductName", "Pharo\0"
+            VALUE "ProductVersion", "1.0.15\0"
+        END
+    END
+    BLOCK "VarFileInfo"
+    BEGIN
+        VALUE "Translation", 0x409, 1252
+    END
+END
+#endif
\ No newline at end of file

Modified: branches/Cog/image/VMMaker-Squeak4.1.changes
===================================================================
--- branches/Cog/image/VMMaker-Squeak4.1.changes	2011-06-02 00:38:51 UTC (rev 2389)
+++ branches/Cog/image/VMMaker-Squeak4.1.changes	2011-06-02 20:37:13 UTC (rev 2390)
@@ -193678,4 +193678,159 @@
 					FFIPlugin ReentrantARMFFIPlugin ReentrantFFIPlugin ReentrantPPCBEFFIPlugin
 					NewsqueakIA32ABIPlugin NewsqueakIA32ABIPluginAttic)!
 
-----QUIT----{1 June 2011 . 4:49:44 pm} VMMaker-Squeak4.1.image priorSource: 7358714!
\ No newline at end of file
+----QUIT----{1 June 2011 . 4:49:44 pm} VMMaker-Squeak4.1.image priorSource: 7358714!
+
+----STARTUP----{2 June 2011 . 11:53:22 am} as /Users/eliot/Cog/oscogvm/image/VMMaker-Squeak4.1.image!
+
+
+'From Squeak4.1 of 17 April 2010 [latest update: #9957] on 2 June 2011 at 11:53:08 am'!
+!ObjectMemory methodsFor: 'gc -- compaction' stamp: 'eem 6/2/2011 11:52' prior: 41562934!
+existImmutableReferencesToForwardedInRangeFrom: memStart to: memEnd
+	"Answer if any immutable objects refer to any forwarded objects so that the become: primitives can fail if a become would update a reference from an immutable object."
+
+	| oop |
+	<inline: true>
+	1 to: rootTableCount do:
+		[:i | 
+		oop := rootTable at: i.
+		(oop < memStart or: [oop >= memEnd]) ifTrue:
+			["Note: must not remap the fields of any object twice!!"
+			"remap this oop only if not in the memory range 
+			covered below"
+			(self objectIsImmutableAndReferencesForwarded: oop) ifTrue:
+				[^true]]].
+
+	oop := self oopFromChunk: memStart.
+	[oop < memEnd] whileTrue:
+		[(self isFreeObject: oop) ifFalse:
+			[(self objectIsImmutableAndReferencesForwarded: oop) ifTrue:
+				[^true]].
+		oop := self objectAfterWhileForwarding: oop].
+	^false! !
+
+----End fileIn of /Users/eliot/Cog/ObjectMemory-existImmutableReferencesToForwardedInRangeFromto.st----!
+!CCodeGenerator commentStamp: 'tpr 5/2/2003 14:30' prior: 34425829!
+This class oversees the translation of a subset of Smalltalk to C, allowing the comforts of Smalltalk during development and the efficiency and portability of C for the resulting interpreter.  
+See VMMaker for more useful info!
+
+----STARTUP----{2 June 2011 . 1:01:29 pm} as /Users/eliot/Cog/oscogvm/image/VMMaker-Squeak4.1.image!
+
+!InterpreterSimulatorMSB64 methodsFor: 'as yet unclassified' stamp: 'di 6/9/2004 12:17' prior: 40937807!
+byteSwapped: w
+	"Return the given integer with its bytes in the reverse order."
+
+	^ (super byteSwapped: ((w bitShift: -32) bitAnd: 16rFFFFFFFF)) +
+	  ((super byteSwapped: (w bitAnd: 16rFFFFFFFF)) bitShift: 32)! !
+!InterpreterSimulatorMSB64 methodsFor: 'as yet unclassified' stamp: 'di 7/3/2004 10:40' prior: 40938125!
+long32At: byteAddress
+	"Return the 32-bit word at byteAddress which must be 0 mod 4."
+
+	^ super longAt: byteAddress! !
+!InterpreterSimulatorMSB64 methodsFor: 'as yet unclassified' stamp: 'di 7/3/2004 10:41' prior: 40938349!
+long32At: byteAddress put: a32BitValue
+	"Store the 32-bit value at byteAddress which must be 0 mod 4."
+
+	super longAt: byteAddress put: a32BitValue! !
+!InterpreterSimulatorMSB64 methodsFor: 'as yet unclassified' stamp: 'di 6/9/2004 15:43' prior: 40938605!
+longAt: byteAddress
+	"Note: Adjusted for Smalltalk's 1-based array indexing."
+
+	^ ((super longAt: byteAddress) bitShift: 32) bitOr: (super longAt: byteAddress + 4)! !
+!InterpreterSimulatorMSB64 methodsFor: 'as yet unclassified' stamp: 'di 6/9/2004 15:48' prior: 40938877!
+longAt: byteAddress put: a64BitValue
+	"Note: Adjusted for Smalltalk's 1-based array indexing."
+
+	super longAt: byteAddress put: (a64BitValue bitShift: -32).
+	super longAt: byteAddress + 4 put: (a64BitValue bitAnd: 16rFFFFFFFF).
+	^ a64BitValue! !
+!CCodeGenerator methodsFor: 'inlining' stamp: 'eem 6/2/2011 12:38' prior: 34372907!
+pruneUnreachableMethods
+	"Remove any methods that are not reachable. Retain methods needed by the translated classes - see implementors of requiredMethodNames"
+ 	
+	| newMethods previousSize visited |
+	"add all the exported methods and all the called methods to the requiredSelectors"
+	"keep all the fake methods (macros and struct accessors; these are needed
+	 to ensure correct code generation."
+
+	methods do: [ :m |
+		m export ifTrue:
+			[requiredSelectors add: m selector].
+		m isRealMethod ifFalse:
+			[requiredSelectors add: m selector]].
+
+	"Now compute the transitive closure..."
+	previousSize := requiredSelectors size.
+	visited := IdentitySet new: methods size.
+	[requiredSelectors do:
+		[:s|
+		(methods at: s ifAbsent: []) ifNotNil:
+			[:m|
+			(visited includes: m) ifFalse:
+				[visited add: m.
+				 m isRealMethod ifTrue:
+					[requiredSelectors addAll: m allCalls]]]].
+	 requiredSelectors size > previousSize]
+		whileTrue:
+			[previousSize := requiredSelectors size].
+
+	"build a new dictionary of methods from the collection of all the ones to keep"			
+	newMethods := Dictionary new: requiredSelectors size.
+	requiredSelectors do:
+		[:sel|
+		methods at: sel ifPresent:[:meth| newMethods at: sel put: meth]].
+	methods := newMethods! !
+!CCodeGenerator methodsFor: 'public' stamp: 'eem 6/2/2011 12:27' prior: 34324168!
+removeUnneededBuiltins
+	| toRemove |
+	toRemove := Set new: 64.
+	methods keysDo:
+		[:sel|
+		(self builtin: sel) ifTrue:
+			[(requiredSelectors includes: sel) ifFalse:
+				[toRemove add: sel]]].
+	toRemove do:
+		[:sel| self removeMethodForSelector: sel]! !
+!CCodeGenerator methodsFor: 'inlining' stamp: 'eem 6/2/2011 12:27' prior: 34376588!
+retainMethods: aListOfSelectorsToKeep
+	"add aListOfSelectorsToKeep to requiredSelectors so that they will not be pruned"
+	requiredSelectors ifNil:[requiredSelectors := Set new:100].
+	requiredSelectors addAll: aListOfSelectorsToKeep.
+	^aListOfSelectorsToKeep! !
+!InterpreterSimulatorLSB64 methodsFor: 'as yet unclassified' stamp: 'di 6/13/2004 10:56' prior: 40955181!
+long32At: byteAddress
+
+	"Return the 32-bit word at byteAddress which must be 0 mod 4."
+	| lowBits long |
+	lowBits := byteAddress bitAnd: 4.
+	long := self longAt: byteAddress - lowBits.
+	^ lowBits = 4
+		ifTrue: [ long bitShift: -32 ]
+		ifFalse: [ long bitAnd: 16rFFFFFFFF ].
+! !
+!InterpreterSimulatorLSB64 methodsFor: 'as yet unclassified' stamp: 'di 6/13/2004 11:01' prior: 40955565!
+long32At: byteAddress put: a32BitValue
+	"Store the 32-bit value at byteAddress which must be 0 mod 4."
+	| lowBits long64 longAddress |
+	lowBits := byteAddress bitAnd: 4.
+	lowBits = 0
+		ifTrue:
+		[ "storing into LS word"
+		long64 := self longAt: byteAddress.
+		self longAt: byteAddress
+				put: ((long64 bitAnd: 16rFFFFFFFF00000000) bitOr: a32BitValue)
+		]
+		ifFalse:
+		[longAddress := byteAddress - 4.
+		long64 := self longAt: longAddress.
+		self longAt: longAddress
+				put: ((long64 bitAnd: 16rFFFFFFFF) bitOr: (a32BitValue bitShift: 32))
+		]! !
+
+"VMMaker"!
+
+----QUIT----{2 June 2011 . 1:04:20 pm} VMMaker-Squeak4.1.image priorSource: 8051921!
+
+----STARTUP----{2 June 2011 . 1:14:32 pm} as /Users/eliot/Cog/oscogvm/image/VMMaker-Squeak4.1.image!
+
+
+----QUIT----{2 June 2011 . 1:17:56 pm} VMMaker-Squeak4.1.image priorSource: 8058095!
\ No newline at end of file

Modified: branches/Cog/image/VMMaker-Squeak4.1.image
===================================================================
(Binary files differ)

Modified: branches/Cog/image/Workspace.text
===================================================================
--- branches/Cog/image/Workspace.text	2011-06-02 00:38:51 UTC (rev 2389)
+++ branches/Cog/image/Workspace.text	2011-06-02 20:37:13 UTC (rev 2390)
@@ -1,4 +1,4 @@
-This image is intended to build new CoInterpreter or StackInterpreter Cog VMs.
+This image is intended to build new CoInterpreter or StackInterpreter Cog VMs, and a Newspeak VM.
 The following doits create a single; source tree (../src) for all platforms.  Since they use a relative path they will work out of the box.  Generate the entire VM using them.
 
 x86 platforms:
@@ -20,6 +20,17 @@
 		platformDir: (FileDirectory default / '../platforms') fullName
 		excluding: (InterpreterPlugin withAllSubclasses collect: [:ea| ea name]))
 
+Newspeak VM:
+	(VMMaker
+		generate: NewspeakInterpreter
+		to: (FileDirectory default / '../nssrc') fullName
+		platformDir: (FileDirectory default / '../platforms') fullName
+		including:#(	AsynchFilePlugin FloatArrayPlugin RePlugin BalloonEnginePlugin FloatMathPlugin
+					SecurityPlugin BMPReadWriterPlugin NewsqueakIA32ABIPlugin SocketPlugin
+					SoundPlugin BitBltSimulation JPEGReadWriter2Plugin SurfacePlugin DSAPlugin
+					JPEGReaderPlugin UUIDPlugin DropPlugin LargeIntegersPlugin UnixOSProcessPlugin
+					FileCopyPlugin Matrix2x3Plugin Win32OSProcessPlugin FilePlugin
+					MiscPrimitivePlugin InflatePlugin VMProfileMacSupportPlugin))
 To generate a single plugin you can use a VMMaker.
 
 To rebuild this image
Modified: branches/Cog/image/Workspace2.text
===================================================================
--- branches/Cog/image/Workspace2.text	2011-06-02 00:38:51 UTC (rev 2389)
+++ branches/Cog/image/Workspace2.text	2011-06-02 20:37:13 UTC (rev 2390)
@@ -1,4 +1,4 @@
-Remember, set to _your_ initials, then save as VMMaker-oscog.N
+Remember, set to _your_ initials, then save as VMMaker.oscog-initials.N
 (| user pw |
 Utilities setAuthorInitials.
 user := UIManager default request: 'Repository user name'.
@@ -6,7 +6,8 @@
 MCHttpRepository allSubInstancesDo: [ : rep |
 	rep user: user;
 	password: pw ].
-user = 'anon' ifTrue: [MCFileBasedRepository flushAllCaches])
+user = 'anon' ifTrue: [MCFileBasedRepository flushAllCaches].
+self halt: 'close me')
 
 Smalltalk condenseChanges.
 MCFileBasedRepository flushAllCaches
@@ -60,7 +61,8 @@
 
 "Purge irrelevant history from Cog VMMaker"
 (| vmmwc strings |
-strings := #(681 684 687 689 693 694 695 698 707) collect: [:n| '.', n].
+strings := #(681 684 687 689 693 694 695 698 707 710 711 719 735 737 739 738) collect: [:n| '.', n].
 vmmwc := MCWorkingCopy allManagers detect: [:p| p package name = 'VMMaker'].
 vmmwc instVarNamed: 'ancestry'
-	put: (vmmwc ancestry copyReject: [:a| strings anySatisfy: [:ver| a name endsWith: ver]]))
\ No newline at end of file
+	put: (vmmwc ancestry copyReject: [:a| strings anySatisfy: [:ver| a name endsWith: ver]]).
+	self halt: 'close me')
\ No newline at end of file

Modified: branches/Cog/macbuild/plugins.int
===================================================================
--- branches/Cog/macbuild/plugins.int	2011-06-02 00:38:51 UTC (rev 2389)
+++ branches/Cog/macbuild/plugins.int	2011-06-02 20:37:13 UTC (rev 2390)
@@ -24,7 +24,6 @@
 Matrix2x3Plugin \
 MIDIPlugin \
 MiscPrimitivePlugin \
-QVMProfileMacSupportPlugin \
 RePlugin \
 SecurityPlugin \
 SerialPlugin \
@@ -34,4 +33,5 @@
 SoundPlugin \
 StarSqueakPlugin \
 SurfacePlugin \
-UUIDPlugin
+UUIDPlugin \
+VMProfileMacSupportPlugin \

Modified: branches/Cog/nssrc/vm/gcc3x-interp.c
===================================================================
--- branches/Cog/nssrc/vm/gcc3x-interp.c	2011-06-02 00:38:51 UTC (rev 2389)
+++ branches/Cog/nssrc/vm/gcc3x-interp.c	2011-06-02 20:37:13 UTC (rev 2390)
@@ -2,11 +2,11 @@
 
 
 /* Automatically generated by
-	CCodeGeneratorGlobalStructure VMMaker.oscog-eem.69 uuid: fd9c171e-3731-4093-912d-ad8fefb4800c
+	CCodeGeneratorGlobalStructure VMMaker.oscog-eem.70 uuid: 36b63465-1b05-401f-bcb2-f9cae49422b8
    from
-	NewspeakInterpreter VMMaker.oscog-eem.69 uuid: fd9c171e-3731-4093-912d-ad8fefb4800c
+	NewspeakInterpreter VMMaker.oscog-eem.70 uuid: 36b63465-1b05-401f-bcb2-f9cae49422b8
  */
-static char __buildInfo[] = "NewspeakInterpreter VMMaker.oscog-eem.69 uuid: fd9c171e-3731-4093-912d-ad8fefb4800c " __DATE__ ;
+static char __buildInfo[] = "NewspeakInterpreter VMMaker.oscog-eem.70 uuid: 36b63465-1b05-401f-bcb2-f9cae49422b8 " __DATE__ ;
 char *__interpBuildInfo = __buildInfo;
 
 
@@ -425,7 +425,6 @@
 sqInt isKindOf(sqInt oop, char *className);
 sqInt isMemberOf(sqInt oop, char *className);
 static sqInt lastPointerOf(sqInt oop);
-static sqInt lengthOfNameOfClass(sqInt classOop);
 sqInt lengthOf(sqInt oop);
 static sqInt lengthOfbaseHeaderformat(sqInt oop, sqInt hdr, sqInt fmt);
 sqInt literalCountOf(sqInt methodPointer);
@@ -447,7 +446,6 @@
 sqInt methodPrimitiveIndex(void);
 sqInt methodReturnValue(sqInt oop);
 EXPORT(sqInt) moduleUnloaded(char *aModuleName);
-static char * nameOfClass(sqInt classOop);
 sqInt nilObject(void);
 static sqInt nonWeakFieldsOf(sqInt oop);
 sqInt objectAfter(sqInt oop);
@@ -456,7 +454,6 @@
 sqInt objectExactlyBefore(sqInt oop);
 static sqInt objectIsImmutableAndReferencesForwarded(sqInt oop);
 sqInt obsoleteDontUseThisFetchWordofObject(sqInt fieldIndex, sqInt oop);
-static sqInt okayFields(sqInt oop);
 static sqInt okayOop(sqInt signedOop);
 static sqInt oopFromChunk(sqInt chunk);
 static sqInt oopHasAcceptableClass(sqInt signedOop);
@@ -800,13 +797,11 @@
 _iss sqInt nextWakeupTick;
 _iss sqInt growHeadroom;
 _iss sqInt statGrowMemory;
-_iss sqInt classNameIndex;
 _iss sqInt interruptCheckCounterFeedBackReset;
 _iss sqInt signalLowSpace;
 _iss usqInt compEnd;
 _iss sqInt freeLargeContexts;
 _iss sqInt lastTick;
-_iss sqInt metaclassSizeBytes;
 _iss sqInt pendingFinalizationSignals;
 _iss sqInt statMarkCount;
 _iss sqInt statShrinkMemory;
@@ -815,11 +810,12 @@
 _iss sqInt statCompMoveCount;
 _iss sqInt statMkFwdCount;
 _iss sqInt statSweepCount;
-_iss sqInt thisClassIndex;
+_iss sqInt classNameIndex;
 _iss sqInt forceTenureFlag;
 _iss usqLong gcStartUsecs;
 _iss sqInt interruptChecksEveryNms;
 _iss sqInt interruptPending;
+_iss sqInt metaclassSizeBytes;
 _iss usqLong statFullGCUsecs;
 _iss sqInt statFullGCs;
 _iss usqLong statIncrGCUsecs;
@@ -835,6 +831,7 @@
 _iss sqInt statGCEndTime;
 _iss usqLong statIGCDeltaUsecs;
 _iss sqInt statPendingFinalizationSignals;
+_iss sqInt thisClassIndex;
 _iss sqInt gcBiasToGrow;
 _iss sqInt gcBiasToGrowGCLimit;
 _iss sqInt gcSemaphoreIndex;
@@ -1455,7 +1452,7 @@
  0 };
 char * breakSelector;
 sqInt breakSelectorLength = -1;
-const char *interpreterVersion = "Newspeak Virtual Machine [NewspeakInterpreter VMMaker.oscog-eem.69]";
+const char *interpreterVersion = "Newspeak Virtual Machine [NewspeakInterpreter VMMaker.oscog-eem.70]";
 volatile int sendTrace;
 
 
@@ -13243,37 +13240,7 @@
 	return (((((usqInt) methodHeader) >> 10) & 255) * BytesPerWord) + BaseHeaderSize;
 }
 
-static sqInt
-lengthOfNameOfClass(sqInt classOop)
-{   DECL_MAYBE_SQ_GLOBAL_STRUCT
-    sqInt header;
-    sqInt sz;
 
-	if ((sizeBitsOf(classOop)) == GIV(metaclassSizeBytes)) {
-		return lengthOfNameOfClass(longAt((classOop + BaseHeaderSize) + (GIV(thisClassIndex) << ShiftForWord)));
-	}
-	/* begin lengthOf: */
-	header = longAt(longAt((classOop + BaseHeaderSize) + (GIV(classNameIndex) << ShiftForWord)));
-	/* begin lengthOf:baseHeader:format: */
-	if ((header & TypeMask) == HeaderTypeSizeAndClass) {
-		sz = (longAt((longAt((classOop + BaseHeaderSize) + (GIV(classNameIndex) << ShiftForWord))) - (BytesPerWord * 2))) & LongSizeMask;
-	}
-	else {
-		sz = header & SizeMask;
-	}
-	sz -= header & Size4Bit;
-	if (((((usqInt) header) >> 8) & 15) <= 4) {
-		return ((usqInt) (sz - BaseHeaderSize)) >> ShiftForWord;
-	}
-	if (((((usqInt) header) >> 8) & 15) < 8) {
-		return ((usqInt) (sz - BaseHeaderSize)) >> 2;
-	}
-	else {
-		return (sz - BaseHeaderSize) - (((((usqInt) header) >> 8) & 15) & 3);
-	}
-}
-
-
 /*	Return the number of indexable bytes or words in the given object. Assume
 	the argument is not an integer. For a CompiledMethod, the size of the
 	method header (in bytes) should be subtracted from the result.
@@ -14302,20 +14269,6 @@
 }
 
 
-/*	Brain-damaged nameOfClass: for C VM. Does *not* answer Foo class for
-	metaclasses. Use e.g. classIsMeta: to avoid being fooled. */
-
-static char *
-nameOfClass(sqInt classOop)
-{   DECL_MAYBE_SQ_GLOBAL_STRUCT
-	if ((sizeBitsOf(classOop)) == GIV(metaclassSizeBytes)) {
-		return nameOfClass(longAt((classOop + BaseHeaderSize) + (GIV(thisClassIndex) << ShiftForWord)));
-	}
-	/* begin firstFixedField: */
-	return ((void *) (pointerForOop((longAt((classOop + BaseHeaderSize) + (GIV(classNameIndex) << ShiftForWord))) + BaseHeaderSize)));
-}
-
-
 /*	For access from BitBlt module & Cogit */
 
 sqInt
@@ -14591,61 +14544,6 @@
 }
 
 
-/*	If this is a pointers object, check that its fields are all okay oops. */
-
-static sqInt
-okayFields(sqInt oop)
-{   DECL_MAYBE_SQ_GLOBAL_STRUCT
-    sqInt c;
-    sqInt ccIndex;
-    sqInt fieldOop;
-    sqInt i;
-
-	if ((oop == null)
-	 || (oop == 0)) {
-		return 1;
-	}
-	if ((oop & 1)) {
-		return 1;
-	}
-	okayOop(oop);
-	oopHasOkayClass(oop);
-	if (!(((oop & 1) == 0)
-		 && (((((usqInt) (longAt(oop))) >> 8) & 15) <= 4))) {
-		return 1;
-	}
-	/* begin fetchClassOf: */
-	if ((oop & 1)) {
-		c = longAt((GIV(specialObjectsOop) + BaseHeaderSize) + (ClassInteger << ShiftForWord));
-		goto l1;
-	}
-	if (((ccIndex = (((usqInt) (longAt(oop))) >> 12) & 31)) == 0) {
-		c = (longAt(oop - BaseHeaderSize)) & AllButTypeMask;
-		goto l1;
-	}
-	else {
-		c = longAt(((longAt((GIV(specialObjectsOop) + BaseHeaderSize) + (CompactClasses << ShiftForWord))) + BaseHeaderSize) + ((ccIndex - 1) << ShiftForWord));
-		goto l1;
-	}
-l1:	/* end fetchClassOf: */;
-	if ((c == (longAt((GIV(specialObjectsOop) + BaseHeaderSize) + (ClassMethodContext << ShiftForWord))))
-	 || (c == (longAt((GIV(specialObjectsOop) + BaseHeaderSize) + (ClassBlockContext << ShiftForWord))))) {
-		i = (CtxtTempFrameStart + (fetchStackPointerOf(oop))) - 1;
-	}
-	else {
-		i = (lengthOf(oop)) - 1;
-	}
-	while (i >= 0) {
-		fieldOop = longAt((oop + BaseHeaderSize) + (i << ShiftForWord));
-		if (!((fieldOop & 1))) {
-			okayOop(fieldOop);
-			oopHasOkayClass(fieldOop);
-		}
-		i -= 1;
-	}
-}
-
-
 /*	Verify that the given oop is legitimate. Check address, header, and size
 	but not class.
  */

Modified: branches/Cog/nssrc/vm/interp.c
===================================================================
--- branches/Cog/nssrc/vm/interp.c	2011-06-02 00:38:51 UTC (rev 2389)
+++ branches/Cog/nssrc/vm/interp.c	2011-06-02 20:37:13 UTC (rev 2390)
@@ -1,9 +1,9 @@
 /* Automatically generated by
-	CCodeGeneratorGlobalStructure VMMaker.oscog-eem.69 uuid: fd9c171e-3731-4093-912d-ad8fefb4800c
+	CCodeGeneratorGlobalStructure VMMaker.oscog-eem.70 uuid: 36b63465-1b05-401f-bcb2-f9cae49422b8
    from
-	NewspeakInterpreter VMMaker.oscog-eem.69 uuid: fd9c171e-3731-4093-912d-ad8fefb4800c
+	NewspeakInterpreter VMMaker.oscog-eem.70 uuid: 36b63465-1b05-401f-bcb2-f9cae49422b8
  */
-static char __buildInfo[] = "NewspeakInterpreter VMMaker.oscog-eem.69 uuid: fd9c171e-3731-4093-912d-ad8fefb4800c " __DATE__ ;
+static char __buildInfo[] = "NewspeakInterpreter VMMaker.oscog-eem.70 uuid: 36b63465-1b05-401f-bcb2-f9cae49422b8 " __DATE__ ;
 char *__interpBuildInfo = __buildInfo;
 
 
@@ -422,7 +422,6 @@
 sqInt isKindOf(sqInt oop, char *className);
 sqInt isMemberOf(sqInt oop, char *className);
 static sqInt lastPointerOf(sqInt oop);
-static sqInt lengthOfNameOfClass(sqInt classOop);
 sqInt lengthOf(sqInt oop);
 static sqInt lengthOfbaseHeaderformat(sqInt oop, sqInt hdr, sqInt fmt);
 sqInt literalCountOf(sqInt methodPointer);
@@ -444,7 +443,6 @@
 sqInt methodPrimitiveIndex(void);
 sqInt methodReturnValue(sqInt oop);
 EXPORT(sqInt) moduleUnloaded(char *aModuleName);
-static char * nameOfClass(sqInt classOop);
 sqInt nilObject(void);
 static sqInt nonWeakFieldsOf(sqInt oop);
 sqInt objectAfter(sqInt oop);
@@ -453,7 +451,6 @@
 sqInt objectExactlyBefore(sqInt oop);
 static sqInt objectIsImmutableAndReferencesForwarded(sqInt oop);
 sqInt obsoleteDontUseThisFetchWordofObject(sqInt fieldIndex, sqInt oop);
-static sqInt okayFields(sqInt oop);
 static sqInt okayOop(sqInt signedOop);
 static sqInt oopFromChunk(sqInt chunk);
 static sqInt oopHasAcceptableClass(sqInt signedOop);
@@ -797,13 +794,11 @@
 _iss sqInt nextWakeupTick;
 _iss sqInt growHeadroom;
 _iss sqInt statGrowMemory;
-_iss sqInt classNameIndex;
 _iss sqInt interruptCheckCounterFeedBackReset;
 _iss sqInt signalLowSpace;
 _iss usqInt compEnd;
 _iss sqInt freeLargeContexts;
 _iss sqInt lastTick;
-_iss sqInt metaclassSizeBytes;
 _iss sqInt pendingFinalizationSignals;
 _iss sqInt statMarkCount;
 _iss sqInt statShrinkMemory;
@@ -812,11 +807,12 @@
 _iss sqInt statCompMoveCount;
 _iss sqInt statMkFwdCount;
 _iss sqInt statSweepCount;
-_iss sqInt thisClassIndex;
+_iss sqInt classNameIndex;
 _iss sqInt forceTenureFlag;
 _iss usqLong gcStartUsecs;
 _iss sqInt interruptChecksEveryNms;
 _iss sqInt interruptPending;
+_iss sqInt metaclassSizeBytes;
 _iss usqLong statFullGCUsecs;
 _iss sqInt statFullGCs;
 _iss usqLong statIncrGCUsecs;
@@ -832,6 +828,7 @@
 _iss sqInt statGCEndTime;
 _iss usqLong statIGCDeltaUsecs;
 _iss sqInt statPendingFinalizationSignals;
+_iss sqInt thisClassIndex;
 _iss sqInt gcBiasToGrow;
 _iss sqInt gcBiasToGrowGCLimit;
 _iss sqInt gcSemaphoreIndex;
@@ -1452,7 +1449,7 @@
  0 };
 char * breakSelector;
 sqInt breakSelectorLength = -1;
-const char *interpreterVersion = "Newspeak Virtual Machine [NewspeakInterpreter VMMaker.oscog-eem.69]";
+const char *interpreterVersion = "Newspeak Virtual Machine [NewspeakInterpreter VMMaker.oscog-eem.70]";
 volatile int sendTrace;
 
 
@@ -13239,37 +13236,7 @@
 	return (((((usqInt) methodHeader) >> 10) & 255) * BytesPerWord) + BaseHeaderSize;
 }
 
-static sqInt
-lengthOfNameOfClass(sqInt classOop)
-{   DECL_MAYBE_SQ_GLOBAL_STRUCT
-    sqInt header;
-    sqInt sz;
 
-	if ((sizeBitsOf(classOop)) == GIV(metaclassSizeBytes)) {
-		return lengthOfNameOfClass(longAt((classOop + BaseHeaderSize) + (GIV(thisClassIndex) << ShiftForWord)));
-	}
-	/* begin lengthOf: */
-	header = longAt(longAt((classOop + BaseHeaderSize) + (GIV(classNameIndex) << ShiftForWord)));
-	/* begin lengthOf:baseHeader:format: */
-	if ((header & TypeMask) == HeaderTypeSizeAndClass) {
-		sz = (longAt((longAt((classOop + BaseHeaderSize) + (GIV(classNameIndex) << ShiftForWord))) - (BytesPerWord * 2))) & LongSizeMask;
-	}
-	else {
-		sz = header & SizeMask;
-	}
-	sz -= header & Size4Bit;
-	if (((((usqInt) header) >> 8) & 15) <= 4) {
-		return ((usqInt) (sz - BaseHeaderSize)) >> ShiftForWord;
-	}
-	if (((((usqInt) header) >> 8) & 15) < 8) {
-		return ((usqInt) (sz - BaseHeaderSize)) >> 2;
-	}
-	else {
-		return (sz - BaseHeaderSize) - (((((usqInt) header) >> 8) & 15) & 3);
-	}
-}
-
-
 /*	Return the number of indexable bytes or words in the given object. Assume
 	the argument is not an integer. For a CompiledMethod, the size of the
 	method header (in bytes) should be subtracted from the result.
@@ -14298,20 +14265,6 @@
 }
 
 
-/*	Brain-damaged nameOfClass: for C VM. Does *not* answer Foo class for
-	metaclasses. Use e.g. classIsMeta: to avoid being fooled. */
-
-static char *
-nameOfClass(sqInt classOop)
-{   DECL_MAYBE_SQ_GLOBAL_STRUCT
-	if ((sizeBitsOf(classOop)) == GIV(metaclassSizeBytes)) {
-		return nameOfClass(longAt((classOop + BaseHeaderSize) + (GIV(thisClassIndex) << ShiftForWord)));
-	}
-	/* begin firstFixedField: */
-	return ((void *) (pointerForOop((longAt((classOop + BaseHeaderSize) + (GIV(classNameIndex) << ShiftForWord))) + BaseHeaderSize)));
-}
-
-
 /*	For access from BitBlt module & Cogit */
 
 sqInt
@@ -14587,61 +14540,6 @@
 }
 
 
-/*	If this is a pointers object, check that its fields are all okay oops. */
-
-static sqInt
-okayFields(sqInt oop)
-{   DECL_MAYBE_SQ_GLOBAL_STRUCT
-    sqInt c;
-    sqInt ccIndex;
-    sqInt fieldOop;
-    sqInt i;
-
-	if ((oop == null)
-	 || (oop == 0)) {
-		return 1;
-	}
-	if ((oop & 1)) {
-		return 1;
-	}
-	okayOop(oop);
-	oopHasOkayClass(oop);
-	if (!(((oop & 1) == 0)
-		 && (((((usqInt) (longAt(oop))) >> 8) & 15) <= 4))) {
-		return 1;
-	}
-	/* begin fetchClassOf: */
-	if ((oop & 1)) {
-		c = longAt((GIV(specialObjectsOop) + BaseHeaderSize) + (ClassInteger << ShiftForWord));
-		goto l1;
-	}
-	if (((ccIndex = (((usqInt) (longAt(oop))) >> 12) & 31)) == 0) {
-		c = (longAt(oop - BaseHeaderSize)) & AllButTypeMask;
-		goto l1;
-	}
-	else {
-		c = longAt(((longAt((GIV(specialObjectsOop) + BaseHeaderSize) + (CompactClasses << ShiftForWord))) + BaseHeaderSize) + ((ccIndex - 1) << ShiftForWord));
-		goto l1;
-	}
-l1:	/* end fetchClassOf: */;
-	if ((c == (longAt((GIV(specialObjectsOop) + BaseHeaderSize) + (ClassMethodContext << ShiftForWord))))
-	 || (c == (longAt((GIV(specialObjectsOop) + BaseHeaderSize) + (ClassBlockContext << ShiftForWord))))) {
-		i = (CtxtTempFrameStart + (fetchStackPointerOf(oop))) - 1;
-	}
-	else {
-		i = (lengthOf(oop)) - 1;
-	}
-	while (i >= 0) {
-		fieldOop = longAt((oop + BaseHeaderSize) + (i << ShiftForWord));
-		if (!((fieldOop & 1))) {
-			okayOop(fieldOop);
-			oopHasOkayClass(fieldOop);
-		}
-		i -= 1;
-	}
-}
-
-
 /*	Verify that the given oop is legitimate. Check address, header, and size
 	but not class.
  */

Modified: branches/Cog/nssrc/vm/interp.h
===================================================================
--- branches/Cog/nssrc/vm/interp.h	2011-06-02 00:38:51 UTC (rev 2389)
+++ branches/Cog/nssrc/vm/interp.h	2011-06-02 20:37:13 UTC (rev 2390)
@@ -1,5 +1,5 @@
 /* Automatically generated by
-	CCodeGeneratorGlobalStructure VMMaker.oscog-eem.69 uuid: fd9c171e-3731-4093-912d-ad8fefb4800c
+	CCodeGeneratorGlobalStructure VMMaker.oscog-eem.70 uuid: 36b63465-1b05-401f-bcb2-f9cae49422b8
  */
 
 #define NewspeakVM 1

Modified: branches/Cog/nssrc/vm/vmCallback.h
===================================================================
--- branches/Cog/nssrc/vm/vmCallback.h	2011-06-02 00:38:51 UTC (rev 2389)
+++ branches/Cog/nssrc/vm/vmCallback.h	2011-06-02 20:37:13 UTC (rev 2390)
@@ -1,5 +1,5 @@
 /* Automatically generated by
-	CCodeGeneratorGlobalStructure VMMaker.oscog-eem.69 uuid: fd9c171e-3731-4093-912d-ad8fefb4800c
+	CCodeGeneratorGlobalStructure VMMaker.oscog-eem.70 uuid: 36b63465-1b05-401f-bcb2-f9cae49422b8
  */
 
 #define VM_CALLBACK_INC 1

Modified: branches/Cog/scripts/mkvmarchives
===================================================================
--- branches/Cog/scripts/mkvmarchives	2011-06-02 00:38:51 UTC (rev 2389)
+++ branches/Cog/scripts/mkvmarchives	2011-06-02 20:37:13 UTC (rev 2390)
@@ -1,6 +1,8 @@
 #!/bin/sh
+test -d Cog.app || mkdir Cog.app
 rm -rf Cog.app/* Cog.app.tgz
 (cd macbuild/Fast.app>/dev/null;tar cf - *)|(cd Cog.app;tar xvf -)
+test -d cogwin || mkdir cogwin
 rm -rf cogwin/* cogwin.zip
 ln cygwinbuild/build/vm/{Croquet.exe,Croquet.ini,Croquet.map} cogwin
 ln cygwinbuild/build/vm/*.dll cogwin

Modified: branches/Cog/scripts/uploadvms
===================================================================
--- branches/Cog/scripts/uploadvms	2011-06-02 00:38:51 UTC (rev 2389)
+++ branches/Cog/scripts/uploadvms	2011-06-02 20:37:13 UTC (rev 2390)
@@ -3,4 +3,4 @@
 echo $VER
 test -f README.$VER || vi README.$VER
 ssh -x eliotmiranda at bugsy.dreamhost.com mkdir mirandabanda.org/files/Cog/VM/VM.r$VER
-scp README.$VER Cog.app.tgz coglinux.tgz cogwin.zip eliotmiranda at bugsy.dreamhost.com:mirandabanda.org/files/Cog/VM/VM.r$VER
+scp README.$VER Cog.app.tgz coglinux.tgz cogwin.zip Newspeak\ Virtual\ Machine.app.zip nsvmwin.zip eliotmiranda at bugsy.dreamhost.com:mirandabanda.org/files/Cog/VM/VM.r$VER

Modified: branches/Cog/src/vm/cointerp.c
===================================================================
--- branches/Cog/src/vm/cointerp.c	2011-06-02 00:38:51 UTC (rev 2389)
+++ branches/Cog/src/vm/cointerp.c	2011-06-02 20:37:13 UTC (rev 2390)
@@ -1,9 +1,9 @@
 /* Automatically generated by
-	CCodeGeneratorGlobalStructure VMMaker.oscog-eem.69 uuid: fd9c171e-3731-4093-912d-ad8fefb4800c
+	CCodeGeneratorGlobalStructure VMMaker.oscog-eem.70 uuid: 36b63465-1b05-401f-bcb2-f9cae49422b8
    from
-	CoInterpreter VMMaker.oscog-eem.69 uuid: fd9c171e-3731-4093-912d-ad8fefb4800c
+	CoInterpreter VMMaker.oscog-eem.70 uuid: 36b63465-1b05-401f-bcb2-f9cae49422b8
  */
-static char __buildInfo[] = "CoInterpreter VMMaker.oscog-eem.69 uuid: fd9c171e-3731-4093-912d-ad8fefb4800c " __DATE__ ;
+static char __buildInfo[] = "CoInterpreter VMMaker.oscog-eem.70 uuid: 36b63465-1b05-401f-bcb2-f9cae49422b8 " __DATE__ ;
 char *__interpBuildInfo = __buildInfo;
 
 
@@ -203,7 +203,6 @@
 #define HeaderTypeShort 3
 #define HeaderTypeSizeAndClass 0
 #define IFrameSlots 7
-#define ImmutabilityBit 0x20000000
 #define InstanceSpecificationIndex 2
 #define InstructionPointerIndex 1
 #define LargeContextBit 0x40000
@@ -586,7 +585,6 @@
 sqInt isFloatObject(sqInt oop);
 static sqInt isFree(StackPage * self_in_isFree);
 static sqInt isFreeObject(sqInt oop);
-static sqInt isImmutableWhileForwarding(sqInt oop);
 sqInt isIndexable(sqInt oop);
 sqInt isInMemory(sqInt address);
 sqInt isIntegerObject(sqInt objectPointer);
@@ -684,10 +682,8 @@
 sqInt objectArg(sqInt index);
 sqInt objectBefore(sqInt address);
 sqInt objectExactlyBefore(sqInt oop);
-static sqInt objectIsImmutableAndReferencesForwarded(sqInt oop);
 sqInt objectIsOld(sqInt anObject);
 sqInt obsoleteDontUseThisFetchWordofObject(sqInt fieldIndex, sqInt oop);
-static sqInt okayFields(sqInt oop);
 static sqInt okayOop(sqInt signedOop);
 sqInt oopFromChunk(sqInt chunk);
 static sqInt oopHasAcceptableClass(sqInt signedOop);
@@ -1869,7 +1865,7 @@
 	/* 575 */ (void (*)(void))0,
  0 };
 static void (*externalPrimitiveTable[MaxExternalPrimitiveTableSize + 1 /* 4097 */])(void);
-const char *interpreterVersion = "Croquet Closure Cog VM [CoInterpreter VMMaker.oscog-eem.69]";
+const char *interpreterVersion = "Croquet Closure Cog VM [CoInterpreter VMMaker.oscog-eem.70]";
 sqInt minBackwardJumpCountForCompile = MinBackwardJumpCountForCompile /* 10 */;
 volatile int sendTrace;
 
@@ -18314,30 +18310,6 @@
 	return ((longAt(oop)) & TypeMask) == HeaderTypeFree;
 }
 
-
-/*	The given object may have its header word in a forwarding block. Find 
-	the value of the isImmutable flag in the object in spite of this obstacle. */
-
-static sqInt
-isImmutableWhileForwarding(sqInt oop)
-{
-    sqInt fwdBlock;
-    sqInt header;
-
-	header = longAt(oop);
-	if ((header & MarkBit) != 0) {
-
-		/* oop is forwarded; get its real header from its forwarding table entry */
-
-		fwdBlock = (header & AllButMarkBitAndTypeMask) << 1;
-		if (DoAssertionChecks) {
-			fwdBlockValidate(fwdBlock);
-		}
-		header = longAt(fwdBlock + BytesPerWord);
-	}
-	return (header & ImmutabilityBit) != 0;
-}
-
 sqInt
 isIndexable(sqInt oop)
 {
@@ -21928,86 +21900,6 @@
 	return 0;
 }
 
-
-/*	Answer if an object is immutable and references a forwarded object. Used
-	to fail become for immutable referents of becomees. */
-/*	Note: The given oop may be forwarded itself, which means that its real
-	header is in its forwarding table entry.
- */
-
-static sqInt
-objectIsImmutableAndReferencesForwarded(sqInt oop)
-{
-    sqInt contextSize;
-    sqInt fieldOffset;
-    sqInt fieldOop;
-    sqInt fmt;
-    sqInt fwdBlock;
-    sqInt header;
-    sqInt header1;
-    sqInt methodHeader;
-    sqInt size;
-    sqInt sp;
-
-	if (isImmutableWhileForwarding(oop)) {
-		/* begin lastPointerWhileForwarding: */
-		VM_LABEL(0lastPointerWhileForwarding);
-		/* begin headerWhileForwardingOf: */
-		header1 = longAt(oop);
-		if ((header1 & MarkBit) != 0) {
-
-			/* oop is forwarded; get its real header from its forwarding table entry */
-
-			fwdBlock = (header1 & AllButMarkBitAndTypeMask) << 1;
-			assert(fwdBlockValid(fwdBlock));
-			header1 = longAt(fwdBlock + BytesPerWord);
-		}
-		header = header1;
-		fmt = (((usqInt) header) >> 8) & 15;
-		if (fmt <= 4) {
-			if ((fmt == 3)
-			 && (((((usqInt) header) >> 12) & 31) == ClassMethodContextCompactIndex)) {
-				/* begin nacFetchStackPointerOf: */
-				sp = longAt((oop + BaseHeaderSize) + (StackPointerIndex << ShiftForWord));
-				if (!((sp & 1))) {
-					contextSize = 0;
-					goto l1;
-				}
-				contextSize = (sp >> 1);
-			l1:	/* end nacFetchStackPointerOf: */;
-				assert((ReceiverIndex + contextSize) < (lengthOfbaseHeaderformat(oop, header, fmt)));
-				fieldOffset = (CtxtTempFrameStart + contextSize) * BytesPerWord;
-				goto l2;
-			}
-			size = ((header & TypeMask) == HeaderTypeSizeAndClass
-				? (longAt(oop - (BytesPerWord * 2))) & AllButTypeMask
-				: header & SizeMask);
-			fieldOffset = size - BaseHeaderSize;
-			goto l2;
-		}
-		if (fmt < 12) {
-			fieldOffset = 0;
-			goto l2;
-		}
-		methodHeader = longAt(oop + BaseHeaderSize);
-		if (isCogMethodReference(methodHeader)) {
-			assert(((((CogMethod *) methodHeader)->cmType)) == CMMethod);
-			methodHeader = (((CogMethod *) methodHeader)->methodHeader);
-		}
-		fieldOffset = (((((usqInt) methodHeader) >> 10) & 255) * BytesPerWord) + BaseHeaderSize;
-	l2:	/* end lastPointerWhileForwarding: */;
-		while (fieldOffset >= BaseHeaderSize) {
-			fieldOop = longAt(oop + fieldOffset);
-			if (((fieldOop & 1) == 0)
-			 && (((longAt(fieldOop)) & MarkBit) != 0)) {
-				return 1;
-			}
-			fieldOffset -= BytesPerWord;
-		}
-	}
-	return 0;
-}
-
 sqInt
 objectIsOld(sqInt anObject)
 {
@@ -22031,61 +21923,6 @@
 }
 
 
-/*	Check if the argument is an ok object.
-	If this is a pointers object, check that its fields are all okay oops. */
-
-static sqInt
-okayFields(sqInt oop)
-{
-    sqInt fieldOop;
-    sqInt i;
-
-	if ((oop == null)
-	 || (oop == 0)) {
-		return 1;
-	}
-	if ((oop & 1)) {
-		return 1;
-	}
-	if (!(okayOop(oop))) {
-		return 0;
-	}
-	if (!(oopHasOkayClass(oop))) {
-		return 0;
-	}
-	if (!((((oop & 1) == 0)
- && (((((usqInt) (longAt(oop))) >> 8) & 15) <= 4))
-		 || (((((usqInt) (longAt(oop))) >> 8) & 15) >= 12))) {
-		return 1;
-	}
-	if (((((usqInt) (longAt(oop))) >> 8) & 15) >= 12) {
-		i = (literalCountOf(oop)) - 1;
-	}
-	else {
-		if (((oop & 1) == 0)
-		 && (((((usqInt) (longAt(oop))) >> 12) & 31) == ClassMethodContextCompactIndex)) {
-			i = (CtxtTempFrameStart + (fetchStackPointerOf(oop))) - 1;
-		}
-		else {
-			i = (lengthOf(oop)) - 1;
-		}
-	}
-	while (i >= 0) {
-		fieldOop = longAt((oop + BaseHeaderSize) + (i << ShiftForWord));
-		if (!((fieldOop & 1))) {
-			if (!(okayOop(fieldOop))) {
-				return 0;
-			}
-			if (!(oopHasOkayClass(fieldOop))) {
-				return 0;
-			}
-		}
-		i -= 1;
-	}
-	return 1;
-}
-
-
 /*	Verify that the given oop is legitimate. Check address, header, and size
 	but not class.
  */
@@ -43390,7 +43227,7 @@
 			/* begin remapFieldsAndClassOf: */
 			VM_LABEL(0remapFieldsAndClassOf);
 			/* begin lastPointerWhileForwarding: */
-			VM_LABEL(1lastPointerWhileForwarding);
+			VM_LABEL(0lastPointerWhileForwarding);
 			/* begin headerWhileForwardingOf: */
 			header11 = longAt(oop);
 			if ((header11 & MarkBit) != 0) {
@@ -43651,7 +43488,7 @@
 			/* begin remapFieldsAndClassOf: */
 			VM_LABEL(1remapFieldsAndClassOf);
 			/* begin lastPointerWhileForwarding: */
-			VM_LABEL(2lastPointerWhileForwarding);
+			VM_LABEL(1lastPointerWhileForwarding);
 			/* begin headerWhileForwardingOf: */
 			header11 = longAt(oop);
 			if ((header11 & MarkBit) != 0) {

Modified: branches/Cog/src/vm/cointerp.h
===================================================================
--- branches/Cog/src/vm/cointerp.h	2011-06-02 00:38:51 UTC (rev 2389)
+++ branches/Cog/src/vm/cointerp.h	2011-06-02 20:37:13 UTC (rev 2390)
@@ -1,5 +1,5 @@
 /* Automatically generated by
-	CCodeGeneratorGlobalStructure VMMaker.oscog-eem.69 uuid: fd9c171e-3731-4093-912d-ad8fefb4800c
+	CCodeGeneratorGlobalStructure VMMaker.oscog-eem.70 uuid: 36b63465-1b05-401f-bcb2-f9cae49422b8
  */
 
 

Modified: branches/Cog/src/vm/gcc3x-cointerp.c
===================================================================
--- branches/Cog/src/vm/gcc3x-cointerp.c	2011-06-02 00:38:51 UTC (rev 2389)
+++ branches/Cog/src/vm/gcc3x-cointerp.c	2011-06-02 20:37:13 UTC (rev 2390)
@@ -2,11 +2,11 @@
 
 
 /* Automatically generated by
-	CCodeGeneratorGlobalStructure VMMaker.oscog-eem.69 uuid: fd9c171e-3731-4093-912d-ad8fefb4800c
+	CCodeGeneratorGlobalStructure VMMaker.oscog-eem.70 uuid: 36b63465-1b05-401f-bcb2-f9cae49422b8
    from
-	CoInterpreter VMMaker.oscog-eem.69 uuid: fd9c171e-3731-4093-912d-ad8fefb4800c
+	CoInterpreter VMMaker.oscog-eem.70 uuid: 36b63465-1b05-401f-bcb2-f9cae49422b8
  */
-static char __buildInfo[] = "CoInterpreter VMMaker.oscog-eem.69 uuid: fd9c171e-3731-4093-912d-ad8fefb4800c " __DATE__ ;
+static char __buildInfo[] = "CoInterpreter VMMaker.oscog-eem.70 uuid: 36b63465-1b05-401f-bcb2-f9cae49422b8 " __DATE__ ;
 char *__interpBuildInfo = __buildInfo;
 
 
@@ -206,7 +206,6 @@
 #define HeaderTypeShort 3
 #define HeaderTypeSizeAndClass 0
 #define IFrameSlots 7
-#define ImmutabilityBit 0x20000000
 #define InstanceSpecificationIndex 2
 #define InstructionPointerIndex 1
 #define LargeContextBit 0x40000
@@ -589,7 +588,6 @@
 sqInt isFloatObject(sqInt oop);
 static sqInt isFree(StackPage * self_in_isFree);
 static sqInt isFreeObject(sqInt oop);
-static sqInt isImmutableWhileForwarding(sqInt oop);
 sqInt isIndexable(sqInt oop);
 sqInt isInMemory(sqInt address);
 sqInt isIntegerObject(sqInt objectPointer);
@@ -687,10 +685,8 @@
 sqInt objectArg(sqInt index);
 sqInt objectBefore(sqInt address);
 sqInt objectExactlyBefore(sqInt oop);
-static sqInt objectIsImmutableAndReferencesForwarded(sqInt oop);
 sqInt objectIsOld(sqInt anObject);
 sqInt obsoleteDontUseThisFetchWordofObject(sqInt fieldIndex, sqInt oop);
-static sqInt okayFields(sqInt oop);
 static sqInt okayOop(sqInt signedOop);
 sqInt oopFromChunk(sqInt chunk);
 static sqInt oopHasAcceptableClass(sqInt signedOop);
@@ -1872,7 +1868,7 @@
 	/* 575 */ (void (*)(void))0,
  0 };
 static void (*externalPrimitiveTable[MaxExternalPrimitiveTableSize + 1 /* 4097 */])(void);
-const char *interpreterVersion = "Croquet Closure Cog VM [CoInterpreter VMMaker.oscog-eem.69]";
+const char *interpreterVersion = "Croquet Closure Cog VM [CoInterpreter VMMaker.oscog-eem.70]";
 sqInt minBackwardJumpCountForCompile = MinBackwardJumpCountForCompile /* 10 */;
 volatile int sendTrace;
 
@@ -18318,30 +18314,6 @@
 	return ((longAt(oop)) & TypeMask) == HeaderTypeFree;
 }
 
-
-/*	The given object may have its header word in a forwarding block. Find 
-	the value of the isImmutable flag in the object in spite of this obstacle. */
-
-static sqInt
-isImmutableWhileForwarding(sqInt oop)
-{
-    sqInt fwdBlock;
-    sqInt header;
-
-	header = longAt(oop);
-	if ((header & MarkBit) != 0) {
-
-		/* oop is forwarded; get its real header from its forwarding table entry */
-
-		fwdBlock = (header & AllButMarkBitAndTypeMask) << 1;
-		if (DoAssertionChecks) {
-			fwdBlockValidate(fwdBlock);
-		}
-		header = longAt(fwdBlock + BytesPerWord);
-	}
-	return (header & ImmutabilityBit) != 0;
-}
-
 sqInt
 isIndexable(sqInt oop)
 {
@@ -21932,86 +21904,6 @@
 	return 0;
 }
 
-
-/*	Answer if an object is immutable and references a forwarded object. Used
-	to fail become for immutable referents of becomees. */
-/*	Note: The given oop may be forwarded itself, which means that its real
-	header is in its forwarding table entry.
- */
-
-static sqInt
-objectIsImmutableAndReferencesForwarded(sqInt oop)
-{
-    sqInt contextSize;
-    sqInt fieldOffset;
-    sqInt fieldOop;
-    sqInt fmt;
-    sqInt fwdBlock;
-    sqInt header;
-    sqInt header1;
-    sqInt methodHeader;
-    sqInt size;
-    sqInt sp;
-
-	if (isImmutableWhileForwarding(oop)) {
-		/* begin lastPointerWhileForwarding: */
-		VM_LABEL(0lastPointerWhileForwarding);
-		/* begin headerWhileForwardingOf: */
-		header1 = longAt(oop);
-		if ((header1 & MarkBit) != 0) {
-
-			/* oop is forwarded; get its real header from its forwarding table entry */
-
-			fwdBlock = (header1 & AllButMarkBitAndTypeMask) << 1;
-			assert(fwdBlockValid(fwdBlock));
-			header1 = longAt(fwdBlock + BytesPerWord);
-		}
-		header = header1;
-		fmt = (((usqInt) header) >> 8) & 15;
-		if (fmt <= 4) {
-			if ((fmt == 3)
-			 && (((((usqInt) header) >> 12) & 31) == ClassMethodContextCompactIndex)) {
-				/* begin nacFetchStackPointerOf: */
-				sp = longAt((oop + BaseHeaderSize) + (StackPointerIndex << ShiftForWord));
-				if (!((sp & 1))) {
-					contextSize = 0;
-					goto l1;
-				}
-				contextSize = (sp >> 1);
-			l1:	/* end nacFetchStackPointerOf: */;
-				assert((ReceiverIndex + contextSize) < (lengthOfbaseHeaderformat(oop, header, fmt)));
-				fieldOffset = (CtxtTempFrameStart + contextSize) * BytesPerWord;
-				goto l2;
-			}
-			size = ((header & TypeMask) == HeaderTypeSizeAndClass
-				? (longAt(oop - (BytesPerWord * 2))) & AllButTypeMask
-				: header & SizeMask);
-			fieldOffset = size - BaseHeaderSize;
-			goto l2;
-		}
-		if (fmt < 12) {
-			fieldOffset = 0;
-			goto l2;
-		}
-		methodHeader = longAt(oop + BaseHeaderSize);
-		if (isCogMethodReference(methodHeader)) {
-			assert(((((CogMethod *) methodHeader)->cmType)) == CMMethod);
-			methodHeader = (((CogMethod *) methodHeader)->methodHeader);
-		}
-		fieldOffset = (((((usqInt) methodHeader) >> 10) & 255) * BytesPerWord) + BaseHeaderSize;
-	l2:	/* end lastPointerWhileForwarding: */;
-		while (fieldOffset >= BaseHeaderSize) {
-			fieldOop = longAt(oop + fieldOffset);
-			if (((fieldOop & 1) == 0)
-			 && (((longAt(fieldOop)) & MarkBit) != 0)) {
-				return 1;
-			}
-			fieldOffset -= BytesPerWord;
-		}
-	}
-	return 0;
-}
-
 sqInt
 objectIsOld(sqInt anObject)
 {
@@ -22035,61 +21927,6 @@
 }
 
 
-/*	Check if the argument is an ok object.
-	If this is a pointers object, check that its fields are all okay oops. */
-
-static sqInt
-okayFields(sqInt oop)
-{
-    sqInt fieldOop;
-    sqInt i;
-
-	if ((oop == null)
-	 || (oop == 0)) {
-		return 1;
-	}
-	if ((oop & 1)) {
-		return 1;
-	}
-	if (!(okayOop(oop))) {
-		return 0;
-	}
-	if (!(oopHasOkayClass(oop))) {
-		return 0;
-	}
-	if (!((((oop & 1) == 0)
- && (((((usqInt) (longAt(oop))) >> 8) & 15) <= 4))
-		 || (((((usqInt) (longAt(oop))) >> 8) & 15) >= 12))) {
-		return 1;
-	}
-	if (((((usqInt) (longAt(oop))) >> 8) & 15) >= 12) {
-		i = (literalCountOf(oop)) - 1;
-	}
-	else {
-		if (((oop & 1) == 0)
-		 && (((((usqInt) (longAt(oop))) >> 12) & 31) == ClassMethodContextCompactIndex)) {
-			i = (CtxtTempFrameStart + (fetchStackPointerOf(oop))) - 1;
-		}
-		else {
-			i = (lengthOf(oop)) - 1;
-		}
-	}
-	while (i >= 0) {
-		fieldOop = longAt((oop + BaseHeaderSize) + (i << ShiftForWord));
-		if (!((fieldOop & 1))) {
-			if (!(okayOop(fieldOop))) {
-				return 0;
-			}
-			if (!(oopHasOkayClass(fieldOop))) {
-				return 0;
-			}
-		}
-		i -= 1;
-	}
-	return 1;
-}
-
-
 /*	Verify that the given oop is legitimate. Check address, header, and size
 	but not class.
  */
@@ -43394,7 +43231,7 @@
 			/* begin remapFieldsAndClassOf: */
 			VM_LABEL(0remapFieldsAndClassOf);
 			/* begin lastPointerWhileForwarding: */
-			VM_LABEL(1lastPointerWhileForwarding);
+			VM_LABEL(0lastPointerWhileForwarding);
 			/* begin headerWhileForwardingOf: */
 			header11 = longAt(oop);
 			if ((header11 & MarkBit) != 0) {
@@ -43655,7 +43492,7 @@
 			/* begin remapFieldsAndClassOf: */
 			VM_LABEL(1remapFieldsAndClassOf);
 			/* begin lastPointerWhileForwarding: */
-			VM_LABEL(2lastPointerWhileForwarding);
+			VM_LABEL(1lastPointerWhileForwarding);
 			/* begin headerWhileForwardingOf: */
 			header11 = longAt(oop);
 			if ((header11 & MarkBit) != 0) {

Modified: branches/Cog/src/vm/interp.h
===================================================================
--- branches/Cog/src/vm/interp.h	2011-06-02 00:38:51 UTC (rev 2389)
+++ branches/Cog/src/vm/interp.h	2011-06-02 20:37:13 UTC (rev 2390)
@@ -1,5 +1,5 @@
 /* Automatically generated by
-	CCodeGeneratorGlobalStructure VMMaker.oscog-eem.69 uuid: fd9c171e-3731-4093-912d-ad8fefb4800c
+	CCodeGeneratorGlobalStructure VMMaker.oscog-eem.70 uuid: 36b63465-1b05-401f-bcb2-f9cae49422b8
  */
 
 #define COGVM 1

Modified: branches/Cog/src/vm/vmCallback.h
===================================================================
--- branches/Cog/src/vm/vmCallback.h	2011-06-02 00:38:51 UTC (rev 2389)
+++ branches/Cog/src/vm/vmCallback.h	2011-06-02 20:37:13 UTC (rev 2390)
@@ -1,5 +1,5 @@
 /* Automatically generated by
-	CCodeGeneratorGlobalStructure VMMaker.oscog-eem.69 uuid: fd9c171e-3731-4093-912d-ad8fefb4800c
+	CCodeGeneratorGlobalStructure VMMaker.oscog-eem.70 uuid: 36b63465-1b05-401f-bcb2-f9cae49422b8
  */
 
 #define VM_CALLBACK_INC 1

Modified: branches/Cog/stacksrc/vm/gcc3x-interp.c
===================================================================
--- branches/Cog/stacksrc/vm/gcc3x-interp.c	2011-06-02 00:38:51 UTC (rev 2389)
+++ branches/Cog/stacksrc/vm/gcc3x-interp.c	2011-06-02 20:37:13 UTC (rev 2390)
@@ -2,11 +2,11 @@
 
 
 /* Automatically generated by
-	CCodeGeneratorGlobalStructure VMMaker.oscog-eem.69 uuid: fd9c171e-3731-4093-912d-ad8fefb4800c
+	CCodeGeneratorGlobalStructure VMMaker.oscog-eem.70 uuid: 36b63465-1b05-401f-bcb2-f9cae49422b8
    from
-	StackInterpreter VMMaker.oscog-eem.69 uuid: fd9c171e-3731-4093-912d-ad8fefb4800c
+	StackInterpreter VMMaker.oscog-eem.70 uuid: 36b63465-1b05-401f-bcb2-f9cae49422b8
  */
-static char __buildInfo[] = "StackInterpreter VMMaker.oscog-eem.69 uuid: fd9c171e-3731-4093-912d-ad8fefb4800c " __DATE__ ;
+static char __buildInfo[] = "StackInterpreter VMMaker.oscog-eem.70 uuid: 36b63465-1b05-401f-bcb2-f9cae49422b8 " __DATE__ ;
 char *__interpBuildInfo = __buildInfo;
 
 
@@ -174,7 +174,6 @@
 #define HeaderTypeGC 2
 #define HeaderTypeShort 3
 #define HeaderTypeSizeAndClass 0
-#define ImmutabilityBit 0x20000000
 #define InstanceSpecificationIndex 2
 #define InstructionPointerIndex 1
 #define LargeContextBit 0x40000
@@ -458,7 +457,6 @@
 sqInt isFloatObject(sqInt oop);
 static sqInt isFreeObject(sqInt oop);
 static sqInt isFree(StackPage *thePage);
-static sqInt isImmutableWhileForwarding(sqInt oop);
 sqInt isIndexable(sqInt oop);
 sqInt isInMemory(sqInt address);
 sqInt isIntegerObject(sqInt objectPointer);
@@ -531,9 +529,7 @@
 sqInt objectArg(sqInt index);
 sqInt objectBefore(sqInt address);
 sqInt objectExactlyBefore(sqInt oop);
-static sqInt objectIsImmutableAndReferencesForwarded(sqInt oop);
 sqInt obsoleteDontUseThisFetchWordofObject(sqInt fieldIndex, sqInt oop);
-static sqInt okayFields(sqInt oop);
 static sqInt okayOop(sqInt signedOop);
 sqInt oopFromChunk(sqInt chunk);
 static sqInt oopHasAcceptableClass(sqInt signedOop);
@@ -1657,7 +1653,7 @@
  0 };
 char * breakSelector;
 sqInt breakSelectorLength = -1;
-const char *interpreterVersion = "Croquet Closure Stack VM [StackInterpreter VMMaker.oscog-eem.69]";
+const char *interpreterVersion = "Croquet Closure Stack VM [StackInterpreter VMMaker.oscog-eem.70]";
 volatile int sendTrace;
 sqInt suppressHeartbeatFlag;
 
@@ -14421,30 +14417,6 @@
 	return ((thePage->baseFP)) == 0;
 }
 
-
-/*	The given object may have its header word in a forwarding block. Find 
-	the value of the isImmutable flag in the object in spite of this obstacle. */
-
-static sqInt
-isImmutableWhileForwarding(sqInt oop)
-{
-    sqInt fwdBlock;
-    sqInt header;
-
-	header = longAt(oop);
-	if ((header & MarkBit) != 0) {
-
-		/* oop is forwarded; get its real header from its forwarding table entry */
-
-		fwdBlock = (header & AllButMarkBitAndTypeMask) << 1;
-		if (DoAssertionChecks) {
-			fwdBlockValidate(fwdBlock);
-		}
-		header = longAt(fwdBlock + BytesPerWord);
-	}
-	return (header & ImmutabilityBit) != 0;
-}
-
 sqInt
 isIndexable(sqInt oop)
 {
@@ -17259,80 +17231,6 @@
 }
 
 
-/*	Answer if an object is immutable and references a forwarded object. Used
-	to fail become for immutable referents of becomees. */
-/*	Note: The given oop may be forwarded itself, which means that its real
-	header is in its forwarding table entry.
- */
-
-static sqInt
-objectIsImmutableAndReferencesForwarded(sqInt oop)
-{   DECL_MAYBE_SQ_GLOBAL_STRUCT
-    sqInt contextSize;
-    sqInt fieldOffset;
-    sqInt fieldOop;
-    sqInt fmt;
-    sqInt fwdBlock;
-    sqInt header;
-    sqInt header1;
-    sqInt size;
-    sqInt sp;
-
-	if (isImmutableWhileForwarding(oop)) {
-		/* begin lastPointerWhileForwarding: */
-		VM_LABEL(0lastPointerWhileForwarding);
-		/* begin headerWhileForwardingOf: */
-		header1 = longAt(oop);
-		if ((header1 & MarkBit) != 0) {
-
-			/* oop is forwarded; get its real header from its forwarding table entry */
-
-			fwdBlock = (header1 & AllButMarkBitAndTypeMask) << 1;
-			assert(fwdBlockValid(fwdBlock));
-			header1 = longAt(fwdBlock + BytesPerWord);
-		}
-		header = header1;
-		fmt = (((usqInt) header) >> 8) & 15;
-		if (fmt <= 4) {
-			if ((fmt == 3)
-			 && (((((usqInt) header) >> 12) & 31) == ClassMethodContextCompactIndex)) {
-				/* begin nacFetchStackPointerOf: */
-				sp = longAt((oop + BaseHeaderSize) + (StackPointerIndex << ShiftForWord));
-				if (!((sp & 1))) {
-					contextSize = 0;
-					goto l1;
-				}
-				contextSize = (sp >> 1);
-			l1:	/* end nacFetchStackPointerOf: */;
-				assert((ReceiverIndex + contextSize) < (lengthOfbaseHeaderformat(oop, header, fmt)));
-				fieldOffset = (CtxtTempFrameStart + contextSize) * BytesPerWord;
-				goto l2;
-			}
-			size = ((header & TypeMask) == HeaderTypeSizeAndClass
-				? (longAt(oop - (BytesPerWord * 2))) & AllButTypeMask
-				: header & SizeMask);
-			fieldOffset = size - BaseHeaderSize;
-			goto l2;
-		}
-		if (fmt < 12) {
-			fieldOffset = 0;
-			goto l2;
-		}
-		fieldOffset = (((((usqInt) (longAt((oop + BaseHeaderSize) + (HeaderIndex << ShiftForWord)))) >> 10) & 255) * BytesPerWord) + BaseHeaderSize;
-	l2:	/* end lastPointerWhileForwarding: */;
-		while (fieldOffset >= BaseHeaderSize) {
-			fieldOop = longAt(oop + fieldOffset);
-			if (((fieldOop & 1) == 0)
-			 && (((longAt(fieldOop)) & MarkBit) != 0)) {
-				return 1;
-			}
-			fieldOffset -= BytesPerWord;
-		}
-	}
-	return 0;
-}
-
-
 /*	This message is deprecated but supported for a while via a tweak to
 	sqVirtualMachine.[ch] Use fetchLong32, fetchLong64 or fetchPointer instead
 	for new code
@@ -17345,61 +17243,6 @@
 }
 
 
-/*	Check if the argument is an ok object.
-	If this is a pointers object, check that its fields are all okay oops. */
-
-static sqInt
-okayFields(sqInt oop)
-{   DECL_MAYBE_SQ_GLOBAL_STRUCT
-    sqInt fieldOop;
-    sqInt i;
-
-	if ((oop == null)
-	 || (oop == 0)) {
-		return 1;
-	}
-	if ((oop & 1)) {
-		return 1;
-	}
-	if (!(okayOop(oop))) {
-		return 0;
-	}
-	if (!(oopHasOkayClass(oop))) {
-		return 0;
-	}
-	if (!((((oop & 1) == 0)
- && (((((usqInt) (longAt(oop))) >> 8) & 15) <= 4))
-		 || (((((usqInt) (longAt(oop))) >> 8) & 15) >= 12))) {
-		return 1;
-	}
-	if (((((usqInt) (longAt(oop))) >> 8) & 15) >= 12) {
-		i = ((((usqInt) (longAt((oop + BaseHeaderSize) + (HeaderIndex << ShiftForWord)))) >> 10) & 255) - 1;
-	}
-	else {
-		if (((oop & 1) == 0)
-		 && (((((usqInt) (longAt(oop))) >> 12) & 31) == ClassMethodContextCompactIndex)) {
-			i = (CtxtTempFrameStart + (fetchStackPointerOf(oop))) - 1;
-		}
-		else {
-			i = (lengthOf(oop)) - 1;
-		}
-	}
-	while (i >= 0) {
-		fieldOop = longAt((oop + BaseHeaderSize) + (i << ShiftForWord));
-		if (!((fieldOop & 1))) {
-			if (!(okayOop(fieldOop))) {
-				return 0;
-			}
-			if (!(oopHasOkayClass(fieldOop))) {
-				return 0;
-			}
-		}
-		i -= 1;
-	}
-	return 1;
-}
-
-
 /*	Verify that the given oop is legitimate. Check address, header, and size
 	but not class.
  */
@@ -37328,7 +37171,7 @@
 			/* begin remapFieldsAndClassOf: */
 			VM_LABEL(0remapFieldsAndClassOf);
 			/* begin lastPointerWhileForwarding: */
-			VM_LABEL(1lastPointerWhileForwarding);
+			VM_LABEL(0lastPointerWhileForwarding);
 			/* begin headerWhileForwardingOf: */
 			header12 = longAt(oop);
 			if ((header12 & MarkBit) != 0) {
@@ -37583,7 +37426,7 @@
 			/* begin remapFieldsAndClassOf: */
 			VM_LABEL(1remapFieldsAndClassOf);
 			/* begin lastPointerWhileForwarding: */
-			VM_LABEL(2lastPointerWhileForwarding);
+			VM_LABEL(1lastPointerWhileForwarding);
 			/* begin headerWhileForwardingOf: */
 			header12 = longAt(oop);
 			if ((header12 & MarkBit) != 0) {

Modified: branches/Cog/stacksrc/vm/interp.c
===================================================================
--- branches/Cog/stacksrc/vm/interp.c	2011-06-02 00:38:51 UTC (rev 2389)
+++ branches/Cog/stacksrc/vm/interp.c	2011-06-02 20:37:13 UTC (rev 2390)
@@ -1,9 +1,9 @@
 /* Automatically generated by
-	CCodeGeneratorGlobalStructure VMMaker.oscog-eem.69 uuid: fd9c171e-3731-4093-912d-ad8fefb4800c
+	CCodeGeneratorGlobalStructure VMMaker.oscog-eem.70 uuid: 36b63465-1b05-401f-bcb2-f9cae49422b8
    from
-	StackInterpreter VMMaker.oscog-eem.69 uuid: fd9c171e-3731-4093-912d-ad8fefb4800c
+	StackInterpreter VMMaker.oscog-eem.70 uuid: 36b63465-1b05-401f-bcb2-f9cae49422b8
  */
-static char __buildInfo[] = "StackInterpreter VMMaker.oscog-eem.69 uuid: fd9c171e-3731-4093-912d-ad8fefb4800c " __DATE__ ;
+static char __buildInfo[] = "StackInterpreter VMMaker.oscog-eem.70 uuid: 36b63465-1b05-401f-bcb2-f9cae49422b8 " __DATE__ ;
 char *__interpBuildInfo = __buildInfo;
 
 
@@ -171,7 +171,6 @@
 #define HeaderTypeGC 2
 #define HeaderTypeShort 3
 #define HeaderTypeSizeAndClass 0
-#define ImmutabilityBit 0x20000000
 #define InstanceSpecificationIndex 2
 #define InstructionPointerIndex 1
 #define LargeContextBit 0x40000
@@ -455,7 +454,6 @@
 sqInt isFloatObject(sqInt oop);
 static sqInt isFreeObject(sqInt oop);
 static sqInt isFree(StackPage *thePage);
-static sqInt isImmutableWhileForwarding(sqInt oop);
 sqInt isIndexable(sqInt oop);
 sqInt isInMemory(sqInt address);
 sqInt isIntegerObject(sqInt objectPointer);
@@ -528,9 +526,7 @@
 sqInt objectArg(sqInt index);
 sqInt objectBefore(sqInt address);
 sqInt objectExactlyBefore(sqInt oop);
-static sqInt objectIsImmutableAndReferencesForwarded(sqInt oop);
 sqInt obsoleteDontUseThisFetchWordofObject(sqInt fieldIndex, sqInt oop);
-static sqInt okayFields(sqInt oop);
 static sqInt okayOop(sqInt signedOop);
 sqInt oopFromChunk(sqInt chunk);
 static sqInt oopHasAcceptableClass(sqInt signedOop);
@@ -1654,7 +1650,7 @@
  0 };
 char * breakSelector;
 sqInt breakSelectorLength = -1;
-const char *interpreterVersion = "Croquet Closure Stack VM [StackInterpreter VMMaker.oscog-eem.69]";
+const char *interpreterVersion = "Croquet Closure Stack VM [StackInterpreter VMMaker.oscog-eem.70]";
 volatile int sendTrace;
 sqInt suppressHeartbeatFlag;
 
@@ -14417,30 +14413,6 @@
 	return ((thePage->baseFP)) == 0;
 }
 
-
-/*	The given object may have its header word in a forwarding block. Find 
-	the value of the isImmutable flag in the object in spite of this obstacle. */
-
-static sqInt
-isImmutableWhileForwarding(sqInt oop)
-{
-    sqInt fwdBlock;
-    sqInt header;
-
-	header = longAt(oop);
-	if ((header & MarkBit) != 0) {
-
-		/* oop is forwarded; get its real header from its forwarding table entry */
-
-		fwdBlock = (header & AllButMarkBitAndTypeMask) << 1;
-		if (DoAssertionChecks) {
-			fwdBlockValidate(fwdBlock);
-		}
-		header = longAt(fwdBlock + BytesPerWord);
-	}
-	return (header & ImmutabilityBit) != 0;
-}
-
 sqInt
 isIndexable(sqInt oop)
 {
@@ -17255,80 +17227,6 @@
 }
 
 
-/*	Answer if an object is immutable and references a forwarded object. Used
-	to fail become for immutable referents of becomees. */
-/*	Note: The given oop may be forwarded itself, which means that its real
-	header is in its forwarding table entry.
- */
-
-static sqInt
-objectIsImmutableAndReferencesForwarded(sqInt oop)
-{   DECL_MAYBE_SQ_GLOBAL_STRUCT
-    sqInt contextSize;
-    sqInt fieldOffset;
-    sqInt fieldOop;
-    sqInt fmt;
-    sqInt fwdBlock;
-    sqInt header;
-    sqInt header1;
-    sqInt size;
-    sqInt sp;
-
-	if (isImmutableWhileForwarding(oop)) {
-		/* begin lastPointerWhileForwarding: */
-		VM_LABEL(0lastPointerWhileForwarding);
-		/* begin headerWhileForwardingOf: */
-		header1 = longAt(oop);
-		if ((header1 & MarkBit) != 0) {
-
-			/* oop is forwarded; get its real header from its forwarding table entry */
-
-			fwdBlock = (header1 & AllButMarkBitAndTypeMask) << 1;
-			assert(fwdBlockValid(fwdBlock));
-			header1 = longAt(fwdBlock + BytesPerWord);
-		}
-		header = header1;
-		fmt = (((usqInt) header) >> 8) & 15;
-		if (fmt <= 4) {
-			if ((fmt == 3)
-			 && (((((usqInt) header) >> 12) & 31) == ClassMethodContextCompactIndex)) {
-				/* begin nacFetchStackPointerOf: */
-				sp = longAt((oop + BaseHeaderSize) + (StackPointerIndex << ShiftForWord));
-				if (!((sp & 1))) {
-					contextSize = 0;
-					goto l1;
-				}
-				contextSize = (sp >> 1);
-			l1:	/* end nacFetchStackPointerOf: */;
-				assert((ReceiverIndex + contextSize) < (lengthOfbaseHeaderformat(oop, header, fmt)));
-				fieldOffset = (CtxtTempFrameStart + contextSize) * BytesPerWord;
-				goto l2;
-			}
-			size = ((header & TypeMask) == HeaderTypeSizeAndClass
-				? (longAt(oop - (BytesPerWord * 2))) & AllButTypeMask
-				: header & SizeMask);
-			fieldOffset = size - BaseHeaderSize;
-			goto l2;
-		}
-		if (fmt < 12) {
-			fieldOffset = 0;
-			goto l2;
-		}
-		fieldOffset = (((((usqInt) (longAt((oop + BaseHeaderSize) + (HeaderIndex << ShiftForWord)))) >> 10) & 255) * BytesPerWord) + BaseHeaderSize;
-	l2:	/* end lastPointerWhileForwarding: */;
-		while (fieldOffset >= BaseHeaderSize) {
-			fieldOop = longAt(oop + fieldOffset);
-			if (((fieldOop & 1) == 0)
-			 && (((longAt(fieldOop)) & MarkBit) != 0)) {
-				return 1;
-			}
-			fieldOffset -= BytesPerWord;
-		}
-	}
-	return 0;
-}
-
-
 /*	This message is deprecated but supported for a while via a tweak to
 	sqVirtualMachine.[ch] Use fetchLong32, fetchLong64 or fetchPointer instead
 	for new code
@@ -17341,61 +17239,6 @@
 }
 
 
-/*	Check if the argument is an ok object.
-	If this is a pointers object, check that its fields are all okay oops. */
-
-static sqInt
-okayFields(sqInt oop)
-{   DECL_MAYBE_SQ_GLOBAL_STRUCT
-    sqInt fieldOop;
-    sqInt i;
-
-	if ((oop == null)
-	 || (oop == 0)) {
-		return 1;
-	}
-	if ((oop & 1)) {
-		return 1;
-	}
-	if (!(okayOop(oop))) {
-		return 0;
-	}
-	if (!(oopHasOkayClass(oop))) {
-		return 0;
-	}
-	if (!((((oop & 1) == 0)
- && (((((usqInt) (longAt(oop))) >> 8) & 15) <= 4))
-		 || (((((usqInt) (longAt(oop))) >> 8) & 15) >= 12))) {
-		return 1;
-	}
-	if (((((usqInt) (longAt(oop))) >> 8) & 15) >= 12) {
-		i = ((((usqInt) (longAt((oop + BaseHeaderSize) + (HeaderIndex << ShiftForWord)))) >> 10) & 255) - 1;
-	}
-	else {
-		if (((oop & 1) == 0)
-		 && (((((usqInt) (longAt(oop))) >> 12) & 31) == ClassMethodContextCompactIndex)) {
-			i = (CtxtTempFrameStart + (fetchStackPointerOf(oop))) - 1;
-		}
-		else {
-			i = (lengthOf(oop)) - 1;
-		}
-	}
-	while (i >= 0) {
-		fieldOop = longAt((oop + BaseHeaderSize) + (i << ShiftForWord));
-		if (!((fieldOop & 1))) {
-			if (!(okayOop(fieldOop))) {
-				return 0;
-			}
-			if (!(oopHasOkayClass(fieldOop))) {
-				return 0;
-			}
-		}
-		i -= 1;
-	}
-	return 1;
-}
-
-
 /*	Verify that the given oop is legitimate. Check address, header, and size
 	but not class.
  */
@@ -37324,7 +37167,7 @@
 			/* begin remapFieldsAndClassOf: */
 			VM_LABEL(0remapFieldsAndClassOf);
 			/* begin lastPointerWhileForwarding: */
-			VM_LABEL(1lastPointerWhileForwarding);
+			VM_LABEL(0lastPointerWhileForwarding);
 			/* begin headerWhileForwardingOf: */
 			header12 = longAt(oop);
 			if ((header12 & MarkBit) != 0) {
@@ -37579,7 +37422,7 @@
 			/* begin remapFieldsAndClassOf: */
 			VM_LABEL(1remapFieldsAndClassOf);
 			/* begin lastPointerWhileForwarding: */
-			VM_LABEL(2lastPointerWhileForwarding);
+			VM_LABEL(1lastPointerWhileForwarding);
 			/* begin headerWhileForwardingOf: */
 			header12 = longAt(oop);
 			if ((header12 & MarkBit) != 0) {

Modified: branches/Cog/stacksrc/vm/interp.h
===================================================================
--- branches/Cog/stacksrc/vm/interp.h	2011-06-02 00:38:51 UTC (rev 2389)
+++ branches/Cog/stacksrc/vm/interp.h	2011-06-02 20:37:13 UTC (rev 2390)
@@ -1,5 +1,5 @@
 /* Automatically generated by
-	CCodeGeneratorGlobalStructure VMMaker.oscog-eem.69 uuid: fd9c171e-3731-4093-912d-ad8fefb4800c
+	CCodeGeneratorGlobalStructure VMMaker.oscog-eem.70 uuid: 36b63465-1b05-401f-bcb2-f9cae49422b8
  */
 
 #define STACKVM 1

Modified: branches/Cog/stacksrc/vm/vmCallback.h
===================================================================
--- branches/Cog/stacksrc/vm/vmCallback.h	2011-06-02 00:38:51 UTC (rev 2389)
+++ branches/Cog/stacksrc/vm/vmCallback.h	2011-06-02 20:37:13 UTC (rev 2390)
@@ -1,5 +1,5 @@
 /* Automatically generated by
-	CCodeGeneratorGlobalStructure VMMaker.oscog-eem.69 uuid: fd9c171e-3731-4093-912d-ad8fefb4800c
+	CCodeGeneratorGlobalStructure VMMaker.oscog-eem.70 uuid: 36b63465-1b05-401f-bcb2-f9cae49422b8
  */
 
 #define VM_CALLBACK_INC 1



More information about the Vm-dev mailing list