The Trunk: Collections-ul.186.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

The Trunk: Collections-ul.186.mcz

commits-2
Andreas Raab uploaded a new version of Collections to project The Trunk:
http://source.squeak.org/trunk/Collections-ul.186.mcz

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

Name: Collections-ul.186
Author: ul
Time: 11 November 2009, 8:32:51 am
UUID: 978f1a6f-c445-6745-bf80-47e1c48f0ecf
Ancestors: Collections-nice.184

- removed Character >> #asIRCLowercase and String >> #asIRCLowercase, because they belong to the Network-IRC package
- moved all #hasContentsInExplorer and #explorerContents to Morphic-Explorer
- updated Collection's #ifEmpty:, #ifEmpty:ifNotEmpty:, #ifEmpty:ifNotEmptyDo:, #ifNotEmpty:ifEmpty:, #ifNotEmptyDo:ifEmpty: to enable the compiler to optimize the #ifTrue:ifFalse: sends
- same for Text >> #alignmentAt:ifAbsent:
- added SequenceableCollection >> #replace: which is an in-place version of #collect: (the implementation of Dictionary >> #explorerContents in Morphic-Explorer uses it)
- changed Set >> #atRandom: to use #= instead of #== for integer comparison



=============== Diff against Collections-nice.184 ===============

Item was changed:
  ----- Method: Collection>>ifEmpty: (in category 'testing') -----
  ifEmpty: aBlock
  "Evaluate the block if I'm empty"
 
+ ^self isEmpty ifTrue: [ aBlock value ]!
- ^ self isEmpty ifTrue: aBlock!

Item was changed:
  ----- Method: Collection>>ifEmpty:ifNotEmptyDo: (in category 'testing') -----
  ifEmpty: emptyBlock ifNotEmptyDo: notEmptyBlock
  "Evaluate emptyBlock if I'm empty, notEmptyBlock otherwise"
  "Evaluate the notEmptyBlock with the receiver as its argument"
 
+ self isEmpty ifTrue: [ ^emptyBlock value ].
+ ^notEmptyBlock value: self!
- ^ self isEmpty ifTrue: emptyBlock ifFalse: [notEmptyBlock value: self]!

Item was changed:
  ----- Method: Collection>>ifNotEmpty:ifEmpty: (in category 'testing') -----
  ifNotEmpty: notEmptyBlock ifEmpty: emptyBlock
  "Evaluate emptyBlock if I'm empty, notEmptyBlock otherwise
  If the notEmptyBlock has an argument, eval with the receiver as its argument"
 
+ self isEmpty ifFalse: [ ^notEmptyBlock valueWithPossibleArgument: self ].
+ ^emptyBlock value!
- ^ self isEmpty ifFalse: [notEmptyBlock valueWithPossibleArgument: self] ifTrue: emptyBlock!

Item was added:
+ ----- Method: SequenceableCollection>>replace: (in category 'enumerating') -----
+ replace: aBlock
+ "Evaluate aBlock with each of the receiver's elements as the argument.  
+ Collect the resulting values into self."
+
+ 1 to: self size do: [ :index |
+ self at: index put: (aBlock value: (self at: index)) ]!

Item was changed:
  ----- Method: Set>>atRandom: (in category 'accessing') -----
  atRandom: aGenerator
  "Answer a random element of the receiver. Uses aGenerator which
      should be kept by the user in a variable and used every time. Use
      this instead of #atRandom for better uniformity of random numbers because
  only you use the generator. Causes an error if self has no elements."
  | rand |
 
  self emptyCheck.
  rand := aGenerator nextInt: self size.
  self doWithIndex:[:each :ind |
+ ind = rand ifTrue:[^each]].
- ind == rand ifTrue:[^each]].
  ^ self errorEmptyCollection
  !

Item was changed:
  ----- Method: Collection>>ifNotEmptyDo:ifEmpty: (in category 'testing') -----
  ifNotEmptyDo: notEmptyBlock ifEmpty: emptyBlock
  "Evaluate emptyBlock if I'm empty, notEmptyBlock otherwise
  Evaluate the notEmptyBlock with the receiver as its argument"
 
+ self isEmpty ifFalse: [ ^notEmptyBlock value: self ].
+ ^emptyBlock value!
- ^ self isEmpty ifFalse: [notEmptyBlock value: self] ifTrue: emptyBlock!

Item was changed:
  ----- Method: Text>>alignmentAt:ifAbsent: (in category 'emphasis') -----
  alignmentAt: characterIndex ifAbsent: aBlock
  | attributes emph |
  self size = 0 ifTrue: [^aBlock value].
  emph := nil.
  attributes := runs at: characterIndex.
  attributes do:[:att | (att isKindOf: TextAlignment) ifTrue:[emph := att]].
+ emph ifNil: [ ^aBlock value ].
+ ^emph alignment!
- ^ emph ifNil: aBlock ifNotNil:[emph alignment]!

Item was changed:
  ----- Method: Collection>>ifEmpty:ifNotEmpty: (in category 'testing') -----
  ifEmpty: emptyBlock ifNotEmpty: notEmptyBlock
  "Evaluate emptyBlock if I'm empty, notEmptyBlock otherwise"
  " If the notEmptyBlock has an argument, eval with the receiver as its argument"
 
+ self isEmpty ifTrue: [ ^emptyBlock value ].
+ ^notEmptyBlock valueWithPossibleArgument: self!
- ^ self isEmpty ifTrue: emptyBlock ifFalse: [notEmptyBlock valueWithPossibleArgument: self]!

Item was removed:
- ----- Method: SequenceableCollection>>explorerContents (in category 'explorer') -----
- explorerContents
-
- ^self asOrderedCollection withIndexCollect: [:value :index |
- ObjectExplorerWrapper
- with: value
- name: index printString
- model: self]!

Item was removed:
- ----- Method: Set>>explorerContents (in category 'explorer') -----
- explorerContents
-
- ^self asOrderedCollection withIndexCollect: [:each :index |
- ObjectExplorerWrapper
- with: each
- name: index printString
- model: self]!

Item was removed:
- ----- Method: String>>hasContentsInExplorer (in category 'testing') -----
- hasContentsInExplorer
-
- ^false!

Item was removed:
- ----- Method: Dictionary>>hasContentsInExplorer (in category 'testing') -----
- hasContentsInExplorer
-
- ^self isEmpty not!

Item was removed:
- ----- Method: Character>>asIRCLowercase (in category 'converting') -----
- asIRCLowercase
- "convert to lowercase, using IRC's rules"
-
- self == $[ ifTrue: [ ^ ${ ].
- self == $] ifTrue: [ ^ $} ].
- self == $\ ifTrue: [ ^ $| ].
-
- ^self asLowercase!

Item was removed:
- ----- Method: Set>>hasContentsInExplorer (in category 'explorer') -----
- hasContentsInExplorer
-
- ^self isEmpty not!

Item was removed:
- ----- Method: OrderedCollection>>hasContentsInExplorer (in category 'testing') -----
- hasContentsInExplorer
-
- ^self isEmpty not!

Item was removed:
- ----- Method: Dictionary>>explorerContents (in category 'user interface') -----
- explorerContents
-
- | contents |
-
- contents := OrderedCollection new.
- self keysSortedSafely do: [:key |
- contents add: (ObjectExplorerWrapper
- with: (self at: key)
- name: (key printString contractTo: 32)
- model: self)].
- ^contents
- !

Item was removed:
- ----- Method: String>>asIRCLowercase (in category 'converting') -----
- asIRCLowercase
- "Answer a String made up from the receiver whose characters are all
- lowercase, where 'lowercase' is by IRC's definition"
-
- ^self collect: [ :c | c asIRCLowercase ]!