[Pkg] The Trunk: Environments-cwp.19.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Apr 2 06:10:38 UTC 2013


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

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

Name: Environments-cwp.19
Author: cwp
Time: 1 April 2013, 11:08:28.022 pm
UUID: 90a9eda4-b8ad-4f7e-9e71-c5e940c08e4f
Ancestors: Environments-cwp.18

Bindings cleanup stage 1/2.

=============== Diff against Environments-cwp.18 ===============

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

Item was added:
+ ----- 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 added:
+ ----- Method: AbstractBinding class>>initialize (in category 'as yet unclassified') -----
+ initialize
+ 	self convertInstances!

Item was added:
+ ----- 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 added:
+ ----- Method: AbstractBinding>>canAssign (in category 'as yet unclassified') -----
+ canAssign
+ 	^ true!

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

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

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

Item was added:
+ ----- 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 added:
+ ----- Method: AbstractBinding>>printOn: (in category 'as yet unclassified') -----
+ printOn: aStream
+ 	key printOn: aStream.
+ 	aStream nextPutAll: '=>'.
+ 	self value printOn: aStream!

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

Item was changed:
+ ----- Method: Alias>>initializeWithKey:source: (in category 'initialization') -----
- ----- Method: Alias>>initializeWithKey:source: (in category 'as yet unclassified') -----
  initializeWithKey: aSymbol source: anAssociation
  	self initialize.
  	key := aSymbol.
  	source := anAssociation!

Item was changed:
+ ----- Method: Alias>>isSpecialReadBinding (in category 'testing') -----
- ----- Method: Alias>>isSpecialReadBinding (in category 'as yet unclassified') -----
  isSpecialReadBinding
  	^ true!

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

Item was added:
+ ----- Method: Alias>>literalEqual: (in category 'error handling') -----
+ literalEqual: other 
+ 	"Two aliases are equal if they have the same source"
+ 
+ 	^ self species = other species and: [self source == other source]!

Item was added:
+ ----- Method: Alias>>source (in category 'accessing') -----
+ source
+ 	^ source!

Item was changed:
+ ----- Method: Alias>>value (in category 'evaluating') -----
- ----- Method: Alias>>value (in category 'as yet unclassified') -----
  value
  	^ source value!

Item was changed:
+ ----- Method: Alias>>value: (in category 'accessing') -----
- ----- Method: Alias>>value: (in category 'as yet unclassified') -----
  value: anObject
  	source value: anObject!

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

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

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

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

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

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

Item was added:
+ ----- Method: ClassBinding>>literalEqual: (in category 'as yet unclassified') -----
+ literalEqual: other
+ 	"Class bindings are equal when the bind the same class"
+ 	
+ 	^ self species = other species and: [self value = other value]!

Item was added:
+ ----- Method: ClassBinding>>value (in category 'as yet unclassified') -----
+ value
+ 	^ value!

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

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

Item was added:
+ ----- Method: Global class>>key:value: (in category 'as yet unclassified') -----
+ key: aSymbol value: anObject
+ 	^ self basicNew initializeWithKey: aSymbol value: anObject!

Item was added:
+ ----- Method: Global>>asBinding: (in category 'as yet unclassified') -----
+ asBinding: aSymbol
+ 	^ Alias key: aSymbol source: self!

Item was added:
+ ----- Method: Global>>initializeWithKey:value: (in category 'as yet unclassified') -----
+ initializeWithKey: aSymbol value: anObject
+ 	self initialize.
+ 	key := aSymbol.
+ 	value := anObject!

Item was added:
+ ----- Method: Global>>literalEqual: (in category 'as yet unclassified') -----
+ literalEqual: other
+ 	"Globals are only equal to themselves, since another global with the same
+ 	name could have a different value in the future."
+ 	
+ 	^ self == other!

Item was added:
+ ----- Method: Global>>value (in category 'as yet unclassified') -----
+ value
+ 	^ value!

Item was added:
+ ----- Method: Global>>value: (in category 'as yet unclassified') -----
+ value: anObject
+ 	value := anObject!

Item was added:
+ ----- Method: Symbol>>=> (in category '*environments') -----
+ => anObject
+ 	
+ 	^ anObject isBehavior
+ 		ifTrue: [ClassBinding key: self value: anObject]
+ 		ifFalse: [Global key: self value: anObject]!



More information about the Packages mailing list