[GHC] #12115: CoreLint error in safe program

#12115: CoreLint error in safe program -------------------------------------+------------------------------------- Reporter: osa1 | Owner: 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: -------------------------------------+------------------------------------- This correct program is failing with a CoreLint error: {{{ {-# LANGUAGE MagicHash, UnboxedTuples #-} module Main where import GHC.Prim import GHC.Types showAlt0 :: (# Void#, (# #) #) -> String showAlt0 (# _, (# #) #) = "()" main :: IO () main = return () }}} Error: {{{ *** Core Lint errors : in result of Desugar (after optimization) *** <no location info>: warning: In the type ‘(# Void#, (# #) #) -> String’ Kind application error in type ‘(# Void#, (# #) #)’ Function kind = * -> * -> TYPE 'UnboxedTupleRep Arg kinds = [('VoidRep, RuntimeRep), ('UnboxedTupleRep, RuntimeRep), (Void#, TYPE 'VoidRep), ((# #), TYPE 'VoidRep)] core_err.hs:13:1: warning: [RHS of showAlt0 :: (# Void#, (# #) #) -> String] The type of this binder doesn't match the type of its RHS: showAlt0 Binder's type: (# Void#, (# #) #) -> String Rhs type: (# Void#, (# #) #) -> String }}} Tried with: GHC HEAD, 8.0.1. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12115 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12115: CoreLint error in safe program
-------------------------------------+-------------------------------------
Reporter: osa1 | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.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

#12115: CoreLint error in safe program -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | codegen/should_compile/T12115 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * testcase: => codegen/should_compile/T12115 * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12115#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12115: CoreLint error in safe program -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | codegen/should_compile/T12115 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: closed => merge Comment: Maybe merge to 8.0 branch. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12115#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12115: CoreLint error in safe program -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | codegen/should_compile/T12115 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by thomie): This patch is causing the following panic in `tcrun051` (on Linux): {{{ [1 of 1] Compiling Main ( tcrun051.hs, tcrun051.o ) 7907 ghc: panic! (the 'impossible' happened) 7908 (GHC version 8.1.20160527 for x86_64-unknown-linux): 7909 unboxed tuple PrimRep 7910 7911 Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug 7912 7913 7914 *** unexpected failure for tcrun051(normal) 7915 }}} tcrun051.hs: {{{#!hs {-# LANGUAGE UnboxedTuples #-} module Main where -- Tests unboxed tuple slow calls {-# NOINLINE g #-} g :: Int -> (# Int, Int #) -> Int -> (# Int, (# Int #) #) -> (# #) -> Int g a (# b, c #) d (# e, (# f #) #) (# #) = a + b + c + d + e + f {-# NOINLINE h #-} h :: (Int -> (# Int, Int #) -> Int -> (# Int, (# Int #) #) -> (# #) -> Int) -> (Int, Int) h g = (g5, g5') where -- Apply all the arguments at once g5' = g 1 (# 2, 3 #) 4 (# 5, (# 6 #) #) (# #) -- Try to force argument-at-a-time application as a stress-test g1 = g 1 g2 = g1 `seq` g1 (# 2, 3 #) g3 = g2 `seq` g2 4 g4 = g3 `seq` g3 (# 5, (# 6 #) #) g5 = g4 `seq` g4 (# #) main = print $ h g }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12115#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12115: CoreLint error in safe program -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | codegen/should_compile/T12115 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Yes thanks. I found that last night. (I didn't do 'slow' validate before pushing.) I have a fix; will push shortly. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12115#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12115: CoreLint error in safe program
-------------------------------------+-------------------------------------
Reporter: osa1 | Owner:
Type: bug | Status: merge
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Resolution: fixed | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
| codegen/should_compile/T12115
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#12115: CoreLint error in safe program -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | codegen/should_compile/T12115 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Fixed now. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12115#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12115: CoreLint error in safe program -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | codegen/should_compile/T12115 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): I'm a bit lost with these patches. - The commentary says that `(# #)` becomes `Void#` during unarisation. But there is also a change in !TysWiredIn that removes the special case for nullary unboxed tuples. - `Note [The kind invariant]` is awfully out-of-date: {{{ Note [The kind invariant] ~~~~~~~~~~~~~~~~~~~~~~~~~ The kinds # UnliftedTypeKind OpenKind super-kind of *, # can never appear under an arrow or type constructor in a kind; they can only be at the top level of a kind. It follows that primitive TyCons, which have a naughty pseudo-kind State# :: * -> # must always be saturated, so that we can never get a type whose kind has a UnliftedTypeKind or ArgTypeKind underneath an arrow. Nor can we abstract over a type variable with any of these kinds. k :: = kk | # | ArgKind | (#) | OpenKind kk :: = * | kk -> kk | T kk1 ... kkn So a type variable can only be abstracted kk. }}} (I'm sure I'm implicated in letting this fall out-of-date. But I honestly don't know how to fix.) There is no `#` anymore, and there is no `OpenKind` anymore. One might think this means that a representation-polymorphic kind (that is, `TYPE r`) cannot appear below top-level, but indeed they do, as in the type of `error`. So I'm not sure what this is saying. Also, this Note is missing ''why'' these restrictions are in place. I recall several months ago moving to allow unsaturated unlifted things, but now we've backpedaled on this decision. I'm sure there's a good reason, but what is it? This Note is also missing ''where'' these restrictions are enforced. Is there a check in !CoreLint that we never abstract over a kind `* -> TYPE <something unlifted>`? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12115#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12115: CoreLint error in safe program -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | codegen/should_compile/T12115 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * milestone: => 8.0.2 Comment: comment:1 merged to `ghc-8.0` as 9ddb9338aa052ef06849c8d6cd8846916d7b2f23 and comment:6 as e9c5ca8aa750b1583f19da195e1e7268ac4a35ff. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12115#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12115: CoreLint error in safe program -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | codegen/should_compile/T12115 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Opened #12536 to track the task of addressing comment:8. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12115#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC