[commit] r2341 - OSCogVM StackToRegisterMappingCogit as per VMMaker-oscog.43.

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

[commit] r2341 - OSCogVM StackToRegisterMappingCogit as per VMMaker-oscog.43.

commits-3
 
Author: eliot
Date: 2011-01-02 14:44:59 -0800 (Sun, 02 Jan 2011)
New Revision: 2341

Modified:
   branches/Cog/image/VMMaker-Squeak4.1.changes
   branches/Cog/image/VMMaker-Squeak4.1.image
   branches/Cog/platforms/Cross/vm/sq.h
   branches/Cog/platforms/unix/config/make.cfg.in
   branches/Cog/platforms/unix/vm/Makefile.in
   branches/Cog/src/vm/cogit.c
   branches/Cog/src/vm/cogit.h
   branches/Cog/src/vm/cogmethod.h
   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
Log:
OSCogVM StackToRegisterMappingCogit as per VMMaker-oscog.43.
Eliminate some warnings in the CoInterpreter.
Stop attemptToSwitchToMachineCode: being inlined to fix apparent
optimization bug at -O2 on linux gcc 4.1.2.

Lower the cointerpreter's optimization level to -O1 on linux to avoid apparent
flakiness with the gcc 4.1.2 compiler at -O2.
Fix INSTALL_SCRIPT usage on linux.


Modified: branches/Cog/image/VMMaker-Squeak4.1.changes
===================================================================
--- branches/Cog/image/VMMaker-Squeak4.1.changes 2011-01-01 22:51:31 UTC (rev 2340)
+++ branches/Cog/image/VMMaker-Squeak4.1.changes 2011-01-02 22:44:59 UTC (rev 2341)
@@ -151607,4 +151607,309 @@
  password: pw ].
 user = 'anon' ifTrue: [MCFileBasedRepository flushAllCaches]!
 
-----QUIT----{1 January 2011 . 2:37:30 pm} VMMaker-Squeak4.1.image priorSource: 6105162!
\ No newline at end of file
+----QUIT----{1 January 2011 . 2:37:30 pm} VMMaker-Squeak4.1.image priorSource: 6105162!
+
+----STARTUP----{2 January 2011 . 1:49:57 pm} as /Users/eliot/Cog/oscog/Cog.squeakvm.org/image/VMMaker-Squeak4.1.image!
+
+
+'From Squeak4.1 of 17 April 2010 [latest update: #9957] on 2 January 2011 at 1:49:11 pm'!
+!CoInterpreter methodsFor: 'jump bytecodes' stamp: 'eem 1/2/2011 13:47' prior: 34693658!
+attemptToSwitchToMachineCode: bcpc
+ | cogMethod pc |
+ <inline: #false>
+ <var: #cogMethod type: #'CogMethod *'>
+ (self methodHasCogMethod: method) ifFalse:
+ [cogit cog: method selector: objectMemory nilObject].
+ (self methodHasCogMethod: method) ifTrue:
+ [cogMethod := self cogMethodOf: method.
+ pc := self convertToMachineCodeFrame: cogMethod bcpc: bcpc.
+ self assertValidMachineCodeFrame: pc.
+ self push: pc.
+ self push: objectMemory nilObject.
+ cogit ceEnterCogCodePopReceiverReg]! !
+!CoInterpreter methodsFor: 'frame access' stamp: 'eem 1/2/2011 13:39' prior: 34548261!
+convertToMachineCodeFrame: cogHomeMethod bcpc: bcpc
+ <var: #cogHomeMethod type: #'CogHomeMethod *'>
+ "Convert the current interpreter frame into a machine code frame
+ and answer the machine code pc matching bcpc."
+ | startBcpc methodField closure cogMethod pc |
+ <var: #cogMethod type: #'CogBlockMethod *'>
+ <var: #p type: #'char *'>
+ self assert: (self isMachineCodeFrame: framePointer) not.
+ "Update the return pc, perhaps saving it in the caller's iframeSavedIP."
+ (self isBaseFrame: framePointer)
+ ifTrue:
+ [stackPages
+ longAt: framePointer + FoxCallerSavedIP
+ put: cogit ceBaseFrameReturnPC]
+ ifFalse:
+ [(self isMachineCodeFrame: (self frameCallerFP: framePointer)) ifFalse:
+ [self iframeSavedIP: (self frameCallerFP: framePointer)
+ put: (self frameCallerSavedIP: framePointer).
+ stackPages
+ longAt: framePointer + FoxCallerSavedIP
+ put: cogit ceReturnToInterpreterPC]].
+ "Set the cog method field"
+ (self iframeIsBlockActivation: framePointer)
+ ifTrue:
+ [closure := self pushedReceiverOrClosureOfFrame: framePointer.
+ startBcpc := self startPCOfClosure: closure.
+ cogMethod := cogit
+ findMethodForStartBcpc: startBcpc
+ inHomeMethod: cogHomeMethod.
+ methodField := cogMethod asInteger + MFMethodFlagIsBlockFlag]
+ ifFalse:
+ [startBcpc := self startPCOfMethodHeader: cogHomeMethod methodHeader.
+ cogMethod := self cCoerceSimple: cogHomeMethod to: #'CogBlockMethod *'.
+ methodField := cogHomeMethod asInteger].
+ stackPages
+ longAt: framePointer + FoxMethod
+ put: methodField
+ + ((self iframeHasContext: framePointer)
+ ifTrue: [MFMethodFlagHasContextFlag]
+ ifFalse: [0]).
+ framePointer + FoxIFReceiver to: stackPointer by: BytesPerWord negated do:
+ [:p|
+ stackPages longAt: p + FoxMFReceiver - FoxIFReceiver put: (stackPages longAt: p)].
+ stackPointer := stackPointer + FoxMFReceiver - FoxIFReceiver.
+ pc := cogit mcPCFor: bcpc startBcpc: startBcpc in: cogMethod.
+ self assert: pc > cogit noCheckEntryOffset.
+ ^cogMethod asInteger + pc! !
+!CoInterpreter methodsFor: 'jump bytecodes' stamp: 'eem 1/2/2011 13:46' prior: 34694242!
+longUnconditionalJump
+ | offset switched |
+ offset := (((currentBytecode bitAnd: 7) - 4) * 256) + self fetchByte.
+ localIP := localIP + offset.
+ offset < 0 ifTrue: "backward jump means we're in a loop; check for possible interrupts"
+ [localSP < stackLimit ifTrue:
+ [self externalizeIPandSP.
+ switched := self checkForEventsMayContextSwitch: true.
+ self returnToExecutive: true postContextSwitch: switched.
+ self browserPluginReturnIfNeeded.
+ self internalizeIPandSP].
+ method = lastBackwardJumpMethod
+ ifTrue:
+ [(backwardJumpCount := backwardJumpCount - 1) <= 0 ifTrue:
+ [(self methodWithHeaderShouldBeCogged: (self headerOf: method))
+ ifTrue:
+ [self externalizeFPandSP.
+ self attemptToSwitchToMachineCode: localIP - offset - method - BaseHeaderSize + 1]
+ ifFalse: "don't ask if one should compile a second time..."
+ [backwardJumpCount := 1 bitShift: BytesPerWord * 8 - 2]]]
+ ifFalse:
+ [lastBackwardJumpMethod := method.
+ backwardJumpCount := minBackwardJumpCountForCompile]].
+ self fetchNextBytecode! !
+!StackToRegisterMappingCogit methodsFor: 'bytecode generators' stamp: 'eem 1/1/2011 21:05' prior: 38846291!
+genSpecialSelectorArithmetic
+ | primDescriptor rcvrIsConst argIsConst rcvrIsInt argIsInt rcvrInt argInt result jumpNotSmallInts jumpContinue |
+ <var: #primDescriptor type: #'BytecodeDescriptor *'>
+ <var: #jumpNotSmallInts type: #'AbstractInstruction *'>
+ <var: #jumpOverflow type: #'AbstractInstruction *'>
+ <var: #jumpContinue type: #'AbstractInstruction *'>
+ primDescriptor := self generatorAt: byte0.
+ argIsInt := (argIsConst := self ssTop type = SSConstant)
+ and: [objectMemory isIntegerObject: (argInt := self ssTop constant)].
+ rcvrIsInt := (rcvrIsConst := (self ssValue: 1) type = SSConstant)
+ and: [objectMemory isIntegerObject: (rcvrInt := (self ssValue: 1) constant)].
+
+ (argIsInt and: [rcvrIsInt]) ifTrue:
+ [rcvrInt := objectMemory integerValueOf: rcvrInt.
+ argInt := objectMemory integerValueOf: argInt.
+ primDescriptor opcode caseOf: {
+ [AddRR] -> [result := rcvrInt + argInt].
+ [SubRR] -> [result := rcvrInt - argInt].
+ [AndRR] -> [result := rcvrInt & argInt].
+ [OrRR] -> [result := rcvrInt | argInt] }.
+ (objectMemory isIntegerValue: result) ifTrue:
+ ["Must annotate the bytecode for correct pc mapping."
+ self annotateBytecode: self Label.
+ ^self ssPop: 2; ssPushConstant: (objectMemory integerObjectOf: result)].
+ ^self genSpecialSelectorSend].
+
+ "If there's any constant involved other than a SmallInteger don't attempt to inline."
+ ((rcvrIsConst and: [rcvrIsInt not])
+ or: [argIsConst and: [argIsInt not]]) ifTrue:
+ [^self genSpecialSelectorSend].
+
+ "If we know nothing about the types then better not to inline as the inline cache and
+ primitive code is not terribly slow so wasting time on duplicating tag tests is pointless."
+ (argIsInt or: [rcvrIsInt]) ifFalse:
+ [^self genSpecialSelectorSend].
+
+ argIsInt
+ ifTrue:
+ [self ssFlushTo: simStackPtr - 2.
+ (self ssValue: 1) popToReg: ReceiverResultReg.
+ self ssPop: 2.
+ self MoveR: ReceiverResultReg R: TempReg]
+ ifFalse:
+ [self marshallSendArguments: 1.
+ self MoveR: Arg0Reg R: TempReg.
+ rcvrIsInt ifFalse:
+ [objectRepresentation isSmallIntegerTagNonZero
+ ifTrue: [self AndR: ReceiverResultReg R: TempReg]
+ ifFalse: [self OrR: ReceiverResultReg R: TempReg]]].
+ jumpNotSmallInts := objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg.
+ primDescriptor opcode caseOf: {
+ [AddRR] -> [argIsInt
+ ifTrue:
+ [self AddCq: argInt - ConstZero R: ReceiverResultReg.
+ jumpContinue := self JumpNoOverflow: 0.
+ "overflow; must undo the damage before continuing"
+ self SubCq: argInt - ConstZero R: ReceiverResultReg]
+ ifFalse:
+ [objectRepresentation genRemoveSmallIntegerTagsInScratchReg: ReceiverResultReg.
+ self AddR: Arg0Reg R: ReceiverResultReg.
+ jumpContinue := self JumpNoOverflow: 0.
+ "overflow; must undo the damage before continuing"
+ rcvrIsInt
+ ifTrue: [self MoveCq: rcvrInt R: ReceiverResultReg]
+ ifFalse:
+ [self SubR: Arg0Reg R: ReceiverResultReg.
+ objectRepresentation genSetSmallIntegerTagsIn: ReceiverResultReg]]].
+ [SubRR] -> [argIsInt
+ ifTrue:
+ [self SubCq: argInt - ConstZero R: ReceiverResultReg.
+ jumpContinue := self JumpNoOverflow: 0.
+ "overflow; must undo the damage before continuing"
+ self AddCq: argInt - ConstZero R: ReceiverResultReg]
+ ifFalse:
+ [objectRepresentation genRemoveSmallIntegerTagsInScratchReg: Arg0Reg.
+ self SubR: Arg0Reg R: ReceiverResultReg.
+ jumpContinue := self JumpNoOverflow: 0.
+ "overflow; must undo the damage before continuing"
+ self AddR: Arg0Reg R: ReceiverResultReg.
+ objectRepresentation genSetSmallIntegerTagsIn: Arg0Reg]].
+ [AndRR] -> [argIsInt
+ ifTrue: [self AndCq: argInt R: ReceiverResultReg]
+ ifFalse: [self AndR: Arg0Reg R: ReceiverResultReg].
+ jumpContinue := self Jump: 0].
+ [OrRR] -> [argIsInt
+ ifTrue: [self OrCq: argInt R: ReceiverResultReg]
+ ifFalse: [self OrR: Arg0Reg R: ReceiverResultReg].
+ jumpContinue := self Jump: 0] }.
+ jumpNotSmallInts jmpTarget: self Label.
+ argIsInt ifTrue:
+ [self MoveCq: argInt R: Arg0Reg].
+ self genMarshalledSend: (coInterpreter specialSelector: byte0 - 176) numArgs: 1.
+ jumpContinue jmpTarget: self Label.
+ ^0! !
+
+----End fileIn of /Users/eliot/Cog/methods.st----!
+
+----QUIT----{2 January 2011 . 1:50:54 pm} VMMaker-Squeak4.1.image priorSource: 6107741!
+
+----STARTUP----{2 January 2011 . 2:05:08 pm} as /Users/eliot/Cog/oscog/Cog.squeakvm.org/image/VMMaker-Squeak4.1.image!
+
+!CoInterpreter methodsFor: 'jump bytecodes' stamp: 'eem 1/2/2011 13:55' prior: 39665257!
+longUnconditionalJump
+ | offset switched |
+ offset := (((currentBytecode bitAnd: 7) - 4) * 256) + self fetchByte.
+ localIP := localIP + offset.
+ offset < 0 ifTrue: "backward jump means we're in a loop; check for possible interrupts"
+ [localSP < stackLimit ifTrue:
+ [self externalizeIPandSP.
+ switched := self checkForEventsMayContextSwitch: true.
+ self returnToExecutive: true postContextSwitch: switched.
+ self browserPluginReturnIfNeeded.
+ self internalizeIPandSP].
+ method = lastBackwardJumpMethod
+ ifTrue:
+ [(backwardJumpCount := backwardJumpCount - 1) <= 0 ifTrue:
+ [(self methodWithHeaderShouldBeCogged: (self headerOf: method))
+ ifTrue:
+ [self externalizeFPandSP.
+ self attemptToSwitchToMachineCode: (self oopForPointer: localIP) - offset - method - BaseHeaderSize + 1]
+ ifFalse: "don't ask if one should compile a second time..."
+ [backwardJumpCount := 1 bitShift: BytesPerWord * 8 - 2]]]
+ ifFalse:
+ [lastBackwardJumpMethod := method.
+ backwardJumpCount := minBackwardJumpCountForCompile]].
+ self fetchNextBytecode! !
+
+----QUIT----{2 January 2011 . 2:06:04 pm} VMMaker-Squeak4.1.image priorSource: 6116306!
+
+----STARTUP----{2 January 2011 . 2:10:20 pm} as /Users/eliot/Cog/oscog/Cog.squeakvm.org/image/VMMaker-Squeak4.1.image!
+
+!CoInterpreter methodsFor: 'frame access' stamp: 'eem 1/2/2011 14:09' prior: 39663149!
+convertToMachineCodeFrame: cogHomeMethod bcpc: bcpc
+ <var: #cogHomeMethod type: #'CogHomeMethod *'>
+ "Convert the current interpreter frame into a machine code frame
+ and answer the machine code pc matching bcpc."
+ | startBcpc methodField closure cogMethod pc |
+ <var: #cogMethod type: #'CogBlockMethod *'>
+ <var: #p type: #'char *'>
+ self assert: (self isMachineCodeFrame: framePointer) not.
+ "Update the return pc, perhaps saving it in the caller's iframeSavedIP."
+ (self isBaseFrame: framePointer)
+ ifTrue:
+ [stackPages
+ longAt: framePointer + FoxCallerSavedIP
+ put: cogit ceBaseFrameReturnPC]
+ ifFalse:
+ [(self isMachineCodeFrame: (self frameCallerFP: framePointer)) ifFalse:
+ [self iframeSavedIP: (self frameCallerFP: framePointer)
+ put: (self frameCallerSavedIP: framePointer) asInteger.
+ stackPages
+ longAt: framePointer + FoxCallerSavedIP
+ put: cogit ceReturnToInterpreterPC]].
+ "Set the cog method field"
+ (self iframeIsBlockActivation: framePointer)
+ ifTrue:
+ [closure := self pushedReceiverOrClosureOfFrame: framePointer.
+ startBcpc := self startPCOfClosure: closure.
+ cogMethod := cogit
+ findMethodForStartBcpc: startBcpc
+ inHomeMethod: cogHomeMethod.
+ methodField := cogMethod asInteger + MFMethodFlagIsBlockFlag]
+ ifFalse:
+ [startBcpc := self startPCOfMethodHeader: cogHomeMethod methodHeader.
+ cogMethod := self cCoerceSimple: cogHomeMethod to: #'CogBlockMethod *'.
+ methodField := cogHomeMethod asInteger].
+ stackPages
+ longAt: framePointer + FoxMethod
+ put: methodField
+ + ((self iframeHasContext: framePointer)
+ ifTrue: [MFMethodFlagHasContextFlag]
+ ifFalse: [0]).
+ framePointer + FoxIFReceiver to: stackPointer by: BytesPerWord negated do:
+ [:p|
+ stackPages longAt: p + FoxMFReceiver - FoxIFReceiver put: (stackPages longAt: p)].
+ stackPointer := stackPointer + FoxMFReceiver - FoxIFReceiver.
+ pc := cogit mcPCFor: bcpc startBcpc: startBcpc in: cogMethod.
+ self assert: pc > cogit noCheckEntryOffset.
+ ^cogMethod asInteger + pc! !
+!StackInterpreter methodsFor: 'frame access' stamp: 'eem 1/2/2011 14:09' prior: 38390444!
+frameCallerSavedIP: theFP
+ <inline: true>
+ <returnTypeC: #'char *'>
+ <var: #theFP type: #'char *'>
+ ^self pointerForOop: (stackPages longAt: theFP + FoxCallerSavedIP) "a.k.a. FoxCallerSavedIP"! !
+
+----SNAPSHOT----{2 January 2011 . 2:11:33 pm} VMMaker-Squeak4.1.image priorSource: 6117693!
+
+----STARTUP----{2 January 2011 . 2:33:12 pm} as /Users/eliot/Cog/oscog/Cog.squeakvm.org/image/VMMaker-Squeak4.1.image!
+
+
+| user pw |
+Utilities setAuthorInitials.
+user := UIManager default request: 'Repository user name'.
+pw := UIManager default requestPassword: 'Monticello password'.
+MCHttpRepository allSubInstancesDo: [ : rep |
+ rep user: user;
+ password: pw ].
+user = 'anon' ifTrue: [MCFileBasedRepository flushAllCaches]!
+
+"VMMaker"!
+
+| user pw |
+Utilities setAuthorInitials.
+user := UIManager default request: 'Repository user name'.
+pw := UIManager default requestPassword: 'Monticello password'.
+MCHttpRepository allSubInstancesDo: [ : rep |
+ rep user: user;
+ password: pw ].
+user = 'anon' ifTrue: [MCFileBasedRepository flushAllCaches]!
+
+----QUIT----{2 January 2011 . 2:36:19 pm} VMMaker-Squeak4.1.image priorSource: 6120305!
\ No newline at end of file

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

