ghc-mod/Language/Haskell/GhcMod/GHCApi.hs

183 lines
6.0 KiB
Haskell
Raw Normal View History

2014-04-23 01:41:28 +00:00
{-# LANGUAGE ScopedTypeVariables, RecordWildCards #-}
2013-04-10 06:02:49 +00:00
2013-05-17 01:00:01 +00:00
module Language.Haskell.GhcMod.GHCApi (
2013-03-04 04:41:56 +00:00
withGHC
2014-04-23 07:37:24 +00:00
, withGHC'
2013-03-04 04:41:56 +00:00
, initializeFlagsWithCradle
, setTargetFiles
2014-03-19 01:23:32 +00:00
, addTargetFiles
2013-03-04 04:41:56 +00:00
, getDynamicFlags
2014-03-20 08:40:06 +00:00
, getSystemLibDir
, withDynFlags
2013-03-04 04:41:56 +00:00
) where
2012-02-14 07:09:53 +00:00
import Language.Haskell.GhcMod.CabalApi
import Language.Haskell.GhcMod.GHCChoice
import Language.Haskell.GhcMod.GhcPkg
import Control.Applicative ((<$>))
2014-04-26 05:38:49 +00:00
import Control.Monad (forM, void, unless)
2014-03-27 06:08:07 +00:00
import CoreMonad (liftIO)
2014-03-27 06:43:33 +00:00
import Data.Maybe (isJust, fromJust)
import Exception (ghandle, SomeException(..))
2014-04-24 03:15:59 +00:00
import GHC (Ghc, GhcMonad, DynFlags(..), GhcLink(..), HscTarget(..), LoadHowMuch(..))
2014-03-27 06:43:33 +00:00
import qualified GHC as G
import qualified Language.Haskell.GhcMod.Gap as Gap
import Language.Haskell.GhcMod.Types
2014-03-27 06:43:33 +00:00
import System.Exit (exitSuccess)
import System.IO (hPutStr, hPrint, stderr)
import System.Process (readProcess)
----------------------------------------------------------------
2014-03-26 03:09:02 +00:00
-- | Obtaining the directory for system libraries.
getSystemLibDir :: IO (Maybe FilePath)
getSystemLibDir = do
res <- readProcess "ghc" ["--print-libdir"] []
return $ case res of
"" -> Nothing
dirn -> Just (init dirn)
2012-02-14 07:09:53 +00:00
----------------------------------------------------------------
2013-05-20 05:28:56 +00:00
-- | Converting the 'Ghc' monad to the 'IO' monad.
withGHC :: FilePath -- ^ A target file displayed in an error message.
-> Ghc a -- ^ 'Ghc' actions created by the Ghc utilities.
-> IO a
2014-04-23 07:37:24 +00:00
withGHC file body = ghandle ignore $ withGHC' body
2012-02-14 07:09:53 +00:00
where
ignore :: SomeException -> IO a
ignore e = do
2012-12-07 05:27:02 +00:00
hPutStr stderr $ file ++ ":0:0:Error:"
hPrint stderr e
2012-06-04 06:40:26 +00:00
exitSuccess
2012-02-14 07:09:53 +00:00
2014-04-23 07:37:24 +00:00
withGHC' :: Ghc a -> IO a
withGHC' body = do
mlibdir <- getSystemLibDir
G.runGhc mlibdir $ do
dflags <- G.getSessionDynFlags
G.defaultCleanupHandler dflags body
2012-02-14 07:09:53 +00:00
----------------------------------------------------------------
importDirs :: [IncludeDir]
importDirs = [".","..","../..","../../..","../../../..","../../../../.."]
data Build = CabalPkg | SingleFile deriving Eq
-- | Initialize the 'DynFlags' relating to the compilation of a single
-- file or GHC session according to the 'Cradle' and 'Options'
-- provided.
2014-04-23 01:41:28 +00:00
initializeFlagsWithCradle :: GhcMonad m
=> Options
-> Cradle
-> [GHCOption]
-> m ()
initializeFlagsWithCradle opt cradle ghcopts
| cabal = withCabal |||> withSandbox
| otherwise = withSandbox
where
2013-09-19 07:21:48 +00:00
mCradleFile = cradleCabalFile cradle
cabal = isJust mCradleFile
2013-04-10 06:02:49 +00:00
withCabal = do
2013-09-19 07:21:48 +00:00
pkgDesc <- liftIO $ parseCabalFile $ fromJust mCradleFile
compOpts <- liftIO $ getCompilerOptions ghcopts cradle pkgDesc
initSession CabalPkg opt compOpts
withSandbox = initSession SingleFile opt compOpts
2013-09-19 06:58:50 +00:00
where
pkgOpts = ghcDbStackOpts $ cradlePkgDbStack cradle
compOpts
| null pkgOpts = CompilerOptions ghcopts importDirs []
| otherwise = CompilerOptions (ghcopts ++ pkgOpts) [wdir,rdir] []
wdir = cradleCurrentDir cradle
rdir = cradleRootDir cradle
2013-03-04 04:41:56 +00:00
----------------------------------------------------------------
2014-04-23 01:41:28 +00:00
initSession :: GhcMonad m
=> Build
-> Options
2013-09-19 06:58:50 +00:00
-> CompilerOptions
-> m ()
initSession build Options {..} CompilerOptions {..} = do
2014-04-23 01:41:28 +00:00
df <- G.getSessionDynFlags
void $ G.setSessionDynFlags =<< (addCmdOpts ghcOptions
2014-04-23 01:41:28 +00:00
$ setLinkerOptions
$ setIncludeDirs includeDirs
$ setBuildEnv build
$ setEmptyLogger
2014-04-23 01:41:28 +00:00
$ Gap.addPackageFlags depPackages df)
2013-03-04 04:41:56 +00:00
setEmptyLogger :: DynFlags -> DynFlags
setEmptyLogger df = Gap.setLogAction df $ \_ _ _ _ _ -> return ()
2013-03-04 03:53:28 +00:00
2013-03-13 04:17:22 +00:00
----------------------------------------------------------------
2014-04-23 01:41:28 +00:00
-- we don't want to generate object code so we compile to bytecode
-- (HscInterpreted) which implies LinkInMemory
-- HscInterpreted
setLinkerOptions :: DynFlags -> DynFlags
setLinkerOptions df = df {
ghcLink = LinkInMemory
, hscTarget = HscInterpreted
}
setIncludeDirs :: [IncludeDir] -> DynFlags -> DynFlags
setIncludeDirs idirs df = df { importPaths = idirs }
setBuildEnv :: Build -> DynFlags -> DynFlags
setBuildEnv build = setHideAllPackages build . setCabalPackage build
-- At the moment with this option set ghc only prints different error messages,
-- suggesting the user to add a hidden package to the build-depends in his cabal
-- file for example
setCabalPackage :: Build -> DynFlags -> DynFlags
setCabalPackage CabalPkg df = Gap.setCabalPkg df
setCabalPackage _ df = df
-- | Enable hiding of all package not explicitly exposed (like Cabal does)
setHideAllPackages :: Build -> DynFlags -> DynFlags
setHideAllPackages CabalPkg df = Gap.setHideAllPackages df
setHideAllPackages _ df = df
-- | Parse command line ghc options and add them to the 'DynFlags' passed
addCmdOpts :: GhcMonad m => [GHCOption] -> DynFlags -> m DynFlags
addCmdOpts cmdOpts df =
tfst <$> G.parseDynamicFlags df (map G.noLoc cmdOpts)
2013-03-05 07:16:27 +00:00
where
tfst (a,_,_) = a
2012-02-14 07:09:53 +00:00
----------------------------------------------------------------
2014-04-24 03:15:59 +00:00
-- | Set the files and load
2013-09-16 02:00:39 +00:00
setTargetFiles :: (GhcMonad m) => [FilePath] -> m ()
setTargetFiles files = do
2014-03-27 06:43:33 +00:00
targets <- forM files $ \file -> G.guessTarget file Nothing
2014-04-26 05:38:49 +00:00
unless (null targets) $ do
G.setTargets targets
void $ G.load LoadAllTargets
2013-03-04 02:21:41 +00:00
2014-03-26 03:09:02 +00:00
-- | Adding the files to the targets.
2014-03-19 01:23:32 +00:00
addTargetFiles :: (GhcMonad m) => [FilePath] -> m ()
addTargetFiles files = do
2014-03-27 06:43:33 +00:00
targets <- forM files $ \file -> G.guessTarget file Nothing
2014-04-26 05:38:49 +00:00
unless (null targets) $ mapM_ G.addTarget targets
2014-03-19 01:23:32 +00:00
2013-03-04 02:21:41 +00:00
----------------------------------------------------------------
2013-09-05 05:35:28 +00:00
-- | Return the 'DynFlags' currently in use in the GHC session.
2013-03-04 04:41:56 +00:00
getDynamicFlags :: IO DynFlags
getDynamicFlags = do
mlibdir <- getSystemLibDir
2014-03-27 06:43:33 +00:00
G.runGhc mlibdir G.getSessionDynFlags
withDynFlags :: (DynFlags -> DynFlags) -> Ghc a -> Ghc a
withDynFlags setFlag body = G.gbracket setup teardown (\_ -> body)
where
setup = do
dflag <- G.getSessionDynFlags
void $ G.setSessionDynFlags (setFlag dflag)
return dflag
teardown = void . G.setSessionDynFlags