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

commits at source.squeak.org commits at source.squeak.org
Fri May 1 17:26:15 UTC 2020


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

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

Name: Kernel-eem.1324
Author: eem
Time: 1 May 2020, 10:26:11.511925 am
UUID: cd934a41-effd-45b7-8216-5ae56ae92687
Ancestors: Kernel-eem.1323

Rename BlockClosure's startpc inst var to startpcOrMethod, to reduce confusion in FullBlockClosure.

In FullBlockClosure replace sends of self compiledBlock with startpcOrMethod.  Simplify FullBlockClosure>>#=.

=============== Diff against Kernel-eem.1323 ===============

Item was added:
+ (PackageInfo named: 'Kernel') preamble: '"below, add code to be run before the loading of this package"
+ BlockClosure instVarNames at: 2 put: ''startpcOrMethod'''!

Item was changed:
  Object variableSubclass: #BlockClosure
+ 	instanceVariableNames: 'outerContext startpcOrMethod numArgs'
- 	instanceVariableNames: 'outerContext startpc numArgs'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Kernel-Methods'!
  
+ !BlockClosure commentStamp: 'eem 5/1/2020 10:04' prior: 0!
+ Instances of BlockClosure represent blocks, a sequence of statements inside square brackets that can be evaluated at any time via one of the value messages (value, value:, value:value:, ... valueWithArguments:), which answer their last statement.  Blocks therefore allow deferred evaluation and so are used to build control structures where a sequence of statements are evaluated or not depending on other values in the program.
- !BlockClosure commentStamp: 'eem 4/10/2017 11:17' prior: 0!
- Instances of BlockClosure represent blocks, a sequence of statements inside square brackets that can be evaluated at any time via one of the value messages (value, value:, value:value:, ... valueWithArguments:), which answer their last statement.  Blocks therefore allow deferred evaluation and so are used to buikld control structures where a sequence of statements are evaluated or not depending on other values in the program.
  
+ Blocks can close over variables in their enclosing method or block.  The method in which a block is nested is called its home method.  Blocks can return from their home method via an up-arrow return, and return to the sender of the message that created the home method, just like a return from the method itself.  BlockClosures are fully first-class objects; they can outlive their enclosing method activation and be answered as results and/or assigned to variables.
- Blocks can close over variables in their enclosing method or block.  The method in which a block is nested is called its home method.  Blocks can return from their home method via an up-arrow return, and returns to the sender of the message that created the home method, just like a return from the method itself.  BlockClosures are fully first-class objects; they can outlive their enclosing method activation and be answered as results and/or assigned to variables.
  
+ BlockClosures are central to the implementation of control structures in Smalltalk.  The arguments to the conditional message ifTrue:ifFalse: are zero-argument blocks; the receiver of ifTrue:ifFalse: is a boolean which responds by evaluating ether the first argument or the second.  The bytecode compiler inlines blocks for certain selectors, compiling to conditional branch and branch bytecodes.  This is done for efficiency.  The full list of inlined messages can be found in MessageNode's MacroSelectors class variable (at time of writing ther=se are ifTrue:, ifFalse:, ifTrue:ifFalse:, ifFalse:ifTrue:, and:, or:, whileFalse:, whileTrue:, whileFalse, whileTrue, to:do:, to:by:do:, caseOf:, caseOf:otherwise:, ifNil:, ifNotNil:, ifNil:ifNotNil:, ifNotNil:ifNil: and repeat.
- BlockClosures are central to the implementation of control structures in Smalltalk.  The arguments to the conditional message ifTrue:ifFalse: are zero-argument blocks, which the receiver is a boolean which responds by evaluating ether the first argument or the second.  The bytecode compiler inlines blocks for certain selectors, compiling to conditional branch and branch bytecodes.  This is done for efficiency.  The full list of inlined messages can be found in MessageNode's MacroSelectors class variable (at time of writing ther=se are ifTrue:, ifFalse:, ifTrue:ifFalse:, ifFalse:ifTrue:, and:, or:, whileFalse:, whileTrue:, whileFalse, whileTrue, to:do:, to:by:do:, caseOf:, caseOf:otherwise:, ifNil:, ifNotNil:, ifNil:ifNotNil:, ifNotNil:ifNil: and repeat.
  
  Examples (more can be found in BlockClosureTest's class comment):
  	[1 at 2] value
  
  	| counter |
  	counter := 0.
  	{ counter. (1 to: 10) collect: [:n| counter := counter + 1. n + counter]. counter }
  
  	| fibonacciBlock |
  	fibonacciBlock := [:n|
  					n > 1 ifTrue: [(fibonacciBlock value: n - 1) + (fibonacciBlock value: n - 2)] ifFalse: [1]].
  	(1 to: 10) collect: fibonacciBlock
  
  	| randomNumbers |
  	randomNumbers := Random new next: 20.
  	{ randomNumbers. randomNumbers sorted: [:a :b| a > b] }
  
  Implementation:
  BlockClosure implements blocks that are nested within an enclosing method or block context.  Further, the bytecodes for the block are embedded within the home method.  BlockClosure's subclass FullBlockClosure has an independent CompiledBlock as its method, and may or may not have an outerContext.
  
  Instance Variables
+ 	numArgs:			<Integer>
+ 	outerContext:		<Context>
+ 	startpcOrMethod:	<Integer|CompiledBlock>
- 	numArgs:		<Integer>
- 	outerContext:	<Context>
- 	startpc:			<Integer>
  
  numArgs
  	- the number of arguments the block expects
  
  outerContext
  	- the Context of the method or block activation in which the receiver is created
  
+ startpcOrMethod
+ 	- in BlockClosure this is the pc of the first bytecode of the block.  Its bytecodes are embedded in the bytecodes of the home method.  In FullBlockClosure this is the block's method.!
- startpc
- 	- the startpc of the block's bytecodes within the home method.!

Item was changed:
  ----- Method: BlockClosure>>abstractBytecodeMessagesDo: (in category 'scanning') -----
  abstractBytecodeMessagesDo: aBlock
  	"Evaluate aBlock with the sequence of abstract bytecodes in the receiver."
  	self method
+ 		abstractBytecodeMessagesFrom: startpcOrMethod
- 		abstractBytecodeMessagesFrom: startpc
  		to: self endPC
  		do: aBlock
  
  	"| msgs |
  	 msgs := OrderedCollection new.
  	 (SortedCollection sortBlock: [:a :b| a compare: b caseSensitive: false]) sortBlock
  		abstractBytecodeMessagesDo: [:msg| msgs add: msg selector].
  	 msgs"!

Item was changed:
  ----- Method: BlockClosure>>asContextWithSender: (in category 'private') -----
  asContextWithSender: aContext
  	"Inner private support method for evaluation.  Do not use unless you know what you're doing."
  
  	^(Context newForMethod: outerContext method)
  		setSender: aContext
  		receiver: outerContext receiver
  		method: outerContext method
  		closure: self
+ 		startpc: startpcOrMethod;
- 		startpc: startpc;
  		privRefresh!

Item was changed:
  ----- Method: BlockClosure>>blockCreationPC (in category 'scanning') -----
  blockCreationPC
  	"Answer the pc for the bytecode that created the receiver."
  	| method |
  	method := self method.
  	^method encoderClass
+ 		pcOfBlockCreationBytecodeForBlockStartingAt: startpcOrMethod
- 		pcOfBlockCreationBytecodeForBlockStartingAt: startpc
  		in: method!

Item was changed:
  ----- Method: BlockClosure>>endPC (in category 'accessing') -----
  endPC
+ 	^self blockCreationBytecodeMessage arguments last + startpcOrMethod - 1!
- 	^self blockCreationBytecodeMessage arguments last + startpc - 1!

Item was changed:
  ----- Method: BlockClosure>>hasMethodReturn (in category 'testing') -----
  hasMethodReturn
  	"Answer whether the receiver has a method-return ('^') in its code."
  	| scanner endpc |
+ 	scanner := InstructionStream new method: outerContext method pc: startpcOrMethod.
- 	scanner := InstructionStream new method: outerContext method pc: startpc.
  	endpc := self endPC.
  	scanner scanFor: [:byte | (byte between: 120 and: 124) or: [scanner pc > endpc]].
  	^scanner pc <= endpc!

Item was changed:
  ----- Method: BlockClosure>>hash (in category 'comparing') -----
  hash
+ 	^(self method hash + startpcOrMethod hash) hashMultiply!
- 	^(self method hash + startpc hash) hashMultiply!

Item was changed:
  ----- Method: BlockClosure>>numTemps (in category 'accessing') -----
  numTemps
  	"Answer the number of temporaries for the receiver; this includes
  	 the number of arguments and the number of copied values."
  	^self numCopiedValues
  	 + self numArgs
  	 + (BlockLocalTempCounter
+ 			tempCountForBlockStartingAt: startpcOrMethod
- 			tempCountForBlockStartingAt: startpc
  			in: self method)!

Item was changed:
  ----- Method: BlockClosure>>once (in category 'evaluating') -----
  once
  	"Evaluate the receiver exactly once, so that repeated evaluations
  	 answer exactly the same object as the first evaluation.  This
  	 allows one to intern values with the idiom
  		myResourceMethod
  			^[expression] once"
  
  	| cache |
  	cache := self method
  				propertyValueAt: #onceCache
  				ifAbsent: [self method propertyValueAt: #onceCache put: Dictionary new].
+ 	^cache at: startpcOrMethod ifAbsentPut: [self value]!
- 	^cache at: startpc ifAbsentPut: [self value]!

Item was changed:
  ----- Method: BlockClosure>>outerContext:startpc:numArgs:copiedValues: (in category 'initialize-release') -----
  outerContext: aContext startpc: aStartpc numArgs: argCount copiedValues: anArrayOrNil
  	outerContext := aContext.
+ 	startpcOrMethod := aStartpc.
- 	startpc := aStartpc.
  	numArgs := argCount.
  	1 to: self numCopiedValues do:
  		[:i|
  		self at: i put: (anArrayOrNil at: i)]!

Item was changed:
  ----- Method: BlockClosure>>simulateValueWithArguments:caller: (in category 'system simulation') -----
  simulateValueWithArguments: anArray caller: aContext
  	"Simulate the valueWithArguments: primitive. Fail if anArray is not an array of the right arity."
  	| newContext sz |
  	newContext := (Context newForMethod: outerContext method)
  						setSender: aContext
  						receiver: outerContext receiver
  						method: outerContext method
  						closure: self
+ 						startpc: startpcOrMethod.
- 						startpc: startpc.
  	((newContext objectClass: anArray) ~~ Array
  	 or: [numArgs ~= anArray size]) ifTrue:
  		[^Context primitiveFailTokenFor: nil].
  	sz := self basicSize.
  	newContext stackp: sz + numArgs.
  	1 to: numArgs do:
  		[:i| newContext at: i put: (anArray at: i)].
  	1 to: sz do:
  		[:i| newContext at: i + numArgs put: (self at: i)].
  	^newContext!

Item was changed:
  ----- Method: BlockClosure>>startpc (in category 'accessing') -----
  startpc
+ 	^startpcOrMethod!
- 	^startpc!

Item was changed:
  BlockClosure variableSubclass: #FullBlockClosure
  	instanceVariableNames: 'receiver'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Kernel-Methods'!
  
+ !FullBlockClosure commentStamp: 'eem 5/1/2020 10:24' prior: 0!
- !FullBlockClosure commentStamp: 'ct 2/14/2020 15:56' prior: 0!
  Instances of FullBlockClosure represent blocks, a sequence of statements inside square brackets that can be evaluated at any time via one of the value messages (value, value:, value:value:, ..., valueWithArguments:), which answer their last statement.  Blocks therefore allow deferred evaluation and so are used to build control structures where a sequence of statements are evaluated or not depending on other values in the program.
  
  FullBlockClosure is a refinement of BlockClosure that allows the block to use its own method to hold its code instead of embedding that code within its home method.
  
- Implementation notes:
- 
- A FullBlockClosure is a closure that can be independent of any outerContext if desired.  It has its own method (currently reusing the startpc inst var) and its own receiver.  outerContext can be either a Context or nil.
- 
- This closure design, implemented by Eliot Miranda and Clement Bera along with the sista work, aims to simplify the block closure model while enhacing its capabilities. It allows lazy decompilation of closures and fast machine code dispatch in Cog's JIT, while allowing inlining of methods and blocks to be independent from their enclosing blocks.
- 
- At closure creation time, the bytecode specifies:
- - the compiledBlock to execute when executing this block's code (in the literal frame)
- - if the receiver is the current receiver or a receiver passed on stack before the copied values.
- - if the closure needs an outerContext. outerContexts are used for non local returns and debugging. Blocks with non local returns have to set their outerContext. For other blocks (97% of blocks), it's a trade-off between performance and debuggability.
- 
  Instance Variables (inherited)
+ 	numArgs			<SmallInteger> 
+ 	outerContext:		<Context|nil> 
+ 	startpcOrMethod	<CompiledBlock>
- 	numArgs				<SmallInteger> 
- 	outerContext:			<Context|nil> 
- 	compiledBlock(startpc) <CompiledBlock>
  
  Instance Variables
+ 	receiver:			<Object>
- 	receiver:				<Object>
  
  numArgs
  	- the number of arguments the block expects. This is superfluous; the number of arguments can be obtained from the receiver's compiledBlock.
  
  outerContext
  	- the Context of the method or block activation in which the receiver is created.
  
+ compiledBlock(startpcOrMethod)
- compiledBlock(startpc)
  	- reused to refer to the CompiledBlock that implements the receiver's code.
  
  receiver
+ 	- the receiver of the message that created the block's home method activation.
+ 
+ 
+ Implementation notes:
+ 
+ A FullBlockClosure is a closure that can be independent of any outerContext if desired.  It has its own method (reusing the startpcOrMethod inst var) and its own receiver.  outerContext can be either a Context or nil.
+ 
+ This closure design, implemented by Eliot Miranda and Clement Bera along with the Sista work, aims to simplify the block closure model while enhacing its capabilities. It allows lazy decompilation of closures and fast machine code dispatch in Cog's JIT, while allowing inlining of methods and blocks to be independent from their enclosing blocks.
+ 
+ At closure creation time, the Sista closure creation bytecode specifies:
+ - the compiledBlock to execute when executing this block's code (in the literal frame)
+ - if the receiver is the current receiver or a receiver passed on stack before the copied values.
+ - if the closure needs an outerContext. outerContexts are used for non local returns and debugging. Blocks with non-local (up arrow) returns have to set their outerContext. For other blocks (97% of blocks), it's a trade-off between performance and debuggability.!
- 	- the receiver of the message that created the block's home method activation.!

Item was changed:
  ----- Method: FullBlockClosure>>= (in category 'comparing') -----
  = aClosure
  	self == aClosure ifTrue: [^true].
+ 	aClosure class == self class ifFalse: [^false].
+ 	startpcOrMethod = aClosure compiledBlock ifFalse: [^false].
+ 	^outerContext = aClosure outerContext or: [self isClean]!
- 	aClosure class = self class ifFalse: [^false].
- 	(self method == aClosure method and: [self compiledBlock = aClosure compiledBlock and: [self isClean]])
- 		ifTrue: [^true].
- 	^outerContext = aClosure outerContext and: [self compiledBlock = aClosure compiledBlock]!

Item was changed:
  ----- Method: FullBlockClosure>>abstractBytecodeMessagesDo: (in category 'scanning') -----
  abstractBytecodeMessagesDo: aBlock
+ 	^startpcOrMethod abstractBytecodeMessagesDo: aBlock!
- 	^ self compiledBlock abstractBytecodeMessagesDo: aBlock!

Item was changed:
  ----- Method: FullBlockClosure>>asContextWithSender: (in category 'private') -----
  asContextWithSender: aContext
  	"Inner private support method for evaluation.  Do not use unless you know what you're doing."
  
+ 	^(Context newForMethod: startpcOrMethod)
- 	^(Context newForMethod: self compiledBlock)
  		setSender: aContext
  		receiver: self receiver
+ 		method: startpcOrMethod
- 		method: self compiledBlock
  		closure: self
+ 		startpc: startpcOrMethod initialPC;
- 		startpc: self startpc;
  		privRefresh!

Item was added:
+ ----- Method: FullBlockClosure>>blockCreationPC (in category 'scanning') -----
+ blockCreationPC
+ 	self shouldNotImplement!

Item was changed:
  ----- Method: FullBlockClosure>>compiledBlock (in category 'accessing') -----
  compiledBlock
  	"To be able to inherit from BlockClosure"
+ 	^ startpcOrMethod!
- 	^ startpc!

Item was changed:
  ----- Method: FullBlockClosure>>compiledBlock: (in category 'accessing') -----
+ compiledBlock: aCompiledBlock
- compiledBlock: aCompiledMethod
  	"To be able to inherit from BlockClosure"
+ 	startpcOrMethod := aCompiledBlock!
- 	startpc := aCompiledMethod!

Item was changed:
  ----- Method: FullBlockClosure>>endPC (in category 'accessing') -----
  endPC
+ 	^startpcOrMethod endPC!
- 	^ self compiledBlock endPC!

Item was changed:
  ----- Method: FullBlockClosure>>hasMethodReturn (in category 'scanning') -----
  hasMethodReturn
  	"Answer whether the receiver has a method-return ('^') in its code."
+ 	^startpcOrMethod hasMethodReturn!
- 	^ self compiledBlock hasMethodReturn!

Item was changed:
  ----- Method: FullBlockClosure>>homeMethod (in category 'accessing') -----
  homeMethod
+ 	^startpcOrMethod homeMethod!
- 	^self compiledBlock homeMethod!

Item was changed:
  ----- Method: FullBlockClosure>>method (in category 'accessing') -----
  method
+ 	^startpcOrMethod!
- 	^ self compiledBlock!

Item was changed:
  ----- Method: FullBlockClosure>>numTemps (in category 'accessing') -----
  numTemps
+ 	^startpcOrMethod numTemps!
- 	^ self compiledBlock numTemps!

Item was changed:
  ----- Method: FullBlockClosure>>receiver:outerContext:method:copiedValues: (in category 'initialize-release') -----
  receiver: aReceiver outerContext: aContextOrNil method: aCompiledBlock copiedValues: anArrayOrNil
  	receiver := aReceiver.
  	outerContext := aContextOrNil.
+ 	startpcOrMethod := aCompiledBlock.
- 	startpc := aCompiledBlock.
  	numArgs := aCompiledBlock numArgs.
  	1 to: self numCopiedValues do:
  		[:i|
  		self at: i put: (anArrayOrNil at: i)]!

Item was changed:
  ----- Method: FullBlockClosure>>simulateValueWithArguments:caller: (in category 'simulation') -----
  simulateValueWithArguments: anArray caller: aContext
  	"Simulate the valueWithArguments: primitive. Fail if anArray is not an array of the right arity."
  	| newContext |
+ 	newContext := (Context newForMethod: startpcOrMethod)
- 	newContext := (Context newForMethod: self compiledBlock)
  						setSender: aContext
  						receiver: receiver
+ 						method: startpcOrMethod
- 						method: self compiledBlock
  						closure: self
+ 						startpc: startpcOrMethod initialPC.
- 						startpc: self compiledBlock initialPC.
  	((newContext objectClass: anArray) ~~ Array
  	 or: [numArgs ~= anArray size]) ifTrue:
  		[^Context primitiveFailTokenFor: nil].
+ 	newContext stackp: startpcOrMethod numTemps.
- 	newContext stackp: self compiledBlock numTemps.
  	1 to: numArgs do:
  		[:i| newContext at: i put: (anArray at: i)].
  	1 to: self basicSize do:
  		[:i| newContext at: i + numArgs put: (self at: i)].
  	^newContext!

Item was changed:
  ----- Method: FullBlockClosure>>size (in category 'accessing') -----
  size
  	"Answer closure's bytecode size (number of bytes) by accessing
  	 the closure's method."
+ 	^startpcOrMethod endPC - startpcOrMethod initialPC + 1!
- 	^self compiledBlock endPC - self compiledBlock initialPC + 1!

Item was changed:
  ----- Method: FullBlockClosure>>startpc (in category 'accessing') -----
  startpc
+ 	^startpcOrMethod initialPC!
- 	^ self compiledBlock initialPC!



More information about the Squeak-dev mailing list