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

commits at source.squeak.org commits at source.squeak.org
Tue Nov 30 22:35:44 UTC 2021


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

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

Name: VMMaker.oscog-eem.3114
Author: eem
Time: 30 November 2021, 2:35:32.159341 pm
UUID: 0522972d-531d-4f3a-9559-5c9bdbbf5427
Ancestors: VMMaker.oscog-eem.3113

Cogit: eliminate some C compiler warnings in the 64-bit cogits.

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

Item was changed:
  ----- Method: CCodeGenerator>>returnTypeForSend:in:ifNil: (in category 'type inference') -----
  returnTypeForSend: sendNode in: aTMethod ifNil: typeIfNil
  	"Answer the return type for a send.  Unbound sends default to typeIfNil.
  	 Methods with types as yet unknown have a type determined either by the
  	 kernelReturnTypes or the table below, or, if they are in neither set, then nil.
  	 The inferred type should match as closely as possible the C type of
  	 generated expessions so that inlining would not change the expression.
  	 If there is a method for sel but its return type is as yet unknown it mustn't
  	 be defaulted, since on a subsequent pass its type may be computable."
  	| sel methodOrNil |
  	methodOrNil := self anyMethodNamed: (sel := sendNode selector).
  	(methodOrNil notNil and: [methodOrNil returnType notNil]) ifTrue:
  		[^self baseTypeForType: methodOrNil returnType].
  	^kernelReturnTypes
  		at: sel
  		ifAbsent:
  			[sel
  				caseOf: {
  				[#integerValueOf:]		->	[#sqInt].
  				[#isIntegerObject:]		->	[#int].
  				[#negated]				->	[self promoteArithmeticTypes: (sendNode receiver typeFrom: self in: aTMethod) and: #int].
  				[#+]					->	[self typeForArithmetic: sendNode in: aTMethod].
  				[#-]					->	[self typeForArithmetic: sendNode in: aTMethod].
  				[#*]					->	[self typeForArithmetic: sendNode in: aTMethod].
  				[#/]						->	[self typeForArithmetic: sendNode in: aTMethod].
  				[#//]					->	[self typeForArithmetic: sendNode in: aTMethod].
  				[#\\]					->	[self typeForArithmetic: sendNode in: aTMethod].
  				[#rem:]				->	[self typeForArithmetic: sendNode in: aTMethod].
  				[#quo:]					->	[self typeForArithmetic: sendNode in: aTMethod].
  				"C99 Sec Bitwise shift operators ... 3 Semantics ...
  				 The integer promotions are performed on each of the operands. The type of the result is that of the promoted left operand..."
  				[#>>]					->	[sendNode receiver typeFrom: self in: aTMethod].
  				[#<<]					->	[(self isSignedIntegralCType: (sendNode receiver typeFrom: self in: aTMethod))
  												ifTrue: [#sqInt]
  												ifFalse: [#usqInt]].
  				[#addressOf:]			->	[(sendNode args first typeFrom: self in: aTMethod)
  												ifNil: [#sqInt]
  												ifNotNil: [:type| type, (type last isSeparator ifTrue: ['*'] ifFalse: [' *'])]].
  				[#addressOf:put:]		->	[(sendNode args first typeFrom: self in: aTMethod)
  												ifNil: [#sqInt]
  												ifNotNil: [:type| type, (type last isSeparator ifTrue: ['*'] ifFalse: [' *'])]].
  				[#at:]					->	[self typeForDereference: sendNode in: aTMethod].
  				[#bitAnd:]				->	[self typeForArithmetic: sendNode in: aTMethod].
  				[#bitOr:]				->	[self typeForArithmetic: sendNode in: aTMethod].
  				[#bitXor:]				->	[self typeForArithmetic: sendNode in: aTMethod].
  				[#bitClear:]				->	[self typeForArithmetic: sendNode in: aTMethod].
  				[#bitInvert32]			->	[#'unsigned int'].
  				[#bitInvert64]			->	[self promoteArithmeticTypes: (sendNode receiver typeFrom: self in: aTMethod) and: #int].
  				[#byteSwap32]			->	[#'unsigned int'].
  				[#byteSwap64]			->	[#'unsigned long long'].
  				[#byteSwapped32IfBigEndian:]	->	[#'unsigned int'].
  				[#byteSwapped64IfBigEndian:]	->	[#'unsigned long long'].
  				[#=]					->	[#int].
  				[#~=]					->	[#int].
  				[#==]					->	[#int].
  				[#~~]					->	[#int].
  				[#<]					->	[#int].
  				[#<=]					->	[#int].
  				[#>]					->	[#int].
  				[#>=]					->	[#int].
  				[#between:and:]		->	[#int].
  				[#anyMask:]				->	[#int].
  				[#allMask:]				->	[#int].
  				[#noMask:]				->	[#int].
  				[#isNil]					->	[#int].
  				[#notNil]				->	[#int].
  				[#&]					->	[#int].
  				[#|]						->	[#int].
  				[#not]					->	[#int].
  				[#asFloat]				->	[#double].
  				[#atan]					->	[#double].
  				[#exp]					->	[#double].
  				[#log]					->	[#double].
  				[#sin]					->	[#double].
  				[#sqrt]					->	[#double].
  				[#asLong]				->	[#long].
  				[#asInteger]			->	[#sqInt].
  				[#asIntegerPtr]			->	[#'sqIntptr_t'].
  				[#asUnsignedInteger]	->	[#usqInt].
  				[#asUnsignedIntegerPtr]->	[#'usqIntptr_t'].
  				[#asUnsignedLong]		->	[#'unsigned long'].
  				[#asUnsignedLongLong]		->	[#'unsigned long long'].
  				[#asVoidPointer]		->	[#'void *'].
+ 				[#signedIntFromLong]	->	[#int]. "c.f. generateSignedIntFromLong:on:indent:"
+ 				[#signedIntFromLong64]	->	[#sqInt]. "c.f. generateSignedIntFromLong64:on:indent: N.B. not written to answer sqLong because only used in 64-bit realm"
+ 				[#signedIntToLong]	->	[#usqInt]. "c.f. generateSignedIntToLong:on:indent:"
+ 				[#signedIntToLong64]	->	[#usqInt]. "c.f. generateSignedIntToLong64:on:indent:"
- 				[#signedIntToLong]		->	[#usqInt]. "c.f. generateSignedIntToLong:on:indent:"
  				[#signedIntToShort]	->	[#usqInt]. "c.f. generateSignedIntToShort:on:indent:"
  				[#cCoerce:to:]			->	[self conventionalTypeForType: sendNode args last value].
  				[#cCoerceSimple:to:]	->	[self conventionalTypeForType: sendNode args last value].
  				[#sizeof:]				->	[#'usqIntptr_t']. "Technically it's a size_t but it matches on target architectures so far..."
  				[#ifTrue:ifFalse:]		->	[self typeForConditional: sendNode in: aTMethod].
  				[#ifFalse:ifTrue:]		->	[self typeForConditional: sendNode in: aTMethod].
  				[#ifTrue:]				->	[self typeForConditional: sendNode in: aTMethod].
  				[#ifFalse:]				->	[self typeForConditional: sendNode in: aTMethod].
  				[#and:]					->	[#sqInt].
  				[#or:]					->	[#sqInt].
  				[#caseOf:]				->	[self typeFor: sendNode args first in: aTMethod] }
  				otherwise: "If there /is/ a method for sel but its return type is as yet unknown it /mustn't/ be defaulted,
  							since on a subsequent pass its type may be computable.  Only default unbound selectors."
  					[methodOrNil ifNotNil: [nil] ifNil: [typeIfNil]]]!

Item was changed:
  ----- Method: Cogit>>markLiteralsAndUnlinkIfUnmarkedSend:pc:method: (in category 'garbage collection') -----
  markLiteralsAndUnlinkIfUnmarkedSend: annotation pc: mcpc method: cogMethod
  	"Mark and trace literals.  Unlink sends that have unmarked cache tags or targets."
  	<var: #mcpc type: #'char *'>
+ 	<var: #cogMethod type: #'CogMethod *'>
- 	<var: #nsSendCache type: #'NSSendCache *'>
  	| literal |
+ 	<var: #nsSendCache type: #'NSSendCache *'>
  	annotation = IsObjectReference ifTrue:
  		[literal := literalsManager fetchLiteralAtAnnotatedAddress: mcpc asUnsignedInteger using: backEnd.
  		 (objectRepresentation
  				markAndTraceLiteral: literal
  				in: (self cCoerceSimple: cogMethod to: #'CogMethod *')
  				atpc: mcpc asUnsignedInteger) ifTrue:
  			[codeModified := true]].
  
  	NewspeakVM ifTrue:
  		[annotation = IsNSSendCall ifTrue:
  			[| nsSendCache entryPoint targetMethod sel eo |
  			nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			entryPoint := nsSendCache target.
  			entryPoint ~= 0 ifTrue: "Send is linked"
  				[targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
  				 (self markAndTraceOrFreeCogMethod: targetMethod
  					firstVisit: targetMethod asUnsignedInteger > mcpc asUnsignedInteger) ifTrue:	
  						[self voidNSSendCache: nsSendCache]].
  			sel := nsSendCache selector.
  			(objectMemory isForwarded: sel)
  				ifFalse: [objectMemory markAndTrace: sel]
  				ifTrue: [sel := objectMemory followForwarded: literal.
  						nsSendCache selector: sel.
  						self markAndTraceUpdatedLiteral: sel in: (self cCoerceSimple: cogMethod to: #'CogMethod *')].
  			eo := nsSendCache enclosingObject.
  			eo ~= 0 ifTrue:
  				[(objectMemory isForwarded: eo)
  					ifFalse: [objectMemory markAndTrace: eo]
  					ifTrue: [eo := objectMemory followForwarded: literal.
  							nsSendCache enclosingObject: eo.
  							self markAndTraceUpdatedLiteral: eo in: (self cCoerceSimple: cogMethod to: #'CogMethod *')]]]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[self entryCacheTagAndCouldBeObjectAt: mcpc annotation: annotation into:
  			[:entryPoint :cacheTag :tagCouldBeObj | | cacheTagMarked |
  			 cacheTagMarked := tagCouldBeObj and: [objectRepresentation cacheTagIsMarked: cacheTag].
  			 entryPoint > methodZoneBase
  				ifTrue: "It's a linked send."
  					[self targetMethodAndSendTableFor: entryPoint annotation: annotation into:
  						[:targetMethod :sendTable| 
  						 (cacheTagMarked not
  						  or: [self markAndTraceOrFreeCogMethod: targetMethod
  								firstVisit: targetMethod asUnsignedInteger > mcpc asUnsignedInteger]) ifTrue:
  							["Either the cacheTag is unmarked (e.g. new class) or the target
  							  has been freed (because it is unmarked), so unlink the send."
  							 self unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable.
  							 objectRepresentation
  								markAndTraceLiteral: targetMethod selector
  								in: targetMethod
  								at: (self addressOf: targetMethod selector put: [:val| targetMethod selector: val])]]]
  				ifFalse:  "cacheTag is selector"
  					[(objectRepresentation
  							markAndTraceCacheTagLiteral: cacheTag
  							in: (self cCoerceSimple: cogMethod to: #'CogMethod *')
  							atpc: mcpc asUnsignedInteger) ifTrue:
  						[codeModified := true]]]].
  
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>unlinkIfLinkedSend:pc:to: (in category 'in-line cacheing') -----
  unlinkIfLinkedSend: annotation pc: mcpc to: theCogMethod
  	<var: #mcpc type: #'char *'>
+ 	<var: #theCogMethod type: #'CogMethod *'>
- 	<var: #nsSendCache type: #'NSSendCache *'>
  	| entryPoint |
+ 	<var: #nsSendCache type: #'NSSendCache *'>
  
  	NewspeakVM ifTrue:
  		[| nsSendCache |
  		 annotation = IsNSSendCall ifTrue:
+ 			[nsSendCache := self nsSendCacheFromReturnAddress: mcpc.
- 			[nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			(entryPoint := nsSendCache target) ~= 0 ifTrue:
  				[ | targetMethod |
  				targetMethod := entryPoint - cmNoCheckEntryOffset.
+ 				targetMethod = theCogMethod asInteger ifTrue:
- 				targetMethod = theCogMethod ifTrue:
  					[self voidNSSendCache: nsSendCache]].
  			^0 "keep scanning"]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		 entryPoint > methodZoneBase
  			ifTrue: "It's a linked send."
  				[self targetMethodAndSendTableFor: entryPoint annotation: annotation into:
  					[:targetMethod :sendTable| 
+ 					 targetMethod = theCogMethod ifTrue:
- 					 targetMethod asInteger = theCogMethod ifTrue:
  						[self unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable]]]].
  
  	^0 "keep scanning"!



More information about the Vm-dev mailing list