[Haskell-cafe] Accessing and Inspecting StgBindings in Ghci
Michael Christensen
chmdko at gmail.com
Wed Feb 3 06:30:06 UTC 2016
Hi all,
I'm currently trying to understand how STG works, and my goal right now
is to be able to inspect StgBinding values. I've written a short
program, based on the wiki article GHC/As a library
<https://wiki.haskell.org/GHC/As_a_library>, like below:
-- Code.hs --
module Lib (printSTG, dumpSTG) where
import Control.Monad.Ghc (lift, runGhcT)
import CorePrep (corePrepPgm)
import CoreToStg (coreToStg)
import DynFlags (defaultFatalMessager, defaultFlushOut)
import GHC hiding (runGhcT)
import GHC.Paths (libdir)
import HscMain (newHscEnv)
import HscTypes (hsc_dflags, typeEnvTyCons)
import Outputable (interppSP, showSDoc)
import System.Environment (getArgs)
import StgSyn (StgBinding)
dumpSTG :: String -> IO [StgBinding]
dumpSTG fileName = defaultErrorHandler defaultFatalMessager
defaultFlushOut $
runGhcT (Just libdir) $ do
sess <- getSession
let dflags = hsc_dflags sess
setSessionDynFlags dflags
cm <- compileToCoreModule fileName
let md = cm_module cm
ml <- fmap ms_location $ getModSummary $ moduleName md
lift $ do
cp <- corePrepPgm sess ml <$> cm_binds <*> (typeEnvTyCons .
cm_types) $ cm
coreToStg dflags md cp
printSTG =
getArgs >>= \x -> case x of
[] -> putStrLn "usage: Main <file.hs>"
(fileName:_) -> do
bindings <- dumpSTG fileName
str <- runGhcT (Just libdir) $ do
dflags <- getSessionDynFlags
return $ showSDoc dflags $ interppSP bindings
putStrLn str
This works when I compile it to print out a Haskell file in STG format.
However, *my question is*, is there a way so that I can call dumpSTG to
get back that list of StgBindings, *from within Ghci*? Whenever I do so
within Ghci, i.e.
ghci> :l code.hs
ghci> bindings <- dumpSTG "fileToTest.hs"
<interactive>: panic! (the 'impossible' happened)
(GHC version 7.10.3 for x86_64-unknown-linux):
no package state yet: call GHC.setSessionDynFlags
I know that it's saying I need to set the session dyn flags, but I'm not
sure how that can get done from within Ghci, especially because that
needs to get done within the GhcMonad. Part of my problem may stem from
having a inadequate understanding of monads. Any help or pointers would
be greatly appreciated!
Thank you very much,
Mike
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20160202/82c55f98/attachment.html>
More information about the Haskell-Cafe
mailing list