
#14883: QuantifiedConstraints don't kick in when used in TypeApplications -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.5 checker) | Keywords: Resolution: | QuantifiedConstraints, wipT2893 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): Another example in the same vein: {{{#!hs {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE ImpredicativeTypes #-} {-# LANGUAGE InstanceSigs #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE QuantifiedConstraints #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} module Bug where import Data.Coerce import Data.Kind type Phantom1 p = (forall a b. Coercible (p a) (p b) :: Constraint) class Foo a where bar :: Phantom1 proxy => proxy a -> Int instance Foo Int where bar _ = 42 -- Typecheck newtype Age1 = MkAge1 Int instance Foo Age1 where bar :: forall proxy. Phantom1 proxy => proxy Age1 -> Int bar = coerce @(proxy Int -> Int) @(proxy Age1 -> Int) bar -- Doesn't typecheck newtype Age2 = MkAge2 Int instance Foo Age2 where bar = coerce @(forall proxy. Phantom1 proxy => proxy Int -> Int) @(forall proxy. Phantom1 proxy => proxy Age2 -> Int) bar }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14883#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler