Mariano

Some of the combinations are inlined automatically by the compiler as levente 
explained.
The problems is that without a rule checking that for me, I cannot remember 
which one are optimized :)
Now the cost is that if you have more inlined expressions, then the decompiler 
gets more complex.
So having a good and flexible decompiler would be a way to favor optimization. 
For now the list of levente and a slow machine 
        
        "So "== nil" #ifNil:, #ifNil:ifNotNil:, #ifNotNil:, #ifNotNil:ifNil: 
should be used whenever possible."
is the one to use


Now 

> 
> 2010/5/24 Levente Uzonyi <le...@elte.hu>
> On Sun, 23 May 2010, Mariano Abel Coca wrote:
> 
> There are few now, but it was done yesterday in a few hours. We will keep
> adding new tests to that suites, so suggestions are welcome :).
> 
> Actually there are only 3 tests there:
> 
> - One that checks that all the methods in the image are categorized
> - One that checks that never redefine #doesNotUnderstand: without redefining
> #respondsTo: and vice versa.
> - And one that checks that never sent = nil, ==nil, nil =, or nil ==, ~=
> nil, etc. as suggested in issue 1594 (Actually, after reading this issue is
> that we started with this idea).
> 
> "x = nil", "nil = x", "x ~= nil", "nil ~= x", "x ~~ nil" and "nil ~~ x" are 
> usually bad ideas, but #isNil is 2.9x(*) slower than "== nil" and
> "== nil" is not less readable if you know what #== means (but that's basic 
> smalltalk knowledge, so it's fair to assume that everybody knows it).
> 
> Also "foo isNil ifTrue:" is 2.7x(*) slower than "foo ifNil:" for the same 
> reasons (#ifNil: will be compiled as "== nil ifTrue:" if possible).
> 
> So "== nil" #ifNil:, #ifNil:ifNotNil:, #ifNotNil:, #ifNotNil:ifNil: should be 
> used whenever possible.
> 
> (*) Benchmarks on my slow machine:
> 
> ((1 to: 10) collect: [ :run |
>        [ 1 to: 10000000 do: [ :i | 1 == nil ] ] timeToRun ]) average asFloat. 
> "===> 386.6"
> 
> ((1 to: 10) collect: [ :run |
>        [ 1 to: 10000000 do: [ :i | 1 isNil ] ] timeToRun ]) average asFloat. 
> "===> 586.4"
> 
> ((1 to: 10) collect: [ :run |
>        [ 1 to: 10000000 do: [ :i | ] ] timeToRun ]) average asFloat. "===> 
> 282.3"
> 
> 586.4 - 282.3 / (386.6 - 282.3) "===> 2.915627996164908"
> 
> ((1 to: 10) collect: [ :run |
>        [ 1 to: 10000000 do: [ :i | 1 ifNil: [ 2 ] ] ] timeToRun ]) average 
> asFloat. "===> 393.6"
> 
> ((1 to: 10) collect: [ :run |
>        [ 1 to: 10000000 do: [ :i | 1 isNil ifTrue: [ 2 ] ] ] timeToRun ]) 
> average asFloat. "===> 585.2"
> 
> 585.2 - 282.3 / (393.6 - 282.3). "===> 2.7214734950584"
> 
> 
> 
> I ask completely in ignorance, but can't we do some Compiler/Parser teaks so 
> that allow us to write the more readable and nice but then it  convert them 
> to the fast ones?
> 
> 
> 
>  
> 
> Levente
> 
> 
> Cheers,
> 
> Mariano.
> 
> 
> On Sun, May 23, 2010 at 4:53 AM, Stéphane Ducasse <stephane.duca...@inria.fr
> wrote:
> 
> Sounds exciting can you tell us a bit more?
> 
> On May 23, 2010, at 2:54 AM, Mariano Abel Coca wrote:
> 
> If anyone want, can take a look at:
> 
> http://www.squeaksource.com/CodeQualityTests
> http://www.squeaksource.com/CodeStandardsTests
> 
> And run the tests before committing the next version of their packages.
> 
> We will try to help to pass the tests as soon as possible.
> 
> Cheers,
> 
> Mariano.
> 
> 
> On Sat, May 22, 2010 at 8:06 PM, Francisco Ortiz Pe?aloza <
> patchi...@gmail.com> wrote:
> We're working on it, making small changes and creating code standards
> tests and code quality tests.
> 
> It would be great to have a way of tracking the results of these tests
> in a distant future and make them mandatory before integrate new
> things into the image.
> 
> Francisco
> 
> On Sat, May 22, 2010 at 7:17 PM, Stéphane Ducasse
> <stephane.duca...@inria.fr> wrote:
> What I was thinking mariano is that we could move one class at a time
> in classTests and make the tests green.
> This way we do not have red tests and still make progress
> Stef
> 
> 
> On May 22, 2010, at 8:06 PM, Mariano Abel Coca wrote:
> 
> It is a must. We have to got all the tests in green. But actually that
> isn't tested.
> 
> I'll make the tests, I'll fix them, and then I'll send the whole
> changes to merge in the baseline.
> 
> Cheers,
> 
> Mariano.
> 
> 
> On Sat, May 22, 2010 at 2:58 PM, Stéphane Ducasse <
> stephane.duca...@inria.fr> wrote:
> the key point is that we would like to avoid to have red tests all the
> time
> so fixing the as yet unclassified should be done before.
> 
> 
> BTW Does anybody use
>       BadEqualer
>       HashTester
>       PrototypeTester
> 
> because so far I do not see anybody user of them.
> They look like experiment code to me.
> 
> Stef
> 
> On May 22, 2010, at 7:31 PM, Mariano Abel Coca wrote:
> 
> Hi, I want to make global the checks included in ClassTestCase, and
> remove it. That is because actually it's only being tested for it's
> subclasses. And also, it's declaring that a subclass will be a class test
> instead of just a test, but no one of it's subclasses actually test the
> class, but the instances, therefore is a TestCase, not a ClassTestCase. See
> TimespanTest as an example.
> 
> What Im saying is that I'm trying to force a run of a suit of Code
> Standards and Code Quality tests before sending something to merge to a
> baseline of a project.
> 
> What do you think? Are you agree with that?
> 
> Cheers,
> 
> Mariano.
> _______________________________________________
> Pharo-project mailing list
> Pharo-project@lists.gforge.inria.fr
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
> 
> 
> _______________________________________________
> Pharo-project mailing list
> Pharo-project@lists.gforge.inria.fr
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
> 
> _______________________________________________
> Pharo-project mailing list
> Pharo-project@lists.gforge.inria.fr
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
> 
> 
> _______________________________________________
> Pharo-project mailing list
> Pharo-project@lists.gforge.inria.fr
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
> 
> 
> _______________________________________________
> Pharo-project mailing list
> Pharo-project@lists.gforge.inria.fr
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
> 
> _______________________________________________
> Pharo-project mailing list
> Pharo-project@lists.gforge.inria.fr
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
> 
> 
> _______________________________________________
> Pharo-project mailing list
> Pharo-project@lists.gforge.inria.fr
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
> 
> 
> _______________________________________________
> Pharo-project mailing list
> Pharo-project@lists.gforge.inria.fr
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
> 
> _______________________________________________
> Pharo-project mailing list
> Pharo-project@lists.gforge.inria.fr
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project


_______________________________________________
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

Reply via email to