[GHC] #7767: "internal error: evacuate: strange closure type 154886248" crash

#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

#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: --------------------------+------------------------------------------------- Comment(by rodlogic): This was built using ghc-heap-view-0.5 and ghc-vis-0.7. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7767#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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: --------------------------+------------------------------------------------- Comment(by rodlogic): The issue seems to be in ghc-heap-view, which relies on some C hackery to get to RTS heap objects. One of these hacks copies and pastes code from Printer.c and is very dependent on RTS heap layout. This a diff in one of these copy&paste: {{{ --- untitled.c Wed Mar 13 19:45:38 2013 +++ untitled2.c Wed Mar 13 19:45:52 2013 @@ -1,4 +1,4 @@ -char *gtc_heap_view_closure_type_names[] = { +char *closure_type_names[] = { [INVALID_OBJECT] = "INVALID_OBJECT", [CONSTR] = "CONSTR", [CONSTR_1_0] = "CONSTR_1_0", @@ -33,16 +33,16 @@ [RET_BCO] = "RET_BCO", [RET_SMALL] = "RET_SMALL", [RET_BIG] = "RET_BIG", - [RET_DYN] = "RET_DYN", [RET_FUN] = "RET_FUN", [UPDATE_FRAME] = "UPDATE_FRAME", [CATCH_FRAME] = "CATCH_FRAME", [UNDERFLOW_FRAME] = "UNDERFLOW_FRAME", [STOP_FRAME] = "STOP_FRAME", + [BLOCKING_QUEUE] = "BLOCKING_QUEUE", [BLACKHOLE] = "BLACKHOLE", - [BLOCKING_QUEUE] = "BLOCKING_QUEUE", [MVAR_CLEAN] = "MVAR_CLEAN", [MVAR_DIRTY] = "MVAR_DIRTY", + [TVAR] = "TVAR", [ARR_WORDS] = "ARR_WORDS", [MUT_ARR_PTRS_CLEAN] = "MUT_ARR_PTRS_CLEAN", [MUT_ARR_PTRS_DIRTY] = "MUT_ARR_PTRS_DIRTY", @@ -51,7 +51,7 @@ [MUT_VAR_CLEAN] = "MUT_VAR_CLEAN", [MUT_VAR_DIRTY] = "MUT_VAR_DIRTY", [WEAK] = "WEAK", - [PRIM] = "PRIM", + [PRIM] = "PRIM", [MUT_PRIM] = "MUT_PRIM", [TSO] = "TSO", [STACK] = "STACK", }}} -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7767#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7767: "internal error: evacuate: strange closure type 154886248" crash ----------------------------+----------------------------------------------- Reporter: rodlogic | Owner: Type: feature request | 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: ----------------------------+----------------------------------------------- Changes (by rodlogic): * type: bug => feature request Comment: Now, this is not really a GHC issue (changed to a feature request), but would it be possible to expose an API to avoid this code duplication with ghc-heap-view? Or is there a better approach to browse live heap objects? -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7767#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7767: "internal error: evacuate: strange closure type 154886248" crash ----------------------------+----------------------------------------------- Reporter: rodlogic | Owner: Type: feature request | 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: ----------------------------+----------------------------------------------- Comment(by ezyang): We could export these symbols, maybe `closure_type_names`, so that you can foreign import it. Of course, it's still internal, so we can still decide to change it at our whim. Would that work for you? -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7767#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7767: "internal error: evacuate: strange closure type 154886248" crash
----------------------------+-----------------------------------------------
Reporter: rodlogic | Owner:
Type: feature request | 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:
----------------------------+-----------------------------------------------
Comment(by rodlogic):
I need to defer the answer to this to Joachim Breitner

#7767: "internal error: evacuate: strange closure type 154886248" crash ----------------------------+----------------------------------------------- Reporter: rodlogic | Owner: Type: feature request | 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: ----------------------------+----------------------------------------------- Comment(by rodlogic): I have attached the c bits from ghc-heap-view, if that is of any help. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7767#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7767: "internal error: evacuate: strange closure type 154886248" crash ----------------------------+----------------------------------------------- Reporter: rodlogic | Owner: Type: feature request | 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: ----------------------------+----------------------------------------------- Changes (by nomeata): * cc: mail@… (added) Comment: ghc-heap-view has to do some nasty stuff, so I’m not too surprised that it does not work flawlessly in every case; this is not necessary a bug in GHC. It could indeed profit from some support by GHC. The `closure_type_names` list is actually not used in ghc-heap-view; it was added only for debugging purposes. It might still be handy to have that symbol exposed, though. The only code that needs to be synchronized with the RTS (besides the closure layout) seems to be the `data ClosureType`. Only now I am discovering the `RtClosureInspect` module, which seems to be quite similar to ghc-heap-view.... strange that I did not see that before. I need to see if that can serve my purposes well enough. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7767#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7767: "internal error: evacuate: strange closure type 154886248" crash --------------------------------+------------------------------------------- Reporter: rodlogic | Owner: Type: feature request | Status: new Priority: normal | Milestone: 7.8.1 Component: Runtime System | Version: 7.6.2 Keywords: | Os: MacOS X Architecture: x86_64 (amd64) | Failure: Runtime crash Difficulty: Unknown | Testcase: Blockedby: | Blocking: Related: | --------------------------------+------------------------------------------- Changes (by igloo): * difficulty: => Unknown * milestone: => 7.8.1 -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7767#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC