Coercible causes ghc to hang
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
Trac metadata
Trac field | Value |
---|---|
Version | 7.10.1-rc2 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |