[GHC] #13530: Horrible error message due to TypeInType

#13530: Horrible error message due to TypeInType -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Consider this {{{ {-# LANGUAGE MagicHash, UnboxedTuples #-} module Foo where import GHC.Exts g :: Int -> (# Int#, a #) g (I# y) = (# y, undefined #) f :: Int -> (# Int#, Int# #) f x = g x }}} With GHC 8 we get {{{ Foo.hs:11:7: error: • Couldn't match a lifted type with an unlifted type Expected type: (# Int#, Int# #) Actual type: (# Int#, Int# #) }}} What a terrible error message!! It was much better in GHC 7.10: {{{ Foo.hs:11:7: Couldn't match kind ‘*’ with ‘#’ When matching types a0 :: * Int# :: # Expected type: (# Int#, Int# #) Actual type: (# Int#, a0 #) }}} What's going on? The constraint solver sees {{{ [W] alpha::TYPE LiftedRep ~ Int#::TYPE IntRep }}} So it homogenises the kinds, ''and unifies alpha'' (this did not happen in GHC 7.10), thus {{{ alpha := Int# |> TYPE co [W] co :: LiftedRep ~ IntRep }}} Of course the new constraint fails. But since we have unified alpha, when we print out the types are are unifying they both look like `(# Int#, Int# #)` (there's a suppressed cast in the second component). I'm not sure what to do here. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13530 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13530: Horrible error message due to TypeInType -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: => TypeInType -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13530#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13530: Horrible error message due to TypeInType -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): I think this is #11198. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13530#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13530: Horrible error message due to TypeInType -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Dead right. We should fix this! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13530#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13530: Horrible error message due to TypeInType
-------------------------------------+-------------------------------------
Reporter: simonpj | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Resolution: | Keywords: TypeInType
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#13530: Horrible error message due to TypeInType -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by simonpj: Old description:
Consider this {{{ {-# LANGUAGE MagicHash, UnboxedTuples #-}
module Foo where
import GHC.Exts
g :: Int -> (# Int#, a #) g (I# y) = (# y, undefined #)
f :: Int -> (# Int#, Int# #) f x = g x }}} With GHC 8 we get {{{ Foo.hs:11:7: error: • Couldn't match a lifted type with an unlifted type Expected type: (# Int#, Int# #) Actual type: (# Int#, Int# #) }}} What a terrible error message!! It was much better in GHC 7.10: {{{ Foo.hs:11:7: Couldn't match kind ‘*’ with ‘#’ When matching types a0 :: * Int# :: # Expected type: (# Int#, Int# #) Actual type: (# Int#, a0 #) }}} What's going on?
The constraint solver sees {{{ [W] alpha::TYPE LiftedRep ~ Int#::TYPE IntRep }}} So it homogenises the kinds, ''and unifies alpha'' (this did not happen in GHC 7.10), thus {{{ alpha := Int# |> TYPE co
[W] co :: LiftedRep ~ IntRep }}} Of course the new constraint fails. But since we have unified alpha, when we print out the types are are unifying they both look like `(# Int#, Int# #)` (there's a suppressed cast in the second component).
I'm not sure what to do here.
New description: Consider this {{{ {-# LANGUAGE MagicHash, UnboxedTuples #-} module Foo where import GHC.Exts g :: Int -> (# Int#, a #) g (I# y) = (# y, undefined #) f :: Int -> (# Int#, Int# #) f x = g x }}} With GHC 8 we get {{{ Foo.hs:11:7: error: • Couldn't match a lifted type with an unlifted type Expected type: (# Int#, Int# #) Actual type: (# Int#, Int# #) }}} What a terrible error message!! It was much better in GHC 7.10: {{{ Foo.hs:11:7: Couldn't match kind ‘*’ with ‘#’ When matching types a0 :: * Int# :: # Expected type: (# Int#, Int# #) Actual type: (# Int#, a0 #) }}} What's going on? The constraint solver sees {{{ [W] alpha::TYPE LiftedRep ~ Int#::TYPE IntRep }}} So it homogenises the kinds, ''and unifies alpha'' (this did not happen in GHC 7.10), thus {{{ alpha := Int# |> TYPE co [W] co :: LiftedRep ~ IntRep }}} Of course the new constraint fails. But since we have unified alpha, when we print out the types are are unifying they both look like `(# Int#, Int# #)` (there's a suppressed cast in the second component). I'm not sure what to do here. (I tripped over this when debugging #13509.) -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13530#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13530: Horrible error message due to TypeInType
-------------------------------------+-------------------------------------
Reporter: simonpj | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Resolution: | Keywords: TypeInType
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Richard Eisenberg

#13530: Horrible error message due to TypeInType -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_fail/T13530 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * testcase: => typecheck/should_fail/T13530 * status: new => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13530#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC