
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