{-# LANGUAGE RecordWildCards, CPP #-}
module HIE.Bios.Environment (initSession, getSystemLibDir, addCmdOpts, getDynamicFlags) where
import CoreMonad (liftIO)
import GHC (DynFlags(..), GhcLink(..), HscTarget(..), GhcMonad)
import qualified GHC as G
import qualified DriverPhases as G
import qualified Util as G
import DynFlags
import Control.Monad (void, when)
import System.Process (readProcess)
import System.Directory
import System.FilePath
import qualified Crypto.Hash.SHA1 as H
import qualified Data.ByteString.Char8 as B
import Data.ByteString.Base16
import Data.List
import HIE.Bios.Types
initSession :: (GhcMonad m)
=> CompilerOptions
-> m [G.Target]
initSession CompilerOptions {..} = do
df <- G.getSessionDynFlags
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
return targets
getSystemLibDir :: IO (Maybe FilePath)
getSystemLibDir = do
res <- readProcess "ghc" ["--print-libdir"] []
return $ case res of
"" -> Nothing
dirn -> Just (init dirn)
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)
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)
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
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)
disableOptimisation :: DynFlags -> DynFlags
disableOptimisation df = updOptLevel 0 df