Hi David,

You can see how Halive does it here:
https://github.com/lukexi/halive/blob/master/src/Halive/FindPackageDBs.hs#L56
https://github.com/lukexi/halive/blob/master/src/Halive/FindPackageDBs.hs#L65

basically just using "stack path". That'll at least get you the package dirs!

I haven't needed to pass any package ids to make things work after that.

The actual compilation code is here:
https://github.com/lukexi/halive/blob/master/src/Halive/SubHalive.hs

Cheers
Luke

On Fri, Mar 11, 2016 at 1:27 AM, David Turner <dct25-561bs@mythic-beasts.com> wrote:
Hi all,

I'm working on a little program that uses GHC as a library to do some static analysis on a project I'm working on. It runs things as far as the typechecker (so there's no Template Haskell remaining) and then does the analysis on the resulting AST.

Here is how I'm calling GHC at the moment:

runAnalyser :: FilePath -> [String] -> [String] -> IO [(Module, [Fact], [Assertion])]
runAnalyser srcDir args modules = do
  defaultErrorHandler defaultFatalMessager defaultFlushOut $ do
      runGhc (Just libdir) $ do
        dflags <- getSessionDynFlags
        (dflags', leftover, warnings) <- parseDynamicFlagsCmdLine dflags
                                          (map noLoc $ args ++ modules)
        setSessionDynFlags dflags'
        setTargets =<< forM modules (\exampleModule ->
          guessTarget (exampleModuleFile srcDir exampleModule) Nothing)
        load LoadAllTargets

        execWriterT $ forM_ modules $ \exampleModule -> do
          modSum <- lift $ getModSummary $ mkModuleName exampleModule
          p <- lift $ parseModule modSum
          t <- lift $ typecheckModule p
          case tm_renamed_source t of
            Nothing -> return ()
            Just (hsGroup, _, _, _) -> do
              assertions <- liftIO $ loadAssertions
                          $ exampleModuleFile srcDir exampleModule
              let mod = ms_mod $ pm_mod_summary $ tm_parsed_module t
              tell [( mod
                    , runFactM (moduleName mod) (facts hsGroup)
                    , assertions)]


The problem I'm currently facing is that this requires me to pass in the arguments to GHC, including where all the package databases are and all the package ids that stack has decided to use. So far, I've just copy-pasted this from the stack log and hard-coded it, but that's clearly not a good long-term solution.

I've half-heartedly tried to fool stack into running my analyser as the compiler, but stack calls ghc more times than just the one call that I need the arguments from. I could make it pass through to the real ghc but this feels like piling hacks on top of hacks.

I've also briefly contemplated using the Cabal library to read my .cabal file and work out what to do, but I'm unsure that this would work nicely under stack. At least, I'm not sure quite what to do with all the package databases and other stuff that stack does for you.

Is there a sensible and robust way to get these args as stack would make them?

Many thanks,

David




_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe