[squeak-dev] The Trunk: Compiler-eem.322.mcz

commits at source.squeak.org commits at source.squeak.org
Fri May 13 19:37:37 UTC 2016


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

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

Name: Compiler-eem.322
Author: eem
Time: 13 May 2016, 12:36:54.992126 pm
UUID: b7bb5d79-1a2e-4a45-a6cc-dd0a8cf438bb
Ancestors: Compiler-nice.321

Add bytecode scanning machinery to identify "synthetic" stores, i.e. the stores of indirect temp vectors at the start of methods containing closures.

Add a "high-quality" pcPreviousTo:in:for: that answers nil for the first pcs of blocks, and answers the block creation bytecode's pc for the pc following an embedded block, and use it to disambiguate bytecode sequences that look like pushNewArray of an empty array..

Add isTempStoreAt:in: & pcFollowingBlockAt:in: to support the above.

=============== Diff against Compiler-nice.321 ===============

Item was added:
+ ----- Method: BytecodeEncoder class>>createClosureCode (in category 'bytecode decoding') -----
+ createClosureCode
+ 	"Answer the create closure bytecode, if it exists in the encoder's byetcode set, or nil if not."
+ 	^nil!

Item was added:
+ ----- Method: BytecodeEncoder class>>isNonSyntheticStoreAt:in:for: (in category 'instruction stream support') -----
+ isNonSyntheticStoreAt: pc in: method for: anInstructionStream
+ 	"Answer whether the bytecode at pc is a store or store-pop into an explicit variable.
+ 	 This eliminates stores into indirect temp vectors, which implement mutable closed-over
+ 	 variables in the the closure implementation, and hence stores into temp vectors are not real stores."
+ 
+ 	^(self isStoreAt: pc in: method)
+ 	  and: [(self isSyntheticStoreAt: pc in: method for: anInstructionStream) not]!

Item was added:
+ ----- Method: BytecodeEncoder class>>isSyntheticStoreAt:in:for: (in category 'instruction stream support') -----
+ isSyntheticStoreAt: pc in: method for: anInstructionStream
+ 	"Answer whether the bytecode at pc is a store or store-pop of an indirect temp vector,
+ 	 which implement mutable closed-over variables in the the closure implementation.
+ 	 Stores into temp vectors are not real stores."
+ 
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: BytecodeEncoder class>>pcFollowingBlockAt:in: (in category 'bytecode decoding') -----
+ pcFollowingBlockAt: pc in: method
+ 	"Assuming the pc is that of a block creation bytecode, answer the pc immediately following the block,
+ 	 i.e. the next pc after the block creation."
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: BytecodeEncoder class>>pcPreviousTo:in:for: (in category 'bytecode decoding') -----
+ pcPreviousTo: thePC in: method for: anInstructionStreamOrContext
+ 	"Answer the pc of the bytecode before the bytecode at thePC.
+ 	 Unlike CompiledMethod>>pcPreviousTo:, this version answers nil for
+ 	 the first bytecode of an embedded block, and answers the pc of the
+ 	 block creation bytecode for a bytecode following an embedded block."
+ 	| pc nextPc prevPc byte createClosureCode |
+ 	thePC > method endPC ifTrue:
+ 		[^method endPC].
+ 	pc := method initialPC.
+ 	"We could save time by scanning from the block creation bytecode of an embedded block,
+ 	 using the following, but it saves less time than it loses in additional tests."
+ 	"(anInstructionStreamOrContext isContext
+ 	 and: [anInstructionStreamOrContext isClosureContext
+ 	 and: [(nextPc := anInstructionStreamOrContext startpc) > pc]]) ifTrue:
+ 		[pc := self pcOfBlockCreationBytecodeForBlockStartingAt: nextPc in: method]."
+ 	createClosureCode := self createClosureCode.
+ 	[pc < thePC] whileTrue:
+ 		[byte := method at: (prevPc := pc).
+ 		 [pc := createClosureCode == byte
+ 					ifTrue:
+ 						[nextPc := self pcFollowingBlockAt: pc in: method.
+ 						 nextPc = thePC ifTrue: "first bytecode following block"
+ 							[^prevPc].
+ 						 nextPc > thePC
+ 							ifTrue:
+ 								[pc + (self bytecodeSize: byte) = thePC ifTrue: "first bytecode of block"
+ 									[^nil].
+ 								 pc + (self bytecodeSize: byte)]
+ 						 	ifFalse: [nextPc]]
+ 					ifFalse: [pc + (self bytecodeSize: byte)].
+ 		  self isExtension: byte] whileTrue:
+ 			[byte := method at: pc]].
+ 	^prevPc
+ 
+ "Here's code to measure the effect of short-cutting scanning for blocks by starting at the startpc.
+  It measures how much time is used to scan for the pcs from the last block to the end of all mwetods containing blocks.  Uncomment out the short-cut above to compare time with the optimization and time without.  I see approximately 290ms for all such methods with the optimization and 292 ms without, so given that this slows down the substantial majority of methods without blocks, we KISS."
+ "| candidates |
+ candidates := Dictionary new.
+ self systemNavigation allSelect:
+ 	[:m| | ebc |
+ 	(m isQuick or: [(ebc := m embeddedBlockClosures) isEmpty]) ifFalse:
+ 		[candidates at: m put: { ebc last.
+ 								Array streamContents:
+ 									[:s| | is |
+ 									(is:= InstructionStream on: m)
+ 										pc: ebc last startpc;
+ 										scanFor:
+ 											[:b|
+ 											s nextPut: is pc.
+ 											false]] }].
+ 	 false].
+ (1 to: 10) collect:
+ 	[:ign|
+ 	{ [candidates keysAndValuesDo:
+ 		[:m :tuple|
+ 		[:ebc :pcs| | c |
+ 		c := ebc outerContext.
+ 		pcs do:
+ 			[:pc| m encoderClass pcPreviousTo: pc in: m for: c]] valueWithArguments: tuple]] timeToRun.
+ 	  [candidates keysAndValuesDo:
+ 		[:m :tuple|
+ 		[:ebc :pcs| | c |
+ 		c := ebc outerContext.
+ 		pcs do:
+ 			[:pc| m encoderClass pcPreviousTo: pc in: m for: nil]] valueWithArguments: tuple]] timeToRun. }]"!

Item was added:
+ ----- Method: BytecodeEncoder class>>pushNewArrayCode (in category 'bytecode decoding') -----
+ pushNewArrayCode
+ 	"Answer the pushNewArray bytecode, if it exists in the encoder's byetcode set, or nil if not."
+ 	^nil!

Item was added:
+ ----- Method: EncoderForV3 class>>isSyntheticStoreAt:in:for: (in category 'instruction stream support') -----
+ isSyntheticStoreAt: pc in: method for: anInstructionStream
+ 	"Answer whether the bytecode at pc is a store or store-pop of an indirect temp vector,
+ 	 which implement mutable closed-over variables in the the closure implementation.
+ 	 Stores into temp vectors are not real stores."
+ 
+ 	^false!

Item was added:
+ ----- Method: EncoderForV3 class>>isTempStoreAt:in: (in category 'instruction stream support') -----
+ isTempStoreAt: pc in: method
+ 	"Answer whether the bytecode at pc is a store or store-pop into a temporary variable.
+ 	 104-111 	01101iii 	Pop and Store Temporary Location #iii
+ 	 129 		10000001 jjkkkkkk 	Store (Receiver Variable, Temporary Location, Illegal, Literal Variable) [jj] #kkkkkk
+ 	 130 		10000010 jjkkkkkk 	Pop and Store (Receiver Variable, Temporary Location, Illegal, Literal Variable) [jj] #kkkkkk"
+ 
+ 	| byte |
+ 	byte := method at: pc.
+ 	^byte >= 104
+ 	  and: [byte <= 111
+ 			or: [byte <= 130 and: [byte >= 129 and: [(method at: pc + 1) >> 6 = 1]]]]!

Item was added:
+ ----- Method: EncoderForV3PlusClosures class>>createClosureCode (in category 'bytecode decoding') -----
+ createClosureCode
+ 	"Answer the create closure bytecode, if it exists in the encoder's byetcode set, or nil if not."
+ 	^143!

Item was added:
+ ----- Method: EncoderForV3PlusClosures class>>isSyntheticStoreAt:in:for: (in category 'instruction stream support') -----
+ isSyntheticStoreAt: pc in: method for: anInstructionStream
+ 	"Answer whether the bytecode at pc is a store or store-pop of an indirect temp vector,
+ 	 which implement mutable closed-over variables in the the closure implementation.
+ 	 Stores into temp vectors are not real stores.  N.B. pcPreviousTo:in:for: is slow, so filter
+ 	 out any preceding bytecodes other than what looks like a pushNewArrayCode.  But the
+ 	 pcPreviousTo:in:for: is still necessary, since the presence of a pcPreviousTo:in:for: in the
+ 	 right place is potentially ambiguous, possibly part of a different bytecode seqence."
+ 
+ 	^(self isTempStoreAt: pc in: method)
+ 	  and: [pc - 2 >= method initialPC
+ 	  and: [(method at: pc - 2) = self pushNewArrayCode
+ 	  and: [(method at: pc - 1) <= 127
+ 	  and: [pc - 2 = (self pcPreviousTo: pc in: method for: anInstructionStream)]]]]!

Item was added:
+ ----- Method: EncoderForV3PlusClosures class>>pcFollowingBlockAt:in: (in category 'bytecode decoding') -----
+ pcFollowingBlockAt: pc in: method
+ 	"Assuming the pc is that of a block creation bytecode, answer the pc immediately following the block,
+ 	 i.e. the next pc after the block creation."
+ 	self assert: (method at: pc) = self createClosureCode.
+ 	^(method at: pc + 2) * 256 + (method at: pc + 3) + pc + 4!

Item was added:
+ ----- Method: EncoderForV3PlusClosures class>>pushNewArrayCode (in category 'bytecode decoding') -----
+ pushNewArrayCode
+ 	"138   10001010 jkkkkkkk		Push (Array new: kkkkkkk) (j = 0)
+ 								or	Pop kkkkkkk elements into: (Array new: kkkkkkk) (j = 1)"
+ 	^138!



More information about the Squeak-dev mailing list