
#16204: GHC HEAD-only Core Lint error (Argument value doesn't match argument type) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.8.1 Component: Compiler (Type | Version: 8.7 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #16188 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by monoidal): I simplified to: {{{ #!haskell {-# LANGUAGE DataKinds #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} module T16204 where import Data.Kind data family Sing :: forall k. k -> Type type family Rep (a :: Type) :: Type type family PTo (x :: Rep a) :: a sTo :: forall (k :: Type) (a :: Rep k). (Sing a, Sing (PTo a :: k)) sTo = sTo x :: forall (a :: Type). Sing a x = fst sTo }}} This program is rejected (IMO correctly) by 8.6, but gives Core Lint error in HEAD. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16204#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler