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

commits at source.squeak.org commits at source.squeak.org
Wed Feb 6 02:39:49 UTC 2013


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

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

Name: VMMaker.oscog-eem.264
Author: eem
Time: 5 February 2013, 6:37:47.099 pm
UUID: 64e76092-8af7-449f-9188-e65f3bd1f08d
Ancestors: VMMaker.oscog-lw.263

Fix snapshot primitive failure in the StackVM and Cogit.  The
primitive should fail, not merely return the receiver.  Also if in
Cogit, need to back-up instrufiton pointer on failure.

Make reportMinimumUnusedHeadroom more informative (also print
available headroom).

Back out of named SerialPlugin primitives (comprehensive
platform support is lacking).

Fix simulation of forceInterruptCheck when snapshotting.

Fix simulation of writeImageFileIO: when image file is not writable.

Fix generateSqueakStackVM.

=============== Diff against VMMaker.oscog-lw.263 ===============

Item was changed:
  ----- Method: CoInterpreter>>reportMinimumUnusedHeadroom (in category 'debug support') -----
  reportMinimumUnusedHeadroom
  	"Report the stack page size and minimum unused headroom to stdout."
  	<api>
  	self cCode:
+ 			[self pri: 'stack page bytes %ld available headroom %ld minimum unused headroom %ld\n'
+ 				n: self stackPageByteSize
+ 				t: self stackPageByteSize - self stackLimitBytes - self stackLimitOffset
- 			[self prin: 'stack page size %ld minimum unused stack headroom %ld bytes\n'
- 				t: self stackPageByteSize
  				f: self minimumUnusedHeadroom]
  		inSmalltalk:
+ 			["CogVMSimulator new initStackPagesForTests reportMinimumUnusedHeadroom"
+ 			 self print: 'stack page bytes '; printNum: self stackPageByteSize;
+ 				print: ' available headroom '; printNum: self stackPageByteSize - self stackLimitBytes - self stackLimitOffset;
+ 				print: ' minimum unused headroom '; printNum: self minimumUnusedHeadroom;
+ 				cr]!
- 			[self print: 'stack page size '; printNum: self stackPageByteSize;
- 				print: ' minimum unused stack headroom '; printNum: self minimumUnusedHeadroom;
- 				print: ' bytes'; cr]!

Item was changed:
  ----- Method: CoInterpreterPrimitives>>primitiveSnapshot (in category 'system control primitives') -----
  primitiveSnapshot
  	"Save a normal snapshot under the same name as it was loaded
  	 unless it has been renamed by the last primitiveImageName.
  
  	 Override to jump to the interpreter because the machine code zone is now void."
  	<inline: false>
  	self snapshot: false.
+ 	(self iframeMethod: framePointer) = newMethod ifTrue:
+ 		["snapshot: has reached the end and built a frame.
+ 		 In the JIT we need to back-up the pc before reentering the interpreter."
+ 		instructionPointer := instructionPointer - 1].
  	self siglong: reenterInterpreter jmp: ReturnToInterpreter
  	"NOTREACHED"!

Item was changed:
  ----- Method: CoInterpreterPrimitives>>primitiveSnapshotEmbedded (in category 'system control primitives') -----
  primitiveSnapshotEmbedded
  	"Save an embedded snapshot.
  
  	 Override to jump to the interpreter because the machine code zone is now void."
  	<inline: false>
  	self snapshot: true.
+ 	(self iframeMethod: framePointer) = newMethod ifTrue:
+ 		["snapshot: has reached the end and built a frame.
+ 		 In the JIT we need to back-up the pc before reentering the interpreter."
+ 		instructionPointer := instructionPointer - 1].
  	self siglong: reenterInterpreter jmp: ReturnToInterpreter
  	"NOTREACHED"!

Item was changed:
  ----- Method: CogVMSimulator>>writeImageFileIO: (in category 'image save/restore') -----
  writeImageFileIO: numberOfBytesToWrite
  	"Actually emit the first numberOfBytesToWrite object memory bytes onto the snapshot."
  
  	| headerSize file |
  	BytesPerWord = 4 ifFalse: [self error: 'Not rewritten for 64 bits yet'].
  	headerSize := 64.
  
  	[
+ 		file := FileStream fileNamed: imageName.
+ 		file == nil ifTrue:
+ 			[self primitiveFail.
+ 			 ^nil].
+ 		file binary.
+ 
- 		file := (FileStream fileNamed: imageName) binary.
- 		file == nil ifTrue: [^nil].
- 	
  		{
  			self imageFormatVersion.
  			headerSize.
  			numberOfBytesToWrite.
  			objectMemory startOfMemory.
  			(objectMemory specialObjectsOop).
  			(objectMemory lastHash).
  			self ioScreenSize.
  			self getImageHeaderFlags.
  			extraVMMemory
  		}
  			do: [:long | self putLong: long toFile: file].
  
  		{	desiredNumStackPages. self unknownShortOrCodeSizeInKs } do:
  			[:short| self putShort: short toFile: file].
  
  		self putLong: desiredEdenBytes toFile: file.
  
  		{	maxExtSemTabSizeSet ifTrue: [self ioGetMaxExtSemTableSize] ifFalse: [0]. 0 } do:
  			[:short| self putShort: short toFile: file].
  
  		"Pad the rest of the header."
  		4 timesRepeat: [self putLong: 0 toFile: file].
  	
  		"Position the file after the header."
  		file position: headerSize.
  	
  		"Write the object memory."
  		objectMemory startOfMemory // 4 + 1
  			to: numberOfBytesToWrite // 4
  			do: [:index |
  				self
  					putLong: (objectMemory memory at: index)
  					toFile: file].
  	
  		self success: true
  	]
+ 		ensure: [file ifNotNil: [file close]]!
- 		ensure: [file close]!

Item was changed:
  ----- Method: NewspeakInterpreterSimulator>>writeImageFileIO: (in category 'image save/restore') -----
  writeImageFileIO: numberOfBytesToWrite
  	"Actually emit the first numberOfBytesToWrite object memory bytes onto the snapshot."
  
  	| headerSize file |
  	BytesPerWord = 4 ifFalse: [self error: 'Not rewritten for 64 bits yet'].
  	headerSize := 64.
  
  	[
+ 		file := FileStream fileNamed: imageName.
+ 		file == nil ifTrue:
+ 			[self primitiveFail.
+ 			 ^nil].
+ 		file binary.
- 		file := (FileStream fileNamed: imageName) binary.
- 		file == nil ifTrue: [^nil].
  	
  		{
  			self imageFormatVersion.
  			headerSize.
  			numberOfBytesToWrite.
  			self startOfMemory.
  			specialObjectsOop.
  			lastHash.
  			self ioScreenSize.
  			fullScreenFlag.
  			extraVMMemory
  		}
  			do: [:long | self putLong: long toFile: file].
  	
  		"Pad the rest of the header."
  		7 timesRepeat: [self putLong: 0 toFile: file].
  	
  		"Position the file after the header."
  		file position: headerSize.
  	
  		"Write the object memory."
  		1
  			to: numberOfBytesToWrite // 4
  			do: [:index |
  				self
  					putLong: (memory at: index)
  					toFile: file].
  	
  		self success: true
  	]
+ 		ensure: [file ifNotNil: [file close]]!
- 		ensure: [file close]!

Item was removed:
- ----- Method: SerialPlugin>>primitiveSerialPortOpenByName:baudRate:stopBitsType:parityType:dataBits:inFlowControlType:outFlowControlType:xOnByte:xOffByte: (in category 'primitives') -----
- primitiveSerialPortOpenByName: portName baudRate: baudRate stopBitsType: stopBitsType parityType: parityType dataBits: dataBits inFlowControlType: inFlowControl outFlowControlType: outFlowControl xOnByte: xOnChar xOffByte: xOffChar
- 	<var: #port type: 'char *'>
- 
- 	| port portNameSize |
- 	
- 	self primitive: 'primitiveSerialPortOpenByName'
- 		parameters: #(String SmallInteger SmallInteger SmallInteger SmallInteger SmallInteger SmallInteger SmallInteger SmallInteger ).
- 
- 	portNameSize := interpreterProxy slotSizeOf: (portName asOop: String).
- 	port := self cCode: 'calloc(portNameSize, sizeof(char))'.
- 	self cCode: 'memcpy(port, portName, portNameSize)'.
- 	
- 	self cCode: 'serialPortOpenByName(
- 			port, baudRate, stopBitsType, parityType, dataBits,
- 			inFlowControl, outFlowControl, xOnChar, xOffChar)'.
- 	
- 	self free: port.!

