[GHC] #7767: "internal error: evacuate: strange closure type 154886248" crash
GHC
cvs-ghc at haskell.org
Wed Mar 13 15:31:10 CET 2013
#7767: "internal error: evacuate: strange closure type 154886248" crash
--------------------------+-------------------------------------------------
Reporter: rodlogic | Owner:
Type: bug | Status: new
Priority: normal | Component: Runtime System
Version: 7.6.2 | Keywords:
Os: MacOS X | Architecture: x86_64 (amd64)
Failure: Runtime crash | Blockedby:
Blocking: | Related:
--------------------------+-------------------------------------------------
I have a simple Main.hs that uses the GHC API to produce a
'''ParsedModule'''. I then use ghc-vis this value, which is when I get:
{{{
Starting ...
Setting dynamic flags ...
Guessing and adding target ...
Analyze dependencies ...
Getting module summary ...
Parsing module ...
Main: internal error: evacuate: strange closure type 154886248
(GHC version 7.6.2 for x86_64_apple_darwin)
Please report this as a GHC bug:
http://www.haskell.org/ghc/reportabug
[1] 7583 abort ./Main
}}}
Here is the Main.hs:
{{{
{-# LANGUAGE CPP #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE RecordWildCards #-}
{-
See the following link for additional details about the API:
http://hackage.haskell.org/trac/ghc/wiki/Commentary/Compiler/API
-}
module Main where
import Module
import RdrName
import OccName
import BasicTypes
--import Bag
--import HsDecls
--import Control.Monad
import Control.Exception (throw)
import GHC hiding (loadModule)
import SrcLoc
import MonadUtils
import GHC.Paths (libdir)
import HscTypes
--import DynFlags
import Unsafe.Coerce
--import Bag (bagToList)
--import Outputable
--import Name
import Data.Typeable
import Text.Show
import Data.Foldable(forM_)
import GHC.Exts
--import GHC.HeapView
import GHC.Vis
main :: IO ()
main = do
doMain
getLine
return ()
--libdir =
"/Library/Frameworks/GHC.framework/Versions/7.6.2-x86_64/usr/lib"
doMain = do
putStrLn "Starting ..."
runGhc (Just libdir) $ do
--
liftIO $ putStrLn "Setting dynamic flags ..."
dflags <- getSessionDynFlags
setSessionDynFlags (dflags)
--
liftIO $ putStrLn "Guessing and adding target ..."
-- guessTarget :: GhcMonad m => String -> Maybe Phase -> m Target
target <- guessTarget "Test.hs" Nothing
-- addTarget :: GhcMonad m => Target -> m ()
addTarget target
--liftIO $ putStrLn "Loading all targets ..."
--_ <- load (LoadUpTo modName)
liftIO $ putStrLn "Analyze dependencies ..."
-- depanal :: GhcMonad m =>
-- [ModuleName] -- ^ excluded modules
-- -> Bool -- ^ allow duplicate roots
-- -> m ModuleGraph
modGraph <- depanal [] False
let modName = mkModuleName "Test"
liftIO $ putStrLn "Getting module summary ..."
-- getModSummary :: GhcMonad m => ModuleName -> m ModSummary
modSummary <- getModSummary modName
liftIO $ putStrLn "Parsing module ..."
--data ParsedModule = ParsedModule { pm_mod_summary :: ModSummary
-- , pm_parsed_source :: ParsedSource
-- , pm_extra_src_files :: [FilePath]
}
-- type ParsedSource = Located (HsModule RdrName)
-- type Located e = GenLocated SrcSpan e
-- parseModule :: GhcMonad m => ModSummary -> m ParsedModule
parsedMod <- parseModule modSummary
liftIO $ vis
liftIO $ view parsedMod "parsedMod"
--let parsedSrc = pm_parsed_source parsedMod
----walkLocSource parsedSrc
----typecheckModule :: GhcMonad m => ParsedModule -> m
TypecheckedModule
--liftIO $ putStrLn "Type checking module ..."
--typedMod <- typecheckModule parsedMod
----let parsedMod = tm_parsed_module typedMod
----walkLocSource (pm_parsed_source parsedMod)
--let rnSource = tm_renamed_source typedMod
----walkRenamedSource rnSource
---- desugarModule :: GhcMonad m => TypecheckedModule -> m
DesugaredModule
--liftIO $ putStrLn "Desugaring module ..."
--desugaredMod <- desugarModule typedMod
return ()
}}}
I have built it using:
{{{
ghc --make -L/usr/lib -package ghc Main.hs -threaded
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/7767>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list