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
|
2013-08-21 08:21:49 +00:00
|
|
|
, setTargetFiles
|
2013-03-04 04:41:56 +00:00
|
|
|
, getDynamicFlags
|
2014-03-20 08:40:06 +00:00
|
|
|
, getSystemLibDir
|
2014-04-26 02:43:30 +00:00
|
|
|
, withDynFlags
|
2014-05-09 14:45:34 +00:00
|
|
|
, withCmdFlags
|
2014-04-28 03:52:09 +00:00
|
|
|
, setNoWaringFlags
|
|
|
|
, setAllWaringFlags
|
2013-03-04 04:41:56 +00:00
|
|
|
) where
|
2012-02-14 07:09:53 +00:00
|
|
|
|
2014-04-15 03:13:10 +00:00
|
|
|
import Language.Haskell.GhcMod.CabalApi
|
|
|
|
import Language.Haskell.GhcMod.GHCChoice
|
|
|
|
import Language.Haskell.GhcMod.GhcPkg
|
|
|
|
|
2014-04-18 01:55:49 +00:00
|
|
|
import Control.Applicative ((<$>))
|
2014-04-26 12:59:06 +00:00
|
|
|
import Control.Monad (forM, void)
|
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
|
2014-05-09 18:36:20 +00:00
|
|
|
import GHC.Paths (libdir)
|
2013-07-02 08:48:44 +00:00
|
|
|
import qualified Language.Haskell.GhcMod.Gap as Gap
|
2013-09-19 07:25:36 +00:00
|
|
|
import Language.Haskell.GhcMod.Types
|
2014-03-27 06:43:33 +00:00
|
|
|
import System.Exit (exitSuccess)
|
|
|
|
import System.IO (hPutStr, hPrint, stderr)
|
2014-04-28 03:52:09 +00:00
|
|
|
import System.IO.Unsafe (unsafePerformIO)
|
2014-03-17 07:58:55 +00:00
|
|
|
|
|
|
|
----------------------------------------------------------------
|
|
|
|
|
2014-03-26 03:09:02 +00:00
|
|
|
-- | Obtaining the directory for system libraries.
|
2014-03-17 07:58:55 +00:00
|
|
|
getSystemLibDir :: IO (Maybe FilePath)
|
2014-05-09 18:36:20 +00:00
|
|
|
getSystemLibDir = return $ Just libdir
|
2012-02-14 07:09:53 +00:00
|
|
|
|
|
|
|
----------------------------------------------------------------
|
|
|
|
|
2013-05-20 05:28:56 +00:00
|
|
|
-- | Converting the 'Ghc' monad to the 'IO' monad.
|
2014-04-18 01:55:49 +00:00
|
|
|
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
|
2014-04-18 01:55:49 +00:00
|
|
|
ignore :: SomeException -> IO a
|
2012-04-16 02:01:29 +00:00
|
|
|
ignore e = do
|
2012-12-07 05:27:02 +00:00
|
|
|
hPutStr stderr $ file ++ ":0:0:Error:"
|
2012-04-16 02:01:29 +00:00
|
|
|
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
|
|
|
----------------------------------------------------------------
|
|
|
|
|
2013-03-01 12:17:52 +00:00
|
|
|
importDirs :: [IncludeDir]
|
|
|
|
importDirs = [".","..","../..","../../..","../../../..","../../../../.."]
|
|
|
|
|
2013-04-02 00:56:57 +00:00
|
|
|
data Build = CabalPkg | SingleFile deriving Eq
|
|
|
|
|
2013-08-26 16:28:21 +00:00
|
|
|
-- | 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
|
2014-04-26 08:54:15 +00:00
|
|
|
-> m ()
|
2014-04-28 04:00:25 +00:00
|
|
|
initializeFlagsWithCradle opt cradle
|
2014-03-30 08:28:57 +00:00
|
|
|
| cabal = withCabal |||> withSandbox
|
|
|
|
| otherwise = withSandbox
|
2013-03-01 12:17:52 +00:00
|
|
|
where
|
2013-09-19 07:21:48 +00:00
|
|
|
mCradleFile = cradleCabalFile cradle
|
|
|
|
cabal = isJust mCradleFile
|
2014-04-28 04:00:25 +00:00
|
|
|
ghcopts = ghcOpts opt
|
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
|
2014-04-26 08:54:15 +00:00
|
|
|
initSession CabalPkg opt compOpts
|
|
|
|
withSandbox = initSession SingleFile opt compOpts
|
2013-09-19 06:58:50 +00:00
|
|
|
where
|
2014-04-15 03:13:10 +00:00
|
|
|
pkgOpts = ghcDbStackOpts $ cradlePkgDbStack cradle
|
2014-03-30 08:28:57 +00:00
|
|
|
compOpts
|
2014-04-15 03:13:10 +00:00
|
|
|
| null pkgOpts = CompilerOptions ghcopts importDirs []
|
|
|
|
| otherwise = CompilerOptions (ghcopts ++ pkgOpts) [wdir,rdir] []
|
2014-03-30 08:28:57 +00:00
|
|
|
wdir = cradleCurrentDir cradle
|
|
|
|
rdir = cradleRootDir cradle
|
2013-03-01 12:17:52 +00:00
|
|
|
|
2013-03-04 04:41:56 +00:00
|
|
|
----------------------------------------------------------------
|
|
|
|
|
2014-04-23 01:41:28 +00:00
|
|
|
initSession :: GhcMonad m
|
|
|
|
=> Build
|
2013-04-02 00:56:57 +00:00
|
|
|
-> Options
|
2013-09-19 06:58:50 +00:00
|
|
|
-> CompilerOptions
|
2014-04-26 08:54:15 +00:00
|
|
|
-> m ()
|
|
|
|
initSession build Options {..} CompilerOptions {..} = do
|
2014-04-23 01:41:28 +00:00
|
|
|
df <- G.getSessionDynFlags
|
2014-04-26 08:54:15 +00:00
|
|
|
void $ G.setSessionDynFlags =<< (addCmdOpts ghcOptions
|
2014-04-23 01:41:28 +00:00
|
|
|
$ setLinkerOptions
|
|
|
|
$ setIncludeDirs includeDirs
|
|
|
|
$ setBuildEnv build
|
2014-04-26 08:54:15 +00:00
|
|
|
$ setEmptyLogger
|
2014-04-23 01:41:28 +00:00
|
|
|
$ Gap.addPackageFlags depPackages df)
|
2013-03-04 04:41:56 +00:00
|
|
|
|
2014-04-26 08:54:15 +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-28 12:51:39 +00:00
|
|
|
-- | Set the files as targets and load them.
|
2013-09-16 02:00:39 +00:00
|
|
|
setTargetFiles :: (GhcMonad m) => [FilePath] -> m ()
|
2013-08-21 08:21:49 +00:00
|
|
|
setTargetFiles files = do
|
2014-03-27 06:43:33 +00:00
|
|
|
targets <- forM files $ \file -> G.guessTarget file Nothing
|
2014-04-26 12:59:06 +00:00
|
|
|
G.setTargets targets
|
|
|
|
void $ G.load LoadAllTargets
|
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
|
2014-03-17 07:58:55 +00:00
|
|
|
getDynamicFlags = do
|
|
|
|
mlibdir <- getSystemLibDir
|
2014-03-27 06:43:33 +00:00
|
|
|
G.runGhc mlibdir G.getSessionDynFlags
|
2014-04-26 02:43:30 +00:00
|
|
|
|
2014-05-14 16:05:40 +00:00
|
|
|
withDynFlags :: GhcMonad m
|
|
|
|
=> (DynFlags -> DynFlags)
|
|
|
|
-> m a
|
|
|
|
-> m a
|
|
|
|
withDynFlags setFlags body = G.gbracket setup teardown (\_ -> body)
|
2014-04-26 02:43:30 +00:00
|
|
|
where
|
|
|
|
setup = do
|
2014-05-14 16:05:40 +00:00
|
|
|
dflags <- G.getSessionDynFlags
|
|
|
|
void $ G.setSessionDynFlags (setFlags dflags)
|
|
|
|
return dflags
|
2014-04-26 02:43:30 +00:00
|
|
|
teardown = void . G.setSessionDynFlags
|
2014-04-26 13:51:29 +00:00
|
|
|
|
2014-05-14 16:05:40 +00:00
|
|
|
withCmdFlags :: GhcMonad m => [GHCOption] -> m a -> m a
|
2014-05-09 14:45:34 +00:00
|
|
|
withCmdFlags flags body = G.gbracket setup teardown (\_ -> body)
|
|
|
|
where
|
|
|
|
setup = do
|
2014-05-14 16:05:40 +00:00
|
|
|
dflags <- G.getSessionDynFlags >>= addCmdOpts flags
|
|
|
|
void $ G.setSessionDynFlags dflags
|
|
|
|
return dflags
|
2014-05-09 14:45:34 +00:00
|
|
|
teardown = void . G.setSessionDynFlags
|
|
|
|
|
2014-04-26 13:51:29 +00:00
|
|
|
----------------------------------------------------------------
|
|
|
|
|
2014-04-28 12:51:39 +00:00
|
|
|
-- | Set 'DynFlags' equivalent to "-w:".
|
2014-04-28 03:52:09 +00:00
|
|
|
setNoWaringFlags :: DynFlags -> DynFlags
|
2014-04-28 05:36:55 +00:00
|
|
|
setNoWaringFlags df = df { warningFlags = Gap.emptyWarnFlags}
|
2014-04-28 03:52:09 +00:00
|
|
|
|
2014-04-28 12:51:39 +00:00
|
|
|
-- | Set 'DynFlags' equivalent to "-Wall".
|
2014-04-28 03:52:09 +00:00
|
|
|
setAllWaringFlags :: DynFlags -> DynFlags
|
|
|
|
setAllWaringFlags df = df { warningFlags = allWarningFlags }
|
|
|
|
|
2014-04-28 05:36:55 +00:00
|
|
|
allWarningFlags :: Gap.WarnFlags
|
2014-04-28 03:52:09 +00:00
|
|
|
allWarningFlags = unsafePerformIO $ do
|
|
|
|
mlibdir <- getSystemLibDir
|
|
|
|
G.runGhc mlibdir $ do
|
|
|
|
df <- G.getSessionDynFlags
|
|
|
|
df' <- addCmdOpts ["-Wall"] df
|
|
|
|
return $ G.warningFlags df'
|