[squeak-dev] The Inbox: Collections-nice.766.mcz

David T. Lewis lewis at mail.msen.com
Mon Nov 6 00:05:07 UTC 2017


Hi Nicolas,

I have only partly followed your discussion on the pharo list, and I am no expert in
this area. But the idea of having objects that clearly represent sort functions seems
like a good idea, if omly for purposes of making the intent of the functions clear.

Were you using a different name other than 'SortFunction' before? I don't entirely
like the use of 'Function" in the class names, but that is a false objection because
the classes actually *are* functions. Still it still seems a bit too mmuch like FORTRAN
to me so I would not mind a name more like 'Collator' or 'Sorter' if that is what you
originally had in mind.

The use of #<=> seems important for clarifying the sort behavior, so I would think
that this is a good thing to do.

Way off topic, but if we can have an elegant implementation of two-state Boolean
in Smalltalk, I wonder if there might be an equally elegant way to express the
concept of a three-state object as answered by #<=> and possibly other contexts?
GreaterThan/LessThan/SameAs, Yes/No/Maybe, True/False/NotSure, and so on.

Of course my all time favorite implementation of elegant logic is this one:
http://lists.squeakfoundation.org/pipermail/squeak-dev/2017-January/192927.html

Dave

On Sun, Nov 05, 2017 at 10:52:50PM +0000, commits at source.squeak.org wrote:
> Nicolas Cellier uploaded a new version of Collections to project The Inbox:
> http://source.squeak.org/inbox/Collections-nice.766.mcz
> 
> ==================== Summary ====================
> 
> Name: Collections-nice.766
> Author: nice
> Time: 5 November 2017, 11:52:17.600192 pm
> UUID: 0008f12f-55e5-4c73-abcd-0e082a6013d1
> Ancestors: Collections-bp.765
> 
> Revisit the SortFunction in the spirit of refactorings started by Denis Kudriashov in Pharo, but pushing them further.
> 
> SortFunction are by nature composable.
> So make SortFunction abstract, and add different subclasses for different kind of composition.
> 
> Add the ability of sorting by properties with an odd collator rather than default <=>, which was missing in original implementation
> 
> Also add the ability to sort undefinedFirst as proposed by Denis.
> 
> Reversing the direction is now implemented with a subclass.
> 
> And the main SortFunction message is now collate:with: which must answer the collation order (-1,0,1).
> 
> =============== Diff against Collections-bp.765 ===============
> 
> Item was changed:
>   ----- 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 numArgs = 1 ifTrue: [^PropertySortFunction property: self].
> + 	self numArgs = 2 ifTrue: [^CollatorBlockFunction new collator: self].
> + 	self error: 'a block for sorting should have 1 or 2 parameters'!
> - 	| function |
> - 	function := SortFunction ascend.
> - 	self numArgs = 1 ifTrue: [function monadicBlock: self].
> - 	self numArgs = 2 ifTrue: [function collator: self].
> - 	^function!
> 
> Item was added:
> + ----- Method: BlockClosure>>sortedWith: (in category '*Collections-Support-sorting') -----
> + sortedWith: aSortFunction
> + 	"Return a SortFunction around the receiver.
> + 	The receiver is a one arg block.
> + 	It will be evaluated for each a and b and of the sort input, and answer the result of collating those with aSortFunction."
> + 
> + 	self numArgs = 1 ifTrue: [^PropertySortFunction property: self sortedWith: aSortFunction asSortFunction].
> + 	self error: 'a block for sorting should have 1 or 2 parameters'!
> 
> Item was changed:
>   SortFunction subclass: #ChainedSortFunction
>   	instanceVariableNames: 'next'
>   	classVariableNames: ''
>   	poolDictionaries: ''
>   	category: 'Collections-Support'!
>   
> + !ChainedSortFunction commentStamp: 'nice 11/5/2017 22:35' prior: 0!
> - !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
> + 	collator	<SortFunction>	the first SortFunction.
> + 	next	<SortFunction>	the next SortFunction to evaluate in the event the first results in equal values.
> - 	next	<SortFunction>	the next SortFunction to evaluate in the event my evaluator results in equal values.
>   
>   !
> 
> Item was changed:
>   ----- Method: ChainedSortFunction>>, (in category 'converting') -----
>   , aSortFunction
>   
> + 	^self copy next: next , aSortFunction!
> - 	self next: next , aSortFunction!
> 
> Item was added:
> + ----- Method: ChainedSortFunction>>collate:with: (in category 'evaluating') -----
> + collate: anObject with: 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 collate: anObject with: bObject).
> + 	^result isZero
> + 		ifTrue: [next collate: anObject with: bObject]
> + 		ifFalse: [result]!
> 
> 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: ''
> + 	classVariableNames: ''
> + 	poolDictionaries: ''
> + 	category: 'Collections-Support'!
> + 
> + !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>>collate:with: (in category 'evaluating') -----
> + collate: value1 with: value2
> + 	^collator value: value1 value: value2!
> 
> Item was removed:
> - ----- Method: Collection>>median (in category 'math functions') -----
> - median
> - 	^ self asSortedCollection median!
> 
> Item was added:
> + SortFunction subclass: #DefaultSortFunction
> + 	instanceVariableNames: ''
> + 	classVariableNames: 'UniqueInstance'
> + 	poolDictionaries: ''
> + 	category: 'Collections-Support'!
> + 
> + !DefaultSortFunction commentStamp: 'nice 11/5/2017 21:45' prior: 0!
> + A DefaultSortFunction is a collator using the default <=> operator.
> + It is known to work on String and Magnitude.
> + 
> + !
> 
> 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: value1 with: value2
> + 	^value1 <=> value2!
> 
> Item was added:
> + ----- Method: DefaultSortFunction>>initialize (in category 'initailize-release') -----
> + initialize
> + 	collator := #<=>!
> 
> Item was added:
> + SortFunction subclass: #PropertySortFunction
> + 	instanceVariableNames: 'property'
> + 	classVariableNames: ''
> + 	poolDictionaries: ''
> + 	category: 'Collections-Support'!
> + 
> + !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: aValuable
> + 	^self new property: aValuable!
> 
> Item was added:
> + ----- Method: PropertySortFunction class>>property:sortedWith: (in category 'instance creation') -----
> + property: aValuable sortedWith: aSortFunction
> + 	^self new property: aValuable; collator: aSortFunction!
> 
> Item was added:
> + ----- Method: PropertySortFunction>>collate:with: (in category 'evaluating') -----
> + collate: value1 with: value2
> + 	^collator collate: (property value: value1) with: (property value: value2)!
> 
> Item was added:
> + ----- Method: PropertySortFunction>>property: (in category 'initailize-release') -----
> + property: aValuable
> + 	property := aValuable!
> 
> Item was added:
> + ----- Method: PropertySortFunction>>undefinedFirst (in category 'converting') -----
> + undefinedFirst
> + 	"apply on the property"
> + 	^self class
> + 		property: property
> + 		sortedWith: (UndefinedSortFunction new collator: collator) undefinedFirst!
> 
> Item was added:
> + ----- Method: PropertySortFunction>>undefinedLast (in category 'converting') -----
> + undefinedLast
> + 	"apply on the property"
> + 	^self class
> + 		property: property
> + 		sortedWith: (UndefinedSortFunction new collator: collator) undefinedLast!
> 
> Item was added:
> + SortFunction subclass: #ReverseSortFunction
> + 	instanceVariableNames: ''
> + 	classVariableNames: ''
> + 	poolDictionaries: ''
> + 	category: 'Collections-Support'!
> + 
> + !ReverseSortFunction commentStamp: 'nice 11/5/2017 22:40' prior: 0!
> + A ReverseSortFunction is reversing the order of original sortFunction
> + 
> + Instance Variables
> + 	collator	<SortFunction>	the original SortFunction.
> + !
> 
> Item was added:
> + ----- Method: ReverseSortFunction>>collate:with: (in category 'evaluating') -----
> + collate: value1 with: value2
> + 	^(collator collate: value1 with: value2) negated!
> 
> 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"
> + 	^collator undefinedFirst toggleDirection!
> 
> Item was added:
> + ----- Method: ReverseSortFunction>>undefinedLast (in category 'converting') -----
> + undefinedLast
> + 	"apply on the original"
> + 	^collator undefinedLast toggleDirection!
> 
> Item was changed:
>   Object subclass: #SortFunction
> + 	instanceVariableNames: 'collator'
> - 	instanceVariableNames: 'direction collator'
>   	classVariableNames: ''
>   	poolDictionaries: ''
>   	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 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 new)
> + 		collator: self;
> - 		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 changed:
>   ----- Method: SortFunction>>collator: (in category 'initailize-release') -----
> + collator: aSortFunction
> + 	"Used by subclasses for composition."
> - collator: a2ArgBlock
> - 	"a2ArgBlock MUST return the collation order, -1, 0, or 1"
>   
> + 	collator := aSortFunction!
> - 	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 added:
> + ----- Method: SortFunction>>initialize (in category 'initailize-release') -----
> + initialize
> + 	"set the default collator"
> + 	
> + 	collator := DefaultSortFunction new!
> 
> 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 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 changed:
>   ----- Method: SortFunction>>toggleDirection (in category 'converting') -----
>   toggleDirection
> + 	^ReverseSortFunction new collator: self!
> - 	"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
> + 	^(UndefinedSortFunction new collator: self) undefinedFirst!
> 
> Item was added:
> + ----- Method: SortFunction>>undefinedLast (in category 'converting') -----
> + undefinedLast
> + 	^(UndefinedSortFunction new collator: 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>>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."
>   	"Example: #('abc'  'de' 'fghi') sorted: #size asscending"
>   
> + 	^PropertySortFunction property: self!
> - 	^SortFunction ascend sendMessage: self!
> 
> Item was changed:
>   ----- 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."
>   	"Example: #('abc'  'de' 'fghi') sorted: #size descending"
>   
> + 	^(PropertySortFunction property: self) toggleDirection!
> - 	^SortFunction descend sendMessage: self!
> 
> Item was added:
> + ----- Method: Symbol>>sortedWith: (in category 'sorting') -----
> + sortedWith: 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 in descending order using the aSortFunction."
> + 	"Example: #('abc'  'de' 'fghi') sorted: (#size collatedBy: #<=> asSortFunction)"
> + 
> + 	^PropertySortFunction property: self sortedWith: aSortFunction asSortFunction!
> 
> Item was added:
> + SortFunction subclass: #UndefinedSortFunction
> + 	instanceVariableNames: 'direction'
> + 	classVariableNames: ''
> + 	poolDictionaries: ''
> + 	category: 'Collections-Support'!
> + 
> + !UndefinedSortFunction commentStamp: 'nice 11/5/2017 23:18' prior: 0!
> + An UndefinedSortFunction is a specialization of SortFunction for sorting UndefinedObject either first or last.
> + 
> + Instance Variables
> + 	collator			<SortFunction>	the SortFunction to be used for non nil values
> + 	direction:		<Integer>			-1 if nil is sorted first, 1 if sorted last
> + !
> 
> Item was added:
> + ----- Method: UndefinedSortFunction>>collate:with: (in category 'evaluating') -----
> + collate: value1 with: value2
> + 	value1 ifNil: [^value2 ifNil: [0] ifNotNil: [direction]].
> + 	value2 ifNil: [^direction negated].
> + 	^collator collate: value1 with: value2!
> 
> 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