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

commits at source.squeak.org commits at source.squeak.org
Thu Dec 29 17:07:15 UTC 2016


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

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

Name: VMMaker.oscog-eem.2057
Author: eem
Time: 29 December 2016, 9:06:52.675429 am
UUID: 183112c3-adba-4e59-870e-c99e09343e23
Ancestors: VMMaker.oscog-eem.2056

SmartSyntaxPluginSimulator:

Fix several bugs with smart syntax operations (cPtrAsOop asSmallIntegerObj et al) that weren't being simulated.

Delete Object>>primitive: and implement it in SmartSyntaxInterpreterPlugin & SmartSyntaxPluginSimulator to be able to collect the signatures of zero-arg smart syntax prims.

Extend SmartSyntaxPluginSimulator instantiation to include a simulator subclass if one exists (the simulatorClass has to remain SmartSyntaxPluginSimulator to get the wrapping and marshalling on forwarding to work).

Fix returning self in SmartSyntaxPluginSimulator>>doesNotUnderstand:

Implement the ccgLoad:*andThen: methods.

FIx coercion of the byteArrayArg in the FilePluginSimulator read and write methods.

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

Item was changed:
  ----- Method: CArray>>cPtrAsOop (in category 'accessing') -----
  cPtrAsOop
+ 	ptrOffset = 0 ifFalse: [self error: 'offset must be zero'].
+ 	^arrayBaseAddress - interpreter baseHeaderSize!
- 	^arrayBaseAddress + ptrOffset!

Item was changed:
  ----- Method: FilePluginSimulator>>sqFile:Read:Into:At: (in category 'simulation') -----
  sqFile: file Read: count Into: byteArrayIndexArg At: startIndex
  	| interpreter byteArrayIndex |
  	interpreter := interpreterProxy interpreter.
+ 	byteArrayIndex := byteArrayIndexArg asInteger. "Coerces CArray et al correctly"
- 	byteArrayIndex := byteArrayIndexArg isInteger ifTrue: [byteArrayIndexArg] ifFalse: [byteArrayIndexArg cPtrAsOop].
  	[[startIndex to: startIndex + count - 1 do:
  		[ :i |
  		file atEnd ifTrue:
  			[(file isKindOf: FakeStdinStream) ifTrue: [file atEnd: false].
  			 ^i - startIndex].
  		interpreter
  			byteAt: byteArrayIndex + i
  			put: (file next ifNil: [(file isKindOf: FakeStdinStream) ifTrue: [^0]] ifNotNil: [:c| c asInteger])]]
  			on: Error
  			do: [:ex|
  				(file isKindOf: TranscriptStream) ifFalse: [ex pass].
  				^0]]
  		ensure: [self recordStateOf: file].
  	^count!

Item was changed:
  ----- Method: FilePluginSimulator>>sqFile:Write:From:At: (in category 'simulation') -----
  sqFile: file Write: count From: byteArrayIndexArg At: startIndex
  	| interpreter byteArrayIndex |
  	interpreter := interpreterProxy interpreter.
+ 	byteArrayIndex := byteArrayIndexArg asInteger. "Coerces CArray et al correctly"
- 	byteArrayIndex := byteArrayIndexArg isInteger ifTrue: [byteArrayIndexArg] ifFalse: [byteArrayIndexArg cPtrAsOop].
  	file isBinary
  		ifTrue:
  			[startIndex to: startIndex + count - 1 do:
  				[ :i | file nextPut: (interpreter byteAt: byteArrayIndex + i)]]
  		ifFalse:
  			[startIndex to: startIndex + count - 1 do:
  				[ :i | | byte |
  				byte := interpreter byteAt: byteArrayIndex + i.
  				file nextPut: (Character value: (byte == 12 "lf" ifTrue: [15"cr"] ifFalse: [byte]))]].
  	self recordStateOf: file.
  	^count!

Item was added:
+ ----- Method: Integer>>asCharPtr (in category '*VMMaker-interpreter simulator') -----
+ asCharPtr
+ 	^(Notification new tag: #getSimulator; signal)
+ 		ifNotNil: [:simulator| self coerceTo: #'char *' sim: simulator getInterpreter]
+ 		ifNil: [self]!

Item was added:
+ ----- Method: Integer>>asSmallIntegerObj (in category '*VMMaker-interpreter simulator') -----
+ asSmallIntegerObj
+ 	^(Notification new tag: #getSimulator; signal)
+ 		ifNotNil: [:simulator| simulator getInterpreter integerObjectOf: self]
+ 		ifNil: [self]!

Item was removed:
- ----- Method: Object>>asSmallIntegerObj (in category '*VMMaker-translation support') -----
- asSmallIntegerObj
- 
- 	^self!

Item was removed:
- ----- Method: Object>>primitive: (in category '*VMMaker-translation support') -----
- primitive: primName
- 	"For translation only; noop when running in Smalltalk."!

Item was added:
+ ----- Method: SmartSyntaxInterpreterPlugin>>primitive: (in category 'simulation') -----
+ primitive: primName
+ 	<doNotGenerate>
+ 	^simulator primitive: primName!

Item was changed:
  InterpreterPlugin subclass: #SmartSyntaxPluginSimulator
+ 	instanceVariableNames: 'actualPlugin signatureMap forMap pluginClass'
- 	instanceVariableNames: 'actualPlugin signatureMap forMap'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-SmartSyntaxPlugins'!

Item was changed:
  ----- Method: SmartSyntaxPluginSimulator class>>newFor: (in category 'simulation') -----
  newFor: anUnsimulatedInterpreterPluginClass
+ 	| simulatorClass |
+ 	simulatorClass := anUnsimulatedInterpreterPluginClass subclasses
+ 						detect: [:sc| sc name endsWith: 'Simulator']
+ 						ifNone: [anUnsimulatedInterpreterPluginClass].
  	^self new
+ 		actualPlugin: simulatorClass new signatureClass: anUnsimulatedInterpreterPluginClass;
- 		actualPlugin: anUnsimulatedInterpreterPluginClass new;
  		yourself!

Item was removed:
- ----- Method: SmartSyntaxPluginSimulator>>actualPlugin: (in category 'accessing') -----
- actualPlugin: aSmartSyntaxInterpreterPlugin
- 	actualPlugin := aSmartSyntaxInterpreterPlugin.
- 	actualPlugin simulator: self!

Item was added:
+ ----- Method: SmartSyntaxPluginSimulator>>actualPlugin:signatureClass: (in category 'accessing') -----
+ actualPlugin: aSmartSyntaxInterpreterPlugin signatureClass: signatureClass
+ 	pluginClass := signatureClass.
+ 	actualPlugin := aSmartSyntaxInterpreterPlugin.
+ 	actualPlugin simulator: self!

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

Item was added:
+ ----- Method: SmartSyntaxPluginSimulator>>ccgLoad:expr:asFloatValueFrom: (in category 'simulation') -----
+ ccgLoad: codeGen expr: exprBlock asFloatValueFrom: stackIndex
+ 	self shouldBeImplemented!

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

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

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

Item was added:
+ ----- Method: SmartSyntaxPluginSimulator>>ccgLoad:expr:asUnsignedValueFrom: (in category 'simulation') -----
+ ccgLoad: codeGen expr: exprBlock asUnsignedValueFrom: stackIndex
+ 	self shouldBeImplemented!

Item was added:
+ ----- Method: SmartSyntaxPluginSimulator>>ccgLoad:expr:asWBFloatPtrFrom: (in category 'simulation') -----
+ ccgLoad: codeGen expr: exprBlock asWBFloatPtrFrom: stackIndex
+ 	self shouldBeImplemented!

Item was added:
+ ----- Method: SmartSyntaxPluginSimulator>>ccgValBlock: (in category 'simulation') -----
+ ccgValBlock: aString 
+ 	^aString caseOf: {
+ 		['isBytes']			-> [	[:oop|
+ 								 interpreterProxy success: (interpreterProxy isBytes: oop).
+ 								 oop]].
+ 		['isWordsOrBytes']	-> [	[:oop|
+ 								 interpreterProxy success: (interpreterProxy isWordsOrBytes: oop).
+ 								 oop]] }!

Item was changed:
  ----- Method: SmartSyntaxPluginSimulator>>computeSignatureMap (in category 'initialize') -----
  computeSignatureMap
  	forMap := true. "true only while we compute the signatureMap"
  	signatureMap := Dictionary new.
+ 	pluginClass selectorsAndMethodsDo:
- 	actualPlugin class selectorsAndMethodsDo:
  		[:s :m|
+ 		(m messages includesAnyOf: #(primitive: primitive:parameters: primitive:parameters:receiver:))
- 		(m messages includesAnyOf: #(primitive:parameters: primitive:parameters:receiver:))
  			ifTrue: [self getPrimitiveSignatureFor: s]
  			ifFalse:
  				[(m pragmaAt: #export:) ifNotNil:
  					[:exportPragma|
  					(exportPragma argumentAt: 1) ifTrue:
  						[self computeSignatureFor: s from: { #forMap. s. #(). nil }]]]].
  	forMap := false!

Item was changed:
  ----- Method: SmartSyntaxPluginSimulator>>doesNotUnderstand: (in category 'message forwarding') -----
  doesNotUnderstand: aMessage
  	| signature selector parameters result |
  	signature := signatureMap
  					at: aMessage selector
  					ifAbsent: [^super doesNotUnderstand: aMessage].
  	selector := signature first.
  	parameters := signature second.
  	signature third "receiver block" value: (interpreterProxy stackValue: parameters size).
  	interpreterProxy failed ifTrue:
  		[^nil].
  	result := [actualPlugin
  					perform: selector
  					withArguments: (parameters withIndexCollect:
  										[:block :index|
  										block value: (interpreterProxy stackValue: parameters size - index)])]
  					on: Notification
  					do: [:ex|
  						ex tag == #getSimulator
  							ifTrue: [ex resume: self]
  							ifFalse: [ex pass]].
  	interpreterProxy failed ifTrue:
  		[^nil].
+ 	result == actualPlugin ifTrue:
+ 		[interpreterProxy pop: interpreterProxy methodArgumentCount.
+ 		 ^nil].
  	interpreterProxy
  		pop: interpreterProxy methodArgumentCount + 1
  		thenPush: result.
  	^nil "SmartSyntaxPluginPrimitives return null"!

Item was added:
+ ----- Method: SmartSyntaxPluginSimulator>>primitive: (in category 'simulation') -----
+ primitive: primNameString
+ 	"If initializing, pass back the type signature.  If executing, answer nil."
+ 	^self primitive: primNameString parameters: #() receiver: nil!



More information about the Vm-dev mailing list