[Hugs] #37: Equal Ints are not equal

Hugs trac at galois.com
Sun Oct 15 11:22:31 EDT 2006


#37: Equal Ints are not equal
----------------------+-----------------------------------------------------
  Reporter:  guest    |       Owner:  ross    
      Type:  defect   |      Status:  assigned
  Priority:  blocker  |   Milestone:          
 Component:  hugs     |     Version:  current 
Resolution:           |    Keywords:          
----------------------+-----------------------------------------------------
Old description:

> Hi,
>
> a few days ago I wrote a program which handles my own integers. Then I
> check my own implementation against the normal Int implementation in
> Hugs.
> Thereby I wonder about inequality of Ints which are definitely equal.
>
> This is a test program I wrote after I recognized that hugs
> has probably a bug in the inequality check of Ints.
>

>   data MInt = Zero | Succ MInt | Pred MInt deriving Show
>
>   tn :: Int -> MInt
>   tn x | x<0 = Pred (tn (x+1))
>   tn 0     =  Zero
>   tn (n+1) = Succ (tn n)
>
>   ti :: MInt -> Int
>   ti Zero = 0
>   ti (Succ x) = 1+(ti x)
>   ti (Pred x) = (ti x) -1
>
>   testi :: (MInt -> MInt -> MInt) -> (Int -> Int -> Int) -> Int -> Int ->
> Bool
>   testi f g x y = (ti (f (tn x) (tn y))) /= (g x y)
>
>   myMul x y = tn ((ti x) * (ti y))
>
>   test = [(x,y,ti (myMul (tn x) (tn y)),x * y)|
>             x<-[-100..100],
>             y<-([-100..(-1)]++[1..100]),(testi myMul (*)  x y) ]
>
> the list "test" should be empty in any case
> but unfortunately hugs returns this (copy of the console):
>
>   __   __ __  __  ____   ___
> _________________________________________
>   ||   || ||  || ||  || ||__      Hugs 98: Based on the Haskell 98
> standard
>   ||___|| ||__|| ||__||  __||     Copyright (c) 1994-2003
>   ||---||         ___||           World Wide Web: http://haskell.org/hugs
>   ||   ||                         Report bugs to: hugs-bugs at haskell.org
>   ||   || Version: November 2003
> _________________________________________
>
>   Haskell 98 mode: Restart with command line option -98 to enable
> extensions
>
>   Type :? for help
>   Main> test
>   [(-100,80,-8000,-8000),(-100,99,-9900,-9900),
>   (-99,58,-5742,-5742),(-99,83,-8217,-8217),
>   (-98,71,-6958,-6958),(-98,86,-8428,-8428),
>   (-97,46,-4462,-4462),(-97,87,-8439,-8439),
>   (-96,76,-7296,-7296),(-95,88,-8360,-8360),(-94,73,-6862,-6862)
>   ERROR - Control stack overflow
>   Main>
>
> I have checked this program with Hugs on different plattforms:
> Gentoo Linux x86 64-Bit and Suse Linux 32-Bit. On both plattforms
> the same bug occurs with different Ints for each run (i.e. the list
> contains different tuples). I have also checked my program with
> other Haskell implementations and there it returns an empty list
> as expected.
>
> Best regards,
> Stephan Swiderski (swiderski at informatik.rwth-aachen.de)
>
> P.S.: We have tested Sep2006 with similar results:
> __   __ __  __  ____   ___      _________________________________________
> ||   || ||  || ||  || ||__      Hugs 98: Based on the Haskell 98 standard
> ||___|| ||__|| ||__||  __||     Copyright (c) 1994-2005
> ||---||         ___||           World Wide Web: http://haskell.org/hugs
> ||   ||                         Bugs:
> http://hackage.haskell.org/trac/hugs
> ||   || Version: September 2006 _________________________________________
>
> Haskell 98 mode: Restart with command line option -98 to enable
> extensions
>
> Type :? for help
> Main> :e
> Main> test
> [(-100,90,-9000,-9000),(-98,40,-3920,-3920),(-97,63,-6111,-6111),(-97,69,-6693,-
> 6693)
> ERROR - Control stack overflow

New description:

 Hi,

 a few days ago I wrote a program which handles my own integers. Then I
 check my own implementation against the normal Int implementation in Hugs.
 Thereby I wonder about inequality of Ints which are definitely equal.

 This is a test program I wrote after I recognized that hugs has probably a
 bug in the inequality check of Ints.
 {{{
 data MInt = Zero | Succ MInt | Pred MInt deriving Show

 tn :: Int -> MInt
 tn x | x<0 = Pred (tn (x+1))
 tn 0     =  Zero
 tn (n+1) = Succ (tn n)

 ti :: MInt -> Int
 ti Zero = 0
 ti (Succ x) = 1+(ti x)
 ti (Pred x) = (ti x) -1

 testi :: (MInt -> MInt -> MInt) -> (Int -> Int -> Int) -> Int -> Int ->
 Bool
 testi f g x y = (ti (f (tn x) (tn y))) /= (g x y)

 myMul x y = tn ((ti x) * (ti y))

 test = [(x,y,ti (myMul (tn x) (tn y)),x * y)|
           x<-[-100..100],
           y<-([-100..(-1)]++[1..100]),(testi myMul (*)  x y) ]
 }}}
 The list "test" should be empty in any case but unfortunately hugs returns
 this (copy of the console):
 {{{
 __   __ __  __  ____   ___      _________________________________________
 ||   || ||  || ||  || ||__      Hugs 98: Based on the Haskell 98 standard
 ||___|| ||__|| ||__||  __||     Copyright (c) 1994-2003
 ||---||         ___||           World Wide Web: http://haskell.org/hugs
 ||   ||                         Report bugs to: hugs-bugs at haskell.org
 ||   || Version: November 2003  _________________________________________

 Haskell 98 mode: Restart with command line option -98 to enable extensions

 Type :? for help
 Main> test
 [(-100,80,-8000,-8000),(-100,99,-9900,-9900),
 (-99,58,-5742,-5742),(-99,83,-8217,-8217),
 (-98,71,-6958,-6958),(-98,86,-8428,-8428),
 (-97,46,-4462,-4462),(-97,87,-8439,-8439),
 (-96,76,-7296,-7296),(-95,88,-8360,-8360),(-94,73,-6862,-6862)
 ERROR - Control stack overflow
 Main>
 }}}
 I have checked this program with Hugs on different plattforms:  Gentoo
 Linux x86 64-Bit and Suse Linux 32-Bit. On both platforms  the same bug
 occurs with different Ints for each run (i.e. the list  contains different
 tuples). I have also checked my program with
 other Haskell implementations and there it returns an empty list
 as expected.

 Best regards,
 Stephan Swiderski (swiderski at informatik.rwth-aachen.de)

 P.S.: We have tested Sep2006 with similar results:
 {{{
 __   __ __  __  ____   ___      _________________________________________
 ||   || ||  || ||  || ||__      Hugs 98: Based on the Haskell 98 standard
 ||___|| ||__|| ||__||  __||     Copyright (c) 1994-2005
 ||---||         ___||           World Wide Web: http://haskell.org/hugs
 ||   ||                         Bugs: http://hackage.haskell.org/trac/hugs
 ||   || Version: September 2006 _________________________________________

 Haskell 98 mode: Restart with command line option -98 to enable extensions

 Type :? for help
 Main> :e
 Main> test
 [(-100,90,-9000,-9000),(-98,40,-3920,-3920),(-97,63,-6111,-6111),(-97,69,-6693,-6693)
 ERROR - Control stack overflow
 }}}

-- 
Ticket URL: <http://hackage.haskell.org/trac/hugs/ticket/37>
Hugs <http://www.haskell.org/hugs/>
Hugs 98, an interpreter for Haskell


More information about the Hugs-Bugs mailing list