api to access .hi files

Brandon Allbery allbery.b at gmail.com
Fri Aug 2 20:12:37 UTC 2019


No, those are in base. But I don't think you would be seeing imported names
as such there, come to think of it, only names declared locally.

On Fri, Aug 2, 2019 at 4:06 PM Sam Halliday <sam.halliday at gmail.com> wrote:

> Brandon Allbery <allbery.b at gmail.com> writes:
>
> > At a guess, because the ghc package defaults to being hidden (it's
> creating
> > a new ghc instance at runtime, so the visibility of the ghc package when
> > compiling your code is not relevant) you need to do the ghc-api
> equivalent
> > of "-package ghc". Or for testing just "ghc-pkg expose ghc".
>
> Hmm, would that also explain why the Prelude and Control.Monad modules
> are not shown either?
>
> Is there a way to expose all modules programmatically?
>
>
> >
> > On Fri, Aug 2, 2019 at 3:47 PM Sam Halliday <sam.halliday at 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 at haskell.org
> >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
> >>
> >
> >
> > --
> > brandon s allbery kf8nh
> > allbery.b at gmail.com
>
> --
> Best regards,
> Sam
>


-- 
brandon s allbery kf8nh
allbery.b at gmail.com
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-devs/attachments/20190802/d970d664/attachment.html>


More information about the ghc-devs mailing list