[squeak-dev] The Inbox: Kernel-ul.613.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Aug 16 09:51:14 UTC 2011


A new version of Kernel was added to project The Inbox:
http://source.squeak.org/inbox/Kernel-ul.613.mcz

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

Name: Kernel-ul.613
Author: ul
Time: 16 August 2011, 11:33:03.744 am
UUID: cd3bc5e7-fabf-b74a-9f8c-18eee845bc9b
Ancestors: Kernel-cmm.612

Extracted and enhanced the ProcessSpecific from Pharo.

=============== Diff against Kernel-cmm.612 ===============

Item was changed:
  SystemOrganization addCategory: #'Kernel-Chronology'!
  SystemOrganization addCategory: #'Kernel-Classes'!
  SystemOrganization addCategory: #'Kernel-Methods'!
+ SystemOrganization addCategory: #'Kernel-Models'!
  SystemOrganization addCategory: #'Kernel-Numbers'!
  SystemOrganization addCategory: #'Kernel-Objects'!
  SystemOrganization addCategory: #'Kernel-Processes'!
+ SystemOrganization addCategory: #'Kernel-Processes-Variables'!
- SystemOrganization addCategory: #'Kernel-Models'!

Item was removed:
- ----- Method: ContextPart>>object:basicAt: (in category 'mirror primitives') -----
- object: anObject basicAt: index 
- 	"Answer the value of an indexable element in the argument anObject without sending
- 	 it a message. Fail if the argument index is not an Integer or is out of bounds, or if
- 	 anObject is not indexable. This mimics the action of the VM when it indexes an object.
- 	 Used to simulate the execution machinery by, for example, the debugger.
- 	 Primitive.  See Object documentation whatIsAPrimitive."
- 
- 	<primitive: 60>
- 	index isInteger ifTrue: [self errorSubscriptBounds: index].
- 	index isNumber
- 		ifTrue: [^self object: anObject basicAt: index asInteger]
- 		ifFalse: [self errorNonIntegerIndex]!

Item was added:
+ ----- Method: ContextPart>>object:basicAt: (in category 'mirror primitives') -----
+ object: anObject basicAt: index 
+ 	"Answer the value of an indexable element in the argument anObject without sending
+ 	 it a message. Fail if the argument index is not an Integer or is out of bounds, or if
+ 	 anObject is not indexable. This mimics the action of the VM when it indexes an object.
+ 	 Used to simulate the execution machinery by, for example, the debugger.
+ 	 Primitive.  See Object documentation whatIsAPrimitive."
+ 
+ 	<primitive: 60>
+ 	index isInteger ifTrue: [self errorSubscriptBounds: index].
+ 	index isNumber
+ 		ifTrue: [^self object: anObject basicAt: index asInteger]
+ 		ifFalse: [self errorNonIntegerIndex]!

Item was added:
+ ----- Method: ContextPart>>object:instVarAt: (in category 'mirror primitives') -----
+ object: anObject instVarAt: anIndex
+ 	"Primitive. Answer a fixed variable in an object. The numbering of the 
+ 	 variables corresponds to the named instance variables. Fail if the index 
+ 	 is not an Integer or is not the index of a fixed variable. Essential for the
+ 	 debugger. See  Object documentation whatIsAPrimitive."
+ 
+ 	<primitive: 73>
+ 	"Access beyond fixed variables."
+ 	^self object: anObject basicAt: anIndex - (self objectClass: anObject) instSize!

Item was removed:
- ----- Method: ContextPart>>object:instVarAt: (in category 'mirror primitives') -----
- object: anObject instVarAt: anIndex
- 	"Primitive. Answer a fixed variable in an object. The numbering of the 
- 	 variables corresponds to the named instance variables. Fail if the index 
- 	 is not an Integer or is not the index of a fixed variable. Essential for the
- 	 debugger. See  Object documentation whatIsAPrimitive."
- 
- 	<primitive: 73>
- 	"Access beyond fixed variables."
- 	^self object: anObject basicAt: anIndex - (self objectClass: anObject) instSize!

