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

commits at source.squeak.org commits at source.squeak.org
Thu Mar 27 23:12:58 UTC 2014


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

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

Name: VMMaker.oscog-eem.657
Author: eem
Time: 27 March 2014, 4:10:30.432 pm
UUID: 11ce8f75-e6b4-4923-8336-720d3da9acbd
Ancestors: VMMaker.oscog-eem.656

Make primitivePathToUsing work on Spur also.

Add ImmX11Plugin to generated plugins.

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

Item was changed:
  ----- Method: CoInterpreterPrimitives>>pathTo:using:followWeak: (in category 'object access primitives') -----
  pathTo: goal using: stack followWeak: followWeak
  	"Trace objects and frames from the root, marking visited objects, pushing the current path on stack, until goal is found.
  	 If found, unmark, leaving path in stack, and answer 0.  Otherwise answer an error:
  		PrimErrBadArgument if stack is not an Array
  		PrimErrBadIndex if search overflows stack
  		PrimErrNotFound if goal cannot be found"
+ 	| current index next stackSize stackp freeStartAtStart |
- 	| current hdr index next stackSize stackp freeStartAtStart |
  	(objectMemory isArray: stack) ifFalse:
  		[^PrimErrBadArgument].
+ 	self assert: objectMemory allObjectsUnmarked.
  	freeStartAtStart := objectMemory freeStart. "check no allocations during search"
  	objectMemory beRootIfOld: stack. "so no store checks are necessary on stack"
  	stackSize := objectMemory lengthOf: stack.
  	objectMemory mark: stack.
  	"no need. the current context is not reachable from the active process (suspendedContext is nil)"
  	"objectMemory mark: self activeProcess."
  	current := objectMemory specialObjectsOop.
  	objectMemory mark: current.
  	index := objectMemory lengthOf: current.
  	stackp := 0.
  	[[(index := index - 1) >= -1] whileTrue:
  		[(stackPages couldBeFramePointer: current)
  			ifTrue:
  				[next := index >= 0
  							ifTrue: [self field: index ofFrame: (self cCoerceSimple: current to: #'char *')]
  							ifFalse: [objectMemory nilObject]]
  			ifFalse:
  				[index >= 0
  					ifTrue:
+ 						[next := (objectMemory isContextNonImm: current)
- 						[hdr := objectMemory baseHeader: current.
- 						next := (objectMemory isContextHeader: hdr)
  									ifTrue: [self fieldOrSenderFP: index ofContext: current]
  									ifFalse: [objectMemory fetchPointer: index ofObject: current]]
  					ifFalse:
  						[next := objectMemory fetchClassOfNonImm: current]].
  		 (stackPages couldBeFramePointer: next)
  			ifTrue: [self assert: (self isFrame: (self cCoerceSimple: next to: #'char *')
  										onPage: (stackPages stackPageFor: (self cCoerceSimple: next to: #'char *')))]
  			ifFalse:
+ 				[next >= heapBase ifTrue: "exclude Cog methods"
- 				[next >= heapBase ifTrue:
  					[self assert: (self checkOkayOop: next)]].
  		 next = goal ifTrue:
  			[self assert: freeStartAtStart = objectMemory freeStart.
  			 self unmarkAfterPathTo.
  			 objectMemory storePointer: stackp ofObject: stack withValue: current.
  			 self pruneStack: stack stackp: stackp.
  			 ^0].
  		 ((objectMemory isNonIntegerObject: next)
  		  and: [(stackPages couldBeFramePointer: next)
  				ifTrue: [(self frameIsMarked: next) not]
  				ifFalse:
  					[next >= heapBase "exclude Cog methods"
  					  and: [(objectMemory isMarked: next) not
  					  and: [((objectMemory isPointers: next) or: [objectMemory isCompiledMethod: next])
  					  and: [followWeak or: [(objectMemory isWeakNonImm: next) not]]]]]])
  			ifTrue:
  				[stackp + 2 > stackSize ifTrue:
  					[self assert: freeStartAtStart = objectMemory freeStart.
  					 self unmarkAfterPathTo.
  					 objectMemory nilFieldsOf: stack.
  					 ^PrimErrBadIndex]. "PrimErrNoMemory ?"
  				 objectMemory
  					storePointerUnchecked: stackp ofObject: stack withValue: current;
  					storePointerUnchecked: stackp + 1 ofObject: stack withValue: (objectMemory integerObjectOf: index).
  				 stackp := stackp + 2.
  				 (stackPages couldBeFramePointer: (self cCoerceSimple: next to: #'char *'))
  					ifTrue:
  						[self markFrame: next.
  						index := self fieldsInFrame: (self cCoerceSimple: next to: #'char *')]
  					ifFalse:
+ 						[objectMemory mark: next.
+ 						 (objectMemory isCompiledMethod: next)
- 						[hdr := objectMemory baseHeader: next.
- 						 objectMemory baseHeader: next put: (hdr bitOr: MarkBit).
- 						 (objectMemory isCompiledMethodHeader: hdr)
  							ifTrue: [index := (self literalCountOf: next) + LiteralStart]
  							ifFalse: [index := objectMemory lengthOf: next]].
  				 current := next]].
  		 current = objectMemory specialObjectsOop ifTrue:
  			[self assert: freeStartAtStart = objectMemory freeStart.
  			 self unmarkAfterPathTo.
  			 objectMemory nilFieldsOf: stack.
  			^PrimErrNotFound].
  		 index := objectMemory integerValueOf: (objectMemory fetchPointer: stackp - 1 ofObject: stack).
  		 current := objectMemory fetchPointer: stackp - 2 ofObject: stack.
  		 stackp := stackp - 2] repeat!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitivePathToUsing (in category 'other primitives') -----
  primitivePathToUsing
  	"primitivePathTo: anObject using: stack <Array> followWeak: boolean
  	 Answer a path to anObject from the root that does not pass through
  	 the current context"
  	| err path |
  	<export: true>
- 	<option: #SqueakV3ObjectMemory> "for now..."
  	self externalWriteBackHeadFramePointers.
+ 	argumentCount >= 2 ifFalse:
+ 		[^self primitiveFailFor: PrimErrBadNumArgs].
+ 	(self stackTop = objectMemory trueObject
+ 	 or: [self stackTop = objectMemory falseObject]) ifFalse:
+ 		[^self primitiveFailFor: PrimErrBadArgument].
+ 	err := self pathTo: (self stackValue: 2)
+ 				using: (self stackValue: 1)
+ 				followWeak: self stackTop = objectMemory trueObject.
- 	err := self pathTo: (self stackValue: 2) using: (self stackValue: 1) followWeak: self stackTop = objectMemory trueObject.
  	err ~= 0 ifTrue:
  		[^self primitiveFailFor: err].
  	path := self self stackValue: 1.
  	self pop: argumentCount + 1 thenPush: path!

Item was added:
+ ----- Method: NewObjectMemory>>allObjectsUnmarked (in category 'primitive support') -----
+ allObjectsUnmarked
+ 	self allObjectsDo:
+ 		[:o| (self isMarked: o) ifTrue: [^false]].
+ 	^true!

Item was added:
+ ----- Method: ObjectMemory>>setIsMarkedOf:to: (in category 'header access') -----
+ setIsMarkedOf: objOop to: aBoolean
+ 	| header |
+ 	self assert: (self isFreeObject: objOop) not.
+ 	header := self baseHeader: objOop.
+ 	self
+ 		baseHeader: objOop
+ 		put: (aBoolean
+ 				ifTrue: [header bitOr: MarkBit]
+ 				ifFalse: [(header bitOr: MarkBit) - MarkBit])!

Item was added:
+ ----- Method: SpurMemoryManager>>mark: (in category 'primitive support') -----
+ mark: objOop
+ 	<inline: true>
+ 	self setIsMarkedOf: objOop to: true!

Item was added:
+ ----- Method: SpurMemoryManager>>unmarkAllObjects (in category 'primitive support') -----
+ unmarkAllObjects
+ 	self allHeapEntitiesDo:
+ 		[:obj|
+ 		 (self isMarked: obj) ifTrue:
+ 			[(self isNormalObject: obj)
+ 				ifTrue:
+ 					[self setIsMarkedOf: obj to: false]
+ 				ifFalse:
+ 					[(self isSegmentBridge: obj) ifFalse:
+ 						[self setIsMarkedOf: obj to: false]]]].
+ !

Item was changed:
  ----- Method: StackInterpreterPrimitives>>pathTo:using:followWeak: (in category 'object access primitives') -----
  pathTo: goal using: stack followWeak: followWeak
  	"Trace objects and frames from the root, marking visited objects, pushing the current path on stack, until goal is found.
  	 If found, unmark, leaving path in stack, and answer 0.  Otherwise answer an error:
  		PrimErrBadArgument if stack is not an Array
  		PrimErrBadIndex if search overflows stack
  		PrimErrNotFound if goal cannot be found"
+ 	| current index next stackSize stackp freeStartAtStart |
- 	| current hdr index next stackSize stackp freeStartAtStart |
  	(objectMemory isArray: stack) ifFalse:
  		[^PrimErrBadArgument].
+ 	self assert: objectMemory allObjectsUnmarked.
  	freeStartAtStart := objectMemory freeStart. "check no allocations during search"
  	objectMemory beRootIfOld: stack. "so no store checks are necessary on stack"
  	stackSize := objectMemory lengthOf: stack.
  	objectMemory mark: stack.
  	"no need. the current context is not reachable from the active process (suspendedContext is nil)"
  	"objectMemory mark: self activeProcess."
  	current := objectMemory specialObjectsOop.
  	objectMemory mark: current.
  	index := objectMemory lengthOf: current.
  	stackp := 0.
  	[[(index := index - 1) >= -1] whileTrue:
  		[(stackPages couldBeFramePointer: current)
  			ifTrue:
  				[next := index >= 0
  							ifTrue: [self field: index ofFrame: (self cCoerceSimple: current to: #'char *')]
  							ifFalse: [objectMemory nilObject]]
  			ifFalse:
  				[index >= 0
  					ifTrue:
+ 						[next := (objectMemory isContextNonImm: current)
- 						[hdr := objectMemory baseHeader: current.
- 						next := (objectMemory isContextHeader: hdr)
  									ifTrue: [self fieldOrSenderFP: index ofContext: current]
  									ifFalse: [objectMemory fetchPointer: index ofObject: current]]
  					ifFalse:
  						[next := objectMemory fetchClassOfNonImm: current]].
  		 (stackPages couldBeFramePointer: next)
  			ifTrue: [self assert: (self isFrame: next onPage: (stackPages stackPageFor: next))]
  			ifFalse: [self assert: (self checkOkayOop: next)].
  		 next = goal ifTrue:
  			[self assert: freeStartAtStart = objectMemory freeStart.
  			 self unmarkAfterPathTo.
  			 objectMemory storePointer: stackp ofObject: stack withValue: current.
  			 self pruneStack: stack stackp: stackp.
  			 ^0].
  		 ((objectMemory isNonIntegerObject: next)
  		  and: [(stackPages couldBeFramePointer: next)
  				ifTrue: [(self frameIsMarked: next) not]
  				ifFalse:
  					[(objectMemory isMarked: next) not
  					  and: [((objectMemory isPointers: next) or: [objectMemory isCompiledMethod: next])
  					  and: [followWeak or: [(objectMemory isWeakNonImm: next) not]]]]])
  			ifTrue:
  				[stackp + 2 > stackSize ifTrue:
  					[self assert: freeStartAtStart = objectMemory freeStart.
  					 self unmarkAfterPathTo.
  					 objectMemory nilFieldsOf: stack.
  					 ^PrimErrBadIndex]. "PrimErrNoMemory ?"
  				 objectMemory
  					storePointerUnchecked: stackp ofObject: stack withValue: current;
  					storePointerUnchecked: stackp + 1 ofObject: stack withValue: (objectMemory integerObjectOf: index).
  				 stackp := stackp + 2.
  				 (stackPages couldBeFramePointer: (self cCoerceSimple: next to: #'char *'))
  					ifTrue:
  						[self markFrame: next.
  						index := self fieldsInFrame: (self cCoerceSimple: next to: #'char *')]
  					ifFalse:
+ 						[objectMemory mark: next.
+ 						 (objectMemory isCompiledMethod: next)
- 						[hdr := objectMemory baseHeader: next.
- 						 objectMemory baseHeader: next put: (hdr bitOr: MarkBit).
- 						 (objectMemory isCompiledMethodHeader: hdr)
  							ifTrue: [index := (self literalCountOf: next) + LiteralStart]
  							ifFalse: [index := objectMemory lengthOf: next]].
  				 current := next]].
  		 current = objectMemory specialObjectsOop ifTrue:
  			[self assert: freeStartAtStart = objectMemory freeStart.
  			 self unmarkAfterPathTo.
  			 objectMemory nilFieldsOf: stack.
  			^PrimErrNotFound].
  		 index := objectMemory integerValueOf: (objectMemory fetchPointer: stackp - 1 ofObject: stack).
  		 current := objectMemory fetchPointer: stackp - 2 ofObject: stack.
  		 stackp := stackp - 2] repeat!

Item was changed:
  ----- Method: VMMaker class>>generateNewspeakCogVM (in category 'configurations') -----
  generateNewspeakCogVM
  	^VMMaker
  		generate: CoInterpreter
+ 		and: StackToRegisterMappingCogit
- 		and: StackToRegisterMappingCogit"Cogit chooseCogitClass"
  		with: #(	NewspeakVM true
  				MULTIPLEBYTECODESETS true)
  		to: (FileDirectory default pathFromURI: 'oscogvm/nscogsrc')
  		platformDir: (FileDirectory default pathFromURI: 'oscogvm/platforms')
+ 		including:#(	AsynchFilePlugin BMPReadWriterPlugin BalloonEnginePlugin BitBltSimulation DeflatePlugin DSAPlugin DropPlugin
+ 					FileCopyPlugin FilePlugin FloatArrayPlugin FloatMathPlugin ImmX11Plugin JPEGReadWriter2Plugin
- 		including:#(	AsynchFilePlugin BMPReadWriterPlugin BalloonEnginePlugin BitBltSimulation DSAPlugin DropPlugin
- 					FileCopyPlugin FilePlugin FloatArrayPlugin FloatMathPlugin DeflatePlugin JPEGReadWriter2Plugin
  					JPEGReaderPlugin LargeIntegersPlugin Matrix2x3Plugin MiscPrimitivePlugin NewsqueakIA32ABIPlugin
  					RePlugin SecurityPlugin SocketPlugin SoundPlugin SqueakSSLPlugin SurfacePlugin ThreadedIA32FFIPlugin
  					UUIDPlugin UnixOSProcessPlugin VMProfileLinuxSupportPlugin VMProfileMacSupportPlugin Win32OSProcessPlugin)!

Item was changed:
  ----- Method: VMMaker class>>generateNewspeakInterpreterVM (in category 'configurations') -----
  generateNewspeakInterpreterVM
  	^VMMaker
  		generate: NewspeakInterpreter
  		to: (FileDirectory default pathFromURI: 'oscogvm/nssrc')
  		platformDir: (FileDirectory default pathFromURI: 'oscogvm/platforms')
+ 		including:#(	AsynchFilePlugin BMPReadWriterPlugin BalloonEnginePlugin BitBltSimulation DeflatePlugin DSAPlugin DropPlugin
+ 					FileCopyPlugin FilePlugin FloatArrayPlugin FloatMathPlugin ImmX11Plugin JPEGReadWriter2Plugin
- 		including:#(	AsynchFilePlugin BMPReadWriterPlugin BalloonEnginePlugin BitBltSimulation DSAPlugin DropPlugin
- 					FileCopyPlugin FilePlugin FloatArrayPlugin FloatMathPlugin InflatePlugin JPEGReadWriter2Plugin
  					JPEGReaderPlugin LargeIntegersPlugin Matrix2x3Plugin MiscPrimitivePlugin NewsqueakIA32ABIPlugin
  					RePlugin SecurityPlugin SocketPlugin SoundPlugin SqueakSSLPlugin SurfacePlugin
  					UUIDPlugin UnixOSProcessPlugin VMProfileLinuxSupportPlugin VMProfileMacSupportPlugin Win32OSProcessPlugin)!

Item was changed:
  ----- Method: VMMaker class>>generateSqueakCogVMWithInterpreterClass: (in category 'confs-support') -----
  generateSqueakCogVMWithInterpreterClass: interpreterClass
  	^VMMaker
  		generate: interpreterClass
  		and: StackToRegisterMappingCogit
  		to: (FileDirectory default pathFromURI: 'oscogvm/src')
  		platformDir: (FileDirectory default pathFromURI: 'oscogvm/platforms')
  		including:#(	ADPCMCodecPlugin AsynchFilePlugin
  					BalloonEnginePlugin B3DAcceleratorPlugin BMPReadWriterPlugin BitBltSimulation BochsIA32Plugin
  					CameraPlugin CroquetPlugin DSAPlugin DeflatePlugin DropPlugin
  					FT2Plugin FFTPlugin FileCopyPlugin FilePlugin FloatArrayPlugin FloatMathPlugin
+ 					GeniePlugin HostWindowPlugin IA32ABIPlugin ImmX11Plugin InternetConfigPlugin
- 					GeniePlugin HostWindowPlugin IA32ABIPlugin InternetConfigPlugin
  					JPEGReadWriter2Plugin JPEGReaderPlugin JoystickTabletPlugin KlattSynthesizerPlugin
  					LargeIntegersPlugin LocalePlugin MIDIPlugin MacMenubarPlugin Matrix2x3Plugin
  					MiscPrimitivePlugin Mpeg3Plugin QuicktimePlugin RePlugin
  					ScratchPlugin SecurityPlugin SerialPlugin SocketPlugin
  					SoundCodecPlugin SoundGenerationPlugin SoundPlugin SqueakSSLPlugin StarSqueakPlugin
  					ThreadedIA32FFIPlugin UnicodePlugin UnixAioPlugin UUIDPlugin UnixOSProcessPlugin
  					Win32OSProcessPlugin VMProfileLinuxSupportPlugin VMProfileMacSupportPlugin WeDoPlugin)
  					
  !



More information about the Vm-dev mailing list