[Vm-dev] VM Maker: VMMaker-oscog-dtl.124.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Sep 7 11:49:37 UTC 2011


David T. Lewis uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker-oscog-dtl.124.mcz

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

Name: VMMaker-oscog-dtl.124
Author: dtl
Time: 7 September 2011, 7:47:23.321 am
UUID: 22506b93-842d-45e3-b57d-42b84f1657ae
Ancestors: VMMaker.oscog-eem.123

Support plugins (e.g FreetypePlugin) that use #bytesPerWord or #baseHeaderSize by adding these selectors to the C translation dictionary.

These changes produce no change to generated code for the VM except for the case of 'self bytesPerWord' which is now translated to the expected 'BytesPerWord' on oscog.

Class variables BytesPerWord and BaseHeaderSize (and others) do not exist in trunk VMMaker. These are now controlled at compile time rather than at C code generation time to support support a single generated code base for 32/64 bit object memory VMs.

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

Item was added:
+ ----- Method: CCodeGenerator>>generateBaseHeaderSize:on:indent: (in category 'C translation') -----
+ generateBaseHeaderSize: msgNode on: aStream indent: level
+ 	"Generate the C code for this message onto the given stream."
+ 
+ 	aStream nextPutAll: 'BaseHeaderSize'
+ 
+ !

Item was added:
+ ----- Method: CCodeGenerator>>generateBytesPerWord:on:indent: (in category 'C translation') -----
+ generateBytesPerWord: msgNode on: aStream indent: level
+ 	"Generate the C code for this message onto the given stream."
+ 
+ 	aStream nextPutAll: 'BytesPerWord'
+ !

Item was changed:
  ----- Method: CCodeGenerator>>initializeCTranslationDictionary (in category 'C translation') -----
  initializeCTranslationDictionary 
  	"Initialize the dictionary mapping message names to actions for C code generation."
  
  	| pairs |
  	translationDict := Dictionary new: 200.
  	pairs := #(
  	#&				#generateAnd:on:indent:
  	#|				#generateOr:on:indent:
  	#and:			#generateSequentialAnd:on:indent:
  	#or:			#generateSequentialOr:on:indent:
  	#not			#generateNot:on:indent:
  
  	#+				#generatePlus:on:indent:
  	#-				#generateMinus:on:indent:
  	#negated		#generateNegated:on:indent:
  	#*				#generateTimes:on:indent:
  	#/				#generateDivide:on:indent:
  	#//				#generateDivide:on:indent:
  	#\\				#generateModulo:on:indent:
  	#<<			#generateShiftLeft:on:indent:
  	#>>			#generateShiftRight:on:indent:
  	#min:			#generateMin:on:indent:
  	#max:			#generateMax:on:indent:
  	#between:and:	#generateBetweenAnd:on:indent:
  
  	#bitAnd:			#generateBitAnd:on:indent:
  	#bitOr:				#generateBitOr:on:indent:
  	#bitXor:			#generateBitXor:on:indent:
  	#bitShift:			#generateBitShift:on:indent:
  	#signedBitShift:	#generateSignedBitShift:on:indent:
  	#bitInvert32		#generateBitInvert32:on:indent:
  	#bitClear:			#generateBitClear:on:indent:
  
  	#<				#generateLessThan:on:indent:
  	#<=			#generateLessThanOrEqual:on:indent:
  	#=				#generateEqual:on:indent:
  	#>				#generateGreaterThan:on:indent:
  	#>=			#generateGreaterThanOrEqual:on:indent:
  	#~=			#generateNotEqual:on:indent:
  	#==			#generateEqual:on:indent:
  	#~~			#generateNotEqual:on:indent:
  	#isNil			#generateIsNil:on:indent:
  	#notNil			#generateNotNil:on:indent:
  
  	#whileTrue: 	#generateWhileTrue:on:indent:
  	#whileFalse:	#generateWhileFalse:on:indent:
  	#whileTrue 	#generateDoWhileTrue:on:indent:
  	#whileFalse		#generateDoWhileFalse:on:indent:
  	#to:do:			#generateToDo:on:indent:
  	#to:by:do:		#generateToByDo:on:indent:
  	#repeat 		#generateRepeat:on:indent:
  
  	#ifTrue:			#generateIfTrue:on:indent:
  	#ifFalse:		#generateIfFalse:on:indent:
  	#ifTrue:ifFalse:	#generateIfTrueIfFalse:on:indent:
  	#ifFalse:ifTrue:	#generateIfFalseIfTrue:on:indent:
  
  	#ifNotNil:		#generateIfNotNil:on:indent:
  	#ifNil:			#generateIfNil:on:indent:
  	#ifNotNil:ifNil:	#generateIfNotNilIfNil:on:indent:
  	#ifNil:ifNotNil:	#generateIfNilIfNotNil:on:indent:
  
  	#at:				#generateAt:on:indent:
  	#at:put:			#generateAtPut:on:indent:
  	#basicAt:		#generateAt:on:indent:
  	#basicAt:put:	#generateAtPut:on:indent:
  
  	#integerValueOf:			#generateIntegerValueOf:on:indent:
  	#integerObjectOf:			#generateIntegerObjectOf:on:indent:
  	#isIntegerObject: 			#generateIsIntegerObject:on:indent:
  	#cCode:					#generateInlineCCode:on:indent:
  	#cCode:inSmalltalk:			#generateInlineCCode:on:indent:
  	#cPreprocessorDirective:	#generateInlineCPreprocessorDirective:on:indent:
  	#cppIf:ifTrue:ifFalse:		#generateInlineCppIfElse:on:indent:
  	#cppIf:ifTrue:				#generateInlineCppIfElse:on:indent:
  	#cCoerce:to:				#generateCCoercion:on:indent:
  	#cCoerceSimple:to:			#generateCCoercion:on:indent:
  	#addressOf:				#generateAddressOf:on:indent:
  	#signedIntFromLong		#generateSignedIntFromLong:on:indent:
  	#signedIntToLong			#generateSignedIntToLong:on:indent:
  	#signedIntFromShort		#generateSignedIntFromShort:on:indent:
  	#signedIntToShort			#generateSignedIntToShort:on:indent:
  	#preIncrement				#generatePreIncrement:on:indent:
  	#preDecrement			#generatePreDecrement:on:indent:
  	#inline:						#generateInlineDirective:on:indent:
  	#asFloat					#generateAsFloat:on:indent:
  	#asInteger					#generateAsInteger:on:indent:
  	#asUnsignedInteger		#generateAsUnsignedInteger:on:indent:
  	#asSymbol					#generateAsSymbol:on:indent:
  	#anyMask:					#generateBitAnd:on:indent:
  	#raisedTo:					#generateRaisedTo:on:indent:
  	#touch:						#generateTouch:on:indent:
  
+ 	#bytesPerWord			#generateBytesPerWord:on:indent:
+ 	#baseHeaderSize			#generateBaseHeaderSize:on:indent:
+ 
  	#sharedCodeNamed:inCase:		#generateSharedCodeDirective:on:indent:
  
  	#perform:							#generatePerform:on:indent:
  	#perform:with:						#generatePerform:on:indent:
  	#perform:with:with:					#generatePerform:on:indent:
  	#perform:with:with:with:				#generatePerform:on:indent:
  	#perform:with:with:with:with:		#generatePerform:on:indent:
  	#perform:with:with:with:with:with:	#generatePerform:on:indent:
  
  	#value								#generateValue:on:indent:
  	#value:								#generateValue:on:indent:
  	#value:value:						#generateValue:on:indent:
  
  	#shouldNotImplement				#generateSmalltalkMetaError:on:indent:
  	#shouldBeImplemented			#generateSmalltalkMetaError:on:indent:
  	).
  
  	1 to: pairs size by: 2 do: [:i |
  		translationDict at: (pairs at: i) put: (pairs at: i + 1)].
  
  	pairs := #(
  	#ifTrue:					#generateIfTrueAsArgument:on:indent:	
  	#ifFalse:				#generateIfFalseAsArgument:on:indent:
  	#ifTrue:ifFalse:			#generateIfTrueIfFalseAsArgument:on:indent:
  	#ifFalse:ifTrue:			#generateIfFalseIfTrueAsArgument:on:indent:
  	#ifNotNil:				#generateIfNotNilAsArgument:on:indent:	
  	#ifNil:					#generateIfNilAsArgument:on:indent:
  	#ifNotNil:ifNil:			#generateIfNotNilIfNilAsArgument:on:indent:
  	#ifNil:ifNotNil:			#generateIfNilIfNotNilAsArgument:on:indent:
  	#cCode:				#generateInlineCCodeAsArgument:on:indent:
  	#cCode:inSmalltalk:		#generateInlineCCodeAsArgument:on:indent:
  	#cppIf:ifTrue:ifFalse:	#generateInlineCppIfElseAsArgument:on:indent:
  	#cppIf:ifTrue:			#generateInlineCppIfElseAsArgument:on:indent:
  	).
  
  	asArgumentTranslationDict := Dictionary new: 8.
  	1 to: pairs size by: 2 do: [:i |
  		asArgumentTranslationDict at: (pairs at: i) put: (pairs at: i + 1)].
  !

Item was changed:
+ ----- Method: InterpreterSimulatorLSB64>>long32At: (in category 'memory access') -----
- ----- Method: InterpreterSimulatorLSB64>>long32At: (in category 'as yet unclassified') -----
  long32At: byteAddress
  
  	"Return the 32-bit word at byteAddress which must be 0 mod 4."
  	| lowBits long |
  	lowBits := byteAddress bitAnd: 4.
  	long := self longAt: byteAddress - lowBits.
  	^ lowBits = 4
  		ifTrue: [ long bitShift: -32 ]
  		ifFalse: [ long bitAnd: 16rFFFFFFFF ].
  !

