[GHC] #12375: type synonym to unboxed tuple causes crash
GHC
ghc-devs at haskell.org
Fri Jul 8 14:17:10 UTC 2016
#12375: type synonym to unboxed tuple causes crash
-------------------------------------+-------------------------------------
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:
-------------------------------------+-------------------------------------
{{{#!haskell
{-# LANGUAGE UnboxedTuples #-}
module Main where
-- type Null = (# #)
{-# NOINLINE showNull #-}
showNull :: (# #) -> String
showNull (# #) = "(# #)"
{-# NOINLINE showNullPair #-}
showNullPair :: (# (# #), (# #) #) -> String
showNullPair (# n1, n2 #) = "(# " ++ showNull n1 ++ ", " ++ showNull n2 ++
"#)"
main :: IO ()
main = do
putStrLn (showNullPair (# (# #), (# #) #))
}}}
If I use the `Null` type synonym here instead of `(# #)`, I get:
{{{
[1 of 1] Compiling Main ( empty.hs, empty.o )
ghc: panic! (the 'impossible' happened)
(GHC version 8.0.1 for x86_64-unknown-linux):
unboxed tuple PrimRep
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
}}}
Tried with: 8.0.1
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12375>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list