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
|
|
|
|
, setTargetFile
|
|
|
|
, getDynamicFlags
|
2013-04-01 05:16:34 +00:00
|
|
|
, setSlowDynFlags
|
2013-03-15 05:40:36 +00:00
|
|
|
, checkSlowAndSet
|
2013-04-01 06:59:53 +00:00
|
|
|
, canCheckFast
|
2013-03-04 04:41:56 +00:00
|
|
|
) where
|
2012-02-14 07:09:53 +00:00
|
|
|
|
2012-02-15 05:52:48 +00:00
|
|
|
import Control.Applicative
|
2012-04-16 02:01:29 +00:00
|
|
|
import Control.Exception
|
2013-03-04 04:41:56 +00:00
|
|
|
import Control.Monad
|
2012-02-14 07:09:53 +00:00
|
|
|
import CoreMonad
|
2013-03-02 07:14:55 +00:00
|
|
|
import Data.Maybe (isJust)
|
2012-02-14 07:09:53 +00:00
|
|
|
import DynFlags
|
|
|
|
import Exception
|
|
|
|
import GHC
|
|
|
|
import GHC.Paths (libdir)
|
2013-05-17 01:00:01 +00:00
|
|
|
import Language.Haskell.GhcMod.CabalApi
|
|
|
|
import Language.Haskell.GhcMod.ErrMsg
|
|
|
|
import Language.Haskell.GhcMod.GHCChoice
|
|
|
|
import Language.Haskell.GhcMod.Types
|
2013-07-02 08:48:44 +00:00
|
|
|
import qualified Language.Haskell.GhcMod.Gap as Gap
|
2012-04-16 02:01:29 +00:00
|
|
|
import System.Exit
|
|
|
|
import System.IO
|
2012-02-14 07:09:53 +00:00
|
|
|
|
|
|
|
----------------------------------------------------------------
|
|
|
|
|
2013-05-20 05:28:56 +00:00
|
|
|
-- | Converting the 'Ghc' monad to the 'IO' monad.
|
|
|
|
withGHCDummyFile :: Alternative m => Ghc (m a) -- ^ 'Ghc' actions created by the Ghc utilities
|
|
|
|
-> 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.
|
|
|
|
withGHC :: Alternative m => FilePath -- ^ A target file displayed in an error message
|
|
|
|
-> Ghc (m a) -- ^ 'Ghc' actions created by the Ghc utilities
|
|
|
|
-> IO (m a)
|
2013-03-04 04:41:56 +00:00
|
|
|
withGHC file body = ghandle ignore $ runGhc (Just libdir) $ do
|
2012-02-14 10:14:21 +00:00
|
|
|
dflags <- getSessionDynFlags
|
|
|
|
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)
|
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
|
|
|
|
|
|
|
----------------------------------------------------------------
|
|
|
|
|
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-03-13 04:17:22 +00:00
|
|
|
initializeFlagsWithCradle :: Options -> Cradle -> [GHCOption] -> Bool -> Ghc LogReader
|
|
|
|
initializeFlagsWithCradle opt cradle ghcOptions logging
|
2013-05-09 01:09:12 +00:00
|
|
|
| cabal = withCabal ||> withoutCabal
|
2013-04-10 06:02:49 +00:00
|
|
|
| otherwise = withoutCabal
|
2013-03-01 12:17:52 +00:00
|
|
|
where
|
2013-03-02 07:14:55 +00:00
|
|
|
cabal = isJust $ cradleCabalFile cradle
|
2013-04-10 06:02:49 +00:00
|
|
|
withCabal = do
|
|
|
|
(gopts,idirs,depPkgs) <- liftIO $ fromCabalFile ghcOptions cradle
|
|
|
|
initSession CabalPkg opt gopts idirs (Just depPkgs) logging
|
|
|
|
withoutCabal =
|
|
|
|
initSession SingleFile opt ghcOptions importDirs Nothing logging
|
2013-03-01 12:17:52 +00:00
|
|
|
|
2013-03-04 04:41:56 +00:00
|
|
|
----------------------------------------------------------------
|
|
|
|
|
2013-04-02 00:56:57 +00:00
|
|
|
initSession :: Build
|
|
|
|
-> Options
|
2013-03-01 12:17:52 +00:00
|
|
|
-> [GHCOption]
|
|
|
|
-> [IncludeDir]
|
|
|
|
-> Maybe [Package]
|
|
|
|
-> Bool
|
|
|
|
-> Ghc LogReader
|
2013-04-02 00:56:57 +00:00
|
|
|
initSession build opt cmdOpts idirs mDepPkgs logging = do
|
2013-03-04 02:21:41 +00:00
|
|
|
dflags0 <- getSessionDynFlags
|
2013-03-04 04:11:04 +00:00
|
|
|
(dflags1,readLog) <- setupDynamicFlags dflags0
|
|
|
|
_ <- setSessionDynFlags dflags1
|
2012-02-14 07:09:53 +00:00
|
|
|
return readLog
|
2013-03-04 04:11:04 +00:00
|
|
|
where
|
|
|
|
setupDynamicFlags df0 = do
|
|
|
|
df1 <- modifyFlagsWithOpts df0 cmdOpts
|
2013-04-02 00:56:57 +00:00
|
|
|
let df2 = modifyFlags df1 idirs mDepPkgs (expandSplice opt) build
|
2013-03-05 07:16:27 +00:00
|
|
|
df3 <- modifyFlagsWithOpts df2 $ ghcOpts opt
|
2013-03-04 04:11:04 +00:00
|
|
|
liftIO $ setLogger logging df3
|
2012-02-14 07:09:53 +00:00
|
|
|
|
2013-03-04 02:21:41 +00:00
|
|
|
----------------------------------------------------------------
|
|
|
|
|
2013-03-04 04:41:56 +00:00
|
|
|
initializeFlags :: Options -> Ghc ()
|
|
|
|
initializeFlags opt = do
|
|
|
|
dflags0 <- getSessionDynFlags
|
2013-03-05 07:16:27 +00:00
|
|
|
dflags1 <- modifyFlagsWithOpts dflags0 $ ghcOpts opt
|
2013-03-04 04:41:56 +00:00
|
|
|
void $ setSessionDynFlags dflags1
|
|
|
|
|
|
|
|
----------------------------------------------------------------
|
|
|
|
|
2013-03-04 03:53:28 +00:00
|
|
|
-- FIXME removing Options
|
2013-04-02 00:56:57 +00:00
|
|
|
modifyFlags :: DynFlags -> [IncludeDir] -> Maybe [Package] -> Bool -> Build -> DynFlags
|
|
|
|
modifyFlags d0 idirs mDepPkgs 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 }
|
2013-04-01 05:16:34 +00:00
|
|
|
d2 = setFastOrNot d1 Fast
|
2013-07-02 08:48:44 +00:00
|
|
|
d3 = maybe d2 (Gap.addDevPkgs d2) mDepPkgs
|
|
|
|
d4 | build == CabalPkg = Gap.setCabalPkg d3
|
2013-04-02 00:56:57 +00:00
|
|
|
| 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-04-01 05:16:34 +00:00
|
|
|
setFastOrNot :: DynFlags -> CheckSpeed -> DynFlags
|
|
|
|
setFastOrNot dflags Slow = dflags {
|
2013-03-04 04:11:04 +00:00
|
|
|
ghcLink = LinkInMemory
|
|
|
|
, hscTarget = HscInterpreted
|
2013-03-04 03:53:28 +00:00
|
|
|
}
|
2013-04-01 05:16:34 +00:00
|
|
|
setFastOrNot dflags Fast = dflags {
|
2013-03-04 04:11:04 +00:00
|
|
|
ghcLink = NoLink
|
|
|
|
, hscTarget = HscNothing
|
2013-03-04 03:53:28 +00:00
|
|
|
}
|
2012-02-14 07:09:53 +00:00
|
|
|
|
2013-03-13 04:17:22 +00:00
|
|
|
setSlowDynFlags :: Ghc ()
|
2013-04-01 05:16:34 +00:00
|
|
|
setSlowDynFlags = (flip setFastOrNot Slow <$> getSessionDynFlags)
|
2013-03-13 04:17:22 +00:00
|
|
|
>>= void . setSessionDynFlags
|
2013-03-04 02:21:41 +00:00
|
|
|
|
2013-03-15 05:40:36 +00:00
|
|
|
-- To check TH, a session module graph is necessary.
|
|
|
|
-- "load" sets a session module graph using "depanal".
|
|
|
|
-- But we have to set "-fno-code" to DynFlags before "load".
|
|
|
|
-- So, this is necessary redundancy.
|
|
|
|
checkSlowAndSet :: Ghc ()
|
|
|
|
checkSlowAndSet = do
|
2013-04-01 06:59:53 +00:00
|
|
|
fast <- canCheckFast <$> depanal [] False
|
|
|
|
unless fast setSlowDynFlags
|
2013-03-15 05:40:36 +00:00
|
|
|
|
2013-03-04 02:21:41 +00:00
|
|
|
----------------------------------------------------------------
|
2012-02-14 07:09:53 +00:00
|
|
|
|
2013-03-05 07:16:27 +00:00
|
|
|
modifyFlagsWithOpts :: DynFlags -> [String] -> Ghc DynFlags
|
|
|
|
modifyFlagsWithOpts dflags cmdOpts =
|
|
|
|
tfst <$> parseDynamicFlags dflags (map noLoc cmdOpts)
|
|
|
|
where
|
|
|
|
tfst (a,_,_) = a
|
2012-02-14 07:09:53 +00:00
|
|
|
|
|
|
|
----------------------------------------------------------------
|
|
|
|
|
|
|
|
setTargetFile :: (GhcMonad m) => String -> m ()
|
|
|
|
setTargetFile file = do
|
|
|
|
target <- guessTarget file Nothing
|
|
|
|
setTargets [target]
|
2013-03-04 02:21:41 +00:00
|
|
|
|
|
|
|
----------------------------------------------------------------
|
|
|
|
|
2013-03-04 04:41:56 +00:00
|
|
|
getDynamicFlags :: IO DynFlags
|
|
|
|
getDynamicFlags = runGhc (Just libdir) getSessionDynFlags
|
2013-04-01 06:59:53 +00:00
|
|
|
|
|
|
|
canCheckFast :: ModuleGraph -> Bool
|
|
|
|
canCheckFast = not . any (hasTHorQQ . ms_hspp_opts)
|
|
|
|
where
|
|
|
|
hasTHorQQ :: DynFlags -> Bool
|
2013-04-10 06:05:46 +00:00
|
|
|
hasTHorQQ dflags = any (`xopt` dflags) [Opt_TemplateHaskell, Opt_QuasiQuotes]
|