[GHC] #10403: GHC crashes on a partial type signature
GHC
ghc-devs at haskell.org
Mon May 11 16:18:39 UTC 2015
#10403: GHC crashes on a partial type signature
-------------------------------------+-------------------------------------
Reporter: Artyom.Kazak | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.10.1
Resolution: | Keywords:
Operating System: Linux | Architecture: x86_64
Type of failure: Compile-time | (amd64)
crash | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Revisions:
-------------------------------------+-------------------------------------
Description changed by Artyom.Kazak:
Old description:
> 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)
> }}}
New description:
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
main :: IO ()
main = return ()
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#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list