[GHC] #10139: Coercible causes ghc to hang

GHC ghc-devs at haskell.org
Fri Mar 6 06:40:43 UTC 2015


#10139: Coercible causes ghc to hang
-------------------------------------+-------------------------------------
              Reporter:              |             Owner:
  nitromaster101                     |            Status:  new
                  Type:  bug         |         Milestone:
              Priority:  normal      |           Version:  7.10.1-rc2
             Component:  Compiler    |  Operating System:  Unknown/Multiple
              Keywords:              |   Type of failure:  None/Unknown
          Architecture:              |        Blocked By:
  Unknown/Multiple                   |   Related Tickets:
             Test Case:              |
              Blocking:              |
Differential Revisions:              |
-------------------------------------+-------------------------------------
 Consider my two instance declarations. The second one will hang ghc. If I
 change (coerce) to (coerce :: Normal a -> Sized a) it compiles fine. The
 first declaration also works fine.

 {{{
 {-# LANGUAGE TypeFamilies, FlexibleInstances #-}

 import qualified Data.FingerTree as FT
 import GHC.Exts

 class DOps a where
   plus :: a -> D a -> a

 type family D a :: *
 type instance D (FT.FingerTree (Size Int, v) (Sized a)) = [Diff (Normal
 a)]

 type family Normal a :: *

 data Diff a = Add Int a

 newtype Sized a = Sized a
 newtype Size a = Size a

 -- This works:
 instance (FT.Measured (Size Int, v) (Sized a), Coercible (Normal a) (Sized
 a)) => DOps (FT.FingerTree (Size Int, v) (Sized a)) where
   plus = foldr (\(Add index val) seq -> FT.singleton ((coerce) val))

 -- This hangs:
 instance (FT.Measured (Size Int, v) (Sized a), Coercible (Normal a) (Sized
 a)) => DOps (FT.FingerTree (Size Int, v) (Sized a)) where
   plus = foldr (flip f)
     where f seq x = case x of
             Add index val -> FT.singleton ((coerce) val)
 }}}

 {{{
 $ ~/downloads/ghc-7.10.0.20150123/out/bin/ghci --version
 The Glorious Glasgow Haskell Compilation System, version 7.10.0.20150123
 }}}

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


More information about the ghc-tickets mailing list