[GHC] #9258: Type inference fails with closed type families
GHC
ghc-devs at haskell.org
Wed Jul 2 14:46:33 UTC 2014
#9258: Type inference fails with closed type families
------------------------------------+-------------------------------------
Reporter: augustss | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.8.2
Keywords: | Operating System: Unknown/Multiple
Architecture: Unknown/Multiple | Type of failure: None/Unknown
Difficulty: Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: |
------------------------------------+-------------------------------------
Consider the following module:
{{{
{-# LANGUAGE TypeFamilies #-}
module M where
type family D d a where
D () a = Bool
data Descr d = Descr {
fld :: D d Double
}
--descrIn :: (D d Double ~ Bool) => Descr d
descrIn = Descr { fld = True }
}}}
I expected ghc to infer the commented out type signature, but instead I
get an error:
{{{
$ ghc -Wall -c ./test/M.hs
test\M.hs:12:25:
Couldn't match expected type `D d0 Double' with actual type `Bool'
The type variable `d0' is ambiguous
Relevant bindings include
descrIn :: Descr d0 (bound at test\M.hs:12:1)
In the `fld' field of a record
In the expression: Descr {fld = True}
}}}
Uncommenting the type signature makes the module compile.
As an aside, the signature I really want ghc to deduce is
{{{
descrIn :: Descr ()
}}}
But since ghc doesn't (yet) use the full information provided by the
closed type family equations this doesn't happen. Still, it should be
able to figure out the commented out one.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9258>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list