Nicolas Cellier uploaded a new version of VMMaker to project VM Maker Inbox: http://source.squeak.org/VMMakerInbox/VMMaker.oscog-nice.2540.mcz ==================== Summary ==================== Name: VMMaker.oscog-nice.2540 Author: nice Time: 21 August 2019, 7:57:54.88068 pm UUID: 4771da98-01f0-5141-b321-59c001f8390e Ancestors: VMMaker.oscog-nice.2539, VMMaker.oscog-eem.2537 Partial fix - Part 3 - for bug https://github.com/OpenSmalltalk/opensmalltalk-vm/issues/417 Remove the restriction about (SmallInteger asFloat exactness) from Spur64 loadFloatOrIntFrom: Replace it with the solution described in bug report if ( (double) si == sf ) return si <= (int64) sf; else return (double) si <= sf; Also merge VMMaker.oscog-eem.2537 because we need to regenerate cointerp.c THIS NEEDS TO BE REVIEWED I get unstable behavior of elementary GUI (scroll bars, splitters, etc...) or thing like (ColorValue veryveryLightGray hue) failing randomly... It depends on a test span = 0.0 where span is SmallInteger 0 =============== Diff against VMMaker.oscog-nice.2539 =============== Item was changed: ----- Method: InterpreterPrimitives>>primitiveSmallFloatEqual (in category 'arithmetic float primitives') ----- primitiveSmallFloatEqual <option: #Spur64BitMemoryManager> + | rcvr arg intArg | - | rcvr arg | <var: #rcvr type: #double> <var: #arg type: #double> rcvr := objectMemory smallFloatValueOf: (self stackValue: 1). arg := objectMemory loadFloatOrIntFrom: self stackTop. self successful ifTrue: + [self cppIf: objectMemory wordSize > 4 + ifTrue: [((self isIntegerObject: self stackTop) and: [rcvr = arg]) + ifTrue: + ["Resolve case of ambiguity so as to have comparison of exact values" + intArg := self integerValueOf: self stackTop. + self pop: 2 thenPushBool: rcvr asInteger = intArg] + ifFalse: [self pop: 2 thenPushBool: false]] + ifFalse: [self pop: 2 thenPushBool: rcvr = arg]]! - [self pop: 2 thenPushBool: rcvr = arg]! Item was changed: ----- Method: InterpreterPrimitives>>primitiveSmallFloatGreaterOrEqual (in category 'arithmetic float primitives') ----- primitiveSmallFloatGreaterOrEqual <option: #Spur64BitMemoryManager> + | rcvr arg intArg | - | rcvr arg | <var: #rcvr type: #double> <var: #arg type: #double> rcvr := objectMemory smallFloatValueOf: (self stackValue: 1). arg := objectMemory loadFloatOrIntFrom: self stackTop. self successful ifTrue: + [self cppIf: objectMemory wordSize > 4 + ifTrue: [((self isIntegerObject: self stackTop) and: [rcvr = arg]) + ifTrue: + ["Resolve case of ambiguity so as to have comparison of exact values" + intArg := self integerValueOf: self stackTop. + self pop: 2 thenPushBool: rcvr asInteger >= intArg] + ifFalse: [self pop: 2 thenPushBool: rcvr >= arg]] + ifFalse: [self pop: 2 thenPushBool: rcvr >= arg]]! - [self pop: 2 thenPushBool: rcvr >= arg]! Item was changed: ----- Method: InterpreterPrimitives>>primitiveSmallFloatGreaterThan (in category 'arithmetic float primitives') ----- primitiveSmallFloatGreaterThan <option: #Spur64BitMemoryManager> + | rcvr arg intArg | - | rcvr arg | <var: #rcvr type: #double> <var: #arg type: #double> rcvr := objectMemory smallFloatValueOf: (self stackValue: 1). arg := objectMemory loadFloatOrIntFrom: self stackTop. self successful ifTrue: + [self cppIf: objectMemory wordSize > 4 + ifTrue: [((self isIntegerObject: self stackTop) and: [rcvr = arg]) + ifTrue: + ["Resolve case of ambiguity so as to have comparison of exact values" + intArg := self integerValueOf: self stackTop. + self pop: 2 thenPushBool: rcvr asInteger > intArg] + ifFalse: [self pop: 2 thenPushBool: rcvr > arg]] + ifFalse: [self pop: 2 thenPushBool: rcvr > arg]]! - [self pop: 2 thenPushBool: rcvr > arg]! Item was changed: ----- Method: InterpreterPrimitives>>primitiveSmallFloatLessOrEqual (in category 'arithmetic float primitives') ----- primitiveSmallFloatLessOrEqual <option: #Spur64BitMemoryManager> + | rcvr arg intArg | - | rcvr arg | <var: #rcvr type: #double> <var: #arg type: #double> rcvr := objectMemory smallFloatValueOf: (self stackValue: 1). arg := objectMemory loadFloatOrIntFrom: self stackTop. self successful ifTrue: + [self cppIf: objectMemory wordSize > 4 + ifTrue: [((self isIntegerObject: self stackTop) and: [rcvr = arg]) + ifTrue: + ["Resolve case of ambiguity so as to have comparison of exact values" + intArg := self integerValueOf: self stackTop. + self pop: 2 thenPushBool: rcvr asInteger <= intArg] + ifFalse: [self pop: 2 thenPushBool: rcvr <= arg]] + ifFalse: [self pop: 2 thenPushBool: rcvr <= arg]]! - [self pop: 2 thenPushBool: rcvr <= arg]! Item was changed: ----- Method: InterpreterPrimitives>>primitiveSmallFloatLessThan (in category 'arithmetic float primitives') ----- primitiveSmallFloatLessThan <option: #Spur64BitMemoryManager> + | rcvr arg intArg | - | rcvr arg | <var: #rcvr type: #double> <var: #arg type: #double> rcvr := objectMemory smallFloatValueOf: (self stackValue: 1). arg := objectMemory loadFloatOrIntFrom: self stackTop. self successful ifTrue: + [self cppIf: objectMemory wordSize > 4 + ifTrue: [((self isIntegerObject: self stackTop) and: [rcvr = arg]) + ifTrue: + ["Resolve case of ambiguity so as to have comparison of exact values" + intArg := self integerValueOf: self stackTop. + self pop: 2 thenPushBool: rcvr asInteger < intArg] + ifFalse: [self pop: 2 thenPushBool: rcvr < arg]] + ifFalse: [self pop: 2 thenPushBool: rcvr < arg]]! - [self pop: 2 thenPushBool: rcvr < arg]! Item was changed: ----- Method: InterpreterPrimitives>>primitiveSmallFloatNotEqual (in category 'arithmetic float primitives') ----- primitiveSmallFloatNotEqual <option: #Spur64BitMemoryManager> + | rcvr arg intArg | - | rcvr arg | <var: #rcvr type: #double> <var: #arg type: #double> rcvr := objectMemory smallFloatValueOf: (self stackValue: 1). arg := objectMemory loadFloatOrIntFrom: self stackTop. self successful ifTrue: + [self cppIf: objectMemory wordSize > 4 + ifTrue: [((self isIntegerObject: self stackTop) and: [rcvr = arg]) + ifTrue: ["Resolve case of ambiguity so as to have comparison of exact values" + intArg := self integerValueOf: self stackTop. + self pop: 2 thenPushBool: (rcvr asInteger = intArg) not] + ifFalse: [self pop: 2 thenPushBool: true]] + ifFalse: [self pop: 2 thenPushBool: (rcvr = arg) not]]! - [self pop: 2 thenPushBool: (rcvr = arg) not]! Item was changed: ----- Method: InterpreterProxy>>methodReturnString: (in category 'stack access') ----- methodReturnString: aCString + "Attempt to answer a ByteString for a given C string as the result of a primitive." - "Sets the return value for a method." - "THIS IS DUBIOUS!! CONSIDER REMOVING IT!! RIGHT NOW IT IS NOT SENT." <var: 'aCString' type: #'char *'> + aCString + ifNil: [primFailCode := PrimErrOperationFailed] + ifNotNil: + [(self stringForCString: aCString) + ifNil: [primFailCode := PrimErrNoMemory] + ifNotNil: [:result| self pop: argumentCount+1 thenPush: result]]. - (self stringForCString: aCString) - ifNil: [primFailCode := PrimErrNoMemory] - ifNotNil: [:result| self pop: argumentCount+1 thenPush: result]. ^0! Item was changed: ----- Method: Spur64BitMemoryManager>>loadFloatOrIntFrom: (in category 'interpreter access') ----- loadFloatOrIntFrom: floatOrIntOop "If floatOrInt is an integer, then convert it to a C double float and return it. If it is a Float, then load its value and return it. Otherwise fail -- ie return with primErrorCode non-zero." <inline: true> <returnTypeC: #double> + | result tagBits | - | result tagBits shift | <var: #result type: #double> (tagBits := floatOrIntOop bitAnd: self tagMask) ~= 0 ifTrue: [tagBits = self smallFloatTag ifTrue: [^self smallFloatValueOf: floatOrIntOop]. + tagBits = self smallIntegerTag ifTrue: - (tagBits = self smallIntegerTag - and: [shift := 64 - self numTagBits - self smallFloatMantissaBits. - (self cCode: [floatOrIntOop << shift] - inSmalltalk: [floatOrIntOop << shift bitAnd: 1 << 64 - 1]) >>> shift = floatOrIntOop]) ifTrue: [^(self integerValueOf: floatOrIntOop) asFloat]] ifFalse: [(self classIndexOf: floatOrIntOop) = ClassFloatCompactIndex ifTrue: [self cCode: '' inSmalltalk: [result := Float new: 2]. self fetchFloatAt: floatOrIntOop + self baseHeaderSize into: result. ^result]]. coInterpreter primitiveFail. ^0.0! Item was changed: ----- Method: StackInterpreter>>methodReturnString: (in category 'plugin primitive support') ----- methodReturnString: aCString + "Attempt to answer a ByteString for a given C string as the result of a primitive." - "Sets the return value for a method." <var: 'aCString' type: #'char *'> + aCString + ifNil: [primFailCode := PrimErrOperationFailed] + ifNotNil: + [(self stringForCString: aCString) + ifNil: [primFailCode := PrimErrNoMemory] + ifNotNil: [:result| self pop: argumentCount+1 thenPush: result]]. - self pop: argumentCount+1 thenPush: (objectMemory stringForCString: aCString). ^0! Item was changed: ----- Method: StackInterpreter>>primitiveFloatEqual:toArg: (in category 'comparison float primitives') ----- primitiveFloatEqual: rcvrOop toArg: argOop | rcvr arg | <var: #rcvr type: #double> <var: #arg type: #double> rcvr := objectMemory loadFloatOrIntFrom: rcvrOop. arg := objectMemory loadFloatOrIntFrom: argOop. + self cppIf: objectMemory wordSize > 4 + ifTrue: [rcvr = arg + ifTrue: + [(self isIntegerObject: argOop) + ifTrue: + ["Resolve case of ambiguity so as to have comparison of exact values" + ^ rcvr asInteger = (self integerValueOf: argOop)] + ifFalse: [(self isIntegerObject: rcvrOop) + ifTrue: + ["Same when used from bytecodePrim... + note that rcvr and arg cannot be both integer (case is already handled)" + ^ (self integerValueOf: rcvrOop) = arg asInteger]]]]. ^rcvr = arg! Item was changed: ----- Method: StackInterpreter>>primitiveFloatGreater:thanArg: (in category 'comparison float primitives') ----- primitiveFloatGreater: rcvrOop thanArg: argOop | rcvr arg | <var: #rcvr type: #double> <var: #arg type: #double> rcvr := objectMemory loadFloatOrIntFrom: rcvrOop. arg := objectMemory loadFloatOrIntFrom: argOop. + self cppIf: objectMemory wordSize > 4 + ifTrue: [rcvr = arg + ifTrue: + [(self isIntegerObject: argOop) + ifTrue: + ["Resolve case of ambiguity so as to have comparison of exact values" + ^ rcvr asInteger > (self integerValueOf: argOop)] + ifFalse: [(self isIntegerObject: rcvrOop) + ifTrue: + ["Same when used from bytecodePrim... + note that rcvr and arg cannot be both integer (case is already handled)" + ^ (self integerValueOf: rcvrOop) > arg asInteger]]]]. ^rcvr > arg! Item was changed: ----- Method: StackInterpreter>>primitiveFloatGreaterOrEqual:toArg: (in category 'comparison float primitives') ----- primitiveFloatGreaterOrEqual: rcvrOop toArg: argOop | rcvr arg | <var: #rcvr type: #double> <var: #arg type: #double> rcvr := objectMemory loadFloatOrIntFrom: rcvrOop. arg := objectMemory loadFloatOrIntFrom: argOop. + self cppIf: objectMemory wordSize > 4 + ifTrue: [rcvr = arg + ifTrue: + [(self isIntegerObject: argOop) + ifTrue: + ["Resolve case of ambiguity so as to have comparison of exact values" + ^ rcvr asInteger >= (self integerValueOf: argOop)] + ifFalse: [(self isIntegerObject: rcvrOop) + ifTrue: + ["Same when used from bytecodePrim... + note that rcvr and arg cannot be both integer (case is already handled)" + ^ (self integerValueOf: rcvrOop) >= arg asInteger]]]]. ^rcvr >= arg! Item was changed: ----- Method: StackInterpreter>>primitiveFloatLess:thanArg: (in category 'comparison float primitives') ----- primitiveFloatLess: rcvrOop thanArg: argOop | rcvr arg | <var: #rcvr type: #double> <var: #arg type: #double> rcvr := objectMemory loadFloatOrIntFrom: rcvrOop. arg := objectMemory loadFloatOrIntFrom: argOop. + self cppIf: objectMemory wordSize > 4 + ifTrue: [rcvr = arg + ifTrue: + [(self isIntegerObject: argOop) + ifTrue: + ["Resolve case of ambiguity so as to have comparison of exact values" + ^ rcvr asInteger < (self integerValueOf: argOop)] + ifFalse: [(self isIntegerObject: rcvrOop) + ifTrue: + ["Same when used from bytecodePrim... + note that rcvr and arg cannot be both integer (case is already handled)" + ^ (self integerValueOf: rcvrOop) < arg asInteger]]]]. ^rcvr < arg! Item was changed: ----- Method: StackInterpreter>>primitiveFloatLessOrEqual:toArg: (in category 'comparison float primitives') ----- primitiveFloatLessOrEqual: rcvrOop toArg: argOop | rcvr arg | <var: #rcvr type: #double> <var: #arg type: #double> rcvr := objectMemory loadFloatOrIntFrom: rcvrOop. arg := objectMemory loadFloatOrIntFrom: argOop. + self cppIf: objectMemory wordSize > 4 + ifTrue: [rcvr = arg + ifTrue: + [(self isIntegerObject: argOop) + ifTrue: + ["Resolve case of ambiguity so as to have comparison of exact values" + ^ rcvr asInteger <= (self integerValueOf: argOop)] + ifFalse: [(self isIntegerObject: rcvrOop) + ifTrue: + ["Same when used from bytecodePrim... + note that rcvr and arg cannot be both integer (case is already handled)" + ^ (self integerValueOf: rcvrOop) <= arg asInteger]]]]. ^rcvr <= arg! |
Free forum by Nabble | Edit this page |