crash caused by generic visitor (?)
Ranjit Jhala
jhala at cs.ucsd.edu
Sat May 14 01:34:54 CEST 2011
Hi all,
I'm trying to extract the set of identifiers that are read in given
source file. To this end, I wrote the following code (full source at end.)
------------------------------------------------------------------------
main
= do fname <- (!! 0) `fmap` getArgs
tcm <- loadTypecheckedSource fname
putStrLn $ showPpr tcm -- this works fine
putStrLn $ showPpr $ allIds tcm -- this causes the crash
return ()
allIds :: Data a => a -> [Id]
allIds = listify (\x -> case (x :: Id) of _ -> True)
------------------------------------------------------------------------
and where:
loadTypecheckedSource :: FilePath -> IO TypecheckedSource
unfortunately, when I compile and run it, I get the dreaded:
Bug: Bug: panic! (the 'impossible' happened)
(GHC version 7.0.3 for i386-unknown-linux):
placeHolderNames
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
Turns out that the problem is when the file contains a type annotation.
That is,
./Bug Test00.hs
crashes, when Test00.hs is:
module Test where
x :: Int
x = 0
but does not crash when the file is:
module Test where
x = 0
Can anyone tell me why listify chokes in the latter case? (And how one might
get around the problem?) I include the full source below (compiled with: ghc --make Bug, using ghc 7.0.3)
Thanks!
Ranjit.
------------------------------------------------------------------------------------------------------
import GHC
import Outputable
import DynFlags (defaultDynFlags)
import GHC.Paths (libdir)
import System.Environment (getArgs)
import Control.Monad
import qualified Data.List as L
import Data.Data
import Data.Generics.Schemes (listify)
main
= do fname <- (!! 0) `fmap` getArgs
tcm <- loadTypecheckedSource fname
putStrLn $ showPpr tcm -- this works fine
putStrLn $ showPpr $ allIds tcm -- this causes the crash
return ()
allIds :: Data a => a -> [Id]
allIds = listify (\x -> case (x :: Id) of _ -> True)
loadTypecheckedSource :: FilePath -> IO TypecheckedSource
loadTypecheckedSource fname
= defaultErrorHandler defaultDynFlags $
runGhc (Just libdir) $ do
df <- getSessionDynFlags
setSessionDynFlags df
tgt <- guessTarget fname Nothing
setTargets [tgt]
load LoadAllTargets
res <- load LoadAllTargets
if failed res
then pprPanic "Load Failed!!" (text "AAARGH!")
else tm_typechecked_source `fmap` getTypecheckedModule fname
findModSummary :: GhcMonad m => FilePath -> m ModSummary
findModSummary fname
= do msums <- depanal [] False
case L.find ((fname ==) . ms_hspp_file) msums of
Just msum -> return msum
Nothing -> pprPanic "ModuleName Lookup Failed!!" (text "AARGHC!")
getTypecheckedModule :: GhcMonad m => FilePath -> m TypecheckedModule
getTypecheckedModule = findModSummary >=> parseModule >=> typecheckModule
More information about the Glasgow-haskell-users
mailing list