[GHC] #13872: Strange Typeable error message involving TypeInType
GHC
ghc-devs at haskell.org
Sat Jun 24 16:06:17 UTC 2017
#13872: Strange Typeable error message involving TypeInType
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
(Type checker) |
Keywords: TypeInType, | Operating System: Unknown/Multiple
Typeable |
Architecture: | Type of failure: Poor/confusing
Unknown/Multiple | error message
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
I originally discovered this when tinkering with #13871. This program:
{{{#!hs
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeInType #-}
{-# LANGUAGE TypeOperators #-}
module Foo where
import Data.Kind
import Data.Typeable
data Foo (a :: Type) (b :: Type) where
MkFoo :: (a ~ Int, b ~ Char) => Foo a b
data family Sing (a :: k)
data SFoo (z :: Foo a b) where
SMkFoo :: SFoo MkFoo
f :: String
f = show $ typeOf SMkFoo
}}}
Fails in GHC 8.0.1, 8.0.2, and 8.2 (after applying Phab:D3671) with a
rather unsightly error message:
{{{
GHCi, version 8.3.20170624: http://www.haskell.org/ghc/ :? for help
Loaded GHCi configuration from /home/rgscott/.ghci
[1 of 1] Compiling Foo ( Foo.hs, interpreted )
Foo.hs:19:12: error:
• No instance for (Typeable <>) arising from a use of ‘typeOf’
• In the second argument of ‘($)’, namely ‘typeOf SMkFoo’
In the expression: show $ typeOf SMkFoo
In an equation for ‘f’: f = show $ typeOf SMkFoo
|
19 | f = show $ typeOf SMkFoo
| ^^^^^^^^^^^^^
}}}
I'm not sure what this mysterious `<>` is, but I'm pretty sure it
shouldn't be making an appearance here. (See also #13780, where `<>` also
makes a surprise guest appearance.)
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13872>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list