[GHC] #13610: Unhelpful error messages about lifted and unlifted types

#13610: Unhelpful error messages about lifted and unlifted types -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 (Type checker) | 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: -------------------------------------+------------------------------------- I wrote this code: {{{ {-# LANGUAGE MagicHash #-} import GHC.Prim import GHC.Types main = do let primDouble = 0.42## :: Double# let double = 0.42 :: Double IO (\s -> mkWeakNoFinalizer# double () s) }}} and I get this error message: {{{ WeakDouble.hs:8:15: error: • Couldn't match a lifted type with an unlifted type Expected type: (# State# RealWorld, Weak# () #) Actual type: (# State# RealWorld, Weak# () #) • In the expression: mkWeakNoFinalizer# double () s In the first argument of ‘IO’, namely ‘(\ s -> mkWeakNoFinalizer# double () s)’ In a stmt of a 'do' block: IO (\ s -> mkWeakNoFinalizer# double () s) }}} with `-fprint-explicit-kinds`. (Without the flag, it looks the same, but tells me to use this flag…). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13610 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13610: Unhelpful error messages about lifted and unlifted types -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: 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 nomeata): Ah, the problem is that `IO`’s type expects the second component of the tuple to be lifted, but `Weak#` is not. So the code is indeed bogus, but the error message is not very helpful. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13610#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13610: Unhelpful error messages about lifted and unlifted types -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: 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 guess the question is this: should `-fprint-explicit-kinds` print unboxed tuple types in prefix so that the levity arguments are displayed? I think: no. But perhaps `-fprint-explicit-runtime-reps` should, and GHC should be taught to tell the user about this flag instead of `-fprint- explicit-kinds` in this scenario. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13610#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13610: Unhelpful error messages about lifted and unlifted types -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: bug | Status: new Priority: low | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: 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 nomeata): * priority: normal => low Comment: I am not sure if printing type prefixes would have improved manners. What would it say? Maybe {{{ Expected type: (#,#) VoidRep LiftedRep (State# RealWorld) (Weak# ()) Actual type: (#,#) VoidRep PrimRep (State# RealWorld) (Weak# ()) }}} But the “actual type” is not well-kinded; it cannot really be the “actual type” of anything. So it seems that something went wrong earlier during type inference? I guess something along these lines would have been more helpful: {{{ WeakDouble.hs:8:15: error: • Couldn't match a lifted type with an unlifted type Expected type representation: LiftedRep Actual type representation: PrimRep • In the second element of the unlifted tuple • In the type of the expression: mkWeakNoFinalizer# double () s }}} Anyways; this was not triggered by writing real code, so I’ll lower the priority. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13610#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13610: Unhelpful error messages about lifted and unlifted types -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: bug | Status: new Priority: low | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: 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): This may be fixed by the fix to #11198. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13610#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13610: Unhelpful error messages about lifted and unlifted types -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: bug | Status: new Priority: low | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: 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 bgamari): * milestone: => 8.2.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13610#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13610: Unhelpful error messages about lifted and unlifted types -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: bug | Status: new Priority: low | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: 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 bgamari): * milestone: 8.2.1 => 8.4.1 Comment: Bumping off to 8.4. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13610#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13610: Unhelpful error messages about lifted and unlifted types
-------------------------------------+-------------------------------------
Reporter: nomeata | Owner: (none)
Type: bug | Status: new
Priority: low | Milestone: 8.4.1
Component: Compiler (Type | Version: 8.1
checker) |
Resolution: | Keywords:
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

#13610: Unhelpful error messages about lifted and unlifted types -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: bug | Status: closed Priority: low | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_fail/T13610 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * testcase: => typecheck/should_fail/T13610 * status: new => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13610#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC