
#9750: Core lint failure with TypeLits Symbol -------------------------------------+------------------------------------- Reporter: dreixel | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 Keywords: | Operating System: Architecture: Unknown/Multiple | Unknown/Multiple Difficulty: Unknown | Type of failure: Blocked By: | None/Unknown Related Tickets: | Test Case: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- The following module: {{{ {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE ScopedTypeVariables #-} module Bug where import GHC.TypeLits ( Symbol, KnownSymbol ) -------------------------------------------------------------------------------- data Meta = MetaCons Symbol data M1 (c :: Meta) = M1 class Generic a where type Rep a :: * from :: a -> Rep a -------------------------------------------------------------------------------- data A = A1 instance Generic A where type Rep A = M1 ('MetaCons "test") from A1 = M1 class GShow' f where gshowsPrec' :: f -> ShowS instance (KnownSymbol c) => GShow' (M1 ('MetaCons c)) instance GShow' A where gshowsPrec' = gshowsPrec' . from }}} fails `-dcore-lint` in HEAD with: {{{ *** Core Lint errors : in result of Desugar (after optimization) *** <no location info>: Warning: [RHS of $dKnownSymbol_azn :: GHC.TypeLits.KnownSymbol "test"] From-type of Cast differs from type of enclosed expression From-type: GHC.TypeLits.KnownSymbol "test" Type of enclosed expr: [GHC.Types.Char] Actual enclosed expr: GHC.CString.unpackCString# "test"# Coercion used in cast: GHC.TypeLits.NTCo:KnownSymbol[0] <"test">_N ; GHC.TypeLits.NTCo:SSymbol[0] <"test">_P }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9750 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler