[GHC] #11471: Kind polymorphism and unboxed types: bad things are happening

GHC ghc-devs at haskell.org
Sat Mar 19 19:26:13 UTC 2016


#11471: Kind polymorphism and unboxed types: bad things are happening
-------------------------------------+-------------------------------------
        Reporter:  bgamari           |                Owner:  goldfire
            Type:  bug               |               Status:  closed
        Priority:  normal            |            Milestone:  8.0.1
       Component:  Compiler (Type    |              Version:  7.10.3
  checker)                           |             Keywords:  TypeInType,
      Resolution:  fixed             |  LevityPolymorphism
Operating System:  Unknown/Multiple  |         Architecture:
                                     |  Unknown/Multiple
 Type of failure:  None/Unknown      |            Test Case:
                                     |  dependent/should_fail/T11471
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):  Phab:D1891
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by RyanGlScott):

 I'm a bit confused as to how unboxed tuples fit into this scheme. I bring
 this up since 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`.)

 I notice that there's a single constructor of `RuntimeRep` for unboxed
 tuples (`UnboxedTupleRep`). Does this mean something like this should be
 allowed?

 {{{#!hs
 {-# LANGUAGE DataKinds #-}
 {-# LANGUAGE KindSignatures #-}
 module Example where

 import Data.Typeable
 import GHC.Exts

 data Wat (a :: TYPE 'UnboxedTupleRep) = Wat a
 }}}

 Currently, that fails to compile due to a separate GHC panic:

 {{{
 $ /opt/ghc/head/bin/ghc -O2 -fforce-recomp Example.hs
 [1 of 1] Compiling Example          ( Example.hs, Example.o )
 ghc: panic! (the 'impossible' happened)
   (GHC version 8.1.20160317 for x86_64-unknown-linux):
         unboxed tuple PrimRep

 Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug
 }}}

 But wouldn't this be dangerous anyway? After all, unboxed tuples are
 supposed to represent arguments on the stack, so couldn't unboxed tuple
 polymorphic potentially lead to the RTS miscalculating how much data to
 read? Or am I misreading this?

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11471#comment:28>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list