[squeak-dev] The Trunk: Environments-cwp.20.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Apr 2 07:29:19 UTC 2013


Colin Putney uploaded a new version of Environments to project The Trunk:
http://source.squeak.org/trunk/Environments-cwp.20.mcz

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

Name: Environments-cwp.20
Author: cwp
Time: 2 April 2013, 12:27:08.241 am
UUID: ebb65551-c6d9-4a51-b174-6e6306fbf55f
Ancestors: Environments-cwp.19

Bindings cleanup stage 2/2.

=============== Diff against Environments-cwp.19 ===============

Item was removed:
- LookupKey subclass: #AbstractBinding
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Environments-Core'!

Item was removed:
- ----- Method: AbstractBinding class>>convertInstances (in category 'as yet unclassified') -----
- convertInstances
- 	| new old |
- 	old := Binding allInstances.
- 	new := old collect: [:ea | ClassBinding key: ea key value: ea value].
- 	old elementsForwardIdentityTo: new.
- 	
- 	old := ReadOnlyVariableBinding allInstances.
- 	new := old collect: [:ea | ClassBinding key: ea key value: ea value].
- 	old elementsForwardIdentityTo: new.
- 	
- 	Environment allInstancesDo:
- 		[:env |
- 		#('contents' 'bindings' 'public' 'undeclared') do:
- 			[:var || dict |
- 			old := Array new writeStream.
- 			new := Array new writeStream.
- 			dict := env instVarNamed: var.
- 			dict associations do:
- 				[:binding |
- 				binding class == Association ifTrue:
- 					[old nextPut: binding.
- 					new nextPut: binding key => binding value]].
- 			old contents elementsForwardIdentityTo: new contents]]!

Item was removed:
- ----- Method: AbstractBinding class>>initialize (in category 'as yet unclassified') -----
- initialize
- 	self convertInstances!

Item was removed:
- ----- Method: AbstractBinding>>analogousCodeTo: (in category 'as yet unclassified') -----
- analogousCodeTo: anObject
- 	"For MethodProperties comparison."
- 	^anObject isVariableBinding
- 	  and: [self key = anObject key
- 	  and: [self value = anObject value]]!

Item was removed:
- ----- Method: AbstractBinding>>canAssign (in category 'as yet unclassified') -----
- canAssign
- 	^ true!

Item was removed:
- ----- Method: AbstractBinding>>isSpecialReadBinding (in category 'as yet unclassified') -----
- isSpecialReadBinding
- 	^ false!

Item was removed:
- ----- Method: AbstractBinding>>isSpecialWriteBinding (in category 'as yet unclassified') -----
- isSpecialWriteBinding
- 	^ false!

Item was removed:
- ----- Method: AbstractBinding>>isVariableBinding (in category 'as yet unclassified') -----
- isVariableBinding
- 	^ true!

Item was removed:
- ----- Method: AbstractBinding>>objectForDataStream: (in category 'as yet unclassified') -----
- objectForDataStream: refStream
- 	"It's not yet clear how serialization should work in the presence of environments"
- 	
- 	self shouldBeImplemented.!

Item was removed:
- ----- Method: AbstractBinding>>printOn: (in category 'as yet unclassified') -----
- printOn: aStream
- 	key printOn: aStream.
- 	aStream nextPutAll: '=>'.
- 	self value printOn: aStream!

Item was changed:
+ Binding subclass: #Alias
- AbstractBinding subclass: #Alias
  	instanceVariableNames: 'source'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Environments-Core'!

Item was changed:
  LookupKey subclass: #Binding
+ 	instanceVariableNames: ''
- 	instanceVariableNames: 'value'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Environments-Core'!

Item was added:
+ ----- Method: Binding class>>convertInstances (in category 'as yet unclassified') -----
+ convertInstances
+ 	| new old |
+ 	old := Binding allInstances.
+ 	new := old collect: [:ea | ClassBinding key: ea key value: ea value].
+ 	old elementsForwardIdentityTo: new.
+ 	
+ 	old := ReadOnlyVariableBinding allInstances.
+ 	new := old collect: [:ea | ClassBinding key: ea key value: ea value].
+ 	old elementsForwardIdentityTo: new.
+ 	
+ 	Environment allInstancesDo:
+ 		[:env |
+ 		#('contents' 'bindings' 'public' 'undeclared') do:
+ 			[:var || dict |
+ 			old := Array new writeStream.
+ 			new := Array new writeStream.
+ 			dict := env instVarNamed: var.
+ 			dict associations do:
+ 				[:binding |
+ 				binding class == Association ifTrue:
+ 					[old nextPut: binding.
+ 					new nextPut: binding key => binding value]].
+ 			old contents elementsForwardIdentityTo: new contents]]!

Item was removed:
- ----- Method: Binding class>>key:value: (in category 'as yet unclassified') -----
- key: key value: value
- 	^ self basicNew initializeWithKey: key value: value!

Item was added:
+ ----- Method: Binding>>analogousCodeTo: (in category 'as yet unclassified') -----
+ analogousCodeTo: anObject
+ 	"For MethodProperties comparison."
+ 	^anObject isVariableBinding
+ 	  and: [self key = anObject key
+ 	  and: [self value = anObject value]]!

Item was removed:
- ----- Method: Binding>>asBinding: (in category 'as yet unclassified') -----
- asBinding: aSymbol
- 	^ self class key: aSymbol value: value!

Item was changed:
  ----- Method: Binding>>canAssign (in category 'as yet unclassified') -----
  canAssign
+ 	^ true!
- 	^ false!

Item was removed:
- ----- Method: Binding>>initializeWithKey:value: (in category 'as yet unclassified') -----
- initializeWithKey: kObject value: vObject
- 	self initialize.
- 	key := kObject.
- 	value := vObject.!

Item was added:
+ ----- Method: Binding>>isSpecialReadBinding (in category 'as yet unclassified') -----
+ isSpecialReadBinding
+ 	^ false!

Item was changed:
  ----- Method: Binding>>isSpecialWriteBinding (in category 'as yet unclassified') -----
  isSpecialWriteBinding
+ 	^ false!
- 	^ true!

Item was added:
+ ----- Method: Binding>>isVariableBinding (in category 'as yet unclassified') -----
+ isVariableBinding
+ 	^ true!

Item was added:
+ ----- Method: Binding>>objectForDataStream: (in category 'as yet unclassified') -----
+ objectForDataStream: refStream
+ 	"It's not yet clear how serialization should work in the presence of environments"
+ 	
+ 	self shouldBeImplemented.!

Item was added:
+ ----- Method: Binding>>printOn: (in category 'as yet unclassified') -----
+ printOn: aStream
+ 	key printOn: aStream.
+ 	aStream nextPutAll: '=>'.
+ 	self value printOn: aStream!

Item was removed:
- ----- Method: Binding>>value (in category 'as yet unclassified') -----
- value
- 	^ value!

Item was removed:
- ----- Method: Binding>>value: (in category 'as yet unclassified') -----
- value: anObject
- 	(AttemptToWriteReadOnlyGlobal signal: 'Cannot store into read-only bindings')
- 		ifTrue: [value := anObject]!

Item was changed:
+ Binding subclass: #ClassBinding
- AbstractBinding subclass: #ClassBinding
  	instanceVariableNames: 'value'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Environments-Core'!

Item was changed:
  ----- Method: Environment>>at:put: (in category 'emulating') -----
  at: aSymbol put: anObject
  	| binding |
  	(contents includesKey: aSymbol)
  		ifTrue: [contents at: aSymbol put: anObject]
  		ifFalse:
  			[(undeclared includesKey: aSymbol) 
  				ifTrue: 
  					[contents declare: aSymbol from: undeclared.
  					contents at: aSymbol put: anObject]
  				ifFalse: 
+ 					[binding := aSymbol => anObject.
- 					[binding := anObject isBehavior
- 						ifTrue: [Binding key: aSymbol value: anObject]
- 						ifFalse: [Association key: aSymbol value: anObject].
  					contents add: binding.
  					exports bind: binding]].
  	^ anObject
  !

Item was changed:
+ Binding subclass: #Global
- AbstractBinding subclass: #Global
  	instanceVariableNames: 'value'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Environments-Core'!

Item was changed:
  ----- Method: ReadOnlyVariableBinding>>asBinding: (in category '*environments') -----
  asBinding: aSymbol
+ 	^ ClassBinding key: aSymbol value: value!
- 	^ Binding key: aSymbol value: value!



More information about the Squeak-dev mailing list