[GHC] #9893: Switching on TypeFamilies extension stops code from typechecking

#9893: Switching on TypeFamilies extension stops code from typechecking -------------------------------------+------------------------------------- Reporter: phischu | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.3 Keywords: | Operating System: Architecture: x86_64 (amd64) | Unknown/Multiple Difficulty: Unknown | Type of failure: GHC Blocked By: | rejects valid program Related Tickets: | Test Case: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- The following code has the `TypeFamilies` extension enabled but does not use it. It does not typecheck with GHC 7.8.3. If we do not enable `TypeFamilies` (i.e. delete the first line) it typechecks. {{{ {-# LANGUAGE TypeFamilies #-} module ExistentialFamilies where import Control.Monad.ST (runST,ST) un :: () un = runST f where f = return un :: ST s () }}} This happens when trying to compile the program as well as when trying to load it into ghci. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9893 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9893: Switching on TypeFamilies extension stops code from typechecking -------------------------------------+------------------------------------- Reporter: phischu | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.3 Resolution: | Keywords: Operating System: | Architecture: x86_64 (amd64) Unknown/Multiple | Difficulty: Unknown Type of failure: GHC | Blocked By: rejects valid program | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Description changed by phischu: Old description:
The following code has the `TypeFamilies` extension enabled but does not use it. It does not typecheck with GHC 7.8.3. If we do not enable `TypeFamilies` (i.e. delete the first line) it typechecks.
{{{ {-# LANGUAGE TypeFamilies #-} module ExistentialFamilies where
import Control.Monad.ST (runST,ST)
un :: () un = runST f where f = return un :: ST s () }}} This happens when trying to compile the program as well as when trying to load it into ghci.
New description: The following code has the `TypeFamilies` extension enabled but does not use it. It does not typecheck with GHC 7.8.3. If we do not enable `TypeFamilies` (i.e. delete the first line) it typechecks. {{{ {-# LANGUAGE TypeFamilies #-} module ExistentialFamilies where import Control.Monad.ST (runST,ST) un :: () un = runST f where f = return un :: ST s () }}} This happens when trying to compile the program as well as when trying to load it into ghci. The error message when `TypeFamilies` is on is {{{
ghc ExistentialFamilies.hs [1 of 1] Compiling ExistentialFamilies ( ExistentialFamilies.hs, ExistentialFamilies.o )
ExistentialFamilies.hs:7:12: Couldn't match type ‘s0’ with ‘s’ because type variable ‘s’ would escape its scope This (rigid, skolem) type variable is bound by a type expected by the context: ST s () at ExistentialFamilies.hs:7:6-12 Expected type: ST s () Actual type: ST s0 () Relevant bindings include f :: ST s0 () (bound at ExistentialFamilies.hs:8:5) In the first argument of ‘runST’, namely ‘f’ In the expression: runST f }}} -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9893#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9893: Switching on TypeFamilies extension stops code from typechecking -------------------------------------+------------------------------------- Reporter: phischu | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.8.3 Resolution: invalid | Keywords: Operating System: | Architecture: x86_64 (amd64) Unknown/Multiple | Difficulty: Unknown Type of failure: GHC | Blocked By: rejects valid program | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * resolution: => invalid Comment: This is confusing, but it's by design. With `TypeFamilies` we also get `MonoLocalBinds`, so that `f`'s definition (which is local) is not generalised. But `runST` requires a polymorphic `f`; and a monomorphic `f` isn't good enough. Hence the error. Giving a type signature to `f` is enough. (Giving a type signature to its right hand side, on the other hand, is not enough Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9893#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC