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

177 lines
6.1 KiB
Haskell
Raw Normal View History

2013-04-10 06:02:49 +00:00
{-# LANGUAGE ScopedTypeVariables #-}
2013-05-17 01:00:01 +00:00
module Language.Haskell.GhcMod.GHCApi (
2013-03-04 04:41:56 +00:00
withGHC
, withGHCDummyFile
, initializeFlags
, 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
2013-03-04 04:41:56 +00:00
) where
2012-02-14 07:09:53 +00:00
2014-03-27 06:43:33 +00:00
import Control.Applicative (Alternative, (<$>))
import Control.Monad (void, forM)
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 Distribution.PackageDescription (PackageDescription)
2014-03-27 06:43:33 +00:00
import DynFlags (dopt_set)
import Exception (ghandle, SomeException(..))
import GHC (Ghc, GhcMonad, DynFlags(..), DynFlag(Opt_D_dump_splices), GhcLink(..), HscTarget(..))
import qualified GHC as G
2013-05-17 01:00:01 +00:00
import Language.Haskell.GhcMod.CabalApi
import Language.Haskell.GhcMod.ErrMsg
import Language.Haskell.GhcMod.GHCChoice
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.
2013-09-05 05:35:28 +00:00
withGHCDummyFile :: Alternative m => Ghc (m a) -- ^ 'Ghc' actions created by the Ghc utilities.
2013-05-20 05:28:56 +00:00
-> IO (m a)
2013-03-04 04:41:56 +00:00
withGHCDummyFile = withGHC "Dummy"
2012-12-07 05:27:02 +00:00
2013-05-20 05:28:56 +00:00
-- | Converting the 'Ghc' monad to the 'IO' monad.
2013-09-05 05:35:28 +00:00
withGHC :: Alternative m => FilePath -- ^ A target file displayed in an error message.
-> Ghc (m a) -- ^ 'Ghc' actions created by the Ghc utilities.
2013-05-20 05:28:56 +00:00
-> IO (m a)
withGHC file body = do
mlibdir <- getSystemLibDir
2014-03-27 06:43:33 +00:00
ghandle ignore $ G.runGhc mlibdir $ do
dflags <- G.getSessionDynFlags
G.defaultCleanupHandler dflags body
2012-02-14 07:09:53 +00:00
where
2012-02-15 05:52:48 +00:00
ignore :: Alternative m => SomeException -> IO (m 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
----------------------------------------------------------------
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.
initializeFlagsWithCradle :: GhcMonad m => Options -> Cradle -> [GHCOption] -> Bool -> m (LogReader, Maybe PackageDescription)
2013-09-19 06:58:50 +00:00
initializeFlagsWithCradle opt cradle ghcopts logging
| cabal = withCabal |||> withoutCabal
2013-04-10 06:02:49 +00:00
| otherwise = withoutCabal
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
logger <- initSession CabalPkg opt compOpts logging
return (logger, Just pkgDesc)
withoutCabal = do
logger <- initSession SingleFile opt compOpts logging
return (logger, Nothing)
2013-09-19 06:58:50 +00:00
where
compOpts = CompilerOptions ghcopts importDirs []
2013-03-04 04:41:56 +00:00
----------------------------------------------------------------
initSession :: GhcMonad m => Build
-> Options
2013-09-19 06:58:50 +00:00
-> CompilerOptions
-> Bool
-> m LogReader
2013-09-19 06:58:50 +00:00
initSession build opt compOpts logging = do
2014-03-27 06:43:33 +00:00
dflags0 <- G.getSessionDynFlags
2013-03-04 04:11:04 +00:00
(dflags1,readLog) <- setupDynamicFlags dflags0
2014-03-27 06:43:33 +00:00
_ <- G.setSessionDynFlags dflags1
2012-02-14 07:09:53 +00:00
return readLog
2013-03-04 04:11:04 +00:00
where
2013-09-19 06:58:50 +00:00
cmdOpts = ghcOptions compOpts
idirs = includeDirs compOpts
depPkgs = depPackages compOpts
2013-09-03 05:40:51 +00:00
ls = lineSeparator opt
2013-03-04 04:11:04 +00:00
setupDynamicFlags df0 = do
df1 <- modifyFlagsWithOpts df0 cmdOpts
2013-09-19 06:58:50 +00:00
let df2 = modifyFlags df1 idirs depPkgs (expandSplice opt) build
2013-03-05 07:16:27 +00:00
df3 <- modifyFlagsWithOpts df2 $ ghcOpts opt
2013-09-03 05:40:51 +00:00
liftIO $ setLogger logging df3 ls
2012-02-14 07:09:53 +00:00
2013-03-04 02:21:41 +00:00
----------------------------------------------------------------
2013-09-16 00:56:08 +00:00
-- | Initialize the 'DynFlags' relating to the compilation of a single
-- file or GHC session.
initializeFlags :: GhcMonad m => Options -> m ()
2013-03-04 04:41:56 +00:00
initializeFlags opt = do
2014-03-27 06:43:33 +00:00
dflags0 <- G.getSessionDynFlags
2013-03-05 07:16:27 +00:00
dflags1 <- modifyFlagsWithOpts dflags0 $ ghcOpts opt
2014-03-27 06:43:33 +00:00
void $ G.setSessionDynFlags dflags1
2013-03-04 04:41:56 +00:00
----------------------------------------------------------------
2013-03-04 03:53:28 +00:00
-- FIXME removing Options
2013-09-19 06:58:50 +00:00
modifyFlags :: DynFlags -> [IncludeDir] -> [Package] -> Bool -> Build -> DynFlags
2013-10-02 03:43:40 +00:00
modifyFlags d0 idirs depPkgs splice build
| splice = setSplice d4
| otherwise = d4
2012-02-14 07:09:53 +00:00
where
2013-03-04 03:53:28 +00:00
d1 = d0 { importPaths = idirs }
2014-03-17 06:56:00 +00:00
d2 = d1 {
ghcLink = LinkInMemory
, hscTarget = HscInterpreted
}
2013-10-02 03:43:40 +00:00
d3 = Gap.addDevPkgs d2 depPkgs
d4 | build == CabalPkg = Gap.setCabalPkg d3
| otherwise = d3
2013-03-04 03:53:28 +00:00
setSplice :: DynFlags -> DynFlags
2013-03-04 04:11:04 +00:00
setSplice dflag = dopt_set dflag Opt_D_dump_splices
2013-03-04 03:53:28 +00:00
2013-03-13 04:17:22 +00:00
----------------------------------------------------------------
2013-09-16 02:00:39 +00:00
modifyFlagsWithOpts :: GhcMonad m => DynFlags -> [GHCOption] -> m DynFlags
2013-03-05 07:16:27 +00:00
modifyFlagsWithOpts dflags cmdOpts =
2014-03-27 06:43:33 +00:00
tfst <$> G.parseDynamicFlags dflags (map G.noLoc cmdOpts)
2013-03-05 07:16:27 +00:00
where
tfst (a,_,_) = a
2012-02-14 07:09:53 +00:00
----------------------------------------------------------------
2013-09-05 05:35:28 +00:00
-- | Set the files that GHC will load / compile.
2013-09-16 02:00:39 +00:00
setTargetFiles :: (GhcMonad m) => [FilePath] -> m ()
setTargetFiles [] = error "ghc-mod: setTargetFiles: No target files given"
setTargetFiles files = do
2014-03-27 06:43:33 +00:00
targets <- forM files $ \file -> G.guessTarget file Nothing
G.setTargets targets
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 [] = error "ghc-mod: addTargetFiles: No target files given"
addTargetFiles files = do
2014-03-27 06:43:33 +00:00
targets <- forM files $ \file -> G.guessTarget file Nothing
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