Alex Ferguson writes:
> 
> module R where
> 
> data NumVal = RealNum Float
> 
> isZero (RealNum 0.0) = True
> 
> 
> This is the Sun NCG, of course.  Doesn't happen without the constructor,
> or with Int's, or with -fvia-C...
> 

Thanks for narrowing this down, here's the offending line

        .double 0r<<function>>

One line fix at the end - Death to 'instance Show (->)'!

--Sigbjorn

*** ghc/compiler/nativeGen/MachRegs.lhs.~1~     1998/01/08 18:06:32
--- ghc/compiler/nativeGen/MachRegs.lhs         1998/01/30 11:50:09
***************
*** 95,99 ****
        ,IF_ARCH_i386( '0' : 'd' :
        ,IF_ARCH_sparc('0' : 'r' :,)))
!       show (rational r))
  \end{code}
  
--- 95,99 ----
        ,IF_ARCH_i386( '0' : 'd' :
        ,IF_ARCH_sparc('0' : 'r' :,)))
!       showSDoc (rational r))
  \end{code}

Reply via email to