Hey Sam, Starting from the implementation of :browse and going through the call graph in: https://gitlab.haskell.org/ghc/ghc/blob/master/ghc/GHCi/UI.hs gave the following, which works for me:
module Main where import Control.Monad import Control.Monad.IO.Class import BasicTypes import DynFlags import GHC import GHC.Paths (libdir) import Maybes import Panic main = runGhc (Just libdir) $ do dflags <- getSessionDynFlags void $ setSessionDynFlags $ dflags { hscTarget = HscInterpreted , ghcLink = LinkInMemory } t <- guessTarget "Main.hs" Nothing setTargets [t] _ <- load LoadAllTargets graph <- getModuleGraph mss <- filterM (isLoaded . ms_mod_name) (mgModSummaries graph) let m = ms_mod ms ms = head mss liftIO . putStrLn $ (show . length $ mss) ++ " modules loaded" mi <- getModuleInfo m let mod_info = fromJust mi dflags <- getDynFlags let names = GHC.modInfoTopLevelScope mod_info `orElse` [] liftIO $ putStrLn $ "seen " <> (show $ length names) <> " Names" -- Best, Artem On Fri, 2 Aug 2019 at 15:47, Sam Halliday <sam.halli...@gmail.com> wrote: > To answer my own question with a solution and another question: > > Sam Halliday writes: > > I'm mostly interested in gathering information about symbols and their > > type signatures. As a first exercise: given a module+import section > > for a haskell source file, I want to find out which symbols (and their > > types) are available. Like :browse in ghci, but programmatically. > > This is answered by Stephen Diehl's blog post on the ghc api! How lucky > I am: http://www.stephendiehl.com/posts/ghc_01.html > > He points to getNamesInScope > > Unfortunately I'm getting zero Names back when loading a file that > imports several modules from ghc. Is there something I'm missing in the > following? > > module Main where > > import Control.Monad > import Control.Monad.IO.Class > import GHC > import GHC.Paths (libdir) > > main = runGhc (Just libdir) $ do > dflags <- getSessionDynFlags > void $ setSessionDynFlags $ dflags { > hscTarget = HscInterpreted > , ghcLink = LinkInMemory > } > addTarget $ Target (TargetFile "exe/Main.hs" Nothing) False Nothing > res <- load LoadAllTargets > liftIO $ putStrLn $ showPpr dflags res > names <- getNamesInScope > liftIO $ putStrLn $ "seen " <> (show $ length names) <> " Names" > > > -- > Best regards, > Sam > _______________________________________________ > ghc-devs mailing list > ghc-devs@haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs >
_______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs