[GHC] #9258: Type inference fails with closed type families

#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

#9258: Type inference fails with closed type families -------------------------------------+------------------------------------ Reporter: augustss | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by jstolarek): I'm not an expert here, but it looks like you expect GHC to infer the arguments of s type family based on its result. I believe that's not possible in general and my guess is that GHC doesn't even try, even for a trivial case such as yours. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9258#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9258: Type inference fails with closed type families -------------------------------------+------------------------------------ Reporter: augustss | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by augustss): I don't see why ghc couldn't infer the commented out type. In a similar example {{{ --f :: D d Double ~ Double => Descr d -> Double f d = fld d :: Double }}} ghc is able to infer the commented out type. (Of course, for this function an error message would have been appropriate since there is no way this function can ever be used; it's like having Bool~Double as a constraint.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9258#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9258: Type inference fails with closed type families -------------------------------------+------------------------------------ Reporter: augustss | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by josef): It's the monomorphism restriction kicking in. The module compiles just fine with `-XNoMonomorphismRestriction` and infers the expected type to `decrIn`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9258#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9258: Type inference fails with closed type families -------------------------------------+------------------------------------ Reporter: augustss | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by augustss): Argh! You'd think I'd be old enough to turn off the monomorphism restriction. Thanks! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9258#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9258: Type inference fails with closed type families -------------------------------------+------------------------------------ Reporter: augustss | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Changes (by augustss): * status: new => closed * resolution: => invalid -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9258#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC