[squeak-dev] The Trunk: Kernel-eem.1069.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Mar 23 18:11:12 UTC 2017


Eliot Miranda uploaded a new version of Kernel to project The Trunk:
http://source.squeak.org/trunk/Kernel-eem.1069.mcz

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

Name: Kernel-eem.1069
Author: eem
Time: 23 March 2017, 11:10:58.741571 am
UUID: f327f174-6584-4322-9adf-aabbb7b95f89
Ancestors: Kernel-eem.1068

Move most relevant accessing mehtods up from Compiledmethod to CompiledCode.  Still remaining is a comprehensive localLiterals/literals split.

Add the outerCode accessors to CompiledBlock and its (non-Opal-specific) senders.

Nuke hasNewPropertyFormat; this has been obsolete for ages.

=============== Diff against Kernel-eem.1068 ===============

Item was added:
+ ----- Method: CompiledBlock>>method (in category 'accessing') -----
+ method
+ 	"answer the compiled method that I am installed in, or nil if none."
+ 	^self outerCode method!

Item was added:
+ ----- Method: CompiledBlock>>methodClass (in category 'accessing') -----
+ methodClass
+ 	"answer the compiled method that I am installed in, or nil if none."
+ 	^self outerCode methodClass!

Item was added:
+ ----- Method: CompiledBlock>>methodNode (in category 'accessing') -----
+ methodNode
+ 	^ self outerCode methodNode!

Item was added:
+ ----- Method: CompiledBlock>>outerCode (in category 'accessing') -----
+ outerCode
+ 	"answer the compiled code that I am installed in, or nil if none."
+ 	^self literalAt: self numLiterals!

Item was added:
+ ----- Method: CompiledBlock>>outerCode: (in category 'accessing') -----
+ outerCode: aCompiledCode
+ 	^self literalAt: self numLiterals put: aCompiledCode!

Item was added:
+ ----- Method: CompiledBlock>>selector (in category 'accessing') -----
+ selector
+ 	^ self outerCode selector!

Item was added:
+ ----- Method: CompiledCode>>= (in category 'comparing') -----
+ = method
+ 	"Answer whether the receiver implements the same code as the argument, method.
+ 	 Here ``same code'' means that if the receiver's source is compiled with the same
+ 	 compiler it should produce the same sequence of bytecodes and literals, same
+ 	 trailer and same properties.  Hence this definition of #= (only one of many plausible
+ 	 definitions) can be used to quickly identify changes in the compiler's output."
+ 	| numLits |
+ 	method isCompiledMethod ifFalse: [^false].
+ 	self size = method size ifFalse: [^false].
+ 	self header = method header ifFalse: [^false]. "N.B. includes numLiterals comparison."
+ 	self initialPC to: self endPC do:
+ 		[:i | (self at: i) = (method at: i) ifFalse: [^false]].
+ 	numLits := self numLiterals.
+ 	1 to: numLits do:
+ 		[:i| | lit1 lit2 |
+ 		lit1 := self literalAt: i.
+ 		lit2 := method literalAt: i.
+ 		(lit1 == lit2 or: [lit1 literalEqual: lit2]) ifFalse:
+ 			[(i = 1 and: [#(117 120) includes: self primitive])
+ 				ifTrue:
+ 					[lit1 isArray
+ 						ifTrue:
+ 							[(lit2 isArray and: [(lit1 first: 2) = (lit2 first: 2)]) ifFalse:
+ 								[^false]]
+ 						ifFalse: "ExternalLibraryFunction"
+ 							[(lit1 analogousCodeTo: lit2) ifFalse:
+ 								[^false]]]
+ 				ifFalse:
+ 					[i = (numLits - 1)
+ 						ifTrue: "properties"
+ 							[(self properties analogousCodeTo: method properties)
+ 								ifFalse: [^false]]
+ 						ifFalse: "last literal (methodClassAssociation) of class-side methods is not unique"
+ 							[(i = numLits
+ 							 and: [lit1 isVariableBinding
+ 							 and: [lit2 isVariableBinding
+ 							 and: [lit1 key == lit2 key
+ 							 and: [lit1 value == lit2 value]]]]) ifFalse:
+ 								[^false]]]]].
+ 	^true!

Item was added:
+ ----- Method: CompiledCode>>asString (in category 'converting') -----
+ asString
+ 
+ 	^self printString!

Item was added:
+ ----- Method: CompiledCode>>at:ifAbsent: (in category 'accessing') -----
+ at: index ifAbsent: exceptionBlock 
+ 	"Answer the element at my position index. If I do not contain an element 
+ 	at index, answer the result of evaluating the argument, exceptionBlock."
+ 
+ 	(index <= self size  and: [self initialPC <= index]) ifTrue: [^self at: index].
+ 	^exceptionBlock value!

Item was added:
+ ----- Method: CompiledCode>>bytecodeSetName (in category 'accessing') -----
+ bytecodeSetName
+ 	^self encoderClass name copyReplaceAll: 'EncoderFor' with: ''!

Item was added:
+ ----- Method: CompiledCode>>clearFlag (in category 'accessing') -----
+ clearFlag
+ 	"Clear the user-level flag bit"
+ 
+ 	self objectAt: 1 put: (self header bitAnd: (1 << 29) bitInvert)!

Item was added:
+ ----- Method: CompiledCode>>clearSignFlag (in category 'accessing') -----
+ clearSignFlag
+ 	"Clear the sign flag bit.  The sign flag bit may be
+ 	 used by the VM to select an alternate bytecode set."
+ 
+ 	self signFlag ifTrue:
+ 		[self objectAt: 1 put: self header - SmallInteger minVal]!

Item was added:
+ ----- Method: CompiledCode>>copyFrom: (in category 'copying') -----
+ copyFrom: anotherObject
+ 	"Copy to myself all instance variables I have in common with anotherObject.
+ 	 This is dangerous because it ignores an object's control over its own inst vars."
+ 
+ 	<primitive: 168>
+ 	anotherObject isCompiledCode
+ 		ifTrue:
+ 			[1 to: self numLiterals do:
+ 				[:i| self literalAt: i put: (anotherObject literalAt: i)]]
+ 		ifFalse:
+ 			[1 to: self numLiterals do:
+ 				[:i| self literalAt: i put: (anotherObject at: i)]].
+ 	self initialPC to: (self basicSize min: anotherObject basicSize) do:
+ 		[:i|
+ 		 self basicAt: i put: (anotherObject basicAt: i)]!

Item was added:
+ ----- Method: CompiledCode>>copyWithTrailerBytes: (in category 'copying') -----
+ copyWithTrailerBytes: trailer
+ "Testing:
+ 	(CompiledMethod compiledMethodAt: #copyWithTrailerBytes:)
+ 		tempNamesPut: 'copy end '
+ "
+ 	| copy end start |
+ 	start := self initialPC.
+ 	end := self endPC.
+ 	copy := trailer createMethod: end - start + 1 class: self class header: self header.
+ 	1 to: self numLiterals do: [:i | copy literalAt: i put: (self literalAt: i)].
+ 	start to: end do: [:i | copy at: i put: (self at: i)].
+ 	copy postCopy.
+ 	^copy!

Item was added:
+ ----- Method: CompiledCode>>encoderClass (in category 'accessing') -----
+ encoderClass
+ 	"Answer the encoder class that encoded the bytecodes in this method.
+ 	 The sign flag bit is used by the VM to select a bytecode set.  This formulation
+ 	 may seem odd but this has to be fast, so no property probe unless needed."
+ 
+ 	^self header >= 0
+ 		ifTrue: 
+ 			[PrimaryBytecodeSetEncoderClass]
+ 		ifFalse:
+ 			[PrimaryBytecodeSetEncoderClass == SecondaryBytecodeSetEncoderClass
+ 				ifTrue: "Support for testing prior to installing another set"
+ 					[(self propertyValueAt: #encoderClass) ifNil: [SecondaryBytecodeSetEncoderClass]]
+ 				ifFalse:
+ 					[SecondaryBytecodeSetEncoderClass]]!

Item was added:
+ ----- Method: CompiledCode>>endPC (in category 'accessing') -----
+ endPC
+ 	"Answer the index of the last bytecode."
+ 	^ self trailer endPC
+ !

Item was added:
+ ----- Method: CompiledCode>>flag (in category 'accessing') -----
+ flag
+ 	"Answer the user-level flag bit"
+ 
+ 	^((self header bitShift: -29) bitAnd: 1) = 1!

Item was added:
+ ----- Method: CompiledCode>>flushCache (in category 'cleaning') -----
+ flushCache
+ 	"Tell the virtual machine to remove all references to this method from its method
+ 	 lookup cache(s), if it has them. This is provided for backwards compatibility.
+ 	 When a method is redefined (added to, removed from, or replaced in, a method
+ 	 dictionary) then Symbol flushCache should be used. This is because adding or
+ 	 removing a method may alter the method that a given selector should invoke
+ 	 for methods other than the receiver.  For example, if a subclass inherits a
+ 	 method and this is overridden, flushing the new method will not flush the existing
+ 	 method.
+ 
+ 	 If a method is modified in-place (for example, some bytecode is replaced by
+ 	 bytecode that effects a breakpoint) then voidCogVMState should be used."
+ 
+ 	<primitive: 116>!

Item was added:
+ ----- Method: CompiledCode>>frameSize (in category 'accessing') -----
+ frameSize
+ 	"Answer the size of temporary frame needed to run the receiver."
+ 	"NOTE:  Versions 2.7 and later use two sizes of contexts."
+ 
+ 	(self header noMask: 16r20000)
+ 		ifTrue: [^ SmallFrame]
+ 		ifFalse: [^ LargeFrame]
+ !

Item was added:
+ ----- Method: CompiledCode>>hash (in category 'comparing') -----
+ hash
+ 	"CompiledMethod>>#= compares code, i.e. same literals and same bytecode.
+ 	 So we look at the header, methodClass and some bytes between initialPC and endPC,
+ 	 but /not/ the selector because the equal method does not compare selectors.
+ 	 Note that we must override ByteArray>hash which looks at all bytes of the receiver.
+ 	 Using bytes from the pointer part of a COmpiledmethod can lead to a variable hash
+ 	 if and when when the GC moves literals in the receiver."
+ 	| initialPC endPC hash |
+ 	initialPC := self initialPC.
+ 	endPC := self endPC.
+ 	hash := self species hash + self header + initialPC + endPC + self methodClass hash bitAnd: 16rFFFFFFF.
+ 	"sample approximately 20 bytes"
+ 	initialPC to: endPC by: (endPC - initialPC // 20 max: 1) do:
+ 		[:i| hash := hash + (self at: i)].
+ 	^hash
+ 
+ 	"(CompiledMethod>>#hash) hash"!

Item was added:
+ ----- Method: CompiledCode>>header (in category 'literals') -----
+ header
+ 	"Answer the word containing the information about the form of the 
+ 	 receiver and the form of the context needed to run the receiver.
+ 
+ 		sign:1 29-28:accessModifier 27-24:numArgs 23-18:numTemps 17:largeFrameFlag 16:hasPrimitive 15:isOptimized 14-0:numLits"
+ 
+ 	^self objectAt: 1!

Item was added:
+ ----- Method: CompiledCode>>initialPC (in category 'accessing') -----
+ initialPC
+ 	"Answer the program counter for the receiver's first bytecode."
+ 
+ 	^ (self numLiterals + 1) * Smalltalk wordSize + 1
+ !

Item was added:
+ ----- Method: CompiledCode>>literalAt: (in category 'literals') -----
+ literalAt: index 
+ 	"Answer the literal indexed by the argument."
+ 
+ 	^self objectAt: index + 1!

Item was added:
+ ----- Method: CompiledCode>>literalAt:put: (in category 'literals') -----
+ literalAt: index put: value 
+ 	"Replace the literal indexed by the first argument with the second 
+ 	argument. Answer the second argument."
+ 
+ 	^self objectAt: index + 1 put: value!

Item was added:
+ ----- Method: CompiledCode>>methodClass (in category 'accessing') -----
+ methodClass
+ 	^self subclassResponsibility!

Item was added:
+ ----- Method: CompiledCode>>needsFrameSize: (in category 'initialize-release') -----
+ needsFrameSize: newFrameSize
+ 	"Set the largeFrameBit to accomodate the newFrameSize"
+ 	| largeFrameBit header |
+ 	largeFrameBit := 16r20000.
+ 	(self numTemps + newFrameSize) > LargeFrame ifTrue:
+ 		[^ self error: 'Cannot compile -- stack including temps is too deep'].
+ 	header := self objectAt: 1.
+ 	(header bitAnd: largeFrameBit) ~= 0
+ 		ifTrue: [header := header - largeFrameBit].
+ 	self objectAt: 1 put: header
+ 			+ ( ((self numTemps + newFrameSize) > SmallFrame or: [ self primitive = 84 "perform:withArguments:"])
+ 					ifTrue: [largeFrameBit]
+ 					ifFalse: [0])!

Item was added:
+ ----- Method: CompiledCode>>numArgs (in category 'accessing') -----
+ numArgs
+ 	"Answer the number of arguments the receiver takes."
+ 
+ 	^ (self header bitShift: -24) bitAnd: 16r0F!

Item was added:
+ ----- Method: CompiledCode>>numLiterals (in category 'accessing') -----
+ numLiterals
+ 	"Answer the number of literals used by the receiver."
+ 	^self header bitAnd: 16r7FFF!

Item was added:
+ ----- Method: CompiledCode>>numTemps (in category 'accessing') -----
+ numTemps
+ 	"Answer the number of temporary variables used by the receiver."
+ 	
+ 	^ (self header bitShift: -18) bitAnd: 16r3F!

Item was added:
+ ----- Method: CompiledCode>>objectAt: (in category 'literals') -----
+ objectAt: index 
+ 	"Primitive. Answer the method header (if index=1) or a literal (if index 
+ 	>1) from the receiver. Essential. See Object documentation 
+ 	whatIsAPrimitive."
+ 
+ 	<primitive: 68>
+ 	self primitiveFailed!

Item was added:
+ ----- Method: CompiledCode>>objectAt:put: (in category 'literals') -----
+ objectAt: index put: value 
+ 	"Primitive. Store the value argument into a literal in the receiver. An 
+ 	index of 2 corresponds to the first literal. Fails if the index is less than 2 
+ 	or greater than the number of literals. Answer the value as the result. 
+ 	Normally only the compiler sends this message, because only the 
+ 	compiler stores values in CompiledMethods. Essential. See Object 
+ 	documentation whatIsAPrimitive."
+ 
+ 	<primitive: 69>
+ 	self primitiveFailed!

Item was added:
+ ----- Method: CompiledCode>>outboundPointersDo: (in category 'tracing') -----
+ outboundPointersDo: aBlock
+ 
+ 	| numLiterals |
+ 	aBlock value: self class.
+ 	numLiterals := self numLiterals.
+ 	1 to: numLiterals do: [:i | aBlock value: (self literalAt: i)]!

Item was added:
+ ----- Method: CompiledCode>>printOn: (in category 'printing') -----
+ printOn: aStream 
+ 	"Overrides method inherited from the byte arrayed collection."
+ 	aStream nextPut: $(.
+ 	self printReferenceOn: aStream.
+ 	aStream space; nextPut: $".
+ 	self printNameOn: aStream.
+ 	aStream nextPut: $(;
+ 		 print: self identityHash;
+ 		 nextPut: $);
+ 		 nextPut: $";
+ 		 nextPut: $)!

Item was added:
+ ----- Method: CompiledCode>>protocol (in category 'accessing') -----
+ protocol
+ 	^self methodClass ifNotNil:
+ 		[:class|
+ 		self selector ifNotNil:
+ 			[:selector|
+ 			class whichCategoryIncludesSelector: selector]]!

Item was added:
+ ----- Method: CompiledCode>>readDataFrom:size: (in category 'file in/out') -----
+ readDataFrom: aDataStream size: varsOnDisk
+ 	"Fill in my fields.  My header and number of literals are already installed.  Must read both objects for the literals and bytes for the bytecodes."
+ 
+ 	self error: 'Must use readMethod'.!

Item was added:
+ ----- Method: CompiledCode>>reference (in category 'printing') -----
+ reference
+ 	^ String streamContents: [ : stream | self printReferenceOn: stream ]!

Item was added:
+ ----- Method: CompiledCode>>referredInstVars (in category 'accessing') -----
+ referredInstVars
+ 	"Answer a Set of the inst var names the receiver accesses."
+ 	| allInstVarNames instVarNames |
+ 	allInstVarNames := self methodClass allInstVarNames.
+ 	self isReturnField ifTrue:
+ 		[^Set with: (allInstVarNames at: self returnField + 1)].
+ 	instVarNames := Set new.
+ 	self abstractBytecodeMessagesDo:
+ 		[:msg|
+ 		(#(#popIntoReceiverVariable:
+ 		    #pushReceiverVariable:
+ 		    #storeIntoReceiverVariable:) includes: msg selector) ifTrue:
+ 			[instVarNames add: (allInstVarNames at: msg argument + 1)]].
+ 	^instVarNames
+ 
+ 	"Dictionary newFromPairs: (Point selectors collect: [:s| { s. (Point >> s) referredInstVars}])"!

Item was added:
+ ----- Method: CompiledCode>>scanner (in category 'accessing') -----
+ scanner
+ 
+ 	^ InstructionStream on: self!

Item was added:
+ ----- Method: CompiledCode>>setSignFlag (in category 'accessing') -----
+ setSignFlag
+ 	"Set the sign flag bit.  The sign flag bit may be
+ 	 used by the VM to select an alternate bytecode set."
+ 
+ 	self signFlag ifFalse:
+ 		[self objectAt: 1 put: self header + SmallInteger minVal]!

Item was added:
+ ----- Method: CompiledCode>>signFlag (in category 'accessing') -----
+ signFlag
+ 	"Answer the sign flag bit.  The sign flag bit may be
+ 	 used by the VM to select an alternate bytecode set."
+ 
+ 	^self header < 0!

Item was added:
+ ----- Method: CompiledCode>>storeDataOn: (in category 'file in/out') -----
+ storeDataOn: aDataStream
+ 	"Store myself on a DataStream.  I am a mixture of objects and raw data bytes.  Only use this for blocks.  Normal methodDictionaries should not be put out using ReferenceStreams.  Their fileOut should be attached to the beginning of the file."
+ 
+ 	| byteLength lits |
+ 	"No inst vars of the normal type"
+ 	byteLength := self basicSize.
+ 	aDataStream
+ 		beginInstance: self class
+ 		size: byteLength.
+ 	lits := self numLiterals + 1.	"counting header"
+ 	1 to: lits do:
+ 		[:ii | aDataStream nextPut: (self objectAt: ii)].
+ 	lits*4+1 to: byteLength do:
+ 		[:ii | aDataStream byteStream nextPut: (self basicAt: ii)].
+ 			"write bytes straight through to the file"!

Item was added:
+ ----- Method: CompiledCode>>storeOn: (in category 'printing') -----
+ storeOn: aStream
+ 	| noneYet |
+ 	aStream nextPutAll: '(('.
+ 	aStream nextPutAll: self class name.
+ 	aStream nextPutAll: ' newMethod: '.
+ 	aStream store: self size - self initialPC + 1.
+ 	aStream nextPutAll: ' header: '.
+ 	aStream store: self header.
+ 	aStream nextPut: $).
+ 	noneYet := self storeElementsFrom: self initialPC to: self endPC on: aStream.
+ 	1 to: self numLiterals do:
+ 		[:index |
+ 		noneYet
+ 			ifTrue: [noneYet := false]
+ 			ifFalse: [aStream nextPut: $;].
+ 		aStream nextPutAll: ' literalAt: '.
+ 		aStream store: index.
+ 		aStream nextPutAll: ' put: '.
+ 		aStream store: (self literalAt: index)].
+ 	noneYet ifFalse: [aStream nextPutAll: '; yourself'].
+ 	aStream nextPut: $)!

Item was added:
+ ----- Method: CompiledCode>>trailer (in category 'accessing') -----
+ trailer
+ 	"Answer the receiver's trailer"
+ 	^ CompiledMethodTrailer new method: self
+ !

Item was added:
+ ----- Method: CompiledCode>>veryDeepCopyWith: (in category 'file in/out') -----
+ veryDeepCopyWith: deepCopier
+ 	"Return self.  I am always shared.  Do not record me.  Only use this for blocks.  Normally methodDictionaries should not be copied this way."!

Item was added:
+ ----- Method: CompiledCode>>voidCogVMState (in category 'cleaning') -----
+ voidCogVMState
+ 	"Tell the VM to remove all references to any machine code form of the method.
+ 	 This primitive must be called whenever a method is in use and modified.  This is
+ 	 more aggressive (and *much* more costly) than flushCache since it must search
+ 	 through all context objects, making sure that none have a (hidden) machine code pc
+ 	 in the receiver.  Since modifying a method will likely change the generated machine code,
+ 	 modifying a method (rather than redefining it) requires this more aggressive flush."
+ 
+ 	<primitive: 215>
+ 	^self flushCache!

Item was removed:
- ----- Method: CompiledMethod>>= (in category 'comparing') -----
- = method
- 	"Answer whether the receiver implements the same code as the argument, method.
- 	 Here ``same code'' means that if the receiver's source is compiled with the same
- 	 compiler it should produce the same sequence of bytecodes and literals, same
- 	 trailer and same properties.  Hence this definition of #= (only one of many plausible
- 	 definitions) can be used to quickly identify changes in the compiler's output."
- 	| numLits |
- 	method isCompiledMethod ifFalse: [^false].
- 	self size = method size ifFalse: [^false].
- 	self header = method header ifFalse: [^false]. "N.B. includes numLiterals comparison."
- 	self initialPC to: self endPC do:
- 		[:i | (self at: i) = (method at: i) ifFalse: [^false]].
- 	numLits := self numLiterals.
- 	1 to: numLits do:
- 		[:i| | lit1 lit2 |
- 		lit1 := self literalAt: i.
- 		lit2 := method literalAt: i.
- 		(lit1 == lit2 or: [lit1 literalEqual: lit2]) ifFalse:
- 			[(i = 1 and: [#(117 120) includes: self primitive])
- 				ifTrue:
- 					[lit1 isArray
- 						ifTrue:
- 							[(lit2 isArray and: [(lit1 first: 2) = (lit2 first: 2)]) ifFalse:
- 								[^false]]
- 						ifFalse: "ExternalLibraryFunction"
- 							[(lit1 analogousCodeTo: lit2) ifFalse:
- 								[^false]]]
- 				ifFalse:
- 					[i = (numLits - 1)
- 						ifTrue: "properties"
- 							[(self properties analogousCodeTo: method properties)
- 								ifFalse: [^false]]
- 						ifFalse: "last literal (methodClassAssociation) of class-side methods is not unique"
- 							[(i = numLits
- 							 and: [lit1 isVariableBinding
- 							 and: [lit2 isVariableBinding
- 							 and: [lit1 key == lit2 key
- 							 and: [lit1 value == lit2 value]]]]) ifFalse:
- 								[^false]]]]].
- 	^true!

Item was removed:
- ----- Method: CompiledMethod>>asString (in category 'converting') -----
- asString
- 
- 	^self printString!

Item was removed:
- ----- Method: CompiledMethod>>at:ifAbsent: (in category 'accessing') -----
- at: index ifAbsent: exceptionBlock 
- 	"Answer the element at my position index. If I do not contain an element 
- 	at index, answer the result of evaluating the argument, exceptionBlock."
- 
- 	(index <= self size  and: [self initialPC <= index]) ifTrue: [^self at: index].
- 	^exceptionBlock value!

Item was removed:
- ----- Method: CompiledMethod>>bytecodeSetName (in category 'accessing') -----
- bytecodeSetName
- 	^self encoderClass name copyReplaceAll: 'EncoderFor' with: ''!

Item was removed:
- ----- Method: CompiledMethod>>clearFlag (in category 'accessing') -----
- clearFlag
- 	"Clear the user-level flag bit"
- 
- 	self objectAt: 1 put: (self header bitAnd: (1 << 29) bitInvert)!

Item was removed:
- ----- Method: CompiledMethod>>clearSignFlag (in category 'accessing') -----
- clearSignFlag
- 	"Clear the sign flag bit.  The sign flag bit may be
- 	 used by the VM to select an alternate bytecode set."
- 
- 	self signFlag ifTrue:
- 		[self objectAt: 1 put: self header - SmallInteger minVal]!

Item was removed:
- ----- Method: CompiledMethod>>copyFrom: (in category 'copying') -----
- copyFrom: anotherObject
- 	"Copy to myself all instance variables I have in common with anotherObject.
- 	 This is dangerous because it ignores an object's control over its own inst vars."
- 
- 	<primitive: 168>
- 	anotherObject isCompiledMethod
- 		ifTrue:
- 			[1 to: self numLiterals do:
- 				[:i| self literalAt: i put: (anotherObject literalAt: i)]]
- 		ifFalse:
- 			[1 to: self numLiterals do:
- 				[:i| self literalAt: i put: (anotherObject at: i)]].
- 	self initialPC to: (self basicSize min: anotherObject basicSize) do:
- 		[:i|
- 		 self basicAt: i put: (anotherObject basicAt: i)]!

Item was removed:
- ----- Method: CompiledMethod>>copyWithTrailerBytes: (in category 'copying') -----
- copyWithTrailerBytes: trailer
- "Testing:
- 	(CompiledMethod compiledMethodAt: #copyWithTrailerBytes:)
- 		tempNamesPut: 'copy end '
- "
- 	| copy end start |
- 	start := self initialPC.
- 	end := self endPC.
- 	copy := trailer createMethod: end - start + 1 class: self class header: self header.
- 	1 to: self numLiterals do: [:i | copy literalAt: i put: (self literalAt: i)].
- 	start to: end do: [:i | copy at: i put: (self at: i)].
- 	copy postCopy.
- 	^copy!

Item was removed:
- ----- Method: CompiledMethod>>encoderClass (in category 'accessing') -----
- encoderClass
- 	"Answer the encoder class that encoded the bytecodes in this method.
- 	 The sign flag bit is used by the VM to select a bytecode set.  This formulation
- 	 may seem odd but this has to be fast, so no property probe unless needed."
- 
- 	^self header >= 0
- 		ifTrue: 
- 			[PrimaryBytecodeSetEncoderClass]
- 		ifFalse:
- 			[PrimaryBytecodeSetEncoderClass == SecondaryBytecodeSetEncoderClass
- 				ifTrue: "Support for testing prior to installing another set"
- 					[(self propertyValueAt: #encoderClass) ifNil: [SecondaryBytecodeSetEncoderClass]]
- 				ifFalse:
- 					[SecondaryBytecodeSetEncoderClass]]!

Item was removed:
- ----- Method: CompiledMethod>>endPC (in category 'accessing') -----
- endPC
- 	"Answer the index of the last bytecode."
- 	^ self trailer endPC
- !

Item was removed:
- ----- Method: CompiledMethod>>flag (in category 'accessing') -----
- flag
- 	"Answer the user-level flag bit"
- 
- 	^((self header bitShift: -29) bitAnd: 1) = 1!

Item was removed:
- ----- Method: CompiledMethod>>flushCache (in category 'accessing') -----
- flushCache
- 	"Tell the interpreter to remove all references to this method from its method lookup cache, if it has one.  This primitive must be called whenever a method is defined or removed.
- 	NOTE:  Only one of two selective flush methods needs to be used.
- 	Squeak 2.2 and earlier uses 119 (See Symbol flushCache).
- 	Squeak 2.3 and later uses 116 (See CompiledMethod flushCache)."
- 
- 	<primitive: 116>
- !

Item was removed:
- ----- Method: CompiledMethod>>frameSize (in category 'accessing') -----
- frameSize
- 	"Answer the size of temporary frame needed to run the receiver."
- 	"NOTE:  Versions 2.7 and later use two sizes of contexts."
- 
- 	(self header noMask: 16r20000)
- 		ifTrue: [^ SmallFrame]
- 		ifFalse: [^ LargeFrame]
- !

Item was removed:
- ----- Method: CompiledMethod>>hasNewPropertyFormat (in category 'testing') -----
- hasNewPropertyFormat
- 	"As of the closure compiler all methods have (or better have) the new
- 	 format where the penultimate literal is either the method's selector
- 	 or its properties and the ultimate literal is the class association."
- 	^true!

Item was removed:
- ----- Method: CompiledMethod>>hash (in category 'comparing') -----
- hash
- 	"CompiledMethod>>#= compares code, i.e. same literals and same bytecode.
- 	 So we look at the header, methodClass and some bytes between initialPC and endPC,
- 	 but /not/ the selector because the equal method does not compare selectors.
- 	 Note that we must override ByteArray>hash which looks at all bytes of the receiver.
- 	 Using bytes from the pointer part of a COmpiledmethod can lead to a variable hash
- 	 if and when when the GC moves literals in the receiver."
- 	| initialPC endPC hash |
- 	initialPC := self initialPC.
- 	endPC := self endPC.
- 	hash := self species hash + self header + initialPC + endPC + self methodClass hash bitAnd: 16rFFFFFFF.
- 	"sample approximately 20 bytes"
- 	initialPC to: endPC by: (endPC - initialPC // 20 max: 1) do:
- 		[:i| hash := hash + (self at: i)].
- 	^hash
- 
- 	"(CompiledMethod>>#hash) hash"!

Item was removed:
- ----- Method: CompiledMethod>>header (in category 'literals') -----
- header
- 	"Answer the word containing the information about the form of the 
- 	 receiver and the form of the context needed to run the receiver.
- 	 There are two different formats, selected by the sign bit.  These are
- 
- 	 Original Squeak V3:
- 		30:sign:0 29:flag 28:prim (high bit) 27-24:numArgs 23-18:numTemps 17:largeFrameFlag 16-9:numLits 8-0:prim (low 9 bits)
- 
- 	 Alternate Bytecode Set
- 		30:sign:1 29-28:accessModifier 27-24:numArgs 23-18:numTemps 17:largeFrameFlag 16:hasPrimitive 15-0:numLits
- 
- 	 i.e. the Alternate Bytecode Set expands the number of literals to 65535 by assuming a CallPrimitive bytecode."
- 
- 	^self objectAt: 1!

Item was removed:
- ----- Method: CompiledMethod>>initialPC (in category 'accessing') -----
- initialPC
- 	"Answer the program counter for the receiver's first bytecode."
- 
- 	^ (self numLiterals + 1) * Smalltalk wordSize + 1
- !

Item was removed:
- ----- Method: CompiledMethod>>literalAt: (in category 'literals') -----
- literalAt: index 
- 	"Answer the literal indexed by the argument."
- 
- 	^self objectAt: index + 1!

Item was removed:
- ----- Method: CompiledMethod>>literalAt:put: (in category 'literals') -----
- literalAt: index put: value 
- 	"Replace the literal indexed by the first argument with the second 
- 	argument. Answer the second argument."
- 
- 	^self objectAt: index + 1 put: value!

Item was removed:
- ----- Method: CompiledMethod>>needsFrameSize: (in category 'initialize-release') -----
- needsFrameSize: newFrameSize
- 	"Set the largeFrameBit to accomodate the newFrameSize"
- 	| largeFrameBit header |
- 	largeFrameBit := 16r20000.
- 	(self numTemps + newFrameSize) > LargeFrame ifTrue:
- 		[^ self error: 'Cannot compile -- stack including temps is too deep'].
- 	header := self objectAt: 1.
- 	(header bitAnd: largeFrameBit) ~= 0
- 		ifTrue: [header := header - largeFrameBit].
- 	self objectAt: 1 put: header
- 			+ ( ((self numTemps + newFrameSize) > SmallFrame or: [ self primitive = 84 "perform:withArguments:"])
- 					ifTrue: [largeFrameBit]
- 					ifFalse: [0])!

Item was removed:
- ----- Method: CompiledMethod>>numArgs (in category 'accessing') -----
- numArgs
- 	"Answer the number of arguments the receiver takes."
- 
- 	^ (self header bitShift: -24) bitAnd: 16r0F!

Item was removed:
- ----- Method: CompiledMethod>>numLiterals (in category 'accessing') -----
- numLiterals
- 	"Answer the number of literals used by the receiver."
- 	^self header bitAnd: 16r7FFF!

Item was removed:
- ----- Method: CompiledMethod>>numTemps (in category 'accessing') -----
- numTemps
- 	"Answer the number of temporary variables used by the receiver."
- 	
- 	^ (self header bitShift: -18) bitAnd: 16r3F!

Item was removed:
- ----- Method: CompiledMethod>>objectAt: (in category 'literals') -----
- objectAt: index 
- 	"Primitive. Answer the method header (if index=1) or a literal (if index 
- 	>1) from the receiver. Essential. See Object documentation 
- 	whatIsAPrimitive."
- 
- 	<primitive: 68>
- 	self primitiveFailed!

Item was removed:
- ----- Method: CompiledMethod>>objectAt:put: (in category 'literals') -----
- objectAt: index put: value 
- 	"Primitive. Store the value argument into a literal in the receiver. An 
- 	index of 2 corresponds to the first literal. Fails if the index is less than 2 
- 	or greater than the number of literals. Answer the value as the result. 
- 	Normally only the compiler sends this message, because only the 
- 	compiler stores values in CompiledMethods. Essential. See Object 
- 	documentation whatIsAPrimitive."
- 
- 	<primitive: 69>
- 	self primitiveFailed!

Item was removed:
- ----- Method: CompiledMethod>>outboundPointersDo: (in category 'tracing') -----
- outboundPointersDo: aBlock
- 
- 	| numLiterals |
- 	aBlock value: self class.
- 	numLiterals := self numLiterals.
- 	1 to: numLiterals do: [:i | aBlock value: (self literalAt: i)]!

Item was removed:
- ----- Method: CompiledMethod>>printOn: (in category 'printing') -----
- printOn: aStream 
- 	"Overrides method inherited from the byte arrayed collection."
- 	aStream nextPut: $(.
- 	self printReferenceOn: aStream.
- 	aStream space; nextPut: $".
- 	self printNameOn: aStream.
- 	aStream nextPut: $(;
- 		 print: self identityHash;
- 		 nextPut: $);
- 		 nextPut: $";
- 		 nextPut: $)!

Item was removed:
- ----- Method: CompiledMethod>>protocol (in category 'accessing') -----
- protocol
- 	^self methodClass ifNotNil:
- 		[:class|
- 		self selector ifNotNil:
- 			[:selector|
- 			class whichCategoryIncludesSelector: selector]]!

Item was removed:
- ----- Method: CompiledMethod>>readDataFrom:size: (in category 'file in/out') -----
- readDataFrom: aDataStream size: varsOnDisk
- 	"Fill in my fields.  My header and number of literals are already installed.  Must read both objects for the literals and bytes for the bytecodes."
- 
- 	self error: 'Must use readMethod'.!

Item was removed:
- ----- Method: CompiledMethod>>reference (in category 'printing') -----
- reference
- 	^ String streamContents: [ : stream | self printReferenceOn: stream ]!

Item was removed:
- ----- Method: CompiledMethod>>referredInstVars (in category 'accessing') -----
- referredInstVars
- 	"Answer a Set of the inst var names the receiver accesses."
- 	| allInstVarNames instVarNames |
- 	allInstVarNames := self methodClass allInstVarNames.
- 	self isReturnField ifTrue:
- 		[^Set with: (allInstVarNames at: self returnField + 1)].
- 	instVarNames := Set new.
- 	self abstractBytecodeMessagesDo:
- 		[:msg|
- 		(#(#popIntoReceiverVariable:
- 		    #pushReceiverVariable:
- 		    #storeIntoReceiverVariable:) includes: msg selector) ifTrue:
- 			[instVarNames add: (allInstVarNames at: msg argument + 1)]].
- 	^instVarNames
- 
- 	"Dictionary newFromPairs: (Point selectors collect: [:s| { s. (Point >> s) referredInstVars}])"!

Item was removed:
- ----- Method: CompiledMethod>>scanner (in category 'accessing') -----
- scanner
- 
- 	^ InstructionStream on: self!

Item was removed:
- ----- Method: CompiledMethod>>setSignFlag (in category 'accessing') -----
- setSignFlag
- 	"Set the sign flag bit.  The sign flag bit may be
- 	 used by the VM to select an alternate bytecode set."
- 
- 	self signFlag ifFalse:
- 		[self objectAt: 1 put: self header + SmallInteger minVal]!

Item was removed:
- ----- Method: CompiledMethod>>signFlag (in category 'accessing') -----
- signFlag
- 	"Answer the sign flag bit.  The sign flag bit may be
- 	 used by the VM to select an alternate bytecode set."
- 
- 	^self header < 0!

Item was removed:
- ----- Method: CompiledMethod>>storeDataOn: (in category 'file in/out') -----
- storeDataOn: aDataStream
- 	"Store myself on a DataStream.  I am a mixture of objects and raw data bytes.  Only use this for blocks.  Normal methodDictionaries should not be put out using ReferenceStreams.  Their fileOut should be attached to the beginning of the file."
- 
- 	| byteLength lits |
- 	"No inst vars of the normal type"
- 	byteLength := self basicSize.
- 	aDataStream
- 		beginInstance: self class
- 		size: byteLength.
- 	lits := self numLiterals + 1.	"counting header"
- 	1 to: lits do:
- 		[:ii | aDataStream nextPut: (self objectAt: ii)].
- 	lits*4+1 to: byteLength do:
- 		[:ii | aDataStream byteStream nextPut: (self basicAt: ii)].
- 			"write bytes straight through to the file"!

Item was removed:
- ----- Method: CompiledMethod>>storeOn: (in category 'printing') -----
- storeOn: aStream
- 	| noneYet |
- 	aStream nextPutAll: '(('.
- 	aStream nextPutAll: self class name.
- 	aStream nextPutAll: ' newMethod: '.
- 	aStream store: self size - self initialPC + 1.
- 	aStream nextPutAll: ' header: '.
- 	aStream store: self header.
- 	aStream nextPut: $).
- 	noneYet := self storeElementsFrom: self initialPC to: self endPC on: aStream.
- 	1 to: self numLiterals do:
- 		[:index |
- 		noneYet
- 			ifTrue: [noneYet := false]
- 			ifFalse: [aStream nextPut: $;].
- 		aStream nextPutAll: ' literalAt: '.
- 		aStream store: index.
- 		aStream nextPutAll: ' put: '.
- 		aStream store: (self literalAt: index)].
- 	noneYet ifFalse: [aStream nextPutAll: '; yourself'].
- 	aStream nextPut: $)!

Item was removed:
- ----- Method: CompiledMethod>>trailer (in category 'accessing') -----
- trailer
- 	"Answer the receiver's trailer"
- 	^ CompiledMethodTrailer new method: self
- !

Item was removed:
- ----- Method: CompiledMethod>>veryDeepCopyWith: (in category 'file in/out') -----
- veryDeepCopyWith: deepCopier
- 	"Return self.  I am always shared.  Do not record me.  Only use this for blocks.  Normally methodDictionaries should not be copied this way."!

Item was removed:
- ----- Method: CompiledMethod>>voidCogVMState (in category 'cleaning') -----
- voidCogVMState
- 	"Tell the VM to remove all references to any machine code form of the method.
- 	 This primitive must be called whenever a method is in use and modified.  This is
- 	 more aggressive (and *much* more costly) than flushCache since it must search
- 	 through all context objects, making sure that none have a (hidden) machine code pc
- 	 in the receiver.  Since modifying a method will likely change the generated machine code,
- 	 modifying a method (rather than redefining it) requires this more aggressive flush."
- 
- 	<primitive: 215>
- 	^self flushCache!



More information about the Squeak-dev mailing list