Item was removed:
- ----- Method: SerialPlugin>>primitiveSerialPortReadByName:into:startingAt:count: (in category 'primitives') -----
- primitiveSerialPortReadByName: portName into: array startingAt: startIndex count: count 
- 	<var: #port type: 'char *'>
- 
- 	| port portNameSize bytesRead arrayPtr |
- 
- 	self primitive: 'primitiveSerialPortReadByName'
- 		parameters: #(String ByteArray SmallInteger SmallInteger ).
- 
- 	interpreterProxy success: (startIndex >= 1 and: [startIndex + count - 1 <= (interpreterProxy byteSizeOf: array cPtrAsOop)]).
- 	"adjust for zero-origin indexing"
- 
- 	portNameSize := interpreterProxy slotSizeOf: (portName asOop: String).
- 	port := self cCode: 'calloc(portNameSize, sizeof(char))'.
- 	self cCode: 'memcpy(port, portName, portNameSize)'.
- 
- 	arrayPtr := array asInteger + startIndex - 1.
- 	bytesRead := self cCode: 'serialPortReadIntoByName( port, count, arrayPtr)'.
- 	
- 	self free: port.
- 	
- 	^ bytesRead asSmallIntegerObj!

Item was removed:
- ----- Method: SerialPlugin>>primitiveSerialPortWriteByName:from:startingAt:count: (in category 'primitives') -----
- primitiveSerialPortWriteByName: portName from: array startingAt: startIndex count: count 
- 	<var: #port type: 'char *'>
- 
- 	| bytesWritten arrayPtr portNameSize port |
- 	
- 	self primitive: 'primitiveSerialPortWriteByName'
- 		parameters: #(String ByteArray SmallInteger SmallInteger ).
- 
- 	portNameSize := interpreterProxy slotSizeOf: (portName asOop: String).
- 	port := self cCode: 'calloc(portNameSize, sizeof(char))'.
- 	self cCode: 'memcpy(port, portName, portNameSize)'.
- 
- 	interpreterProxy success: (startIndex >= 1 and: [startIndex + count - 1 <= (interpreterProxy byteSizeOf: array cPtrAsOop)]).
- 	interpreterProxy failed
- 		ifFalse: [arrayPtr := array asInteger + startIndex - 1.
- 			bytesWritten := self cCode: 'serialPortWriteFromByName(port, count, arrayPtr)' ].
- 	
- 	self free: port.
- 
- 	^ bytesWritten asSmallIntegerObj!

Item was changed:
  ----- Method: StackInterpreter>>forceInterruptCheck (in category 'process primitive support') -----
  forceInterruptCheck
  	"Force an interrupt check ASAP.
  	 Must set the stack page's limit before stackLimit to avoid
  	 a race condition if this is called from an interrupt handler."
  	| thePage iccFunc |
  	<inline: false>
  	<var: #thePage type: #'StackPage *'>
  	<var: #iccFunc declareC: 'void (*iccFunc)()'>
  	"Do _not_ set stackLimit until the stack system has been initialized.
  	 stackLimit is the initialization flag for the stack system."
  	stackLimit = 0 ifTrue:
  		[^nil].
  	thePage := stackPage.
+ 	(thePage notNil and: [thePage ~= 0]) ifTrue:
- 	thePage notNil ifTrue:
  		[thePage stackLimit: (self cCoerceSimple: -1 signedIntToLong to: #'char *')].
  	stackLimit := self cCoerceSimple: -1 signedIntToLong to: #'char *'.
  	self sqLowLevelMFence.
  	"There is a race condition if we test the function and then dereference
  	 it a second time to call it.  This is called from interrupt code but at the
  	 same time other code could be clearing the interruptCheckChain via
  	 setInterruptCheckChain:."
  	(iccFunc := interruptCheckChain) notNil ifTrue:
  		[self perform: iccFunc].
  	statForceInterruptCheck := statForceInterruptCheck + 1!

Item was changed:
  ----- Method: StackInterpreter>>snapshot: (in category 'image save/restore') -----
  snapshot: embedded 
  	"update state of active context"
  	| activeContext activeProc dataSize rcvr setMacType stackIndex |
  	<var: #setMacType type: 'void *'>
  
+ 	"For nowe the stack munging below doesn't deal with more than omne argument.
+ 	 It can, and should."
+ 	argumentCount ~= 0 ifTrue:
+ 		[^self primitiveFailFor: PrimErrBadNumArgs].
+ 
  	"Need to convert all frames into contexts since the snapshot file only holds objects."
  	self push: instructionPointer.
  	activeContext := self voidVMStateForSnapshot.
  
  	"update state of active process"
  	activeProc := self activeProcess.
  	objectMemory
  		storePointer: SuspendedContextIndex
  		ofObject: activeProc
  		withValue: activeContext.
  
  	objectMemory pushRemappableOop: activeContext.
  
  	"compact memory and compute the size of the memory actually in use"
  	objectMemory incrementalGC.
  
  	"maximimize space for forwarding table"
  	objectMemory fullGC.
  	self snapshotCleanUp.
  
  	"Nothing moves from here on so it is safe to grab the activeContext again."
  	activeContext := objectMemory popRemappableOop.
  
  	dataSize := objectMemory freeStart - objectMemory startOfMemory. "Assume all objects are below the start of the free block"
  	self successful ifTrue:
  		["Without contexts or stacks simulate
  			rcvr := self popStack.
  			''pop rcvr''
  			self push: trueObj.
  		  to arrange that the snapshot resumes with true.  N.B. stackIndex is one-relative."
  		stackIndex := self quickFetchInteger: StackPointerIndex ofObject: activeContext.
  		rcvr := objectMemory fetchPointer: stackIndex + CtxtTempFrameStart - 1 ofObject: activeContext.
+ 		objectMemory
+ 			storePointerUnchecked: stackIndex + CtxtTempFrameStart - 1
- 		objectMemory storePointerUnchecked: stackIndex + CtxtTempFrameStart - 1
  			ofObject: activeContext
  			withValue: objectMemory trueObject.
  		"now attempt to write the snapshot file"
+ 		self writeImageFileIO: dataSize.
+ 		(self successful and: [embedded not]) ifTrue:
- 		self writeImageFile: dataSize.
- 		embedded ifFalse:
  			["set Mac file type and creator; this is a noop on other platforms"
  			setMacType := self ioLoadFunction: 'setMacFileTypeAndCreator' From: 'FilePlugin'.
  			setMacType = 0 ifFalse:
  				[self cCode: '((sqInt (*)(char *, char *, char *))setMacType)(imageName, "STim", "FAST")']].
  		"Without contexts or stacks simulate
  			self pop: 1"
+ 		objectMemory
+ 			storePointerUnchecked: StackPointerIndex
- 		objectMemory storePointerUnchecked: StackPointerIndex
  			ofObject: activeContext
  			withValue: (objectMemory integerObjectOf: stackIndex - 1)].
  
  	self marryContextInNewStackPageAndInitializeInterpreterRegisters: activeContext.
  	self successful
  		ifTrue: [self push: objectMemory falseObject]
+ 		ifFalse:
+ 			[self push: rcvr.
+ 			 self justActivateNewMethod]!
- 		ifFalse: [self push: rcvr]!

Item was changed:
  ----- Method: StackInterpreter>>writeImageFile: (in category 'image save/restore') -----
  writeImageFile: imageBytes
  
  	| fn |
  	<var: #fn type: 'void *'>
  	self writeImageFileIO: imageBytes.
+ 	self successful ifTrue:
+ 		["set Mac file type and creator; this is a noop on other platforms"
+ 		fn := self ioLoadFunction: 'setMacFileTypeAndCreator' From: 'FilePlugin'.
+ 		fn = 0 ifFalse:
+ 			[self cCode:'((sqInt (*)(char*, char*, char*))fn)(imageName, "STim", "FAST")']]
- 	"set Mac file type and creator; this is a noop on other platforms"
- 	fn := self ioLoadFunction: 'setMacFileTypeAndCreator' From: 'FilePlugin'.
- 	fn = 0 ifFalse:[
- 		self cCode:'((sqInt (*)(char*, char*, char*))fn)(imageName, "STim", "FAST")'.
- 	].
  !

Item was changed:
  ----- Method: StackInterpreterSimulator>>writeImageFileIO: (in category 'image save/restore') -----
  writeImageFileIO: numberOfBytesToWrite
  	"Actually emit the first numberOfBytesToWrite object memory bytes onto the snapshot."
  
  	| headerSize file |
  	BytesPerWord = 4 ifFalse: [self error: 'Not rewritten for 64 bits yet'].
  	headerSize := 64.
  
  	[
+ 		file := FileStream fileNamed: imageName.
+ 		file == nil ifTrue:
+ 			[self primitiveFail.
+ 			 ^nil].
+ 		file binary.
- 		file := (FileStream fileNamed: imageName) binary.
- 		file == nil ifTrue: [^nil].
  	
  		{
  			self imageFormatVersion.
  			headerSize.
  			numberOfBytesToWrite.
  			objectMemory startOfMemory.
  			(objectMemory specialObjectsOop).
  			(objectMemory lastHash).
  			self ioScreenSize.
  			fullScreenFlag.
  			extraVMMemory
  		}
  			do: [:long | self putLong: long toFile: file].
  
  		{	desiredNumStackPages. 	self unknownShortOrCodeSizeInKs } do:
  			[:short| self putShort: short toFile: file].
  
  		self putLong: desiredEdenBytes toFile: file.
  
  		{	maxExtSemTabSizeSet ifTrue: [self ioGetMaxExtSemTableSize] ifFalse: [0]. 0 } do:
  			[:short| self putShort: short toFile: file].
  
  		"Pad the rest of the header."
  		4 timesRepeat: [self putLong: 0 toFile: file].
  	
  		"Position the file after the header."
  		file position: headerSize.
  	
  		"Write the object memory."
  		objectMemory startOfMemory // 4 + 1
  			to: numberOfBytesToWrite // 4
  			do: [:index |
  				self
  					putLong: (objectMemory memory at: index)
  					toFile: file].
  	
  		self success: true
  	]
+ 		ensure: [file ifNotNil: [file close]]!
- 		ensure: [file close]!

Item was changed:
  ----- Method: VMMaker class>>generateSqueakStackVM (in category 'configurations') -----
  generateSqueakStackVM
  	"No primitives since we can use those for the Cog VM"
  	^VMMaker
  		generate: StackInterpreter
  		to: (FileDirectory default pathFromURI: 'oscogvm/stacksrc')
+ 		platformDir: (FileDirectory default pathFromURI: 'oscogvm/platforms')
- 		platformDir: (FileDirectory default pathFromURI: 'cogvm/platforms')
  		excluding: (InterpreterPlugin withAllSubclasses collect: [:ea| ea name])!



More information about the Vm-dev mailing list