
#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