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

commits at source.squeak.org commits at source.squeak.org
Wed Aug 8 21:38:23 UTC 2012


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

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

Name: VMMaker.oscog-eem.196
Author: eem
Time: 8 August 2012, 2:36:30.063 pm
UUID: 01753d70-0311-46ec-a06b-a8be6d8697fb
Ancestors: VMMaker.oscog-lw.195

Fix generation of CogAbstractInstruction typedefs now there are
multiple concrete subclasses.
Eliminate a few warnings by setting return type of startOfMemory.
Fix bug in inliner with leaf methods.  Fix ^self slip uncovered by fix.
Elimnate unnecessary blocks around first args of cppIf:ifTrue:...

=============== Diff against VMMaker.oscog-lw.195 ===============

Item was changed:
  ----- Method: CCodeGenerator>>emitCTypesOn: (in category 'C code generator') -----
  emitCTypesOn: aStream 
  	"Store local type declarations on the given stream."
  	vmClass ifNotNil:
  		[vmClass ancilliaryStructClasses do:
  			[:structClass|
+ 			(structClass isAbstract not
+ 			 and: [vmClass shouldGenerateTypedefFor: structClass]) ifTrue:
- 			(vmClass shouldGenerateTypedefFor: structClass) ifTrue:
  				[structClass printTypedefOn: aStream.
  				 aStream cr; cr]]]!

Item was changed:
  ----- Method: CogARMCompiler>>numberOfSaveableRegisters (in category 'abi') -----
  numberOfSaveableRegisters
  	"Answer the number of registers to be saved in a trampoline call that saves registers.
  	 R0 through R12, See genSaveRegisters."
+ 	<cmacro: '(self) 13'>
- 	<cmacro: '() 13'>
  	^13!

Item was changed:
  ----- Method: CogAbstractInstruction class>>instVarNamesAndTypesForTranslationDo: (in category 'translation') -----
  instVarNamesAndTypesForTranslationDo: aBinaryBlock
  	"enumerate aBinaryBlock with the names and C type strings for the inst vars to include in an AbstractInstruction struct."
+ 	"{CogAbstractInstruction. CogIA32Compiler. CogARMCompiler} do:
+ 		[:c| Transcript print: c; cr. c printTypedefOn: Transcript]"
- 	"CogIA32Compiler printTypedefOn: Transcript"
- 	"CogARMCompiler printTypedefOn: Transcript"
  	| machineCodeBytes |
  	machineCodeBytes := self ==  CogAbstractInstruction
  								ifTrue: [0]
