[Vm-dev] VM Maker Inbox: VMMakerTests-GuillermoPolito.1.mcz

commits at source.squeak.org commits at source.squeak.org
Tue May 7 09:27:14 UTC 2019


A new version of VMMakerTests was added to project VM Maker Inbox:
http://source.squeak.org/VMMakerInbox/VMMakerTests-GuillermoPolito.1.mcz

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

Name: VMMakerTests-GuillermoPolito.1
Author: GuillermoPolito
Time: 7 May 2019, 11:27:14.195596 am
UUID: 77f9288f-aa44-0d00-873a-d0970059f8ce
Ancestors: 

Tests for AST translation and C code generation

==================== Snapshot ====================

SystemOrganization addCategory: #VMMakerTests!

TestCase subclass: #VMCodeGenerationTest
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'VMMakerTests'!

----- Method: VMCodeGenerationTest>>methodWithIfNil (in category 'generation-targets') -----
methodWithIfNil

	self something
		ifNil: [ 1 ]
		ifNotNil: [ 2 ]!

----- Method: VMCodeGenerationTest>>methodWithIfNilAssignment (in category 'generation-targets') -----
methodWithIfNilAssignment

	| variable |
	variable := self something
		ifNil: [ 1 ]
		ifNotNil: [ 2 ]!

----- Method: VMCodeGenerationTest>>methodWithIfNilAssignmentOfComplexStatements (in category 'generation-targets') -----
methodWithIfNilAssignmentOfComplexStatements

	| variable |
	variable := self something
		ifNil: [ | temp |
			temp := 1.
			temp := temp + 1.
			temp * 3 ]
		ifNotNil: [ | temp |
			temp := 2.
			temp := temp + 5.
			temp * 3 ]!

----- Method: VMCodeGenerationTest>>methodWithLoop (in category 'generation-targets') -----
methodWithLoop

	1 to: 10 do: [ :i | self foo: i ]!

----- Method: VMCodeGenerationTest>>methodWithNilIfNil (in category 'generation-targets') -----
methodWithNilIfNil

	^ nil
		ifNil: [ 1 ]
		ifNotNil: [ 2 ]!

----- Method: VMCodeGenerationTest>>testComplexIfNilAssignment (in category 'tests') -----
testComplexIfNilAssignment

	| translation thisAST codeGenerator result |
	thisAST := (self class >> #methodWithIfNilAssignmentOfComplexStatements) ast.
	translation := thisAST asTranslationMethodOfClass: TMethod.
	codeGenerator := CCodeGeneratorGlobalStructure new.
	codeGenerator addMethod: translation.
	codeGenerator doInlining: true.
		
	result := String streamContents: [ :stream |
		translation parseTree statements first emitCCodeOn: stream level: 0 generator: codeGenerator.
	].
	
	self assert: result equals: 'if ((something()) == null) {
	temp = 1;
	temp += 1;
	variable = temp * 3;
}
else {
	temp = 2;
	temp += 5;
	variable = temp * 3;
}'!

----- Method: VMCodeGenerationTest>>testLoopVariableIsTemp (in category 'tests') -----
testLoopVariableIsTemp

	| translation thisAST codeGenerator result |
	thisAST := (self class >> #methodWithLoop) ast.
	translation := thisAST asTranslationMethodOfClass: TMethod.
	codeGenerator := CCodeGeneratorGlobalStructure new.
	codeGenerator doInlining: true.
	
	result := String streamContents: [ :stream |
		translation emitCCodeOn: stream generator: codeGenerator.
	].

	self assert: result equals: '
	/* VMCodeGenerationTest>>#methodWithLoop */
static sqInt
methodWithLoop(void)
{
    sqInt i;

	for (i = 1; i <= 10; i += 1) {
		foo(i);
	}
	return self;
}
'!

----- Method: VMCodeGenerationTest>>testNilIfNilGeneratesOnlyFirstBranch (in category 'tests') -----
testNilIfNilGeneratesOnlyFirstBranch

	| translation thisAST codeGenerator result |
	thisAST := (self class >> #methodWithNilIfNil) ast.
	translation := thisAST asTranslationMethodOfClass: TMethod.
	codeGenerator := CCodeGeneratorGlobalStructure new.
	codeGenerator generateDeadCode: false.
	codeGenerator addMethod: translation.
	codeGenerator doInlining: true.

	result := String streamContents: [ :stream |
		translation parseTree statements first emitCCodeOn: stream level: 0 generator: codeGenerator.
	].
	
	self assert: result equals: 'return 1'!

----- Method: VMCodeGenerationTest>>testSimpleIfNil (in category 'tests') -----
testSimpleIfNil

	| translation thisAST codeGenerator result |
	thisAST := (self class >> #methodWithIfNilAssignment) ast.
	translation := thisAST asTranslationMethodOfClass: TMethod.
	codeGenerator := CCodeGeneratorGlobalStructure new.
	codeGenerator generateDeadCode: false.
	codeGenerator addMethod: translation.
	codeGenerator doInlining: true.
	
	result := String streamContents: [ :stream |
		translation parseTree statements first emitCCodeOn: stream level: 0 generator: codeGenerator.
	].
	
	self assert: result equals: 'variable = ((something()) == null
	? 1
	: 2)'!

----- Method: VMCodeGenerationTest>>testSimpleIfNilAssignment (in category 'tests') -----
testSimpleIfNilAssignment

	| translation thisAST codeGenerator result |
	thisAST := (self class >> #methodWithIfNil) ast.
	translation := thisAST asTranslationMethodOfClass: TMethod.
	codeGenerator := CCodeGeneratorGlobalStructure new.
	codeGenerator generateDeadCode: false.
	codeGenerator addMethod: translation.
	codeGenerator doInlining: true.
	
	result := String streamContents: [ :stream |
		translation parseTree statements first emitCCodeOn: stream level: 0 generator: codeGenerator.
	].
	
	self assert: result equals: 'if ((something()) == null) {
}
else {
}'!

TestCase subclass: #VMMASTTranslationTest
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'VMMakerTests'!

----- Method: VMMASTTranslationTest>>+ (in category 'generation-targets') -----
+ arg!

----- Method: VMMASTTranslationTest>>inlineMethodWithLoop (in category 'generation-targets') -----
inlineMethodWithLoop

	self methodWithLoop!

----- Method: VMMASTTranslationTest>>inlineSecondLevelMethodWithLoop (in category 'generation-targets') -----
inlineSecondLevelMethodWithLoop

	self inlineMethodWithLoop!

----- Method: VMMASTTranslationTest>>inlineTwiceMethodWithLoop (in category 'generation-targets') -----
inlineTwiceMethodWithLoop

	self methodWithLoop.
	self methodWithLoop!

----- Method: VMMASTTranslationTest>>inlineTwiceSecondLevelMethodWithLoop (in category 'generation-targets') -----
inlineTwiceSecondLevelMethodWithLoop

	self inlineMethodWithLoop.
	self inlineMethodWithLoop!

----- Method: VMMASTTranslationTest>>methodWithArgument: (in category 'generation-targets') -----
methodWithArgument: anArgument!

----- Method: VMMASTTranslationTest>>methodWithIfNil (in category 'generation-targets') -----
methodWithIfNil

	self something
		ifNil: [ 1 ]
		ifNotNil: [ 2 ]!

----- Method: VMMASTTranslationTest>>methodWithLoop (in category 'generation-targets') -----
methodWithLoop

	1 to: 10 do: [ :i | self foo: i ]!

----- Method: VMMASTTranslationTest>>methodWithNoArguments (in category 'generation-targets') -----
methodWithNoArguments!

----- Method: VMMASTTranslationTest>>testArgumentIsNoTemp (in category 'tests') -----
testArgumentIsNoTemp

	| translation thisAST |
	thisAST := (self class >> #methodWithArgument:) ast.
	translation := thisAST asTranslationMethodOfClass: TMethod.
	
	self deny: (translation locals includes: thisAST arguments first name)!

----- Method: VMMASTTranslationTest>>testIfNilIfNotNilBecomesIfTrueIfFalse (in category 'tests') -----
testIfNilIfNotNilBecomesIfTrueIfFalse

	| translation thisAST |
	thisAST := (self class >> #methodWithIfNil) ast.
	translation := thisAST asTranslationMethodOfClass: TMethod.
	
	self assert: translation statements first selector equals: #ifTrue:ifFalse:!

----- Method: VMMASTTranslationTest>>testInlineMethodWithLoopDeclaresLoopIndexVariable (in category 'tests') -----
testInlineMethodWithLoopDeclaresLoopIndexVariable

	| translation thisAST codeGenerator inlinedMethod |
	thisAST := (self class >> #inlineMethodWithLoop) ast.
	translation := thisAST asTranslationMethodOfClass: TMethod.
	inlinedMethod := ((self class >> #methodWithLoop) asTranslationMethodOfClass: TMethod).
	
	codeGenerator := CCodeGeneratorGlobalStructure new.
	codeGenerator addMethod: translation.
	codeGenerator addMethod: inlinedMethod.
	codeGenerator doInlining: true.

	self assert: (translation locals includesAll: inlinedMethod locals)!

----- Method: VMMASTTranslationTest>>testInlineSecondLevelMethodWithLoopDeclaresLoopIndexVariable (in category 'tests') -----
testInlineSecondLevelMethodWithLoopDeclaresLoopIndexVariable

	| translation thisAST codeGenerator inlinedMethods |
	thisAST := (self class >> #inlineSecondLevelMethodWithLoop) ast.
	translation := thisAST asTranslationMethodOfClass: TMethod.
	inlinedMethods := #( inlineMethodWithLoop methodWithLoop ) collect: [ :s | ((self class >> s) asTranslationMethodOfClass: TMethod)].
	
	codeGenerator := CCodeGeneratorGlobalStructure new.
	codeGenerator addMethod: translation.
	inlinedMethods do: [ :e |
		codeGenerator addMethod: e ].
	codeGenerator doInlining: true.

	self assert: translation locals size equals: 1!

----- Method: VMMASTTranslationTest>>testInlineTwiceMethodWithLoopDeclaresTwiceLoopIndexVariable (in category 'tests') -----
testInlineTwiceMethodWithLoopDeclaresTwiceLoopIndexVariable

	| translation thisAST codeGenerator inlinedMethod |
	thisAST := (self class >> #inlineTwiceMethodWithLoop) ast.
	translation := thisAST asTranslationMethodOfClass: TMethod.
	inlinedMethod := ((self class >> #methodWithLoop) asTranslationMethodOfClass: TMethod).
	
	codeGenerator := CCodeGeneratorGlobalStructure new.
	codeGenerator addMethod: translation.
	codeGenerator addMethod: inlinedMethod.
	codeGenerator doInlining: true.

	self assert: translation locals size equals: 2!

----- Method: VMMASTTranslationTest>>testInlineTwiceSecondLevelMethodWithLoopDeclaresLoopIndexVariable (in category 'tests') -----
testInlineTwiceSecondLevelMethodWithLoopDeclaresLoopIndexVariable

	| translation thisAST codeGenerator inlinedMethods |
	thisAST := (self class >> #inlineTwiceSecondLevelMethodWithLoop) ast.
	translation := thisAST asTranslationMethodOfClass: TMethod.
	inlinedMethods := #( inlineMethodWithLoop methodWithLoop ) collect: [ :s | ((self class >> s) asTranslationMethodOfClass: TMethod)].
	
	codeGenerator := CCodeGeneratorGlobalStructure new.
	codeGenerator addMethod: translation.
	inlinedMethods do: [ :e |
		codeGenerator addMethod: e ].
	codeGenerator doInlining: true.

	self assert: translation locals size equals: 2!

----- Method: VMMASTTranslationTest>>testKeywordMethodHasArgument (in category 'tests') -----
testKeywordMethodHasArgument

	| translation thisAST |
	thisAST := (self class >> #methodWithArgument:) ast.
	translation := thisAST asTranslationMethodOfClass: TMethod.
	
	self assert: (translation args includes: thisAST arguments first name)!

----- Method: VMMASTTranslationTest>>testMethodWithLoopDeclaresLoopIndexVariable (in category 'tests') -----
testMethodWithLoopDeclaresLoopIndexVariable

	| translation thisAST block |
	thisAST := (self class >> #methodWithLoop) ast.
	translation := thisAST asTranslationMethodOfClass: TMethod.
	
	block := thisAST statements first arguments second.
	self deny: (translation locals includes: block arguments first)!

----- Method: VMMASTTranslationTest>>testTranslateBinaryMethodHasSameName (in category 'tests') -----
testTranslateBinaryMethodHasSameName

	| translation thisAST |
	thisAST := self class >> #+.
	translation := thisAST asTranslationMethodOfClass: TMethod.
	
	self assert: translation selector equals: thisAST selector.!

----- Method: VMMASTTranslationTest>>testTranslateKeywordMethodHasSameName (in category 'tests') -----
testTranslateKeywordMethodHasSameName

	| translation thisAST |
	thisAST := self class >> #methodWithArgument:.
	translation := thisAST asTranslationMethodOfClass: TMethod.
	
	self assert: translation selector equals: thisAST selector.!

----- Method: VMMASTTranslationTest>>testTranslateUnaryMethodHasSameName (in category 'tests') -----
testTranslateUnaryMethodHasSameName

	| translation thisAST |
	thisAST := self class >> #methodWithNoArguments.
	translation := thisAST asTranslationMethodOfClass: TMethod.
	
	self assert: translation selector equals: thisAST selector.!



More information about the Vm-dev mailing list