api to access .hi files

Sam Halliday sam.halliday at gmail.com
Fri Aug 2 19:46:41 UTC 2019


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
-------------- next part --------------
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 194 bytes
Desc: not available
URL: <http://mail.haskell.org/pipermail/ghc-devs/attachments/20190802/61bb6860/attachment.sig>


More information about the ghc-devs mailing list