[GHC] #13333: Typeable regression in GHC HEAD
GHC
ghc-devs at haskell.org
Fri Feb 24 21:54:21 UTC 2017
#13333: Typeable regression in GHC HEAD
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: high | Milestone: 8.2.1
Component: Compiler (Type | Version: 8.1
checker) |
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by RyanGlScott):
I've observed something even stranger about this program. Let's tweak it
slightly and add a couple more things (note that the definition of
`dataCast1T` is unchanged):
{{{#!hs
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeInType #-}
{-# LANGUAGE TypeOperators #-}
module DataCast where
import Data.Data
import GHC.Exts (Constraint)
data T (phantom :: k) = T
data D (p :: k -> Constraint) (x :: j) where
D :: forall (p :: k -> Constraint) (x :: k). p x => D p x
class Possibly p x where
possibly :: proxy1 p -> proxy2 x -> Maybe (D p x)
instance Possibly Data () where
possibly _ _ = Just D
dataCast1T :: forall k c t (phantom :: k).
(Typeable k, Typeable t, Typeable phantom, Possibly Data
phantom)
=> (forall d. Data d => c (t d))
-> Maybe (c (T phantom))
dataCast1T f = case possibly (Proxy :: Proxy Data) (Proxy :: Proxy
phantom) of
Nothing -> Nothing
Just D -> gcast1 f
newtype Q q x = Q { unQ :: x -> q }
ext1Q :: (Typeable k, Typeable t, Typeable (phantom :: k), Possibly Data
phantom)
=> (T phantom -> q)
-> (forall e. Data e => t e -> q)
-> T phantom -> q
ext1Q def ext arg =
case dataCast1T (Q ext) of
Just (Q ext') -> ext' arg
Nothing -> def arg
}}}
With GHC HEAD, this gives the same error as the original program. But if
you add this one definition to this file:
{{{#!hs
test1 :: Char
test1 = (const 'p') `ext1Q` (\T -> 'q') $ (T :: T ())
}}}
Then it typechecks without issue on GHC HEAD! This is pretty bizarre,
considering that the error was originally reported in `dataCast1T`, and we
managed to make the error go away without making a single change to
`dataCast1T`.
FWIW, this program also compiles without issue on GHC 8.0.2 (with and
without `test1`).
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13333#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list