<div dir="ltr"><div dir="ltr"><br></div><br><div class="gmail_quote"><div dir="ltr" class="gmail_attr">On Wed, Feb 19, 2020 at 10:30 AM Levente Uzonyi <<a href="mailto:leves@caesar.elte.hu">leves@caesar.elte.hu</a>> wrote:<br></div><blockquote class="gmail_quote" style="margin:0px 0px 0px 0.8ex;border-left-width:1px;border-left-style:solid;border-left-color:rgb(204,204,204);padding-left:1ex">Before 2010, #sorted: and #sorted didn't exist. #sort and #sort: were only <br>
implemented by ArrayedCollection but were rarely used.<br>
The most common ways to sort a collection was by the means of <br>
#asSortedCollection, #asSortedCollection:, #sortBy: and #asSortedArray.<br>
Since then, these senders have all been rewritten to use the newer <br>
methods.<br>
<br>
#(sort sorted sort: sorted:) collect: [ :each |<br>
        each -> (<br>
                (SystemNavigation default allCallsOn: each) count: [ :ea |<br>
                        (ea actualClass inheritsFrom: TestCase) not  ]) ]. <br>
{<br>
        #sort->123 .<br>
        #sorted->58 .<br>
        #sort:->111 .<br>
        #sorted:->62<br>
}<br>
<br>
The above distribution tells me that it's twice as common to sort the <br>
receiver than to sort a copy. But passing a custom sorter is about as <br>
common as using the default sorter.<br>
<br>
Before 2014, #asSortFunction didn't exist. You had to use a sorter block, <br>
a symbol, or nil.<br>
SortFunctions are much more comfortable to use than regular sort blocks, <br>
but they have some impact on performance. They are often times created by <br>
sending #ascending or #descending to a block or a symbol, which is another <br>
reason why #asSortFunction doesn't have too many senders.<br>
<br>
Anyway, it's no wonder why SortFunctions are not widely used: they are <br>
fairly new, and the complex sorters, where they really shine, are not that <br>
common.<br>
<br>
<br>
Levente<br>
<br>
P.S.: Since we're discussing #allMethodCategoriesIntegratedThrough:, it <br>
should use #withAllSuperclassesDo: instead of #withAllSuperclasses and <br>
#do:.<br></blockquote><div><br></div><div>+1.  I just fixed the bug that I got bit by in the debugger by making the most minimal changes I could think of.  i apologies for not giving this more thought.</div><div> </div><blockquote class="gmail_quote" style="margin:0px 0px 0px 0.8ex;border-left-width:1px;border-left-style:solid;border-left-color:rgb(204,204,204);padding-left:1ex">
<br>
<br>
On Wed, 19 Feb 2020, John Pfersich via Squeak-dev wrote:<br>
<br>
> That snippet might be useful but it’s not used much in the code base. sorted: is only used 71 times, and asSortFunction is only used 9 times. And the combination is even rarer. So if you’re like most programmers, you wouldn’t<br>
> have seen either selector.<br>
> <br>
> /————————————————————/For encrypted mail use jgpfersich@protonmail.comGet a free account at ProtonMail.com<br>
> Web: <a href="https://objectnets.net" rel="noreferrer" target="_blank">https://objectnets.net</a> and <a href="https://objectnets.org" rel="noreferrer" target="_blank">https://objectnets.org</a><br>
> <a href="https://datascilv.com" rel="noreferrer" target="_blank">https://datascilv.com</a> <a href="https://datascilv.org" rel="noreferrer" target="_blank">https://datascilv.org</a><br>
> <br>
><br>
>       On Feb 19, 2020, at 01:08, Thiede, Christoph <<a href="mailto:Christoph.Thiede@student.hpi.uni-potsdam.de" target="_blank">Christoph.Thiede@student.hpi.uni-potsdam.de</a>> wrote:<br>
> <br>
><br>
>       Hi Marcel,<br>
> <br>
><br>
>       I did *not* mean:<br>
> <br>
> ^aColl asArray sorted: ...<br>
> I *did* mean:<br>
> ^aColl sorted: ...<br>
> <br>
> Very minor, but what else do we have #sorted: for? Law of Demeter and so on ... :-)<br>
> <br>
> Best,<br>
> Christoph<br>
> <br>
> _________________________________________________________________________________________________________________________________________________________________________________________________________________________________<br>
> Von: Squeak-dev <<a href="mailto:squeak-dev-bounces@lists.squeakfoundation.org" target="_blank">squeak-dev-bounces@lists.squeakfoundation.org</a>> im Auftrag von Taeumel, Marcel<br>
> Gesendet: Mittwoch, 19. Februar 2020 09:52:34<br>
> An: John Pfersich via Squeak-dev; <a href="mailto:packages@lists.squeakfoundation.org" target="_blank">packages@lists.squeakfoundation.org</a><br>
> Betreff: Re: [squeak-dev] The Trunk: Kernel-eem.1296.mcz  <br>
> Since #asArray did already a copy, there is no need to call #sorted: here.<br>
> Best,<br>
> Marcel<br>
><br>
>       Am 19.02.2020 09:44:40 schrieb Thiede, Christoph <<a href="mailto:christoph.thiede@student.hpi.uni-potsdam.de" target="_blank">christoph.thiede@student.hpi.uni-potsdam.de</a>>:<br>
><br>
>       > +        ^aColl asArray sort: [:a :b | a asLowercase < b asLowercase]<br>
> <br>
> <br>
> Hm, shouldn't you prefer #sorted: here? :-)<br>
> aColl sorted: #asLowercase asSortFunction<br>
> Or maybe use a SortedCollection from the beginning ...<br>
> <br>
> _________________________________________________________________________________________________________________________________________________________________________________________________________________________________<br>
> Von: Squeak-dev <<a href="mailto:squeak-dev-bounces@lists.squeakfoundation.org" target="_blank">squeak-dev-bounces@lists.squeakfoundation.org</a>> im Auftrag von <a href="mailto:commits@source.squeak.org" target="_blank">commits@source.squeak.org</a> <<a href="mailto:commits@source.squeak.org" target="_blank">commits@source.squeak.org</a>><br>
> Gesendet: Mittwoch, 19. Februar 2020 04:43:19<br>
> An: <a href="mailto:squeak-dev@lists.squeakfoundation.org" target="_blank">squeak-dev@lists.squeakfoundation.org</a>; <a href="mailto:packages@lists.squeakfoundation.org" target="_blank">packages@lists.squeakfoundation.org</a><br>
> Betreff: [squeak-dev] The Trunk: Kernel-eem.1296.mcz  <br>
> Eliot Miranda uploaded a new version of Kernel to project The Trunk:<br>
> <a href="http://source.squeak.org/trunk/Kernel-eem.1296.mcz" rel="noreferrer" target="_blank">http://source.squeak.org/trunk/Kernel-eem.1296.mcz</a><br>
> <br>
> ==================== Summary ====================<br>
> <br>
> Name: Kernel-eem.1296<br>
> Author: eem<br>
> Time: 18 February 2020, 7:43:15.608431 pm<br>
> UUID: 78e95030-3521-4dd9-b26c-2c8c7939010b<br>
> Ancestors: Kernel-eem.1295, Kernel-tonyg.1293<br>
> <br>
> Fix a bug in allMethodCategoriesIntegratedThrough: which can cause an error in the Debugger when prompting to define a new method.<br>
> <br>
> Fix bugs in CompiledCode>>messagesDo:/selectorsDo: and define the former in terms of the latter (since the former is a misnomer).<br>
> <br>
> Fix a bug in the definition of CompiledMethod>>hasSameLiteralsAs: which should not be confused by the methodClass literal.<br>
> <br>
> Fix perform:with:with:with:with:with:'s comment.<br>
> <br>
> =============== Diff against Kernel-tonyg.1293 ===============<br>
> <br>
> Item was changed:<br>
>   ----- Method: Behavior>>instSpec (in category 'testing') -----<br>
>   instSpec<br>
>          "Answer the instance specification part of the format that defines what kind of object<br>
>           an instance of the receiver is.  The formats are<br>
>                          0       = 0 sized objects (UndefinedObject True False et al)<br>
>                          1       = non-indexable objects with inst vars (Point et al)<br>
>                          2       = indexable objects with no inst vars (Array et al)<br>
>                          3       = indexable objects with inst vars (Context BlockClosure AdditionalMethodState et al)<br>
>                          4       = weak indexable objects with inst vars (WeakArray et al)<br>
>                          5       = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)<br>
>                          6       = unused<br>
>                          7       = immediates (SmallInteger, Character)<br>
>                          8       = unused<br>
> +                        9       = 64-bit indexable      (DoubleWordArray et al)<br>
> +                10-11   = 32-bit indexable      (WordArray et al)                       (includes one odd bit, unused in 32-bit instances)<br>
> +                12-15   = 16-bit indexable      (DoubleByteArray et al)         (includes two odd bits, one unused in 32-bit instances)<br>
> +                16-23   = 8-bit indexable       (ByteArray et al)                       (includes three odd bits, one unused in 32-bit instances)<br>
> +                24-31   = compiled code (CompiledCode et al)            (includes three odd bits, one unused in 32-bit instances)<br>
> +<br>
> -                        9       = 64-bit indexable<br>
> -                10-11   = 32-bit indexable (Bitmap)                                     (plus one odd bit, unused in 32-bits)<br>
> -                12-15   = 16-bit indexable                                                      (plus two odd bits, one unused in 32-bits)<br>
> -                16-23   = 8-bit indexable                                                       (plus three odd bits, one unused in 32-bits)<br>
> -                24-31   = compiled methods (CompiledMethod)     (plus three odd bits, one unused in 32-bits)<br>
>           Note that in the VM instances also have a 5 bit format field that relates to their class's format.<br>
>           Formats 11, 13-15, 17-23 & 25-31 are unused in classes but used in instances to define the<br>
>           number of elements missing up to the slot size.  For example, a 2-byte ByteString instance<br>
> +         has format 18 in 32 bits, since its size is one 32-bit slot - 2 bytes ((18 bitAnd: 3) = 2), and<br>
> +         22 in 64 bits, since its size is one 64-bit slot - 6 bytes ((22 bitAnd: 7) = 6).<br>
> +         Formats 24-31 are for compiled code which is a combination of pointers and bytes.  The number of pointers is<br>
> +         determined by literal count field of the method header, which is the first field of the object and must be a SmallInteger.<br>
> +         The literal count field occupies the least significant 15 bits of the method header, allowing up to 32,767 pointer fields,<br>
> +         not including the header."<br>
> -         has format 18 in 32-bits, since its size is one 32-bit slot - 2 bytes ((18 bitAnd: 3) = 2), and<br>
> -         22 in 64 bits, since its size is one 64-bit slot - 6 bytes ((22 bitAnd: 7) = 6)."<br>
>          ^(format bitShift: -16) bitAnd: 16r1F!<br>
> <br>
> Item was changed:<br>
>   ----- Method: ClassDescription>>allMethodCategoriesIntegratedThrough: (in category 'accessing method dictionary') -----<br>
>   allMethodCategoriesIntegratedThrough: mostGenericClass<br>
>          "Answer a list of all the method categories of the receiver and all its superclasses, up through mostGenericClass"<br>
>  <br>
>          | aColl |<br>
> +        aColl := Set new.<br>
> -        aColl := OrderedCollection new.<br>
>          self withAllSuperclasses do:<br>
>                  [:aClass |<br>
> +                (aClass includesBehavior: mostGenericClass) ifTrue:<br>
> +                        [aColl addAll: aClass organization categories]].<br>
> -                        (aClass includesBehavior: mostGenericClass)<br>
> -                                ifTrue: [aColl addAll: aClass organization categories]].<br>
>          aColl remove: 'no messages' asSymbol ifAbsent: [].<br>
>  <br>
> +        ^aColl asArray sort: [:a :b | a asLowercase < b asLowercase]<br>
> -        ^aColl asSet asArray sort: [:a :b | a asLowercase < b asLowercase]<br>
>  <br>
>   "ColorTileMorph allMethodCategoriesIntegratedThrough: TileMorph"!<br>
> <br>
> Item was changed:<br>
>   ----- Method: CompiledCode>>messagesDo: (in category 'scanning') -----<br>
>   messagesDo: workBlock<br>
> +        "Evaluate aBlock with all the message selectors sent by me. Duplicate seletors are possible."<br>
> -        "Evaluate aBlock with all the message selectors sent by me. Duplicate sends possible."<br>
>  <br>
> +        "If anything should be deprecated it is messagesDo:; it can be an extension in AST/Refactoring.<br>
> +         This method enumerates over selectors, not messages.  c.f. Behavior>>selectorsDo: etc"<br>
> +        ^self selectorsDo: workBlock!<br>
> -        | scanner selector  |<br>
> -        self isQuick ifTrue: [^ self].<br>
> -       <br>
> -        self codeLiteralsDo: [:compiledCode |<br>
> -                scanner := InstructionStream on: compiledCode.<br>
> -                scanner scanFor: [ :x |<br>
> -                        (selector := scanner selectorToSendOrSelf) == scanner<br>
> -                                ifFalse: [workBlock value: selector].<br>
> -                        false "keep scanning" ] ].!<br>
> <br>
> Item was added:<br>
> + ----- Method: CompiledCode>>selectorsDo: (in category 'scanning') -----<br>
> + selectorsDo: workBlock<br>
> +        "Evaluate aBlock with all the message selectors sent by me. Duplicate selectors are possible."<br>
> +<br>
> +        | encoderClass |<br>
> +        self isQuick ifTrue: [^self].<br>
> +        encoderClass := self encoderClass.<br>
> +        self codeLiteralsDo:<br>
> +                [:compiledCode | | scanner limit |<br>
> +                limit := compiledCode size - 1.<br>
> +                (scanner := InstructionStream on: compiledCode) scanFor:<br>
> +                        [:byte| | selector |<br>
> +                        (selector := scanner selectorToSendOrSelf) ~~ scanner ifTrue:<br>
> +                                [workBlock value: selector].<br>
> +                        ((encoderClass isExtension: byte)<br>
> +                         and: [scanner pc < limit]) ifTrue:<br>
> +                                [scanner pc: scanner pc + (encoderClass bytecodeSize: (compiledCode at: scanner pc + 2))].<br>
> +                        false "keep scanning"]]!<br>
> <br>
> Item was changed:<br>
>   ----- Method: CompiledCode>>sendsMessage: (in category 'testing') -----<br>
> + sendsMessage: aSelector<br>
> +        "eem: this should be deprecated. This method does not check if a method sends a message;<br>
> +         it checks if a method sends a message with a particular selector."<br>
> +        self flag: #todo.<br>
> - sendsMessage: aSelector<br>
> -       <br>
>          self messagesDo: [:selector |<br>
>                  selector = aSelector ifTrue: [^ true]].<br>
>          ^ false!<br>
> <br>
> Item was changed:<br>
>   ----- Method: CompiledCode>>sendsSelector: (in category 'testing') -----<br>
>   sendsSelector: aSelector<br>
> +        "Answer if the receiver sends a message whose selector is aSelector."<br>
>  <br>
> +        self selectorsDo:<br>
> +                [:selector | selector = aSelector ifTrue: [^true]].<br>
> +        self flag: #todo. "The use of #= instead of #== is extremely dubious, and IMO erroneous. eem 2/18/2020"<br>
> +        ^false!<br>
> -        self flag: #todo. "mt: Deprecate? AST/Refactoring project needs it..."<br>
> -        ^ self sendsMessage: aSelector!<br>
> <br>
> Item was changed:<br>
>   ----- Method: CompiledMethod>>hasSameLiteralsAs: (in category 'comparing') -----<br>
>   hasSameLiteralsAs: aMethod<br>
>          "Answer whether the receiver has the same sequence of literals as the argument.<br>
>           Compare the last literal, which is the class association, specially so as not to<br>
>           differentiate between otherwise identical methods installed in different classes.<br>
>           Compare the first literal carefully if it is the binding informaiton for an FFI or<br>
>           external primitive call.  Don't compare all of the state so that linked and unlinked<br>
>           methods are still considered equal."<br>
>          | numLits |<br>
>          numLits := self numLiterals.<br>
>          numLits = aMethod numLiterals ifFalse: [^false].<br>
>          1 to: numLits do:<br>
>                  [:i| | lit1 lit2 |<br>
>                  lit1 := self literalAt: i.<br>
>                  lit2 := aMethod literalAt: i.<br>
>                  (lit1 == lit2 or: [lit1 literalEqual: lit2]) ifFalse:<br>
>                          [(i = 1 and: [#(117 120) includes: self primitive])<br>
>                                  ifTrue:<br>
>                                          [lit1 isArray<br>
>                                                  ifTrue:<br>
>                                                          [(lit2 isArray and: [(lit1 first: 2) = (lit2 first: 2)]) ifFalse:<br>
>                                                                  [^false]]<br>
>                                                  ifFalse: "ExternalLibraryFunction"<br>
>                                                          [(lit1 analogousCodeTo: lit2) ifFalse:<br>
>                                                                  [^false]]]<br>
>                                  ifFalse:<br>
>                                          [i = (numLits - 1)<br>
>                                                  ifTrue: "properties"<br>
>                                                          [(self properties analogousCodeTo: aMethod properties)<br>
>                                                                  ifFalse: [^false]]<br>
>                                                  ifFalse: "last literal (methodClassAssociation) of class-side methods is not unique"<br>
>                                                                  "last literal of CompiledBlock is outerMethod and may not be unique."<br>
>                                                          [(self isCompiledBlock<br>
>                                                            and: [lit1 isCompiledCode<br>
>                                                            and: [lit2 isCompiledCode]]) ifTrue:<br>
>                                                                  [^true].<br>
>                                                          (i = numLits<br>
> +                                                         and: [lit1 isVariableBinding and: [lit1 value isBehavior<br>
> +                                                         and: [lit2 isVariableBinding and: [lit2 value isBehavior]]]]) ifFalse:<br>
> -                                                         and: [lit1 isVariableBinding<br>
> -                                                         and: [lit2 isVariableBinding<br>
> -                                                         and: [lit1 key == lit2 key<br>
> -                                                         and: [lit1 value == lit2 value]]]]) ifFalse:<br>
>                                                                  [^false]]]]].<br>
>          ^true!<br>
> <br>
> Item was changed:<br>
>   ----- Method: Object>>perform:with:with:with:with:with: (in category 'message handling') -----<br>
>   perform: aSymbol with: firstObject with: secondObject with: thirdObject with: fourthObject with: fifthObject<br>
>          "Send the selector, aSymbol, to the receiver with the given arguments.<br>
> +        Fail if the number of arguments expected by the selector is not five.<br>
> -        Fail if the number of arguments expected by the selector is not four.<br>
>          Primitive. Optional. See Object documentation whatIsAPrimitive."<br>
>  <br>
>          <primitive: 83><br>
>          ^ self perform: aSymbol withArguments: { firstObject. secondObject. thirdObject. fourthObject. fifthObject }!<br>
> <br>
> <br>
> <br>
> <br>
><br>
<br>
</blockquote></div><br clear="all"><div><br></div>-- <br><div dir="ltr" class="gmail_signature"><div dir="ltr"><div><span style="font-size:small;border-collapse:separate"><div>_,,,^..^,,,_<br></div><div>best, Eliot</div></span></div></div></div></div>