[Vm-dev] VM Maker: VMMaker.oscog-cb.1934.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Sep 5 08:47:45 UTC 2016


ClementBera uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-cb.1934.mcz

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

Name: VMMaker.oscog-cb.1934
Author: cb
Time: 5 September 2016, 10:45:14.790485 am
UUID: efe94566-a80f-410f-9032-ca403fc2ce05
Ancestors: VMMaker.oscog-nice.1933

Re-enabled full block compilation to machine code.

Fixes related to bc to mc pc mapping in full block

Made stack check assert more robust.

Added convenience to simulate Pharo images.

=============== Diff against VMMaker.oscog-nice.1933 ===============

Item was added:
+ ----- Method: CArrayAccessor>>at:ifAbsent: (in category 'accessing') -----
+ at: index ifAbsent: aBlock
+ 	"This is a simulation-time-only convenience..."
+ 	^object at: index + offset + 1 ifAbsent: aBlock!

Item was changed:
  ----- Method: CogVMSimulator>>maybeCheckStackDepth:sp:pc: (in category 'debug support') -----
  maybeCheckStackDepth: delta sp: sp pc: mcpc
  	| asp bcpc startbcpc cogHomeMethod cogBlockMethod csp debugStackPointers |
  	debugStackDepthDictionary ifNil: [^self].
  	(self isMachineCodeFrame: framePointer) ifFalse: [^self].
  	cogBlockMethod := self mframeCogMethod: framePointer.
  	cogHomeMethod := self asCogHomeMethod: cogBlockMethod.
  	debugStackPointers := debugStackDepthDictionary
  								at: cogHomeMethod methodObject
  								ifAbsentPut: [self debugStackPointersFor: cogHomeMethod methodObject].
  	startbcpc := cogHomeMethod = cogBlockMethod
  					ifTrue: [self startPCOfMethod: cogHomeMethod methodObject]
  					ifFalse: [self startPCOfClosure: (self pushedReceiverOrClosureOfFrame: framePointer)].
  	bcpc := cogit bytecodePCFor: mcpc startBcpc: startbcpc in: cogBlockMethod.
  	self assert: bcpc ~= 0.
  	cogBlockMethod ~= cogHomeMethod ifTrue:
  		[| lastbcpc |
  		 lastbcpc := cogit lastBytecodePCForBlockAt: startbcpc in: cogHomeMethod methodObject.
  		 bcpc > lastbcpc ifTrue:
  			[bcpc := lastbcpc]].
  	asp := self stackPointerIndexForFrame: framePointer WithSP: sp + objectMemory wordSize.
+ 	csp := debugStackPointers at: bcpc ifAbsent: [-1].
- 	csp := debugStackPointers at: bcpc.
  	"Compensate lazily for absent receiver sends."
  	(NewspeakVM
  	 and: [asp - delta = csp
  	 and: [cogit isAbsentReceiverSendAt: mcpc in: cogHomeMethod]]) ifTrue:
  		[csp := debugStackPointers at: bcpc put: csp + 1].
  	self assert: asp - delta + 1 = csp!

Item was changed:
  ----- Method: Cogit>>compileEntireFullBlockMethod: (in category 'compile abstract instructions') -----
  compileEntireFullBlockMethod: numCopied
  	"Compile the abstract instructions for the entire full block method."
  	<option: #SistaV1BytecodeSet>
  	| result |
  	self preenMethodLabel.
  	self compileFullBlockEntry.
  
  	"Frame build"
  	self compileFullBlockMethodFrameBuild: numCopied.
  	"Method body"
  	(result := self compileMethodBody) < 0 ifTrue:
  		[^result].
  	self assert: blockCount = 0.
+ 	^0!
- 	^-1!

