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

commits at source.squeak.org commits at source.squeak.org
Sun Dec 13 19:47:01 UTC 2015


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

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

Name: VMMaker.oscog-eem.1588
Author: eem
Time: 13 December 2015, 11:45:14.188 am
UUID: e4446d99-f9ba-4680-be2d-543e9e0dc07e
Ancestors: VMMaker.oscog-eem.1587

x64 Cogit:
Changes to get cogitX64.c to compile and link.

Slang: don't emit leaf statements to eliminate warnings in the cogit.c's.

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

Item was changed:
  ----- Method: CCodeGenerator>>addMethodFor:selector: (in category 'utilities') -----
  addMethodFor: aClass selector: selector
  	"Add the given method to the code base and answer its translation
  	 or nil if it shouldn't be translated."
  
  	| method tmethod |
  	method := aClass compiledMethodAt: selector.
  	(method pragmaAt: #doNotGenerate) ifNotNil:
  		["only remove a previous method if this one overrides it, i.e. this is a subclass method.
  		 If the existing method is in a different hierarchy this method must be merely a redeirect."
  		 (methods at: selector ifAbsent: []) ifNotNil:
  			[:tm|
  			(aClass includesBehavior: tm definingClass) ifTrue:
  				[self removeMethodForSelector: selector]].
  		 ^nil].
  	method isSubclassResponsibility ifTrue:
  		[^nil].
  	(self shouldIncludeMethodFor: aClass selector: selector) ifFalse:
  		[^nil].
  	tmethod := self compileToTMethodSelector: selector in: aClass.
  	"Even thoug we exclude initialize methods, we must consider their
  	 global variable usage, otherwise globals may be incorrectly localized."
  	selector == #initialize ifTrue:
  		[self checkForGlobalUsage: (tmethod allReferencedVariablesIn: self) in: tmethod.
  		 ^nil].
  	self addMethod: tmethod.
  	"If the method has a macro then add the macro.  But keep the method
  	 for analysis purposes (e.g. its variable accesses)."
  	(method pragmaAt: #cmacro:) ifNotNil:
  		[:pragma|
  		self addMacro: (pragma argumentAt: 1) for: selector.
  		(inlineList includes: selector) ifTrue:
  			[inlineList := inlineList copyWithout: selector]].
  	(method pragmaAt: #cmacro) ifNotNil:
+ 		[:pragma| | literal | "Method should be just foo ^const"
+ 		self assert: (method numArgs = 0 and: [method numLiterals = 3 or: [method isQuick]]).
+ 		literal := method isQuick
+ 					ifTrue: [method decompile block statements last expr key]
+ 					ifFalse: [method literalAt: 1].
- 		[:pragma| | literal |
- 		literal := method literalAt: 1. "Method should be just foo ^const"
- 		self assert: (method numArgs = 0 and: [method numLiterals = 3]).
  		self addMacro: '() ', (self cLiteralFor: literal value name: method selector) for: selector.
  		(inlineList includes: selector) ifTrue:
  			[inlineList := inlineList copyWithout: selector]].
  	^tmethod!

Item was changed:
  ----- Method: CogIA32Compiler>>genRestoreRegsExcept: (in category 'abi') -----
  genRestoreRegsExcept: abstractReg
  	| realReg |
  	realReg := self concreteRegister: abstractReg.
+ 	self assert: (EDI > EAX and: [EDI - EAX + 1 = 6]).
+ 	EAX to: EDI do:
+ 		[:reg|
+ 		realReg = reg ifTrue: [cogit AddCq: 4 R: ESP] ifFalse: [cogit PopR: reg]].
- 	realReg = EAX ifTrue: [cogit AddCq: 4 R: ESP] ifFalse: [cogit PopR: EAX].
- 	realReg = EBX ifTrue: [cogit AddCq: 4 R: ESP] ifFalse: [cogit PopR: EBX].
- 	realReg = ECX ifTrue: [cogit AddCq: 4 R: ESP] ifFalse: [cogit PopR: ECX].
- 	realReg = EDX ifTrue: [cogit AddCq: 4 R: ESP] ifFalse: [cogit PopR: EDX].
- 	realReg = ESI   ifTrue: [cogit AddCq: 4 R: ESP] ifFalse: [cogit PopR: ESI].
- 	realReg = EDI   ifTrue: [cogit AddCq: 4 R: ESP] ifFalse: [cogit PopR: EDI].
  	^0!

Item was changed:
  ----- Method: CogIA32Compiler>>genSaveRegisters (in category 'abi') -----
  genSaveRegisters
  	"Save the general purpose registers for a trampoline call."
+ 
+ 	self assert: (EDI > EAX and: [EDI - EAX + 1 = 6]).
+ 	EDI to: EAX by: -1 do: [:reg| cogit PushR: reg].
- 	cogit
- 		PushR: EDI;
- 		PushR: ESI;
- 		PushR: EDX;
- 		PushR: ECX;
- 		PushR: EBX;
- 		PushR: EAX.
  	^0!

Item was added:
+ ----- Method: CogX64Compiler>>genLoadCStackPointer (in category 'smalltalk calling convention') -----
+ genLoadCStackPointer
+ 	"Load the stack pointer register with that of the C stack, effecting
+ 	 a switch to the C stack.  Used when machine code calls into the
+ 	 CoInterpreter run-time (e.g. to invoke interpreter primitives)."
+ 	cogit MoveAw: cogit cStackPointerAddress R: SPReg.
+ 	^0!

Item was added:
+ ----- Method: CogX64Compiler>>genRestoreRegsExcept: (in category 'abi') -----
+ genRestoreRegsExcept: abstractReg
+ 	| realReg |
+ 	realReg := self concreteRegister: abstractReg.
+ 	self assert: (R15 > RAX and: [R15 - RAX + 1 = 16]).
+ 	RAX to: R15 do:
+ 		[:reg|
+ 		realReg = reg ifTrue: [cogit AddCq: 4 R: RSP] ifFalse: [cogit PopR: reg]].
+ 	^0!

Item was changed:
  ----- Method: CogX64Compiler>>genSaveRegisters (in category 'abi') -----
  genSaveRegisters
  	"Save the general purpose registers for a trampoline call."
+ 
+ 	self assert: (R15 > RAX and: [R15 - RAX + 1 = 16]).
+ 	R15 to: RAX by: -1 do: [:reg| cogit PushR: reg].
- 	cogit
- 		PushR: R15;
- 		PushR: R14;
- 		PushR: R13;
- 		PushR: R12;
- 		PushR: R11;
- 		PushR: R10;
- 		PushR: R9;
- 		PushR: R8;
- 		PushR: RDI;
- 		PushR: RSI;
- 		PushR: RDX;
- 		PushR: RCX;
- 		PushR: RBX;
- 		PushR: RAX.
  	^0!

Item was added:
+ ----- Method: CogX64Compiler>>rewriteInlineCacheTag:at: (in category 'inline cacheing') -----
+ rewriteInlineCacheTag: cacheTag at: callSiteReturnAddress
+ 	"Rewrite an inline cache with a new tag.  This variant is used
+ 	 by the garbage collector."
+ 	self unalignedLong32At: callSiteReturnAddress - 9 put: cacheTag!

Item was added:
+ ----- Method: CogX64Compiler>>sizeImmediateGroup1:at: (in category 'disassembly') -----
+ sizeImmediateGroup1: op at: pc
+ 	"see [1] p A-7, p A-13"
+ 	| modrm mod ro rm |
+ 	modrm := objectMemory byteAt: pc + 1.
+ 	mod := modrm >> 6.
+ 	ro := modrm >> 3 bitAnd: 7.
+ 	rm := modrm bitAnd: 7.
+ 	^ro caseOf:
+ 	   {	[7 "cmp"]	->	[op = 16r81
+ 							ifTrue: [6]
+ 							ifFalse: [3]] }!

Item was added:
+ ----- Method: CogX64Compiler>>unalignedLong32At:put: (in category 'memory access') -----
+ unalignedLong32At: byteAddress put: aWord
+ 	<cmacro: '(inst,byteAddress,aWord) long32Atput(byteAddress,aWord)'>
+ 	objectMemory
+ 		byteAt: byteAddress + 0 put:  (aWord bitAnd: 16rFF);
+ 		byteAt: byteAddress + 1 put: ((aWord >> 8) bitAnd: 16rFF);
+ 		byteAt: byteAddress + 2 put: ((aWord >> 16) bitAnd: 16rFF);
+ 		byteAt: byteAddress + 3 put: ((aWord >> 24) bitAnd: 16rFF).
+ 	^aWord!

Item was changed:
  ----- Method: Cogit>>mapFor:performUntil:arg: (in category 'method map') -----
  mapFor: cogMethod performUntil: functionSymbol arg: arg
  	"Unlinking/GC/Disassembly support"
  	<var: #cogMethod type: #'CogMethod *'>
+ 	<var: #functionSymbol declareC: 'sqInt (*functionSymbol)(sqInt annotation, char *mcpc, sqInt arg)'>
- 	<var: #functionSymbol declareC: 'int (*functionSymbol)(sqInt annotation, char *mcpc, sqInt arg)'>
  	<inline: true>
  	| mcpc map mapByte annotation result |
  	mcpc := cogMethod asInteger + cmNoCheckEntryOffset.
  	map := self mapStartFor: cogMethod.
  	objectMemory wordSize = 8 ifTrue:
  		[enumeratingCogMethod := cogMethod].
  	[(mapByte := objectMemory byteAt: map) ~= MapEnd] whileTrue:
  		[mapByte >= FirstAnnotation
  			ifTrue:
  				[mcpc := mcpc + ((mapByte bitAnd: DisplacementMask) * backEnd codeGranularity).
  				 "If this is an IsSendCall annotation, peek ahead for an IsAnnotationExtension, and consume it."
  				 ((annotation := mapByte >> AnnotationShift) = IsSendCall
  				  and: [(mapByte := objectMemory byteAt: map - 1) >> AnnotationShift = IsAnnotationExtension]) ifTrue:
  					[annotation := annotation + (mapByte bitAnd: DisplacementMask).
  					 map := map - 1].
  				 result := self perform: functionSymbol
  							   with: annotation
  							   with: (self cCoerceSimple: mcpc to: #'char *')
  							   with: arg.
  				 result ~= 0 ifTrue:
  					[^result]]
  			ifFalse:
  				[mapByte < (IsAnnotationExtension << AnnotationShift) ifTrue:
  					[mcpc := mcpc + ((mapByte - DisplacementX2N << AnnotationShift) * backEnd codeGranularity)]].
  		 map := map - 1].
  	^0!

Item was changed:
  ----- Method: SpurMemoryManager>>sixtyFourBitIndexableFormat (in category 'header formats') -----
  sixtyFourBitIndexableFormat
+ 	<api>
+ 	<cmacro>
  	^9!

Item was changed:
  ----- Method: TStmtListNode>>emitCCodeOn:prependToEnd:level:generator: (in category 'C code generation') -----
  emitCCodeOn: aStream prependToEnd: aNodeOrNil level: level generator: aCodeGen
  	self emitCCommentOn: aStream level: level.
  	statements withIndexDo:
  		[:s :idx|
  		s isStmtList ifFalse:
  			[s emitCCommentOn: aStream level: level].
+ 		(s isLeaf and: [aNodeOrNil isNil or: [idx < statements size]]) ifFalse:
+ 			[aStream peekLast ~~ Character tab ifTrue:
+ 				[aStream tab: level].
+ 			(aNodeOrNil notNil
+ 			 and: [idx = statements size])
+ 				ifTrue:
+ 					[s emitCCodeOn: aStream prependToEnd: aNodeOrNil level: level generator: aCodeGen]
+ 				ifFalse:
+ 					[s emitCCodeOn: aStream level: level generator: aCodeGen].
+ 			(self stream: aStream endsWithAnyOf: '};') ifFalse:
+ 				[s needsTrailingSemicolon ifTrue:
+ 					[aStream nextPut: $;]].
+ 			aStream peekLast ~~ Character cr ifTrue:
+ 				[aStream cr]]].
- 		aStream peekLast ~~ Character tab ifTrue:
- 			[aStream tab: level].
- 		(aNodeOrNil notNil
- 		 and: [idx = statements size])
- 			ifTrue:
- 				[s emitCCodeOn: aStream prependToEnd: aNodeOrNil level: level generator: aCodeGen]
- 			ifFalse:
- 				[s emitCCodeOn: aStream level: level generator: aCodeGen].
- 		(self stream: aStream endsWithAnyOf: '};') ifFalse:
- 			[s needsTrailingSemicolon ifTrue:
- 				[aStream nextPut: $;]].
- 		aStream peekLast ~~ Character cr ifTrue:
- 			[aStream cr]].
  !



More information about the Vm-dev mailing list