#5326: Polymorphic instances aren't automatically specialised
---------------------------------+------------------------------------------
    Reporter:  reinerp           |       Owner:                         
        Type:  bug               |      Status:  new                    
    Priority:  normal            |   Component:  Compiler               
     Version:  7.0.3             |    Keywords:  specialisation         
    Testcase:                    |   Blockedby:                         
          Os:  Unknown/Multiple  |    Blocking:                         
Architecture:  Unknown/Multiple  |     Failure:  Runtime performance bug
---------------------------------+------------------------------------------
 Related to #255. Given (roughly) the example from that ticket:

 {{{
 f :: (Storable a, Eq a) => T a

 g :: T (Ptr a)
 g = f
 }}}
 we find that g is not specialised. Adding a SPECIALISE pragma fixes this,
 but it ought not to be necessary.

 The following module is a complete example:

 {{{
 module C where

 class C a where f :: a -> a

 newtype Id a = Id a
 instance C (Id a) where f = id

 g :: C a => Int -> a -> a
 g 0 a = a
 g n a = g (n-1) (f a)

 h :: Int -> Id a -> Id a
 h = g

 j :: Int -> Id Int -> Id Int
 j = g
 }}}

 We find that h passes a dictionary to g:

 {{{
 C.h =
   \ (@ a_alq) (w_smq :: Int) (w1_smu :: C.Id a_alq) ->
     case w_smq of _ { I# ww_sms ->
     C.$wg @ (C.Id a_alq) (C.$fCId @ a_alq) ww_sms w1_smu
     }
 }}}

 whereas j is specialised as desired, getting its own worker and no
 dictionaries:

 {{{
 C.j =
   \ (w_smg :: Int) (w1_smk :: C.Id Int) ->
     case w_smg of _ { I# ww_smi ->
     (C.$wj ww_smi w1_smk)
     `cast` (sym (C.NTCo:Id Int)
             :: Int ~ C.Id Int)
     }
 }}}

 If we add

 {{{
 {-# SPECIALISE g :: Int -> Id a -> Id a #-}
 }}}

 then h is specialised as desired.

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