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

commits at source.squeak.org commits at source.squeak.org
Wed Jan 20 04:45:16 UTC 2021


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

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

Name: VMMaker.oscog-eem.2937
Author: eem
Time: 19 January 2021, 8:45:06.642772 pm
UUID: 9f7b8c1a-4f51-4b69-92f4-37bbdc45b73a
Ancestors: VMMaker.oscog-eem.2936

doWithIndex: => withIndexDo:

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

Item was changed:
  ----- Method: CCodeGenerator>>addClass: (in category 'public') -----
  addClass: aClass
  	"Add the variables and methods of the given class to the code base."
  
  	aClass prepareToBeAddedToCodeGenerator: self.
  	self checkClassForNameConflicts: aClass.
  	self addClassVarsFor: aClass.
  	"ikp..."
  	self addPoolVarsFor: aClass.
  	(aClass inheritsFrom: VMStructType) ifFalse:
  		[variables addAll: (self instVarNamesForClass: aClass)].
  	self retainMethods: (aClass requiredMethodNames: self options).
  	
  	'Adding Class ' , aClass name , '...'
  		displayProgressAt: Sensor cursorPoint
  		from: 0
  		to: aClass selectors size
  		during:
  			[:bar |
+ 			 aClass selectors withIndexDo:
- 			 aClass selectors doWithIndex:
  				[:sel :i | | source |
  				bar value: i.
  				self addMethodFor: aClass selector: sel]].
  	aClass declareCVarsIn: self!

Item was changed:
  ----- Method: CCodeGenerator>>addStructClass: (in category 'public') -----
  addStructClass: aClass
  	"Add the non-accessor methods of the given struct class to the code base."
  
  	aClass prepareToBeAddedToCodeGenerator: self.
  	self addClassVarsFor: aClass.
  	self addPoolVarsFor: aClass.
  	self retainMethods: (aClass requiredMethodNames: self options).
  	
  	'Adding Class ' , aClass name , '...'
  		displayProgressAt: Sensor cursorPoint
  		from: 0
  		to: aClass selectors size
  		during:
  			[:bar |
+ 			 aClass selectors withIndexDo:
- 			 aClass selectors doWithIndex:
  				[:sel :i | | source |
  				bar value: i.
  				self addStructMethodFor: aClass selector: sel]].
  	aClass declareCVarsIn: self!

Item was changed:
  ----- Method: CCodeGenerator>>doBasicInlining: (in category 'inlining') -----
  doBasicInlining: inlineFlagOrSymbol
  	"Inline the bodies of all methods that are suitable for inlining.
  	This method does only the basic inlining suitable for both the core VM and plugins - no bytecode inlining etc"
  
  	| pass progress |
  	self collectInlineList: inlineFlagOrSymbol.
  	pass := 0.
  	progress := true.
  	[progress] whileTrue: [
  		"repeatedly attempt to inline methods until no further progress is made"
  		progress := false.
  		('Inlining pass ', (pass := pass + 1) printString, '...')
  			displayProgressAt: Sensor cursorPoint
  			from: 0 to: methods size
  			during: [:bar |
+ 				(self sortMethods: methods) withIndexDo: [:m :i |
- 				(self sortMethods: methods) doWithIndex: [:m :i |
  					bar value: i.
  					currentMethod := m.
  					(m tryToInlineMethodsIn: self)
  						ifTrue: [progress := true]]]].
  
  !

Item was changed:
  ----- Method: CCodeGenerator>>emitCMethods:on: (in category 'C code generator') -----
  emitCMethods: methodList on: aStream
  	'Writing Translated Code...'
  		displayProgressAt: Sensor cursorPoint
  		from: 0 to: methods size
  		during:
  			[:bar |
+ 			methodList withIndexDo:
- 			methodList doWithIndex:
  				[ :m :i |
  				bar value: i.
  				(m isRealMethod
  				 and: [self shouldGenerateMethod: m]) ifTrue:
  					[m emitCCodeOn: aStream generator: self]]]!

Item was changed:
  ----- Method: CCodeGenerator>>removeAssertions (in category 'inlining') -----
  removeAssertions
  	"Remove all assertions in method bodies.  This is for the benefit of inlining, which
  	fails to recognise and disregard empty method bodies when checking the inlinability
  	of sends."
  
  	| newMethods |
  	newMethods := Dictionary new.
  	'Removing assertions...'
  		displayProgressAt: Sensor cursorPoint
  		from: 0 to: methods size
  		during: [ :bar |
+ 			methods withIndexDo: [ :m :i |
- 			methods doWithIndex: [ :m :i |
  				bar value: i.
  				m isAssertion ifFalse: [
  					newMethods at: m selector put: m.
  					m removeAssertions]]].
  	methods := newMethods.!

Item was changed:
  ----- Method: CogARMv8Compiler class>>initialize (in category 'class initialization') -----
  initialize
  	"Initialize various ARM64 instruction-related constants."
  	"self initialize"
  
  	"main registers; a minor complication in reading the doc.
  	ARM refer to the 64bit registers as X0...30 and use R0...30 to refer to the 32bit lower halves.
  	They also use a whole suite of names for the floating point/SIMD registers. See ARMARM DDI0487 B1.2.1 etc for the gory details.
  	Note that R30 (yes, yes, X30) is used as the link register and as such is not really a general purpose register. 
  	Also note that 31 in a general register field means R31, and that in most of these instructions R31 is the zero
  	register named XZR in ARM doc.  but in the rest of these instructions R31 the effective SP register.
  	XZR is a pseudo-register that always reads as 0 and writes to /dev/null.
  	And note that unlike the ARM32, there is no general purpose register for the PC; a big difference.
  	See ARMARM DDI0487 C1.2.5. wrt to both the lack of a PC register and the XZR/SP distinction."
  	
  	"and initialize most sets of variables that run from 0 to N - 1..."
  	#(	"General registers, 0 to 31. We stick with R0...30 to refer to the 64 bit general regs and D0...31 (note the extra reg here!!) for the FP/SIMD regs"
  		(R0 R1 R2 R3 R4 R5 R6 R7 R8 R9 R10 R11 R12 R13 R14 R15 R16 R17 R18 R19 R20 R21 R22 R23 R24 R25 R26 R27 R28 R29 R30 R31)
  		"Floating-point registers, 0 to 31"
  		(D0 D1 D2 D3 D4 D5 D6 D7 D8 D9 D10 D11 D12 D13 D14 D15 D16 D17 D18 D19 D20 D21 D22 D23 D24 D25 D26 D27 D28 D29 D30 D31)
  		"C argument registers, 0 to 6"
  		(CArg0Reg CArg1Reg CArg2Reg CArg3Reg CArg4Reg CArg5Reg CArg6Reg)
  		"Condition Codes 0 to 16. Note that cc=16rF is mapped back to AL in AARCH64. Generally it shouldn't be used."
  		(EQ NE CS CC MI PL VS VC HI LS GE LT GT LE AL)
  		"Logical Op Codes"
  		(LogicalAnd LogicalOr LogicalXor LogicalAndS)
  		"Arithmetic Opcodes"
  		"ADD (shifted register) on page C6-763			10001011
  		 ADDS (shifted register) on page C6-771		10101011
  		 CMN (shifted register) on page C6-854			10101011	Rd=XZR
  		 SUB (shifted register) on page C6-1313		11001011
  		 SUBS (shifted register) on page C6-1323		11101011
  		 CMP (shifted register) on page C6-860			11101011	Rd=XZR
  		 NEG (shifted register) on page C6-1114		11001011	Rn=XZR
  		 NEGS					on page C6-1116		11101011	Rn=XZR"
  		(ArithmeticAdd ArithmeticAddS ArithmeticSub ArithmeticSubS)
  		"Extension Methods "
  		(UXTB UXTH UXTW UXTX "a.k.a. LSL" SXTB SXTH SXTW SXTX)) do:
  		[:classVarNames|
+ 		 classVarNames withIndexDo:
- 		 classVarNames doWithIndex:
  			[:k :v|
  			CogARMv8Compiler classPool at: k put: v - 1]].
  
  	SP := XZR := R31.
  	LR := R30.
  	FP := R29.
  
  	"DC variant selectors; see concretizeDataCacheControl"
  	DC_CISW := 13.
  	DC_CIVAC := 14.
  	DC_CSW := 15.
  	DC_CVAC := 16.
  	DC_CVAU := 19.
  	DC_ISW := 26.
  	DC_IVAC := 27.
  	DC_ZVA := 28.
  
  	"IC variant selectors; see concretizeInstructionCacheControl"
  	IC_IALLU := 0.
  	IC_IALLUIS := 1.
  	IC_IVAU := 2.
  
  	"DSB domains and types	C6.2.81 DSB	C6-891"
  	DSB_OSH := 0.		"Domain_OuterSharable"
  	DSB_NSH := 1.		"Domain_NonSharable"
  	DSB_ISH := 2.		"Domain_InnerSharable"
  	DSB_SY := 3.		"Domain_FullSystem"
  
  	DSB_ALLSY := 0.	"Types_All; domain = Domain_FullSystem"
  	DSB_READS := 1.	"Types_Reads"
  	DSB_WRITES := 2.	"Types_Writes"
  	DSB_ALL := 3.		"Types_All; domain ~= Domain_FullSystem"
  
  	"Specific instructions"
  	self
  		initializeSpecificOpcodes: #(MulRRR MulOverflowRRR SMULHRRR DivRRR MSubRRR "N.B. ARMv8 has MSUBRRRR but we only support three operands"
  									MoveAwRR MoveRRAw NativePushRR NativePopRR "these map to ldp/stp"
  									"Cache control and memory barrier"
  									"B2.3.7		Memory barriers	B2-124"
  									DC IC DMB DSB ISB MRS_CTR_EL0 MRS_ID_AA64ISAR0_EL1
  									CASAL CBNZ CBZ CCMPNE CSET CLREX LDAXR STLXR STLR)
  		in: thisContext method!

