Re: [GHC] #5936: Support for data families in generics

2012-03-12 Thread GHC
#5936: Support for data families in generics
--+-
 Reporter:  reinerp   |  Owner:  
 Type:  feature request   | Status:  patch   
 Priority:  normal|  Component:  Compiler
  Version:  7.4.1 |   Keywords:  
   Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
  Failure:  None/Unknown  |   Testcase:  
Blockedby:|   Blocking:  
  Related:|  
--+-
Changes (by reinerp):

  * status:  new => patch


-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #5936: Support for data families in generics

2012-03-12 Thread GHC
#5936: Support for data families in generics
--+-
 Reporter:  reinerp   |  Owner:  
 Type:  feature request   | Status:  new 
 Priority:  normal|  Component:  Compiler
  Version:  7.4.1 |   Keywords:  
   Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
  Failure:  None/Unknown  |   Testcase:  
Blockedby:|   Blocking:  
  Related:|  
--+-
 Currently {{{DeriveGeneric}}} doesn't handle data families correctly, so
 that the following module

 {{{
 {-# LANGUAGE TypeFamilies, DeriveGeneric #-}
 module FamilyDerive where
 import GHC.Generics

 data family F a
 data instance F Int = FInt deriving Generic
 }}}

 fails to compile, with error

 {{{
 /tmp/FamilyDerive.hs:6:15:
 Couldn't match type `Rep (F Int)' with `M1 t0 t1 (M1 t2 t3 U1)'
 The type variables `t0', `t1', `t2', `t3' are ambiguous
 Possible fix: add a type signature that fixes these type variable(s)
 Expected type: Rep (F Int) x
   Actual type: M1 t0 t1 (M1 t2 t3 U1) x
 In the pattern: M1 (M1 U1)
 In an equation for `to': to (M1 (M1 U1)) = FInt
 In the instance declaration for `Generic (F Int)'
 }}}

 It turns out to require only small changes to GHC to handle data families.
 I've attached patches.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #5903: GHC 7.4.1 32 bit: LLVM backend fails on OSX 64bit

2012-03-12 Thread GHC
#5903: GHC 7.4.1 32 bit: LLVM backend fails on OSX 64bit
-+--
  Reporter:  dterei  |  Owner:  dterei
  Type:  bug | Status:  closed
  Priority:  normal  |  Milestone:
 Component:  Compiler (LLVM) |Version:  7.4.1 
Resolution:  fixed   |   Keywords:
Os:  MacOS X |   Architecture:  x86_64 (amd64)
   Failure:  Compile-time crash  | Difficulty:  Unknown   
  Testcase:  |  Blockedby:
  Blocking:  |Related:
-+--
Changes (by dterei):

  * status:  merge => closed


Comment:

 OK I merged into branch ghc-7.4 as that seems to be the style.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #5928: INLINABLE fails to specialize in presence of simple wrapper

2012-03-12 Thread GHC
#5928: INLINABLE fails to specialize in presence of simple wrapper
--+-
 Reporter:  tibbe |  Owner:  
 Type:  bug   | Status:  new 
 Priority:  normal|  Component:  Compiler
  Version:  7.4.1 |   Keywords:  
   Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
  Failure:  None/Unknown  |   Testcase:  
Blockedby:|   Blocking:  
  Related:|  
--+-
Changes (by PHO):

 * cc: pho@… (added)


-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #5914: armhf build fails in Ubuntu (7.4.1)

2012-03-12 Thread GHC
#5914: armhf build fails in Ubuntu (7.4.1)
-+--
 Reporter:  jani@…   |  Owner:  kgardas
 Type:  bug  | Status:  new
 Priority:  normal   |  Component:  Compiler (LLVM)
  Version:  7.4.1|   Keywords: 
   Os:  Linux|   Architecture:  arm
  Failure:  Building GHC failed  |   Testcase: 
Blockedby:   |   Blocking: 
  Related:   |  
-+--
Changes (by dterei):

 * cc: dterei (added)


-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #5914: armhf build fails in Ubuntu (7.4.1)

2012-03-12 Thread GHC
#5914: armhf build fails in Ubuntu (7.4.1)
-+--
 Reporter:  jani@…   |  Owner:  kgardas
 Type:  bug  | Status:  new
 Priority:  normal   |  Component:  Compiler (LLVM)
  Version:  7.4.1|   Keywords: 
   Os:  Linux|   Architecture:  arm
  Failure:  Building GHC failed  |   Testcase: 
Blockedby:   |   Blocking: 
  Related:   |  
-+--
Changes (by dterei):

  * owner:  dterei => kgardas


Comment:

 Re-assigning as ARM stuff isn't handled by me.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #5214: SIGSEGV in yieldCapability ()

2012-03-12 Thread GHC
#5214: SIGSEGV  in yieldCapability ()
-+--
  Reporter:  j.waldmann  |  Owner:
  Type:  bug | Status:  new   
  Priority:  normal  |  Milestone:
 Component:  Runtime System  |Version:  7.4.1 
Resolution:  |   Keywords:
Os:  Linux   |   Architecture:  x86_64 (amd64)
   Failure:  Runtime crash   | Difficulty:  Unknown   
  Testcase:  |  Blockedby:
  Blocking:  |Related:
-+--

Comment(by vshabanov):

 I replaced curl with http-conduit and still getting sigsegv:
 {{{
 Core was generated by `./Queue +RTS -N2'.
 Program terminated with signal 11, Segmentation fault.
 #0  0x7f0eff61edf8 in ?? () from /lib/x86_64-linux-gnu/libc.so.6
 (gdb) bt
 #0  0x7f0eff61edf8 in ?? () from /lib/x86_64-linux-gnu/libc.so.6
 #1  0x020c70e5 in threadStackUnderflow (cap=0x2d860a0,
 tso=0x7f0ef11f9150) at rts/Threads.c:677
 #2  0x020c11a7 in raiseExceptionHelper (reg=0x2d860b8,
 tso=0x7f0ef11f9150, exception=0x7f0ed694d339) at rts/Schedule.c:2505
 #3  0x020dff80 in stg_raisezh ()
 #4  0x in ?? ()
 }}}

 Core dump available at http://stuff.bazqux.com/5214-N2-nocurl.tar.bz2

 So the error looks unrelated to FFI too (the only FFI libs left are hsdns
 and text-icu, but they don't call haskell from C side).

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #5935: Failure to resolve AnyK

2012-03-12 Thread GHC
#5935: Failure to resolve AnyK
---+
 Reporter:  goldfire   |  Owner:
 
 Type:  bug| Status:  new   
 
 Priority:  normal |  Component:  Compiler (Type 
checker)
  Version:  7.4.1  |   Keywords:  DataKinds PolyKinds   
 
   Os:  Unknown/Multiple   |   Architecture:  Unknown/Multiple  
 
  Failure:  GHC rejects valid program  |   Testcase:
 
Blockedby: |   Blocking:
 
  Related: |  
---+
 Consider the following code:

 {{{
 {-# LANGUAGE PolyKinds,
  GADTs,
  DataKinds,
  KindSignatures
  #-}

 data SList a where
   SNil :: SList '[]

 x :: SList ('[] :: [Bool])
 x = SNil
 }}}

 Compiling this code causes GHC to emit an error saying that {{{AnyK}}}
 cannot be unified with {{{Bool}}}. It seems that {{{AnyK}}} is a
 placeholder for an undetermined kind and that it should unify with any
 well-formed kind.

 As a much smaller issue, the error emitted speaks about "types" where it
 means "kinds".

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #5934: ghc: panic! (the 'impossible' happened)

2012-03-12 Thread GHC
#5934: ghc: panic! (the 'impossible' happened)
+---
 Reporter:  guest   |  Owner:
 Type:  bug | Status:  new   
 Priority:  normal  |  Component:  Compiler  
  Version:  7.4.1   |   Keywords:
   Os:  Linux   |   Architecture:  x86_64 (amd64)
  Failure:  Compile-time crash  |   Testcase:
Blockedby:  |   Blocking:
  Related:  |  
+---
 GHC asked me nicely to report this compile-time panic / crash.

 Minimal code:
 {{{
 {-# LANGUAGE Rank2Types #-}

 module Foo where
 import System.Random.MWC (GenST)
 run :: (forall s . GenST s) -> Int
 run = 0
 }}}

 Output:

 {{{
 $ ghc Foo.hs
 [1 of 1] Compiling Foo  ( Foo.hs, Foo.o )
 ghc: panic! (the 'impossible' happened)
   (GHC version 7.4.1 for x86_64-unknown-linux):
 tcTyVarDetails
 ( s{tv a10F} [tv] :: ghc-prim:GHC.Prim.*{(w) tc 34d} )

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

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #5214: SIGSEGV in yieldCapability ()

2012-03-12 Thread GHC
#5214: SIGSEGV  in yieldCapability ()
-+--
  Reporter:  j.waldmann  |  Owner:
  Type:  bug | Status:  new   
  Priority:  normal  |  Milestone:
 Component:  Runtime System  |Version:  7.4.1 
Resolution:  |   Keywords:
Os:  Linux   |   Architecture:  x86_64 (amd64)
   Failure:  Runtime crash   | Difficulty:  Unknown   
  Testcase:  |  Blockedby:
  Blocking:  |Related:
-+--

Comment(by vshabanov):

 You can download executable (won't work without additional setup, just for
 gdb), core and -Ds output from
 http://stuff.bazqux.com/5214-N2-NoSTM.tar.bz2

 Program with -N2 and QSem+MVar pool worked all the night. But when
 compiled with -debug it fails quite fast. It even faulted with pool size
 1. With -N1 program seems to work even with -debug.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #5933: Expose GHCI_TABLES_NEXT_TO_CODE in some header file

2012-03-12 Thread GHC
#5933: Expose GHCI_TABLES_NEXT_TO_CODE in some header file
--+-
 Reporter:  nomeata   |  Owner:  
 Type:  feature request   | Status:  new 
 Priority:  normal|  Component:  Build System
  Version:  7.4.1 |   Keywords:  
   Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
  Failure:  None/Unknown  |   Testcase:  
Blockedby:|   Blocking:  
  Related:|  
--+-
 Projects that are “close” to the GHC Heap need to know the value of
 GHCI_TABLES_NEXT_TO_CODE; currently they are just guessing (e.g.
 http://hackage.haskell.org/packages/archive/vacuum/1.0.0.2/doc/html/src
 /GHC-Vacuum-Internal.html). It would be nice if this would be exported as
 a macro in, e.g. GHCConstants.h.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #5688: instance Read Integer/Rational/Double readsPrec out of memory and crash due to exponential notation

2012-03-12 Thread GHC
#5688: instance Read Integer/Rational/Double readsPrec out of memory and crash 
due
to exponential notation
---+
  Reporter:  gracjan   |  Owner:  igloo   
  Type:  bug   | Status:  merge   
  Priority:  highest   |  Milestone:  7.4.2   
 Component:  libraries/base|Version:  6.12.3  
Resolution:|   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  Runtime crash | Difficulty:  Unknown 
  Testcase:|  Blockedby:  
  Blocking:|Related:  
---+

Comment(by maeder):

 Yet, I would vote to merge it into 7.4.2 (with or without bumping the base
 version).

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #5688: instance Read Integer/Rational/Double readsPrec out of memory and crash due to exponential notation

2012-03-12 Thread GHC
#5688: instance Read Integer/Rational/Double readsPrec out of memory and crash 
due
to exponential notation
---+
  Reporter:  gracjan   |  Owner:  igloo   
  Type:  bug   | Status:  merge   
  Priority:  highest   |  Milestone:  7.4.2   
 Component:  libraries/base|Version:  6.12.3  
Resolution:|   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  Runtime crash | Difficulty:  Unknown 
  Testcase:|  Blockedby:  
  Blocking:|Related:  
---+

Comment(by maeder):

 I suppose, the change of "data Lexeme" in "Text.Read.Lex" is a more severe
 interface change.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #5214: SIGSEGV in yieldCapability ()

2012-03-12 Thread GHC
#5214: SIGSEGV  in yieldCapability ()
-+--
  Reporter:  j.waldmann  |  Owner:
  Type:  bug | Status:  new   
  Priority:  normal  |  Milestone:
 Component:  Runtime System  |Version:  7.4.1 
Resolution:  |   Keywords:
Os:  Linux   |   Architecture:  x86_64 (amd64)
   Failure:  Runtime crash   | Difficulty:  Unknown   
  Testcase:  |  Blockedby:
  Blocking:  |Related:
-+--
Changes (by simonmar):

  * difficulty:  => Unknown


Comment:

 Thanks for the report.  I've had a look at the code and can't see anything
 obvious that would lead to those assertion failures, and the `+RTS -Ds`
 output doesn't contain any useful clues either.  Do you have a core dump
 corresponding to the first failure (the `ASSERTION FAILED: file
 rts/Schedule.c, line 1268`)?

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #5688: instance Read Integer/Rational/Double readsPrec out of memory and crash due to exponential notation

2012-03-12 Thread GHC
#5688: instance Read Integer/Rational/Double readsPrec out of memory and crash 
due
to exponential notation
---+
  Reporter:  gracjan   |  Owner:  igloo   
  Type:  bug   | Status:  merge   
  Priority:  highest   |  Milestone:  7.4.2   
 Component:  libraries/base|Version:  6.12.3  
Resolution:|   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  Runtime crash | Difficulty:  Unknown 
  Testcase:|  Blockedby:  
  Blocking:|Related:  
---+

Comment(by igloo):

 They go to the cvs-libraries list instead.
 http://www.haskell.org/pipermail/cvs-libraries/

 You can also look at them in http://darcs.haskell.org/packages/base.git/
 or https://github.com/ghc/packages-base

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #5688: instance Read Integer/Rational/Double readsPrec out of memory and crash due to exponential notation

2012-03-12 Thread GHC
#5688: instance Read Integer/Rational/Double readsPrec out of memory and crash 
due
to exponential notation
---+
  Reporter:  gracjan   |  Owner:  igloo   
  Type:  bug   | Status:  merge   
  Priority:  highest   |  Milestone:  7.4.2   
 Component:  libraries/base|Version:  6.12.3  
Resolution:|   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  Runtime crash | Difficulty:  Unknown 
  Testcase:|  Blockedby:  
  Blocking:|Related:  
---+

Comment(by maeder):

 Replying to [comment:58 simonmar]:
 > pasting the hash into Google is usually the best way :-)

 {{{
 Your search - 4d849e6729d25ac4561d597b203c2af8757e6275 - did not match any
 documents.
 }}}

 Which patches go to gmane.comp.lang.haskell.cvs.ghc? Why not these here?

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #5688: instance Read Integer/Rational/Double readsPrec out of memory and crash due to exponential notation

2012-03-12 Thread GHC
#5688: instance Read Integer/Rational/Double readsPrec out of memory and crash 
due
to exponential notation
---+
  Reporter:  gracjan   |  Owner:  igloo   
  Type:  bug   | Status:  merge   
  Priority:  highest   |  Milestone:  7.4.2   
 Component:  libraries/base|Version:  6.12.3  
Resolution:|   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  Runtime crash | Difficulty:  Unknown 
  Testcase:|  Blockedby:  
  Blocking:|Related:  
---+

Comment(by simonmar):

 Replying to [comment:56 igloo]:

 > We need to decide if we want to merge for 7.4.2. The arguments against
 doing so are:
 >  * Breaks the library interface policy, e.g. because the behaviour of
 `read "12e34" :: Integer` changes
 >  * Would mean we should bump base's version number to 4.6, which will
 mean lots of packages need updating.

 We could consider it a bug that `read "12e34"` worked before.  If we can
 reasonably claim that the other interface changes are in "internal"
 modules, then we could avoid bumping the base version (I don't know
 whether that's true or not though).

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #5688: instance Read Integer/Rational/Double readsPrec out of memory and crash due to exponential notation

2012-03-12 Thread GHC
#5688: instance Read Integer/Rational/Double readsPrec out of memory and crash 
due
to exponential notation
---+
  Reporter:  gracjan   |  Owner:  igloo   
  Type:  bug   | Status:  merge   
  Priority:  highest   |  Milestone:  7.4.2   
 Component:  libraries/base|Version:  6.12.3  
Resolution:|   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  Runtime crash | Difficulty:  Unknown 
  Testcase:|  Blockedby:  
  Blocking:|Related:  
---+

Comment(by simonmar):

 Replying to [comment:57 maeder]:
 > I wonder, where I can look up these committed changes easily.

 pasting the hash into Google is usually the best way :-)

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #5932: closure_type_names in Printer.c has BLACKHOLE and BLOCKING_QUEUE swapped

2012-03-12 Thread GHC
#5932: closure_type_names in Printer.c has BLACKHOLE and BLOCKING_QUEUE swapped
--+-
 Reporter:  nomeata   |  Owner:  
 Type:  bug   | Status:  new 
 Priority:  normal|  Component:  Runtime System  
  Version:  7.4.1 |   Keywords:  
   Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
  Failure:  None/Unknown  |   Testcase:  
Blockedby:|   Blocking:  
  Related:|  
--+-
 The attached patch fixes this.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #5688: instance Read Integer/Rational/Double readsPrec out of memory and crash due to exponential notation

2012-03-12 Thread GHC
#5688: instance Read Integer/Rational/Double readsPrec out of memory and crash 
due
to exponential notation
---+
  Reporter:  gracjan   |  Owner:  igloo   
  Type:  bug   | Status:  merge   
  Priority:  highest   |  Milestone:  7.4.2   
 Component:  libraries/base|Version:  6.12.3  
Resolution:|   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  Runtime crash | Difficulty:  Unknown 
  Testcase:|  Blockedby:  
  Blocking:|Related:  
---+

Comment(by maeder):

 I wonder, where I can look up these committed changes easily.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #5931: Allow 'Any' to be passed to a foreign prim function.

2012-03-12 Thread GHC
#5931: Allow 'Any' to be passed to a foreign prim function.
--+-
 Reporter:  nomeata   |  Owner:  
 Type:  feature request   | Status:  new 
 Priority:  normal|  Component:  Compiler (FFI)  
  Version:  7.4.1 |   Keywords:  
   Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
  Failure:  None/Unknown  |   Testcase:  
Blockedby:|   Blocking:  
  Related:|  
--+-
 Real primops can take boxed arguments, and the Cmm code will receive the
 pointer to the object on the Haskell heap, e.g. for unpackClosure#. To be
 able to implement such a function in a "foreign prim" call, this needs to
 be allowed there as well, and the attached patch does that.

 By only allowing Any here (instead of arbitrary types), it is clearer that
 the function will not receive the value in any marshalled form, but just
 the raw pointer. Haskell code using such functions are likely to use
 unsafeCoerce# to turn a Haskell value into a value of type Any.

 I am working on code that helps investigating the heap, similar to vacuum,
 and unwrapClosure was not sufficient. With this patch in GHC I do not have
 to modify the compiler further to create an improved version.

 If applied, the documentation at wiki:Commentary/PrimOps#Foreignout-of-
 linePrimOps needs to be updated. I did not find any documentation in the
 GHC tree to updated accordingly.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs