
#12844: No Skolem Info with PartialTypeSignatures -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | 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: -------------------------------------+------------------------------------- The following program triggers a panic: {{{ {-# LANGUAGE DataKinds #-} {-# LANGUAGE PartialTypeSignatures #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} barWraper :: ('(r,r') ~ Head rngs, Foo rngs) => FooData rngs barWraper = bar bar :: (_) => FooData rngs bar = foo data FooData rngs class Foo xs where foo :: (Head xs ~ '(r,r')) => FooData xs type family Head (xs :: [k]) where Head (x ': xs) = x }}} {{{
ghci NoSkolem.hs [1 of 1] Compiling Main ( NoSkolem.hs, NoSkolem.o )
NoSkolem.hs:8:13: error:ghc: panic! (the 'impossible' happened) (GHC version 8.0.1 for x86_64-unknown-linux): No skolem info: k_aYV[sk] }}} I haven't tested with 8.0.2 or head. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12844 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler