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

commits at source.squeak.org commits at source.squeak.org
Wed Dec 2 03:54:50 UTC 2020


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

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

Name: VMMaker.oscog-eem.2905
Author: eem
Time: 1 December 2020, 7:54:43.160518 pm
UUID: b2778a08-d45d-4f84-8467-21a8eccf46dc
Ancestors: VMMaker.oscog-eem.2904

Cogit: extend the assert in cogMethodContaining: to handle interruption at backward branches.  Rename ceCheckForInterrupts to ceCheckForInterrupt to match Cogit's ceCheckForInterruptTrampoline inst var.

SoundPlugin/SmartSyntaxPlugin Slang:Fix a compile-time warning due to a bad cast of firstIndexableField: for WordsOrBytes parameters.
Nuke usobsoleted generators (ccgLoad:expr:asCharPtrFrom: superceded by ccgLoad:expr:asCharPtrFrom:andThen:, etc).
Avoid the unnecessary cast of the void * return type of firstIndexableField to parameters.

Simulaiton:
Add SignedCArray and coercion between it and CArray.

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

Item was added:
+ ----- Method: BalloonArray>>beSigned (in category 'converting') -----
+ beSigned!

Item was added:
+ ----- Method: BalloonArray>>beUnsigned (in category 'converting') -----
+ beUnsigned
+ 	self shouldNotImplement!

Item was added:
+ ----- Method: CArray>>beSigned (in category 'converting') -----
+ beSigned
+ 	SignedCArray adoptInstance: self!

Item was added:
+ ----- Method: CArray>>beUnsigned (in category 'converting') -----
+ beUnsigned!

Item was changed:
  ----- Method: CArray>>coerceTo:sim: (in category 'converting') -----
  coerceTo: cTypeString sim: interpreterSimulator
  
  	^cTypeString caseOf: {
  		['int']				-> [self ptrAddress].
  		['float *']			-> [self asSingleFloatAccessor].
  		['double *']			-> [self asDoubleFloatAccessor].
+ 		['sqInt *']			-> [self shallowCopy unitSize: interpreter bytesPerOop; beSigned].
+ 		['unsigned int *']	-> [self shallowCopy unitSize: 4; beUnsigned].
+ 		['int *']				-> [self shallowCopy unitSize: 4; beSigned].
+ 		['unsigned short *']	-> [self shallowCopy unitSize: 2; beUnsigned].
+ 		['short *']			-> [self shallowCopy unitSize: 2; beSigned].
+ 		['unsigned char *']	-> [self shallowCopy unitSize: 1; beUnsigned].
+ 		['char *']			-> [self shallowCopy unitSize: 1; beSigned]. "C is ambivalent on the issue; sigh..."
- 		['sqInt *']			-> [self shallowCopy unitSize: interpreter bytesPerOop; yourself].
- 		['unsigned int *']	-> [self shallowCopy unitSize: 4; yourself].
- 		['int *']				-> [self shallowCopy unitSize: 4; yourself].
- 		['char *']			-> [self shallowCopy unitSize: 1; yourself].
- 		['unsigned char *']	-> [self shallowCopy unitSize: 1; yourself].
  		['unsigned']		-> [self ptrAddress].
  		['sqInt']				-> [self ptrAddress].
  		['usqInt']			-> [self ptrAddress].
  		['sqIntptr_t']		-> [self shallowCopy unitSize: interpreter bytesPerOop; yourself] }!

Item was added:
+ ----- Method: CFloatArray>>beSigned (in category 'converting') -----
+ beSigned!

Item was added:
+ ----- Method: CFloatArray>>beUnsigned (in category 'converting') -----
+ beUnsigned
+ 	self shouldNotImplement!

Item was added:
+ ----- Method: CoInterpreter>>ceCheckForInterrupt (in category 'trampolines') -----
+ ceCheckForInterrupt
+ 	<api>
+ 	| switched |
+ 	self cCode: [] inSmalltalk:
+ 		[self maybeCheckStackDepth: 0 sp: stackPointer pc: instructionPointer].
+ 	switched := self checkForEventsMayContextSwitch: true.
+ 	self returnToExecutive: false postContextSwitch: switched!

Item was removed:
- ----- Method: CoInterpreter>>ceCheckForInterrupts (in category 'trampolines') -----
- ceCheckForInterrupts
- 	<api>
- 	| switched |
- 	self cCode: [] inSmalltalk:
- 		[self maybeCheckStackDepth: 0 sp: stackPointer pc: instructionPointer].
- 	switched := self checkForEventsMayContextSwitch: true.
- 	self returnToExecutive: false postContextSwitch: switched!

Item was changed:
  ----- Method: CogMethodZone>>cogMethodContaining: (in category 'jit - api') -----
  cogMethodContaining: mcpc
  	"Answer the method containing mcpc for the purposes of code zone compaction,
  	 where mcpc is actually the value of instructionPointer at the time of a compaction."
  	<var: 'mcpc' type: #usqInt>
  	<api>
  	| cogMethod prevMethod |
  	mcpc > limitAddress ifTrue:
  		[^nil].
  	mcpc < baseAddress ifTrue:
  		[cogit assertMcpcIsPrimReturn: mcpc.
  		 ^nil].
  	self assert: mcpc < self limitZony.
  	cogMethod := coInterpreter cCoerceSimple: baseAddress to: #'CogMethod *'.
  	[cogMethod asUnsignedInteger < mcpc] whileTrue:
  		[prevMethod := cogMethod.
  		 cogMethod := self methodAfter: cogMethod].
  
  	"Since mcpc is actually instructionPointer we expect that it is either at the stack check
  	 (normal code zone reclamation invoked through checkForEventsMayContextSwitch:)
  	 or is in a primitive, immediately following the call of the C primitive routine."
  	self assert: (prevMethod notNil
  				and: [mcpc = (prevMethod asUnsignedInteger + prevMethod stackCheckOffset)
+ 					or: [(cogit backEnd isCallPrecedingReturnPC: mcpc)
+ 						and: [(coInterpreter
+ 									primitiveIndexOfMethod: prevMethod methodObject
+ 									header: prevMethod methodHeader) > 0
+ 							or: [(cogit backEnd callTargetFromReturnAddress: mcpc) = cogit ceCheckForInterruptTrampoline]]]]).
- 					or: [(coInterpreter
- 							primitiveIndexOfMethod: prevMethod methodObject
- 							header: prevMethod methodHeader) > 0
- 						and: [cogit backEnd isCallPrecedingReturnPC: mcpc]]]).
  	 ^prevMethod!

Item was added:
+ ----- Method: Cogit>>ceCheckForInterruptTrampoline (in category 'accessing') -----
+ ceCheckForInterruptTrampoline
+ 	<cmacro: '() ceCheckForInterruptTrampoline'>
+ 	^ceCheckForInterruptTrampoline!

Item was changed:
  ----- Method: Cogit>>genCheckForInterruptsTrampoline (in category 'initialization') -----
  genCheckForInterruptsTrampoline
  	<inline: true>
  	self zeroOpcodeIndex.
  	"if we have a link register we will assume that it does not get automatically pushed onto the stack
  	and thus there is no need to pop it before saving to instructionPointerAddress"
  	backEnd hasLinkRegister
  		ifTrue:
  			[self MoveR: LinkReg Aw: coInterpreter instructionPointerAddress]
  		ifFalse:
  			[self PopR: TempReg. "instruction pointer"
  			 self MoveR: TempReg Aw: coInterpreter instructionPointerAddress].
+ 	^self genTrampolineFor: #ceCheckForInterrupt
+ 		called: 'ceCheckForInterruptTrampoline'
- 	^self genTrampolineFor: #ceCheckForInterrupts
- 		called: 'ceCheckForInterruptsTrampoline'
  		numArgs: 0
  		arg: nil
  		arg: nil
  		arg: nil
  		arg: nil
  		regsToSave: self emptyRegisterMask
  		pushLinkReg: false
  		resultReg: NoReg
  		appendOpcodes: true!

Item was added:
+ CArray subclass: #SignedCArray
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-InterpreterSimulation'!

Item was added:
+ ----- Method: SignedCArray>>at: (in category 'accessing') -----
+ at: offset
+ 	| value |
+ 	value := super at: offset.
+ 	(value bitShift: unitSize * -8 + 1) = 0 ifTrue:
+ 		[^value].
+ 	^value - (1 bitShift: unitSize * 8)!

Item was added:
+ ----- Method: SignedCArray>>at:put: (in category 'accessing') -----
+ at: offset put: value
+ 	super
+ 		at: offset
+ 		put: (value >= 0
+ 				ifTrue: [value]
+ 				ifFalse: [value bitAnd: (1 bitShift: unitSize * 8) - 1]).
+ 	^value!

Item was added:
+ ----- Method: SignedCArray>>beSigned (in category 'converting') -----
+ beSigned!

Item was added:
+ ----- Method: SignedCArray>>beUnsigned (in category 'converting') -----
+ beUnsigned
+ 	CArray adoptInstance: self!

Item was removed:
- ----- Method: SmartSyntaxPluginAssignmentCodeGenerator>>ccgLoad:expr:asCharPtrFrom: (in category 'coercing') -----
- ccgLoad: aBlock expr: aString asCharPtrFrom: stackIndex
- 	^self assign: aString coerceTo: #'char *' from: stackIndex!

Item was removed:
- ----- Method: SmartSyntaxPluginAssignmentCodeGenerator>>ccgLoad:expr:asIntPtrFrom: (in category 'coercing') -----
- ccgLoad: aBlock expr: aString asIntPtrFrom: stackIndex
- 	^self assign: aString coerceTo: #'int *' from: stackIndex!

Item was removed:
- ----- Method: SmartSyntaxPluginAssignmentCodeGenerator>>ccgLoad:expr:asOopPtrFrom: (in category 'coercing') -----
- ccgLoad: aBlock expr: aString asOopPtrFrom: stackIndex
- 	^self assign: aString coerceTo: 'sqInt *' from: stackIndex!

Item was added:
+ ----- Method: SmartSyntaxPluginAssignmentCodeGenerator>>ccgLoad:expr:asShortPtrFrom:andThen: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asShortPtrFrom: stackIndex andThen: valBlock
+ 	^self assign: aString coerceTo: #'short *' from: stackIndex!

Item was removed:
- ----- Method: SmartSyntaxPluginCodeGenerator>>ccgLoad:expr:asCharPtrFrom: (in category 'coercing') -----
- ccgLoad: aBlock expr: aString asCharPtrFrom: anInteger
- 	"Answer codestring for character pointer to first indexable field of object (without validating side-effect), as described in comment to ccgLoad:expr:asRawOopFrom:"
- 
- 	^aBlock value: (String streamContents: [:aStream | aStream
- 		nextPutAll: 'self cCoerce: (interpreterProxy firstIndexableField:';
- 		crtab: 4;
- 		nextPutAll: '(interpreterProxy stackValue:';
- 		nextPutAll: anInteger asString;
- 		nextPutAll:	'))';
- 		crtab: 3;
- 		nextPutAll: 'to: ''char *'''])!

Item was changed:
  ----- Method: SmartSyntaxPluginCodeGenerator>>ccgLoad:expr:asCharPtrFrom:andThen: (in category 'coercing') -----
  ccgLoad: aBlock expr: aString asCharPtrFrom: anInteger andThen: valBlock
  	"Answer codestring for character pointer to first indexable field of object (without validating side-effect unless specified in valBlock), as described in comment to ccgLoad:expr:asRawOopFrom:"
  
+ 	^self ccgLoad: aBlock expr: aString asPtrFrom: anInteger andThen: valBlock!
- 	^(valBlock value: anInteger), '.',
- 	 (aBlock value: (String streamContents: [:aStream | aStream
- 		nextPutAll: 'self cCoerce: (interpreterProxy firstIndexableField:';
- 		crtab: 4;
- 		nextPutAll: '(interpreterProxy stackValue:';
- 		nextPutAll: anInteger asString;
- 		nextPutAll:	'))';
- 		crtab: 3;
- 		nextPutAll: 'to: ''char *''']))
- 	 !

Item was removed:
- ----- Method: SmartSyntaxPluginCodeGenerator>>ccgLoad:expr:asIntPtrFrom: (in category 'coercing') -----
- ccgLoad: aBlock expr: aString asIntPtrFrom: anInteger
- 	"Answer codestring for integer pointer to first indexable field of object (without validating side-effect), as described in comment to ccgLoad:expr:asRawOopFrom:"
- 
- 	^aBlock value: (String streamContents: [:aStream | aStream
- 		nextPutAll: 'self cCoerce: (interpreterProxy firstIndexableField:';
- 		crtab: 4;
- 		nextPutAll: '(interpreterProxy stackValue:';
- 		nextPutAll: anInteger asString;
- 		nextPutAll:	'))';
- 		crtab: 3;
- 		nextPutAll: 'to: ''int *'''])!

Item was changed:
  ----- Method: SmartSyntaxPluginCodeGenerator>>ccgLoad:expr:asIntPtrFrom:andThen: (in category 'coercing') -----
  ccgLoad: aBlock expr: aString asIntPtrFrom: anInteger andThen: valBlock
  	"Answer codestring for integer pointer to first indexable field of object (without validating side-effect unless specified in valBlock), as described in comment to ccgLoad:expr:asRawOopFrom:"
  
+ 	^self ccgLoad: aBlock expr: aString asPtrFrom: anInteger andThen: valBlock!
- 	^(valBlock value: anInteger), '.',
- 	 (aBlock value: (String streamContents: [:aStream | aStream
- 		nextPutAll: 'self cCoerce: (interpreterProxy firstIndexableField:';
- 		crtab: 4;
- 		nextPutAll: '(interpreterProxy stackValue:';
- 		nextPutAll: anInteger asString;
- 		nextPutAll:	'))';
- 		crtab: 3;
- 		nextPutAll: 'to: ''int *''']))!

Item was removed:
- ----- Method: SmartSyntaxPluginCodeGenerator>>ccgLoad:expr:asOopPtrFrom: (in category 'coercing') -----
- ccgLoad: aBlock expr: aString asOopPtrFrom: anInteger
- 	"Answer codestring for integer pointer to first indexable field of object (without validating side-effect), as described in comment to ccgLoad:expr:asRawOopFrom:"
- 
- 	^aBlock value: (String streamContents:
- 		[:aStream |
- 		 aStream
- 			nextPutAll: 'self cCoerce: (interpreterProxy firstIndexableField:';
- 			crtab: 4;
- 			nextPutAll: '(interpreterProxy stackValue:';
- 			print: anInteger;
- 			nextPutAll:	'))';
- 			crtab: 3;
- 			nextPutAll: 'to: ''sqInt *'''])!

Item was changed:
  ----- Method: SmartSyntaxPluginCodeGenerator>>ccgLoad:expr:asOopPtrFrom:andThen: (in category 'coercing') -----
  ccgLoad: aBlock expr: aString asOopPtrFrom: anInteger andThen: valBlock
  	"Answer codestring for integer pointer to first indexable field of object (without validating side-effect unless specified in valBlock), as described in comment to ccgLoad:expr:asRawOopFrom:"
  
+ 	^self ccgLoad: aBlock expr: aString asPtrFrom: anInteger andThen: valBlock!
- 	^(valBlock value: anInteger), '.',
- 	 (aBlock value: (String streamContents:
- 		[:aStream |
- 		aStream
- 			nextPutAll: 'self cCoerce: (interpreterProxy firstIndexableField:';
- 			crtab: 4;
- 			nextPutAll: '(interpreterProxy stackValue:';
- 			print: anInteger;
- 			nextPutAll:	'))';
- 			crtab: 3;
- 			nextPutAll: 'to: ''sqInt *''']))!

Item was added:
+ ----- Method: SmartSyntaxPluginCodeGenerator>>ccgLoad:expr:asPtrFrom:andThen: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asPtrFrom: anInteger andThen: valBlock
+ 	"Answer codestring for void pointer to first indexable field of object (without validating side-effect unless specified in valBlock), as described in comment to ccgLoad:expr:asRawOopFrom:"
+ 
+ 	^(valBlock value: anInteger),
+ 	  '.',
+ 	  (aBlock value: 'interpreterProxy firstIndexableField:(interpreterProxy stackValue:', anInteger asString, '))')!

Item was added:
+ ----- Method: SmartSyntaxPluginCodeGenerator>>ccgLoad:expr:asShortPtrFrom:andThen: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asShortPtrFrom: anInteger andThen: valBlock
+ 	^self ccgLoad: aBlock expr: aString asPtrFrom: anInteger andThen: valBlock!

Item was changed:
  ----- Method: SmartSyntaxPluginCodeGenerator>>ccgLoad:expr:asUnsignedLong64PtrFrom:andThen: (in category 'coercing') -----
  ccgLoad: aBlock expr: aString asUnsignedLong64PtrFrom: anInteger andThen: valBlock
  	"Answer a codestring for integer pointer to first indexable field of object (without validating side-effect unless specified in valBlock), as described in comment to ccgLoad:expr:asRawOopFrom:"
  
+ 	^self ccgLoad: aBlock expr: aString asPtrFrom: anInteger andThen: valBlock!
- 	^(valBlock value: anInteger), '.',
- 	 (aBlock value: (String streamContents: [:aStream | aStream
- 		nextPutAll: 'self cCoerce: (interpreterProxy firstIndexableField:';
- 		crtab: 4;
- 		nextPutAll: '(interpreterProxy stackValue:';
- 		nextPutAll: anInteger asString;
- 		nextPutAll:	'))';
- 		crtab: 3;
- 		nextPutAll: 'to: ''unsigned long long *''']))!

Item was changed:
  ----- Method: SmartSyntaxPluginCodeGenerator>>ccgLoad:expr:asUnsignedPtrFrom:andThen: (in category 'coercing') -----
  ccgLoad: aBlock expr: aString asUnsignedPtrFrom: anInteger andThen: valBlock
  	"Answer a codestring for integer pointer to first indexable field of object (without validating side-effect unless specified in valBlock), as described in comment to ccgLoad:expr:asRawOopFrom:"
  
+ 	^self ccgLoad: aBlock expr: aString asPtrFrom: anInteger andThen: valBlock!
- 	^(valBlock value: anInteger), '.',
- 	 (aBlock value: (String streamContents: [:aStream | aStream
- 		nextPutAll: 'self cCoerce: (interpreterProxy firstIndexableField:';
- 		crtab: 4;
- 		nextPutAll: '(interpreterProxy stackValue:';
- 		nextPutAll: anInteger asString;
- 		nextPutAll:	'))';
- 		crtab: 3;
- 		nextPutAll: 'to: ''unsigned *''']))!

Item was changed:
  ----- Method: SmartSyntaxPluginCodeGenerator>>ccgLoad:expr:asUnsignedShortPtrFrom:andThen: (in category 'coercing') -----
  ccgLoad: aBlock expr: aString asUnsignedShortPtrFrom: anInteger andThen: valBlock
  	"Answer a codestring for integer pointer to first indexable field of object (without validating side-effect unless specified in valBlock), as described in comment to ccgLoad:expr:asRawOopFrom:"
  
+ 	^self ccgLoad: aBlock expr: aString asPtrFrom: anInteger andThen: valBlock!
- 	^(valBlock value: anInteger), '.',
- 	 (aBlock value: (String streamContents: [:aStream | aStream
- 		nextPutAll: 'self cCoerce: (interpreterProxy firstIndexableField:';
- 		crtab: 4;
- 		nextPutAll: '(interpreterProxy stackValue:';
- 		nextPutAll: anInteger asString;
- 		nextPutAll:	'))';
- 		crtab: 3;
- 		nextPutAll: 'to: ''unsigned short *''']))!

Item was added:
+ ----- Method: SmartSyntaxPluginSimulator>>ccgLoad:expr:asShortPtrFrom:andThen: (in category 'simulation') -----
+ ccgLoad: codeGen expr: exprBlock asShortPtrFrom: stackIndex andThen: validateBlock
+ 	^[:oop|
+ 	   validateBlock value: oop.
+ 	   interpreterProxy cCoerce: (interpreterProxy firstIndexableField: oop) asInteger to: #'short *']!

Item was removed:
- ----- Method: SmartSyntaxPluginValidationCodeGenerator>>ccgLoad:expr:asCharPtrFrom: (in category 'coercing') -----
- ccgLoad: aBlock expr: aString asCharPtrFrom: stackIndex
- 	^self loadAs: #isWordsOrBytes: from: stackIndex!

Item was removed:
- ----- Method: SmartSyntaxPluginValidationCodeGenerator>>ccgLoad:expr:asIntPtrFrom: (in category 'coercing') -----
- ccgLoad: aBlock expr: aString asIntPtrFrom: stackIndex
- 	^self loadAs: #isWordsOrBytes: from: stackIndex!

Item was removed:
- ----- Method: SmartSyntaxPluginValidationCodeGenerator>>ccgLoad:expr:asOopPtrFrom: (in category 'coercing') -----
- ccgLoad: aBlock expr: aString asOopPtrFrom: stackIndex
- 	^self loadAs: #isNonImmediate: from: stackIndex!

Item was added:
+ ----- Method: SmartSyntaxPluginValidationCodeGenerator>>ccgLoad:expr:asShortPtrFrom:andThen: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asShortPtrFrom: stackIndex andThen: validationString
+ 	^validationString, (self stackAccessorFor: stackIndex)!

Item was changed:
  ----- Method: WordsOrShorts class>>ccg:prolog:expr:index: (in category 'plugin generation') -----
  ccg: cg prolog: aBlock expr: aString index: anInteger
  
  	^cg 
  		ccgLoad: aBlock 
  		expr: aString 
+ 		asShortPtrFrom: anInteger
- 		asCharPtrFrom: anInteger
  		andThen: (cg ccgValBlock: 'isWordsOrShorts')!



More information about the Vm-dev mailing list