[GHC] #14149: Tyepchecker generates top-level unboxed coercion

#14149: Tyepchecker generates top-level unboxed coercion -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.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 code {{{ {-# OPTIONS_GHC -fdefer-out-of-scope-variables #-} module Foo where import Data.Coerce f :: Bool f = coerce (k :: Int) }}} It generates a lint error: {{{ *** Core Lint errors : in result of Desugar (after optimization) *** <no location info>: warning: [RHS of cobox_a11N :: (Int :: *) ~R# (Bool :: *)] The type of this binder is unlifted: cobox_a11N Binder's type: (Int :: *) ~R# (Bool :: *) *** Offending Program *** $trModule :: Module [LclIdX] $trModule = Module (TrNameS "main"#) (TrNameS "Foo"#) cobox_a11N :: (Int :: *) ~R# (Bool :: *) [LclId[CoVarId]] cobox_a11N = typeError @ ('TupleRep '[]) @ ((Int :: *) ~R# (Bool :: *)) "Foo.hs:8:5: error:\n\ \ \\226\\128\\162 Couldn't match representation of type \\226\\128\\152Int\\226\\128\\153 with that of \\226\\128\\152Bool\\226\\128\\153\n\ \ arising from a use of \\226\\128\\152coerce\\226\\128\\153\n\ \ \\226\\128\\162 In the expression: coerce (k :: Int)\n\ \ In an equation for \\226\\128\\152f\\226\\128\\153: f = coerce (k :: Int)\n\ \(deferred type error)"# f :: Bool [LclIdX] f = (typeError @ 'LiftedRep @ Int "Foo.hs:8:13: error: Variable not in scope: k :: Int\n\ \(deferred type error)"#) `cast` (cobox_a11N :: (Int :: *) ~R# (Bool :: *)) *** End of Offense *** }}} Reason: this rather hacky test in `TcUnify.buildImplication` {{{ ; if null skol_tvs && null given && (not deferred_type_errors || not (isTopTcLevel tc_lvl)) }}} did take account of `Opt_DeferOutOfScopeVariables`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14149 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14149: Tyepchecker generates top-level unboxed coercion -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 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 simonpj): Patch coming... -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14149#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14149: Tyepchecker generates top-level unboxed coercion -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 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 duog): * cc: duog (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14149#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14149: Tyepchecker generates top-level unboxed coercion
-------------------------------------+-------------------------------------
Reporter: simonpj | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.2.1
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 Simon Peyton Jones

#14149: Tyepchecker generates top-level unboxed coercion -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | testsuite/tests/typecheck/should_compile/T14149 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * testcase: => testsuite/tests/typecheck/should_compile/T14149 * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14149#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14149: Tyepchecker generates top-level unboxed coercion
-------------------------------------+-------------------------------------
Reporter: simonpj | Owner: (none)
Type: bug | Status: closed
Priority: normal | Milestone:
Component: Compiler | Version: 8.2.1
Resolution: fixed | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
| testsuite/tests/typecheck/should_compile/T14149
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones
participants (1)
-
GHC