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

commits at source.squeak.org commits at source.squeak.org
Sat Jul 10 04:30:19 UTC 2021


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

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

Name: VMMaker.oscog-eem.2985
Author: eem
Time: 9 July 2021, 9:30:10.933174 pm
UUID: f1d118fb-fac8-4f42-82d9-68635c83d686
Ancestors: VMMaker.oscog-eem.2984

CogARMv8Compiler: give up on generating a JIT cache flush on Apple. Their code is clean and simple and very hard to beat.

Do a better job eliding the implicit ^self at the end of a method when collecting TMethods.  This allows numICacheFlushOpcodes to translate nicely.  Results in several CogAbstractInstruction methods having a return type of void.  Nice.

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

Item was added:
+ ----- Method: Class>>isVMClass (in category '*VMMaker-testing') -----
+ isVMClass
+ 	^false!

Item was changed:
  ----- Method: CogARMv8Compiler class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
  		
  	#('hasAtomicInstructions' 'instructionCacheLineLength' 'instructionCacheFlushRequired' 'dataCacheLineLength' 'dataCacheFlushRequired') do:
  		[:varName|
  		aCCodeGenerator
  			declareVar: varName type: #'unsigned char';
  			removeConstant: varName capitalized].
  	aCCodeGenerator
+ 		var: #ceFlushDCache "sigh; this is here to placate Slang; we don't use this, but Slang doesn't elide the assignment..."
+ 			declareC: 'static void (*ceFlushDCache)(usqIntptr_t from, usqIntptr_t to)'!
- 		var: #ceFlushDCache
- 			declareC: '#if __APPLE__\static void (*ceFlushDCache)(usqIntptr_t from, usqIntptr_t to)\#endif'!

Item was changed:
  ----- Method: CogARMv8Compiler>>detectFeaturesOnMacOS (in category 'memory access') -----
  detectFeaturesOnMacOS
  	<option: #__APPLE__>
  	"MacOS does not allow access to ctl_el0, so derive cache information etc from sysctl"
  	"Here are values from sysctl(8), hardwired for now rather than derived through sysctl(3)
  		hw.cacheconfig: 8 1 1 0 0 0 0 0 0 0 (we speculate that the 1's indicate cache flush required)
  		hw.cachelinesize: 128
  		hw.l1icachesize: 131072
  		hw.l1dcachesize: 131072
  		hw.optional.neon: 1
  		hw.optional.neon_hpfp: 1
  		hw.optional.neon_fp16: 1
  		hw.optional.armv8_1_atomics: 1"
  
+ 	false ifTrue: "Apple's cache flush code on M1 is simple and effective; we can't easily better it..."
+ 		[self setDataCacheLineLength: 128.
+ 		self setDataCacheFlushRequired: true.
+ 		self setInstructionCacheLineLength: 128.
+ 		self setInstructionCacheFlushRequired: true].
- 	self setDataCacheLineLength: 128.
- 	self setDataCacheFlushRequired: true.
- 	self setInstructionCacheLineLength: 128.
- 	self setInstructionCacheFlushRequired: true.
  	self setHasAtomicInstructions: true!

Item was changed:
  ----- Method: CogARMv8Compiler>>flushICacheFrom:to: (in category 'inline cacheing') -----
  flushICacheFrom: startAddress "<Integer>" to: endAddress "<Integer>"
  	"Flush the instruction cache from (startAddress to endAddress].
+ 
  	 If there is a dual mapped code zone (the normal zone but marked with read/execute, and a
  	 read/write zone codeToDataDelta bytes away) then also flush the data cache for the corresp-
+ 	 onding range in the read/write zone and invalidate the data cache for the read/execute zone.
+ 
+ 	 If using the Apple MAP_JIT/pthread_jit_write_protect_np: also flush the data cache.  Use Apple's
+ 	 implementations for both; they are simple and effective."
+ 	
- 	 onding range in the read/write zone and invalidate the data cache for the read/execute zone."
  	<inline: #always>
  	cogit ensureExecutableCodeZone.
  	self cCode:
+ 			[self cppIf: #__APPLE__ & #__MACH__
+ 				ifTrue: [cogit sys_dcache_flush: (self cCoerce: startAddress to: #'void *') _: endAddress - startAddress + 1;
+ 						sys_icache_invalidate: (self cCoerce: startAddress to: #'void *') _: endAddress - startAddress + 1]
+ 				ifFalse: [cogit ceFlushICache: startAddress _: endAddress]]
- 			[self cppIf: #__APPLE__
- 				ifTrue: [self initialFlushICacheFrom: startAddress to: endAddress]
- 				ifFalse:
- 					[self cppIf: #__APPLE__
- 						ifTrue: [cogit ceFlushDCache: startAddress _: endAddress].
- 					 cogit ceFlushICache: startAddress _: endAddress]]
  		inSmalltalk:  [cogit simulateCeFlushICacheFrom: startAddress to: endAddress]!

Item was changed:
  ----- Method: CogARMv8Compiler>>generateDCacheFlush (in category 'inline cacheing') -----
  generateDCacheFlush
  	"Use the DC instruction to implement ceFlushDCache(void *start, void *end); see flushDCacheFrom:to:.
  	 If there is a dual mapped zone then clean data via DC_CVAU as address + codeToDataDelta,
  	 then invalidate data at address via CIVAC."
  
  	"D4.4.7		About cache maintenance in AArch64 state													D4-2478
  
  		Terminology for Clean, Invalidate, and Clean and Invalidate instructions									D4-2479
  		...
  		-	For instructions operating by VA, the following conceptual points are defined:						D4-2480
  		Point of Unification (PoU)							
  			The PoU for a PE is the point by which the instruction and data caches and the translation table walks of that
  			PE are guaranteed to see the same copy of a memory location. In many cases, the Point of Unification is the
  			point in a uniprocessor memory system by which the instruction and data caches and the translation table
  			walks have merged.
  
  			The PoU for an Inner Shareable shareability domain is the point by which the instruction and data caches
  			and the translation table walks of all the PEs in that Inner Shareable shareability domain are guaranteed to
  			see the same copy of a memory location. Defining this point permits self-modifying software to ensure future
  			instruction fetches are associated with the modified version of the software by using the standard correctness
  			policy of:
  				1. Clean data cache entry by address.
  				2. Invalidate instruction cache entry by address.
  
  		Example code for cache maintenance instructions D4-2490 - D4-2491"
+ 	self cppIf: #__APPLE__ & #__MACH__
+ 		ifFalse:
+ 			[| mask loop |
+ 			self assert: cogit getCodeToDataDelta ~= 0.
+ 			"Mask is large enough to encompass the method zone and has the correct minimum alignment."
+ 			mask := 1 << (cogit coInterpreter highBit: cogit methodZone zoneEnd) - self dataCacheLineLength.
- 	| mask loop |
- 	self assert: cogit getCodeToDataDelta ~= 0.
- 	"Mask is large enough to encompass the method zone and has the correct minimum alignment."
- 	mask := 1 << (cogit coInterpreter highBit: cogit methodZone zoneEnd) - self dataCacheLineLength.
  
+ 			"Since this is used from C code we must use only caller-saved registers.
+ 			 C arg registers 2 & 3 are such a convenient pair of caller-saved registers."
+ 			cogit AndCq: mask R: CArg0Reg R: CArg2Reg. "CArg2Reg = aligned pointer to start of each data cache line"
+ 			cogit AddCq: cogit getCodeToDataDelta R: CArg2Reg R: CArg3Reg.
+ 			loop := cogit Label.
+ 			"see concretizeDataCacheControl"
+ 			cogit gen: DC operand: CArg3Reg operand: DC_CVAU.	"clean (flush) address + codeToDataDelta"
+ 			cogit gen: DC operand: CArg2Reg operand: DC_CIVAC.	"invalidate address"
+ 			cogit
+ 				AddCq: self dataCacheLineLength R: CArg2Reg;
+ 				AddCq: self dataCacheLineLength R: CArg3Reg;
+ 				CmpR: CArg1Reg R: CArg2Reg;
+ 				JumpBelowOrEqual: loop.
+ 			cogit RetN: 0]!
- 	"Since this is used from C code we must use only caller-saved registers.
- 	 C arg registers 2 & 3 are such a convenient pair of caller-saved registers."
- 	cogit AndCq: mask R: CArg0Reg R: CArg2Reg. "CArg2Reg = aligned pointer to start of each data cache line"
- 	cogit AddCq: cogit getCodeToDataDelta R: CArg2Reg R: CArg3Reg.
- 	loop := cogit Label.
- 	"see concretizeDataCacheControl"
- 	cogit gen: DC operand: CArg3Reg operand: DC_CVAU.	"clean (flush) address + codeToDataDelta"
- 	cogit gen: DC operand: CArg2Reg operand: DC_CIVAC.	"invalidate address"
- 	cogit
- 		AddCq: self dataCacheLineLength R: CArg2Reg;
- 		AddCq: self dataCacheLineLength R: CArg3Reg;
- 		CmpR: CArg1Reg R: CArg2Reg;
- 		JumpBelowOrEqual: loop.
- 	cogit RetN: 0!

Item was changed:
  ----- Method: CogARMv8Compiler>>generateICacheFlush (in category 'inline cacheing') -----
  generateICacheFlush
  	"Use DC VAUC, DSB, IC IVAU, and ISB instructions to implement ceFlushICache(void *start, void *end); see flushICacheFrom:to:.
  	 One might think that if there is a dual zone then data at address + codeToDataDelta must be cleaned,
  	 but this isn't the case.  All we need to do is clean data at address via DC VAUC and instructions via IC IVAU."
  
  	"B2.2.5		Concurrent modification and execution of instructions											B2-112
  
  		...to avoid UNPREDICTABLE or CONSTRAINED UNPREDICTABLE behavior, instruction modifications must be explicitly synchronized before they are executed. The required synchronization is as follows:
  
  		1.	No PE must be executing an instruction when another PE is modifying that instruction.
  
  		2.	To ensure that the modified instructions are observable, a PE that is writing the instructions must issue the following sequence of instructions and operations:
  
  			; Coherency example for data and instruction accesses within the same Inner Shareable domain.
  			; enter this code with <Wt> containing a new 32-bit instruction, to be held in Cacheable space at a location pointed to by Xn.
  
  			STR Wt, [Xn]
  			DC CVAU, Xn		; Clean data cache by VA to point of unification (PoU)
  			DSB ISH			; Ensure visibility of the data cleaned from cache
  			IC IVAU, Xn			; Invalidate instruction cache by VA to PoU
  			DSB ISH
  
  			Note
  			 -	The DC CVAU operation is not required if the area of memory is either Non-cacheable or Write-Through Cacheable.
  			 -	If the contents of physical memory differ between the mappings, changing the mapping of VAs to PAs can cause
  				the instructions to be concurrently modified by one PE and executed by another PE. If the modifications affect
  				instructions other than those listed as being acceptable for modification, synchronization must be used to avoid
  				UNPREDICTABLE or CONSTRAINED UNPREDICTABLE behavior.
  
  		3.	In a multiprocessor system, the IC IVAU is broadcast to all PEs within the Inner Shareable domain of the PE running this sequence.
  			However, when the modified instructions are observable, each PE that is executing the modified instructions must issue the following
  			instruction to ensure execution of the modified instructions:
  
  			ISB					; Synchronize fetched instruction stream"
  
  	"D4.4.7		About cache maintenance in AArch64 state													D4-2478
  
  		Terminology for Clean, Invalidate, and Clean and Invalidate instructions									D4-2479
  		...
  		-	For instructions operating by VA, the following conceptual points are defined:						D4-2480
  		Point of Unification (PoU)							
  			The PoU for a PE is the point by which the instruction and data caches and the translation table walks of that
  			PE are guaranteed to see the same copy of a memory location. In many cases, the Point of Unification is the
  			point in a uniprocessor memory system by which the instruction and data caches and the translation table
  			walks have merged.
  
  			The PoU for an Inner Shareable shareability domain is the point by which the instruction and data caches
  			and the translation table walks of all the PEs in that Inner Shareable shareability domain are guaranteed to
  			see the same copy of a memory location. Defining this point permits self-modifying software to ensure future
  			instruction fetches are associated with the modified version of the software by using the standard correctness
  			policy of:
  				1. Clean data cache entry by address.
  				2. Invalidate instruction cache entry by address.
  
  		Example code for cache maintenance instructions D4-2490 - D4-2491"
+ 	self cppIf: #__APPLE__ & #__MACH__
+ 		ifFalse:
+ 			[| mask loop |
+ 			"See concretizeCacheControlOp1:CRm:Op2: & 
+ 			 http://infocenter.arm.com/help/index.jsp?topic=/com.arm.doc.100403_0200_00_en/lau1443435580346.html"
+ 			self dataCacheFlushRequired ifTrue: "CTR_EL0.IDC is zero; must clean data cache to point of unification."
+ 				["Since this is used from C code we must use only caller-saved registers.
+ 				  C arg registers 2 & 3 are as such a convenient pair of caller-saved registers."
+ 				 "Mask is large enough to encompass the method zone and has the correct minimum alignment."
+ 				 mask := 1 << (cogit coInterpreter highBit: cogit methodZone zoneEnd) - self dataCacheLineLength.
+ 				 cogit AndCq: mask R: CArg0Reg R: CArg2Reg. "CArg2Reg = aligned pointer to start of each data cache line"
- 	| mask loop |
- 	"See concretizeCacheControlOp1:CRm:Op2: & 
- 	 http://infocenter.arm.com/help/index.jsp?topic=/com.arm.doc.100403_0200_00_en/lau1443435580346.html"
- 	self dataCacheFlushRequired ifTrue: "CTR_EL0.IDC is zero; must clean data cache to point of unification."
- 		["Since this is used from C code we must use only caller-saved registers.
- 		  C arg registers 2 & 3 are as such a convenient pair of caller-saved registers."
- 		 "Mask is large enough to encompass the method zone and has the correct minimum alignment."
- 		 mask := 1 << (cogit coInterpreter highBit: cogit methodZone zoneEnd) - self dataCacheLineLength.
- 		 cogit AndCq: mask R: CArg0Reg R: CArg2Reg. "CArg2Reg = aligned pointer to start of each data cache line"
  	
+ 				 loop := cogit Label.
+ 				 "see concretizeDataCacheControl"
+ 				 cogit
+ 					gen: DC operand: CArg2Reg operand: DC_CVAU;		"clean (flush) address"
+ 					AddCq: self dataCacheLineLength R: CArg2Reg;
+ 					CmpR: CArg1Reg R: CArg2Reg;
+ 					JumpBelowOrEqual: loop].
- 		 loop := cogit Label.
- 		 "see concretizeDataCacheControl"
- 		 cogit
- 			gen: DC operand: CArg2Reg operand: DC_CVAU;		"clean (flush) address"
- 			AddCq: self dataCacheLineLength R: CArg2Reg;
- 			CmpR: CArg1Reg R: CArg2Reg;
- 			JumpBelowOrEqual: loop].
  
+ 			cogit gen: DSB operand: DSB_ISH operand: DSB_ALL.		"Ensure visibility of the data cleaned from cache"
- 	cogit gen: DSB operand: DSB_ISH operand: DSB_ALL.		"Ensure visibility of the data cleaned from cache"
  
+ 			self instructionCacheFlushRequired ifTrue: "CTR_EL0.DIC is zero; must clean instruction cache to point of unification."
+ 				["Mask is large enough to encompass the method zone and has the correct minimum alignment."
+ 				 mask := 1 << (cogit coInterpreter highBit: cogit methodZone zoneEnd) - self instructionCacheLineLength.
+ 				 cogit AndCq: mask R: CArg0Reg R: CArg2Reg. "CArg2Reg = aligned pointer to start of each data cache line"
- 	self instructionCacheFlushRequired ifTrue: "CTR_EL0.DIC is zero; must clean instruction cache to point of unification."
- 		["Mask is large enough to encompass the method zone and has the correct minimum alignment."
- 		 mask := 1 << (cogit coInterpreter highBit: cogit methodZone zoneEnd) - self instructionCacheLineLength.
- 		 cogit AndCq: mask R: CArg0Reg R: CArg2Reg. "CArg2Reg = aligned pointer to start of each data cache line"
  	
+ 				 loop := cogit Label.
+ 				 "see concretizeDataCacheControl"
+ 				 cogit
+ 					gen: IC operand: CArg2Reg operand: IC_IVAU;		"clean (flush) address"
+ 					AddCq: self instructionCacheLineLength R: CArg2Reg;
+ 					CmpR: CArg1Reg R: CArg2Reg;
+ 					JumpBelowOrEqual: loop.
- 		 loop := cogit Label.
- 		 "see concretizeDataCacheControl"
- 		 cogit
- 			gen: IC operand: CArg2Reg operand: IC_IVAU;		"clean (flush) address"
- 			AddCq: self instructionCacheLineLength R: CArg2Reg;
- 			CmpR: CArg1Reg R: CArg2Reg;
- 			JumpBelowOrEqual: loop.
  
+ 				 cogit gen: DSB operand: DSB_ISH operand: DSB_ALL].
- 		 cogit gen: DSB operand: DSB_ISH operand: DSB_ALL].
  
+ 			cogit
+ 				gen: ISB;
+ 				RetN: 0]!
- 	cogit
- 		gen: ISB;
- 		RetN: 0!

Item was changed:
  ----- Method: CogARMv8Compiler>>numDCacheFlushOpcodes (in category 'inline cacheing') -----
  numDCacheFlushOpcodes
+ 	self cppIf: #DUAL_MAPPED_CODE_ZONE
+ 		ifTrue: [^cogit getCodeToDataDelta ~= 0 ifTrue: [15] ifFalse: [0]]
+ 		ifFalse: [^0]!
- 	^cogit getCodeToDataDelta ~= 0 ifTrue: [15] ifFalse: [0]!

Item was changed:
  ----- Method: CogARMv8Compiler>>numICacheFlushOpcodes (in category 'inline cacheing') -----
  numICacheFlushOpcodes
+ 	"Apple's code is simple and works; we can't better it..."
+ 	self cppIf: #__APPLE__
+ 		ifTrue: [^0]
+ 		ifFalse: [^24]!
- 	^24!

Item was changed:
  ----- Method: Cogit>>maybeGenerateCacheFlush (in category 'initialization') -----
  maybeGenerateCacheFlush
  	| startAddress |
  	<inline: true>
  	backEnd numICacheFlushOpcodes > 0 ifTrue:
  		[self allocateOpcodes: backEnd numICacheFlushOpcodes bytecodes: 0.
  		 startAddress := methodZoneBase.
  		 backEnd generateICacheFlush.
  		 self outputInstructionsForGeneratedRuntimeAt: startAddress.
  		 self recordGeneratedRunTime: 'ceFlushICache' address: startAddress.
  		 ceFlushICache := self cCoerceSimple: startAddress to: #'void (*)(usqIntptr_t,usqIntptr_t)'.
  		 backEnd initialFlushICacheFrom: startAddress to: methodZoneBase].
+ 	backEnd numDCacheFlushOpcodes > 0 ifTrue:
+ 		[self allocateOpcodes: backEnd numDCacheFlushOpcodes bytecodes: 0.
+ 		 startAddress := methodZoneBase.
+ 		 backEnd generateDCacheFlush.
+ 		 self outputInstructionsForGeneratedRuntimeAt: startAddress.
+ 		 self recordGeneratedRunTime: 'ceFlushDCache' address: startAddress.
+ 		 ceFlushDCache := self cCoerceSimple: startAddress to: #'void (*)(usqIntptr_t,usqIntptr_t)'.
+ 		 backEnd initialFlushICacheFrom: startAddress to: methodZoneBase]!
- 	self cppIf: #DUAL_MAPPED_CODE_ZONE
- 		ifTrue:
- 			[backEnd numDCacheFlushOpcodes > 0 ifTrue:
- 				[self allocateOpcodes: backEnd numDCacheFlushOpcodes bytecodes: 0.
- 				 startAddress := methodZoneBase.
- 				 backEnd generateDCacheFlush.
- 				 self outputInstructionsForGeneratedRuntimeAt: startAddress.
- 				 self recordGeneratedRunTime: 'ceFlushDCache' address: startAddress.
- 				 ceFlushDCache := self cCoerceSimple: startAddress to: #'void (*)(usqIntptr_t,usqIntptr_t)'.
- 				 backEnd initialFlushICacheFrom: startAddress to: methodZoneBase]]!

Item was changed:
  ----- Method: TMethod>>removeFinalSelfReturnIn: (in category 'transformations') -----
  removeFinalSelfReturnIn: aCodeGenOrNil
  	"The Smalltalk parser automatically adds the statement '^self' to the end of methods
  	 without explicit returns.  This method removes such statements, since in most VMMaker
  	 classes (except struct classes) the generated code has no notion of 'self' anyway.
  	 If the statement is removed and no return type has yet been specified and the class
  	 specifies a default return type (e.g. #void) for methods that don't return, then set the
  	 return type accordingly."
  
+ 	| removeLastStatement |
- 	| lastStmt |
  	parseTree statements isEmpty ifTrue: [^self].
+ 	removeLastStatement := false.
+ 	(parseTree statements size > 1
+ 	 and: [(parseTree statements at: parseTree statements size - 1) isReturningIf])
+ 		ifTrue: [removeLastStatement := true]
+ 		ifFalse:
+ 			[| nameOfSelf lastStmt  |
+ 			 nameOfSelf := (definingClass isVMClass and: [definingClass isStructClass])
+ 								ifTrue: ['self_in_', ((aCodeGenOrNil ifNil: [CCodeGenerator basicNew]) cFunctionNameFor: selector)]
+ 								ifFalse: ['self'].
+ 			 ((lastStmt := parseTree statements last) isReturn
+ 			  and: [lastStmt expression isVariable
+ 			  and: [nameOfSelf = lastStmt expression name]]) ifTrue:
+ 				[| tokens |
+ 				 tokens := Scanner new scanTokens: (definingClass sourceCodeAt: selector ifAbsent: ['']).
+ 				 (tokens size < 2 or: [tokens last ~= nameOfSelf or: [(tokens at: tokens size - 1) ~= #'^']]) ifTrue:
+ 					[removeLastStatement := true]]].
+ 
+ 	removeLastStatement ifTrue:
+ 		[parseTree setStatements: parseTree statements allButLast.
+ 		 (returnType isNil
+ 		  and: [aCodeGenOrNil notNil
+ 		  and: [parseTree noneSatisfy: [:node| node isReturn and: [node expression isVariable not or: [node expression name ~= 'self']]]]]) ifTrue:
+ 			[self returnType: (aCodeGenOrNil implicitReturnTypeFor: selector)]]!
- 	((lastStmt := parseTree statements last) isReturn
- 	 and: [lastStmt expression isVariable
- 	 and: ['self' = lastStmt expression name]]) ifTrue:
- 		[| tokens |
- 		tokens := Scanner new scanTokens: (definingClass sourceCodeAt: selector ifAbsent: ['']).
- 		(tokens size < 2
- 		 or: [(tokens last: 2) ~= #(#'^' 'self')]) ifTrue:
- 			[parseTree setStatements: parseTree statements allButLast.
- 			 (returnType isNil
- 			  and: [aCodeGenOrNil notNil
- 			  and: [parseTree noneSatisfy: [:node| node isReturn and: [node expression isVariable not or: [node expression name ~= 'self']]]]]) ifTrue:
- 				[self returnType: (aCodeGenOrNil implicitReturnTypeFor: selector)]]]!

Item was changed:
  ----- Method: TSendNode>>isReturningIf (in category 'testing') -----
  isReturningIf
+ 	^((#(ifTrue:ifFalse: ifFalse:ifTrue: ifNil:ifNotNil: ifNotNil:ifNil:) includes: selector)
+ 	   and: [arguments allSatisfy: [:arg| arg endsWithReturn]])
+ 		or: [(#(cppIf:ifTrue:ifFalse: cppIf:ifTrue:cppIf:ifTrue:ifFalse:) includes: selector)
+ 			and: [| keywords |
+ 				keywords := selector keywords.
+ 				keywords first = 'cppIf:'
+ 				and: [(1 to: arguments size) allSatisfy:
+ 							[:i| (keywords at: i) = 'cppIf:' or: [(arguments at: i) endsWithReturn]]]]]!
- 	^(#(ifTrue:ifFalse: ifFalse:ifTrue: ifNil:ifNotNil: ifNotNil:ifNil:) includes: selector)
- 	   and: [arguments allSatisfy: [:arg| arg endsWithReturn]]!

Item was changed:
+ ----- Method: VMClass class>>isCogitClass (in category 'testing') -----
- ----- Method: VMClass class>>isCogitClass (in category 'translation') -----
  isCogitClass
  	"The various Cogit classes override this."
  	^false!

Item was changed:
+ ----- Method: VMClass class>>isInterpreterClass (in category 'testing') -----
- ----- Method: VMClass class>>isInterpreterClass (in category 'translation') -----
  isInterpreterClass
  	"The various Interpreter classes override this."
  	^false!

Item was changed:
+ ----- Method: VMClass class>>isPluginClass (in category 'testing') -----
- ----- Method: VMClass class>>isPluginClass (in category 'translation') -----
  isPluginClass
  	"InterpreterPlugin class override this."
  	^false!

Item was changed:
+ ----- Method: VMClass class>>isStructClass (in category 'testing') -----
- ----- Method: VMClass class>>isStructClass (in category 'translation') -----
  isStructClass
  	"The various VMStructType classes override this."
  	^false!

Item was added:
+ ----- Method: VMClass class>>isVMClass (in category 'testing') -----
+ isVMClass
+ 	^true!



More information about the Vm-dev mailing list