[GHC] #13161: Unexpected error about untouchable variable

#13161: Unexpected error about untouchable variable -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 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: -------------------------------------+------------------------------------- Hello! I've got a strange error here. Let's consider the following code: {{{ {-# LANGUAGE RankNTypes #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE TypeFamilies #-} module Main where data X data Expr a = Expr Int type family Sum a b type instance Sum X X = X app :: Expr l -> (Expr l') -> m (Expr (Sum l l')) app = undefined finish :: Builder (Expr l) -> Builder (Expr X) finish = undefined type family Foo (m :: * -> *) :: * -> * class (Monad m, Foo (Foo m) ~ Foo m) => Ctx (m :: * -> *) newtype Builder a = Builder (forall m. Ctx m => m a) f :: Builder (Expr X) -> Builder (Expr X) -> Builder (Expr X) -> Builder (Expr X) f mop ma mb = finish $ Builder $ app (undefined :: (Expr X)) (undefined :: (Expr X)) main :: IO () main = return () }}} it results in error: {{{ UT.hs:24:34: error: • Couldn't match type ‘l0’ with ‘X’ ‘l0’ is untouchable inside the constraints: Ctx m bound by a type expected by the context: Ctx m => m (Expr l0) at UT.hs:24:24-84 Expected type: m (Expr l0) Actual type: m (Expr (Sum X X)) • In the second argument of ‘($)’, namely ‘app (undefined :: Expr X) (undefined :: Expr X)’ In the second argument of ‘($)’, namely ‘Builder $ app (undefined :: Expr X) (undefined :: Expr X)’ In the expression: finish $ Builder $ app (undefined :: Expr X) (undefined :: Expr X) }}} And that's very interesting, because it should (according to my knowledge) not happen. It is caused by the line: `finish $ Builder $ app (undefined :: (Expr X)) (undefined :: (Expr X))`. And we can observe here couple of things. First of all `app :: Expr l -> (Expr l') -> m (Expr (Sum l l'))` and `Sum X X = X`, so `app (undefined :: (Expr X)) (undefined :: (Expr X)) :: Expr X` - and GHC can clearly see it. What is more interesting is that if we put this signature explicitly it works! So If we change the error line to: {{{ ... f mop ma mb = finish $ (Builder $ app (undefined :: (Expr X)) (undefined :: (Expr X)) :: Builder (Expr X) }}} it compiles fine. Another interesting fact is that if I remove the constraint `Foo (Foo m) ~ Foo m` it also compiles fine, which is even more strange. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13161 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13161: Unexpected error about untouchable variable -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 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 goldfire): This is expected behavior, for a sufficiently nuanced expectation. The argument to builder is type-checked with an assumed equality, `Foo (Foo m) ~ Foo m`. Type variables brought into scope outside an assumed equality cannot be influenced by anything that arises with an equality assumption, because perhaps the equality assumption affects how that outer variable should be solved. In your case, GHC must infer the index `a` to the type `Builder`. We see that `a` should be `Expr l` for some `l`, looking at the type of `finish`. But what `l`? The only way to know would be to unify `l` with `X`, the result of the `app` -- but that `X` was derived with an assumed equality in scope. So we have an error. It is fixed by your type signature, which tells GHC what `l` should be, and it is fixed by removing the equality assumption, which avoid triggering the "untouchable variable" behavior. The beginning of section 5 of the [https://www.microsoft.com/en- us/research/publication/outsideinx-modular-type-inference-with-local- assumptions/ OutsideIn paper] gives a nice introduction to untouchable variables, accessible to intermediate (or better) Haskell programmers and with no need to read anything before section 5. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13161#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13161: Unexpected error about untouchable variable -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 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 goldfire): If you're satisfied with this answer, please close the ticket. Thanks! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13161#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13161: Unexpected error about untouchable variable -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 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 danilo2): Richard, thanks for the explanation. I'm closing the ticket right now, but after reading the docs I might re-open it with some further thoughts. Thank you once again! :) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13161#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13161: Unexpected error about untouchable variable -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: invalid | 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 danilo2): * status: new => closed * resolution: => invalid -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13161#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC