[Vm-dev] VM Maker: VMMaker.oscog-eem.2839.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Oct 13 16:34:25 UTC 2020


Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-eem.2839.mcz

==================== Summary ====================

Name: VMMaker.oscog-eem.2839
Author: eem
Time: 13 October 2020, 9:34:17.903415 am
UUID: 5eedee46-0fa4-447e-9120-9aebf820f065
Ancestors: VMMaker.oscog-eem.2838

Correct the coercion code.
- no longer have a catch-all in Object, requiring the relevant classes to coerce themselves explicitly.
- have Integer do its best to properly interpret C integer casts, including signed values, so that e.g. (self cCoerce: 65535 to: #short) = -1.
So far Float only deals with #float.
Have HostWindowPlugin use cCoerce:to:, not cCoerceSimple:to:

=============== Diff against VMMaker.oscog-eem.2838 ===============

Item was changed:
  ----- Method: Cogit>>cCoerce:to: (in category 'simulation only') -----
  cCoerce: value to: cTypeString
  	"Type coercion. For translation a cast will be emmitted. When running in Smalltalk
  	  answer a suitable wrapper for correct indexing."
  	<doNotGenerate>
+ 	^value coerceTo: cTypeString sim: objectMemory!
- 	^value
- 		ifNil: [value]
- 		ifNotNil: [value coerceTo: cTypeString sim: objectMemory]!

Item was added:
+ ----- Method: Float>>coerceTo:sim: (in category '*VMMaker-interpreter simulator') -----
+ coerceTo: cTypeString sim: interpreter
+ 
+ 	cTypeString = #'float' ifTrue:
+ 		[^self].
+ 	self halt!

Item was changed:
  ----- Method: HostWindowPlugin>>pointFromCompactPointEncoding: (in category 'support') -----
  pointFromCompactPointEncoding: encodedPoint
  	"Answer a point from one of the funky encoded x,y position/size values the VM uses.
  	 The issue here is that the values can be negative, each value being in the range -32768 to 32767"
  	<inline: #always>
  	^interpreterProxy
  		makePointwithxValue: (self cCoerceSimple: encodedPoint >> 16 to: #short)
+ 		yValue: (self cCoerce: (encodedPoint bitAnd: 16rFFFF) to: #short)!
- 		yValue: (self cCoerceSimple: (encodedPoint bitAnd: 16rFFFF) to: #short)!

Item was changed:
  ----- Method: Integer>>coerceTo:sim: (in category '*VMMaker-interpreter simulator') -----
  coerceTo: cTypeString sim: interpreter
  
+ 	| bits unitSize |
- 	| unitSize |
  	cTypeString last == $* ifTrue:  "C pointer"
  		[unitSize := cTypeString caseOf: {
  		[#'char *'] -> [1].
  		[#'short *'] -> [2].
  		[#'int *'] -> [4].
  		[#'long long *'] -> [8].
  		[#'float *'] -> [^CFloatArray basicNew interpreter: interpreter address: self unitSize: 4; yourself].
  		[#'double *'] -> [^CFloatArray basicNew interpreter: interpreter address: self unitSize: 8; yourself].
  		[#'unsigned *'] -> [4].
  		[#'unsigned int *'] -> [4].
  		[#'unsigned char *'] -> [1].
  		[#'signed char *'] -> [1].
  		[#'unsigned short *'] -> [2].
  		[#'unsigned long long *'] -> [8].
  		[#'oop *'] -> [interpreter objectMemory bytesPerOop].
  		}
  		otherwise: [interpreter objectMemory wordSize].
  		^CArray basicNew
  			interpreter: interpreter address: self unitSize: unitSize;
  			yourself].
  	cTypeString first == $u ifTrue:
+ 		[bits := cTypeString caseOf: {
+ 		[#usqInt] -> [interpreter objectMemory wordSize * 8].
+ 		[#usqLong] -> [64].
+ 		[#unsigned] -> [32].
+ 		[#'unsigned char'] -> [8].
+ 		[#'unsigned int'] -> [8].
+ 		[#'unsigned long'] -> [48]. "LLP64 on Windows :-("
+ 		[#'unsigned long long'] -> [64].
+ 		[#'unsigned short'] -> [16].
- 		[unitSize := cTypeString caseOf: {
- 		[#usqInt] -> [interpreter objectMemory wordSize].
- 		[#usqLong] -> [8].
- 		[#unsigned] -> [4].
- 		[#'unsigned int'] -> [4].
- 		[#'unsigned char'] -> [1].
- 		[#'unsigned long'] -> [6].
- 		[#'unsigned short'] -> [2].
- 		[#'unsigned long long'] -> [8].
  		}
+ 		otherwise: [self error: 'unknown unsigned integer type name'].
+ 		^self bitAnd: 1 << bits - 1].
+ 	bits := cTypeString caseOf: {
+ 		[#'sqIntptr_t'] -> [interpreter objectMemory wordSize * 8].
+ 		[#sqLong] -> [64].
+ 		[#char] -> [^self bitAnd: 255]. "char may be signed, may be unsigned; interpret as unsigned by default"
+ 		[#'signed char'] -> [8].
+ 		[#'short'] -> [16].
+ 		[#int] -> [32].
+ 		[#long] -> [48]. "LLP64 on Windows :-("
+ 		[#'long long'] -> [64].
+ 		}
+ 		otherwise: [self error: 'unknown signed integer type name'].
+ 	^(self bitAnd: (1 bitShift: bits) - 1) - ((self bitAnd: (1 bitShift: bits - 1)) bitShift: 1)!
- 		otherwise: [self error: 'unknown unsigned type name'].
- 		^self bitAnd: 1 << (8 * unitSize) - 1].
- 	^self  "C number (int, char, etc)"!

Item was changed:
  ----- Method: InterpreterPlugin>>cCoerce:to: (in category 'simulation') -----
  cCoerce: value to: cTypeString
  	<doNotGenerate>
+ 	^value coerceTo: cTypeString sim: interpreterProxy!
- 	"Type coercion for translation only; just return the value when running in Smalltalk.
- 	 This overrides the generic coercion method in VMClass.  For some reason we are the exception.
- 	 If we want that style of coercion we can send cCoerce:to: to interpreterProxy, not self."
- 
- 	^value isCArray
- 		ifTrue: [value coerceTo: cTypeString sim: interpreterProxy]
- 		ifFalse: [value]!

Item was changed:
  ----- Method: InterpreterProxy>>cCoerce:to: (in category 'simulation only') -----
  cCoerce: value to: cTypeString
  	"Type coercion. For translation a cast will be emitted. When running in Smalltalk
  	  answer a suitable wrapper for correct indexing."
+ 	^value coerceTo: cTypeString sim: self!
- 	^value
- 		ifNil: [value]
- 		ifNotNil: [value coerceTo: cTypeString sim: self]!

Item was removed:
- ----- Method: Object>>cCoerce:to: (in category '*VMMaker-translation support') -----
- cCoerce: value to: cType
- 	"Type coercion for translation only; just return the value when running in Smalltalk."
- 
- 	^ value!

Item was changed:
  ----- Method: SocketPluginSimulator>>cCoerce:to: (in category 'simulation') -----
  cCoerce: value to: cTypeString
  	"Type coercion for translation only; just return the value when running in Smalltalk.
  	 This overrides the generic coercion method in VMClass.  For some reason we are the exception.
  	 If we want that style of coercion we can send cCoerce:to: to interpreterProxy, not self."
  
+ 	^value
+ 		coerceTo: (cTypeString = #SocketPtr ifTrue: [#'char *'] ifFalse: [cTypeString])
+ 		sim: interpreterProxy!
- 	^cTypeString = #SocketPtr
- 		ifTrue: [value coerceTo: #'char *' sim: interpreterProxy]
- 		ifFalse: [super cCoerce: value to: cTypeString]!

Item was added:
+ ----- Method: UndefinedObject>>coerceTo:sim: (in category '*VMMaker-interpreter simulator') -----
+ coerceTo: cTypeString sim: interpreterSimulator
+ 	^self!

Item was changed:
  ----- Method: VMClass>>cCoerce:to: (in category 'memory access') -----
  cCoerce: value to: cTypeString
  	"Type coercion. For translation a cast will be emitted. When running in Smalltalk
  	  answer a suitable wrapper for correct indexing."
  	<doNotGenerate>
+ 	^value coerceTo: cTypeString sim: self!
- 	^value
- 		ifNil: [value]
- 		ifNotNil: [value coerceTo: cTypeString sim: self]!



More information about the Vm-dev mailing list