Item was changed:
+ ----- Method: InterpreterSimulatorLSB64>>long32At:put: (in category 'memory access') -----
- ----- Method: InterpreterSimulatorLSB64>>long32At:put: (in category 'as yet unclassified') -----
  long32At: byteAddress put: a32BitValue
  	"Store the 32-bit value at byteAddress which must be 0 mod 4."
  	| lowBits long64 longAddress |
  	lowBits := byteAddress bitAnd: 4.
  	lowBits = 0
  		ifTrue:
  		[ "storing into LS word"
  		long64 := self longAt: byteAddress.
  		self longAt: byteAddress
  				put: ((long64 bitAnd: 16rFFFFFFFF00000000) bitOr: a32BitValue)
  		]
  		ifFalse:
  		[longAddress := byteAddress - 4.
  		long64 := self longAt: longAddress.
  		self longAt: longAddress
  				put: ((long64 bitAnd: 16rFFFFFFFF) bitOr: (a32BitValue bitShift: 32))
  		]!

Item was changed:
+ ----- Method: InterpreterSimulatorMSB64>>byteSwapped: (in category 'memory access') -----
- ----- Method: InterpreterSimulatorMSB64>>byteSwapped: (in category 'as yet unclassified') -----
  byteSwapped: w
  	"Return the given integer with its bytes in the reverse order."
  
  	^ (super byteSwapped: ((w bitShift: -32) bitAnd: 16rFFFFFFFF)) +
  	  ((super byteSwapped: (w bitAnd: 16rFFFFFFFF)) bitShift: 32)!

Item was changed:
+ ----- Method: InterpreterSimulatorMSB64>>long32At: (in category 'memory access') -----
- ----- Method: InterpreterSimulatorMSB64>>long32At: (in category 'as yet unclassified') -----
  long32At: byteAddress
  	"Return the 32-bit word at byteAddress which must be 0 mod 4."
  
  	^ super longAt: byteAddress!

Item was changed:
+ ----- Method: InterpreterSimulatorMSB64>>long32At:put: (in category 'memory access') -----
- ----- Method: InterpreterSimulatorMSB64>>long32At:put: (in category 'as yet unclassified') -----
  long32At: byteAddress put: a32BitValue
  	"Store the 32-bit value at byteAddress which must be 0 mod 4."
  
  	super longAt: byteAddress put: a32BitValue!

Item was changed:
+ ----- Method: InterpreterSimulatorMSB64>>longAt: (in category 'memory access') -----
- ----- Method: InterpreterSimulatorMSB64>>longAt: (in category 'as yet unclassified') -----
  longAt: byteAddress
  	"Note: Adjusted for Smalltalk's 1-based array indexing."
  
  	^ ((super longAt: byteAddress) bitShift: 32) bitOr: (super longAt: byteAddress + 4)!

Item was changed:
+ ----- Method: InterpreterSimulatorMSB64>>longAt:put: (in category 'memory access') -----
- ----- Method: InterpreterSimulatorMSB64>>longAt:put: (in category 'as yet unclassified') -----
  longAt: byteAddress put: a64BitValue
  	"Note: Adjusted for Smalltalk's 1-based array indexing."
  
  	super longAt: byteAddress put: (a64BitValue bitShift: -32).
  	super longAt: byteAddress + 4 put: (a64BitValue bitAnd: 16rFFFFFFFF).
  	^ a64BitValue!

Item was changed:
  Object subclass: #TMethod
  	instanceVariableNames: 'selector returnType args locals declarations primitive parseTree labels writtenToGlobalVarsCache complete export static sharedLabel sharedCase comment definingClass globalStructureBuildMethodHasFoo canAsmLabel mustAsmLabel properties typedByPropagation cascadeVariableNumber'
  	classVariableNames: 'CaseStatements'
  	poolDictionaries: ''
  	category: 'VMMaker-Translation to C'!
+ 
+ !TMethod commentStamp: 'dtl 9/15/2008 09:06' prior: 0!
+ A TMethod is a translation method, representing a MethodNode that is to be translated to C source. It has a parseTree of translation nodes that mirrors the parse tree of the corresponding Smalltalk method.!

Item was changed:
  Object subclass: #TParseNode
  	instanceVariableNames: 'comment'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-Translation to C'!
+ 
+ !TParseNode commentStamp: 'dtl 9/15/2008 09:05' prior: 0!
+ A TParseNode is node in the parse tree of a TMethod. Subclasses correspond to different types of nodes in a method parse tree. The tree of translation parse nodes mirrors the parse tree of a Smalltalk method, and is used for translating a Smalltalk method to C source.!



More information about the Vm-dev mailing list