Item was added:
+ ProcessSpecificVariable subclass: #DynamicVariable
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Kernel-Processes-Variables'!
+ 
+ !DynamicVariable commentStamp: 'mvl 3/13/2007 13:55' prior: 0!
+ My subclasses are dynamic variables: each subclass represents a variable
+ whose value persists inside the block passed to #value:during:. There is
+ no way to change the value inside such a block, but it is possible to
+ temporarirly rebind it in a nested manner.!

Item was added:
+ ----- Method: DynamicVariable class>>value:during: (in category 'accessing') -----
+ value: anObject during: aBlock
+ 
+ 	| p oldValue |
+ 	p := Processor activeProcess.
+ 	oldValue := p environmentAt: self ifAbsent: [self default].
+ 	^[
+ 		p environmentAt: self put: anObject.
+ 		aBlock value ] 
+ 			ensure: [ p environmentAt: self put: oldValue ].!

Item was added:
+ ----- Method: Process>>environmentAt: (in category 'process specific') -----
+ environmentAt: key 
+ 	^ self environmentAt: key ifAbsent: [self environmentKeyNotFound]!

Item was added:
+ ----- Method: Process>>environmentAt:ifAbsent: (in category 'process specific') -----
+ environmentAt: key  ifAbsent: aBlock
+ 	
+ 	^(env ifNil: [ ^aBlock value ]) at: key ifAbsent: aBlock.!

Item was added:
+ ----- Method: Process>>environmentAt:put: (in category 'process specific') -----
+ environmentAt: key put: value
+ 	
+ 	^(env ifNil: [ env := Dictionary new ]) at: key put: value.!

Item was added:
+ ----- Method: Process>>environmentKeyNotFound (in category 'process specific') -----
+ environmentKeyNotFound 
+ 	self error: 'Environment key not found'!

Item was added:
+ ----- Method: Process>>environmentRemoveKey: (in category 'process specific') -----
+ environmentRemoveKey: key
+ 	^ self environmentRemoveKey: key ifAbsent: [self environmentKeyNotFound]!

Item was added:
+ ----- Method: Process>>environmentRemoveKey:ifAbsent: (in category 'process specific') -----
+ environmentRemoveKey: key ifAbsent: errorBlock
+ 	
+ 	^(env ifNil: [ ^errorBlock value ]) removeKey: key ifAbsent: errorBlock!

Item was added:
+ ProcessSpecificVariable subclass: #ProcessLocalVariable
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Kernel-Processes-Variables'!
+ 
+ !ProcessLocalVariable commentStamp: 'mvl 3/13/2007 12:28' prior: 0!
+ My subclasses have values specific to the active process. They can be read with #value and set with #value:!

Item was added:
+ ----- Method: ProcessLocalVariable class>>value: (in category 'accessing') -----
+ value: anObject
+ 	Processor activeProcess environmentAt: self put: anObject!

Item was added:
+ Object subclass: #ProcessSpecificVariable
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Kernel-Processes-Variables'!
+ ProcessSpecificVariable class
+ 	instanceVariableNames: 'hash'!
+ 
+ !ProcessSpecificVariable commentStamp: 'mvl 3/13/2007 13:53' prior: 0!
+ My subclasses (not instances of them) keep state specific to the current process.
+ 
+ There are two kinds of process-specific variables: process-local (state available
+ for read and write in all methods inside the process), and dynamic variables
+ (implementing dynamic scope).!
+ ProcessSpecificVariable class
+ 	instanceVariableNames: 'hash'!

Item was added:
+ ----- Method: ProcessSpecificVariable class>>default (in category 'accessing') -----
+ default
+ 	"Answer the default value for the variable. The default for the default value is nil."
+ 	^nil!

Item was added:
+ ----- Method: ProcessSpecificVariable class>>hash (in category 'accessing') -----
+ hash
+ 	
+ 	^hash ifNil: [ hash := super hash ]!

Item was added:
+ ----- Method: ProcessSpecificVariable class>>value (in category 'accessing') -----
+ value
+ 	"Answer the current value for this variable in the current context."
+ 	^Processor activeProcess environmentAt: self ifAbsent: [self default].!




More information about the Squeak-dev mailing list