[GHC] #9371: Overlapping type families, segafult

GHC ghc-devs at haskell.org
Mon Jul 28 02:07:21 UTC 2014


#9371: Overlapping type families, segafult
----------------------------------+----------------------------------------
       Reporter:  pingu           |                   Owner:
           Type:  bug             |                  Status:  new
       Priority:  normal          |               Milestone:
      Component:  Compiler        |                 Version:  7.8.3
       Keywords:                  |        Operating System:  Linux
   Architecture:  x86_64 (amd64)  |         Type of failure:  Runtime crash
     Difficulty:  Unknown         |               Test Case:
     Blocked By:                  |                Blocking:
Related Tickets:                  |  Differential Revisions:
----------------------------------+----------------------------------------
 Not entirely sure what's going on here. I don't think this should type
 check; it appears to segfault whilst calling show on the wrong type.

 This is probably not the absolute minimum required to reproduce.

 I have reproduced on 7.8.3 and 7.9.20140727.

 {{{#!haskell
 {-# LANGUAGE TypeFamilies #-}
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE UndecidableInstances #-}
 {-# LANGUAGE OverlappingInstances #-}
 import Data.Monoid

 class C x where
     data D x :: *
     makeD :: D x

 instance Monoid x => C x where
     data D x = D1 (Either x ())
     makeD = D1 (Left mempty)

 instance (Monoid x, Monoid y) => C (x, y) where
     data D (x,y) = D2 (x,y)
     makeD = D2 (mempty, mempty)

 instance Show x => Show (D x) where
     show (D1 x) = show x


 main = print (makeD :: D (String, String))
 }}}

 This does not segfault if you add:

 {{{#!haskell
   instance (Show x, Show y) => Show (D (x,y)) where
       show (D2 x) = show x
 }}}

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9371>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list