[GHC] #11722: No TypeRep for unboxed tuples

#11722: No TypeRep for unboxed tuples -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.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 now crashes on GHC HEAD: {{{#!hs {-# LANGUAGE MagicHash #-} {-# LANGUAGE UnboxedTuples #-} module Main where import Data.Typeable import GHC.Exts main :: IO () main = print $ typeOf (Proxy :: Proxy (# Int, Int #)) }}} {{{ $ /opt/ghc/head/bin/ghc -O2 -fforce-recomp Example.hs [1 of 1] Compiling Main ( Example.hs, Example.o ) ghc: panic! (the 'impossible' happened) (GHC version 8.1.20160317 for x86_64-unknown-linux): tyConRep (#,#) Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} (Previously, this was rejected with an error message, since you couldn't put an unlifted type as the argument of `Proxy`.) (Copied from comment:28:ticket:11471.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11722 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11722: No TypeRep for unboxed tuples -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.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 RyanGlScott): * cc: bgamari (added) Comment: Suspiciously similar shenanigans: {{{#!hs {-# LANGUAGE UnboxedTuples #-} module Main where import Data.Typeable main :: IO () main = print $ typeOf (Proxy :: Proxy (# #)) }}} {{{ $ /opt/ghc/head/bin/ghc -O2 -fforce-recomp Example.hs [1 of 1] Compiling Main ( Example.hs, Example.o ) Example.hs:7:24: error: • Couldn't match kind ‘'GHC.Types.VoidRep’ with ‘'GHC.Types.UnboxedTupleRep’ When matching the kind of ‘(# #)’ • In the first argument of ‘typeOf’, namely ‘(Proxy :: Proxy (# #))’ In the second argument of ‘($)’, namely ‘typeOf (Proxy :: Proxy (# #))’ In the expression: print $ typeOf (Proxy :: Proxy (# #)) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11722#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11722: No TypeRep for unboxed tuples -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.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): See also #11736, which is closely related. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11722#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11722: No TypeRep for unboxed tuples -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: Typeable 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 simonpj): * keywords: => Typeable -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11722#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11722: No TypeRep for unboxed tuples -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: Typeable 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 bgamari): #12409 is a duplicate of this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11722#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11722: No TypeRep for unboxed tuples -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: Typeable Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12409 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * related: => #12409 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11722#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11722: No TypeRep for unboxed tuples -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.1 Resolution: fixed | Keywords: Typeable Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12409 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => fixed * milestone: => 8.2.1 Comment: This was fixed in 8fa4bf9ab3f4ea4b208f4a43cc90857987e6d497 (Type-indexed Typeable). See `typecheck/should_compile/T11736` for a very similar test which exercises this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11722#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC