
#15796: Core Lint error with invalid newtype declaration -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Compiler (Type | Version: 8.6.1 checker) | Resolution: | Keywords: TypeFamilies Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: TypeInType => TypeFamilies * failure: None/Unknown => Compile-time crash or panic * component: Compiler => Compiler (Type checker) * milestone: => 8.8.1 Comment: Even simpler example: {{{#!hs {-# LANGUAGE GADTs #-} {-# LANGUAGE TypeFamilies #-} module Bug where newtype N a where MkN :: Show a => a -> N a type family T a type instance T (N a) = N a }}} {{{ $ /opt/ghc/8.6.1/bin/ghci Bug.hs -dcore-lint GHCi, version 8.6.1: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) ghc: panic! (the 'impossible' happened) (GHC version 8.6.1 for x86_64-unknown-linux): Core Lint error <no location info>: warning: In the type ‘N a_a1P7’ Found TcTyCon: N[tc] Call stack: CallStack (from HasCallStack): callStackDoc, called at compiler/utils/Outputable.hs:1160:37 in ghc:Outputable pprPanic, called at compiler/typecheck/FamInst.hs:171:31 in ghc:FamInst }}} The culprit appears to be the invalid `Show a` context in the `MkN` newtype constructor, as removing that makes the Core Lint error go away. Note that this only happens in GHC 8.6.1 and later. In earlier versions of GHC, this simply gives an error message: {{{ $ /opt/ghc/8.4.4/bin/ghc Bug.hs -dcore-lint [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) Bug.hs:6:3: error: • A newtype constructor cannot have a context in its type MkN :: forall a. Show a => a -> N a • In the definition of data constructor ‘MkN’ In the newtype declaration for ‘N’ | 6 | MkN :: Show a => a -> N a | ^^^^^^^^^^^^^^^^^^^^^^^^^ }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15796#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler