#5325: The -dsuppress-type-signatures flag behaves wrongly on RULES
---------------------------------+------------------------------------------
    Reporter:  reinerp           |       Owner:              
        Type:  bug               |      Status:  new         
    Priority:  normal            |   Component:  Compiler    
     Version:  7.0.3             |    Keywords:              
    Testcase:                    |   Blockedby:              
          Os:  Unknown/Multiple  |    Blocking:              
Architecture:  Unknown/Multiple  |     Failure:  None/Unknown
---------------------------------+------------------------------------------
 Given this module:

 {{{
 module M where

 f :: Num a => a -> a
 f x = x + 1

 {-# SPECIALISE f :: Int -> Int #-}
 }}}

 if we compile with


 {{{
 ghc -dsuppress-type-signatures -O -ddump-simpl M.hs
 }}}

 we see that the SPECIALISE pragma has become the following:


 {{{
 "SPEC M.f" [ALWAYS] forall {} M.f @ GHC.Types.Int $dNum_anE = M.f_f
 }}}

 It looks dNum_anE is a free variable in this rule, but it's actually a
 bound variable, as we can see when we compile without -dsuppress-type-
 signatures:


 {{{
 "SPEC M.f" [ALWAYS]
     forall {$dNum_anE :: GHC.Num.Num GHC.Types.Int}
       M.f @ GHC.Types.Int $dNum_anE
       = M.f_f
 }}}

 I think GHC should produce the following output with -dsuppress-type-
 signatures:


 {{{
 "SPEC M.f" [ALWAYS] forall {$dNum_anE} M.f @ GHC.Types.Int $dNum_anE =
 M.f_f
 }}}

 This is with GHC 7.1.20110629.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5325>
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