Modified: branches/Cog/platforms/Cross/vm/sq.h
===================================================================
--- branches/Cog/platforms/Cross/vm/sq.h 2011-01-01 22:51:31 UTC (rev 2340)
+++ branches/Cog/platforms/Cross/vm/sq.h 2011-01-02 22:44:59 UTC (rev 2341)
@@ -469,6 +469,8 @@
 sqInt imageNameSize(void);
 sqInt vmPathSize(void);
 sqInt vmPathGetLength(sqInt sqVMPathIndex, sqInt length);
+char* ioGetLogDirectory(void);
+char* ioGetWindowLabel(void);
 
 /* Image security traps. */
 sqInt ioCanRenameImage(void);

Modified: branches/Cog/platforms/unix/config/make.cfg.in
===================================================================
--- branches/Cog/platforms/unix/config/make.cfg.in 2011-01-01 22:51:31 UTC (rev 2340)
+++ branches/Cog/platforms/unix/config/make.cfg.in 2011-01-02 22:44:59 UTC (rev 2341)
@@ -72,6 +72,7 @@
 MKINSTALLDIRS= mkdir -p
 INSTALL= @INSTALL@
 INSTALL_PROG= @INSTALL_PROGRAM@ $(INSTALL_ARGS)
+INSTALL_SCRIPT= @INSTALL_SCRIPT@ $(INSTALL_ARGS)
 INSTALL_DATA= @INSTALL_DATA@ $(INSTALL_ARGS)
 UNINSTALL= $(SHELL) $(cfgdir)/uninstall
 AS= @AS@

Modified: branches/Cog/platforms/unix/vm/Makefile.in
===================================================================
--- branches/Cog/platforms/unix/vm/Makefile.in 2011-01-01 22:51:31 UTC (rev 2340)
+++ branches/Cog/platforms/unix/vm/Makefile.in 2011-01-02 22:44:59 UTC (rev 2341)
@@ -68,6 +68,11 @@
 
 [make_targets]
 
+# Ensure the cointerpreter is compiled with less aggressive optimization.  At
+# least with gcc 4.1.2 compiling with -O2 results in an apparently flakey VM.
+gcc3x-cointerp$o : $(srcdir)/vm/gcc3x-cointerp.c
+ $(COMPILE) gcc3x-cointerp$o -O1 -fno-omit-frame-pointer -momit-leaf-frame-pointer -mno-rtd -mno-accumulate-outgoing-args $(srcdir)/vm/gcc3x-cointerp.c
+
 # Ensure the cogit is compiled with less aggressive optimization.  The cogit
 # contains a function that does two alloca's which is miscompiled by a number of
 # optimizing compilers (at least gcc 4.0.x 4.1.x & Intel icc 10.1) under the

Modified: branches/Cog/src/vm/cogit.c
===================================================================
--- branches/Cog/src/vm/cogit.c 2011-01-01 22:51:31 UTC (rev 2340)
+++ branches/Cog/src/vm/cogit.c 2011-01-02 22:44:59 UTC (rev 2341)
@@ -1,9 +1,9 @@
 /* Automatically generated by
- CCodeGenerator VMMaker-oscog.42 uuid: d3b303c1-306e-4343-b078-655fc2bfc436
+ CCodeGenerator VMMaker-oscog.43 uuid: 9afbc6fa-2adb-4ffe-b0b3-84833ead222d
    from
- StackToRegisterMappingCogit VMMaker-oscog.42 uuid: d3b303c1-306e-4343-b078-655fc2bfc436
+ StackToRegisterMappingCogit VMMaker-oscog.43 uuid: 9afbc6fa-2adb-4ffe-b0b3-84833ead222d
  */
-static char __buildInfo[] = "StackToRegisterMappingCogit VMMaker-oscog.42 uuid: d3b303c1-306e-4343-b078-655fc2bfc436 " __DATE__ ;
+static char __buildInfo[] = "StackToRegisterMappingCogit VMMaker-oscog.43 uuid: 9afbc6fa-2adb-4ffe-b0b3-84833ead222d " __DATE__ ;
 char *__cogitBuildInfo = __buildInfo;
 
 
@@ -10095,18 +10095,20 @@
 genSpecialSelectorArithmetic(void)
 {
     sqInt argInt;
+    sqInt argIsConst;
     sqInt argIsInt;
     AbstractInstruction *jumpContinue;
     AbstractInstruction *jumpNotSmallInts;
     BytecodeDescriptor *primDescriptor;
     sqInt rcvrInt;
+    sqInt rcvrIsConst;
     sqInt rcvrIsInt;
     sqInt result;
 
  primDescriptor = generatorAt(byte0);
- argIsInt = (((ssTop()->type)) == SSConstant)
+ argIsInt = ((argIsConst = ((ssTop()->type)) == SSConstant))
  && ((((argInt = (ssTop()->constant))) & 1));
- rcvrIsInt = (((ssValue(1)->type)) == SSConstant)
+ rcvrIsInt = ((rcvrIsConst = ((ssValue(1)->type)) == SSConstant))
  && ((((rcvrInt = (ssValue(1)->constant))) & 1));
  if (argIsInt
  && (rcvrIsInt)) {
@@ -10135,6 +10137,12 @@
  }
  return genSpecialSelectorSend();
  }
+ if ((rcvrIsConst
+ && (!rcvrIsInt))
+ || (argIsConst
+ && (!argIsInt))) {
+ return genSpecialSelectorSend();
+ }
  if (!(argIsInt
  || (rcvrIsInt))) {
  return genSpecialSelectorSend();

Modified: branches/Cog/src/vm/cogit.h
===================================================================
--- branches/Cog/src/vm/cogit.h 2011-01-01 22:51:31 UTC (rev 2340)
+++ branches/Cog/src/vm/cogit.h 2011-01-02 22:44:59 UTC (rev 2341)
@@ -1,5 +1,5 @@
 /* Automatically generated by
- CCodeGenerator VMMaker-oscog.42 uuid: d3b303c1-306e-4343-b078-655fc2bfc436
+ CCodeGenerator VMMaker-oscog.43 uuid: 9afbc6fa-2adb-4ffe-b0b3-84833ead222d
  */
 
 

Modified: branches/Cog/src/vm/cogmethod.h
===================================================================
--- branches/Cog/src/vm/cogmethod.h 2011-01-01 22:51:31 UTC (rev 2340)
+++ branches/Cog/src/vm/cogmethod.h 2011-01-02 22:44:59 UTC (rev 2341)
@@ -1,5 +1,5 @@
 /* Automatically generated by
- CCodeGenerator VMMaker-oscog.40 uuid: 637db40c-33c6-4263-816e-1b8cc19e3c99
+ CCodeGenerator VMMaker-oscog.43 uuid: 9afbc6fa-2adb-4ffe-b0b3-84833ead222d
  */
 
 typedef struct {

Modified: branches/Cog/src/vm/cointerp.c
===================================================================
--- branches/Cog/src/vm/cointerp.c 2011-01-01 22:51:31 UTC (rev 2340)
+++ branches/Cog/src/vm/cointerp.c 2011-01-02 22:44:59 UTC (rev 2341)
@@ -1,9 +1,9 @@
 /* Automatically generated by
- CCodeGeneratorGlobalStructure VMMaker-oscog.41 uuid: 096b8a29-e7e8-4cbf-b29c-0f096abbdd5c
+ CCodeGeneratorGlobalStructure VMMaker-oscog.43 uuid: 9afbc6fa-2adb-4ffe-b0b3-84833ead222d
    from
- CoInterpreter VMMaker-oscog.41 uuid: 096b8a29-e7e8-4cbf-b29c-0f096abbdd5c
+ CoInterpreter VMMaker-oscog.43 uuid: 9afbc6fa-2adb-4ffe-b0b3-84833ead222d
  */
-static char __buildInfo[] = "CoInterpreter VMMaker-oscog.41 uuid: 096b8a29-e7e8-4cbf-b29c-0f096abbdd5c " __DATE__ ;
+static char __buildInfo[] = "CoInterpreter VMMaker-oscog.43 uuid: 9afbc6fa-2adb-4ffe-b0b3-84833ead222d " __DATE__ ;
 char *__interpBuildInfo = __buildInfo;
 
 
@@ -341,6 +341,7 @@
 static void assertValidExecutionPointersimbar(usqInt lip, char *lifp, char *lisp, sqInt inInterpreter);
 void assertValidMachineCodeFrame(sqInt instrPtr);
 static void assertValidStackLimits(void);
+static void attemptToSwitchToMachineCode(sqInt bcpc);
 static sqInt baseHeader(sqInt oop);
 sqInt becomewith(sqInt array1, sqInt array2);
 static sqInt becomewithtwoWaycopyHash(sqInt array1, sqInt array2, sqInt twoWayFlag, sqInt copyHashFlag);
@@ -1859,7 +1860,7 @@
  /* 575 */ (void (*)(void))0,
  0 };
 static void (*externalPrimitiveTable[MaxExternalPrimitiveTableSize + 1 /* 4097 */])(void);
-const char *interpreterVersion = "Croquet Closure Cog VM [CoInterpreter VMMaker-oscog.41]";
+const char *interpreterVersion = "Croquet Closure Cog VM [CoInterpreter VMMaker-oscog.43]";
 sqInt minBackwardJumpCountForCompile = MinBackwardJumpCountForCompile /* 10 */;
 static volatile int sendTrace;
 
@@ -5798,24 +5799,6 @@
  {
  sqInt offset;
  sqInt switched;
- CogMethod *cogMethod;
- sqInt pc;
- CogBlockMethod *cogMethod1;
- CogMethod *homeMethod;
- char *sp;
- char *sp1;
- sqInt methodHeader;
- sqInt closure;
- CogBlockMethod *cogMethod2;
- sqInt i;
- sqInt methodField;
- sqInt pc1;
- sqInt startBcpc;
- char *theFP;
- sqInt savedIP;
- sqInt aCompiledMethodHeader;
- char *theFP1;
- char *theFP2;
 
  VM_LABEL(0longUnconditionalJump);
  offset = (((currentBytecode & 7) - 4) * 256) + (byteAtPointer(++localIP));
@@ -5839,86 +5822,12 @@
  if (GIV(method) == lastBackwardJumpMethod) {
  if (((backwardJumpCount -= 1)) <= 0) {
  if (methodWithHeaderShouldBeCogged(headerOf(GIV(method)))) {
- /* begin attemptToSwitchToMachineCode: */
- VM_LABEL(0attemptToSwitchToMachineCode);
- if (!(methodHasCogMethod(GIV(method)))) {
- cogselector(GIV(method), GIV(nilObj));
- }
- if (methodHasCogMethod(GIV(method))) {
- /* begin cogMethodOf: */
- methodHeader = longAt((GIV(method) + BaseHeaderSize) + (HeaderIndex << ShiftForWord));
- assert((isNonIntegerObject(methodHeader))
- && ((((usqInt)methodHeader)) < (startOfMemory())));
- cogMethod = ((CogMethod *) methodHeader);
- /* begin externalizeFPandSP */
- assert((localSP < ((GIV(stackPage)->baseAddress)))
- && (localSP > (((GIV(stackPage)->realStackLimit)) - LargeContextSize)));
- GIV(stackPointer) = localSP;
- GIV(framePointer) = localFP;
- /* begin convertToMachineCodeFrame:bcpc: */
- VM_LABEL(0convertToMachineCodeFramebcpc);
- assert(!(isMachineCodeFrame(GIV(framePointer))));
- if ((longAt(GIV(framePointer) + FoxSavedFP)) == 0) {
- longAtput(GIV(framePointer) + FoxCallerSavedIP, ceBaseFrameReturnPC());
- }
- else {
- if (!(isMachineCodeFrame(frameCallerFP(GIV(framePointer))))) {
- /* begin iframeSavedIP:put: */
- /* begin frameCallerFP: */
- theFP1 = GIV(framePointer);
- theFP = pointerForOop(longAt(theFP1 + FoxSavedFP));
- /* begin frameCallerSavedIP: */
- theFP2 = GIV(framePointer);
- savedIP = ((char *) (pointerForOop(longAt(theFP2 + FoxCallerSavedIP))));
- assert(!(isMachineCodeFrame(theFP)));
- longAtput(theFP + FoxIFSavedIP, savedIP);
- longAtput(GIV(framePointer) + FoxCallerSavedIP, ceReturnToInterpreterPC());
- }
- }
- if ((byteAt((GIV(framePointer) + FoxIFrameFlags) + 3)) != 0) {
- closure = longAt(GIV(framePointer) + ((FoxCallerSavedIP + BytesPerWord) + ((((((usqInt)(longAt(GIV(framePointer) + FoxMethod)))) < heapBase
- ? (mframeCogMethod(GIV(framePointer))->cmNumArgs)
- : byteAt((GIV(framePointer) + FoxIFrameFlags) + 1))) << ShiftForWord)));
- startBcpc = (((longAt((closure + BaseHeaderSize) + (ClosureStartPCIndex << ShiftForWord))) >> 1)) - 1;
- cogMethod2 = findMethodForStartBcpcinHomeMethod(startBcpc, cogMethod);
- methodField = (((sqInt)cogMethod2)) + MFMethodFlagIsBlockFlag;
- }
- else {
- /* begin startPCOfMethodHeader: */
- aCompiledMethodHeader = (cogMethod->methodHeader);
- startBcpc = (((((usqInt) aCompiledMethodHeader) >> 10) & 255) * BytesPerWord) + BaseHeaderSize;
- cogMethod2 = ((CogBlockMethod *) cogMethod);
- methodField = ((sqInt)cogMethod);
- }
- longAtput(GIV(framePointer) + FoxMethod, methodField + (((byteAt((GIV(framePointer) + FoxIFrameFlags) + 2)) != 0
- ? MFMethodFlagHasContextFlag
- : 0)));
- for (i = (GIV(framePointer) + FoxIFReceiver); i >= GIV(stackPointer); i += (-BytesPerWord)) {
- longAtput((i + FoxMFReceiver) - FoxIFReceiver, longAt(i));
- }
- GIV(stackPointer) = (GIV(stackPointer) + FoxMFReceiver) - FoxIFReceiver;
- pc1 = mcPCForstartBcpcin((((localIP - offset) - GIV(method)) - BaseHeaderSize) + 1, startBcpc, cogMethod2);
- assert(pc1 > (noCheckEntryOffset()));
- pc = (((sqInt)cogMethod2)) + pc1;
- /* begin assertValidMachineCodeFrame: */
- assert(isMachineCodeFrame(GIV(framePointer)));
- /* begin mframeCogMethod: */
- cogMethod1 = ((CogBlockMethod *) ((longAt(GIV(framePointer) + FoxMethod)) & MFMethodMask));
- /* begin asCogHomeMethod: */
- homeMethod = (((cogMethod1->cmType)) == CMMethod
- ? ((CogMethod *) cogMethod1)
- : cogHomeMethod(cogMethod1));
- assert((methodFor(cogMethod1)) == homeMethod);
- assert((pc > (((sqInt)cogMethod1)))
- && (pc < ((((sqInt)homeMethod)) + ((homeMethod->blockSize)))));
- /* begin push: */
- longAtput(sp = GIV(stackPointer) - BytesPerWord, pc);
- GIV(stackPointer) = sp;
- /* begin push: */
- longAtput(sp1 = GIV(stackPointer) - BytesPerWord, GIV(nilObj));
- GIV(stackPointer) = sp1;
- ceEnterCogCodePopReceiverReg();
- }
+ /* begin externalizeFPandSP */
+ assert((localSP < ((GIV(stackPage)->baseAddress)))
+ && (localSP > (((GIV(stackPage)->realStackLimit)) - LargeContextSize)));
+ GIV(stackPointer) = localSP;
+ GIV(framePointer) = localFP;
+ attemptToSwitchToMachineCode(((((oopForPointer(localIP)) - offset) - GIV(method)) - BaseHeaderSize) + 1);
  }
  else {
 
@@ -9323,6 +9232,98 @@
  || (((GIV(stackPage)->stackLimit)) == (((char *) (((usqInt) -1))))));
 }
 
+static void
+attemptToSwitchToMachineCode(sqInt bcpc)
+{   DECL_MAYBE_SQ_GLOBAL_STRUCT
+    sqInt aCompiledMethodHeader;
+    sqInt closure;
+    CogMethod *cogMethod;
+    CogBlockMethod *cogMethod1;
+    CogBlockMethod *cogMethod2;
+    CogMethod *homeMethod;
+    sqInt methodField;
+    sqInt methodHeader;
+    char *p;
+    sqInt pc;
+    sqInt pc1;
+    sqInt savedIP;
+    char *sp;
+    char *sp1;
+    sqInt startBcpc;
+    char *theFP;
+
+ if (!(methodHasCogMethod(GIV(method)))) {
+ cogselector(GIV(method), GIV(nilObj));
+ }
+ if (methodHasCogMethod(GIV(method))) {
+ /* begin cogMethodOf: */
+ methodHeader = longAt((GIV(method) + BaseHeaderSize) + (HeaderIndex << ShiftForWord));
+ assert((isNonIntegerObject(methodHeader))
+ && ((((usqInt)methodHeader)) < (startOfMemory())));
+ cogMethod = ((CogMethod *) methodHeader);
+ /* begin convertToMachineCodeFrame:bcpc: */
+ VM_LABEL(0convertToMachineCodeFramebcpc);
+ assert(!(isMachineCodeFrame(GIV(framePointer))));
+ if ((longAt(GIV(framePointer) + FoxSavedFP)) == 0) {
+ longAtput(GIV(framePointer) + FoxCallerSavedIP, ceBaseFrameReturnPC());
+ }
+ else {
+ if (!(isMachineCodeFrame(frameCallerFP(GIV(framePointer))))) {
+ /* begin iframeSavedIP:put: */
+ /* begin frameCallerFP: */
+ theFP = pointerForOop(longAt(GIV(framePointer) + FoxSavedFP));
+ savedIP = ((sqInt)(frameCallerSavedIP(GIV(framePointer))));
+ assert(!(isMachineCodeFrame(theFP)));
+ longAtput(theFP + FoxIFSavedIP, savedIP);
+ longAtput(GIV(framePointer) + FoxCallerSavedIP, ceReturnToInterpreterPC());
+ }
+ }
+ if ((byteAt((GIV(framePointer) + FoxIFrameFlags) + 3)) != 0) {
+ closure = longAt(GIV(framePointer) + ((FoxCallerSavedIP + BytesPerWord) + ((((((usqInt)(longAt(GIV(framePointer) + FoxMethod)))) < heapBase
+ ? (mframeCogMethod(GIV(framePointer))->cmNumArgs)
+ : byteAt((GIV(framePointer) + FoxIFrameFlags) + 1))) << ShiftForWord)));
+ startBcpc = (((longAt((closure + BaseHeaderSize) + (ClosureStartPCIndex << ShiftForWord))) >> 1)) - 1;
+ cogMethod2 = findMethodForStartBcpcinHomeMethod(startBcpc, cogMethod);
+ methodField = (((sqInt)cogMethod2)) + MFMethodFlagIsBlockFlag;
+ }
+ else {
+ /* begin startPCOfMethodHeader: */
+ aCompiledMethodHeader = (cogMethod->methodHeader);
+ startBcpc = (((((usqInt) aCompiledMethodHeader) >> 10) & 255) * BytesPerWord) + BaseHeaderSize;
+ cogMethod2 = ((CogBlockMethod *) cogMethod);
+ methodField = ((sqInt)cogMethod);
+ }
+ longAtput(GIV(framePointer) + FoxMethod, methodField + (((byteAt((GIV(framePointer) + FoxIFrameFlags) + 2)) != 0
+ ? MFMethodFlagHasContextFlag
+ : 0)));
+ for (p = (GIV(framePointer) + FoxIFReceiver); p >= GIV(stackPointer); p += (-BytesPerWord)) {
+ longAtput((p + FoxMFReceiver) - FoxIFReceiver, longAt(p));
+ }
+ GIV(stackPointer) = (GIV(stackPointer) + FoxMFReceiver) - FoxIFReceiver;
+ pc1 = mcPCForstartBcpcin(bcpc, startBcpc, cogMethod2);
+ assert(pc1 > (noCheckEntryOffset()));
+ pc = (((sqInt)cogMethod2)) + pc1;
+ /* begin assertValidMachineCodeFrame: */
+ assert(isMachineCodeFrame(GIV(framePointer)));
+ /* begin mframeCogMethod: */
+ cogMethod1 = ((CogBlockMethod *) ((longAt(GIV(framePointer) + FoxMethod)) & MFMethodMask));
+ /* begin asCogHomeMethod: */
+ homeMethod = (((cogMethod1->cmType)) == CMMethod
+ ? ((CogMethod *) cogMethod1)
+ : cogHomeMethod(cogMethod1));
+ assert((methodFor(cogMethod1)) == homeMethod);
+ assert((pc > (((sqInt)cogMethod1)))
+ && (pc < ((((sqInt)homeMethod)) + ((homeMethod->blockSize)))));
+ /* begin push: */
+ longAtput(sp = GIV(stackPointer) - BytesPerWord, pc);
+ GIV(stackPointer) = sp;
+ /* begin push: */
+ longAtput(sp1 = GIV(stackPointer) - BytesPerWord, GIV(nilObj));
+ GIV(stackPointer) = sp1;
+ ceEnterCogCodePopReceiverReg();
+ }
+}
+
 static sqInt
 baseHeader(sqInt oop)
 {
@@ -9638,9 +9639,7 @@
     volatile void *currentCStackPointer;
     volatile sqInt header;
     volatile sqInt methodHeader;
-    volatile sqInt savedIP;
     volatile jmp_buf savedReenterInterpreter;
-    volatile char *theFP;
     volatile sqInt wasInMachineCode;
     volatile sqInt xArray;
 
@@ -9702,10 +9701,8 @@
  if (calledFromMachineCode) {
  if (GIV(instructionPointer) >= heapBase) {
  /* begin iframeSavedIP:put: */
- theFP = GIV(framePointer);
- savedIP = GIV(instructionPointer);
- assert(!(isMachineCodeFrame(theFP)));
- longAtput(theFP + FoxIFSavedIP, savedIP);
+ assert(!(isMachineCodeFrame(GIV(framePointer))));
+ longAtput(GIV(framePointer) + FoxIFSavedIP, GIV(instructionPointer));
  GIV(instructionPointer) = ceReturnToInterpreterPC();
  }
  }
@@ -9838,7 +9835,6 @@
     char *sp1;
     char *sp2;
     char *sp3;
-    char *theFP;
     StackPage *thePage;
     sqInt value;
 
@@ -9883,14 +9879,13 @@
  }
  else {
  /* begin findFrameAbove:inPage: */
- theFP = GIV(framePointer);
  fp = (thePage->headFP);
- if (fp == theFP) {
+ if (fp == GIV(framePointer)) {
  frameAbove = 0;
  goto l1;
  }
  while (((callerFP = frameCallerFP(fp))) != 0) {
- if (callerFP == theFP) {
+ if (callerFP == GIV(framePointer)) {
  frameAbove = fp;
  goto l1;
  }
@@ -10179,8 +10174,6 @@
     char *theFP2;
     char *theFP3;
     char *theFP4;
-    char *theFP5;
-    char *theFP6;
     sqInt theMethod;
     StackPage *thePage;
     StackPage *thePage1;
@@ -10188,7 +10181,6 @@
     StackPage *thePage3;
     char *theSP;
     char *theSP1;
-    char *theSP2;
     sqInt top;
     sqInt unwindContextOrNilOrZero;
     sqInt value;
@@ -10233,16 +10225,16 @@
  if (unwindContextOrNilOrZero == GIV(nilObj)) {
  /* begin ensureFrameIsMarried:SP: */
  VM_LABEL(6ensureFrameIsMarriedSP);
- theFP4 = GIV(framePointer);
+ theFP3 = GIV(framePointer);
  theSP = GIV(stackPointer);
- if (((((usqInt)(longAt(theFP4 + FoxMethod)))) < heapBase
- ? ((longAt(theFP4 + FoxMethod)) & MFMethodFlagHasContextFlag) != 0
- : (byteAt((theFP4 + FoxIFrameFlags) + 2)) != 0)) {
- assert(isContext(frameContext(theFP4)));
- ourContext = longAt(theFP4 + FoxThisContext);
+ if (((((usqInt)(longAt(theFP3 + FoxMethod)))) < heapBase
+ ? ((longAt(theFP3 + FoxMethod)) & MFMethodFlagHasContextFlag) != 0
+ : (byteAt((theFP3 + FoxIFrameFlags) + 2)) != 0)) {
+ assert(isContext(frameContext(theFP3)));
+ ourContext = longAt(theFP3 + FoxThisContext);
  goto l2;
  }
- ourContext = marryFrameSP(theFP4, theSP);
+ ourContext = marryFrameSP(theFP3, theSP);
  l2: /* end ensureFrameIsMarried:SP: */;
  /* begin externalCannotReturn:from: */
  /* begin push: */
@@ -10261,16 +10253,14 @@
  VM_LABEL(0externalAboutToReturnthrough);
  /* begin ensureFrameIsMarried:SP: */
  VM_LABEL(7ensureFrameIsMarriedSP);
- theFP6 = GIV(framePointer);
- theSP2 = GIV(stackPointer);
- if (((((usqInt)(longAt(theFP6 + FoxMethod)))) < heapBase
- ? ((longAt(theFP6 + FoxMethod)) & MFMethodFlagHasContextFlag) != 0
- : (byteAt((theFP6 + FoxIFrameFlags) + 2)) != 0)) {
- assert(isContext(frameContext(theFP6)));
- ourContext1 = longAt(theFP6 + FoxThisContext);
+ if (((((usqInt)(longAt(GIV(framePointer) + FoxMethod)))) < heapBase
+ ? ((longAt(GIV(framePointer) + FoxMethod)) & MFMethodFlagHasContextFlag) != 0
+ : (byteAt((GIV(framePointer) + FoxIFrameFlags) + 2)) != 0)) {
+ assert(isContext(frameContext(GIV(framePointer))));
+ ourContext1 = longAt(GIV(framePointer) + FoxThisContext);
  goto l4;
  }
- ourContext1 = marryFrameSP(theFP6, theSP2);
+ ourContext1 = marryFrameSP(GIV(framePointer), GIV(stackPointer));
  l4: /* end ensureFrameIsMarried:SP: */;
  /* begin push: */
  longAtput(sp4 = GIV(stackPointer) - BytesPerWord, ourContext1);
@@ -10333,16 +10323,16 @@
  if (frameToReturnTo == 0) {
  /* begin ensureFrameIsMarried:SP: */
  VM_LABEL(8ensureFrameIsMarriedSP);
- theFP5 = GIV(framePointer);
+ theFP4 = GIV(framePointer);
  theSP1 = GIV(stackPointer);
- if (((((usqInt)(longAt(theFP5 + FoxMethod)))) < heapBase
- ? ((longAt(theFP5 + FoxMethod)) & MFMethodFlagHasContextFlag) != 0
- : (byteAt((theFP5 + FoxIFrameFlags) + 2)) != 0)) {
- assert(isContext(frameContext(theFP5)));
- ourContext = longAt(theFP5 + FoxThisContext);
+ if (((((usqInt)(longAt(theFP4 + FoxMethod)))) < heapBase
+ ? ((longAt(theFP4 + FoxMethod)) & MFMethodFlagHasContextFlag) != 0
+ : (byteAt((theFP4 + FoxIFrameFlags) + 2)) != 0)) {
+ assert(isContext(frameContext(theFP4)));
+ ourContext = longAt(theFP4 + FoxThisContext);
  goto l3;
  }
- ourContext = marryFrameSP(theFP5, theSP1);
+ ourContext = marryFrameSP(theFP4, theSP1);
  l3: /* end ensureFrameIsMarried:SP: */;
  /* begin externalCannotReturn:from: */
  /* begin push: */
@@ -10442,8 +10432,7 @@
  do {
  callerFP = GIV(framePointer);
  /* begin frameCallerFP: */
- theFP3 = GIV(framePointer);
- GIV(framePointer) = pointerForOop(longAt(theFP3 + FoxSavedFP));
+ GIV(framePointer) = pointerForOop(longAt(GIV(framePointer) + FoxSavedFP));
  } while(GIV(framePointer) != frameToReturnTo);
  GIV(instructionPointer) = ((usqInt)(frameCallerSavedIP(callerFP)));
  /* begin frameCallerSP: */

Modified: branches/Cog/src/vm/cointerp.h
===================================================================
--- branches/Cog/src/vm/cointerp.h 2011-01-01 22:51:31 UTC (rev 2340)
+++ branches/Cog/src/vm/cointerp.h 2011-01-02 22:44:59 UTC (rev 2341)
@@ -1,5 +1,5 @@
 /* Automatically generated by
- CCodeGeneratorGlobalStructure VMMaker-oscog.40 uuid: 637db40c-33c6-4263-816e-1b8cc19e3c99
+ CCodeGeneratorGlobalStructure VMMaker-oscog.43 uuid: 9afbc6fa-2adb-4ffe-b0b3-84833ead222d
  */
 
 

Modified: branches/Cog/src/vm/gcc3x-cointerp.c
===================================================================
--- branches/Cog/src/vm/gcc3x-cointerp.c 2011-01-01 22:51:31 UTC (rev 2340)
+++ branches/Cog/src/vm/gcc3x-cointerp.c 2011-01-02 22:44:59 UTC (rev 2341)
@@ -2,11 +2,11 @@
 
 
 /* Automatically generated by
- CCodeGeneratorGlobalStructure VMMaker-oscog.41 uuid: 096b8a29-e7e8-4cbf-b29c-0f096abbdd5c
+ CCodeGeneratorGlobalStructure VMMaker-oscog.43 uuid: 9afbc6fa-2adb-4ffe-b0b3-84833ead222d
    from
- CoInterpreter VMMaker-oscog.41 uuid: 096b8a29-e7e8-4cbf-b29c-0f096abbdd5c
+ CoInterpreter VMMaker-oscog.43 uuid: 9afbc6fa-2adb-4ffe-b0b3-84833ead222d
  */
-static char __buildInfo[] = "CoInterpreter VMMaker-oscog.41 uuid: 096b8a29-e7e8-4cbf-b29c-0f096abbdd5c " __DATE__ ;
+static char __buildInfo[] = "CoInterpreter VMMaker-oscog.43 uuid: 9afbc6fa-2adb-4ffe-b0b3-84833ead222d " __DATE__ ;
 char *__interpBuildInfo = __buildInfo;
 
 
@@ -344,6 +344,7 @@
 static void assertValidExecutionPointersimbar(usqInt lip, char *lifp, char *lisp, sqInt inInterpreter);
 void assertValidMachineCodeFrame(sqInt instrPtr);
 static void assertValidStackLimits(void);
+static void attemptToSwitchToMachineCode(sqInt bcpc);
 static sqInt baseHeader(sqInt oop);
 sqInt becomewith(sqInt array1, sqInt array2);
 static sqInt becomewithtwoWaycopyHash(sqInt array1, sqInt array2, sqInt twoWayFlag, sqInt copyHashFlag);
@@ -1862,7 +1863,7 @@
  /* 575 */ (void (*)(void))0,
  0 };
 static void (*externalPrimitiveTable[MaxExternalPrimitiveTableSize + 1 /* 4097 */])(void);
-const char *interpreterVersion = "Croquet Closure Cog VM [CoInterpreter VMMaker-oscog.41]";
+const char *interpreterVersion = "Croquet Closure Cog VM [CoInterpreter VMMaker-oscog.43]";
 sqInt minBackwardJumpCountForCompile = MinBackwardJumpCountForCompile /* 10 */;
 static volatile int sendTrace;
 
@@ -5802,24 +5803,6 @@
  {
  sqInt offset;
  sqInt switched;
- CogMethod *cogMethod;
- sqInt pc;
- CogBlockMethod *cogMethod1;
- CogMethod *homeMethod;
- char *sp;
- char *sp1;
- sqInt methodHeader;
- sqInt closure;
- CogBlockMethod *cogMethod2;
- sqInt i;
- sqInt methodField;
- sqInt pc1;
- sqInt startBcpc;
- char *theFP;
- sqInt savedIP;
- sqInt aCompiledMethodHeader;
- char *theFP1;
- char *theFP2;
 
  VM_LABEL(0longUnconditionalJump);
  offset = (((currentBytecode & 7) - 4) * 256) + (byteAtPointer(++localIP));
@@ -5843,86 +5826,12 @@
  if (GIV(method) == lastBackwardJumpMethod) {
  if (((backwardJumpCount -= 1)) <= 0) {
  if (methodWithHeaderShouldBeCogged(headerOf(GIV(method)))) {
- /* begin attemptToSwitchToMachineCode: */
- VM_LABEL(0attemptToSwitchToMachineCode);
- if (!(methodHasCogMethod(GIV(method)))) {
- cogselector(GIV(method), GIV(nilObj));
- }
- if (methodHasCogMethod(GIV(method))) {
- /* begin cogMethodOf: */
- methodHeader = longAt((GIV(method) + BaseHeaderSize) + (HeaderIndex << ShiftForWord));
- assert((isNonIntegerObject(methodHeader))
- && ((((usqInt)methodHeader)) < (startOfMemory())));
- cogMethod = ((CogMethod *) methodHeader);
- /* begin externalizeFPandSP */
- assert((localSP < ((GIV(stackPage)->baseAddress)))
- && (localSP > (((GIV(stackPage)->realStackLimit)) - LargeContextSize)));
- GIV(stackPointer) = localSP;
- GIV(framePointer) = localFP;
- /* begin convertToMachineCodeFrame:bcpc: */
- VM_LABEL(0convertToMachineCodeFramebcpc);
- assert(!(isMachineCodeFrame(GIV(framePointer))));
- if ((longAt(GIV(framePointer) + FoxSavedFP)) == 0) {
- longAtput(GIV(framePointer) + FoxCallerSavedIP, ceBaseFrameReturnPC());
- }
- else {
- if (!(isMachineCodeFrame(frameCallerFP(GIV(framePointer))))) {
- /* begin iframeSavedIP:put: */
- /* begin frameCallerFP: */
- theFP1 = GIV(framePointer);
- theFP = pointerForOop(longAt(theFP1 + FoxSavedFP));
- /* begin frameCallerSavedIP: */
- theFP2 = GIV(framePointer);
- savedIP = ((char *) (pointerForOop(longAt(theFP2 + FoxCallerSavedIP))));
- assert(!(isMachineCodeFrame(theFP)));
- longAtput(theFP + FoxIFSavedIP, savedIP);
- longAtput(GIV(framePointer) + FoxCallerSavedIP, ceReturnToInterpreterPC());
- }
- }
- if ((byteAt((GIV(framePointer) + FoxIFrameFlags) + 3)) != 0) {
- closure = longAt(GIV(framePointer) + ((FoxCallerSavedIP + BytesPerWord) + ((((((usqInt)(longAt(GIV(framePointer) + FoxMethod)))) < heapBase
- ? (mframeCogMethod(GIV(framePointer))->cmNumArgs)
- : byteAt((GIV(framePointer) + FoxIFrameFlags) + 1))) << ShiftForWord)));
- startBcpc = (((longAt((closure + BaseHeaderSize) + (ClosureStartPCIndex << ShiftForWord))) >> 1)) - 1;
- cogMethod2 = findMethodForStartBcpcinHomeMethod(startBcpc, cogMethod);
- methodField = (((sqInt)cogMethod2)) + MFMethodFlagIsBlockFlag;
- }
- else {
- /* begin startPCOfMethodHeader: */
- aCompiledMethodHeader = (cogMethod->methodHeader);
- startBcpc = (((((usqInt) aCompiledMethodHeader) >> 10) & 255) * BytesPerWord) + BaseHeaderSize;
- cogMethod2 = ((CogBlockMethod *) cogMethod);
- methodField = ((sqInt)cogMethod);
- }
- longAtput(GIV(framePointer) + FoxMethod, methodField + (((byteAt((GIV(framePointer) + FoxIFrameFlags) + 2)) != 0
- ? MFMethodFlagHasContextFlag
- : 0)));
- for (i = (GIV(framePointer) + FoxIFReceiver); i >= GIV(stackPointer); i += (-BytesPerWord)) {
- longAtput((i + FoxMFReceiver) - FoxIFReceiver, longAt(i));
- }
- GIV(stackPointer) = (GIV(stackPointer) + FoxMFReceiver) - FoxIFReceiver;
- pc1 = mcPCForstartBcpcin((((localIP - offset) - GIV(method)) - BaseHeaderSize) + 1, startBcpc, cogMethod2);
- assert(pc1 > (noCheckEntryOffset()));
- pc = (((sqInt)cogMethod2)) + pc1;
- /* begin assertValidMachineCodeFrame: */
- assert(isMachineCodeFrame(GIV(framePointer)));
- /* begin mframeCogMethod: */
- cogMethod1 = ((CogBlockMethod *) ((longAt(GIV(framePointer) + FoxMethod)) & MFMethodMask));
- /* begin asCogHomeMethod: */
- homeMethod = (((cogMethod1->cmType)) == CMMethod
- ? ((CogMethod *) cogMethod1)
- : cogHomeMethod(cogMethod1));
- assert((methodFor(cogMethod1)) == homeMethod);
- assert((pc > (((sqInt)cogMethod1)))
- && (pc < ((((sqInt)homeMethod)) + ((homeMethod->blockSize)))));
- /* begin push: */
- longAtput(sp = GIV(stackPointer) - BytesPerWord, pc);
- GIV(stackPointer) = sp;
- /* begin push: */
- longAtput(sp1 = GIV(stackPointer) - BytesPerWord, GIV(nilObj));
- GIV(stackPointer) = sp1;
- ceEnterCogCodePopReceiverReg();
- }
+ /* begin externalizeFPandSP */
+ assert((localSP < ((GIV(stackPage)->baseAddress)))
+ && (localSP > (((GIV(stackPage)->realStackLimit)) - LargeContextSize)));
+ GIV(stackPointer) = localSP;
+ GIV(framePointer) = localFP;
+ attemptToSwitchToMachineCode(((((oopForPointer(localIP)) - offset) - GIV(method)) - BaseHeaderSize) + 1);
  }
  else {
 
@@ -9327,6 +9236,98 @@
  || (((GIV(stackPage)->stackLimit)) == (((char *) (((usqInt) -1))))));
 }
 
+static void
+attemptToSwitchToMachineCode(sqInt bcpc)
+{   DECL_MAYBE_SQ_GLOBAL_STRUCT
+    sqInt aCompiledMethodHeader;
+    sqInt closure;
+    CogMethod *cogMethod;
+    CogBlockMethod *cogMethod1;
+    CogBlockMethod *cogMethod2;
+    CogMethod *homeMethod;
+    sqInt methodField;
+    sqInt methodHeader;
+    char *p;
+    sqInt pc;
+    sqInt pc1;
+    sqInt savedIP;
+    char *sp;
+    char *sp1;
+    sqInt startBcpc;
+    char *theFP;
+
+ if (!(methodHasCogMethod(GIV(method)))) {
+ cogselector(GIV(method), GIV(nilObj));
+ }
+ if (methodHasCogMethod(GIV(method))) {
+ /* begin cogMethodOf: */
+ methodHeader = longAt((GIV(method) + BaseHeaderSize) + (HeaderIndex << ShiftForWord));
+ assert((isNonIntegerObject(methodHeader))
+ && ((((usqInt)methodHeader)) < (startOfMemory())));
+ cogMethod = ((CogMethod *) methodHeader);
+ /* begin convertToMachineCodeFrame:bcpc: */
+ VM_LABEL(0convertToMachineCodeFramebcpc);
+ assert(!(isMachineCodeFrame(GIV(framePointer))));
+ if ((longAt(GIV(framePointer) + FoxSavedFP)) == 0) {
+ longAtput(GIV(framePointer) + FoxCallerSavedIP, ceBaseFrameReturnPC());
+ }
+ else {
+ if (!(isMachineCodeFrame(frameCallerFP(GIV(framePointer))))) {
+ /* begin iframeSavedIP:put: */
+ /* begin frameCallerFP: */
+ theFP = pointerForOop(longAt(GIV(framePointer) + FoxSavedFP));
+ savedIP = ((sqInt)(frameCallerSavedIP(GIV(framePointer))));
+ assert(!(isMachineCodeFrame(theFP)));
+ longAtput(theFP + FoxIFSavedIP, savedIP);
+ longAtput(GIV(framePointer) + FoxCallerSavedIP, ceReturnToInterpreterPC());
+ }
+ }
+ if ((byteAt((GIV(framePointer) + FoxIFrameFlags) + 3)) != 0) {
+ closure = longAt(GIV(framePointer) + ((FoxCallerSavedIP + BytesPerWord) + ((((((usqInt)(longAt(GIV(framePointer) + FoxMethod)))) < heapBase
+ ? (mframeCogMethod(GIV(framePointer))->cmNumArgs)
+ : byteAt((GIV(framePointer) + FoxIFrameFlags) + 1))) << ShiftForWord)));
+ startBcpc = (((longAt((closure + BaseHeaderSize) + (ClosureStartPCIndex << ShiftForWord))) >> 1)) - 1;
+ cogMethod2 = findMethodForStartBcpcinHomeMethod(startBcpc, cogMethod);
+ methodField = (((sqInt)cogMethod2)) + MFMethodFlagIsBlockFlag;
+ }
+ else {
+ /* begin startPCOfMethodHeader: */
+ aCompiledMethodHeader = (cogMethod->methodHeader);
+ startBcpc = (((((usqInt) aCompiledMethodHeader) >> 10) & 255) * BytesPerWord) + BaseHeaderSize;
+ cogMethod2 = ((CogBlockMethod *) cogMethod);
+ methodField = ((sqInt)cogMethod);
+ }
+ longAtput(GIV(framePointer) + FoxMethod, methodField + (((byteAt((GIV(framePointer) + FoxIFrameFlags) + 2)) != 0
+ ? MFMethodFlagHasContextFlag
+ : 0)));
+ for (p = (GIV(framePointer) + FoxIFReceiver); p >= GIV(stackPointer); p += (-BytesPerWord)) {
+ longAtput((p + FoxMFReceiver) - FoxIFReceiver, longAt(p));
+ }
+ GIV(stackPointer) = (GIV(stackPointer) + FoxMFReceiver) - FoxIFReceiver;
+ pc1 = mcPCForstartBcpcin(bcpc, startBcpc, cogMethod2);
+ assert(pc1 > (noCheckEntryOffset()));
+ pc = (((sqInt)cogMethod2)) + pc1;
+ /* begin assertValidMachineCodeFrame: */
+ assert(isMachineCodeFrame(GIV(framePointer)));
+ /* begin mframeCogMethod: */
+ cogMethod1 = ((CogBlockMethod *) ((longAt(GIV(framePointer) + FoxMethod)) & MFMethodMask));
+ /* begin asCogHomeMethod: */
+ homeMethod = (((cogMethod1->cmType)) == CMMethod
+ ? ((CogMethod *) cogMethod1)
+ : cogHomeMethod(cogMethod1));
+ assert((methodFor(cogMethod1)) == homeMethod);
+ assert((pc > (((sqInt)cogMethod1)))
+ && (pc < ((((sqInt)homeMethod)) + ((homeMethod->blockSize)))));
+ /* begin push: */
+ longAtput(sp = GIV(stackPointer) - BytesPerWord, pc);
+ GIV(stackPointer) = sp;
+ /* begin push: */
+ longAtput(sp1 = GIV(stackPointer) - BytesPerWord, GIV(nilObj));
+ GIV(stackPointer) = sp1;
+ ceEnterCogCodePopReceiverReg();
+ }
+}
+
 static sqInt
 baseHeader(sqInt oop)
 {
@@ -9642,9 +9643,7 @@
     volatile void *currentCStackPointer;
     volatile sqInt header;
     volatile sqInt methodHeader;
-    volatile sqInt savedIP;
     volatile jmp_buf savedReenterInterpreter;
-    volatile char *theFP;
     volatile sqInt wasInMachineCode;
     volatile sqInt xArray;
 
@@ -9706,10 +9705,8 @@
  if (calledFromMachineCode) {
  if (GIV(instructionPointer) >= heapBase) {
  /* begin iframeSavedIP:put: */
- theFP = GIV(framePointer);
- savedIP = GIV(instructionPointer);
- assert(!(isMachineCodeFrame(theFP)));
- longAtput(theFP + FoxIFSavedIP, savedIP);
+ assert(!(isMachineCodeFrame(GIV(framePointer))));
+ longAtput(GIV(framePointer) + FoxIFSavedIP, GIV(instructionPointer));
  GIV(instructionPointer) = ceReturnToInterpreterPC();
  }
  }
@@ -9842,7 +9839,6 @@
     char *sp1;
     char *sp2;
     char *sp3;
-    char *theFP;
     StackPage *thePage;
     sqInt value;
 
@@ -9887,14 +9883,13 @@
  }
  else {
  /* begin findFrameAbove:inPage: */
- theFP = GIV(framePointer);
  fp = (thePage->headFP);
- if (fp == theFP) {
+ if (fp == GIV(framePointer)) {
  frameAbove = 0;
  goto l1;
  }
  while (((callerFP = frameCallerFP(fp))) != 0) {
- if (callerFP == theFP) {
+ if (callerFP == GIV(framePointer)) {
  frameAbove = fp;
  goto l1;
  }
@@ -10183,8 +10178,6 @@
     char *theFP2;
     char *theFP3;
     char *theFP4;
-    char *theFP5;
-    char *theFP6;
     sqInt theMethod;
     StackPage *thePage;
     StackPage *thePage1;
@@ -10192,7 +10185,6 @@
     StackPage *thePage3;
     char *theSP;
     char *theSP1;
-    char *theSP2;
     sqInt top;
     sqInt unwindContextOrNilOrZero;
     sqInt value;
@@ -10237,16 +10229,16 @@
  if (unwindContextOrNilOrZero == GIV(nilObj)) {
  /* begin ensureFrameIsMarried:SP: */
  VM_LABEL(6ensureFrameIsMarriedSP);
- theFP4 = GIV(framePointer);
+ theFP3 = GIV(framePointer);
  theSP = GIV(stackPointer);
- if (((((usqInt)(longAt(theFP4 + FoxMethod)))) < heapBase
- ? ((longAt(theFP4 + FoxMethod)) & MFMethodFlagHasContextFlag) != 0
- : (byteAt((theFP4 + FoxIFrameFlags) + 2)) != 0)) {
- assert(isContext(frameContext(theFP4)));
- ourContext = longAt(theFP4 + FoxThisContext);
+ if (((((usqInt)(longAt(theFP3 + FoxMethod)))) < heapBase
+ ? ((longAt(theFP3 + FoxMethod)) & MFMethodFlagHasContextFlag) != 0
+ : (byteAt((theFP3 + FoxIFrameFlags) + 2)) != 0)) {
+ assert(isContext(frameContext(theFP3)));
+ ourContext = longAt(theFP3 + FoxThisContext);
  goto l2;
  }
- ourContext = marryFrameSP(theFP4, theSP);
+ ourContext = marryFrameSP(theFP3, theSP);
  l2: /* end ensureFrameIsMarried:SP: */;
  /* begin externalCannotReturn:from: */
  /* begin push: */
@@ -10265,16 +10257,14 @@
  VM_LABEL(0externalAboutToReturnthrough);
  /* begin ensureFrameIsMarried:SP: */
  VM_LABEL(7ensureFrameIsMarriedSP);
- theFP6 = GIV(framePointer);
- theSP2 = GIV(stackPointer);
- if (((((usqInt)(longAt(theFP6 + FoxMethod)))) < heapBase
- ? ((longAt(theFP6 + FoxMethod)) & MFMethodFlagHasContextFlag) != 0
- : (byteAt((theFP6 + FoxIFrameFlags) + 2)) != 0)) {
- assert(isContext(frameContext(theFP6)));
- ourContext1 = longAt(theFP6 + FoxThisContext);
+ if (((((usqInt)(longAt(GIV(framePointer) + FoxMethod)))) < heapBase
+ ? ((longAt(GIV(framePointer) + FoxMethod)) & MFMethodFlagHasContextFlag) != 0
+ : (byteAt((GIV(framePointer) + FoxIFrameFlags) + 2)) != 0)) {
+ assert(isContext(frameContext(GIV(framePointer))));
+ ourContext1 = longAt(GIV(framePointer) + FoxThisContext);
  goto l4;
  }
- ourContext1 = marryFrameSP(theFP6, theSP2);
+ ourContext1 = marryFrameSP(GIV(framePointer), GIV(stackPointer));
  l4: /* end ensureFrameIsMarried:SP: */;
  /* begin push: */
  longAtput(sp4 = GIV(stackPointer) - BytesPerWord, ourContext1);
@@ -10337,16 +10327,16 @@
  if (frameToReturnTo == 0) {
  /* begin ensureFrameIsMarried:SP: */
  VM_LABEL(8ensureFrameIsMarriedSP);
- theFP5 = GIV(framePointer);
+ theFP4 = GIV(framePointer);
  theSP1 = GIV(stackPointer);
- if (((((usqInt)(longAt(theFP5 + FoxMethod)))) < heapBase
- ? ((longAt(theFP5 + FoxMethod)) & MFMethodFlagHasContextFlag) != 0
- : (byteAt((theFP5 + FoxIFrameFlags) + 2)) != 0)) {
- assert(isContext(frameContext(theFP5)));
- ourContext = longAt(theFP5 + FoxThisContext);
+ if (((((usqInt)(longAt(theFP4 + FoxMethod)))) < heapBase
+ ? ((longAt(theFP4 + FoxMethod)) & MFMethodFlagHasContextFlag) != 0
+ : (byteAt((theFP4 + FoxIFrameFlags) + 2)) != 0)) {
+ assert(isContext(frameContext(theFP4)));
+ ourContext = longAt(theFP4 + FoxThisContext);
  goto l3;
  }
- ourContext = marryFrameSP(theFP5, theSP1);
+ ourContext = marryFrameSP(theFP4, theSP1);
  l3: /* end ensureFrameIsMarried:SP: */;
  /* begin externalCannotReturn:from: */
  /* begin push: */
@@ -10446,8 +10436,7 @@
  do {
  callerFP = GIV(framePointer);
  /* begin frameCallerFP: */
- theFP3 = GIV(framePointer);
- GIV(framePointer) = pointerForOop(longAt(theFP3 + FoxSavedFP));
+ GIV(framePointer) = pointerForOop(longAt(GIV(framePointer) + FoxSavedFP));
  } while(GIV(framePointer) != frameToReturnTo);
  GIV(instructionPointer) = ((usqInt)(frameCallerSavedIP(callerFP)));
  /* begin frameCallerSP: */

Modified: branches/Cog/src/vm/interp.h
===================================================================
--- branches/Cog/src/vm/interp.h 2011-01-01 22:51:31 UTC (rev 2340)
+++ branches/Cog/src/vm/interp.h 2011-01-02 22:44:59 UTC (rev 2341)
@@ -1,5 +1,5 @@
 /* Automatically generated by
- CCodeGeneratorGlobalStructure VMMaker-oscog.40 uuid: 637db40c-33c6-4263-816e-1b8cc19e3c99
+ CCodeGeneratorGlobalStructure VMMaker-oscog.43 uuid: 9afbc6fa-2adb-4ffe-b0b3-84833ead222d
  */
 
 #define COGVM 1

Modified: branches/Cog/src/vm/vmCallback.h
===================================================================
--- branches/Cog/src/vm/vmCallback.h 2011-01-01 22:51:31 UTC (rev 2340)
+++ branches/Cog/src/vm/vmCallback.h 2011-01-02 22:44:59 UTC (rev 2341)
@@ -1,5 +1,5 @@
 /* Automatically generated by
- CCodeGeneratorGlobalStructure VMMaker-oscog.40 uuid: 637db40c-33c6-4263-816e-1b8cc19e3c99
+ CCodeGeneratorGlobalStructure VMMaker-oscog.43 uuid: 9afbc6fa-2adb-4ffe-b0b3-84833ead222d
  */
 
 #define VM_CALLBACK_INC 1