Item was changed:
  ----- Method: CogX64Compiler class>>initialize (in category 'class initialization') -----
  initialize
  	"Initialize various x64 instruction-related constants.
  	 [1] IA-32 Intel® Architecture Software Developer's Manual Volume 2A: Instruction Set Reference, A-M"
  
  	"CogX64Compiler initialize"
  
  	self ~~ CogX64Compiler ifTrue: [^self].
  
  	(InitializationOptions ifNil: [Dictionary new])
  		at: #ABI
  		ifPresent: [:abi| SysV := abi asUppercase ~= #WIN64 and: [abi asUppercase ~= #'_WIN64']]
  		ifAbsent: [SysV := true]. "Default ABI; set to true for SysV, false for WIN64/_WIN64"
  
  	"Initialize most sets of variables that run from 0 to N - 1..."
  	#(	"16 integer registers, rcx, rdx, rbx bizarrely inconsistent"
  		(RAX RCX RDX RBX RSP RBP RSI RDI R8 R9 R10 R11 R12 R13 R14 R15)
  		"16 lower half floating point registers"
  		(XMM0L XMM1L XMM2L XMM3L XMM4L XMM5L XMM6L XMM7L XMM8L XMM9L XMM10L XMM11L XMM12L XMM13L XMM14L XMM15L)
  		"Mod R/M Mod fields.  See [1] Sec 2.4, 2.5 & 2.6 & Table 2-2"
  		(ModRegInd ModRegRegDisp8 ModRegRegDisp32 ModReg ModRegIndSIB ModRegIndDisp32)
  		"SIB Scaled Index modes.  See [1] Sec 2.4, 2.5 & 2.6 & Table 2-3"
  		(SIB1 SIB2 SIB4 SIB8)) do:
  		[:classVarNames|
+ 		 classVarNames withIndexDo:
- 		 classVarNames doWithIndex:
  			[:k :v|
  			self classPool at: k put: v - 1]].
  
  	"Specific instructions"
  	self initializeSpecificOpcodes: #(CPUID
  	"Arithmetic:"					CDQ IDIVR IMULRR XCHGRR
  	"Bit count/data movement:"	CLD REP MOVSB MOVSQ BSR 	
  	"Multi-processing:"				LFENCE MFENCE SFENCE LOCK CMPXCHGRMr SETE MoveRAwNoVBR)
  		in: thisContext method
  		extraClassVarNames: #(CArg0Reg CArg1Reg CArg2Reg CArg3Reg)!

Item was changed:
  ----- Method: InterpreterSimulator>>ioLoadFunction:From: (in category 'plugin support') -----
  ioLoadFunction: functionString From: pluginString
  	"Load and return the requested function from a module"
  	| plugin fnSymbol |
  	fnSymbol := functionString asSymbol.
  	transcript cr; show:'Looking for ', functionString, ' in '.
  	pluginString isEmpty
  		ifTrue:[transcript show: 'vm']
  		ifFalse:[transcript show: pluginString].
  	plugin := pluginList 
  				detect:[:any| any key = pluginString asString]
  				ifNone:[self loadNewPlugin: pluginString].
  	plugin ifNil:[
  		"Transcript cr; show:'Failed ... no plugin found'." ^ 0].
  	plugin := plugin value.
+ 	mappedPluginEntries withIndexDo:[:pluginAndName :index|
- 	mappedPluginEntries doWithIndex:[:pluginAndName :index|
  		((pluginAndName at: 1) == plugin 
  			and:[(pluginAndName at: 2) == fnSymbol]) ifTrue:[
  				"Transcript show:' ... okay'." ^ index]].
  	(plugin respondsTo: fnSymbol) ifFalse:[
  		"Transcript cr; show:'Failed ... primitive not in plugin'." ^ 0].
  	mappedPluginEntries := mappedPluginEntries copyWith: (Array with: plugin with: fnSymbol).
  	"Transcript show:' ... okay'."
  	^ mappedPluginEntries size!

Item was changed:
  ----- Method: KlattSynthesizerPlugin class>>initialize (in category 'class initialization') -----
  initialize
  	"
  	KlattSynthesizerPlugin initialize
  	"
  	| parameterClass |
  	parameterClass := (Smalltalk hasClassNamed: #KlattFrame)
  		ifTrue: [Smalltalk at: #KlattFrame "original package structure"]
  		ifFalse: [Smalltalk at: #KlattResonatorIndices "repackaged to separate plugin from Speech dependency"].
  	
+ 	parameterClass parameterNames withIndexDo:
+ 		[ :each :i | self classPool at: each capitalized asSymbol put: i - 1].
+ 	PI := Float pi.
- 	parameterClass parameterNames
- 		doWithIndex: [ :each :i | self classPool at: each capitalized asSymbol put: i-1].
- 	PI := Float pi	.
  	Epsilon := 1.0e-04!

Item was changed:
  ----- Method: StackInterpreter class>>table:from: (in category 'initialization') -----
  table: anArray from: specArray 
  	"SpecArray is an array of one of (index selector) or (index1 
  	 index2 selector) or (index nil) or (index1 index2 nil).  If selector
  	 then the entry is the selector, but if nil the entry is the index."
  	| contiguous |
  	contiguous := 0.
  	specArray do:
  		[:spec | 
  		(spec at: 1) = contiguous ifFalse:
  			[self error: 'Non-contiguous table entry'].
  		spec size = 2
  			ifTrue:
  				[anArray
  					at: (spec at: 1) + 1
  					put: ((spec at: 2) ifNil: [spec at: 1] ifNotNil: [:sym| sym]).
  				 contiguous := contiguous + 1]
  			ifFalse:
  				[(spec at: 1) to: (spec at: 2) do:
  					[:i | anArray at: i + 1 put: ((spec at: 3) ifNil: [i] ifNotNil: [:sym| sym])].
  				 contiguous := contiguous + ((spec at: 2) - (spec at: 1)) + 1]].
+ 	anArray withIndexDo:
- 	anArray doWithIndex:
  		[:entry :index|
  		entry isSymbol ifTrue:
  			[(self shouldIncludeMethodForSelector: entry) ifFalse:
  				[anArray at: index put: 0]]]!

Item was changed:
  ----- Method: VMInterfaceConsistencyTests>>testInterpreterProxyInterfaceIsConsistentFor: (in category 'private-support') -----
  testInterpreterProxyInterfaceIsConsistentFor: aClass
  	| ccg |
  	ccg := VMPluginCodeGenerator new.
  	InterpreterProxy selectors asArray sort do:
  		[:sel| | pm |
  		((#(initialize #'initialize-release' private) includes: (InterpreterProxy whichCategoryIncludesSelector: sel))
  		  or: [ccg noteUsedPluginFunction: sel]) ifFalse:
  			[pm := ccg compileToTMethodSelector: sel in: InterpreterProxy.
  			(aClass whichClassIncludesSelector: sel) ifNotNil:
  				[:impClass| | im pt it |
  				im := ccg compileToTMethodSelector: sel in: impClass.
  				"A number of functions are actually void in the interpreter but declared as sqInt in sqVirtualMachine.c, e.g. push"
  				self assert: ((pt := pm returnType) = (it := im returnType)
  							 or: [pt = #sqInt and: [it = #void]])
  					description: 'inconsistent returnType for ', sel, ' in InterpreterProxy vs ', impClass, ' ', pt, ' vs ', it.
+ 				pm args withIndexDo:
- 				pm args doWithIndex:
  					[:pma :i| | ima |
  					ima := im args at: i.
  					self assert: (pt := pm typeFor: pma in: ccg) = (it := im typeFor: ima in: ccg)
  						description: 'inconsistent ', i printString, (#('st' 'nd') at: i ifAbsent: 'th'), ' arg type for ', sel, ' in InterpreterProxy vs ', impClass, ' ', pt, ' vs ', it]]]]!



More information about the Vm-dev mailing list