Being able to automate is very good, however...
<rant>
I find a great deal of issues report are unhelpful, not to say totally
useless.
Take for example http://code.google.com/p/pharo/issues/detail?id=5482
 it just tells, "hey look at the fix in this slice, and you'll understand"
Then some bits of status (integrated, closed...).

Generally the code is not even accessible from within the bug report
(unless of few cases of change sets...)
What do we learn from such reports?
Do we find a rationale justifying the change?
Do we only even guess the intention by just reading the report?
What does this bring exactly to the process quality?

If we just have to look at the code, then follow something light like
squeak/trunk, just publish diffs and don't bother with pseudo-quality
disguise.

One huge progress would be the possibility to navigate across continuous
integration server, issue tracker, source code repository, and so called
ScriptLoader containing the list of fixes applied from one version to
another...
Tracking a regression down, seeing in which version it happened, what did
change in this version, browsing the related issue in the tracker to
understand the rationale of the change, and browsing the code diffs, all
this directly from the web pages would help a lot...

Of course, if reports are empty or cryptic, then maybe they can still feed
bots, but don't expect help of humans too much ;)

</rant>

Nicolas

Le 15 mars 2012 22:47, Stéphane Ducasse <stephane.duca...@inria.fr> a écrit
:

> thanks stefan
> Can you open a bug tracker and publish your code with a slice or a cs so
> that our crawler can handle it automatically?
> Yes we are getting professional thanks for camillo and ben :)
>
> Stef
>
> On Mar 15, 2012, at 8:58 PM, Stefan Marr wrote:
>
> > Hi:
> >
> > While stepping through bytecodes, I noticed a slightly annoying
> inefficiency in the SUnit implementation.
> > The description string in #assert:equals: is always computed, even if it
> is not necessary.
> >
> > While that might not be a performance problem, I find it rather
> distracting when I have to debug on the bytecode/VM level.
> >
> > Since there seem to be only 127 senders or so in the image, you will
> probably not notice a big performance gain.
> > The change to compute the string only when necessary is below.
> >
> > Best regards
> > Stefan
> >
> > PS: This is a resend, because the original mail seemed to have been
> lost, while the mailing list was down.
> >
> >
> > !TestCase methodsFor: 'asserting' stamp: 'StefanMarr 3/13/2012 23:41'!
> > assert: aBooleanOrBlock description: aStringOrBlock
> >       aBooleanOrBlock value ifFalse: [
> >               | aString |
> >               aString := aStringOrBlock value.
> >               self logFailure: aString.
> >               TestResult failure signal: aString]
> >                       ! !
> >
> > !TestCase methodsFor: 'asserting' stamp: 'StefanMarr 3/13/2012 23:40'!
> > assert: aBooleanOrBlock description: aStringOrBlock resumable:
> resumableBoolean
> >       | exception |
> >       aBooleanOrBlock value
> >               ifFalse:
> >                       [|aString|
> >                       aString := aStringOrBlock value.
> >                       self logFailure: aString.
> >                       exception := resumableBoolean
> >                                               ifTrue: [TestResult
> resumableFailure]
> >                                               ifFalse: [TestResult
> failure].
> >                       exception signal: aString]
> >                       ! !
> >
> > !TestCase methodsFor: 'asserting' stamp: 'StefanMarr 3/13/2012 23:40'!
> > assert: expected equals: actual
> >       ^ self
> >               assert: (expected = actual)
> >               description: [self comparingStringBetween: actual and:
> expected]
> > ! !
> >
> >
> > --
> > Stefan Marr
> > Software Languages Lab
> > Vrije Universiteit Brussel
> > Pleinlaan 2 / B-1050 Brussels / Belgium
> > http://soft.vub.ac.be/~smarr
> > Phone: +32 2 629 2974
> > Fax:   +32 2 629 3525
> >
> >
>
>
>

Reply via email to