[GHC] #11681: ghc panic with TypeError
GHC
ghc-devs at haskell.org
Wed Mar 9 01:51:27 UTC 2016
#11681: ghc panic with TypeError
-------------------------------------+-------------------------------------
Reporter: inaki | Owner:
Type: bug | Status: new
Priority: normal | Milestone: 8.0.1
Component: Compiler (Type | Version: 8.0.1-rc2
checker) |
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by inaki):
Replying to [comment:5 aavogt]:
> I can't reproduce the original problem with -rc2 either
This is very bizarre: I just updated to the latest build in fedora (which
still identifies itself with the same version) and couldn't reproduce the
crash either. But the example by aavogt above also crashes for me. And
playing around with my original example, the following **does** crash:
{{{#!hs
{-# LANGUAGE DataKinds, FlexibleContexts, TypeOperators,
FlexibleInstances #-}
import GHC.TypeLits
class C t where
instance
(TypeError (Text "A" :<>: {- Text -} "B"))
=> C t where
main :: IO ()
main = return ()
}}}
Notice the absence of the `UndecidableInstances` extension, the content is
otherwise identical. It is not impossible I made a mistake when copying
the original example for the crash, apologies if this was the case.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11681#comment:6>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list