Item was changed:
  ----- Method: Cogit>>mapFor:bcpc:performUntil:arg: (in category 'method map') -----
  mapFor: cogMethod bcpc: startbcpc performUntil: functionSymbol arg: arg
  	"Machine-code <-> bytecode pc mapping support.  Evaluate functionSymbol
  	 for each mcpc, bcpc pair in the map until the function returns non-zero,
  	 answering that result, or 0 if it fails to.  To cut down on number of arguments.
  	 and to be usable for both pc-mapping and method introspection, we encode
  	 the annotation and the isBackwardBranch flag in the same parameter.
  	 Guilty as charged."
  	<var: #cogMethod type: #'CogBlockMethod *'>
  	<var: #functionSymbol declareC: 'sqInt (*functionSymbol)(BytecodeDescriptor *desc, sqInt annotationAndIsBackwardBranch, char *mcpc, sqInt bcpc, void *arg)'>
  	<var: #arg type: #'void *'>
  	<inline: true>
  	| isInBlock mcpc bcpc endbcpc map mapByte homeMethod aMethodObj result
  	  latestContinuation byte descriptor bsOffset nExts annotation |
  	<var: #descriptor type: #'BytecodeDescriptor *'>
  	<var: #homeMethod type: #'CogMethod *'>
  
  	self assert: cogMethod stackCheckOffset > 0.
  	mcpc := cogMethod asUnsignedInteger + cogMethod stackCheckOffset.
  	"The stack check maps to the start of the first bytecode,
  	 the first bytecode being effectively after frame build."
  	result := self perform: functionSymbol
  					with: nil
  					with: 0 + (HasBytecodePC << 1)
  					with: (self cCoerceSimple: mcpc to: #'char *')
  					with: startbcpc
  					with: arg.
  	result ~= 0 ifTrue:
  		[^result].
  	bcpc := startbcpc.
  	"In both CMMethod and CMBlock cases find the start of the map and
  	 skip forward to the bytecode pc map entry for the stack check."
  	cogMethod cmType = CMMethod
  		ifTrue:
+ 			[isInBlock := cogMethod cmIsFullBlock.
- 			[isInBlock := false.
  			 homeMethod := self cCoerceSimple: cogMethod to: #'CogMethod *'.
  			 self assert: startbcpc = (coInterpreter startPCOfMethodHeader: homeMethod methodHeader).
  			 map := self mapStartFor: homeMethod.
  			 annotation := (objectMemory byteAt: map) >> AnnotationShift.
  			 self assert: (annotation = IsAbsPCReference
  						 or: [annotation = IsObjectReference
  						 or: [annotation = IsRelativeCall
  						 or: [annotation = IsDisplacementX2N]]]).
  			 latestContinuation := startbcpc.
  			 aMethodObj := homeMethod methodObject.
  			 endbcpc := (objectMemory numBytesOf: aMethodObj) - 1.
  			 bsOffset := self bytecodeSetOffsetForHeader: homeMethod methodHeader.
  			"If the method has a primitive, skip it and the error code store, if any;
  			 Logically. these come before the stack check and so must be ignored."
  			 bcpc := bcpc + (self deltaToSkipPrimAndErrorStoreIn: aMethodObj
  									header: homeMethod methodHeader)]
  		ifFalse:
  			[isInBlock := true.
  			 self assert: bcpc = cogMethod startpc.
  			 homeMethod := cogMethod cmHomeMethod.
  			 map := self findMapLocationForMcpc: cogMethod asUnsignedInteger + (self sizeof: CogBlockMethod)
  						inMethod: homeMethod.
  			 self assert: map ~= 0.
  			 annotation := (objectMemory byteAt: map) >> AnnotationShift.
  			 self assert: (annotation >> AnnotationShift = HasBytecodePC "fiducial"
  						 or: [annotation >> AnnotationShift = IsDisplacementX2N]).
  			 [(annotation := (objectMemory byteAt: map) >> AnnotationShift) ~= HasBytecodePC] whileTrue:
  				[map := map - 1].
  			 map := map - 1. "skip fiducial; i.e. the map entry for the pc immediately following the method header."
  			 aMethodObj := homeMethod methodObject.
  			 bcpc := startbcpc - (self blockCreationBytecodeSizeForHeader: homeMethod methodHeader).
  			 bsOffset := self bytecodeSetOffsetForHeader: homeMethod methodHeader.
  			 byte := (objectMemory fetchByte: bcpc ofObject: aMethodObj) + bsOffset.
  			 descriptor := self generatorAt: byte.
  			 endbcpc := self nextBytecodePCFor: descriptor at: bcpc exts: -1 in: aMethodObj.
  			 bcpc := startbcpc].
  	nExts := 0.
  	self inlineCacheTagsAreIndexes ifTrue:
  		[enumeratingCogMethod := homeMethod].
  	"Now skip up through the bytecode pc map entry for the stack check." 
  	[(objectMemory byteAt: map) >> AnnotationShift ~= HasBytecodePC] whileTrue:
  		[map := map - 1].
  	map := map - 1.
  	[(mapByte := objectMemory byteAt: map) ~= MapEnd] whileTrue: "defensive; we exit on bcpc"
  		[mapByte >= FirstAnnotation
  			ifTrue:
  				[| nextBcpc isBackwardBranch |
  				annotation := mapByte >> AnnotationShift.
  				mcpc := mcpc + ((mapByte bitAnd: DisplacementMask) * backEnd codeGranularity).
  				(self isPCMappedAnnotation: annotation) ifTrue:
  					[(annotation = IsSendCall
  					  and: [(mapByte := objectMemory byteAt: map - 1) >> AnnotationShift = IsAnnotationExtension]) ifTrue:
  						[annotation := annotation + (mapByte bitAnd: DisplacementMask).
  						 map := map - 1].
  					 [byte := (objectMemory fetchByte: bcpc ofObject: aMethodObj) + bsOffset.
  					  descriptor := self generatorAt: byte.
  					  isInBlock
  						ifTrue: [bcpc >= endbcpc ifTrue: [^0]]
  						ifFalse:
  							[(descriptor isReturn and: [bcpc >= latestContinuation]) ifTrue: [^0].
  							 (descriptor isBranch or: [descriptor isBlockCreation]) ifTrue:
  								[| targetPC |
  								 targetPC := self latestContinuationPCFor: descriptor at: bcpc exts: nExts in: aMethodObj.
  								 latestContinuation := latestContinuation max: targetPC]].
  					  nextBcpc := self nextBytecodePCFor: descriptor at: bcpc exts: nExts in: aMethodObj.
  					  descriptor isMapped
  					  or: [isInBlock and: [descriptor isMappedInBlock]]] whileFalse:
  						[bcpc := nextBcpc.
  						 nExts := descriptor isExtension ifTrue: [nExts + 1] ifFalse: [0]].
  					 isBackwardBranch := descriptor isBranch
  										   and: [self isBackwardBranch: descriptor at: bcpc exts: nExts in: aMethodObj].
  					 result := self perform: functionSymbol
  									with: descriptor
  									with: (isBackwardBranch ifTrue: [annotation << 1 + 1] ifFalse: [annotation << 1])
  									with: (self cCoerceSimple: mcpc to: #'char *')
  									with: bcpc
  									with: arg.
  					 result ~= 0 ifTrue:
  						[^result].
  					 bcpc := nextBcpc.
  					 nExts := descriptor isExtension ifTrue: [nExts + 1] ifFalse: [0]]]
  			ifFalse:
  				[self assert: (mapByte >> AnnotationShift = IsDisplacementX2N
  							or: [mapByte >> AnnotationShift = IsAnnotationExtension]).
  				 mapByte < (IsAnnotationExtension << AnnotationShift) ifTrue:
  					[mcpc := mcpc + ((mapByte - DisplacementX2N << AnnotationShift) * backEnd codeGranularity)]].
  		 map := map - 1].
  	^0!

Item was changed:
  ----- Method: StackInterpreter>>ioLoadExternalFunction:OfLength:FromModule:OfLength:AccessorDepthInto: (in category 'primitive support') -----
  ioLoadExternalFunction: functionName OfLength: functionLength FromModule: moduleName OfLength: moduleLength AccessorDepthInto: accessorDepthPtr
  	"Load and return the requested function from a module.  Assign the accessor depth through accessorDepthPtr.
  	 N.B. The actual code lives in platforms/Cross/vm/sqNamedPrims.h"
  	<doNotGenerate>
  	| pluginString functionString |
  	pluginString := String new: moduleLength.
  	1 to: moduleLength do:[:i| pluginString byteAt: i put: (objectMemory byteAt: moduleName+i-1)].
+ 	"Pharo images as of 2016 use the FFI plugin (for getenv:?).  We can't simulate such function loads.  So ignore"
+ 	pluginString = 'SqueakFFIPrims' ifTrue:
+ 		[self transcript cr; show: 'ignoring function load from SqueakFFIPrims'.
+ 		 ^0].
  	functionString := String new: functionLength.
  	1 to: functionLength do:[:i| functionString byteAt: i put: (objectMemory byteAt: functionName+i-1)].
  	^self ioLoadFunction: functionString From: pluginString AccessorDepthInto: accessorDepthPtr!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>compileFullBlockMethodFrameBuild: (in category 'compile abstract instructions') -----
  compileFullBlockMethodFrameBuild: numCopied
  	<option: #SistaV1BytecodeSet>
  	needsFrame ifFalse:
+ 		[ self assert: methodOrBlockNumArgs = 0. "Else calling convention would have put args in regs while block activation expects them on stack"
+ 		 self initSimStackForFramelessMethod: initialPC.
- 		[self initSimStackForFramelessMethod: initialPC.
  		 ^self].
  	super compileFullBlockMethodFrameBuild: numCopied.
  	self initSimStackForFramefulMethod: initialPC!



More information about the Vm-dev mailing list