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

commits at source.squeak.org commits at source.squeak.org
Thu Jan 5 21:04:56 UTC 2017


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

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

Name: VMMaker.oscog-eem.2074
Author: eem
Time: 5 January 2017, 1:04:01.289587 pm
UUID: 37096fe1-c17e-4eb5-af1a-2263ca85ca64
Ancestors: VMMaker.oscog-nice.2073

Fix the NumTrampolines issue, albeit in an ugly way.
Revert some timestamps of unchanged methods.

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

Item was changed:
  ----- Method: CCodeGenerator>>emitCConstants:on: (in category 'C code generator') -----
  emitCConstants: constList on: aStream
  	"Store the global variable declarations on the given stream."
  	constList isEmpty ifTrue: [^self].
  	aStream cr; nextPutAll: '/*** Constants ***/'; cr.
  	(self sortStrings: constList) do:
  		[:varName| | node default value conditional |
  		node := constants at: varName.
  		node name isEmpty ifFalse:
+ 			["If the definition includes a C comment, or looks like a conditional, take it as is, otherwise convert
+ 			  the value from Smalltalk to C.
- 			["If the definition includes a C comment, take it as is, otherwise convert the value from Smalltalk to C.
  			  Allow the class to provide an alternative definition, either of just the value or the whole shebang."
+ 			default := (node value isString
+ 						and: [(node value includesSubString: '/*')
+ 								or: [(node value includesSubString: ' ? ') and: [node value includesSubString: ' : ']]])
- 			default := (node value isString and: [node value includesSubString: '/*'])
  							ifTrue: [node value]
  							ifFalse: [self cLiteralFor: node value name: varName].
  			default = #undefined
  				ifTrue: [aStream nextPutAll: '#undef '; nextPutAll: node name; cr]
  				ifFalse:
  					[conditional := (vmClass ifNil: VMBasicConstants) defineAtCompileTime: node name.
  					conditional ifTrue:
  						[aStream nextPutAll: '#if !!defined('; nextPutAll: node name; nextPutAll: ') /* Allow this to be overridden on the compiler command line */'; cr].
  					value := vmClass
  								ifNotNil:
  									[(vmClass specialValueForConstant: node name default: default)
  										ifNotNil: [:specialDef| specialDef]
  										ifNil: [default]]
  								ifNil: [default].
  					value first ~= $# ifTrue:
  						[aStream nextPutAll: (conditional ifTrue: ['# define '] ifFalse: ['#define ']); nextPutAll: node name; space].
  					aStream nextPutAll: value; cr.
  					conditional ifTrue:
  						[aStream nextPutAll: '#endif'; cr]]]].
  	aStream cr!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCodeGen
+ 	"Deal wuth the fact that the number of trampolines depends on IMMUTABILITY
+ 	 and that IMMUTABILITY can be defined at compile time.  Yes, this is a mess."
+ 	| current values |
+ 	self assert: (CogObjectRepresentationForSpur allSubclasses allSatisfy:
+ 					[:sc|
+ 					 CogObjectRepresentationForSpur initializationOptions == sc initializationOptions]).
+ 	current := initializationOptions at: #IMMUTABILITY ifAbsent: nil.
+ 	values := #(true false) collect:
+ 				[:bool|
+ 				 initializationOptions at: #IMMUTABILITY put: bool.
+ 				 self cogitClass initializeNumTrampolines.
+ 				 (Cogit classPool at: #NumTrampolines) printString].
+ 	current
+ 		ifNil: [initializationOptions removeKey: #IMMUTABILITY]
+ 		ifNotNil: [initializationOptions at: #IMMUTABILITY put: current].
+ 	values first ~= values last ifTrue:
+ 		[aCodeGen addConstantForBinding: #NumTrampolines -> ('(IMMUTABILITY ? ' , values first , ' : ' , values last , ')')].
  	aCodeGen
  		var: #ceStoreTrampolines
  		declareC: ('#if IMMUTABILITY\sqInt ceStoreTrampolines[', NumStoreTrampolines printString, '];\#endif') withCRs!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur class>>numTrampolines (in category 'accessing') -----
  numTrampolines
  	^super numTrampolines
  	 + (SistaV1BytecodeSet
  		ifTrue: [8] "(small,large)x(method,block,fullBlock) context creation,
  					 ceStoreCheckContextReceiverTrampoline and ceScheduleScavengeTrampoline"
  		ifFalse: [6] "(small,large)x(method,block) context creation,
  					 ceStoreCheckContextReceiverTrampoline and ceScheduleScavengeTrampoline")
+ 	 + ((initializationOptions at: #IMMUTABILITY ifAbsent: [false])
- 	 + NumStoreTrampolines "FIXME: the generated C code does not take into account whether IMMUTABILITY is defined to one or zero"
- 		"((initializationOptions at: #IMMUTABILITY ifAbsent: [false])
  		ifTrue: [NumStoreTrampolines]
+ 		ifFalse: [0])!
- 		ifFalse: [0])"!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>generateObjectRepresentationTrampolines (in category 'initialization') -----
  generateObjectRepresentationTrampolines
  	"Do the store check.  Answer the argument for the benefit of the code generator;
  	 ReceiverResultReg may be caller-saved and hence smashed by this call.  Answering
  	 it allows the code generator to reload ReceiverResultReg cheaply.
  	 In Spur the only thing we leave to the run-time is adding the receiver to the
  	 remembered set and setting its isRemembered bit."
  	self 
  		cppIf: IMMUTABILITY
  		ifTrue: 
  			[self cCode: [] inSmalltalk:
  				[ceStoreTrampolines := CArrayAccessor on: (Array new: NumStoreTrampolines)].
  			 0 to: NumStoreTrampolines - 1 do:
  				[:instVarIndex |
  				 ceStoreTrampolines
  					at: instVarIndex
  					put: (self 
  							genStoreTrampolineCalled: (cogit 
  															trampolineName: 'ceStoreTrampoline' 
  															numArgs: instVarIndex 
  															limit: NumStoreTrampolines - 2) 
  							instVarIndex: instVarIndex)]].
  	ceStoreCheckTrampoline := self genStoreCheckTrampoline.
  	ceStoreCheckContextReceiverTrampoline := self genStoreCheckContextReceiverTrampoline.
  	ceScheduleScavengeTrampoline := cogit
  											genTrampolineFor: #ceScheduleScavenge
  											called: 'ceScheduleScavengeTrampoline'
  											regsToSave: CallerSavedRegisterMask.
  	ceSmallActiveContextInMethodTrampoline := self genActiveContextTrampolineLarge: false inBlock: 0 called: 'ceSmallMethodContext'.
  	ceSmallActiveContextInBlockTrampoline := self genActiveContextTrampolineLarge: false inBlock: InVanillaBlock called: 'ceSmallBlockContext'.
  	SistaV1BytecodeSet ifTrue:
  		[ceSmallActiveContextInFullBlockTrampoline := self genActiveContextTrampolineLarge: false inBlock: InFullBlock called: 'ceSmallFullBlockContext'].
  	ceLargeActiveContextInMethodTrampoline := self genActiveContextTrampolineLarge: true inBlock: 0 called: 'ceLargeMethodContext'.
  	ceLargeActiveContextInBlockTrampoline := self genActiveContextTrampolineLarge: true inBlock: InVanillaBlock called: 'ceLargeBlockContext'.
  	SistaV1BytecodeSet ifTrue:
  		[ceLargeActiveContextInFullBlockTrampoline := self genActiveContextTrampolineLarge: true inBlock: InFullBlock called: 'ceLargeFullBlockContext'].
  		
  	LowcodeVM ifTrue: [ self generateLowcodeObjectTrampolines ]!

Item was changed:
  ----- Method: Cogit>>generateRunTimeTrampolines (in category 'initialization') -----
  generateRunTimeTrampolines
  	"Generate the run-time entries at the base of the native code zone and update the base."
  	
  	ceSendMustBeBooleanAddFalseTrampoline := self genMustBeBooleanTrampolineFor: objectMemory falseObject
  														called: 'ceSendMustBeBooleanAddFalseTrampoline'.
  	ceSendMustBeBooleanAddTrueTrampoline := self genMustBeBooleanTrampolineFor: objectMemory trueObject
  														called: 'ceSendMustBeBooleanAddTrueTrampoline'.
  	ceNonLocalReturnTrampoline := self genNonLocalReturnTrampoline.
  	ceCheckForInterruptTrampoline := self genCheckForInterruptsTrampoline.
  	"Neither of the context inst var access trampolines save registers.  Their operation could cause
  	 arbitrary update of stack frames, so the assumption is that callers flush the stack before calling
  	 the context inst var access trampolines, and that everything except the result is dead afterwards."
  	ceFetchContextInstVarTrampoline := self genTrampolineFor: #ceContext:instVar:
  											called: 'ceFetchContextInstVarTrampoline'
  											arg: ReceiverResultReg
  											arg: SendNumArgsReg
  											result: SendNumArgsReg.
  	ceStoreContextInstVarTrampoline := self genTrampolineFor: #ceContext:instVar:value:
  											called: 'ceStoreContextInstVarTrampoline'
  											arg: ReceiverResultReg
  											arg: SendNumArgsReg
  											arg: ClassReg
  											result: ReceiverResultReg. "to keep ReceiverResultReg live.".
  	ceCannotResumeTrampoline := self genTrampolineFor: #ceCannotResume
  											called: 'ceCannotResumeTrampoline'.
  	"These two are unusual; they are reached by return instructions."
  	ceBaseFrameReturnTrampoline := self genReturnTrampolineFor: #ceBaseFrameReturn:
  											called: 'ceBaseFrameReturnTrampoline'
  											arg: ReceiverResultReg.
  	ceReturnToInterpreterTrampoline := self
  											genReturnTrampolineFor: #ceReturnToInterpreter:
  											called: 'ceReturnToInterpreterTrampoline'
  											arg: ReceiverResultReg.
  	ceMallocTrampoline := self genTrampolineFor: #ceMalloc:
  											called: 'ceMallocTrampoline'
  											arg: ReceiverResultReg
  											result: TempReg.
  	ceFreeTrampoline := self genTrampolineFor: #ceFree:
  											called: 'ceFreeTrampoline'
  											arg: ReceiverResultReg.
  	LowcodeVM ifTrue: [
  		ceFFICalloutTrampoline := self genFFICalloutTrampoline.
  	]!

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



More information about the Vm-dev mailing list