[GHC] #12520: Segfault when using unboxed tuples in GHCi

#12520: Segfault when using unboxed tuples in GHCi -------------------------------------+------------------------------------- Reporter: mniip | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: GHCi crash Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- If you put this module in a package: {{{#!hs {-# LANGUAGE MagicHash, UnboxedTuples #-} module Bug ( box, wrap, proxy ) where import GHC.Prim box :: (# Proxy# a, b #) -> b box (# x, y #) = y wrap :: b -> Proxy# a -> (# Proxy# a, b #) wrap x = \i# -> (# i#, x #) proxy :: () -> Proxy# a proxy () = proxy# }}} Then in GHCi you can do: {{{ GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help Prelude> import Bug Prelude Bug> box (wrap "foo" (proxy ())) "Segmentation fault (core dumped) }}} Alternatively you can crash `runhaskell` if you put the above code in main. It seems that GHCi fails to pickup usage of (# VoidRep, PtrLiftedRep #) tuples or something. The same trick works with `State#` in place of `Proxy#`, but not with `Int#`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12520 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12520: Segfault when using unboxed tuples in GHCi -------------------------------------+------------------------------------- Reporter: mniip | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: GHCi | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mniip): * status: new => closed * resolution: => fixed Comment: This is fixed in HEAD apparently -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12520#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12520: Segfault when using unboxed tuples in GHCi -------------------------------------+------------------------------------- Reporter: mniip | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: GHCi | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): This is fixed in HEAD. Unboxed tuple handling in the interpreter is a bit hacky (we have special cases for tuples with one void value etc.), but it was recently improved during the implementation of unboxed sums (see new `RepType` module and its uses in `BytecodeGen`). That also fixed this bug. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12520#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12520: Segfault when using unboxed tuples in GHCi -------------------------------------+------------------------------------- Reporter: mniip | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: GHCi | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Great that it's fixed. Would it be worth adding a regression tests, so that it ''stays'' fixed? Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12520#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12520: Segfault when using unboxed tuples in GHCi
-------------------------------------+-------------------------------------
Reporter: mniip | Owner:
Type: bug | Status: closed
Priority: normal | Milestone:
Component: GHCi | Version: 8.0.1
Resolution: fixed | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: GHCi crash | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ömer Sinan Ağacan
participants (1)
-
GHC