[GHC] #10403: GHC crashes on a partial type signature
GHC
ghc-devs at haskell.org
Mon May 11 16:05:33 UTC 2015
#10403: GHC crashes on a partial type signature
-------------------------------------+-------------------------------------
Reporter: | Owner:
Artyom.Kazak | Status: new
Type: bug | Milestone:
Priority: normal | Version: 7.10.1
Component: Compiler | Operating System: Linux
Keywords: | Type of failure: Compile-time
Architecture: x86_64 | crash
(amd64) | Blocked By:
Test Case: | Related Tickets:
Blocking: |
Differential Revisions: |
-------------------------------------+-------------------------------------
The following code crashes GHC 7.10.1 as is, but doesn't result in a crash
if the signature is specified completely or isn't specified at all
(inferred):
{{{#!hs
{-# LANGUAGE PartialTypeSignatures #-}
module Main where
data I a = I a
instance Functor I where
fmap f (I a) = I (f a)
newtype B t a = B a
instance Functor (B t) where
fmap f (B a) = B (f a)
newtype H f = H (f ())
app :: H (B t)
app = h (H . I) (B ())
h :: _
--h :: Functor m => (a -> b) -> m a -> H m
h f b = (H . fmap (const ())) (fmap f b)
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10403>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list