GHC API arguments via cabal/stack?

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

Hi David,
You can see how Halive does it here:
https://github.com/lukexi/halive/blob/master/src/Halive/FindPackageDBs.hs#L5...
https://github.com/lukexi/halive/blob/master/src/Halive/FindPackageDBs.hs#L6...
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 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

Hi David,
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.
There's cabal-cargs[1] to extract the relevant info for ghc from a cabal file. I don't know how much work it would be to make it stack aware/compatible. Greetings, Daniel [1] https://github.com/dan-t/cabal-cargs

On Fri, Mar 11, 2016 at 09:27:40AM +0000, David Turner wrote:
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.
Using the Cabal library to do this works very well in general, we do this in ghc-mod these days. The only way I've seen problems creep up so far is if cabal-install is linked against a different version of Cabal than your program. If your analysis program doesn't have to work on the same cabal dist directory as cabal-install (like ghc-mod does) then that's a non problem though. Anyways we've wrapped all the ugly stuff to work around this problem into a library called cabal-helper: http://hackage.haskell.org/package/cabal-helper/docs/Distribution-Helper.htm... Here's a little example program using that library which should do what you want: ``` import System.Environment import System.Directory import System.Process import Distribution.Helper import Data.Char import Data.List main = do [project_dir] <- getArgs setCurrentDirectory project_dir dist_dir <- dropWhileEnd isSpace <$> readProcess "stack" ["path", "--dist-dir"] "" print =<< (runQuery (defaultQueryEnv "." dist_dir) $ ghcOptions) ``` --Daniel

Cabal-helper looks like just the ticket, thanks!
On 11 Mar 2016 12:32, "Daniel Gröber"
On Fri, Mar 11, 2016 at 09:27:40AM +0000, David Turner wrote:
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.
Using the Cabal library to do this works very well in general, we do this in ghc-mod these days. The only way I've seen problems creep up so far is if cabal-install is linked against a different version of Cabal than your program. If your analysis program doesn't have to work on the same cabal dist directory as cabal-install (like ghc-mod does) then that's a non problem though.
Anyways we've wrapped all the ugly stuff to work around this problem into a library called cabal-helper:
http://hackage.haskell.org/package/cabal-helper/docs/Distribution-Helper.htm...
Here's a little example program using that library which should do what you want:
``` import System.Environment import System.Directory import System.Process import Distribution.Helper import Data.Char import Data.List
main = do [project_dir] <- getArgs setCurrentDirectory project_dir dist_dir <- dropWhileEnd isSpace <$> readProcess "stack" ["path", "--dist-dir"] "" print =<< (runQuery (defaultQueryEnv "." dist_dir) $ ghcOptions)
```
--Daniel

It is quite hacky but if I want to get access to a typechecked module,
I usually modify haddock and then invoke my analysis with "cabal
haddock --haddock-options="--my-flag". That saves me the pain of
having the deal with manually getting the paths to this stuff.
On Fri, Mar 11, 2016 at 9:27 AM, David Turner
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
participants (5)
-
Daniel Gröber
-
Daniel Trstenjak
-
David Turner
-
Luke Iannini
-
Matthew Pickering