[GHC] #14570: Untouchable error arises from type equality, but not equivalent program with fundeps

#14570: Untouchable error arises from type equality, but not equivalent program with fundeps -------------------------------------+------------------------------------- Reporter: lexi.lambda | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 (Type checker) | 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: -------------------------------------+------------------------------------- Given some type definitions: {{{#!hs data A data B (f :: * -> *) data X (k :: *) }}} …and this typeclass: {{{#!hs class C k a | k -> a }}} …these (highly contrived for the purposes of a minimal example) function definitions typecheck: {{{#!hs f :: forall f. (forall k. (C k (B f)) => f k) -> A f _ = undefined g :: (forall k. (C k (B X)) => X k) -> A g = f }}} However, if we use a type family instead of a class with a functional dependency: {{{#!hs type family F (k :: *) }}} …then the equivalent function definitions fail to typecheck: {{{#!hs f :: forall f. (forall k. (F k ~ B f) => f k) -> A f _ = undefined g :: (forall k. (F k ~ B X) => X k) -> A g = f }}} {{{ • Couldn't match type ‘f0’ with ‘X’ ‘f0’ is untouchable inside the constraints: F k ~ B f0 bound by a type expected by the context: F k ~ B f0 => f0 k Expected type: f0 k Actual type: X k • In the expression: f In an equation for ‘g’: g = f }}} I read Section 5.2 of the OutsideIn(X) paper, which describes touchable and untouchable type variables, and I ''sort of'' understand what’s going on here. If I add an extra argument to `f` that pushes the choice of `f` outside the inner `forall`, then the program typechecks: {{{#!hs f :: forall f a. f a -> (forall k. (F k ~ B f) => f k) -> A f _ _ = undefined g :: forall a. X a -> (forall k. (F k ~ B X) => X k) -> A g = f }}} I don’t know if this is actually a bug—it seems entirely reasonable to me that I don’t fully understand what is going on here—but I’m stumped as to ''why'' GHC rejects this program but accepts the one involving functional dependencies. I would expect it to either accept or reject both programs, given they ''seem'' equivalent. Is this just an unfortunate infelicity of the differences between how functional dependencies and type equalities are internally solved? Or is there a deeper difference between these two programs? ,,(Note: This ticket is adapted from [https://stackoverflow.com/q/47734825/465378 this Stack Overflow question].),, -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14570 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14570: Untouchable error arises from type equality, but not equivalent program with fundeps -------------------------------------+------------------------------------- Reporter: lexi.lambda | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.2 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 simonpj): Consider {{{ {-# LANGUAGE MultiParamTypeClasses, FlexibleContexts, GADTs, FunctionalDependencies #-} class C k a | k -> a data T a where MkT :: (a ~ Bool) => a -> T a data S a where MkS :: (C Bool a) => a -> S a f1 (MkT x) = x f2 (MkS x) = x }}} Here, `f2` typechecks fine, yielding `f2 :: S a -> a`. But `f1` is rejected with an untouchable-tyvar error. But, as in your emample, one has a fundep and the other has a type equality. Reason: fundeps affect only type inference, causing more unifications to happen. They do not carry evidence, and are not reflected in GHC's internal language System FC. Schrijvers et al have [https://people.cs.kuleuven.be/~tom.schrijvers/portfolio/haskell2017a.html a paper about this in at HS'17]. I haven't unpicked your example precisely but I wanted to give you a simple case in which fundeps and type equalities behave differently, by design. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14570#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14570: Untouchable error arises from type equality, but not equivalent program with fundeps -------------------------------------+------------------------------------- Reporter: lexi.lambda | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.2 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 lexi.lambda): Thanks, that’s helpful. I’m content with this ticket being closed, though I am a little interested in the fact that you say they behave differently “by design”. I have two small followup questions: 1. Is there a description of this design choice in existing literature somewhere? I imagine the difference is because fundeps are more restricted than type families, so some generality is traded away for better type inference, but I’m not ''entirely'' sure if that’s true. 2. I have not yet read the paper you linked in detail, though I will—it seems quite interesting. However, more generally, if functional dependencies ''are'' elaborated in a way similar to how type families are, will this design difference be maintained? Or will they act more similarly? I think the conversation in #11534 is likely highly relevant to my root problem here—I had some code that used functional dependencies and ended up with an ''enormous'' number of type variables that needed to be propagated around, despite the fact that many of them were determined by other type variables via functional dependency. I tried switching to type families to eliminate the need to carry around so many variables, and my program stopped typechecking (giving the untouchable error). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14570#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14570: Untouchable error arises from type equality, but not equivalent program with fundeps -------------------------------------+------------------------------------- Reporter: lexi.lambda | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.2 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: | -------------------------------------+------------------------------------- Changes (by dfeuer): * cc: dfeuer (added) Comment: At the least, this is a rather poor error message. I don't think it's terribly reasonable to expect users to read and understand near-cutting- edge papers about type inference in order to understand what they've done wrong and how they might fix it. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14570#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14570: Untouchable error arises from type equality, but not equivalent program with fundeps -------------------------------------+------------------------------------- Reporter: lexi.lambda | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.2 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 AntC): Replying to [comment:3 dfeuer]:
At the least, this is a rather poor error message.
I'm wondering if the o.p. gave the full story about the error message. I retried the Type Family version, and got `f0 is untouchable` rejection, but against the type for `f`. The message went on to give more info `f is a rigid type variable ...`; plus a suggestion to `AllowAmbiguousTypes`. Switching that on does indeed suppress the message against `f`; then it just reappears against `g`, as per the o.p., but with less helpful info. (I've put more narrative against the StackOverflow question, link above.) Simon's explanation at comment:1 tells what's going on, but not really why. The Schrijvers et al paper didn't really help: it's aiming to explain FunDep inference in terms of Type Families/System FC, so doesn't tell why/how ghc's behaviour is different in this example. Re the `rigid type variable` message, there are some reasonable explanations on StackOverflow. Re `f0 is untouchable` not so much. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14570#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC