#5405: Strange closure type crash when using Template Haskell on OS X Lion
-------------------------------+--------------------------------------------
    Reporter:  AndreasVoellmy  |       Owner:            
        Type:  bug             |      Status:  new       
    Priority:  normal          |   Component:  GHCi      
     Version:  7.0.4           |    Keywords:            
    Testcase:                  |   Blockedby:            
          Os:  MacOS X         |    Blocking:            
Architecture:  x86_64 (amd64)  |     Failure:  GHCi crash
-------------------------------+--------------------------------------------
 GHCI crashes when I try to use Template Haskell on OS X Lion. To
 illustrate this, I have a small module, in a file A.hs:
 {{{
 module A where

 import Language.Haskell.TH (Exp)
 import Language.Haskell.SyntaxTrees.ExtsToTH (parseToTH)

 transform :: String -> Either String Exp
 transform = parseToTH

 ex1 = "42"
 }}}
 When I start ghci, load A, and evaluate ex1, and wait a couple seconds I
 get a crash, that usually reports something like this:
 {{{
 *A> ghc: internal error: evacuate: strange closure type 0
     (GHC version 7.0.4 for x86_64_apple_darwin)
     Please report this as a GHC bug:
 http://www.haskell.org/ghc/reportabug
 Abort trap: 6
 }}}
 Sometimes I get different crash messages as well, such as:
 {{{
 *A> Segmentation fault: 11
 }}}
 Here is the transcript of a ghci session:
 {{{
 Andreas$ ghci -v
 GHCi, version 7.0.4: http://www.haskell.org/ghc/  :? for help
 Glasgow Haskell Compiler, Version 7.0.4, for Haskell 98, stage 2 booted by
 GHC version 7.0.2
 Using binary package database:
 
/Library/Frameworks/GHC.framework/Versions/7.0.4-x86_64/usr/lib/ghc-7.0.4/package.conf.d/package.cache
 Using binary package database:
 /Users/Andreas/.ghc/x86_64-darwin-7.0.4/package.conf.d/package.cache
 wired-in package ghc-prim mapped to ghc-
 prim-0.2.0.0-d9df11f804556f362beb0ea4e67261ba
 wired-in package integer-gmp mapped to integer-
 gmp-0.2.0.3-298c59ba68b7aaa7e76ae5b1fe5e876e
 wired-in package base mapped to
 base-4.3.1.0-239d76b73f466dc120129098b3472858
 wired-in package rts mapped to builtin_rts
 wired-in package template-haskell mapped to template-
 haskell-2.5.0.0-b46cde34bfee890dc536d5be377e906f
 wired-in package dph-seq not found.
 wired-in package dph-par not found.
 Hsc static flags: -static
 Loading package ghc-prim ... linking ... done.
 Loading package integer-gmp ... linking ... done.
 Loading package base ... linking ... done.
 Loading package ffi-1.0 ... linking ... done.
 Prelude> :l A
 *** Chasing dependencies:
 Chasing modules from:
 Stable obj: []
 Stable BCO: []
 unload: retaining objs []
 unload: retaining bcos []
 Ready for upsweep []
 Upsweep completely successful.
 *** Deleting temp files:
 Deleting:
 *** Chasing dependencies:
 Chasing modules from: *A.hs
 Stable obj: []
 Stable BCO: []
 unload: retaining objs []
 unload: retaining bcos []
 Ready for upsweep
   [NONREC
       ModSummary {
          ms_hs_date = Wed Aug 10 16:52:58 EDT 2011
          ms_mod = main:A,
          ms_imps = [import Prelude,
                     import Language.Haskell.SyntaxTrees.ExtsToTH (
 parseToTH ),
                     import Language.Haskell.TH ( Exp )]
          ms_srcimps = []
       }]
 compile: input file A.hs
 *** Checking old interface for main:A:
 [1 of 1] Compiling A                ( A.hs, interpreted )
 *** Parser:
 *** Renamer/typechecker:
 *** Desugar:
     Result size = 13
 *** Simplifier SimplMode {Phase = 0 [final],
                       inline,
                       no rules,
                       eta-expand,
                       case-of-case} max-iterations=4:
     Result size = 13
 *** Tidy Core:
     Result size = 13
 *** CorePrep:
     Result size = 13
 *** ByteCodeGen:
 *** Deleting temp files:
 Deleting:
 Upsweep completely successful.
 *** Deleting temp files:
 Deleting:
 Ok, modules loaded: A.
 wired-in package ghc-prim mapped to ghc-
 prim-0.2.0.0-d9df11f804556f362beb0ea4e67261ba
 wired-in package integer-gmp mapped to integer-
 gmp-0.2.0.3-298c59ba68b7aaa7e76ae5b1fe5e876e
 wired-in package base mapped to
 base-4.3.1.0-239d76b73f466dc120129098b3472858
 wired-in package rts mapped to builtin_rts
 wired-in package template-haskell mapped to template-
 haskell-2.5.0.0-b46cde34bfee890dc536d5be377e906f
 wired-in package dph-seq not found.
 wired-in package dph-par not found.
 wired-in package ghc-prim mapped to ghc-
 prim-0.2.0.0-d9df11f804556f362beb0ea4e67261ba
 wired-in package integer-gmp mapped to integer-
 gmp-0.2.0.3-298c59ba68b7aaa7e76ae5b1fe5e876e
 wired-in package base mapped to
 base-4.3.1.0-239d76b73f466dc120129098b3472858
 wired-in package rts mapped to builtin_rts
 wired-in package template-haskell mapped to template-
 haskell-2.5.0.0-b46cde34bfee890dc536d5be377e906f
 wired-in package dph-seq not found.
 wired-in package dph-par not found.
 *A> ex1
 wired-in package ghc-prim mapped to ghc-
 prim-0.2.0.0-d9df11f804556f362beb0ea4e67261ba
 wired-in package integer-gmp mapped to integer-
 gmp-0.2.0.3-298c59ba68b7aaa7e76ae5b1fe5e876e
 wired-in package base mapped to
 base-4.3.1.0-239d76b73f466dc120129098b3472858
 wired-in package rts mapped to builtin_rts
 wired-in package template-haskell mapped to template-
 haskell-2.5.0.0-b46cde34bfee890dc536d5be377e906f
 wired-in package dph-seq not found.
 wired-in package dph-par not found.
 *** Parser:
 *** Desugar:
 *** Simplify:
 *** CorePrep:
 *** ByteCodeGen:
 Loading package array-0.3.0.2 ... linking ... done.
 Loading package bytestring-0.9.1.10 ... linking ... done.
 Loading package containers-0.4.0.0 ... linking ... done.
 Loading package ghc-binary-0.5.0.2 ... linking ... done.
 Loading package filepath-1.2.0.0 ... linking ... done.
 Loading package old-locale-1.0.0.2 ... linking ... done.
 Loading package old-time-1.0.0.6 ... linking ... done.
 Loading package unix-2.4.2.0 ... linking ... done.
 Loading package directory-1.1.0.0 ... linking ... done.
 Loading package pretty-1.0.1.2 ... linking ... done.
 Loading package process-1.0.1.5 ... linking ... done.
 Loading package Cabal-1.10.2.0 ... linking ... done.
 Loading package bin-package-db-0.0.0.0 ... linking ... done.
 Loading package hpc-0.5.0.6 ... linking ... done.
 Loading package template-haskell ... linking ... done.
 Loading package ghc-7.0.4 ... linking ... done.
 Loading package extensible-exceptions-0.1.1.2 ... linking ... done.
 Loading package time-1.2.0.3 ... linking ... done.
 Loading package random-1.0.0.3 ... linking ... done.
 Loading package cpphs-1.12 ... linking ... done.
 Loading package haskell-src-exts-1.11.1 ... linking ... done.
 Loading package transformers-0.2.2.0 ... linking ... done.
 Loading package mtl-2.0.1.0 ... linking ... done.
 Loading package MonadCatchIO-mtl-0.3.0.3 ... linking ... done.
 Loading package ghc-mtl-1.0.1.0 ... linking ... done.
 Loading package ghc-paths-0.1.0.8 ... linking ... done.
 Loading package haskell98-1.1.0.1 ... linking ... done.
 Loading package syb-0.3.3 ... linking ... done.
 Loading package haskell-src-1.0.1.4 ... linking ... done.
 Loading package utf8-string-0.3.6 ... linking ... done.
 Loading package hint-0.3.3.2 ... linking ... done.
 Loading package uniplate-1.6 ... linking ... done.
 Loading package syntax-trees-0.1.2 ... linking ... done.
 "42"
 wired-in package ghc-prim mapped to ghc-
 prim-0.2.0.0-d9df11f804556f362beb0ea4e67261ba
 wired-in package integer-gmp mapped to integer-
 gmp-0.2.0.3-298c59ba68b7aaa7e76ae5b1fe5e876e
 wired-in package base mapped to
 base-4.3.1.0-239d76b73f466dc120129098b3472858
 wired-in package rts mapped to builtin_rts
 wired-in package template-haskell mapped to template-
 haskell-2.5.0.0-b46cde34bfee890dc536d5be377e906f
 wired-in package dph-seq not found.
 wired-in package dph-par not found.
 *A> ghc: internal error: evacuate: strange closure type 0
     (GHC version 7.0.4 for x86_64_apple_darwin)
     Please report this as a GHC bug:
 http://www.haskell.org/ghc/reportabug
 Abort trap: 6
 }}}
 Some more details about my setup:

 My machine:
 {{{
 Darwin 11.0.0 Darwin Kernel Version 11.0.0: Sat Jun 18 12:56:35 PDT 2011;
 root:xnu-1699.22.73~1/RELEASE_X86_64 x86_64
 }}}

 gcc -v:
 {{{
 Using built-in specs.
 Target: i686-apple-darwin11
 Configured with:
 /private/var/tmp/llvmgcc42/llvmgcc42-2335.15~25/src/configure --disable-
 checking --enable-werror --prefix=/Developer/usr/llvm-gcc-4.2
 --mandir=/share/man --enable-languages=c,objc,c++,obj-c++ --program-
 prefix=llvm- --program-transform-name=/^[cg][^.-]*$/s/$/-4.2/ --with-
 slibdir=/usr/lib --build=i686-apple-darwin11 --enable-
 llvm=/private/var/tmp/llvmgcc42/llvmgcc42-2335.15~25/dst-
 llvmCore/Developer/usr/local --program-prefix=i686-apple-darwin11-
 --host=x86_64-apple-darwin11 --target=i686-apple-darwin11 --with-gxx-
 include-dir=/usr/include/c++/4.2.1
 Thread model: posix
 gcc version 4.2.1 (Based on Apple Inc. build 5658) (LLVM build 2335.15.00)
 }}}

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5405>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler

_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to