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

commits at source.squeak.org commits at source.squeak.org
Thu Sep 19 01:10:36 UTC 2019


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

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

Name: VMMaker.oscog-eem.2565
Author: eem
Time: 18 September 2019, 6:10:19.899413 pm
UUID: 4878d905-e31e-4027-9660-593effe84ebc
Ancestors: VMMaker.oscog-cb.2564

Cogit:
Eliminate a bogus assert in compileFullBlockMethodFrameBuild: (and explain why).
Use #= to compare integers in isNonForwarderReceiver: instead of #==.

Simulator:
Also add some Socket simulation (sorry Nicolas, we're working on trhe same thing.  My version is correct, because I created the Socket simulation; forgive me for discarding your changes).

These get as far as primitiveSocketListenWithOrWithoutBacklog which breaks the hack used to invoke the smart-syntax methods.

To be clear we should discard VMMaker.oscog-nice.2565 and continue from these changes.

Fix some errors in initializing in-image compilation and include full blocks in the pc mapping tests.

Nuke the now obsolete Cogit>>sizeof:, and fix four instances of a comment typo.

=============== Diff against VMMaker.oscog-cb.2564 ===============

Item was changed:
  ----- Method: Cogit class>>initializedInstanceForTests: (in category 'in-image compilation support') -----
  initializedInstanceForTests: optionsDictionaryOrArray
  	"Answer an instance of a Cogit suitable for running tests that has initialized
  	 its method zone (generated trampolines etc)"
  	| cogit coInterpreter |
  	cogit := self instanceForTests: optionsDictionaryOrArray.
  	coInterpreter := CurrentImageCoInterpreterFacade forCogit: cogit.
  	[cogit
  		setInterpreter: coInterpreter;
  		singleStep: true;
+ 		initializeCodeZoneFrom: 1024 upTo: coInterpreter memory byteSize.
- 		initializeCodeZoneFrom: 1024 upTo: coInterpreter memory size.
  	 cogit methodZone freeStart: (cogit methodZone freeStart roundUpTo: 1024)]
  		on: Notification
  		do: [:ex|
  			(ex messageText beginsWith: 'cannot find receiver for') ifTrue:
  				[ex resume: coInterpreter].
  			ex pass].
  	^cogit!

Item was changed:
  ----- Method: Cogit class>>testPCMappingSelect:options: (in category 'tests') -----
  testPCMappingSelect: aBlock options: optionsDictionaryOrArray
  	"Test pc mapping both ways using a selection of the methods in the current image."
  	| cogit coInterpreter n |
  	cogit := self initializedInstanceForTests: optionsDictionaryOrArray.
  	coInterpreter := cogit coInterpreter.
  	n := -1.
  	SystemNavigation new allSelect:
+ 		[:m| | retrym cm |
+ 		 (m isQuick not
+ 		  and: [aBlock value: m]) ifTrue:
- 		[:m| | cm |
- 		(m isQuick not
- 		 and: [aBlock value: m]) ifTrue:
  			[(n := n + 1) \\ 10 = 0 ifTrue: [Transcript nextPut: $.; flush].
+ 			 retrym := true.
+ 			 [(cm := cogit
- 			 cm := cogit
  						cog: (coInterpreter oopForObject: m)
+ 						selector: (coInterpreter oopForObject: m selector)) isNil and: [retrym]] whileTrue:
+ 				[retrym := false.
+ 				 cogit methodZone clearCogCompiledCode.
+ 				 coInterpreter initializeObjectMap].
+ 			  cm
+ 				ifNil: [Transcript halt show: 'After 1 Cog compiled code compaction, still not able to generate the cog method...']
+ 				ifNotNil: [cogit testPCMappingForCompiledMethod: m cogMethod: cm].
+ 			 m encoderClass supportsFullBlocks ifTrue:
+ 				[m nestedBlockMethods do:
+ 					[:bm| | retryb cbm |			
+ 					 (n := n + 1) \\ 10 = 0 ifTrue: [Transcript nextPut: $,; flush].
+ 					 retryb := true.
+ 					 [(cbm := cogit
+ 								cogFullBlockMethod: (coInterpreter oopForObject: bm)
+ 								numCopied: bm numCopiedValues) isNil and: [retryb]] whileTrue:
+ 						[retryb := false.
+ 						 cogit methodZone clearCogCompiledCode.
+ 						 coInterpreter initializeObjectMap].
+ 					  cbm
+ 						ifNil: [Transcript show: 'After 1 Cog compiled code compaction, still not able to generate the cog block...']
+ 						ifNotNil: [cogit testPCMappingForCompiledMethod: bm cogMethod: cbm]]]].
- 						selector: (coInterpreter oopForObject: m selector).
- 			  cm ifNil:
- 				[cogit methodZone clearCogCompiledCode.
- 				 coInterpreter initializeObjectMap.
- 				 cm := cogit
- 							cog: (coInterpreter oopForObject: m)
- 							selector: (coInterpreter oopForObject: m selector).
- 				cm ifNil: [Transcript show: 'After 1 Cog compiled code compaction, still not able to generate the cog method...' ] ].
- 			  cm ifNotNil:
- 				[cogit testPCMappingForCompiledMethod: m cogMethod: cm]].
  		 false]!

Item was removed:
- ----- Method: Cogit>>sizeof: (in category 'translation support') -----
- sizeof: aCType
- 	<doNotGenerate>
- 	| bfc |
- 	aCType == #BytecodeFixup ifTrue:
- 		[bfc := self class bytecodeFixupClass.
- 		 ^bfc alignedByteSizeOf: bfc forClient: self].
- 	^super sizeof: aCType!

Item was changed:
  ----- Method: SocketPlugin>>primitiveSocket:getOptions: (in category 'primitives') -----
  primitiveSocket: socket getOptions: optionName
- 
  	| s optionNameStart optionNameSize returnedValue errorCode results |
  	<var: #s type: #SocketPtr>
  	<var: #optionNameStart type: #'char *'>
+ 	self primitive: 'primitiveSocketGetOptions' parameters: #(Oop Oop).
- 	self primitive: 'primitiveSocketGetOptions'
- 		parameters: #(Oop Oop).
  
  	s := self socketValueOf: socket.
  	interpreterProxy success: (interpreterProxy isBytes: optionName).
  	optionNameStart := self cCoerce: (interpreterProxy firstIndexableField: optionName) to: #'char *'.
  	optionNameSize := interpreterProxy slotSizeOf: optionName.
  
  	interpreterProxy failed ifTrue: [^nil].
  	returnedValue := 0.
  
  	errorCode := self sqSocketGetOptions: s 
  					optionNameStart: optionNameStart 
  					optionNameSize: optionNameSize
+ 					returnedValue: (self addressOf: returnedValue put: [:val| returnedValue := val]).
- 					returnedValue: (self addressOf: returnedValue).
  
  	results := interpreterProxy instantiateClass: interpreterProxy classArray indexableSize: 2.
+ 	interpreterProxy
+ 		storePointer: 0 ofObject: results withValue: errorCode asSmallIntegerObj;
+ 		storePointer: 1 ofObject: results withValue: returnedValue asSmallIntegerObj.
+ 	^results!
- 	interpreterProxy storePointer: 0 ofObject: results withValue: errorCode asSmallIntegerObj.
- 	interpreterProxy storePointer: 1 ofObject: results withValue: returnedValue asSmallIntegerObj.
- 	^ results!

Item was changed:
  ----- Method: SocketPlugin>>primitiveSocket:setOptions:value: (in category 'primitives') -----
  primitiveSocket: socket setOptions: optionName value: optionValue
  	"THIS BADLY NEEDS TO BE REWRITTEN TO TAKE Booleans AND Integers AS WELL AS (OR INSTEAD OF) Strings.
  	 It is only used with booleans and integers and parsing these back out of strings in
  	 sqSocketSetOptions:optionNameStart:optionNameSize:optionValueStart:optionValueSize:returnedValue:
  	 is STUPID."
  	| s optionNameStart optionNameSize optionValueStart optionValueSize returnedValue errorCode results |
  	<var: #s type: #SocketPtr>
  	<var: #optionNameStart type: #'char *'>
  	<var: #optionValueStart type: #'char *'>
+ 	self primitive: 'primitiveSocketSetOptions' parameters: #(Oop Oop Oop).
- 	self primitive: 'primitiveSocketSetOptions'
- 		parameters: #(Oop Oop Oop).
  
  	s := self socketValueOf: socket.
  	interpreterProxy success: (interpreterProxy isBytes: optionName).
  	optionNameStart := self cCoerce: (interpreterProxy firstIndexableField: optionName) to: #'char *'.
  	optionNameSize := interpreterProxy slotSizeOf: optionName.
  	interpreterProxy success: (interpreterProxy isBytes: optionValue).
  	optionValueStart:= self cCoerce: (interpreterProxy firstIndexableField: optionValue) to: #'char *'.
  	optionValueSize := interpreterProxy slotSizeOf: optionValue.
  
  	interpreterProxy failed ifTrue: [^nil].
  	returnedValue := 0.
  
  	errorCode := self sqSocketSetOptions: s 
  					optionNameStart: optionNameStart 
  					optionNameSize: optionNameSize
  					optionValueStart: optionValueStart
  					optionValueSize: optionValueSize
+ 					returnedValue: (self addressOf: returnedValue put: [:val| returnedValue := val]).
- 					returnedValue: (self addressOf: returnedValue).
  
  	results := interpreterProxy instantiateClass: interpreterProxy classArray indexableSize: 2.
+ 	interpreterProxy
+ 		storePointer: 0 ofObject: results withValue: errorCode asSmallIntegerObj;
+ 		storePointer: 1 ofObject: results withValue: returnedValue asSmallIntegerObj.
+ 	^results!
- 	interpreterProxy storePointer: 0 ofObject: results withValue: errorCode asSmallIntegerObj.
- 	interpreterProxy storePointer: 1 ofObject: results withValue: returnedValue asSmallIntegerObj.
- 	^ results!

Item was added:
+ ----- Method: SocketPluginSimulator>>sqSocket:AcceptFrom:RecvBytes:SendBytes:SemaID:ReadSemaID:WriteSemaID: (in category 'simulation') -----
+ sqSocket: sockPtr AcceptFrom: serverSocket RecvBytes: recvBufSize SendBytes: sendBufSize SemaID: semaIndex ReadSemaID: readSemaIndex WriteSemaID: writeSemaIndex
+ 	"Simulate the sqSocketAcceptFromRecvBytesSendBytesSemaIDReadSemaIDWriteSemaID function.
+ 	 We descend beneath the Socket abstraction to simulate as accurately as possible."
+ 	| semaphoresAndIndexes semaphores indexes socketHandle |
+ 	semaphoresAndIndexes := Smalltalk newExternalSemaphores: 3.
+ 	semaphores := semaphoresAndIndexes first.
+ 	indexes := semaphoresAndIndexes second.
+ 	socketHandle := [Socket basicNew
+ 						primAcceptFrom: serverSocket
+ 						receiveBufferSize: recvBufSize
+ 						sendBufSize: sendBufSize
+ 						semaIndex: indexes first
+ 						readSemaIndex: indexes second
+ 						writeSemaIndex: indexes third]
+ 			on: SocketPrimitiveFailed
+ 			do: [:ex|
+ 				#failed].
+ 	socketHandle == #failed ifTrue:
+ 		[interpreterProxy primitiveFail.
+ 		 Smalltalk unregisterExternalObjects: semaphores.
+ 		 ^self].
+ 	"N.B. There is now a Processor yield in doSignalExternalSemaphores: every 100 virtual microseconds.
+ 	 This allows these to make progress.  Their job is to map a host signal into a signal of the relevant index."
+ 	self map:		socketHandle
+ 		to:			sockPtr
+ 		type:		nil
+ 		register:	semaphores
+ 		spawning:	[[semaphores first wait. interpreterProxy  signalSemaphoreWithIndex: semaIndex] repeat]
+ 		and:		[[semaphores second wait. interpreterProxy  signalSemaphoreWithIndex: readSemaIndex] repeat]
+ 		and:		[[semaphores third wait. interpreterProxy  signalSemaphoreWithIndex: writeSemaIndex] repeat]!

Item was added:
+ ----- Method: SocketPluginSimulator>>sqSocket:ListenOnPort:BacklogSize:Interface: (in category 'simulation') -----
+ sqSocket: socketHandle ListenOnPort: portNumber BacklogSize: backlog Interface: addr
+ 	^[Socket basicNew
+ 			primSocket: ((self hostSocketHandleFromSimSocketHandle: socketHandle) ifNil: [^self])
+ 			listenOn: portNumber
+ 			backlogSize: backlog
+ 			interface: (self netAddressAsByteArrayFromInt: addr)]
+ 		on: SocketPrimitiveFailed
+ 		do: [:ex|
+ 			interpreterProxy primitiveFail.
+ 			0]!

Item was added:
+ ----- Method: SocketPluginSimulator>>sqSocketError: (in category 'simulation') -----
+ sqSocketError: socketHandleCArray 
+ 	^[Socket basicNew
+ 			primSocketError: ((self hostSocketHandleFromSimSocketHandle: socketHandleCArray) ifNil: [^false])]
+ 		on: SocketPrimitiveFailed
+ 		do: [:ex|
+ 			interpreterProxy primitiveFail.
+ 			false]!

Item was added:
+ ----- Method: SocketPluginSimulator>>sqSocketGetOptions:optionNameStart:optionNameSize:returnedValue: (in category 'simulation') -----
+ sqSocketGetOptions: socketHandle
+ 	optionNameStart: optionNameStart optionNameSize: optionNameSize
+ 		returnedValue: valuePtrBlock
+ 	"Simulate sqSocketGetOptionsoptionNameStartoptionNameSizereturnedValue.
+ 	 Answer the error code and assign the value through valuePtrBlock."
+ 	| optionName |
+ 	optionName := self asString: optionNameStart size: optionNameSize.
+ 	^[| errAndValue |
+ 		errAndValue := Socket basicNew
+ 						primSocket: ((self hostSocketHandleFromSimSocketHandle: socketHandle) ifNil: [^self])
+ 						getOption: optionName.
+ 		valuePtrBlock at: 0 put: errAndValue second.
+ 		errAndValue first]
+ 		on: SocketPrimitiveFailed
+ 		do: [:ex|
+ 			interpreterProxy primitiveFail.
+ 			0]!

Item was added:
+ ----- Method: SocketPluginSimulator>>sqSocketRemoteAddress: (in category 'simulation') -----
+ sqSocketRemoteAddress: socketHandleCArray 
+ 	^[| remoteAddress |
+ 	   remoteAddress := Socket basicNew
+ 							primSocketRemoteAddress: ((self hostSocketHandleFromSimSocketHandle: socketHandleCArray) ifNil: [^false]).
+ 		"Effectively netAddressToInt: remoteAddress"
+ 		((remoteAddress at: 4)) +
+ 		((remoteAddress at: 3) <<8) +
+ 		((remoteAddress at: 2) <<16) +
+ 		((remoteAddress at: 1) <<24)]
+ 		on: SocketPrimitiveFailed
+ 		do: [:ex|
+ 			interpreterProxy primitiveFail.
+ 			false]!

Item was added:
+ ----- Method: SocketPluginSimulator>>sqSocketSetOptions:optionNameStart:optionNameSize:optionValueStart:optionValueSize:returnedValue: (in category 'simulation') -----
+ sqSocketSetOptions: socketHandle
+ 	optionNameStart: optionNameStart optionNameSize: optionNameSize optionValueStart: optionValueStart optionValueSize: optionValueSize
+ 		returnedValue: valuePtrBlock
+ 	"Simulate sqSocketSetOptionsoptionNameStartoptionNameSizeoptionValueStartoptionValueSizereturnedValue.
+ 	 Answer the error code and assign the value through valuePtrBlock."
+ 	| optionName optionValue |
+ 	optionName := self asString: optionNameStart size: optionNameSize.
+ 	optionValue := self asString: optionValueStart size: optionValueSize.
+ 	^[| errAndValue |
+ 		errAndValue := Socket basicNew
+ 						primSocket: ((self hostSocketHandleFromSimSocketHandle: socketHandle) ifNil: [^self])
+ 						setOption: optionName
+ 						value: optionValue.
+ 		valuePtrBlock at: 0 put: errAndValue second.
+ 		errAndValue first]
+ 		on: SocketPrimitiveFailed
+ 		do: [:ex|
+ 			interpreterProxy primitiveFail.
+ 			0]!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>compileFullBlockMethodFrameBuild: (in category 'compile abstract instructions') -----
  compileFullBlockMethodFrameBuild: numCopied
  	<option: #SistaV1BytecodeSet>
  	useTwoPaths ifTrue: 
  		[ "method with only inst var store, we compile only slow path for now" 
  		 useTwoPaths := false.
  		 self cppIf: IMMUTABILITY ifTrue: [ needsFrame := true ] ].
  	needsFrame ifFalse:
+ 		["it is OK for numCopied to be non-zero provided that the block does not actually use the copied values.
+ 		 There are some blocks like this, e.g. that simply reference copied values to mark them as used for Slang.
+ 		 See e.g. CroquetPlugin>>#primitiveGatherEntropy which contains the block [bufPtr. bufSize. false],
+ 		 which the bytecode compiler optimizes to [false]."
+ 		 false ifTrue: [self assert: numCopied = 0].
- 		[self assert: numCopied = 0.
  		 self compileFullBlockFramelessEntry: numCopied.
  		 self initSimStackForFramelessBlock: initialPC.
  		 ^self].
  	super compileFullBlockMethodFrameBuild: numCopied.
  	self initSimStackForFramefulMethod: initialPC!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>isNonForwarderReceiver: (in category 'testing') -----
  isNonForwarderReceiver: reg
  	"Do not inline (inBlock access)"
  	^self receiverIsInReceiverResultReg
+ 		and: [inBlock = 0 "Method, rcvr may be forwarder in blocks without inst var access." 
+ 		and: [reg = ReceiverResultReg]]!
- 		and: [inBlock == 0 "Method, rcvr may be forwarder in blocks without inst var access." 
- 		and: [reg == ReceiverResultReg]]!

Item was changed:
  ----- Method: VMClass>>asByteArray: (in category 'C library extensions') -----
  asByteArray: aStringOrStringIndex
  	"aStringOrStringIndex is either a string or an address in the heap.
+ 	 Create a ByteArray of the requested length from the bytes in the
- 	 Create a ByteArray of the requested length form the bytes in the
  	 heap starting at stringIndex."
  	<doNotGenerate>
  	| sz |
  	aStringOrStringIndex isString ifTrue:
  		[^aStringOrStringIndex asByteArray].
  	sz := self strlen: aStringOrStringIndex.
  	^self strncpy: (ByteArray new: sz) _: aStringOrStringIndex _: sz!

Item was changed:
  ----- Method: VMClass>>asByteArray:size: (in category 'C library extensions') -----
  asByteArray: baIndex size: baSize
  	"baIndex is an address in the heap.  Create a ByteArray of the requested length
+ 	 from the bytes in the heap starting at baIndex."
- 	form the bytes in the heap starting at baIndex."
  	<doNotGenerate>
  	^self strncpy: (ByteArray new: baSize) _: baIndex _: baSize!

Item was changed:
  ----- Method: VMClass>>asString: (in category 'C library extensions') -----
  asString: aStringOrStringIndex
  	"aStringOrStringIndex is either a string or an address in the heap.
+ 	 Create a String of the requested length from the bytes in the
- 	 Create a String of the requested length form the bytes in the
  	 heap starting at stringIndex."
  	<doNotGenerate>
  	| sz |
  	aStringOrStringIndex isString ifTrue:
  		[^aStringOrStringIndex].
  	sz := self strlen: aStringOrStringIndex.
  	^self strncpy: (ByteString new: sz) _: aStringOrStringIndex _: sz!

Item was changed:
  ----- Method: VMClass>>asString:size: (in category 'C library extensions') -----
  asString: stringIndex size: stringSize
  	"stringIndex is an address in the heap.  Create a String of the requested length
+ 	 from the bytes in the heap starting at stringIndex."
- 	form the bytes in the heap starting at stringIndex."
  	<doNotGenerate>
  	^self strncpy: (ByteString new: stringSize) _: stringIndex _: stringSize!



More information about the Vm-dev mailing list