To illustrate that these dumb tests that don't look that interesting
might sometimes help, here is how I changed

Integer>>/ aNumber
        "Refer to the comment in Number / "
        | quoRem |
        aNumber isInteger ifTrue:
                [quoRem := self digitDiv: aNumber abs   "*****I've added abs 
here*****"
                                                neg: self negative ~~ aNumber 
negative.
                (quoRem at: 2) = 0
                        ifTrue: [^ (quoRem at: 1) normalize]
                        ifFalse: [^ (Fraction numerator: self denominator: 
aNumber) reduced]].
        aNumber isFraction
                ifTrue:
                        [| n d |
                        n := self // (d := self gcd: aNumber numerator).
                        d := aNumber numerator // d.
                        ^d = 1
                                ifTrue: [n * aNumber denominator * d]
                                ifFalse: [Fraction numerator: n * aNumber 
denominator denominator: d]].
        ^ aNumber adaptToInteger: self andSend: #/

But hey, we can't fail on such trivial method, can we?
Unless... maybe the cyclomatic complexity isn't that low after all...
Please, could you tell me where the error was ?

Nicolas


2012/6/5 Nicolas Cellier <nicolas.cellier.aka.n...@gmail.com>:
> 2012/6/5 Sven Van Caekenberghe <s...@beta9.be>:
>> Haha, very funny.
>>
>> It's a good thing there are so many jokes hidden inside the image.
>>
>> We could add a couple/many more:
>>
>> self deny: 1 = 2.
>> self deny: 1 = -1.
>> self deny: (4 / 2) = 3
>> self shouldnt: [ 1 / 2 ] raise: ZeroDivide
>>
>> ;-)
>>
>
> Yes it's laughable.
> However, I recently hacked Intger/Fraction to speed up mixed
> operations and guess what...
> once you know the miserable error's we can make...
>
> Nicolas
>
>> On 05 Jun 2012, at 12:10, Serge Stinckwich wrote:
>>
>>> On Tue, Jun 5, 2012 at 5:04 PM, Damien Cassou <damien.cas...@gmail.com> 
>>> wrote:
>>>> On Tue, Jun 5, 2012 at 11:55 AM, Camillo Bruni <camillobr...@gmail.com> 
>>>> wrote:
>>>>>> testGeneralInquiries
>>>>>>       | now d t dt |
>>>>>>
>>>>>>       now  := self timeClass dateAndTimeNow.
>>>>>>       self
>>>>>>               assert: now size = 2;
>>>>>>               assert: now last <= self timeClass now.
>>>>>>
>>>>>>       self should: [ self timeClass timeWords ] raise: 
>>>>>> MessageNotUnderstood.
>>>>>>
>>>>>>       d := '2 June 1973' asDate.
>>>>>>       t := '4:02:47 am' asTime.
>>>>>>       dt := self timeClass dateAndTimeFromSeconds: (2285280000 + 14567).
>>>>>>       self
>>>>>>               assert: dt = {d. t.}.
>>>>>>
>>>>>>
>>>>>> The middle part is a GREAT example of a useful unit test…
>>>>>
>>>>> that's called a negative test :D, assume what possible could fail in the 
>>>>> universe and test for it :D
>>>>
>>>> I will write a paper on automatic negative test generation. Who wants
>>>> to join? :-)
>>>
>>> You can even write a program that write a paper about negative tests
>>> generation ;-)
>>>
>>> --
>>> Serge Stinckwich
>>> UMI UMMISCO 209 (IRD/UPMC), Hanoi, Vietnam
>>> Every DSL ends up being Smalltalk
>>> http://doesnotunderstand.org/
>>>
>>
>>

Reply via email to