+ 								ifFalse: [self basicNew machineCodeBytes].
+ 	(self filteredInstVarNames copyWithout: 'machineCode'), #('machineCode') do:
- 								ifFalse: [Cogit cogCompilerClass basicNew machineCodeBytes].
- 	self filteredInstVarNames do:
  		[:ivn|
  		ivn ~= 'bcpc' ifTrue:
  			[aBinaryBlock
  				value: ivn
  				value: (ivn caseOf: {
  							['address']			-> ['unsigned long'].
  							['machineCode']	-> [{'unsigned char'. '[', machineCodeBytes printString, ']'}].
  							['operands']		-> [#('unsigned long' '[3]')].
  							['dependent']		-> ['struct _AbstractInstruction *']}
  						otherwise:
  							[#char])]]!

Item was added:
+ ----- Method: CogAbstractInstruction class>>isAbstract (in category 'testing') -----
+ isAbstract
+ 	^self == CogAbstractInstruction!

Item was changed:
  ----- Method: CogAbstractInstruction class>>structTypeName (in category 'translation') -----
  structTypeName
+ 	^'AbstractInstruction'!
- 	^self name allButFirst: 3 "Drop initial Cog"!

Item was changed:
  ----- Method: CogIA32Compiler>>numberOfSaveableRegisters (in category 'abi') -----
  numberOfSaveableRegisters
  	"Answer the number of registers to be saved in a trampoline call that saves registers.
  	 See genSaveRegisters"
+ 	<cmacro: '(self) 6'>
- 	<cmacro: '() 6'>
  	^6!

Item was changed:
  ----- Method: CogIA32Compiler>>padIfPossibleWithNopsFrom:to: (in category 'generate machine code') -----
  padIfPossibleWithNopsFrom: startAddr to: endAddr
+ 	self nopsFrom: startAddr to: endAddr!
- 	^self nopsFrom: startAddr to: endAddr!

Item was removed:
- ----- Method: Cogit class>>cogCompilerClass (in category 'accessing') -----
- cogCompilerClass
- 	"Answer the concrete subclass of CogAbstractCompiler in current use."
- 	^ProcessorClass basicNew abstractInstructionCompilerClass!

Item was changed:
  ----- Method: IA32ABIPlugin>>primCallOutDoubleReturn (in category 'primitives-callouts') -----
  primCallOutDoubleReturn
  	"Call a foreign function that answers a double-precision floating-point result in %f0
  	 according to IA32-ish ABI rules. The primitive will have a signature of the form
  	functionAddress <Alien> primFFICallResult: result <Alien|Object> with: firstArg <Alien | Integer> ... with: lastArg <Alien | Integer> ^<Alien>
  		<primitive: 'primCallOutDoubleReturn' error: errorCode module: 'IA32ABI'>.
  	Answer result. If result is an Alien the value answered by the call will be assigned to result."
  	| errCode mac result |
  	<export: true>
  	mac := interpreterProxy methodArgumentCount.
+ 	self cppIf: STACKVM
- 	self cppIf: [STACKVM]
  		ifTrue: "In the STACKVM stacks grow down"
  			[self cCode: 'errCode = callIA32DoubleReturn(interpreterProxy->getStackPointer() + mac - 2, /* arg vec */
  															1 - mac	/* nargs */,
  															mac	/* funcOffset*/,
  															mac - 1	/* resultOffset */)'
  				inSmalltalk: [errCode := PrimErrUnsupported]]
  		ifFalse:
  			[self cCode: 'errCode = callIA32DoubleReturn(interpreterProxy->getStackPointer() - mac + 2, /* arg vec */
  															mac - 1	/* nargs */,
  															mac	/* funcOffset*/,
  															mac - 1	/* resultOffset */)'
  				inSmalltalk: [errCode := PrimErrUnsupported]].
  	errCode ~= 0 ifTrue:
  		[^interpreterProxy primitiveFailFor: errCode].
  	result := interpreterProxy stackValue: mac - 1.
  	interpreterProxy pop: mac + 1 thenPush: result!

Item was changed:
  ----- Method: NewCoObjectMemory>>startOfMemory (in category 'accessing') -----
  startOfMemory
  	"Return the start of object memory.  This is immediately after the native code zone.
  	 N.B. the stack zone is alloca'ed."
  	<api>
+ 	<returnTypeC: #usqInt>
  	^coInterpreter heapBase!

Item was changed:
  ----- Method: NewObjectMemory>>newObjectHash (in category 'allocation') -----
  newObjectHash
  	"Derive the new object hash from the allocation pointer.  This is less costly than
  	 using lastHash because it avoids the read-modify-write cycle to update lastHash.
  	 Since the size of eden is a power of two and larger than the hash range this provides
  	 a well-distributed and fairly random set of values."
  	<inline: true>
+ 	^freeStart >> ShiftForWord!
- 	^freeStart >> BytesPerWord!

Item was changed:
  ----- Method: NewspeakInterpreter>>highBit: (in category 'process primitive support') -----
  highBit: anUnsignedValue 
  	"This is a C implementation needed by ioSetMaxExtSemTableSize."
  	| shifted bitNo |
  	<api>
  	<var: #anUnsignedValue type: #usqInt>
  	<var: #shifted type: #usqInt>
  	shifted := anUnsignedValue.
  	bitNo := 0.
+ 	self cppIf: BytesPerWord > 4
- 	self cppIf: [BytesPerWord > 4]
  		ifTrue:
  			[shifted < (1 << 32) ifFalse:
  				[shifted := shifted >> 32.
  				 bitNo := bitNo + 32]].
  	shifted < (1 << 16) ifFalse:
  		[shifted := shifted >> 16.
  		 bitNo := bitNo + 16].
  	shifted < (1 << 8) ifFalse:
  		[shifted := shifted >> 8.
  		 bitNo := bitNo + 8].
  	shifted < (1 << 4) ifFalse:
  		[shifted := shifted >> 4.
  		 bitNo := bitNo + 4].
  	shifted < (1 << 2) ifFalse:
  		[shifted := shifted >> 2.
  		 bitNo := bitNo + 2].
  	shifted < (1 << 1) ifFalse:
  		[shifted := shifted >> 1.
  		 bitNo := bitNo + 1].
  	"shifted 0 or 1 now"
  	^bitNo + shifted!

Item was changed:
  ----- Method: ObjectMemory>>startOfMemory (in category 'object enumeration') -----
  startOfMemory
  	"Return the start of object memory."
+ 	<returnTypeC: #usqInt>
- 
  	^memory!

Item was changed:
  ----- Method: StackInterpreter>>convertFloatsToPlatformOrderFrom:to: (in category 'image save/restore') -----
  convertFloatsToPlatformOrderFrom: startOop to: stopAddr 
  	"Byte-swap the words of all bytes objects in a range of the 
  	 image, including Strings, ByteArrays, and CompiledMethods.
  	 This returns these objects to their original byte ordering 
  	 after blindly byte-swapping the entire image. For compiled 
  	 methods, byte-swap only their bytecodes part.
  	 Ensure floats are in platform-order."
  	| oop temp |
  	objectMemory vmEndianness = imageFloatsBigEndian ifTrue:
+ 		[^nil].
- 		[^self].
  	self assert: ClassFloatCompactIndex ~= 0.
  	oop := startOop.
  	[self oop: oop isLessThan: stopAddr] whileTrue:
  		[(objectMemory isFreeObject: oop) ifFalse:
  			[(objectMemory compactClassIndexOf: oop) = ClassFloatCompactIndex ifTrue:
  				[temp := self longAt: oop + BaseHeaderSize.
  				 self longAt: oop + BaseHeaderSize put: (self longAt: oop + BaseHeaderSize + 4).
  				 self longAt: oop + BaseHeaderSize + 4 put: temp]].
  		 oop := objectMemory objectAfter: oop]!

Item was changed:
  ----- Method: StackInterpreter>>highBit: (in category 'stack pages') -----
  highBit: anUnsignedValue 
  	"This is a C implementation needed by stackPageByteSize when translated."
  	| shifted bitNo |
  	<var: #anUnsignedValue type: #usqInt>
  	<var: #shifted type: #usqInt>
  	shifted := anUnsignedValue.
  	bitNo := 0.
+ 	self cppIf: BytesPerWord > 4
- 	self cppIf: [BytesPerWord > 4]
  		ifTrue:
  			[shifted < (1 << 32) ifFalse:
  				[shifted := shifted >> 32.
  				 bitNo := bitNo + 32]].
  	shifted < (1 << 16) ifFalse:
  		[shifted := shifted >> 16.
  		 bitNo := bitNo + 16].
  	shifted < (1 << 8) ifFalse:
  		[shifted := shifted >> 8.
  		 bitNo := bitNo + 8].
  	shifted < (1 << 4) ifFalse:
  		[shifted := shifted >> 4.
  		 bitNo := bitNo + 4].
  	shifted < (1 << 2) ifFalse:
  		[shifted := shifted >> 2.
  		 bitNo := bitNo + 2].
  	shifted < (1 << 1) ifFalse:
  		[shifted := shifted >> 1.
  		 bitNo := bitNo + 1].
  	"shifted 0 or 1 now"
  	^bitNo + shifted!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>availableRegisterOrNil (in category 'simulation stack') -----
  availableRegisterOrNil
+ 	<returnTypeC: #sqInt>
- 	<returnType: #sqInt>
  	| liveRegs |
  	liveRegs := self liveRegisters.
  	(liveRegs anyMask: (self registerMaskFor: Arg1Reg)) ifFalse:
  		[^Arg1Reg].
  	(liveRegs anyMask: (self registerMaskFor: Arg0Reg)) ifFalse:
  		[^Arg0Reg].
  	(liveRegs anyMask: (self registerMaskFor: SendNumArgsReg)) ifFalse:
  		[^SendNumArgsReg].
  	(liveRegs anyMask: (self registerMaskFor: ClassReg)) ifFalse:
  		[^ClassReg].
  	(liveRegs anyMask: (self registerMaskFor: ReceiverResultReg)) ifFalse:
  		[^ReceiverResultReg].
  	^nil!

Item was changed:
  ----- Method: TMethod>>exitVar:label: (in category 'inlining') -----
  exitVar: exitVar label: exitLabel
  	"Replace each return statement in this method with an assignment to the exit variable followed by a goto to the given label. Return true if a goto was generated."
  	"Optimization: If exitVar is nil, the return value of the inlined method is not being used, so don't add the assignment statement."
  
  	| labelUsed |
  	labelUsed := false.
  	parseTree nodesDo:
  		[:node | | newStmts |
  		node isStmtList ifTrue:
  			[newStmts := OrderedCollection new: 100.
  			node statements do:
  				[:stmt |
  				stmt isReturn
  					ifTrue:
  						[exitVar
  							ifNil:
+ 								[false "eem 8/8/2012 14:18 why exclude leaves explicity?  Makes no sense to me and breaks inlining of asimple accessors"
+ 									ifTrue:
+ 										[stmt expression isLeaf ifFalse: "evaluate return expression even though value isn't used"
+ 											[newStmts add: stmt expression]]
+ 									ifFalse: [newStmts add: stmt expression]]
- 								[stmt expression isLeaf ifFalse: "evaluate return expression even though value isn't used"
- 									[newStmts add: stmt expression]]
  							ifNotNil: "assign return expression to exit variable"
  								[newStmts add:
  									(TAssignmentNode new
  										setVariable: (TVariableNode new setName: exitVar)
  										expression: stmt expression)].
  						stmt ~~ parseTree statements last ifTrue: "generate a goto (this return is NOT the last statement in the method)"
  							[newStmts add: (TGoToNode new setLabel: exitLabel).
  							labelUsed := true]]
  					ifFalse: [newStmts addLast: stmt]].
  			node setStatements: newStmts asArray]].
  	^labelUsed!

Item was changed:
  ----- Method: TMethod>>inlineSend:directReturn:exitVar:in: (in category 'inlining') -----
  inlineSend: aSendNode directReturn: directReturn exitVar: exitVar in: aCodeGen
  	"Answer a collection of statements to replace the given send.  directReturn indicates
  	 that the send is the expression in a return statement, so returns can be left in the
  	 body of the inlined method. If exitVar is nil, the value returned by the send is not
  	 used; thus, returns need not assign to the output variable.
  
  	 Types are propagated to as-yet-untyped variables when inlining a send that is assigned,
  	 otherwise the assignee variable type must match the return type of the inlinee.  Return
  	 types are not propagated."
  
+ 	| sel meth exitLabel inlineStmts label exitType |
- 	| sel meth exitLabel labelUsed inlineStmts label exitType |
  	sel := aSendNode selector.
  	meth := aCodeGen methodNamed: sel.
  	meth args size = aSendNode args size ifFalse:
  		[^nil].
  	meth args with: aSendNode args do:
  		[:formal :actual|
  		(actual isVariable
  		and: [(aCodeGen
  				variableOfType: (self typeFor: formal)
  				acceptsValueOfType: (self typeFor: actual name in: aCodeGen)) not]) ifTrue:
  			[aCodeGen logger
  				nextPutAll:
  					'type mismatch for formal ', formal, ' and actual ', actual name,
  					' when inlining ', sel, ' in ', selector, '. Use a cast.';
  				cr; flush]]. 
  	meth := meth copy.
  
  	"Propagate the return type of an inlined method"
  	(directReturn or:[exitVar notNil]) ifTrue:[
  		exitType := directReturn 
  			ifTrue:[returnType] 
  			ifFalse:[(self typeFor: exitVar in: aCodeGen) ifNil:[#sqInt]].
  		(exitType = #void or:[exitType = meth returnType]) 
  			ifFalse:[meth propagateReturnIn: aCodeGen]].
  
  	meth renameVarsForInliningInto: self except: #() in: aCodeGen.
  	meth renameLabelsForInliningInto: self.
  	self addVarsDeclarationsAndLabelsOf: meth except: #().
  	meth hasReturn ifTrue:[
  		directReturn ifFalse:[
  			exitLabel := self unusedLabelForInliningInto: self.
+ 			(meth exitVar: exitVar label: exitLabel) "is label used?"
- 			(labelUsed := meth exitVar: exitVar label: exitLabel)
  				ifTrue: [ labels add: exitLabel ]
  				ifFalse: [ exitLabel := nil ]]].
  	(inlineStmts := OrderedCollection new: 100)
  		add: (label := TLabeledCommentNode new setComment: 'begin ', sel);
  		addAll: (self argAssignmentsFor: meth args: aSendNode args in: aCodeGen);
  		addAll: meth statements.  "method body"
  	"Vile hacks to prevent too many labels.  If the C compiler inlines functions it can duplicate
  	 labels and cause compilation to fail.  The second statement prevents us creating labels in
  	 anything other than the interpreter.  If we add labels to small functions that may be inlined
  	 by the C compiler then the label can be duplicated by the C compiler and cause the assembler
  	 to fail.  eem 9/20/2008 12:29"
  	(aCodeGen wantsLabels
  	 and: [meth asmLabel
  	 and: [meth mustAsmLabel or: [meth hasMoreSendsThan: 20]]]) ifTrue:
  		[label asmLabel: sel].
  	(directReturn
  	 and: [meth endsWithReturn not]) ifTrue:
  		[inlineStmts add:
  			(TReturnNode new setExpression: (TVariableNode new setName: 'nil'))].
  	exitLabel ~= nil ifTrue:
  		[inlineStmts add:
  			(TLabeledCommentNode new setLabel:
  				exitLabel comment: 'end ', meth selector)].
  	^inlineStmts!

Item was added:
+ ----- Method: VMStructType class>>isAbstract (in category 'accessing class hierarchy') -----
+ isAbstract
+ 	^self == VMStructType!



More information about the Vm-dev mailing list