
#15050: ScopedTypeVariables could allow more programs -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): Here is another case where `ScopedTypeVariables` are less powerful than one might expect. This works: {{{ {-# LANGUAGE GADTs #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} type family F a where F Bool = Int data T a where MkT :: forall b a. b ~ F a => b -> T a foo :: T Bool -> () foo (MkT (_ :: Int)) = () }}} but the equivalent(?) formulation using `TypeFamilies` does not: {{{ {-# LANGUAGE GADTs #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FunctionalDependencies #-} class C b a | a -> b instance C Int Bool data T a where MkT :: forall b a. C b a => b -> T a foo :: T Bool -> () foo (MkT (_ :: Int)) = () }}} gives {{{ /tmp/Foo.hs:11:11: error: • Couldn't match expected type ‘b’ with actual type ‘Int’ ‘b’ is a rigid type variable bound by a pattern with constructor: MkT :: forall b a. C b a => b -> T a, in an equation for ‘foo’ at /tmp/Foo.hs:11:6-19 • When checking that the pattern signature: Int fits the type of its context: b In the pattern: _ :: Int In the pattern: MkT (_ :: Int) }}} }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15050#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler