[commit] r2309 - OSCogVM source as per VMMaker-oscog.28. Fix machine-code Float / to fail for

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

[commit] r2309 - OSCogVM source as per VMMaker-oscog.28. Fix machine-code Float / to fail for

commits-3
 
Author: eliot
Date: 2010-09-18 12:08:00 -0700 (Sat, 18 Sep 2010)
New Revision: 2309

Modified:
   branches/Cog/image/VMMaker-Squeak4.1.changes
   branches/Cog/image/VMMaker-Squeak4.1.image
   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/stacksrc/vm/gcc3x-interp.c
   branches/Cog/stacksrc/vm/interp.c
   branches/Cog/stacksrc/vm/interp.h
Log:
OSCogVM source as per VMMaker-oscog.28.  Fix machine-code Float / to fail for
/ 0.0.  Fix ,interpreter <= & >= bytecodes.


Modified: branches/Cog/image/VMMaker-Squeak4.1.changes
===================================================================
--- branches/Cog/image/VMMaker-Squeak4.1.changes 2010-09-14 02:30:48 UTC (rev 2308)
+++ branches/Cog/image/VMMaker-Squeak4.1.changes 2010-09-18 19:08:00 UTC (rev 2309)
@@ -129517,4 +129517,217 @@
  rep user: user;
  password: pw ]!
 
-----QUIT----{12 September 2010 . 9:06:28 am} VMMaker-Squeak4.1.image priorSource: 5242773!
\ No newline at end of file
+----QUIT----{12 September 2010 . 9:06:28 am} VMMaker-Squeak4.1.image priorSource: 5242773!
+
+----STARTUP----{18 September 2010 . 11:38:19 am} as /Users/eliot/Cog/oscog/Cog.squeakvm.org/image/VMMaker-Squeak4.1.image!
+
+!Cogit methodsFor: 'method map' stamp: 'eem 9/16/2010 17:03' prior: 35096689!
+findEnclosingMethodFor: mcpc inHomeMethod: cogMethod
+ <var: #cogMethod type: #'CogMethod *'>
+ <returnTypeC: #'CogBlockMethod *'>
+ <api>
+ "Find the CMMethod or CMBlock that encloses mcpc.
+ If the method contains blocks then, because block dispatch is not in order,
+ enumerate the block dispatch and find the nearest preceeding entry."
+ self assert: cogMethod cmType = CMMethod.
+ cogMethod blockEntryOffset = 0 ifTrue:
+ [^self cCoerceSimple: cogMethod to: #'CogBlockMethod *'].
+ maxMethodBefore := self cCoerceSimple: cogMethod to: #'CogBlockMethod *'.
+ self blockDispatchTargetsFor: cogMethod perform: #findMinAndMaxMethodsPC:around: asSymbol arg: mcpc.
+ ^maxMethodBefore! !
+!SimpleStackBasedCogit methodsFor: 'primitive generators' stamp: 'eem 9/16/2010 17:01'!
+genDoubleArithmetic: arithmeticOperator preOpCheck: preOpCheckOrNil
+ "Stack looks like
+ receiver (also in ResultReceiverReg)
+ arg
+ return address"
+ <var: #preOpCheckOrNil declareC: 'AbstractInstruction *(*preOpCheckOrNil)(int rcvrReg, int argReg)'>
+ | jumpFailClass jumpFailAlloc jumpFailCheck jumpSmallInt doOp fail |
+ <var: #jumpFailClass type: #'AbstractInstruction *'>
+ <var: #jumpFailAlloc type: #'AbstractInstruction *'>
+ <var: #jumpSmallInt type: #'AbstractInstruction *'>
+ <var: #jumpFailCheck type: #'AbstractInstruction *'>
+ <var: #doOp type: #'AbstractInstruction *'>
+ <var: #fail type: #'AbstractInstruction *'>
+ self MoveMw: BytesPerWord r: SPReg R: TempReg.
+ objectRepresentation genGetDoubleValueOf: ReceiverResultReg into: DPFPReg0.
+ self MoveR: TempReg R: ClassReg.
+ jumpSmallInt := objectRepresentation genJumpSmallIntegerInScratchReg: TempReg.
+ objectRepresentation genGetCompactClassIndexNonIntOf: ClassReg into: SendNumArgsReg.
+ self CmpCq: objectMemory classFloatCompactIndex R: SendNumArgsReg.
+ jumpFailClass := self JumpNonZero: 0.
+ objectRepresentation genGetDoubleValueOf: ClassReg into: DPFPReg1.
+ doOp := self Label.
+ preOpCheckOrNil ifNotNil:
+ [jumpFailCheck := self perform: preOpCheckOrNil with: DPFPReg0 with: DPFPReg1].
+ self gen: arithmeticOperator operand: DPFPReg1 operand: DPFPReg0.
+ jumpFailAlloc := objectRepresentation
+ genAllocFloatValue: DPFPReg0
+ into: SendNumArgsReg
+ scratchReg: ClassReg
+ scratchReg: TempReg.
+ self MoveR: SendNumArgsReg R: ReceiverResultReg.
+ self flag: 'currently caller pushes result'.
+ self RetN: BytesPerWord * 2.
+ jumpSmallInt jmpTarget: self Label.
+ objectRepresentation genConvertSmallIntegerToIntegerInScratchReg: ClassReg.
+ self ConvertR: ClassReg Rd: DPFPReg1.
+ self Jump: doOp.
+ jumpFailAlloc jmpTarget: self Label.
+ self compileInterpreterPrimitive: (coInterpreter
+ functionPointerForCompiledMethod: methodObj
+ primitiveIndex: primitiveIndex).
+ fail := self Label.
+ jumpFailClass jmpTarget: self Label.
+ preOpCheckOrNil ifNotNil:
+ [jumpFailCheck jmpTarget: fail].
+ ^0! !
+!SimpleStackBasedCogit methodsFor: 'primitive generators' stamp: 'eem 9/16/2010 16:59'!
+genDoubleFailIfZeroArgRcvr: rcvrReg arg: argReg
+ <returnTypeC: #'AbstractInstruction *'>
+ self MoveCq: 0 R: TempReg.
+ self ConvertR: TempReg Rd: DPFPReg2.
+ self CmpRd: DPFPReg2 Rd: argReg.
+ ^self JumpFPEqual: 0! !
+!SimpleStackBasedCogit methodsFor: 'primitive generators' stamp: 'eem 9/16/2010 16:38' prior: 37311648!
+genPrimitiveFloatAdd
+ ^self genDoubleArithmetic: AddRdRd preOpCheck: nil! !
+!SimpleStackBasedCogit methodsFor: 'primitive generators' stamp: 'eem 9/16/2010 16:50' prior: 37311797!
+genPrimitiveFloatDivide
+ ^self genDoubleArithmetic: DivRdRd preOpCheck: #genDoubleFailIfZeroArgRcvr:arg: asSymbol! !
+!SimpleStackBasedCogit methodsFor: 'primitive generators' stamp: 'eem 9/16/2010 16:39' prior: 37312819!
+genPrimitiveFloatMultiply
+ ^self genDoubleArithmetic: MulRdRd preOpCheck: nil! !
+!SimpleStackBasedCogit methodsFor: 'primitive generators' stamp: 'eem 9/16/2010 16:39' prior: 37313977!
+genPrimitiveFloatSubtract
+ ^self genDoubleArithmetic: SubRdRd preOpCheck: nil! !
+!StackInterpreter methodsFor: 'common selector sends' stamp: 'eem 9/18/2010 09:59' prior: 37771529!
+bytecodePrimGreaterOrEqual
+ | rcvr arg aBool |
+ rcvr := self internalStackValue: 1.
+ arg := self internalStackValue: 0.
+ (self areIntegers: rcvr and: arg) ifTrue:
+ ["The C code can avoid detagging since tagged integers are still signed.
+ But this means the simulator must override to do detagging."
+ self cCode: '' inSmalltalk: [^self booleanCheat: (self integerValueOf: rcvr) >= (self integerValueOf: arg)].
+ ^self booleanCheat: rcvr >= arg].
+
+ self initPrimCall.
+ aBool := self primitiveFloatGreaterOrEqual: rcvr toArg: arg.
+ self successful ifTrue: [^self booleanCheat: aBool].
+
+ messageSelector := self specialSelector: 5.
+ argumentCount := 1.
+ self normalSend! !
+!StackInterpreter methodsFor: 'common selector sends' stamp: 'eem 9/18/2010 09:59' prior: 37773084!
+bytecodePrimLessOrEqual
+ | rcvr arg aBool |
+ rcvr := self internalStackValue: 1.
+ arg := self internalStackValue: 0.
+ (self areIntegers: rcvr and: arg) ifTrue:
+ ["The C code can avoid detagging since tagged integers are still signed.
+ But this means the simulator must override to do detagging."
+ self cCode: '' inSmalltalk: [^self booleanCheat: (self integerValueOf: rcvr) <= (self integerValueOf: arg)].
+ ^ self booleanCheat: rcvr <= arg].
+
+ self initPrimCall.
+ aBool := self primitiveFloatLessOrEqual: rcvr toArg: arg.
+ self successful ifTrue: [^self booleanCheat: aBool].
+
+ messageSelector := self specialSelector: 4.
+ argumentCount := 1.
+ self normalSend! !
+!TSendNode methodsFor: 'printing' stamp: 'eem 9/18/2010 11:05' prior: 38343734!
+printOn: aStream level: level
+ | possiblyParenthesize |
+ possiblyParenthesize :=
+ [:node :newLevel|
+ (node isSend
+ and: [node selector precedence >= 3]) ifTrue:
+ [aStream nextPut: $(].
+ node printOn: aStream level: newLevel.
+ (node isSend
+ and: [node selector precedence >= 3]) ifTrue:
+ [aStream nextPut: $)]].
+
+ possiblyParenthesize value: receiver value: level.
+ arguments size = 0 ifTrue:
+ [aStream space; nextPutAll: selector.
+ ^self].
+ selector keywords with: arguments do:
+ [:keyword :arg |
+ aStream space; nextPutAll: keyword; space.
+ possiblyParenthesize value: arg value: level + 1]! !
+!SimpleStackBasedCogit methodsFor: 'primitive generators' stamp: 'anon 9/18/2010 11:44' prior: 38798984!
+genDoubleArithmetic: arithmeticOperator preOpCheck: preOpCheckOrNil
+ "Stack looks like
+ receiver (also in ResultReceiverReg)
+ arg
+ return address"
+ <var: #preOpCheckOrNil declareC: 'AbstractInstruction *(*preOpCheckOrNil)(int rcvrReg, int argReg)'>
+ | jumpFailClass jumpFailAlloc jumpFailCheck jumpSmallInt doOp fail |
+ <var: #jumpFailClass type: #'AbstractInstruction *'>
+ <var: #jumpFailAlloc type: #'AbstractInstruction *'>
+ <var: #jumpSmallInt type: #'AbstractInstruction *'>
+ <var: #jumpFailCheck type: #'AbstractInstruction *'>
+ <var: #doOp type: #'AbstractInstruction *'>
+ <var: #fail type: #'AbstractInstruction *'>
+ self MoveMw: BytesPerWord r: SPReg R: TempReg.
+ objectRepresentation genGetDoubleValueOf: ReceiverResultReg into: DPFPReg0.
+ self MoveR: TempReg R: ClassReg.
+ jumpSmallInt := objectRepresentation genJumpSmallIntegerInScratchReg: TempReg.
+ objectRepresentation genGetCompactClassIndexNonIntOf: ClassReg into: SendNumArgsReg.
+ self CmpCq: coInterpreter classFloatCompactIndex R: SendNumArgsReg.
+ jumpFailClass := self JumpNonZero: 0.
+ objectRepresentation genGetDoubleValueOf: ClassReg into: DPFPReg1.
+ doOp := self Label.
+ preOpCheckOrNil ifNotNil:
+ [jumpFailCheck := self perform: preOpCheckOrNil with: DPFPReg0 with: DPFPReg1].
+ self gen: arithmeticOperator operand: DPFPReg1 operand: DPFPReg0.
+ jumpFailAlloc := objectRepresentation
+ genAllocFloatValue: DPFPReg0
+ into: SendNumArgsReg
+ scratchReg: ClassReg
+ scratchReg: TempReg.
+ self MoveR: SendNumArgsReg R: ReceiverResultReg.
+ self flag: 'currently caller pushes result'.
+ self RetN: BytesPerWord * 2.
+ jumpSmallInt jmpTarget: self Label.
+ objectRepresentation genConvertSmallIntegerToIntegerInScratchReg: ClassReg.
+ self ConvertR: ClassReg Rd: DPFPReg1.
+ self Jump: doOp.
+ jumpFailAlloc jmpTarget: self Label.
+ self compileInterpreterPrimitive: (coInterpreter
+ functionPointerForCompiledMethod: methodObj
+ primitiveIndex: primitiveIndex).
+ fail := self Label.
+ jumpFailClass jmpTarget: self Label.
+ preOpCheckOrNil ifNotNil:
+ [jumpFailCheck jmpTarget: fail].
+ ^0! !
+
+| 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 ]!
+
+"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 ]!
+
+VMMaker
+ generate: StackInterpreter
+ to: (FileDirectory default / '../stacksrc') fullName
+ platformDir: (FileDirectory default / '../platforms') fullName
+ excluding: (InterpreterPlugin withAllSubclasses collect: [:ea| ea name])!
+
+----QUIT----{18 September 2010 . 11:56:53 am} VMMaker-Squeak4.1.image priorSource: 5243491!
\ No newline at end of file

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

Modified: branches/Cog/src/vm/cogit.c
===================================================================
--- branches/Cog/src/vm/cogit.c 2010-09-14 02:30:48 UTC (rev 2308)
+++ branches/Cog/src/vm/cogit.c 2010-09-18 19:08:00 UTC (rev 2309)
@@ -1,9 +1,9 @@
 /* Automatically generated by
- CCodeGenerator VMMaker-oscog.20 uuid: 528a9b5e-293c-4fac-9430-1eabdb0d278d
+ CCodeGenerator VMMaker-oscog.28 uuid: abd2e918-6a30-45ec-b5ed-11a563fb8c04
    from
- SimpleStackBasedCogit VMMaker-oscog.20 uuid: 528a9b5e-293c-4fac-9430-1eabdb0d278d
+ SimpleStackBasedCogit VMMaker-oscog.28 uuid: abd2e918-6a30-45ec-b5ed-11a563fb8c04
  */
-static char __buildInfo[] = "SimpleStackBasedCogit VMMaker-oscog.20 uuid: 528a9b5e-293c-4fac-9430-1eabdb0d278d " __DATE__ ;
+static char __buildInfo[] = "SimpleStackBasedCogit VMMaker-oscog.28 uuid: abd2e918-6a30-45ec-b5ed-11a563fb8c04 " __DATE__ ;
 char *__cogitBuildInfo = __buildInfo;
 
 
@@ -501,7 +501,7 @@
 static CogMethod * fillInMethodHeadersizeselector(CogMethod *method, sqInt size, sqInt selector);
 static CogMethod * fillInOPICHeadersizenumArgsselector(CogMethod *pic, sqInt size, sqInt numArgs, sqInt selector);
 static usqInt findBlockMethodWithStartMcpcbcpc(sqInt blockEntryPC, sqInt startBcpc);
-static CogBlockMethod * findEnclosingMethodForinHomeMethod(sqInt mcpc, CogMethod *cogMethod);
+CogBlockMethod * findEnclosingMethodForinHomeMethod(sqInt mcpc, CogMethod *cogMethod);
 static sqInt findMapLocationForMcpcinMethod(sqInt targetMcpc, CogMethod *cogMethod);
 CogBlockMethod * findMethodForStartBcpcinHomeMethod(sqInt startbcpc, CogMethod *cogMethod);
 static usqInt findMinAndMaxMethodsPCaround(sqInt blockEntryPC, sqInt mcpc);
@@ -518,7 +518,9 @@
 static sqInt genConvertSmallIntegerToIntegerInScratchReg(sqInt scratchReg);
 static void genDivRRQuoRem(AbstractInstruction * self_in_genDivRRQuoRem, sqInt abstractRegDivisor, sqInt abstractRegDividend, sqInt abstractRegQuotient, sqInt abstractRegRemainder);
 static sqInt genDoubleArithmetic(sqInt arithmeticOperator);
+static sqInt genDoubleArithmeticpreOpCheck(sqInt arithmeticOperator, AbstractInstruction *(*preOpCheckOrNil)(int rcvrReg, int argReg));
 static sqInt genDoubleComparison(AbstractInstruction *(*jumpOpcodeGenerator)(void *));
+static AbstractInstruction * genDoubleFailIfZeroArgRcvrarg(sqInt rcvrReg, sqInt argReg);
 static void (*genEnilopmartForandcalled(sqInt regArg1, sqInt regArg2, char *trampolineName))(void) ;
 static void (*genEnilopmartForcalled(sqInt regArg, char *trampolineName))(void) ;
 static sqInt genExtendedSendBytecode(void);
@@ -6304,7 +6306,7 @@
  If the method contains blocks then, because block dispatch is not in
  order, enumerate the block dispatch and find the nearest preceeding entry. */
 
-static CogBlockMethod *
+CogBlockMethod *
 findEnclosingMethodForinHomeMethod(sqInt mcpc, CogMethod *cogMethod) {
  assert(((cogMethod->cmType)) == CMMethod);
  if (((cogMethod->blockEntryOffset)) == 0) {
@@ -6687,6 +6689,58 @@
  return address */
 
 static sqInt
+genDoubleArithmeticpreOpCheck(sqInt arithmeticOperator, AbstractInstruction *(*preOpCheckOrNil)(int rcvrReg, int argReg)) {
+    AbstractInstruction *doOp;
+    AbstractInstruction *fail;
+    AbstractInstruction *jumpFailAlloc;
+    AbstractInstruction *jumpFailCheck;
+    AbstractInstruction *jumpFailClass;
+    AbstractInstruction *jumpSmallInt;
+
+ gMoveMwrR(BytesPerWord, SPReg, TempReg);
+ genGetDoubleValueOfinto(ReceiverResultReg, DPFPReg0);
+ gMoveRR(TempReg, ClassReg);
+ jumpSmallInt = genJumpSmallIntegerInScratchReg(TempReg);
+ genGetCompactClassIndexNonIntOfinto(ClassReg, SendNumArgsReg);
+ gCmpCqR(classFloatCompactIndex(), SendNumArgsReg);
+ jumpFailClass = gJumpNonZero(0);
+ genGetDoubleValueOfinto(ClassReg, DPFPReg1);
+ doOp = gLabel();
+ if (preOpCheckOrNil == null) {
+ null;
+ }
+ else {
+ jumpFailCheck = preOpCheckOrNil(DPFPReg0, DPFPReg1);
+ }
+ genoperandoperand(arithmeticOperator, DPFPReg1, DPFPReg0);
+ jumpFailAlloc = genAllocFloatValueintoscratchRegscratchReg(DPFPReg0, SendNumArgsReg, ClassReg, TempReg);
+ gMoveRR(SendNumArgsReg, ReceiverResultReg);
+ flag("currently caller pushes result");
+ gRetN(BytesPerWord * 2);
+ jmpTarget(jumpSmallInt, gLabel());
+ genConvertSmallIntegerToIntegerInScratchReg(ClassReg);
+ gConvertRRd(ClassReg, DPFPReg1);
+ gJump(doOp);
+ jmpTarget(jumpFailAlloc, gLabel());
+ compileInterpreterPrimitive(functionPointerForCompiledMethodprimitiveIndex(methodObj, primitiveIndex));
+ fail = gLabel();
+ jmpTarget(jumpFailClass, gLabel());
+ if (preOpCheckOrNil == null) {
+ null;
+ }
+ else {
+ jmpTarget(jumpFailCheck, fail);
+ }
+ return 0;
+}
+
+
+/* Stack looks like
+ receiver (also in ResultReceiverReg)
+ arg
+ return address */
+
+static sqInt
 genDoubleComparison(AbstractInstruction *(*jumpOpcodeGenerator)(void *)) {
     AbstractInstruction *compare;
     AbstractInstruction *jumpFail;
@@ -6719,7 +6773,15 @@
  return 0;
 }
 
+static AbstractInstruction *
+genDoubleFailIfZeroArgRcvrarg(sqInt rcvrReg, sqInt argReg) {
+ gMoveCqR(0, TempReg);
+ gConvertRRd(TempReg, DPFPReg2);
+ gCmpRdRd(DPFPReg2, argReg);
+ return gJumpFPEqual(0);
+}
 
+
 /* An enilopmart (the reverse of a trampoline) is a piece of code that makes
  the system-call-like transition from the C runtime into generated machine
  code. The desired arguments and entry-point are pushed on a stackPage's
@@ -8133,12 +8195,12 @@
 
 static sqInt
 genPrimitiveFloatAdd(void) {
- return genDoubleArithmetic(AddRdRd);
+ return genDoubleArithmeticpreOpCheck(AddRdRd, null);
 }
 
 static sqInt
 genPrimitiveFloatDivide(void) {
- return genDoubleArithmetic(DivRdRd);
+ return genDoubleArithmeticpreOpCheck(DivRdRd, genDoubleFailIfZeroArgRcvrarg);
 }
 
 static sqInt
@@ -8168,7 +8230,7 @@
 
 static sqInt
 genPrimitiveFloatMultiply(void) {
- return genDoubleArithmetic(MulRdRd);
+ return genDoubleArithmeticpreOpCheck(MulRdRd, null);
 }
 
 static sqInt
@@ -8198,7 +8260,7 @@
 
 static sqInt
 genPrimitiveFloatSubtract(void) {
- return genDoubleArithmetic(SubRdRd);
+ return genDoubleArithmeticpreOpCheck(SubRdRd, null);
 }
 
 static sqInt

Modified: branches/Cog/src/vm/cogit.h
===================================================================
--- branches/Cog/src/vm/cogit.h 2010-09-14 02:30:48 UTC (rev 2308)
+++ branches/Cog/src/vm/cogit.h 2010-09-18 19:08:00 UTC (rev 2309)
@@ -1,5 +1,5 @@
 /* Automatically generated by
- CCodeGenerator VMMaker-oscog.20 uuid: 528a9b5e-293c-4fac-9430-1eabdb0d278d
+ CCodeGenerator VMMaker-oscog.28 uuid: abd2e918-6a30-45ec-b5ed-11a563fb8c04
  */
 
 
@@ -26,6 +26,7 @@
 void compactCogCompiledCode(void);
 void enterCogCodePopReceiver(void);
 void enterCogCodePopReceiverAndClassRegs(void);
+CogBlockMethod * findEnclosingMethodForinHomeMethod(sqInt mcpc, CogMethod *cogMethod);
 CogBlockMethod * findMethodForStartBcpcinHomeMethod(sqInt startbcpc, CogMethod *cogMethod);
 sqInt genQuickReturnConst(void);
 sqInt genQuickReturnInstVar(void);

Modified: branches/Cog/src/vm/cogmethod.h
===================================================================
--- branches/Cog/src/vm/cogmethod.h 2010-09-14 02:30:48 UTC (rev 2308)
+++ branches/Cog/src/vm/cogmethod.h 2010-09-18 19:08:00 UTC (rev 2309)
@@ -1,5 +1,5 @@
 /* Automatically generated by
- CCodeGenerator VMMaker-oscog.20 uuid: 528a9b5e-293c-4fac-9430-1eabdb0d278d
+ CCodeGenerator VMMaker-oscog.28 uuid: abd2e918-6a30-45ec-b5ed-11a563fb8c04
  */
 
 typedef struct {

Modified: branches/Cog/src/vm/cointerp.c
===================================================================
--- branches/Cog/src/vm/cointerp.c 2010-09-14 02:30:48 UTC (rev 2308)
+++ branches/Cog/src/vm/cointerp.c 2010-09-18 19:08:00 UTC (rev 2309)
@@ -1,9 +1,9 @@
 /* Automatically generated by
- CCodeGeneratorGlobalStructure VMMaker-oscog.27 uuid: 7bc4e8e8-b779-4140-8698-5cde0d003c0f
+ CCodeGeneratorGlobalStructure VMMaker-oscog.28 uuid: abd2e918-6a30-45ec-b5ed-11a563fb8c04
    from
- CoInterpreter VMMaker-oscog.27 uuid: 7bc4e8e8-b779-4140-8698-5cde0d003c0f
+ CoInterpreter VMMaker-oscog.28 uuid: abd2e918-6a30-45ec-b5ed-11a563fb8c04
  */
-static char __buildInfo[] = "CoInterpreter VMMaker-oscog.27 uuid: 7bc4e8e8-b779-4140-8698-5cde0d003c0f " __DATE__ ;
+static char __buildInfo[] = "CoInterpreter VMMaker-oscog.28 uuid: abd2e918-6a30-45ec-b5ed-11a563fb8c04 " __DATE__ ;
 char *__interpBuildInfo = __buildInfo;
 
 
@@ -1814,7 +1814,7 @@
  /* 575 */ (void (*)(void))0,
  0 };
 static void (*externalPrimitiveTable[MaxExternalPrimitiveTableSize + 1 /* 4097 */])(void);
-const char *interpreterVersion = "Croquet Closure Cog VM [CoInterpreter VMMaker-oscog.27]";
+const char *interpreterVersion = "Croquet Closure Cog VM [CoInterpreter VMMaker-oscog.28]";
 static volatile int sendTrace;
 sqInt suppressHeartbeatFlag;
 
@@ -6832,8 +6832,8 @@
  }
  /* begin initPrimCall */
  GIV(primFailCode) = 0;
- /* begin primitiveFloatGreater:thanArg: */
- VM_LABEL(1primitiveFloatGreaterthanArg);
+ /* begin primitiveFloatLessOrEqual:toArg: */
+ VM_LABEL(0primitiveFloatLessOrEqualtoArg);
  /* begin loadFloatOrIntFrom: */
  if ((rcvr & 1)) {
  rcvr1 = ((double) ((rcvr >> 1)) );
@@ -6958,7 +6958,7 @@
  }
  arg1 = result1;
  l35: /* end loadFloatOrIntFrom: */;
- aBool = rcvr1 > arg1;
+ aBool = rcvr1 <= arg1;
  if (GIV(primFailCode) == 0) {
  /* begin booleanCheat: */
  VM_LABEL(5booleanCheat);
@@ -6970,7 +6970,7 @@
  localSP += 2 * BytesPerWord;
  if ((bytecode1 < 160)
  && (bytecode1 > 151)) {
- if (!aBool) {
+ if (aBool) {
  /* begin fetchNextBytecode */
  currentBytecode = byteAtPointer(++localIP);
  goto l33;
@@ -6987,7 +6987,7 @@
  /* long jumpIfFalse */
 
  offset1 = byteAtPointer(++localIP);
- if (!aBool) {
+ if (aBool) {
  /* begin fetchNextBytecode */
  currentBytecode = byteAtPointer(++localIP);
  goto l33;
@@ -7002,7 +7002,7 @@
  localIP -= 1;
  /* begin fetchNextBytecode */
  currentBytecode = byteAtPointer(++localIP);
- if (!aBool) {
+ if (aBool) {
  /* begin internalPush: */
  longAtPointerput(localSP -= BytesPerWord, GIV(trueObj));
  }
@@ -7095,8 +7095,8 @@
  }
  /* begin initPrimCall */
  GIV(primFailCode) = 0;
- /* begin primitiveFloatLess:thanArg: */
- VM_LABEL(1primitiveFloatLessthanArg);
+ /* begin primitiveFloatGreaterOrEqual:toArg: */
+ VM_LABEL(0primitiveFloatGreaterOrEqualtoArg);
  /* begin loadFloatOrIntFrom: */
  if ((rcvr & 1)) {
  rcvr1 = ((double) ((rcvr >> 1)) );
@@ -7221,7 +7221,7 @@
  }
  arg1 = result1;
  l40: /* end loadFloatOrIntFrom: */;
- aBool = rcvr1 < arg1;
+ aBool = rcvr1 >= arg1;
  if (GIV(primFailCode) == 0) {
  /* begin booleanCheat: */
  VM_LABEL(7booleanCheat);
@@ -7233,7 +7233,7 @@
  localSP += 2 * BytesPerWord;
  if ((bytecode1 < 160)
  && (bytecode1 > 151)) {
- if (!aBool) {
+ if (aBool) {
  /* begin fetchNextBytecode */
  currentBytecode = byteAtPointer(++localIP);
  goto l38;
@@ -7250,7 +7250,7 @@
  /* long jumpIfFalse */
 
  offset1 = byteAtPointer(++localIP);
- if (!aBool) {
+ if (aBool) {
  /* begin fetchNextBytecode */
  currentBytecode = byteAtPointer(++localIP);
  goto l38;
@@ -7265,7 +7265,7 @@
  localIP -= 1;
  /* begin fetchNextBytecode */
  currentBytecode = byteAtPointer(++localIP);
- if (!aBool) {
+ if (aBool) {
  /* begin internalPush: */
  longAtPointerput(localSP -= BytesPerWord, GIV(trueObj));
  }

Modified: branches/Cog/src/vm/cointerp.h
===================================================================
--- branches/Cog/src/vm/cointerp.h 2010-09-14 02:30:48 UTC (rev 2308)
+++ branches/Cog/src/vm/cointerp.h 2010-09-18 19:08:00 UTC (rev 2309)
@@ -1,5 +1,5 @@
 /* Automatically generated by
- CCodeGeneratorGlobalStructure VMMaker-oscog.27 uuid: 7bc4e8e8-b779-4140-8698-5cde0d003c0f
+ CCodeGeneratorGlobalStructure VMMaker-oscog.28 uuid: abd2e918-6a30-45ec-b5ed-11a563fb8c04
  */
 
 

Modified: branches/Cog/src/vm/gcc3x-cointerp.c
===================================================================
--- branches/Cog/src/vm/gcc3x-cointerp.c 2010-09-14 02:30:48 UTC (rev 2308)
+++ branches/Cog/src/vm/gcc3x-cointerp.c 2010-09-18 19:08:00 UTC (rev 2309)
@@ -2,11 +2,11 @@
 
 
 /* Automatically generated by
- CCodeGeneratorGlobalStructure VMMaker-oscog.27 uuid: 7bc4e8e8-b779-4140-8698-5cde0d003c0f
+ CCodeGeneratorGlobalStructure VMMaker-oscog.28 uuid: abd2e918-6a30-45ec-b5ed-11a563fb8c04
    from
- CoInterpreter VMMaker-oscog.27 uuid: 7bc4e8e8-b779-4140-8698-5cde0d003c0f
+ CoInterpreter VMMaker-oscog.28 uuid: abd2e918-6a30-45ec-b5ed-11a563fb8c04
  */
-static char __buildInfo[] = "CoInterpreter VMMaker-oscog.27 uuid: 7bc4e8e8-b779-4140-8698-5cde0d003c0f " __DATE__ ;
+static char __buildInfo[] = "CoInterpreter VMMaker-oscog.28 uuid: abd2e918-6a30-45ec-b5ed-11a563fb8c04 " __DATE__ ;
 char *__interpBuildInfo = __buildInfo;
 
 
@@ -1817,7 +1817,7 @@
  /* 575 */ (void (*)(void))0,
  0 };
 static void (*externalPrimitiveTable[MaxExternalPrimitiveTableSize + 1 /* 4097 */])(void);
-const char *interpreterVersion = "Croquet Closure Cog VM [CoInterpreter VMMaker-oscog.27]";
+const char *interpreterVersion = "Croquet Closure Cog VM [CoInterpreter VMMaker-oscog.28]";
 static volatile int sendTrace;
 sqInt suppressHeartbeatFlag;
 
@@ -6836,8 +6836,8 @@
  }
  /* begin initPrimCall */
  GIV(primFailCode) = 0;
- /* begin primitiveFloatGreater:thanArg: */
- VM_LABEL(1primitiveFloatGreaterthanArg);
+ /* begin primitiveFloatLessOrEqual:toArg: */
+ VM_LABEL(0primitiveFloatLessOrEqualtoArg);
  /* begin loadFloatOrIntFrom: */
  if ((rcvr & 1)) {
  rcvr1 = ((double) ((rcvr >> 1)) );
@@ -6962,7 +6962,7 @@
  }
  arg1 = result1;
  l35: /* end loadFloatOrIntFrom: */;
- aBool = rcvr1 > arg1;
+ aBool = rcvr1 <= arg1;
  if (GIV(primFailCode) == 0) {
  /* begin booleanCheat: */
  VM_LABEL(5booleanCheat);
@@ -6974,7 +6974,7 @@
  localSP += 2 * BytesPerWord;
  if ((bytecode1 < 160)
  && (bytecode1 > 151)) {
- if (!aBool) {
+ if (aBool) {
  /* begin fetchNextBytecode */
  currentBytecode = byteAtPointer(++localIP);
  goto l33;
@@ -6991,7 +6991,7 @@
  /* long jumpIfFalse */
 
  offset1 = byteAtPointer(++localIP);
- if (!aBool) {
+ if (aBool) {
  /* begin fetchNextBytecode */
  currentBytecode = byteAtPointer(++localIP);
  goto l33;
@@ -7006,7 +7006,7 @@
  localIP -= 1;
  /* begin fetchNextBytecode */
  currentBytecode = byteAtPointer(++localIP);
- if (!aBool) {
+ if (aBool) {
  /* begin internalPush: */
  longAtPointerput(localSP -= BytesPerWord, GIV(trueObj));
  }
@@ -7099,8 +7099,8 @@
  }
  /* begin initPrimCall */
  GIV(primFailCode) = 0;
- /* begin primitiveFloatLess:thanArg: */
- VM_LABEL(1primitiveFloatLessthanArg);
+ /* begin primitiveFloatGreaterOrEqual:toArg: */
+ VM_LABEL(0primitiveFloatGreaterOrEqualtoArg);
  /* begin loadFloatOrIntFrom: */
  if ((rcvr & 1)) {
  rcvr1 = ((double) ((rcvr >> 1)) );
@@ -7225,7 +7225,7 @@
  }
  arg1 = result1;
  l40: /* end loadFloatOrIntFrom: */;
- aBool = rcvr1 < arg1;
+ aBool = rcvr1 >= arg1;
  if (GIV(primFailCode) == 0) {
  /* begin booleanCheat: */
  VM_LABEL(7booleanCheat);
@@ -7237,7 +7237,7 @@
  localSP += 2 * BytesPerWord;
  if ((bytecode1 < 160)
  && (bytecode1 > 151)) {
- if (!aBool) {
+ if (aBool) {
  /* begin fetchNextBytecode */
  currentBytecode = byteAtPointer(++localIP);
  goto l38;
@@ -7254,7 +7254,7 @@
  /* long jumpIfFalse */
 
  offset1 = byteAtPointer(++localIP);
- if (!aBool) {
+ if (aBool) {
  /* begin fetchNextBytecode */
  currentBytecode = byteAtPointer(++localIP);
  goto l38;
@@ -7269,7 +7269,7 @@
  localIP -= 1;
  /* begin fetchNextBytecode */
  currentBytecode = byteAtPointer(++localIP);
- if (!aBool) {
+ if (aBool) {
  /* begin internalPush: */
  longAtPointerput(localSP -= BytesPerWord, GIV(trueObj));
  }

Modified: branches/Cog/src/vm/interp.h
===================================================================
--- branches/Cog/src/vm/interp.h 2010-09-14 02:30:48 UTC (rev 2308)
+++ branches/Cog/src/vm/interp.h 2010-09-18 19:08:00 UTC (rev 2309)
@@ -1,5 +1,5 @@
 /* Automatically generated by
- CCodeGeneratorGlobalStructure VMMaker-oscog.27 uuid: 7bc4e8e8-b779-4140-8698-5cde0d003c0f
+ CCodeGeneratorGlobalStructure VMMaker-oscog.28 uuid: abd2e918-6a30-45ec-b5ed-11a563fb8c04
  */
 
 #define COGVM 1

Modified: branches/Cog/stacksrc/vm/gcc3x-interp.c
===================================================================
--- branches/Cog/stacksrc/vm/gcc3x-interp.c 2010-09-14 02:30:48 UTC (rev 2308)
+++ branches/Cog/stacksrc/vm/gcc3x-interp.c 2010-09-18 19:08:00 UTC (rev 2309)
@@ -2,11 +2,11 @@
 
 
 /* Automatically generated by
- CCodeGeneratorGlobalStructure VMMaker-oscog.27 uuid: 7bc4e8e8-b779-4140-8698-5cde0d003c0f
+ CCodeGeneratorGlobalStructure VMMaker-oscog.28 uuid: abd2e918-6a30-45ec-b5ed-11a563fb8c04
    from
- StackInterpreter VMMaker-oscog.27 uuid: 7bc4e8e8-b779-4140-8698-5cde0d003c0f
+ StackInterpreter VMMaker-oscog.28 uuid: abd2e918-6a30-45ec-b5ed-11a563fb8c04
  */
-static char __buildInfo[] = "StackInterpreter VMMaker-oscog.27 uuid: 7bc4e8e8-b779-4140-8698-5cde0d003c0f " __DATE__ ;
+static char __buildInfo[] = "StackInterpreter VMMaker-oscog.28 uuid: abd2e918-6a30-45ec-b5ed-11a563fb8c04 " __DATE__ ;
 char *__interpBuildInfo = __buildInfo;
 
 
@@ -1599,7 +1599,7 @@
  0 };
 char * breakSelector;
 sqInt breakSelectorLength = -1;
-const char *interpreterVersion = "Croquet Closure Stack VM [StackInterpreter VMMaker-oscog.27]";
+const char *interpreterVersion = "Croquet Closure Stack VM [StackInterpreter VMMaker-oscog.28]";
 static volatile int sendTrace;
 sqInt suppressHeartbeatFlag;
 
@@ -6290,8 +6290,8 @@
  }
  /* begin initPrimCall */
  GIV(primFailCode) = 0;
- /* begin primitiveFloatGreater:thanArg: */
- VM_LABEL(1primitiveFloatGreaterthanArg);
+ /* begin primitiveFloatLessOrEqual:toArg: */
+ VM_LABEL(0primitiveFloatLessOrEqualtoArg);
  /* begin loadFloatOrIntFrom: */
  if ((rcvr & 1)) {
  rcvr1 = ((double) ((rcvr >> 1)) );
@@ -6416,7 +6416,7 @@
  }
  arg1 = result1;
  l35: /* end loadFloatOrIntFrom: */;
- aBool = rcvr1 > arg1;
+ aBool = rcvr1 <= arg1;
  if (GIV(primFailCode) == 0) {
  /* begin booleanCheat: */
  VM_LABEL(5booleanCheat);
@@ -6428,7 +6428,7 @@
  localSP += 2 * BytesPerWord;
  if ((bytecode1 < 160)
  && (bytecode1 > 151)) {
- if (!aBool) {
+ if (aBool) {
  /* begin fetchNextBytecode */
  currentBytecode = byteAtPointer(++localIP);
  goto l33;
@@ -6445,7 +6445,7 @@
  /* long jumpIfFalse */
 
  offset1 = byteAtPointer(++localIP);
- if (!aBool) {
+ if (aBool) {
  /* begin fetchNextBytecode */
  currentBytecode = byteAtPointer(++localIP);
  goto l33;
@@ -6460,7 +6460,7 @@
  localIP -= 1;
  /* begin fetchNextBytecode */
  currentBytecode = byteAtPointer(++localIP);
- if (!aBool) {
+ if (aBool) {
  /* begin internalPush: */
  longAtPointerput(localSP -= BytesPerWord, GIV(trueObj));
  }
@@ -6553,8 +6553,8 @@
  }
  /* begin initPrimCall */
  GIV(primFailCode) = 0;
- /* begin primitiveFloatLess:thanArg: */
- VM_LABEL(1primitiveFloatLessthanArg);
+ /* begin primitiveFloatGreaterOrEqual:toArg: */
+ VM_LABEL(0primitiveFloatGreaterOrEqualtoArg);
  /* begin loadFloatOrIntFrom: */
  if ((rcvr & 1)) {
  rcvr1 = ((double) ((rcvr >> 1)) );
@@ -6679,7 +6679,7 @@
  }
  arg1 = result1;
  l40: /* end loadFloatOrIntFrom: */;
- aBool = rcvr1 < arg1;
+ aBool = rcvr1 >= arg1;
  if (GIV(primFailCode) == 0) {
  /* begin booleanCheat: */
  VM_LABEL(7booleanCheat);
@@ -6691,7 +6691,7 @@
  localSP += 2 * BytesPerWord;
  if ((bytecode1 < 160)
  && (bytecode1 > 151)) {
- if (!aBool) {
+ if (aBool) {
  /* begin fetchNextBytecode */
  currentBytecode = byteAtPointer(++localIP);
  goto l38;
@@ -6708,7 +6708,7 @@
  /* long jumpIfFalse */
 
  offset1 = byteAtPointer(++localIP);
- if (!aBool) {
+ if (aBool) {
  /* begin fetchNextBytecode */
  currentBytecode = byteAtPointer(++localIP);
  goto l38;
@@ -6723,7 +6723,7 @@
  localIP -= 1;
  /* begin fetchNextBytecode */
  currentBytecode = byteAtPointer(++localIP);
- if (!aBool) {
+ if (aBool) {
  /* begin internalPush: */
  longAtPointerput(localSP -= BytesPerWord, GIV(trueObj));
  }

Modified: branches/Cog/stacksrc/vm/interp.c
===================================================================
--- branches/Cog/stacksrc/vm/interp.c 2010-09-14 02:30:48 UTC (rev 2308)
+++ branches/Cog/stacksrc/vm/interp.c 2010-09-18 19:08:00 UTC (rev 2309)
@@ -1,9 +1,9 @@
 /* Automatically generated by
- CCodeGeneratorGlobalStructure VMMaker-oscog.27 uuid: 7bc4e8e8-b779-4140-8698-5cde0d003c0f
+ CCodeGeneratorGlobalStructure VMMaker-oscog.28 uuid: abd2e918-6a30-45ec-b5ed-11a563fb8c04
    from
- StackInterpreter VMMaker-oscog.27 uuid: 7bc4e8e8-b779-4140-8698-5cde0d003c0f
+ StackInterpreter VMMaker-oscog.28 uuid: abd2e918-6a30-45ec-b5ed-11a563fb8c04
  */
-static char __buildInfo[] = "StackInterpreter VMMaker-oscog.27 uuid: 7bc4e8e8-b779-4140-8698-5cde0d003c0f " __DATE__ ;
+static char __buildInfo[] = "StackInterpreter VMMaker-oscog.28 uuid: abd2e918-6a30-45ec-b5ed-11a563fb8c04 " __DATE__ ;
 char *__interpBuildInfo = __buildInfo;
 
 
@@ -1596,7 +1596,7 @@
  0 };
 char * breakSelector;
 sqInt breakSelectorLength = -1;
-const char *interpreterVersion = "Croquet Closure Stack VM [StackInterpreter VMMaker-oscog.27]";
+const char *interpreterVersion = "Croquet Closure Stack VM [StackInterpreter VMMaker-oscog.28]";
 static volatile int sendTrace;
 sqInt suppressHeartbeatFlag;
 
@@ -6286,8 +6286,8 @@
  }
  /* begin initPrimCall */
  GIV(primFailCode) = 0;
- /* begin primitiveFloatGreater:thanArg: */
- VM_LABEL(1primitiveFloatGreaterthanArg);
+ /* begin primitiveFloatLessOrEqual:toArg: */
+ VM_LABEL(0primitiveFloatLessOrEqualtoArg);
  /* begin loadFloatOrIntFrom: */
  if ((rcvr & 1)) {
  rcvr1 = ((double) ((rcvr >> 1)) );
@@ -6412,7 +6412,7 @@
  }
  arg1 = result1;
  l35: /* end loadFloatOrIntFrom: */;
- aBool = rcvr1 > arg1;
+ aBool = rcvr1 <= arg1;
  if (GIV(primFailCode) == 0) {
  /* begin booleanCheat: */
  VM_LABEL(5booleanCheat);
@@ -6424,7 +6424,7 @@
  localSP += 2 * BytesPerWord;
  if ((bytecode1 < 160)
  && (bytecode1 > 151)) {
- if (!aBool) {
+ if (aBool) {
  /* begin fetchNextBytecode */
  currentBytecode = byteAtPointer(++localIP);
  goto l33;
@@ -6441,7 +6441,7 @@
  /* long jumpIfFalse */
 
  offset1 = byteAtPointer(++localIP);
- if (!aBool) {
+ if (aBool) {
  /* begin fetchNextBytecode */
  currentBytecode = byteAtPointer(++localIP);
  goto l33;
@@ -6456,7 +6456,7 @@
  localIP -= 1;
  /* begin fetchNextBytecode */
  currentBytecode = byteAtPointer(++localIP);
- if (!aBool) {
+ if (aBool) {
  /* begin internalPush: */
  longAtPointerput(localSP -= BytesPerWord, GIV(trueObj));
  }
@@ -6549,8 +6549,8 @@
  }
  /* begin initPrimCall */
  GIV(primFailCode) = 0;
- /* begin primitiveFloatLess:thanArg: */
- VM_LABEL(1primitiveFloatLessthanArg);
+ /* begin primitiveFloatGreaterOrEqual:toArg: */
+ VM_LABEL(0primitiveFloatGreaterOrEqualtoArg);
  /* begin loadFloatOrIntFrom: */
  if ((rcvr & 1)) {
  rcvr1 = ((double) ((rcvr >> 1)) );
@@ -6675,7 +6675,7 @@
  }
  arg1 = result1;
  l40: /* end loadFloatOrIntFrom: */;
- aBool = rcvr1 < arg1;
+ aBool = rcvr1 >= arg1;
  if (GIV(primFailCode) == 0) {
  /* begin booleanCheat: */
  VM_LABEL(7booleanCheat);
@@ -6687,7 +6687,7 @@
  localSP += 2 * BytesPerWord;
  if ((bytecode1 < 160)
  && (bytecode1 > 151)) {
- if (!aBool) {
+ if (aBool) {
  /* begin fetchNextBytecode */
  currentBytecode = byteAtPointer(++localIP);
  goto l38;
@@ -6704,7 +6704,7 @@
  /* long jumpIfFalse */
 
  offset1 = byteAtPointer(++localIP);
- if (!aBool) {
+ if (aBool) {
  /* begin fetchNextBytecode */
  currentBytecode = byteAtPointer(++localIP);
  goto l38;
@@ -6719,7 +6719,7 @@
  localIP -= 1;
  /* begin fetchNextBytecode */
  currentBytecode = byteAtPointer(++localIP);
- if (!aBool) {
+ if (aBool) {
  /* begin internalPush: */
  longAtPointerput(localSP -= BytesPerWord, GIV(trueObj));
  }

Modified: branches/Cog/stacksrc/vm/interp.h
===================================================================
--- branches/Cog/stacksrc/vm/interp.h 2010-09-14 02:30:48 UTC (rev 2308)
+++ branches/Cog/stacksrc/vm/interp.h 2010-09-18 19:08:00 UTC (rev 2309)
@@ -1,5 +1,5 @@
 /* Automatically generated by
- CCodeGeneratorGlobalStructure VMMaker-oscog.27 uuid: 7bc4e8e8-b779-4140-8698-5cde0d003c0f
+ CCodeGeneratorGlobalStructure VMMaker-oscog.28 uuid: abd2e918-6a30-45ec-b5ed-11a563fb8c04
  */
 
 #define STACKVM 1