{-# LANGUAGE ScopedTypeVariables, RecordWildCards, CPP #-}
module HIE.Bios.GHCApi (
withGHC
, withGHC'
, withGhcT
, initializeFlagsWithCradle
, initializeFlagsWithCradleWithMessage
, getDynamicFlags
, getSystemLibDir
, withDynFlags
, withCmdFlags
, setNoWarningFlags
, setAllWarningFlags
, setDeferTypeErrors
, CradleError(..)
) where
import CoreMonad (liftIO)
import Exception (ghandle, SomeException(..), ExceptionMonad(..), throwIO, Exception(..))
import GHC (Ghc, DynFlags(..), GhcLink(..), HscTarget(..), LoadHowMuch(..), GhcMonad, GhcT)
import qualified GHC as G
import qualified DriverPhases as G
import qualified Outputable as G
import qualified MonadUtils as G
import qualified HscMain as G
import qualified GhcMake as G
import qualified Util as G
import DynFlags
import Control.Monad (void, when)
import System.Exit (exitSuccess, ExitCode(..))
import System.IO (hPutStr, hPrint, stderr)
import System.IO.Unsafe (unsafePerformIO)
import System.Process (readProcess)
import System.Directory
import System.FilePath
import qualified HIE.Bios.Gap as Gap
import HIE.Bios.Types
import Debug.Trace
import qualified Crypto.Hash.SHA1 as H
import qualified Data.ByteString.Char8 as B
import Data.ByteString.Base16
import Data.List
getSystemLibDir :: IO (Maybe FilePath)
getSystemLibDir = do
res <- readProcess "ghc" ["--print-libdir"] []
return $ case res of
"" -> Nothing
dirn -> Just (init dirn)
withGHC :: FilePath
-> Ghc a
-> IO a
withGHC file body = ghandle ignore $ withGHC' body
where
ignore :: SomeException -> IO a
ignore e = do
hPutStr stderr $ file ++ ":0:0:Error:"
hPrint stderr e
exitSuccess
withGHC' :: Ghc a -> IO a
withGHC' body = do
mlibdir <- getSystemLibDir
G.runGhc mlibdir body
withGhcT :: (Exception.ExceptionMonad m, G.MonadIO m, Monad m) => GhcT m a -> m a
withGhcT body = do
mlibdir <- G.liftIO $ getSystemLibDir
G.runGhcT mlibdir body
data Build = CabalPkg | SingleFile deriving Eq
initializeFlagsWithCradle ::
(GhcMonad m)
=> FilePath
-> Cradle
-> m ()
initializeFlagsWithCradle = initializeFlagsWithCradleWithMessage (Just G.batchMsg)
initializeFlagsWithCradleWithMessage ::
(GhcMonad m)
=> Maybe G.Messager
-> FilePath
-> Cradle
-> m ()
initializeFlagsWithCradleWithMessage msg fp cradle = do
(ex, err, ghcOpts) <- liftIO $ getOptions (cradleOptsProg cradle) fp
G.pprTrace "res" (G.text (show (ex, err, ghcOpts, fp))) (return ())
case ex of
ExitFailure _ -> throwCradleError err
_ -> return ()
let compOpts = CompilerOptions ghcOpts
liftIO $ hPrint stderr ghcOpts
initSessionWithMessage msg compOpts
data CradleError = CradleError String deriving (Show)
instance Exception CradleError where
throwCradleError :: GhcMonad m => String -> m ()
throwCradleError = liftIO . throwIO . CradleError
cacheDir :: String
cacheDir = "haskell-ide-engine"
clearInterfaceCache :: FilePath -> IO ()
clearInterfaceCache fp = do
cd <- getCacheDir fp
res <- doesPathExist cd
when res (removeDirectoryRecursive cd)
getCacheDir :: FilePath -> IO FilePath
getCacheDir fp = getXdgDirectory XdgCache (cacheDir ++ "/" ++ fp)
initSessionWithMessage :: (GhcMonad m)
=> Maybe G.Messager
-> CompilerOptions
-> m ()
initSessionWithMessage msg CompilerOptions {..} = do
df <- G.getSessionDynFlags
traceShowM (length ghcOptions)
let opts_hash = B.unpack $ encode $ H.finalize $ H.updates H.init (map B.pack ghcOptions)
fp <- liftIO $ getCacheDir opts_hash
liftIO $ clearInterfaceCache opts_hash
(df', targets) <- addCmdOpts ghcOptions df
void $ G.setSessionDynFlags
(disableOptimisation
$ setIgnoreInterfacePragmas
$ resetPackageDb
$ writeInterfaceFiles (Just fp)
$ setVerbosity 0
$ setLinkerOptions df'
)
G.setLogAction (\_df _wr _s _ss _pp _m -> return ())
#if __GLASGOW_HASKELL__ < 806
(\_df -> return ())
#endif
G.setTargets targets
mod_graph <- G.depanal [] True
void $ G.load' LoadAllTargets msg mod_graph
setLinkerOptions :: DynFlags -> DynFlags
setLinkerOptions df = df {
ghcLink = LinkInMemory
, hscTarget = HscNothing
, ghcMode = CompManager
}
resetPackageDb :: DynFlags -> DynFlags
resetPackageDb df = df { pkgDatabase = Nothing }
setIgnoreInterfacePragmas :: DynFlags -> DynFlags
setIgnoreInterfacePragmas df = gopt_set df Opt_IgnoreInterfacePragmas
setVerbosity :: Int -> DynFlags -> DynFlags
setVerbosity n df = df { verbosity = n }
writeInterfaceFiles :: Maybe FilePath -> DynFlags -> DynFlags
writeInterfaceFiles Nothing df = df
writeInterfaceFiles (Just hi_dir) df = setHiDir hi_dir (gopt_set df Opt_WriteInterface)
setHiDir :: FilePath -> DynFlags -> DynFlags
setHiDir f d = d { hiDir = Just f}
addCmdOpts :: (GhcMonad m)
=> [String] -> DynFlags -> m (DynFlags, [G.Target])
addCmdOpts cmdOpts df1 = do
(df2, leftovers, warns) <- G.parseDynamicFlags df1 (map G.noLoc cmdOpts)
traceShowM (map G.unLoc leftovers, length warns)
let
normalise_hyp fp
| strt_dot_sl && "-" `isPrefixOf` nfp = cur_dir ++ nfp
| otherwise = nfp
where
#if defined(mingw32_HOST_OS)
strt_dot_sl = "./" `isPrefixOf` fp || ".\\" `isPrefixOf` fp
#else
strt_dot_sl = "./" `isPrefixOf` fp
#endif
cur_dir = '.' : [pathSeparator]
nfp = normalise fp
normal_fileish_paths = map (normalise_hyp . G.unLoc) leftovers
let
(srcs, objs) = partition_args normal_fileish_paths [] []
df3 = df2 { ldInputs = map (FileOption "") objs ++ ldInputs df2 }
ts <- mapM (uncurry G.guessTarget) srcs
return (df3, ts)
getDynamicFlags :: IO DynFlags
getDynamicFlags = do
mlibdir <- getSystemLibDir
G.runGhc mlibdir G.getSessionDynFlags
withDynFlags ::
(GhcMonad m)
=> (DynFlags -> DynFlags) -> m a -> m 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
withCmdFlags ::
(GhcMonad m)
=> [String] -> m a -> m a
withCmdFlags flags body = G.gbracket setup teardown (\_ -> body)
where
setup = do
(dflag, _) <- G.getSessionDynFlags >>= addCmdOpts flags
void $ G.setSessionDynFlags dflag
return dflag
teardown = void . G.setSessionDynFlags
partition_args :: [String] -> [(String, Maybe G.Phase)] -> [String]
-> ([(String, Maybe G.Phase)], [String])
partition_args [] srcs objs = (reverse srcs, reverse objs)
partition_args ("-x":suff:args) srcs objs
| "none" <- suff = partition_args args srcs objs
| G.StopLn <- phase = partition_args args srcs (slurp ++ objs)
| otherwise = partition_args rest (these_srcs ++ srcs) objs
where phase = G.startPhase suff
(slurp,rest) = break (== "-x") args
these_srcs = zip slurp (repeat (Just phase))
partition_args (arg:args) srcs objs
| looks_like_an_input arg = partition_args args ((arg,Nothing):srcs) objs
| otherwise = partition_args args srcs (arg:objs)
looks_like_an_input :: String -> Bool
looks_like_an_input m = G.isSourceFilename m
|| G.looksLikeModuleName m
|| "-" `isPrefixOf` m
|| not (hasExtension m)
setDeferTypeErrors :: DynFlags -> DynFlags
setDeferTypeErrors
= foldDFlags (flip wopt_set) [Opt_WarnTypedHoles, Opt_WarnDeferredTypeErrors, Opt_WarnDeferredOutOfScopeVariables]
. foldDFlags setGeneralFlag' [Opt_DeferTypedHoles, Opt_DeferTypeErrors, Opt_DeferOutOfScopeVariables]
foldDFlags :: (a -> DynFlags -> DynFlags) -> [a] -> DynFlags -> DynFlags
foldDFlags f xs x = foldr f x xs
setNoWarningFlags :: DynFlags -> DynFlags
setNoWarningFlags df = df { warningFlags = Gap.emptyWarnFlags}
setAllWarningFlags :: DynFlags -> DynFlags
setAllWarningFlags df = df { warningFlags = allWarningFlags }
disableOptimisation :: DynFlags -> DynFlags
disableOptimisation df = updOptLevel 0 df
{-# NOINLINE allWarningFlags #-}
allWarningFlags :: Gap.WarnFlags
allWarningFlags = unsafePerformIO $ do
mlibdir <- getSystemLibDir
G.runGhcT mlibdir $ do
df <- G.getSessionDynFlags
(df', _) <- addCmdOpts ["-Wall"] df
return $ G.warningFlags df'