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

commits at source.squeak.org commits at source.squeak.org
Wed Nov 26 01:08:30 UTC 2014


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

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

Name: VMMaker-dtl.355
Author: dtl
Time: 25 November 2014, 7:59:15.571 pm
UUID: 9e6e08b4-e8f0-44b0-803c-de1559fbcb27
Ancestors: VMMaker-dtl.354

VMMaker 4.13.8

Complete the adoption of oscog improvements that eliminate use of #asSymbol hacks, and that produce correct code generation for #sizeOf: and #flag: methods. Also includes generation of constants in hex format, which improves readability of generated code.

Add SlangTest>>testLiteralName to verify translation of sizeOf: #Foo as sizeOf(Foo) rather than sizeOf("Foo").

=============== Diff against VMMaker-dtl.354 ===============

Item was changed:
  Object subclass: #CCodeGenerator
+ 	instanceVariableNames: 'translationDict inlineList constants variables variableDeclarations scopeStack methods macros preparedMethodList variablesSetCache headerFiles globalVariableUsage useSymbolicConstants generateDeadCode doNotRemoveMethodList asArgumentTranslationDict receiverDict vmClass currentMethod logger declareMethodsStatic permitMethodPruning pools abstractDeclarations uncheckedAbstractMethods selectorTranslations breakSrcInlineSelector breakDestInlineSelector'
- 	instanceVariableNames: 'translationDict inlineList constants variables variableDeclarations scopeStack methods macros preparedMethodList variablesSetCache headerFiles globalVariableUsage useSymbolicConstants generateDeadCode doNotRemoveMethodList asArgumentTranslationDict receiverDict vmClass currentMethod logger declareMethodsStatic permitMethodPruning pools abstractDeclarations uncheckedAbstractMethods breakSrcInlineSelector breakDestInlineSelector'
  	classVariableNames: 'UseRightShiftForDivide'
  	poolDictionaries: ''
  	category: 'VMMaker-Translation to C'!
  
  !CCodeGenerator commentStamp: 'tpr 5/2/2003 14:30' prior: 0!
  This class oversees the translation of a subset of Smalltalk to C, allowing the comforts of Smalltalk during development and the efficiency and portability of C for the resulting interpreter.  
  See VMMaker for more useful info!

Item was added:
+ ----- Method: CCodeGenerator>>addSelectorTranslation:to: (in category 'public') -----
+ addSelectorTranslation: aSelector to: aString
+ 	selectorTranslations at: aSelector asSymbol put: aString!

Item was changed:
  ----- Method: CCodeGenerator>>cFunctionNameFor: (in category 'C code generator') -----
  cFunctionNameFor: aSelector
+ 	"Create a C function name from the given selector by finding
+ 	 a specific translation, or if none, simply omitting colons."
+ 	^selectorTranslations at: aSelector ifAbsent: [aSelector copyWithout: $:]!
- 	"Create a C function name from the given selector by omitting colons
- 	and prefixing with the plugin name if the method is exported."
- 	^aSelector copyWithout: $:!

Item was changed:
  ----- Method: CCodeGenerator>>cLiteralFor: (in category 'C code generator') -----
  cLiteralFor: anObject
  	"Return a string representing the C literal value for the given object."
+ 	anObject isNumber
+ 		ifTrue:
+ 			[anObject isInteger ifTrue:
+ 				[| printString |
+ 				 printString := (anObject > 0
+ 								and: [(anObject >> anObject lowBit + 1) isPowerOfTwo
+ 								and: [(anObject highBit = anObject lowBit and: [anObject > 65536])
+ 									  or: [anObject highBit - anObject lowBit >= 4]]])
+ 									ifTrue: ['0x', (anObject printStringBase: 16)]
+ 									ifFalse: [anObject printString].
+ 				^anObject > 16rFFFFFFFF
+ 						ifTrue: [printString, ObjectMemory unsignedLongLongSuffix]
+ 						ifFalse: [anObject < 16r7FFFFFFF
+ 							ifTrue: [printString]
+ 							ifFalse: [printString, ObjectMemory unsignedIntegerSuffix]]].
+ 			anObject isFloat ifTrue:
+ 				[^anObject printString]]
+ 		ifFalse:
+ 			[anObject isSymbol ifTrue:
+ 				[^self cFunctionNameFor: anObject].
+ 			anObject isString ifTrue:
+ 				[^'"', (anObject copyReplaceAll: (String with: Character cr) with: '\n') , '"'].
+ 			anObject == nil ifTrue: [^ 'null' ].
+ 			anObject == true ifTrue: [^ '1' ].
+ 			anObject == false ifTrue: [^ '0' ].
+ 			anObject isCharacter ifTrue:
+ 				[^anObject == $'
+ 					ifTrue: ['''\'''''] "i.e. '\''"
+ 					ifFalse: [anObject asString printString]]].
+ 	self error: 'Warning: A Smalltalk literal could not be translated into a C constant: ', anObject printString.
- 	(anObject isKindOf: Integer) ifTrue: [
- 		(anObject < 16r7FFFFFFF)
- 			ifTrue: [^ anObject printString]
- 			ifFalse: [^ anObject printString , ObjectMemory unsignedIntegerSuffix "ikp"]].
- 	(anObject isKindOf: String) ifTrue: [^ '"', anObject, '"' ].
- 	(anObject isKindOf: Float) ifTrue: [^ anObject printString ].
- 	anObject == nil ifTrue: [^ 'null' ].
- 	anObject == true ifTrue: [^ '1' ].			"ikp"
- 	anObject == false ifTrue: [^ '0' ].			"ikp"
- 	(anObject isKindOf: Character) ifTrue:[^anObject asString printString]. "ar"
- 	self error:								"ikp"
- 		'Warning: A Smalltalk literal could not be translated into a C constant: ', anObject printString.
  	^'"XXX UNTRANSLATABLE CONSTANT XXX"'!

Item was added:
+ ----- Method: CCodeGenerator>>cLiteralFor:name: (in category 'C code generator') -----
+ cLiteralFor: anObject name: smalltalkName
+ 	"Return a string representing the C literal value for the given object.
+ 	 This version may use hex for integers that are bit masks."
+ 	anObject isInteger ifTrue:
+ 		[| hex dec rep |
+ 		hex := anObject printStringBase: 16.
+ 		dec := anObject printStringBase: 10.
+ 		rep := ((smalltalkName endsWith: 'Mask')
+ 				or: [anObject digitLength > 1
+ 					and: [(hex asSet size * 3) <= (dec asSet size * 2)
+ 					and: [(smalltalkName endsWith: 'Size') not]]])
+ 					ifTrue: [hex first = $- ifTrue: ['-0x', hex allButFirst] ifFalse: ['0x', hex]]
+ 					ifFalse: [dec].
+ 		^anObject > 16rFFFFFFFF
+ 			ifTrue: [rep, ObjectMemory unsignedLongLongSuffix]
+ 			ifFalse: [anObject < 16r7FFFFFFF
+ 				ifTrue: [rep]
+ 				ifFalse: [rep, ObjectMemory unsignedIntegerSuffix]]].
+ 	^self cLiteralFor: anObject!

Item was added:
+ ----- Method: CCodeGenerator>>generateFlag:on:indent: (in category 'C translation') -----
+ generateFlag: msgNode on: aStream indent: level
+ 	"Compoensate for the use of self flag: #aSymbol.  We used to translate  symbols
+ 	 as strings unless they were quoted via #aSymbol asSymbol. But this is too tedious,
+ 	 so we now translate symbols directly.  The only use that this affected was in
+ 		 self flag: #aSymbol,
+ 	 so hard-code it to produce a string value.  Note that this isn't strictly necessary
+ 	 because there's a
+ 		#define flag(foo) 0
+ 	 in C land, but it makes the generated C less dissonant."
+ 
+ 	aStream
+ 		nextPutAll: 'flag(';
+ 		nextPutAll: (self cLiteralFor: msgNode args last value asString);
+ 		nextPut: $)!

Item was changed:
  ----- Method: CCodeGenerator>>initialize (in category 'public') -----
  initialize
  	translationDict := Dictionary new.
  	inlineList := Array new.
  	constants := Dictionary new: 100.
  	variables := OrderedCollection new: 100.
  	variableDeclarations := Dictionary new: 100.
  	methods := Dictionary new: 500.
  	macros := Dictionary new.
  	self initializeCTranslationDictionary.
  	receiverDict := Dictionary new.
  	headerFiles := OrderedCollection new.
  	globalVariableUsage := Dictionary new.
  	useSymbolicConstants := true.
  	generateDeadCode := true.
  	scopeStack := OrderedCollection new.
  	logger := (ProvideAnswerNotification new tag: #logger; signal) ifNil: [Transcript].
  	pools := IdentitySet new.
  	abstractDeclarations := IdentitySet new.
  	uncheckedAbstractMethods := OrderedCollection new.
+ 	selectorTranslations := IdentityDictionary new.!
- !

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:
  
  	#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:
  	#preprocessorExpression:	#generateInlineCppDirective:on:indent:
  	#isDefined:inSmalltalk:comment:ifTrue:	#generateInlineCppIfDef:on:indent:
  	#isDefined:inSmalltalk:comment:ifTrue:ifFalse:	#generateInlineCppIfDefElse:on:indent:
  	#isDefinedTrueExpression:inSmalltalk:comment:ifTrue:ifFalse:	#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:
+ 	#flag:						#generateFlag: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:
  	#cCode:			#generateInlineCCodeAsArgument:on:indent:
  	#cCode:inSmalltalk:	#generateInlineCCodeAsArgument:on:indent:
  
  	#value					#generateValueAsArgument:on:indent:
  	#value:					#generateValueAsArgument:on:indent:
  	#value:value:			#generateValueAsArgument: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 added:
+ ----- Method: ObjectMemory class>>unsignedLongLongSuffix (in category 'translation') -----
+ unsignedLongLongSuffix
+ 	"Answer the suffix that should be appended to unsigned integer literals in generated code."
+ 
+ 	^'ULL'!

Item was added:
+ ----- Method: SlangTest>>testLiteralName (in category 'testing variable declaration') -----
+ testLiteralName
+ 	"sizeOf: #Foo should translated to C function call sizeof(Foo), where Foo is a literal, not a string"
+ 
+ 	| stssi s |
+ 	stssi := SlangTestSupportInterpreter inline: false.
+ 	s := stssi asCString: #sizeOfFoo .
+ 	self assert: (s includesSubString: 'sizeOf(Foo)').
+ 	self deny: (s includesSubString: 'sizeOf("Foo")').
+ 
+ !

Item was added:
+ ----- Method: SlangTestSupportInterpreter>>sizeOfFoo (in category 'local and instance vars') -----
+ sizeOfFoo
+ 	^ self sizeOf: #Foo!

Item was changed:
  ----- Method: TConstantNode>>printOn:level: (in category 'printing') -----
  printOn: aStream level: level
+ 	value isSymbol
+ 		ifTrue: [aStream nextPutAll: (value copyWithout: $:)]
+ 		ifFalse: [value storeOn: aStream]!
- 
- 	value storeOn: aStream.!

Item was changed:
+ ----- Method: TParseNode>>allCalls (in category 'utilities') -----
- ----- Method: TParseNode>>allCalls (in category 'as yet unclassified') -----
  allCalls
  	"Answer a collection of selectors for the messages sent in this parse tree."
  
  	| calls |
+ 	calls := Set new: 32.
+ 	self nodesDo:
+ 		[:node|
+ 		node isSend ifTrue:
+ 			[calls add: node selector].
+ 		(node isConstant and: [node value isSymbol]) ifTrue:
+ 			[calls add: node value]].
- 	calls := Set new: 100.
- 	self nodesDo: [ :node |
- 		node isSend ifTrue: [ calls add: node selector ].
- 	].
  	^calls!

Item was changed:
  ----- Method: VMMaker class>>versionString (in category 'version testing') -----
  versionString
  
  	"VMMaker versionString"
  
+ 	^'4.13.8'!
- 	^'4.13.7'!



More information about the Vm-dev mailing list