Issue 3341 in pharo: use #= for integer comparison instead of #==

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

Issue 3341 in pharo: use #= for integer comparison instead of #==

pharo
Status: Accepted
Owner: stephane.ducasse
Labels: Milestone-1.3 Type-Squeak

New issue 3341 by stephane.ducasse: use #= for integer comparison instead  
of #==
http://code.google.com/p/pharo/issues/detail?id=3341

Please read the original statement of dan.
http://bugs.squeak.org/view.php?id=2788
I think that this bunch of fixes are important.



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

Name: Collections-ul.406
Author: ul
Time: 15 November 2010, 10:30:39.825 am
UUID: 9cd8fc97-4673-3340-9ea2-2f3dbd5f38e3
Ancestors: Collections-cmm.405

- use #= for integer comparison instead of #==  
(http://bugs.squeak.org/view.php?id=2788 )

=============== Diff against Collections-cmm.405 ===============

Item was changed:
  ----- Method: SequenceableCollection>>after:ifAbsent: (in  
category 'accessing') -----
  after: target ifAbsent: exceptionBlock
        "Answer the element after target.  Answer the result of evaluation
        the exceptionBlock if target is not in the receiver, or if there are
        no elements after it."

        | index |
        index := self indexOf: target.
+       ^ (index = 0 or: [index = self size])
-       ^ (index == 0 or: [index = self size])
                ifTrue: [exceptionBlock value]
                ifFalse: [self at: index + 1]!

Item was changed:
  ----- Method: SequenceableCollection>>before:ifAbsent: (in  
category 'accessing') -----
  before: target ifAbsent: exceptionBlock
        "Answer the receiver's element immediately before target. Answer
        the result of evaluating the exceptionBlock if target is not an  
element
        of the receiver, or if there are no elements before it."

        | index |
        index := self indexOf: target.
+       ^ (index = 0 or: [index = 1])
-       ^ (index == 0 or: [index == 1])
                ifTrue: [exceptionBlock value]
                ifFalse: [self at: index - 1]!

Item was changed:
  ----- Method: String>>asIdentifier: (in category 'converting') -----
  asIdentifier: shouldBeCapitalized
        "Return a legal identifier, with first character in upper case if  
shouldBeCapitalized is true, else lower case.  This will always return a  
legal identifier, even for an empty string"

        | aString firstChar firstLetterPosition |
        aString := self select: [:el | el isAlphaNumeric].
        firstLetterPosition := aString findFirst: [:ch | ch isLetter].
+       aString := firstLetterPosition = 0
-       aString := firstLetterPosition == 0
                ifFalse:
                        [aString copyFrom: firstLetterPosition to: aString  
size]
                ifTrue:
                        ['a', aString].
        firstChar := shouldBeCapitalized ifTrue: [aString first asUppercase]  
ifFalse: [aString first asLowercase].

        ^ firstChar asString, (aString copyFrom: 2 to: aString size)
  "
  '234Fred987' asIdentifier: false
  '235Fred987' asIdentifier: true
  '' asIdentifier: true
  '()87234' asIdentifier: false
  '())z>=PPve889  U >' asIdentifier: false

  "!

Item was changed:
  ----- Method: String>>initialIntegerOrNil (in category 'converting') -----
  initialIntegerOrNil
        "Answer the integer represented by the leading digits of the  
receiver, or nil if the receiver does not begin with a digit"
        | firstNonDigit |
+       (self size = 0 or: [self first isDigit not]) ifTrue: [^ nil].
-       (self size == 0 or: [self first isDigit not]) ifTrue: [^ nil].
        firstNonDigit := (self findFirst: [:m | m isDigit not]).
        firstNonDigit = 0 ifTrue: [firstNonDigit := self size + 1].
        ^ (self copyFrom: 1  to: (firstNonDigit - 1)) asNumber
  "
  '234Whoopie' initialIntegerOrNil
  'wimpy' initialIntegerOrNil
  '234' initialIntegerOrNil
  '2N' initialIntegerOrNil
  '2' initialIntegerOrNil
  '  89Ten ' initialIntegerOrNil
  '78 92' initialIntegerOrNil
  "
  !

Item was changed:
  ----- Method: String>>sansPeriodSuffix (in category 'converting') -----
  sansPeriodSuffix
        "Return a copy of the receiver up to, but not including, the first  
period.  If the receiver's *first* character is a period, then just return  
the entire receiver. "

        | likely |
        likely := self copyUpTo: $..
+       ^ likely size = 0
-       ^ likely size == 0
                ifTrue: [self]
                ifFalse:        [likely]!

Item was changed:
  ----- Method: String>>utf8ToIso (in category 'internet') -----
  utf8ToIso
        "Only UTF-8 characters that maps to 8-bit ISO-8559-1 values are  
converted. Others raises an error"
        | s i c v c2 v2 |
        s := WriteStream on: (String new: self size).

        i := 1.
        [i <= self size] whileTrue: [
                c := self at: i. i:=i+1.
                v := c asciiValue.
                (v > 128)
                        ifFalse: [ s nextPut: c ]
+                       ifTrue: [((v bitAnd: 252) = 192)
-                       ifTrue: [((v bitAnd: 252) == 192)
                                ifFalse: [self error: 'illegal UTF-8 ISO  
character']
                                ifTrue: [
                                        (i > self size) ifTrue: [ self  
error: 'illegal end-of-string, expected 2nd byte of UTF-8'].
                                        c2 := self at: i. i:=i+1.
                                        v2 := c2 asciiValue.
                                        ((v2 bitAnd: 192) = 128) ifFalse:  
[self error: 'illegal 2nd UTF-8 char'].
                                        s nextPut: ((v2 bitAnd: 63) bitOr:  
((v << 6) bitAnd: 192)) asCharacter]]].
        ^s contents.
  !

Item was changed:
  ----- Method: Symbol class>>selectorsContaining: (in category 'access')  
-----
  selectorsContaining: aString
        "Answer a list of selectors that contain aString within them.  
Case-insensitive.  Does return symbols that begin with a capital letter."

        | size selectorList ascii |

        selectorList := OrderedCollection new.
        (size := aString size) = 0 ifTrue: [^selectorList].

        aString size = 1 ifTrue:
                [
                        ascii := aString first asciiValue.
                        ascii < 128 ifTrue: [selectorList add:  
(OneCharacterSymbols at: ascii+1)]
                ].

        (aString first isLetter or: [aString first isDigit]) ifFalse:
                [
+                       aString size = 2 ifTrue:
-                       aString size == 2 ifTrue:
                                [Symbol hasInterned: aString ifTrue:
                                        [:s | selectorList add: s]].
                        ^selectorList
                ].

        selectorList := selectorList copyFrom: 2 to: selectorList size.

        self allSymbolTablesDo: [:each |
                each size >= size ifTrue:
                        [(each findSubstring: aString in: each startingAt: 1
                                matchTable: CaseInsensitiveOrder) > 0
                                                ifTrue: [selectorList add:  
each]]].

        ^selectorList reject: [:each | "reject non-selectors, but keep ones  
that begin with an uppercase"
                each numArgs < 0 and: [each asString  
withFirstCharacterDownshifted numArgs < 0]].

  "Symbol selectorsContaining: 'scon'"!

Item was changed:
  ----- Method: Symbol>>isInfix (in category 'testing') -----
  isInfix
        "Answer whether the receiver is an infix message selector."

+       ^ self precedence = 2!
-       ^ self precedence == 2!

Item was changed:
  ----- Method: Symbol>>isKeyword (in category 'testing') -----
  isKeyword
        "Answer whether the receiver is a message keyword."

+       ^ self precedence = 3!
-       ^ self precedence == 3!

Item was changed:
  ----- Method: Symbol>>isUnary (in category 'testing') -----
  isUnary
        "Answer whether the receiver is an unary message selector."

+       ^ self precedence = 1!
-       ^ self precedence == 1!


Reply | Threaded
Open this post in threaded view
|

Re: Issue 3341 in pharo: use #= for integer comparison instead of #==

pharo

Comment #1 on issue 3341 by stephane.ducasse: use #= for integer comparison  
instead of #==
http://code.google.com/p/pharo/issues/detail?id=3341

<CompiledMethod>scanForEqSmallConstant
     "Answer whether the receiver contains the pattern <expression> ==  
<constant>,
     where constant is -1, 0, 1, or 2..."

     | scanner |
     scanner _ InstructionStream on: self.
     ^ scanner scanFor: [:instr | (instr between: 116 and: 119) and:  
[scanner followingByte = 198]]

"
SystemNavigation new browseAllSelect: [:m | m scanForEqSmallConstant]
"



Reply | Threaded
Open this post in threaded view
|

Re: Issue 3341 in pharo: use #= for integer comparison instead of #==

pharo

Comment #2 on issue 3341 by stephane.ducasse: use #= for integer comparison  
instead of #==
http://code.google.com/p/pharo/issues/detail?id=3341

http://source.squeak.org/trunk/Kernel-ul.516.mcz

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

Name: Kernel-ul.516
Author: ul
Time: 15 November 2010, 11:23:57.645 am
UUID: 6faf4568-4121-8543-897b-a4aef9f01454
Ancestors: Kernel-ul.515

- reverted Object >> #inboundPointersExcluding: and added a comment with  
some explanation about the use of #==.

=============== Diff against Kernel-ul.515 ===============

Item was changed:
  ----- Method: Object>>inboundPointersExcluding: (in category 'tracing')  
-----
  inboundPointersExcluding: objectsToExclude
  "Answer a list of all objects in the system that point to me, excluding  
those in the collection of objectsToExclude. I do my best to avoid creating  
any temporary objects that point to myself, especially method and block  
contexts. Adapted from PointerFinder class >> #pointersTo:except:"

        | anObj pointers objectsToAlwaysExclude |
        Smalltalk garbageCollect.
        "big collection shouldn't grow, so it's contents array is always the  
same"
        pointers := OrderedCollection new: 1000.

        "#allObjectsDo: and #pointsTo: are expanded inline to keep spurious
         method and block contexts out of the results"
        anObj := self someObject.
+       [0 == anObj] whileFalse: [ "We must use #== here, to avoid leaving  
the loop when anObj is another number that's equal to 0 (e.g. 0.0)."
-       [0 = anObj] whileFalse: [
                anObj isInMemory
                        ifTrue: [((anObj instVarsInclude: self)
                                or: [anObj class == self])
                                        ifTrue: [pointers add: anObj]].
                anObj := anObj nextObject].

        objectsToAlwaysExclude := {
                pointers collector.
                thisContext.
                thisContext sender.
                thisContext sender sender.
                objectsToExclude.
        }.

        ^ pointers removeAllSuchThat: [:ea |
                (objectsToAlwaysExclude identityIncludes: ea)
                        or: [objectsToExclude identityIncludes: ea]]!



Reply | Threaded
Open this post in threaded view
|

Re: Issue 3341 in pharo: use #= for integer comparison instead of #==

pharo

Comment #3 on issue 3341 by stephane.ducasse: use #= for integer comparison  
instead of #==
http://code.google.com/p/pharo/issues/detail?id=3341

Name: Kernel-dtl.517
Author: dtl
Time: 15 November 2010, 12:49:28.804 pm
UUID: 2c83e064-fa7d-4fc0-8e81-140b88e48a49
Ancestors: Kernel-ul.516

Revert last change to Semaphore>>critical:ifLocked: using latest version  
from Cuis, which adds a method comment to explain the reason for use of #==  
rather than #=

=============== Diff against Kernel-ul.516 ===============

Item was changed:
  ----- Method: Semaphore>>critical:ifLocked: (in category 'mutual  
exclusion') -----
  critical: mutuallyExcludedBlock ifLocked: alternativeBlock
        "Evaluate mutuallyExcludedBlock only if the receiver is not  
currently in
        the process of running the critical: message. If the receiver is,  
evaluate
        mutuallyExcludedBlock after the other critical: message is finished."

+       "Note: The following is tricky and depends on the fact that the VM  
will not switch between processes while executing byte codes (process  
switches happen only in real sends). The following test is written  
carefully so that it will result in bytecodes only.
+       Do not change the following #== for #=, as #== is not a real  
message send, just a bytecode."
+       excessSignals == 0 ifTrue: [
-       "Note: The following is tricky and depends on the fact that the VM  
will not switch between processes while executing byte codes (process  
switches happen only in real sends). The following test is written  
carefully so that it will result in bytecodes only."
-       excessSignals = 0 ifTrue:[
                "If we come here, then the semaphore was locked when the  
test executed.
                Evaluate the alternative block and answer its result."
                ^alternativeBlock value
        ].
        ^self critical: mutuallyExcludedBlock!


Reply | Threaded
Open this post in threaded view
|

Re: Issue 3341 in pharo: use #= for integer comparison instead of #==

pharo

Comment #4 on issue 3341 by [hidden email]: use #= for integer  
comparison instead of #==
http://code.google.com/p/pharo/issues/detail?id=3341

SLICE-Issue-3341-IntegerComparisonShallUseEqual-Part1-nice.1
Dependencies: Kernel-nice.847

Transform a few == into = and ~~ into ~= in Kernel


Reply | Threaded
Open this post in threaded view
|

Re: Issue 3341 in pharo: use #= for integer comparison instead of #==

pharo
Updates:
        Status: FixToInclude

Comment #5 on issue 3341 by [hidden email]: use #= for integer  
comparison instead of #==
http://code.google.com/p/pharo/issues/detail?id=3341

(No comment was entered for this change.)


Reply | Threaded
Open this post in threaded view
|

Re: Issue 3341 in pharo: use #= for integer comparison instead of #==

pharo

Comment #6 on issue 3341 by [hidden email]: use #= for integer  
comparison instead of #==
http://code.google.com/p/pharo/issues/detail?id=3341

Thanks this is nice to see some progress on this front too.
We will get there.


Reply | Threaded
Open this post in threaded view
|

Re: Issue 3341 in pharo: use #= for integer comparison instead of #==

pharo

Comment #7 on issue 3341 by [hidden email]: use #= for integer  
comparison instead of #==
http://code.google.com/p/pharo/issues/detail?id=3341

Kernel changed integrated in 13112


Reply | Threaded
Open this post in threaded view
|

Re: Issue 3341 in pharo: use #= for integer comparison instead of #==

pharo
Updates:
        Status: Started

Comment #8 on issue 3341 by [hidden email]: use #= for integer  
comparison instead of #==
http://code.google.com/p/pharo/issues/detail?id=3341

(No comment was entered for this change.)


Reply | Threaded
Open this post in threaded view
|

Re: Issue 3341 in pharo: use #= for integer comparison instead of #==

pharo

Comment #9 on issue 3341 by [hidden email]: use #= for integer comparison  
instead of #==
http://code.google.com/p/pharo/issues/detail?id=3341

sansPeriodSuffix -> withhoutPeriodSuffix


Reply | Threaded
Open this post in threaded view
|

Re: Issue 3341 in pharo: use #= for integer comparison instead of #==

pharo

Comment #10 on issue 3341 by [hidden email]: use #= for integer  
comparison instead of #==
http://code.google.com/p/pharo/issues/detail?id=3341

utf8toIso lo nonger exists


Reply | Threaded
Open this post in threaded view
|

Re: Issue 3341 in pharo: use #= for integer comparison instead of #==

pharo

Comment #11 on issue 3341 by [hidden email]: use #= for integer  
comparison instead of #==
http://code.google.com/p/pharo/issues/detail?id=3341

also Symbol>>isBinary



Reply | Threaded
Open this post in threaded view
|

Re: Issue 3341 in pharo: use #= for integer comparison instead of #==

pharo
Updates:
        Status: FixToInclude

Comment #12 on issue 3341 by [hidden email]: use #= for integer  
comparison instead of #==
http://code.google.com/p/pharo/issues/detail?id=3341

(No comment was entered for this change.)


Reply | Threaded
Open this post in threaded view
|

Re: Issue 3341 in pharo: use #= for integer comparison instead of #==

pharo
Updates:
        Status: Started
        Labels: -Milestone-1.3

Comment #13 on issue 3341 by [hidden email]: use #= for integer  
comparison instead of #==
http://code.google.com/p/pharo/issues/detail?id=3341

(No comment was entered for this change.)