[GHC] #15142: GHC HEAD regression: tcTyVarDetails
GHC
ghc-devs at haskell.org
Mon May 14 12:27:13 UTC 2018
#15142: GHC HEAD regression: tcTyVarDetails
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: highest | Milestone: 8.6.1
Component: Compiler (Type | Version: 8.5
checker) | Keywords: TypeInType,
Resolution: | 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: |
-------------------------------------+-------------------------------------
Comment (by RyanGlScott):
Further observations:
* `MultiParamTypeClasses` is also important to triggering this, since this
panics:
{{{#!hs
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeInType #-}
module Bug where
import Data.Kind
class C (a :: Type) (b :: k) where
type T b
}}}
But not this:
{{{#!hs
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeInType #-}
module Bug where
import Data.Kind
class C (b :: k) where
type T b
}}}
* The order of arguments to `C`, as well as the exact kind signatures
given to them, also appears to be important, as none of the following
panics:
{{{#!hs
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeInType #-}
module Bug where
import Data.Kind
class C1 (b :: k) (a :: Type) where
type T1 b
class C2 b (a :: Type) where
type T2 b
class C3 b a where
type T3 b
class C4 (b :: k) a where
type T4 b
class C5 a (b :: k) where
type T5 b
class C6 (a :: Type) b where
type T6 b
class C7 a b where
type T7 b
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15142#comment:3>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list