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

commits at source.squeak.org commits at source.squeak.org
Sat Oct 11 22:02:21 UTC 2014


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

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

Name: VMMaker.oscog-eem.896
Author: eem
Time: 11 October 2014, 2:59:07.948 pm
UUID: 6a341edb-bba5-473e-86ec-adc3ff98f21d
Ancestors: VMMaker.oscog-eem.895

Use the lemming technique for debugging the
V3 memory manager.  Fix v3 validation and
simulated leak checking under NewObjectMemory.
Fix simulation of asOop: for Boolean and Float.

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

Item was changed:
  CoInterpreterMT subclass: #CogVMSimulator
+ 	instanceVariableNames: 'parent enableCog byteCount lastPollCount lastExtPC sendCount lookupCount printSends traceOn myBitBlt displayForm imageName pluginList mappedPluginEntries quitBlock transcript displayView printFrameAtEachStep printBytecodeAtEachStep systemAttributes uniqueIndices uniqueIndex breakCount atEachStepBlock startMicroseconds externalSemaphoreSignalRequests externalSemaphoreSignalResponses extSemTabSize debugStackDepthDictionary performFilters'
- 	instanceVariableNames: 'enableCog byteCount lastPollCount lastExtPC sendCount lookupCount printSends traceOn myBitBlt displayForm imageName pluginList mappedPluginEntries quitBlock transcript displayView printFrameAtEachStep printBytecodeAtEachStep systemAttributes uniqueIndices uniqueIndex breakCount atEachStepBlock startMicroseconds externalSemaphoreSignalRequests externalSemaphoreSignalResponses extSemTabSize debugStackDepthDictionary performFilters'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-JITSimulation'!
  
  !CogVMSimulator commentStamp: 'eem 9/3/2013 11:16' prior: 0!
  This class defines basic memory access and primitive simulation so that the CoInterpreter can run simulated in the Squeak environment.  It also defines a number of handy object viewing methods to facilitate pawing around in the object memory.  Remember that you can test the Cogit using its class-side in-image compilation facilities.
  
  To see the thing actually run, you could (after backing up this image and changes), execute
  
  	(CogVMSimulator new openOn: Smalltalk imageName) test
  
  and be patient both to wait for things to happen, and to accept various things that may go wrong depending on how large or unusual your image may be.  We usually do this with a small and simple benchmark image.
  
  Here's an example to launch the simulator in a window.  The bottom-right window has a menu packed with useful stuff:
  
  (CogVMSimulator newWithOptions: #(Cogit StackToRegisterMappingCogit))
  	desiredNumStackPages: 8;
  	openOn: '/Users/eliot/Cog/startreader.image';
  	openAsMorph;
  	run
  
  Here's a hairier example that I (Eliot) actually use in daily development with some of the breakpoint facilities commented out.
  
  | cos proc opts |
  CoInterpreter initializeWithOptions: (opts := Dictionary newFromPairs: #(Cogit StackToRegisterMappingCogit)).
  CogVMSimulator chooseAndInitCogitClassWithOpts: opts.
  cos := CogVMSimulator new.
  "cos initializeThreadSupport." "to test the multi-threaded VM"
  cos desiredNumStackPages: 8. "to set the size of the stack zone"
  "cos desiredCogCodeSize: 8 * 1024 * 1024." "to set the size of the Cogit's code zone"
  cos openOn: '/Users/eliot/Squeak/Squeak4.4/trunk44.image'. "choose your favourite image"
  "cos setBreakSelector: 'r:degrees:'." "set a breakpoint at a specific selector"
  proc := cos cogit processor.
  "cos cogit sendTrace: 7." "turn on tracing"
  "set a complex breakpoint at a specific point in machine code"
  "cos cogit singleStep: true; breakPC: 16r56af; breakBlock: [:cg|  cos framePointer > 16r101F3C and: [(cos longAt: cos framePointer - 4) = 16r2479A and: [(cos longAt: 16r101F30) = (cos longAt: 16r101F3C) or: [(cos longAt: 16r101F2C) = (cos longAt: 16r101F3C)]]]]; sendTrace: 1".
  "[cos cogit compilationTrace: -1] on: MessageNotUnderstood do: [:ex|]." "turn on compilation tracing in the StackToRegisterMappingCogit"
  "cos cogit setBreakMethod: 16rB38880."
  cos
  	openAsMorph;
  	"toggleTranscript;" "toggleTranscript will send output to the Transcript instead of the morph's rather small window"
  	halt;
  	run!

Item was added:
+ ----- Method: CogVMSimulator>>parent (in category 'accessing') -----
+ parent
+ 	^ parent!

Item was added:
+ ----- Method: CogVMSimulator>>parent: (in category 'accessing') -----
+ parent: anObject
+ 
+ 	parent := anObject!

Item was added:
+ ----- Method: NewCoObjectMemory>>validate: (in category 'simulation') -----
+ validate: oop
+ 	<doNotGenerate>
+ 	| header type cc sz fmt nextChunk | 
+ 	header := self longAt: oop.
+ 	type := header bitAnd: 3.
+ 	type = 2 ifFalse: [type = (self rightType: header) ifFalse: [self halt]].
+ 	sz := (header bitAnd: SizeMask) >> 2.
+ 	nextChunk := oop + ((self isFreeObject: oop)
+ 							ifTrue: [self sizeOfFree: oop]
+ 							ifFalse: [self sizeBitsOf: oop]).
+ 	nextChunk >= freeStart
+ 		ifTrue:
+ 			[nextChunk = freeStart ifFalse: [self halt]]
+ 		ifFalse:
+ 			[(self headerType: nextChunk) = 0 ifTrue:
+ 				[(self headerType: (nextChunk + (BytesPerWord*2))) = 0 ifFalse: [self halt]].
+ 			(self headerType: nextChunk) = 1 ifTrue:
+ 				[(self headerType: (nextChunk + BytesPerWord)) = 1 ifFalse: [self halt]].
+ 			type = 2 ifTrue:
+ 				["free block" ^ self]].
+ 	fmt := self formatOfHeader: header.
+ 	cc := self compactClassIndexOfHeader: header.
+ 	cc > 16 ifTrue: [self halt].	"up to 32 are legal, but not used"
+ 	type = 0 ifTrue:
+ 		["three-word header"
+ 		((self longAt: oop-BytesPerWord) bitAnd: 3) = type ifFalse: [self halt].
+ 		((self longAt: oop-(BytesPerWord*2)) bitAnd: 3) = type ifFalse: [self halt].
+ 		((self longAt: oop-BytesPerWord) = type) ifTrue: [self halt].	"Class word is 0"
+ 		sz = 0 ifFalse: [self halt]].
+ 	type = 1 ifTrue:
+ 		["two-word header"
+ 		((self longAt: oop-BytesPerWord) bitAnd: 3) = type ifFalse: [self halt].
+ 		cc > 0 ifTrue: [sz = 1 ifFalse: [self halt]].
+ 		sz = 0 ifTrue: [self halt]].
+ 	type = 3 ifTrue:
+ 		["one-word header"
+ 		cc = 0 ifTrue: [self halt]].
+ 	fmt = 5 ifTrue: [self halt].
+ 	fmt = 7 ifTrue: [self halt].
+ 	fmt >= self firstCompiledMethodFormat ifTrue: "must have integer header or be cog method"
+ 		[header := self longAt: oop + BytesPerWord.
+ 		 ((self isIntegerObject: header)
+ 		  or: [(header bitAnd: 7) = 0
+ 			and: [header asUnsignedInteger < self startOfMemory
+ 			and: [header asUnsignedInteger >= cogit minCogMethodAddress]]]) ifFalse: [self halt]].!

Item was changed:
  NewCoObjectMemory subclass: #NewCoObjectMemorySimulator
+ 	instanceVariableNames: 'parent'
- 	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-JITSimulation'!

Item was changed:
+ ----- Method: NewCoObjectMemorySimulator>>fullGC (in category 'gc -- mark and sweep') -----
- ----- Method: NewCoObjectMemorySimulator>>fullGC (in category 'debug support') -----
  fullGC
+ 	"If we're /not/ a clone, clone the VM and push it over the cliff.
+ 	 If it survives, destroy the clone and continue.  We should be OK until next time."
+ 	parent ifNil:
+ 		[coInterpreter cr; print: 'GC number '; print: statFullGCs; tab; flush.
+ 		 coInterpreter cloneSimulation objectMemory fullGC.
+ 		 Smalltalk garbageCollect].
+ 	^super fullGC!
- 	self halt.
- 	coInterpreter transcript
- 		cr; nextPutAll:'<Running full GC ('; print: coInterpreter byteCount; space; print: freeStart; nextPutAll: ')...'; flush.
- 	super fullGC.
- 	coInterpreter transcript show: ' done>'!

Item was added:
+ ----- Method: NewCoObjectMemorySimulator>>heapMapAtWord: (in category 'debug support') -----
+ heapMapAtWord: address
+ 	^heapMap heapMapAtWord: address asInteger!

Item was changed:
+ ----- Method: NewCoObjectMemorySimulator>>incrementalGC (in category 'gc -- mark and sweep') -----
- ----- Method: NewCoObjectMemorySimulator>>incrementalGC (in category 'debug support') -----
  incrementalGC
+ 	"If we're /not/ a clone, clone the VM and push it over the cliff.
+ 	 If it survives, destroy the clone and continue.  We should be OK until next time."
+ 	(self leakCheckIncrementalGC
+ 	 and: [parent isNil]) ifTrue:
+ 		[coInterpreter cr; print: 'Incremental GC number '; print: statIncrGCs; tab; flush.
+ 		 coInterpreter cloneSimulation objectMemory incrementalGC.
+ 		 Smalltalk garbageCollect].
- 	coInterpreter transcript cr; nextPutAll: 'incrementalGC ('; print: coInterpreter byteCount; space; print: freeStart; nextPut: $); flush.
  	^super incrementalGC!

Item was added:
+ ----- Method: NewCoObjectMemorySimulator>>parent (in category 'accessing') -----
+ parent
+ 
+ 	^ parent!

Item was added:
+ ----- Method: NewCoObjectMemorySimulator>>parent: (in category 'accessing') -----
+ parent: anObject
+ 
+ 	parent := anObject!

Item was added:
+ ----- Method: NewObjectMemory>>checkOopIntegrity:named: (in category 'debug support') -----
+ checkOopIntegrity: obj named: name
+ 	<inline: false>
+ 	<var: #name type: #'char *'>
+ 	(heapMap heapMapAtWord: (self pointerForOop: obj)) ~= 0 ifTrue:
+ 		[^true].
+ 	coInterpreter print: name; print: ' leak '; printHex: obj; cr.
+ 	^false!

Item was added:
+ ----- Method: NewObjectMemory>>heapMap (in category 'debug support') -----
+ heapMap
+ 	^heapMap!

Item was changed:
  ----- Method: NewObjectMemory>>validate: (in category 'simulation') -----
  validate: oop
  	<doNotGenerate>
  	| header type cc sz fmt nextChunk | 
  	header := self longAt: oop.
  	type := header bitAnd: 3.
  	type = 2 ifFalse: [type = (self rightType: header) ifFalse: [self halt]].
  	sz := (header bitAnd: SizeMask) >> 2.
  	nextChunk := oop + ((self isFreeObject: oop)
  							ifTrue: [self sizeOfFree: oop]
  							ifFalse: [self sizeBitsOf: oop]).
+ 	nextChunk >= freeStart
+ 		ifTrue:
+ 			[nextChunk = freeStart ifFalse: [self halt]]
+ 		ifFalse:
+ 			[(self headerType: nextChunk) = 0 ifTrue:
+ 				[(self headerType: (nextChunk + (BytesPerWord*2))) = 0 ifFalse: [self halt]].
+ 			(self headerType: nextChunk) = 1 ifTrue:
+ 				[(self headerType: (nextChunk + BytesPerWord)) = 1 ifFalse: [self halt]].
+ 			type = 2 ifTrue:
+ 				["free block" ^ self]].
- 	nextChunk > freeStart ifTrue:
- 		[oop = freeStart ifFalse: [self halt]].
- 	(self headerType: nextChunk) = 0 ifTrue:
- 		[(self headerType: (nextChunk + (BytesPerWord*2))) = 0 ifFalse: [self halt]].
- 	(self headerType: nextChunk) = 1 ifTrue:
- 		[(self headerType: (nextChunk + BytesPerWord)) = 1 ifFalse: [self halt]].
- 	type = 2 ifTrue:
- 		["free block" ^ self].
  	fmt := self formatOfHeader: header.
  	cc := self compactClassIndexOfHeader: header.
  	cc > 16 ifTrue: [self halt].	"up to 32 are legal, but not used"
  	type = 0 ifTrue:
  		["three-word header"
  		((self longAt: oop-BytesPerWord) bitAnd: 3) = type ifFalse: [self halt].
  		((self longAt: oop-(BytesPerWord*2)) bitAnd: 3) = type ifFalse: [self halt].
  		((self longAt: oop-BytesPerWord) = type) ifTrue: [self halt].	"Class word is 0"
  		sz = 0 ifFalse: [self halt]].
  	type = 1 ifTrue:
  		["two-word header"
  		((self longAt: oop-BytesPerWord) bitAnd: 3) = type ifFalse: [self halt].
  		cc > 0 ifTrue: [sz = 1 ifFalse: [self halt]].
  		sz = 0 ifTrue: [self halt]].
  	type = 3 ifTrue:
  		["one-word header"
  		cc = 0 ifTrue: [self halt]].
  	fmt = 5 ifTrue: [self halt].
  	fmt = 7 ifTrue: [self halt].
  	fmt >= self firstCompiledMethodFormat ifTrue: "must have integer header"
  		[(self isIntegerObject: (self longAt: oop + BytesPerWord)) ifFalse: [self halt]].!

Item was changed:
  NewObjectMemory subclass: #NewObjectMemorySimulator
+ 	instanceVariableNames: 'parent'
- 	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-InterpreterSimulation'!

Item was changed:
+ ----- Method: NewObjectMemorySimulator>>fullGC (in category 'gc -- mark and sweep') -----
- ----- Method: NewObjectMemorySimulator>>fullGC (in category 'debug support') -----
  fullGC
+ 	"If we're /not/ a clone, clone the VM and push it over the cliff.
+ 	 If it survives, destroy the clone and continue.  We should be OK until next time."
+ 	parent ifNil:
+ 		[coInterpreter cr; print: 'GC number '; print: statFullGCs; tab; flush.
+ 		 coInterpreter cloneSimulation objectMemory fullGC.
+ 		 Smalltalk garbageCollect].
+ 	^super fullGC!
- 	self halt.
- 	coInterpreter transcript
- 		cr; nextPutAll:'<Running full GC ('; print: coInterpreter byteCount; space; print: freeStart; nextPutAll: ')...'; flush.
- 	super fullGC.
- 	coInterpreter transcript show: ' done>'!

Item was changed:
+ ----- Method: NewObjectMemorySimulator>>incrementalGC (in category 'gc -- mark and sweep') -----
- ----- Method: NewObjectMemorySimulator>>incrementalGC (in category 'debug support') -----
  incrementalGC
+ 	"If we're /not/ a clone, clone the VM and push it over the cliff.
+ 	 If it survives, destroy the clone and continue.  We should be OK until next time."
+ 	(self leakCheckIncrementalGC
+ 	 and: [parent isNil]) ifTrue:
+ 		[coInterpreter cr; print: 'Incremental GC number '; print: statIncrGCs; tab; flush.
+ 		 coInterpreter cloneSimulation objectMemory incrementalGC.
+ 		 Smalltalk garbageCollect].
- 	coInterpreter transcript cr; nextPutAll: 'incrementalGC ('; print: coInterpreter byteCount; space; print: freeStart; nextPut: $); flush.
  	^super incrementalGC!

Item was added:
+ ----- Method: NewObjectMemorySimulator>>parent (in category 'accessing') -----
+ parent
+ 
+ 	^ parent!

Item was added:
+ ----- Method: NewObjectMemorySimulator>>parent: (in category 'accessing') -----
+ parent: anObject
+ 
+ 	parent := anObject!

Item was added:
+ ----- Method: SmartSyntaxPluginSimulator>>generateCoerceToBooleanObjectFrom:on: (in category 'simulation') -----
+ generateCoerceToBooleanObjectFrom: aBoolean on: ignored
+ 	^interpreterProxy booleanObjectOf: aBoolean!

Item was added:
+ ----- Method: SmartSyntaxPluginSimulator>>generateCoerceToFloatObjectFrom:on: (in category 'simulation') -----
+ generateCoerceToFloatObjectFrom: aNumber on: ignored
+ 	^interpreterProxy floatObjectOf: aNumber!



More information about the Vm-dev mailing list