#3132: x86 code generator generates bad FPU register names
-------------------------------+--------------------------------------------
    Reporter:  int-e           |        Owner:  nobody          
        Type:  bug             |       Status:  new             
    Priority:  high            |    Milestone:  6.12.1          
   Component:  Compiler (NCG)  |      Version:  6.11            
    Severity:  normal          |   Resolution:                  
    Keywords:                  |   Difficulty:  Unknown         
    Testcase:                  |           Os:  Unknown/Multiple
Architecture:  x86             |  
-------------------------------+--------------------------------------------
Changes (by benl):

  * owner:  benl => nobody

Comment:

 The cmm code for the failing program contains the following:
 {{{
         if (_c1Wu::I32 >= 1) goto c1Wx;
         _s1Ba::F64 = r1tw_closure;
         _s1Nk::F64 = %MO_F_Sub_W64(D1, _s1Ba::F64);
         _s1Nl::F64 = %MO_F_Mul_W64(F64[Sp + 12], _s1Nk::F64);
 }}}

 Note that r1tw_closure is not a F64.

 Here is a test-case that fails -dcmm-lint as well as -dstg-lint when
 compiled with -O2.

 {{{
 module Spring where
 import Data.Array.Unboxed
 type Arr        = UArray Int Double
 step :: Double -> Int -> Arr -> Arr
 step h sz y     = listArray (0, 0) []
 }}}

 {{{
 ghc-stage1: panic! (the 'impossible' happened)
   (GHC version 6.11.20090514 for i386-unknown-linux):
             *** Stg Lint ErrMsgs: in Stg2Stg ***
     <no location info>:
          [in body of lambda with binders s{v sGe} [lid]
                        :: ghc-prim:GHC.Prim.State#{(w) tc 32q}
                                                  s{tv awN} [tv]]
         In a function application, function type doesn't match arg types:
         Function type:
             forall s{tv axt} [tv] i{tv axu} [tv].
             (base:GHC.Arr.Ix{tc 2i} i{tv axu} [tv]) =>
             (i{tv axu} [tv], i{tv axu} [tv])
             -> base:GHC.ST.ST{tc r65}
                  s{tv axt} [tv]
                  (array-0.2.0.1:Data.Array.Base.STUArray{tc r6}
                     s{tv axt} [tv] i{tv axu} [tv]
                       ghc-prim:GHC.Types.Double{(w) tc 3u})
         Arg types:
             <pred>base:GHC.Arr.Ix{tc 2i} ghc-prim:GHC.Types.Int{(w) tc 3J}
             (ghc-prim:GHC.Types.Int{(w) tc 3J},
              ghc-prim:GHC.Types.Int{(w) tc 3J})
             ghc-prim:GHC.Prim.State#{(w) tc 32q} s{tv awN} [tv]
         Expression:
             array-0.2.0.1:Data.Array.Base.newArray_8{v ra} [gid]
                 base:GHC.Arr.$f14{v r9} [gid]
                 main:Spring.lvl1{v r8} [gid]
                 s{v sGe} [lid]
 }}}

 I'm not sure how to read the STG code, but it looks like something in the
 libs has been messed up, which has then been inlined.

 Perhaps validate should be compiling with all the lint options turned on?

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3132#comment:4>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to