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

commits at source.squeak.org commits at source.squeak.org
Sat Jul 24 23:22:26 UTC 2021


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

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

Name: VMMaker-dtl.427
Author: dtl
Time: 24 July 2021, 7:22:16.962 pm
UUID: 70aadc77-7049-4b08-9128-b4b5f9f049fb
Ancestors: VMMaker-dtl.426

VMMaker 4.19.10
Unit tests and implemention for the _: argument passing convention when translating a method send to a C function in generated code. Plugins shared with oscog e.g. B3D use this convention in recent versions in order to avoid use of CCode: for calls to external C functions.

=============== Diff against VMMaker-dtl.426 ===============

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, and
+ 	 any trailing underscores (this supports a varargs convention)."
+ 	^selectorTranslations
+ 		at: aSelector
+ 		ifAbsent:
+ 			[| cSelector |
+ 			 cSelector := aSelector copyWithout: $:.
+ 			 aSelector last = $: ifTrue:
+ 				[[cSelector last = $_] whileTrue:
+ 					[cSelector := cSelector allButLast]].
+ 			 cSelector]!
- 	 a specific translation, or if none, simply omitting colons."
- 	^selectorTranslations at: aSelector ifAbsent: [aSelector copyWithout: $:]!

Item was added:
+ ----- Method: CCodeGenerator>>removeConstant: (in category 'utilities') -----
+ removeConstant: aName
+ 	"Remove the given (class) variable from the code base."
+ 
+ 	constants removeKey:  aName ifAbsent: []!

Item was changed:
  ----- Method: MessageNode>>asTranslatorNodeIn: (in category '*VMMaker-C translation') -----
  asTranslatorNodeIn: aTMethod
  	"make a CCodeGenerator equivalent of me"
  	"selector is sometimes a Symbol, sometimes a SelectorNode!!
  	On top of this, numArgs is needed due to the (truly grody) use of
  	arguments as a place to store the extra expressions needed to generate
  	code for in-line to:by:do:, etc.  see below, where it is used."
  	| rcvrOrNil sel args |
  	rcvrOrNil := receiver ifNotNil: [receiver asTranslatorNodeIn: aTMethod].
  	(rcvrOrNil notNil
  	and: [rcvrOrNil isVariable
  	and: [rcvrOrNil name = 'super']]) ifTrue:
  		[^aTMethod superExpansionNodeFor: selector key args: arguments].
  	sel := selector isSymbol ifTrue: [selector] ifFalse: [selector key].
  	((sel = #cCode:inSmalltalk: "extracting here rather than in translation allows inlining in the block."
  	  or: [sel = #cCode:])
  	 and: [arguments first isBlockNode]) ifTrue:
  		[| block |
  		 ^(block := arguments first asTranslatorNodeIn: aTMethod) statements size = 1
  			ifTrue: [block statements first]
  			ifFalse: [block]].
+ 	args := (1 to: sel numSelectorArgs) collect:
- 	args := (1 to: sel numArgs) collect:
  			[:i | (arguments at: i) asTranslatorNodeIn: aTMethod].
  	(sel = #to:by:do: and: [arguments size = 7 and: [(arguments at: 7) notNil]]) ifTrue:
  		["Restore limit expr that got moved by transformToDo:"
  		 args := {(arguments at: 7) value asTranslatorNodeIn: aTMethod. 
  				  args second.
  				  args third. "add the limit var as a hidden extra argument; we may need it later"
  				  TVariableNode new setName: arguments first key}].
  	((sel = #ifFalse: or: [sel = #or:])
  	 and: [arguments size = 2 and: [(arguments at: 2) notNil]]) ifTrue:
  		["Restore argument block that got moved by transformOr: or transformIfFalse:"
  		 args at: 1 put: ((arguments at: 2) asTranslatorNodeIn: aTMethod)].
  	^TSendNode new
  		setSelector: sel
  		receiver: rcvrOrNil
  		arguments: args!

Item was added:
+ ----- Method: SlangTest>>testArgumentListForCallingExternalCFunction (in category 'testing variable declaration') -----
+ testArgumentListForCallingExternalCFunction
+ 	"Verify the code generation convention of using _: in a message selector to
+ 	generate a C function without using CCode: "
+ 	"(self selector: #testArgumentListForCallingExternalCFunction) run"
+ 
+ 	| stssi s |
+ 	stssi := SlangTestSupportInterpreter inline: false.
+ 	s := stssi asCString: #callMethodWithSelectorAndArgList .
+ 	self assert: (self string: s includesSubstring: 'someCFunction(ARG1, ARG2, ARG3);').
+ 
+ 	stssi := SlangTestSupportPlugin inline: false.
+ 	s := stssi asCString: #callMethodWithSelectorAndArgList .
+ 	self assert: (self string: s includesSubstring: 'someCFunction(ARG1, ARG2, ARG3);')
+ !

Item was added:
+ ----- Method: SlangTestSupportInterpreter>>callMethodWithSelectorAndArgList (in category 'translation') -----
+ callMethodWithSelectorAndArgList
+ 
+ 	self someCFunction: #ARG1 _: #ARG2 _: #ARG3
+ !

Item was added:
+ ----- Method: SlangTestSupportPlugin>>callMethodWithSelectorAndArgList (in category 'translation') -----
+ callMethodWithSelectorAndArgList
+ 
+ 	self someCFunction: #ARG1 _: #ARG2 _: #ARG3
+ !

Item was added:
+ ----- Method: String>>numSelectorArgs (in category '*VMMaker-Translation to C') -----
+ numSelectorArgs
+ 	"Copied from recent Squeak String>>numArgs which has logic for
+ 	detecting the _: keyword convention, not present in older images."
+ 
+ 	| numColons index size c |
+ 	(size := self size) = 0 ifTrue: [ ^-1 ].
+ 	index := 1.
+ 	(self at: index) isSpecial ifTrue: [
+ 		2 to: size do: [ :i | (self at: i) isSpecial ifFalse: [ ^-1 ] ].
+ 		^1 ].
+ 	self canBeToken ifFalse: [ ^-1 ].
+ 	"Fast colon count"
+ 	numColons := 0.
+ 	[ 
+ 		((c := self at: index) isLetter
+ 		 or: [ c = $_ and: [ Scanner prefAllowUnderscoreSelectors ] ]) ifFalse:
+ 			[ ^-1 ].
+ 		(index := (self indexOf: $: startingAt: index) + 1) > 1 ifFalse:
+ 			[ numColons = 0 ifTrue: [ ^0 ].
+ 			 ^-1 ].
+ 		numColons := numColons + 1.
+ 		index <= size ] whileTrue.
+ 	^numColons!

Item was changed:
  ----- Method: TSendNode>>printOn:level: (in category 'printing') -----
  printOn: aStream level: level
  	| possiblyParenthesize |
  	possiblyParenthesize :=
  		[:node :newLevel|
  		(node isSend
  		 and: [node selector precedence >= 3]) ifTrue:
  			[aStream nextPut: $(].
  		node printOn: aStream level: newLevel.
  		(node isSend
  		 and: [node selector precedence >= 3]) ifTrue:
  			[aStream nextPut: $)]].
  
  	possiblyParenthesize value: receiver value: level.
  	arguments size = 0 ifTrue:
  		[aStream space; nextPutAll: selector.
  		^self].
+ 	selector keywords with: (arguments first: selector numSelectorArgs) do:
- 	selector keywords with: (arguments first: selector numArgs) do:
  		[:keyword :arg |
  		arg ifNotNil: [
  			aStream space; nextPutAll: keyword; space.
  			possiblyParenthesize value: arg value: level + 1]]!

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



More information about the Vm-dev mailing list