[GHC] #9893: Switching on TypeFamilies extension stops code from typechecking
GHC
ghc-devs at haskell.org
Wed Dec 17 11:14:49 UTC 2014
#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
More information about the ghc-tickets
mailing list