[squeak-dev] The Trunk: Collections-nice.768.mcz

commits at source.squeak.org commits at source.squeak.org
Sun Nov 26 21:39:47 UTC 2017


Nicolas Cellier uploaded a new version of Collections to project The Trunk:
http://source.squeak.org/trunk/Collections-nice.768.mcz

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

Name: Collections-nice.768
Author: nice
Time: 26 November 2017, 10:39:18.783084 pm
UUID: 3431c5cc-a7a1-4317-b07d-24a59bd26bb0
Ancestors: Collections-eem.767, Collections-nice.767

Merge (revised SortFunction + Transcript characterLimit)

=============== Diff against Collections-eem.767 ===============

Item was changed:
  SystemOrganization addCategory: #'Collections-Abstract'!
  SystemOrganization addCategory: #'Collections-Arrayed'!
  SystemOrganization addCategory: #'Collections-Cache'!
  SystemOrganization addCategory: #'Collections-Exceptions'!
  SystemOrganization addCategory: #'Collections-Heap'!
  SystemOrganization addCategory: #'Collections-Sequenceable'!
+ SystemOrganization addCategory: #'Collections-SortFunctions'!
  SystemOrganization addCategory: #'Collections-Stack'!
  SystemOrganization addCategory: #'Collections-Streams'!
  SystemOrganization addCategory: #'Collections-Strings'!
  SystemOrganization addCategory: #'Collections-Support'!
  SystemOrganization addCategory: #'Collections-Text'!
  SystemOrganization addCategory: #'Collections-Unordered'!
  SystemOrganization addCategory: #'Collections-Weak'!

Item was changed:
+ ----- Method: BlockClosure>>asSortFunction (in category '*Collections-SortFunctions-converting') -----
- ----- Method: BlockClosure>>asSortFunction (in category '*Collections-Support-sorting') -----
  asSortFunction
+ 	"Return a SortFunction around the receiver. If the receiver is a 2 arg block, it is assumed it will do the collation directly itself, returning -1, 0, or 1. If the receiver is a one arg block, it will be evaluated for each a and b and of the sort input, and the result of sending <=> to those will be used"
+ 	
+ 	self numArgs = 1 ifTrue: [^PropertySortFunction property: self].
+ 	self numArgs = 2 ifTrue: [^CollatorBlockFunction usingBlock: self].
  
+ 	self error: 'Cant be converted to sort function. It should has one or two args'	!
- 	^self ascending!

Item was changed:
+ ----- Method: BlockClosure>>ascending (in category '*Collections-SortFunctions-converting') -----
- ----- Method: BlockClosure>>ascending (in category '*Collections-Support-sorting') -----
  ascending
  	"Return a SortFunction around the receiver. If the receiver is a 2 arg block, it is assumed it will do the collation directly itself, returning -1, 0, or 1. If the receiver is a one arg block, it will be evaluated for each a and b and of the sort input, and the result of sending <=> to those will be used."
  
+ 	^self asSortFunction!
- 	| function |
- 	function := SortFunction ascend.
- 	self numArgs = 1 ifTrue: [function monadicBlock: self].
- 	self numArgs = 2 ifTrue: [function collator: self].
- 	^function!

Item was added:
+ ----- Method: BlockClosure>>collatedBy: (in category '*Collections-SortFunctions-converting') -----
+ collatedBy: aSortFunction
+ 	"Return a SortFunction around the receiver. If the receiver is a 2 arg block, it is assumed it will do the collation directly itself, returning -1, 0, or 1. If the receiver is a one arg block, it will be evaluated for each a and b and of the sort input, and the result of using aSortFunction on those will be used"
+ 	
+ 	self numArgs = 1 ifTrue: [^PropertySortFunction property: self collatedWith: aSortFunction asSortFunction].
+ 	self error: 'Cant be converted to sort function. It should hava one arg'	!

Item was changed:
+ ----- Method: BlockClosure>>descending (in category '*Collections-SortFunctions-converting') -----
- ----- Method: BlockClosure>>descending (in category '*Collections-Support-sorting') -----
  descending
  	"Opposite direction as ascending."
  
+ 	^self asSortFunction reversed!
- 	^self ascending toggleDirection!

Item was changed:
+ ComposedSortFunction subclass: #ChainedSortFunction
+ 	instanceVariableNames: 'nextFunction'
- SortFunction subclass: #ChainedSortFunction
- 	instanceVariableNames: 'next'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Collections-SortFunctions'!
- 	category: 'Collections-Support'!
  
+ !ChainedSortFunction commentStamp: 'nice 11/7/2017 22:14' prior: 0!
+ I add to my parent the idea of a "next" function to use when two objects are equal by my primary sort function.
- !ChainedSortFunction commentStamp: 'nice 3/13/2014 22:25' prior: 0!
- I add to my parent the idea of a "next" function to use when two objects are equal by my particular collator.
  
  Usage
  
  SortFunctions can be chained together in primary, secondary, tertiary, etc order using the comma method. Consider a sequence of customer objects, where each customer object responds to the messages firstName, lastName, and age. If we want to sort them lastName first, then firstName, and finally oldest first, we would use an expression like:
  
  customers sort: #lastName ascending, #firstName ascending, #age descending
  
  As noted in my super's comment, unary symbols or single arg blocks can be used. One can omit the the ascending methods on arguments (not the receiver), it will default blocks or symbols to be ascending if none is specified. In other words, the above expression could be simplified slightly as
  
  customers sort: #lastName ascending, #firstName, #age descending
  
  (note the missing ascending on the #firstName argument)
  
  Instance Variables
+ 	baseSortFunction	<SortFunction> the primary SortFunction to collate given objects
+ 	next	Function	<SortFunction>	the next SortFunction to evaluate in the event primary collation results are equal values!
- 	next	<SortFunction>	the next SortFunction to evaluate in the event my evaluator results in equal values.
- 
- !

Item was added:
+ ----- Method: ChainedSortFunction class>>startWith:then: (in category 'instance creation') -----
+ startWith: aSortFunction then: nextSortFunction
+ 	^self new
+ 		baseSortFunction: aSortFunction;
+ 		nextFunction: nextSortFunction!

Item was changed:
  ----- Method: ChainedSortFunction>>, (in category 'converting') -----
  , aSortFunction
  
+ 	^self class startWith: baseSortFunction then: nextFunction , aSortFunction!
- 	self next: next , aSortFunction!

Item was added:
+ ----- Method: ChainedSortFunction>>= (in category 'comparing') -----
+ = anObject
+ 	"Answer whether the receiver and anObject represent the same object."
+ 
+ 	self == anObject
+ 		ifTrue: [ ^ true ].
+ 	self class = anObject class
+ 		ifFalse: [ ^ false ].
+ 	^ baseSortFunction = anObject baseSortFunction
+ 			and: [ nextFunction = anObject nextFunction ]!

Item was added:
+ ----- Method: ChainedSortFunction>>collate:with: (in category 'evaluating') -----
+ collate: anObject1 with: anObject2
+ 	"If the result of current function is 0, then pass on to the next function to work it out"
+ 
+ 	| result |
+ 	result := baseSortFunction collate: anObject1 with: anObject2.
+ 	^result isZero
+ 		ifTrue: [nextFunction collate: anObject1 with: anObject2.]
+ 		ifFalse: [result]!

Item was added:
+ ----- Method: ChainedSortFunction>>hash (in category 'comparing') -----
+ hash
+ 	"Answer an integer value that is related to the identity of the receiver."
+ 
+ 	^ super hash + nextFunction hash!

Item was removed:
- ----- Method: ChainedSortFunction>>next: (in category 'initialize-release') -----
- next: anObject
- 
- 	next := anObject!

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

Item was added:
+ ----- Method: ChainedSortFunction>>nextFunction: (in category 'accessing') -----
+ nextFunction: aSortFunction
+ 	nextFunction := aSortFunction!

Item was removed:
- ----- Method: ChainedSortFunction>>value:value: (in category 'evaluating') -----
- value: anObject value: bObject
- 	"Refinement of the parent behavior. If the result of my collator is 0, then pass on to the next variable to work it out."
- 
- 	| result |
- 	result := (collator value: anObject value: bObject) * direction.
- 	^result isZero
- 		ifTrue: [next value: anObject value: bObject]
- 		ifFalse: [result < 0]!

Item was added:
+ SortFunction subclass: #CollatorBlockFunction
+ 	instanceVariableNames: 'collatorBlock'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Collections-SortFunctions'!
+ 
+ !CollatorBlockFunction commentStamp: 'nice 11/5/2017 22:57' prior: 0!
+ A CollatorBlockFunction is a special SortFunction using a dyadic block to collate objects.
+ 
+ Instance Variables
+ 
+ 	collator	<Block>	a dyadic block that must return a -1, 0, or 1.!

Item was added:
+ ----- Method: CollatorBlockFunction class>>usingBlock: (in category 'instance creation') -----
+ usingBlock: twoArgsBlock
+ 	^self new
+ 		collatorBlock: twoArgsBlock!

Item was added:
+ ----- Method: CollatorBlockFunction>>= (in category 'comparing') -----
+ = anObject
+ 	"Answer whether the receiver and anObject represent the same object."
+ 
+ 	self == anObject
+ 		ifTrue: [ ^ true ].
+ 	self class = anObject class
+ 		ifFalse: [ ^ false ].
+ 	^collatorBlock = anObject collatorBlock!

Item was added:
+ ----- Method: CollatorBlockFunction>>collate:with: (in category 'evaluating') -----
+ collate: anObject1 with: anObject2
+ 
+ 	^collatorBlock value: anObject1 value: anObject2 !

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

Item was added:
+ ----- Method: CollatorBlockFunction>>collatorBlock: (in category 'accessing') -----
+ collatorBlock: aBlock
+ 	collatorBlock := aBlock!

Item was added:
+ ----- Method: CollatorBlockFunction>>hash (in category 'comparing') -----
+ hash
+ 	"Answer an integer value that is related to the identity of the receiver."
+ 
+ 	^ collatorBlock hash!

Item was removed:
- ----- Method: Collection>>median (in category 'math functions') -----
- median
- 	^ self asSortedCollection median!

Item was added:
+ SortFunction subclass: #ComposedSortFunction
+ 	instanceVariableNames: 'baseSortFunction'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Collections-SortFunctions'!
+ 
+ !ComposedSortFunction commentStamp: 'nice 11/7/2017 22:13' prior: 0!
+ A ComposedSortFunction is an abstract class wrapping over another SortFunction for the sake of composition.
+ 
+ Subclasses have to define the composition behavior via collate:with: message.
+ 
+ Instances variables:
+ 	baseSortFunction		<SortFunction>	the wrapped sort function!

Item was added:
+ ----- Method: ComposedSortFunction class>>on: (in category 'instance creation') -----
+ on: aSortFunction
+ 	^self new baseSortFunction: aSortFunction!

Item was added:
+ ----- Method: ComposedSortFunction>>= (in category 'comparing') -----
+ = aSortFunction
+ 	self == aSortFunction ifTrue: [ ^true ].
+ 	^self class = aSortFunction class and: [ baseSortFunction = aSortFunction baseSortFunction ]!

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

Item was added:
+ ----- Method: ComposedSortFunction>>baseSortFunction: (in category 'accessing') -----
+ baseSortFunction: aSortFunction
+ 	baseSortFunction := aSortFunction!

Item was added:
+ ----- Method: ComposedSortFunction>>hash (in category 'comparing') -----
+ hash
+ 	^baseSortFunction hash hashMultiply!

Item was added:
+ ----- Method: ComposedSortFunction>>initialize (in category 'initailize-release') -----
+ initialize
+ 	super initialize.
+ 	baseSortFunction := self class default!

Item was added:
+ SortFunction subclass: #DefaultSortFunction
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Collections-SortFunctions'!
+ 
+ !DefaultSortFunction commentStamp: 'nice 11/7/2017 23:43' prior: 0!
+ A DefaultSortFunction is a collator using the default <=> operator.
+ It is known to work on String and Magnitude.
+ 
+ It is generally not usefull to create a new instance, and the recommended pattern is to use the single instance available by sending the message SortFunction default .
+ 
+ For other objects  that don't understand threeWayCompareTo: it is necessary to use a custom SortFunction rather than the default one.
+ !

Item was added:
+ ----- Method: DefaultSortFunction class>>initialize (in category 'class initialization') -----
+ initialize
+ 	Default := self new!

Item was added:
+ ----- Method: DefaultSortFunction class>>new (in category 'instance creation') -----
+ new
+ 	^UniqueInstance ifNil: [self basicNew initialize]!

Item was added:
+ ----- Method: DefaultSortFunction>>collate:with: (in category 'evaluating') -----
+ collate: anObject with: anotherObject
+ 	^anObject <=> anotherObject!

Item was added:
+ ComposedSortFunction subclass: #PropertySortFunction
+ 	instanceVariableNames: 'property'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Collections-SortFunctions'!
+ 
+ !PropertySortFunction commentStamp: 'nice 11/5/2017 22:36' prior: 0!
+ A PropertySortFunction is a SortFunction for sorting by a specific property.
+ 
+ Instance Variables
+ 	collator	<SortFunction>	the SortFunction to be used for sorting the properties
+ 	property <Symbol | Block> a valuable returning the value of property for objects to be sorted!

Item was added:
+ ----- Method: PropertySortFunction class>>property: (in category 'instance creation') -----
+ property: selectorOrOneArgBlock
+ 	^self new 
+ 		property: selectorOrOneArgBlock!

Item was added:
+ ----- Method: PropertySortFunction class>>property:collatedWith: (in category 'instance creation') -----
+ property: selectorOrOneArgBlock collatedWith: aSortFunction
+ 	^self new 
+ 		property: selectorOrOneArgBlock;
+ 		baseSortFunction: aSortFunction!

Item was added:
+ ----- Method: PropertySortFunction>>= (in category 'comparing') -----
+ = anObject
+ 	"Answer whether the receiver and anObject represent the same object."
+ 
+ 	self == anObject
+ 		ifTrue: [ ^ true ].
+ 	self class = anObject class
+ 		ifFalse: [ ^ false ].
+ 	^ baseSortFunction = anObject baseSortFunction
+ 		and: [ property = anObject property ]!

Item was added:
+ ----- Method: PropertySortFunction>>collate:with: (in category 'evaluating') -----
+ collate: anObject with: another
+ 	"Answer the collation order of anObject and another based on the property."
+ 	^ baseSortFunction collate: (property value: anObject) with: (property value: another)!

Item was added:
+ ----- Method: PropertySortFunction>>hash (in category 'comparing') -----
+ hash
+ 	"Answer an integer value that is related to the identity of the receiver."
+ 
+ 	^ super hash bitXor: property hash!

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

Item was added:
+ ----- Method: PropertySortFunction>>property: (in category 'accessing') -----
+ property: aValuable
+ 	property := aValuable!

Item was added:
+ ----- Method: PropertySortFunction>>undefinedFirst (in category 'converting') -----
+ undefinedFirst
+ 	"apply on the property"
+ 	^self class
+ 		property: property
+ 		collatedWith: baseSortFunction undefinedFirst!

Item was added:
+ ----- Method: PropertySortFunction>>undefinedLast (in category 'converting') -----
+ undefinedLast
+ 	"apply on the property"
+ 	^self class
+ 		property: property
+ 		collatedWith: baseSortFunction undefinedLast!

Item was added:
+ ComposedSortFunction subclass: #ReverseSortFunction
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Collections-SortFunctions'!
+ 
+ !ReverseSortFunction commentStamp: 'nice 11/6/2017 21:54' prior: 0!
+ A ReverseSortFunction wraps over another SortFunction so as to sort in reverse order.!

Item was added:
+ ----- Method: ReverseSortFunction>>collate:with: (in category 'evaluating') -----
+ collate: anObject with: another
+ 	^(baseSortFunction collate: anObject with: another) negated!

Item was added:
+ ----- Method: ReverseSortFunction>>reversed (in category 'converting') -----
+ reversed
+ 	^baseSortFunction!

Item was added:
+ ----- Method: ReverseSortFunction>>toggleDirection (in category 'converting') -----
+ toggleDirection
+ 	^collator!

Item was added:
+ ----- Method: ReverseSortFunction>>undefinedFirst (in category 'converting') -----
+ undefinedFirst
+ 	"apply on the original"
+ 	^baseSortFunction undefinedLast reversed!

Item was added:
+ ----- Method: ReverseSortFunction>>undefinedLast (in category 'converting') -----
+ undefinedLast
+ 	"apply on the original"
+ 	^baseSortFunction undefinedFirst reversed!

Item was changed:
  Object subclass: #SortFunction
+ 	instanceVariableNames: ''
+ 	classVariableNames: 'Default'
- 	instanceVariableNames: 'direction collator'
- 	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Collections-SortFunctions'!
- 	category: 'Collections-Support'!
  
+ !SortFunction commentStamp: 'nice 11/5/2017 22:52' prior: 0!
- !SortFunction commentStamp: 'nice 3/13/2014 22:24' prior: 0!
  I am intended to be used in place of two arg sort blocks.
  
  Usage
  
  In the following example, an ascending SortFunction is created based on the result of the #first message send to each object.
  #(#(1 2) #(2 3) #(0 0)) sorted: #first ascending.
  
  To sort by the #last element, but descending, the following would be used:
  #(#(1 2) #(2 3) #(0 0)) sorted: #last descending.
  
  One can use blocks as well. The following sorts in descending order, the sub elements based on the sum of their values.
  | sumBlock |
  sumBlock := [:sequence | sequence inject: 0 into: [:sum :each | sum + each]].
  #(#(1 2) #(2 3) #(0 0)) sorted: sumBlock descending.
  
  One can even use 2 arg blocks, for those cases where the function isn't expressible with objects that respond to < and =. The only catch, is that such a function has to return not true and false, but instead a collation order, values of -1 (for before), 0 (the same) or 1 (to follow). For example:
  
  | oddBlock |
  oddBlock :=
  		[:a :b |
  		a odd = b odd ifTrue: [0] ifFalse: [a odd ifTrue: [-1] ifFalse: [1]]].
  #(1 5 1 3 2 7 9 4 6) asSortedCollection: oddBlock descending
  
  Instance Variables
+ 	collator	<SortFunction>	This is the object responsible for collating objetcs, generally a SortFunction.
- 	collator	<BlockClosure>	This is the collation function that must return a -1, 0, or 1. It is usually composed by an initialization method such as sendMessage: or monadicBlock:, but may be set directly.
- 	direction	<SmallInteger>	1 for ascending, -1 for descending
  
  !

Item was removed:
- ----- Method: SortFunction class>>ascend (in category 'instance creation') -----
- ascend
- 
- 	^self new ascend!

Item was added:
+ ----- Method: SortFunction class>>default (in category 'accessing') -----
+ default
+ 	^Default!

Item was removed:
- ----- Method: SortFunction class>>descend (in category 'instance creation') -----
- descend
- 
- 	^self new descend!

Item was changed:
  ----- Method: SortFunction>>, (in category 'converting') -----
  , aSortFunction
  	"Return a new SortFunction which is the concatenation of aSortFunction to me, I will be the primary sort, but if I compare equal, I will defer to the argument."
  
+ 	^ChainedSortFunction startWith: self then: aSortFunction asSortFunction!
- 	^(ChainedSortFunction new)
- 		collator: collator;
- 		direction: direction;
- 		next: aSortFunction asSortFunction!

Item was removed:
- ----- Method: SortFunction>>ascend (in category 'initailize-release') -----
- ascend
- 
- 	direction := 1!

Item was added:
+ ----- Method: SortFunction>>collate:with: (in category 'evaluating') -----
+ collate: value1 with: value2
+ 	"answer the collation order for the two values -1,0 or 1"
+ 	
+ 	^self subclassResponsibility!

Item was removed:
- ----- Method: SortFunction>>collator: (in category 'initailize-release') -----
- collator: a2ArgBlock
- 	"a2ArgBlock MUST return the collation order, -1, 0, or 1"
- 
- 	collator := a2ArgBlock!

Item was removed:
- ----- Method: SortFunction>>descend (in category 'initailize-release') -----
- descend
- 
- 	direction := -1!

Item was removed:
- ----- Method: SortFunction>>direction: (in category 'initailize-release') -----
- direction: anInteger
- 
- 	direction := anInteger!

Item was removed:
- ----- Method: SortFunction>>isAscending (in category 'testing') -----
- isAscending
- 
- 	^direction = 1!

Item was removed:
- ----- Method: SortFunction>>isDescending (in category 'testing') -----
- isDescending
- 
- 	^direction = -1!

Item was removed:
- ----- Method: SortFunction>>monadicBlock: (in category 'initailize-release') -----
- monadicBlock: aSingleArgBlock
- 	"Initialze the receiver's collation block to compare the results of evaluating aSingleArgBlock with each argument, and then collate the return values with the <=> method."
- 
- 	collator := [:a :b | (aSingleArgBlock value: a) <=> (aSingleArgBlock value: b)]!

Item was added:
+ ----- Method: SortFunction>>reversed (in category 'converting') -----
+ reversed
+ 	"Return new sort function with reverse sort order."
+ 
+ 	^ReverseSortFunction on: self!

Item was removed:
- ----- Method: SortFunction>>sendMessage: (in category 'initailize-release') -----
- sendMessage: aUnarySymbol
- 	"Initialze the receiver's collation block to compare the results of sending aUnarySymbol to each argument, and then collate them with the <=> method."
- 
- 	collator := [:a :b | (a perform: aUnarySymbol) <=> (b perform: aUnarySymbol)]!

Item was removed:
- ----- Method: SortFunction>>toggleDirection (in category 'converting') -----
- toggleDirection
- 	"Invert my current direction, if I'm currently ascending, this will cause me to be descending now, and vice-versa."
- 
- 	direction := direction * -1!

Item was added:
+ ----- Method: SortFunction>>undefinedFirst (in category 'converting') -----
+ undefinedFirst
+ 	"Return a new SortFunction that sort all the nil first, an non nil with myself."
+ 	^(UndefinedSortFunction on: self) undefinedFirst!

Item was added:
+ ----- Method: SortFunction>>undefinedLast (in category 'converting') -----
+ undefinedLast
+ 	"Return a new SortFunction that sort all the nil last, an non nil with myself."
+ 	^(UndefinedSortFunction on: self) undefinedLast!

Item was changed:
  ----- Method: SortFunction>>value:value: (in category 'evaluating') -----
  value: anObject value: bObject
  	"Masquerade as a two argument block, used by many of the sorting APIs, by returning whether anObject should be placed before bObject or not."
  
  	| result |
+ 	result := (self collate: anObject with: bObject).
- 	result := (collator value: anObject value: bObject) * direction.
  	^result <= 0!

Item was changed:
+ ----- Method: Symbol>>asSortFunction (in category '*Collections-SortFunctions-converting') -----
- ----- Method: Symbol>>asSortFunction (in category 'sorting') -----
  asSortFunction
+ 	"Return a SortFunction around the receiver, where the receiver will be used as a unary message to send to both a and b during sorting, and then the result of said send will be collated in ascending order using the <=> method."
+ 	"#('abc' 'de' 'fghi') sorted: #size ascending >>> #('de' 'abc' 'fghi')"
  
+ 	^PropertySortFunction property: self!
- 	^self ascending!

Item was changed:
+ ----- Method: Symbol>>ascending (in category '*Collections-SortFunctions-converting') -----
- ----- Method: Symbol>>ascending (in category 'sorting') -----
  ascending
  	"Return a SortFunction around the receiver, where the receiver will be used as a unary message to send to both a and b during sorting, and then the result of said send will be collated in ascending order using the <=> method."
+ 	"#('abc' 'de' 'fghi') sorted: #size ascending >>> #('de' 'abc' 'fghi')"
- 	"Example: #('abc'  'de' 'fghi') sorted: #size asscending"
  
+ 	^self asSortFunction !
- 	^SortFunction ascend sendMessage: self!

Item was added:
+ ----- Method: Symbol>>collatedBy: (in category '*Collections-SortFunctions-converting') -----
+ collatedBy: aSortFunction
+ 	"Return a SortFunction around the receiver, where the receiver will be used as a unary message to send to both a and b during sorting, and then the result of said send will be collated iusing aSortFunction."
+ 	"#('abc' 'de' 'fghi') sorted: (#size collatedWith: [:e|e bitAnd: 1]) , #size >>> #( 'de' 'fghi' 'abc')"
+ 
+ 	^PropertySortFunction property: self collatedWith: aSortFunction asSortFunction!

Item was changed:
+ ----- Method: Symbol>>descending (in category '*Collections-SortFunctions-converting') -----
- ----- Method: Symbol>>descending (in category 'sorting') -----
  descending
  	"Return a SortFunction around the receiver, where the receiver will be used as a unary message to send to both a and b during sorting, and then the result of said send will be collated in descending order using the <=> method."
+ 	"#('abc' 'de' 'fghi') sorted: #size ascending >>> #('fghi' 'abc' 'de')"
- 	"Example: #('abc'  'de' 'fghi') sorted: #size descending"
  
+ 	^self asSortFunction reversed!
- 	^SortFunction descend sendMessage: self!

Item was added:
+ ComposedSortFunction subclass: #UndefinedSortFunction
+ 	instanceVariableNames: 'direction'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Collections-SortFunctions'!
+ 
+ !UndefinedSortFunction commentStamp: 'nice 11/7/2017 22:16' prior: 0!
+ An  UndefinedSortFunction is a specialization usefull for sorting undefined objects (nil), either first or last according to direction.
+ The non nil objects are sorted according to the baseSortFunction defined in superclass.
+ 
+ instance variables:
+ 	direction	<Integer>	-1 for sorting nil first, 1 for sorting nil last!

Item was added:
+ ----- Method: UndefinedSortFunction>>= (in category 'comparing') -----
+ = anObject
+ 	"Answer whether the receiver and anObject represent the same object."
+ 
+ 	self == anObject
+ 		ifTrue: [ ^ true ].
+ 	self class = anObject class
+ 		ifFalse: [ ^ false ].
+ 	^ baseSortFunction = anObject baseSortFunction
+ 		and: [ direction = anObject direction ]!

Item was added:
+ ----- Method: UndefinedSortFunction>>collate:with: (in category 'evaluating') -----
+ collate: anObject with: another
+ 	"Answer the collation order of anObject and another, with nil first or last according to direction"
+ 	anObject ifNil: [^another ifNil: [0] ifNotNil: [direction]].
+ 	another ifNil: [^direction negated].
+ 	^baseSortFunction collate: anObject with: another!

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

Item was added:
+ ----- Method: UndefinedSortFunction>>hash (in category 'comparing') -----
+ hash
+ 	"Answer an integer value that is related to the identity of the receiver."
+ 
+ 	^ super hash bitXor: direction hash!

Item was added:
+ ----- Method: UndefinedSortFunction>>initialize (in category 'initailize-release') -----
+ initialize
+ 	super initialize.
+ 	direction := -1!

Item was added:
+ ----- Method: UndefinedSortFunction>>undefinedFirst (in category 'initailize-release') -----
+ undefinedFirst
+ 	direction := -1!

Item was added:
+ ----- Method: UndefinedSortFunction>>undefinedLast (in category 'initailize-release') -----
+ undefinedLast
+ 	direction := 1!



More information about the Squeak-dev mailing list