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

commits at source.squeak.org commits at source.squeak.org
Wed Mar 18 00:10:38 UTC 2015


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

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

Name: VMMaker.oscog-eem.1094
Author: eem
Time: 17 March 2015, 5:08:01.778 pm
UUID: f3729206-0d5c-4380-bdd8-790bbbbc500d
Ancestors: VMMaker.oscog-eem.1093

Make the ISA explicit in the VM generators, now that
we're running the ARM simulator alongside the IA32
one.  Make sure Cogit is initialized with options
when generating the interpreter.

Fix assertClassOf:is: to handle immediates upstream
of isClassOfNonImm:equalTo:.

Fix CogARMCompiler>>computeMaximumSize for Slang.

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

Item was added:
+ ----- Method: CoInterpreter class>>hasCogit (in category 'accessing class hierarchy') -----
+ hasCogit
+ 	^true!

Item was changed:
  ----- Method: CoInterpreter>>printMethodCacheFor: (in category 'debug printing') -----
  printMethodCacheFor: thing
  	<api>
  	0 to: MethodCacheSize - 1 by: MethodCacheEntrySize do:
  		[:i | | s c m p |
  		s := methodCache at: i + MethodCacheSelector.
  		c := methodCache at: i + MethodCacheClass.
  		m := methodCache at: i + MethodCacheMethod.
  		p := methodCache at: i + MethodCachePrimFunction.
  		((thing = -1 or: [s = thing or: [c = thing or: [p = thing or: [m = thing
  			or: [(objectMemory addressCouldBeObj: m)
  				and: [(self maybeMethodHasCogMethod: m)
  				and: [(self cogMethodOf: m) asInteger = thing]]]]]]])
  		 and: [(objectMemory addressCouldBeOop: s)
  		 and: [c ~= 0
  		 and: [(self addressCouldBeClassObj: c)
  			or: [self addressCouldBeClassObj: (objectMemory classForClassTag: c)]]]]) ifTrue:
  			[self cCode: [] inSmalltalk: [self transcript ensureCr].
  			 self printNum: i; cr; tab.
  			 (objectMemory isBytesNonImm: s)
+ 				ifTrue: [self cCode: 'printf("%lx %.*s\n", s, numBytesOf(s), (char *)firstIndexableField(s))'
- 				ifTrue: [self cCode: 'printf("%x %.*s\n", s, numBytesOf(s), (char *)firstIndexableField(s))'
  						inSmalltalk: [self printHex: s; space; print: (self stringOf: s); cr]]
  				ifFalse: [self shortPrintOop: s].
  			 self tab.
  			 (self addressCouldBeClassObj: c)
  				ifTrue: [self shortPrintOop: c]
  				ifFalse: [self printNum: c; space; shortPrintOop: (objectMemory classForClassTag: c)].
  			self tab; shortPrintOop: m; tab.
  			self cCode:
  					[p > 1024
  						ifTrue: [self printHexnp: p]
  						ifFalse: [self printNum: p]]
  				inSmalltalk:
  					[p isSymbol ifTrue: [self print: p] ifFalse: [self printNum: p]].
  			self cr]]!

Item was changed:
  ----- Method: CogARMCompiler>>computeMaximumSize (in category 'generate machine code') -----
  computeMaximumSize
  	"Because we don't use Thumb, each ARM instruction has 4 bytes. Some abstract opcodes need more than one instruction."
  	
+ 	(opcode between: FirstShortJump and: LastJump) ifTrue:
+ 		[^maxSize := 16].
- 	| rotateableAt0then4or20Block |
- 	rotateableAt0then4or20Block := [^self rotateable8bitImmediate: (operands at: 0)
- 											ifTrue: [:r :i| maxSize := 4]
- 											ifFalse: [maxSize := 20]].
  	
- 	
- 	(opcode between: FirstShortJump and: LastJump) ifTrue: [^maxSize := 16].
- 	
  	opcode
  		caseOf: {
  			[Label]					-> [^maxSize := 0].
  			[AlignmentNops]		-> [^maxSize := (operands at: 0) - 1].
  			[MoveAwR]				-> [^maxSize := 20].
  			[MoveCqR]				-> [^self rotateable8bitImmediate: (operands at: 0)
  											ifTrue: [:r :i| maxSize := 4]
  											ifFalse: [maxSize := 16]].
  			[MoveCwR]				-> [^maxSize := 16].
  			[MoveRAw]				-> [^maxSize := 20].
  			[MoveRMwr]			-> [self is12BitValue: (operands at: 1)
  											ifTrue: [ :u :i | ^maxSize := 4]
  											ifFalse: [ ^maxSize := 20 ]].
  			[MoveRMbr]				-> [self is12BitValue: (operands at: 1)
  											ifTrue: [ :u :i | ^maxSize := 4]
  											ifFalse: [ ^maxSize := 20 ]].
  			[MoveMwrR]			-> [self is12BitValue: (operands at: 0)
  											ifTrue: [ :u :i | ^maxSize := 4]
  											ifFalse: [ ^maxSize := 20 ]].
  			[MoveMbrR]				-> [self is12BitValue: (operands at: 0)
  											ifTrue: [ :u :i | ^maxSize := 4]
  											ifFalse: [ ^maxSize := 20 ]].
  			[PrefetchAw] 			-> [^maxSize := 20].
  			[Call]					-> [^maxSize := 20 "recomputed in #sizePCDependentInstruction."].
  			[RetN]					-> [^(operands at: 0) = 0 
  											ifTrue: [maxSize := 4]
  											ifFalse: [maxSize := 8]].
+ 			[CmpCqR]				-> [^self rotateable8bitImmediate: (operands at: 0)
+ 											ifTrue: [:r :i| maxSize := 4]
+ 											ifFalse: [maxSize := 20]].
+ 			[AddCqR]				-> [^self rotateable8bitImmediate: (operands at: 0)
+ 											ifTrue: [:r :i| maxSize := 4]
+ 											ifFalse: [maxSize := 20]].
+ 			[BICCqR]				-> [^self rotateable8bitImmediate: (operands at: 0)
+ 											ifTrue: [:r :i| maxSize := 4]
+ 											ifFalse: [maxSize := 20]].
+ 			[SubCqR]				-> [^self rotateable8bitImmediate: (operands at: 0)
+ 											ifTrue: [:r :i| maxSize := 4]
+ 											ifFalse: [maxSize := 20]].
+ 			[AndCqR]				-> [^self rotateable8bitImmediate: (operands at: 0)
+ 											ifTrue: [:r :i| maxSize := 4]
+ 											ifFalse: [maxSize := 20]].
+ 			[OrCqR]					-> [^self rotateable8bitImmediate: (operands at: 0)
+ 											ifTrue: [:r :i| maxSize := 4]
+ 											ifFalse: [maxSize := 20]].
+ 			[TstCqR]				-> [^self rotateable8bitImmediate: (operands at: 0)
+ 											ifTrue: [:r :i| maxSize := 4]
+ 											ifFalse: [maxSize := 20]].
+ 			[XorCqR]				-> [^self rotateable8bitImmediate: (operands at: 0)
+ 											ifTrue: [:r :i| maxSize := 4]
+ 											ifFalse: [maxSize := 20]].
- 			[CmpCqR]				-> [rotateableAt0then4or20Block value].
- 			[AddCqR]				-> [rotateableAt0then4or20Block value].
- 			[BICCqR]				-> [rotateableAt0then4or20Block value].
- 			[SubCqR]				-> [rotateableAt0then4or20Block value].
- 			[AndCqR]				-> [rotateableAt0then4or20Block value].
- 			[OrCqR]					-> [rotateableAt0then4or20Block value].
- 			[TstCqR]				-> [rotateableAt0then4or20Block value].
- 			[XorCqR]				-> [rotateableAt0then4or20Block value].
  			[CmpCwR]				-> [^maxSize := 20].
  			[AddCwR]				-> [^maxSize := 20].
  			[SubCwR]				-> [^maxSize := 20].
  			[AndCwR]				-> [^maxSize := 20].
  			[OrCwR]				-> [^maxSize := 20].
  			[XorCwR]				-> [^maxSize := 20].
  			[JumpR]					-> [^maxSize := 4].
  			[JumpFPEqual]			-> [^maxSize := 8].
  			[JumpFPNotEqual]		-> [^maxSize := 8].
  			[JumpFPLess]			-> [^maxSize := 8].
  			[JumpFPGreaterOrEqual]-> [^maxSize := 8].
  			[JumpFPGreater]		-> [^maxSize := 8].
  			[JumpFPLessOrEqual]	-> [^maxSize := 8].
  			[JumpFPOrdered]		-> [^maxSize := 8].
  			[JumpFPUnordered]		-> [^maxSize := 8].
  			[JumpLong]				-> [^maxSize := 20].
  			[JumpLongZero]		-> [^maxSize := 20].
  			[JumpLongNonZero]	-> [^maxSize := 20].
+ 			[LoadEffectiveAddressMwrR]
+ 									-> [^self rotateable8bitImmediate: (operands at: 0)
+ 											ifTrue: [:r :i| maxSize := 4]
+ 											ifFalse: [maxSize := 20]].
- 			[LoadEffectiveAddressMwrR] -> [rotateableAt0then4or20Block value].
  			[PushCw]				-> [^maxSize := 20].
  		}
  		otherwise: [^maxSize := 4].
  	^4 "to keep C compiler quiet"
  !

Item was changed:
  ----- Method: CogARMCompiler>>rotateable8bitImmediate:ifTrue:ifFalse: (in category 'testing') -----
  rotateable8bitImmediate: constant ifTrue: trueAlternativeBlock ifFalse: falseAlternativeBlock
+ 	<inline: true>
  	"For data processing operands, there is the immediate shifter_operand variant, 
  	where an 8 bit value is ring shifted _right_ by 2*i.
  	This is only suitable for quick constant(Cq), which don't change."
  	
  	(constant bitAnd: 16rFF) = constant ifTrue: [ ^trueAlternativeBlock value: 0 value: constant].
  	2 to: 30 do: [:i |
  		(constant bitAnd: 16rFF << i) = constant 
  			ifTrue: [ ^trueAlternativeBlock value: 32 - i value: constant >> i ]].
  	^falseAlternativeBlock value!

Item was changed:
  ----- Method: ObjectMemory>>isClassOfNonImm:equalTo: (in category 'header access') -----
  isClassOfNonImm: oop equalTo: classOop
  	"Answer if the given (non-immediate) object is an instance of the given class."
  
  	| ccIndex cl |
  	<inline: true>
+ 	self assert: (self isNonImmediate: oop).
- 	(self isIntegerObject: oop) ifTrue:
- 		[^false].
  
  	cl := (ccIndex := self compactClassIndexOf: oop) = 0
  			ifTrue: [(self classHeader: oop) bitAnd: AllButTypeMask]
  			ifFalse: [self compactClassAt: ccIndex].
  	^cl = classOop!

Item was changed:
  ----- Method: SpurMemoryManager>>isClassOfNonImm:equalTo: (in category 'object testing') -----
  isClassOfNonImm: objOop equalTo: classOop
+ 	<inline: true>
+ 	self assert: (self isNonImmediate: objOop).
  	^(self classIndexOf: objOop) = (self rawHashBitsOf: classOop)!

Item was changed:
  ----- Method: StackInterpreter>>assertClassOf:is: (in category 'utilities') -----
  assertClassOf: oop is: classOop
  	"Succeed if oop is an instance of the given class. Fail if the object is an integer."
+ 	| ok |
- 
  	<inline: true>
+ 	ok := objectMemory isNonImmediate: oop.
+ 	ok ifTrue:
+ 		[ok := objectMemory isClassOfNonImm: oop equalTo: classOop].
+ 	self success: ok!
- 	self success: (objectMemory isClassOfNonImm: oop equalTo: classOop)!

Item was added:
+ ----- Method: VMClass class>>hasCogit (in category 'accessing class hierarchy') -----
+ hasCogit
+ 	^false!

Item was changed:
  ----- Method: VMMaker class>>generateEitherSqueakCogVM (in category 'configurations') -----
  generateEitherSqueakCogVM
  	| coInterpreterClass |
  	coInterpreterClass := self chooseCoInterpreterClassIfAbsent: [^self].
  	^self generateSqueakCogVMWithInterpreterClass: coInterpreterClass
+ 		  options: #( ISA IA32),
+ 					((coInterpreterClass includesBehavior: CoInterpreterMT)
+ 						ifTrue: [#(COGMTVM true)]
+ 						ifFalse: [#()])!
- 		  options: ((coInterpreterClass includesBehavior: CoInterpreterMT)
- 					ifTrue: [#(COGMTVM true)]
- 					ifFalse: [#()])!

Item was changed:
  ----- Method: VMMaker class>>generateNewspeakSpurCogVM (in category 'configurations') -----
  generateNewspeakSpurCogVM
  	"No primitives since we can use those for the Cog Newspeak VM"
  	^VMMaker
  		generate: CoInterpreter
  		and: StackToRegisterMappingCogit
  		with: #(	ObjectMemory Spur32BitCoMemoryManager
  				MULTIPLEBYTECODESETS true
+ 				NewspeakVM true
+ 				ISA IA32)
- 				NewspeakVM true)
  		to: (FileDirectory default pathFromURI: self sourceTree, '/nsspursrc')
  		platformDir: (FileDirectory default pathFromURI: self sourceTree, '/platforms')
  		including:#(	AsynchFilePlugin BMPReadWriterPlugin BalloonEnginePlugin BitBltSimulation
  					DeflatePlugin DSAPlugin DropPlugin FileCopyPlugin FilePlugin FloatArrayPlugin FloatMathPlugin
  					ImmX11Plugin JPEGReadWriter2Plugin JPEGReaderPlugin LargeIntegersPlugin
  					Matrix2x3Plugin MiscPrimitivePlugin NewsqueakIA32ABIPlugin RePlugin
  					SecurityPlugin SocketPlugin SoundPlugin SqueakSSLPlugin SurfacePlugin
  					UUIDPlugin UnixOSProcessPlugin UnixAioPlugin
  					VMProfileLinuxSupportPlugin VMProfileMacSupportPlugin Win32OSProcessPlugin)
  !

Item was changed:
  ----- Method: VMMaker class>>generateSqueakCogSistaVM (in category 'configurations') -----
  generateSqueakCogSistaVM
  	"No primitives since we can use those for the Cog VM"
  	^VMMaker
  		generate: CoInterpreter
  		and: SistaStackToRegisterMappingCogit
  		with: #(	SistaVM true
  				MULTIPLEBYTECODESETS true
+ 				ISA IA32
  				bytecodeTableInitializer initializeBytecodeTableForSqueakV3PlusClosuresSistaV1Hybrid)
  		to: (FileDirectory default pathFromURI: self sourceTree, '/sistasrc')
  		platformDir: (FileDirectory default pathFromURI: self sourceTree, '/platforms')
  		including: #()!

Item was changed:
  ----- Method: VMMaker class>>generateSqueakSpurCogSistaVM (in category 'configurations') -----
  generateSqueakSpurCogSistaVM
  	"No primitives since we can use those for the Cog VM"
  	^VMMaker
  		generate: CoInterpreter
  		and: SistaStackToRegisterMappingCogit
  		with: #(	SistaVM true
  				ObjectMemory Spur32BitCoMemoryManager
  				MULTIPLEBYTECODESETS true
+ 				ISA IA32
  				bytecodeTableInitializer initializeBytecodeTableForSqueakV3PlusClosuresSistaV1Hybrid)
  		to: (FileDirectory default pathFromURI: self sourceTree, '/spursistasrc')
  		platformDir: (FileDirectory default pathFromURI: self sourceTree, '/platforms')
  		including:#()!

Item was changed:
  ----- Method: VMMaker class>>generateSqueakSpurCogVM (in category 'configurations') -----
  generateSqueakSpurCogVM
  	"No primitives since we can use those for the Cog VM"
  	^VMMaker
  		generate: CoInterpreter
  		and: StackToRegisterMappingCogit
+ 		with: #(	ObjectMemory Spur32BitCoMemoryManager
+ 				ISA IA32)
- 		with: #(	ObjectMemory Spur32BitCoMemoryManager)
  		to: (FileDirectory default pathFromURI: self sourceTree, '/spursrc')
  		platformDir: (FileDirectory default pathFromURI: self sourceTree, '/platforms')
  		including:#()!

Item was changed:
  ----- Method: VMMaker>>buildCodeGeneratorForInterpreter:includeAPIMethods:initializeClasses: (in category 'generate sources') -----
  buildCodeGeneratorForInterpreter: interpreterClass includeAPIMethods: getAPIMethods initializeClasses: initializeClasses
  	"Answer the code generator for translating the interpreter."
  
  	| cg interpreterClasses apicg |
  	initializeClasses ifTrue:
+ 		[interpreterClass initializeWithOptions: optionsDictionary.
+ 		 interpreterClass hasCogit ifTrue:
+ 			[interpreterClass cogitClass initializeWithOptions: optionsDictionary]].
- 		[interpreterClass initializeWithOptions: optionsDictionary].
  
  	(cg := self createCodeGenerator) vmClass: interpreterClass.
  
  	"Construct interpreterClasses as all classes from interpreterClass &
  	 objectMemoryClass up to VMClass in superclass to subclass order."
  	interpreterClasses := OrderedCollection new.
  	{interpreterClass. interpreterClass objectMemoryClass} do:
  		[:vmClass| | theClass |
  		 theClass := vmClass.
  		 [theClass ~~ VMClass] whileTrue:
  			[interpreterClasses addFirst: theClass.
  			 theClass := theClass superclass]].
  	interpreterClasses
  		addFirst: VMClass;
  		addAllLast: (cg nonStructClassesForTranslationClasses: interpreterClasses).
  
  	initializeClasses ifTrue:
  		[interpreterClasses do:
  			[:ic|
  			(ic respondsTo: #initializeWithOptions:)
  				ifTrue: [ic initializeWithOptions: optionsDictionary]
  				ifFalse: [ic initialize]].
  		 (cg structClassesForTranslationClasses: interpreterClasses) do:
  			[:structClass| structClass initialize]].
  
  	cg addStructClasses: (cg structClassesForTranslationClasses: interpreterClasses).
  
  	interpreterClasses do: [:ic| cg addClass: ic].
  
  	getAPIMethods ifTrue:
  		[interpreterClass cogitClass ifNotNil:
  			[:cogitClass|
  			 apicg := self
  						buildCodeGeneratorForCogit: cogitClass
  						includeAPIMethods: false
  						initializeClasses: false.
  			 cg apiMethods: apicg selectAPIMethods]].
  
  	cg removeConstant: #VMBIGENDIAN. "this should be defined in platforms/??/vm/sqConfig.h"
  
  	^cg!



More information about the Vm-dev mailing list