
#8651: 'Untouchable' error when using type function in class constraint in rank-2 type -------------------------------------------+------------------------------- Reporter: sbarclay | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type checker) | Version: 7.7 Keywords: | Operating System: Architecture: Unknown/Multiple | Unknown/Multiple Difficulty: Unknown | Type of failure: Blocked By: | None/Unknown Related Tickets: #8644 #7594 | Test Case: | Blocking: -------------------------------------------+------------------------------- I noticed there are some cases that no longer compile after the recent fix for #8644, such as the following: {{{#!haskell {-# LANGUAGE RankNTypes, FlexibleContexts, TypeFamilies #-} import Data.Monoid type family Id a type instance Id a = a --type instance Id [a] = [Id a] foo :: (Monoid (Id String) => r) -> r foo x = x main :: IO () main = print $ foo "Hello" }}} Attempting to compile this on HEAD produces the same error in 'main' as reported in the earlier ticket: {{{ Couldn't match expected type ‛s0’ with actual type ‛[Char]’ ‛s0’ is untouchable }}} However, it compiles fine if the commented-out type family instance is used instead. It also compiles fine if the type family is replaced with an ordinary type synonym: {{{#!haskell type Id a = a }}} I guess that the problem is caused by equalities of the form t ~ [Char] introduced by the type family instance. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8651 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler