ghc-mod/GHCApi.hs

159 lines
4.8 KiB
Haskell
Raw Normal View History

2013-03-04 04:41:56 +00:00
module GHCApi (
withGHC
, withGHCDummyFile
, initializeFlags
, initializeFlagsWithCradle
, setTargetFile
, getDynamicFlags
, getFastCheck
) where
2012-02-14 07:09:53 +00:00
2013-03-03 06:47:03 +00:00
import CabalApi
2012-02-15 05:52:48 +00:00
import Control.Applicative
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 ErrMsg
import Exception
import GHC
import GHC.Paths (libdir)
import HeaderInfo
import System.Exit
import System.IO
2012-02-14 07:09:53 +00:00
import Types
----------------------------------------------------------------
2013-03-04 04:41:56 +00:00
withGHCDummyFile :: Alternative m => Ghc (m a) -> IO (m a)
withGHCDummyFile = withGHC "Dummy"
2012-12-07 05:27:02 +00:00
2013-03-04 04:41:56 +00:00
withGHC :: Alternative m => FilePath -> Ghc (m a) -> IO (m a)
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)
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 = [".","..","../..","../../..","../../../..","../../../../.."]
2013-03-04 04:41:56 +00:00
initializeFlagsWithCradle :: Options -> Cradle -> FilePath -> [GHCOption] -> Bool -> Ghc LogReader
initializeFlagsWithCradle opt cradle fileName ghcOptions logging
2013-03-04 01:40:33 +00:00
| cabal = do
2013-03-03 06:50:09 +00:00
(gopts,idirs,depPkgs,hdrExts) <- liftIO $ fromCabalFile ghcOptions cradle
2013-03-02 07:14:55 +00:00
initSession opt gopts idirs (Just depPkgs) (Just hdrExts) logging fileName
2013-03-04 01:40:33 +00:00
| otherwise =
initSession opt ghcOptions importDirs Nothing Nothing logging fileName
where
2013-03-02 07:14:55 +00:00
cabal = isJust $ cradleCabalFile cradle
2013-03-04 04:41:56 +00:00
----------------------------------------------------------------
initSession :: Options
-> [GHCOption]
-> [IncludeDir]
-> Maybe [Package]
-> Maybe [LangExt]
-> Bool
-> FilePath
-> Ghc LogReader
initSession opt cmdOpts idirs mDepPkgs mLangExts logging file = 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-03-04 04:41:56 +00:00
fast <- liftIO $ getFastCheck df0 file mLangExts
2013-03-04 04:11:04 +00:00
let df2 = modifyFlags df1 idirs mDepPkgs fast (expandSplice opt)
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-05 07:16:27 +00:00
getHeaderExtension :: DynFlags -> FilePath -> IO [HeaderExt]
2013-03-04 02:21:41 +00:00
getHeaderExtension dflags file = map unLoc <$> getOptionsFromFile dflags file
----------------------------------------------------------------
2013-03-04 04:41:56 +00:00
getFastCheck :: DynFlags -> FilePath -> Maybe [LangExt] -> IO Bool
getFastCheck dflags file mLangExts = do
2013-03-04 04:11:04 +00:00
hdrExts <- getHeaderExtension dflags file
return . not $ useTemplateHaskell mLangExts hdrExts
2013-03-04 03:53:28 +00:00
useTemplateHaskell :: Maybe [LangExt] -> [HeaderExt] -> Bool
useTemplateHaskell mLangExts hdrExts = th1 || th2
where
th1 = "-XTemplateHaskell" `elem` hdrExts
th2 = maybe False ("TemplateHaskell" `elem`) mLangExts
2012-02-14 07:09:53 +00:00
----------------------------------------------------------------
2013-03-04 03:53:28 +00:00
-- FIXME removing Options
modifyFlags :: DynFlags -> [IncludeDir] -> Maybe [Package] -> Bool -> Bool -> DynFlags
modifyFlags d0 idirs mDepPkgs fast splice
| splice = setSplice d3
| otherwise = d3
2012-02-14 07:09:53 +00:00
where
2013-03-04 03:53:28 +00:00
d1 = d0 { importPaths = idirs }
d2 = setFastOrNot d1 fast
d3 = maybe d2 (addDevPkgs d2) mDepPkgs
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
setFastOrNot :: DynFlags -> Bool -> DynFlags
setFastOrNot dflags False = dflags {
2013-03-04 04:11:04 +00:00
ghcLink = LinkInMemory
, hscTarget = HscInterpreted
2013-03-04 03:53:28 +00:00
}
setFastOrNot dflags True = 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-04 02:21:41 +00:00
addDevPkgs :: DynFlags -> [Package] -> DynFlags
addDevPkgs df pkgs = df''
where
df' = dopt_set df Opt_HideAllPackages
2013-03-04 02:21:41 +00:00
df'' = df' {
packageFlags = map ExposePackage pkgs ++ packageFlags df
}
----------------------------------------------------------------
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