module IdeSession.Update.ExecuteSessionUpdate (runSessionUpdate) where
import Prelude hiding (mod, span)
import Control.Applicative (Applicative, (<$>))
import Control.Monad (when, void, forM, liftM, filterM)
import Control.Monad.IO.Class (MonadIO(..))
import Control.Monad.Reader (MonadReader(..), ReaderT, runReaderT, asks)
import Control.Monad.State (MonadState(..))
import Data.Accessor (Accessor, (.>))
import Data.Digest.Pure.MD5 (MD5Digest)
import Data.Foldable (forM_)
import Data.Maybe (isJust, catMaybes, fromMaybe)
import Data.Monoid (Monoid(..))
import System.Exit (ExitCode(..))
import System.FilePath (makeRelative, (</>), takeExtension, replaceExtension, dropFileName)
import System.FilePath.Find (find, always, extension, (&&?), (||?), fileType, (==?), FileType (RegularFile))
import System.Posix.Files (setFileTimes, getFileStatus, modificationTime)
import qualified Control.Exception as Ex
import qualified Data.Accessor.Monad.MTL.State as Acc
import qualified Data.ByteString.Char8 as BSS
import qualified Data.ByteString.Lazy.Char8 as BSL
import qualified Data.Text as Text
import qualified System.Directory as Dir
import IdeSession.Cabal
import IdeSession.Config
import IdeSession.ExeCabalClient (invokeExeCabal)
import IdeSession.GHC.API
import IdeSession.RPC.API (ExternalException)
import IdeSession.State
import IdeSession.Strict.Container
import IdeSession.Strict.IORef (StrictIORef)
import IdeSession.Types.Private hiding (RunResult(..))
import IdeSession.Types.Progress
import IdeSession.Types.Public (RunBufferMode(..), Targets(..), UpdateStatus(..))
import IdeSession.Update.IdeSessionUpdate
import IdeSession.Util
import IdeSession.Util.Logger
import qualified IdeSession.GHC.Client as GHC
import qualified IdeSession.Strict.IORef as IORef
import qualified IdeSession.Strict.IntMap as IntMap
import qualified IdeSession.Strict.List as List
import qualified IdeSession.Strict.Map as Map
import qualified IdeSession.Strict.Maybe as Maybe
import qualified IdeSession.Strict.Trie as Trie
data IdeSessionUpdateEnv = IdeSessionUpdateEnv {
ideUpdateStaticInfo :: IdeStaticInfo
, ideUpdateStatus :: UpdateStatus -> IO ()
, ideUpdateStateRef :: StrictIORef IdeIdleState
, ideUpdateExceptionRef :: StrictIORef (Maybe ExternalException)
, ideUpdateCallbacks :: IdeCallbacks
}
newtype ExecuteSessionUpdate a = ExecuteSessionUpdate {
unwrapUpdate :: ReaderT IdeSessionUpdateEnv IO a
}
deriving ( Functor
, Applicative
, Monad
, MonadReader IdeSessionUpdateEnv
, MonadIO
)
instance MonadState IdeIdleState ExecuteSessionUpdate where
get = ExecuteSessionUpdate $ do
stRef <- ideUpdateStateRef <$> ask
liftIO $ IORef.readIORef stRef
put s = ExecuteSessionUpdate $ do
stRef <- ideUpdateStateRef <$> ask
liftIO $ IORef.writeIORef stRef s
tryIO :: Dummy a => IO a -> ExecuteSessionUpdate a
tryIO act = ExecuteSessionUpdate $ do
exRef <- ideUpdateExceptionRef <$> ask
mPreviousException <- liftIO $ IORef.readIORef exRef
case mPreviousException of
Just _ ->
return dummy
Nothing -> do
mNewException <- liftIO $ Ex.try $ act
case mNewException of
Left ex -> do liftIO $ IORef.writeIORef exRef (Just ex)
return dummy
Right a -> return a
exceptionFree :: IO a -> ExecuteSessionUpdate a
exceptionFree = ExecuteSessionUpdate . liftIO
runSessionUpdate :: Bool
-> IdeSessionUpdate
-> IdeStaticInfo
-> (UpdateStatus -> IO ())
-> IdeCallbacks
-> IdeIdleState
-> IO (IdeIdleState, Maybe ExternalException)
runSessionUpdate justRestarted update staticInfo callback ideCallbacks ideIdleState = do
stRef <- IORef.newIORef ideIdleState
exRef <- IORef.newIORef Nothing
runReaderT (unwrapUpdate $ executeSessionUpdate justRestarted update')
IdeSessionUpdateEnv {
ideUpdateStaticInfo = staticInfo
, ideUpdateStatus = liftIO . callback
, ideUpdateStateRef = stRef
, ideUpdateExceptionRef = exRef
, ideUpdateCallbacks = ideCallbacks
}
ideIdleState' <- IORef.readIORef stRef
mException <- IORef.readIORef exRef
return (ideIdleState', mException)
where
update' = reflectSessionState ideIdleState update
executeSessionUpdate :: Bool -> IdeSessionUpdate -> ExecuteSessionUpdate ()
executeSessionUpdate justRestarted IdeSessionUpdate{..} = do
executeUpdateBufferModes ideUpdateStdoutMode ideUpdateStderrMode
executeUpdateEnv ideUpdateEnv
executeUpdateArgs ideUpdateArgs
filesChanged <- executeUpdateFiles ideUpdateFileCmds
enabledCodeGen <- executeUpdateCodeGen ideUpdateCodeGen
optionWarnings <- executeUpdateGhcOpts ideUpdateGhcOpts
removeObsoleteObjectFiles
let ghcOptionsChanged :: Bool
ghcOptionsChanged = isJust optionWarnings
(numActions, cErrors) <- updateObjectFiles ghcOptionsChanged
let cFilesChanged :: Bool
cFilesChanged = numActions > 0
IdeStaticInfo{ideConfig} <- asks ideUpdateStaticInfo
let hasLocalWorkingDir = isJust (configLocalWorkingDir ideConfig)
let needsRecompile =
filesChanged
||
enabledCodeGen
||
ghcOptionsChanged
|| cFilesChanged
|| justRestarted
|| hasLocalWorkingDir
logFunc <- asks (ideCallbacksLogFunc . ideUpdateCallbacks)
$logDebug $ if needsRecompile
then "Recompile required, starting..."
else "Recompile not required, so skipping"
when needsRecompile $ local (incrementNumSteps numActions) $ do
GhcCompileResult{..} <- rpcCompile
oldComputed <- Acc.get ideComputed
srcDir <- asks $ ideSourceDir . ideUpdateStaticInfo
let applyDiff :: Strict (Map ModuleName) (Diff v)
-> (Computed -> Strict (Map ModuleName) v)
-> Strict (Map ModuleName) v
applyDiff diff f = applyMapDiff diff $ Maybe.maybe Map.empty f oldComputed
let diffSpan = Map.map (fmap mkIdMap) ghcCompileSpanInfo
diffTypes = Map.map (fmap mkExpMap) ghcCompileExpTypes
diffAuto = Map.map (fmap (constructAuto ghcCompileCache)) ghcCompileAuto
Acc.set ideComputed $ Maybe.just Computed {
computedErrors = force cErrors
List.++ ghcCompileErrors
List.++ force (fromMaybe [] optionWarnings)
, computedLoadedModules = ghcCompileLoaded
, computedFileMap = mkFileMapRelative srcDir ghcCompileFileMap
, computedImports = ghcCompileImports `applyDiff` computedImports
, computedAutoMap = diffAuto `applyDiff` computedAutoMap
, computedSpanInfo = diffSpan `applyDiff` computedSpanInfo
, computedExpTypes = diffTypes `applyDiff` computedExpTypes
, computedUseSites = ghcCompileUseSites `applyDiff` computedUseSites
, computedPkgDeps = ghcCompilePkgDeps `applyDiff` computedPkgDeps
, computedCache = mkCacheRelative srcDir ghcCompileCache
}
when ideUpdateDocs $ executeBuildDoc
forM_ ideUpdateExes $ uncurry executeBuildExe
forM_ ideUpdateLicenses $ executeBuildLicenses
where
incrementNumSteps :: Int -> IdeSessionUpdateEnv -> IdeSessionUpdateEnv
incrementNumSteps count IdeSessionUpdateEnv{..} = IdeSessionUpdateEnv{
ideUpdateStatus = \s -> ideUpdateStatus $ case s of
UpdateStatusProgress p -> UpdateStatusProgress p {
progressStep = progressStep p + count
, progressNumSteps = progressNumSteps p + count
}
_ -> s
, ..
}
mkCacheRelative :: FilePath -> ExplicitSharingCache -> ExplicitSharingCache
mkCacheRelative srcDir ExplicitSharingCache{..} =
ExplicitSharingCache {
filePathCache = IntMap.map aux filePathCache
, idPropCache = idPropCache
}
where
aux :: BSS.ByteString -> BSS.ByteString
aux = BSS.pack . makeRelative srcDir . BSS.unpack
mkFileMapRelative :: FilePath -> Strict (Map FilePath) ModuleId -> Strict (Map FilePath) ModuleId
mkFileMapRelative srcDir = Map.mapKeys (makeRelative srcDir)
constructAuto :: ExplicitSharingCache -> Strict [] IdInfo
-> Strict Trie (Strict [] IdInfo)
constructAuto cache lk =
Trie.fromListWith (List.++) $ map aux (toLazyList lk)
where
aux :: IdInfo -> (BSS.ByteString, Strict [] IdInfo)
aux idInfo@IdInfo{idProp = k} =
let idProp = IntMap.findWithDefault
(error "constructAuto: could not resolve idPropPtr")
(idPropPtr k)
(idPropCache cache)
in ( BSS.pack . Text.unpack . idName $ idProp
, List.singleton idInfo
)
reflectSessionState :: IdeIdleState -> IdeSessionUpdate -> IdeSessionUpdate
reflectSessionState IdeIdleState{..} update = mconcat [
when' (ideUpdateDeleteFiles update) $ mconcat $
[updateSourceFileDelete (fst m) | m <- _managedSource]
++ [updateDataFileDelete (fst m) | m <- _managedData]
, update {
ideUpdateDeleteFiles = False
}
]
where
when' :: forall m. Monoid m => Bool -> m -> m
when' True a = a
when' False _ = mempty
ManagedFilesInternal{..} = _ideManagedFiles
executeUpdateFiles :: [FileCmd] -> ExecuteSessionUpdate Bool
executeUpdateFiles fileCmds = or <$> forM fileCmds executeFileCmd
executeUpdateCodeGen :: Maybe Bool -> ExecuteSessionUpdate Bool
executeUpdateCodeGen = maybeSet ideGenerateCode
executeUpdateBufferModes :: Maybe RunBufferMode -> Maybe RunBufferMode -> ExecuteSessionUpdate ()
executeUpdateBufferModes stdoutMode stderrMode = do
void $ maybeSet ideStdoutBufferMode stdoutMode
void $ maybeSet ideStderrBufferMode stderrMode
executeUpdateEnv :: Maybe [(String, Maybe String)] -> ExecuteSessionUpdate ()
executeUpdateEnv env = do
changed <- maybeSet ideEnv env
when changed rpcSetEnv
executeUpdateArgs :: Maybe [String] -> ExecuteSessionUpdate ()
executeUpdateArgs args = do
changed <- maybeSet ideArgs args
when changed rpcSetArgs
executeUpdateGhcOpts :: Maybe [String] -> ExecuteSessionUpdate (Maybe [SourceError])
executeUpdateGhcOpts opts = do
changed <- maybeSet ideGhcOpts opts
if changed then Just <$> rpcSetGhcOpts
else return Nothing
updateObjectFiles :: Bool -> ExecuteSessionUpdate (Int, [SourceError])
updateObjectFiles ghcOptionsChanged = do
outdated <- outdatedObjectFiles ghcOptionsChanged
if not (null outdated)
then do
rpcUnloadObjectFiles =<< Acc.get ideObjectFiles
cErrors <- recompileCFiles outdated
objErrors <- rpcLoadObjectFiles
markAsUpdated $ dependenciesOf outdated
return (length outdated, cErrors ++ objErrors)
else
return (0, [])
where
dependenciesOf :: [FilePath] -> FilePath -> Bool
dependenciesOf _recompiled src = takeExtension src == ".hs"
removeObsoleteObjectFiles :: ExecuteSessionUpdate ()
removeObsoleteObjectFiles = do
objectFiles <- Acc.get ideObjectFiles
obsolete <- filterM isObsolete objectFiles
forM_ obsolete $ \(cFile, (objFile, _timestamp)) -> do
exceptionFree $ Dir.removeFile objFile
Acc.set (ideObjectFiles .> lookup' cFile) Nothing
rpcUnloadObjectFiles obsolete
where
isObsolete :: (FilePath, (FilePath, LogicalTimestamp)) -> ExecuteSessionUpdate Bool
isObsolete (cFile, _) = do
cInfo <- Acc.get (ideManagedFiles .> managedSource .> lookup' cFile)
return $ not (isJust cInfo)
recompileCFiles :: [FilePath] -> ExecuteSessionUpdate [SourceError]
recompileCFiles cFiles = do
updateStatus <- asks ideUpdateStatus
sessionDir <- asks $ ideSessionDir . ideUpdateStaticInfo
ideStaticInfo <- asks ideUpdateStaticInfo
let srcDir, objDir :: FilePath
srcDir = ideSourceDir ideStaticInfo
objDir = ideSessionObjDir sessionDir
errorss <- forM (zip cFiles [1..]) $ \(relC, i) -> do
let relObj = replaceExtension relC ".o"
absC = srcDir </> relC
absObj = objDir </> relObj
let msg = "Compiling " ++ relC
exceptionFree $ updateStatus $ UpdateStatusProgress $ Progress {
progressStep = i
, progressNumSteps = length cFiles
, progressParsedMsg = Just (Text.pack msg)
, progressOrigMsg = Just (Text.pack msg)
}
exceptionFree $ Dir.createDirectoryIfMissing True (dropFileName absObj)
errors <- runGcc absC absObj objDir
if null errors
then do
ts' <- updateFileTimes absObj
Acc.set (ideObjectFiles .> lookup' relC) (Just (absObj, ts'))
else do
Acc.set (ideObjectFiles .> lookup' relC) Nothing
return errors
return $ concat errorss
outdatedObjectFiles :: Bool -> ExecuteSessionUpdate [FilePath]
outdatedObjectFiles ghcOptionsChanged = do
IdeStaticInfo{..} <- asks ideUpdateStaticInfo
managedFiles <- Acc.get (ideManagedFiles .> managedSource)
let cFiles :: [(FilePath, LogicalTimestamp)]
cFiles = filter ((`elem` cExtensions) . takeExtension . fst)
$ map (\(fp, (_, ts)) -> (fp, ts))
$ managedFiles
if ghcOptionsChanged
then return $ map fst cFiles
else liftM catMaybes $ do
forM cFiles $ \(c_fp, c_ts) -> do
mObjFile <- Acc.get (ideObjectFiles .> lookup' c_fp)
return $ case mObjFile of
Nothing -> Just c_fp
Just (_, obj_ts) | obj_ts < c_ts -> Just c_fp
_ -> Nothing
runGcc :: FilePath -> FilePath -> FilePath -> ExecuteSessionUpdate [SourceError]
runGcc absC absObj pref = do
ideStaticInfo@IdeStaticInfo{..} <- asks ideUpdateStaticInfo
updateStatus <- asks ideUpdateStatus
ideCallbacks <- asks ideUpdateCallbacks
relIncl <- Acc.get ideRelativeIncludes
ghcOpts <- Acc.get ideGhcOpts
exceptionFree $ do
let SessionConfig{..} = ideConfig
stdoutLog = ideDistDir </> "ide-backend-cc.stdout"
stderrLog = ideDistDir </> "ide-backend-cc.stderr"
includeDirs = map (ideSourceDir ideStaticInfo </>) relIncl
runCcArgs = RunCcArgs{ rcPackageDBStack = configPackageDBStack
, rcExtraPathDirs = configExtraPathDirs
, rcDistDir = ideDistDir
, rcStdoutLog = stdoutLog
, rcStderrLog = stderrLog
, rcAbsC = absC
, rcAbsObj = absObj
, rcPref = pref
, rcIncludeDirs = includeDirs
, rcOptions = ghcOpts
}
exitCode <- invokeExeCabal ideStaticInfo ideCallbacks (ReqExeCc runCcArgs) updateStatus
stdout <- readFile stdoutLog
stderr <- readFile stderrLog
case exitCode of
ExitSuccess -> return []
ExitFailure _ -> return (parseErrorMsgs stdout stderr)
where
parseErrorMsgs :: String -> String -> [SourceError]
parseErrorMsgs stdout stderr = [SourceError
{ errorKind = KindError
, errorSpan = TextSpan (Text.pack "<gcc error>")
, errorMsg = Text.pack (stdout ++ stderr)
}]
markAsUpdated :: (FilePath -> Bool) -> ExecuteSessionUpdate ()
markAsUpdated shouldMark = do
ideStaticInfo@IdeStaticInfo{..} <- asks ideUpdateStaticInfo
sources <- Acc.get (ideManagedFiles .> managedSource)
sources' <- forM sources $ \(path, (digest, oldTS)) ->
if shouldMark path
then do newTS <- updateFileTimes (ideSourceDir ideStaticInfo)
return (path, (digest, newTS))
else return (path, (digest, oldTS))
Acc.set (ideManagedFiles .> managedSource) sources'
executeFileCmd :: FileCmd -> ExecuteSessionUpdate Bool
executeFileCmd cmd = do
ideStaticInfo@IdeStaticInfo{..} <- asks ideUpdateStaticInfo
let remotePath :: FilePath
remotePath = fileInfoRemoteDir info ideStaticInfo </> fileInfoRemoteFile info
case configLocalWorkingDir ideConfig of
Just _ -> fail "We can't use update functions with configLocalWorkingDir."
Nothing -> case cmd of
FileWrite _ bs -> do
old <- Acc.get cachedInfo
newHash <- exceptionFree $ writeFileAtomic remotePath bs
case old of
Just (oldHash, oldTS) | oldHash == newHash -> do
exceptionFree $ setFileTimes remotePath oldTS oldTS
return False
_ -> do
newTS <- updateFileTimes remotePath
Acc.set cachedInfo (Just (newHash, newTS))
return True
FileCopy _ localFile -> do
bs <- exceptionFree $ BSL.readFile localFile
executeFileCmd (FileWrite info bs)
FileDelete _ -> do
exceptionFree $ ignoreDoesNotExist $ Dir.removeFile remotePath
Acc.set cachedInfo Nothing
return True
where
info :: FileInfo
info = case cmd of FileWrite i _ -> i
FileCopy i _ -> i
FileDelete i -> i
cachedInfo :: Accessor IdeIdleState (Maybe (MD5Digest, LogicalTimestamp))
cachedInfo = ideManagedFiles .> fileInfoAccessor info .> lookup' (fileInfoRemoteFile info)
executeBuildExe :: [String] -> [(ModuleName, FilePath)] -> ExecuteSessionUpdate ()
executeBuildExe extraOpts ms = do
ideStaticInfo@IdeStaticInfo{..} <- asks ideUpdateStaticInfo
let SessionConfig{..} = ideConfig
updateStatus <- asks ideUpdateStatus
ideCallbacks <- asks ideUpdateCallbacks
mcomputed <- Acc.get ideComputed
ghcOpts <- Acc.get ideGhcOpts
relativeIncludes <- Acc.get ideRelativeIncludes
when (not configGenerateModInfo) $
fail "Features using cabal API require configGenerateModInfo, currently (#86)."
exceptionFree $ Dir.createDirectoryIfMissing False $ ideDistDir </> "build"
let beStdoutLog = ideDistDir </> "build/ide-backend-exe.stdout"
beStderrLog = ideDistDir </> "build/ide-backend-exe.stderr"
errors = case toLazyMaybe mcomputed of
Nothing ->
error "This session state does not admit artifact generation."
Just Computed{computedErrors} -> toLazyList computedErrors
exitCode <-
if any (== KindError) $ map errorKind errors then do
exceptionFree $ do
writeFile beStderrLog
"Source or other errors encountered. Not attempting to build executables."
return $ ExitFailure 1
else do
let ghcOpts' = "-rtsopts=some" : ghcOpts ++ extraOpts
exceptionFree $ do
(loadedMs, pkgs) <- buildDeps mcomputed
libDeps <- externalDeps pkgs
let beArgs =
BuildExeArgs{ bePackageDBStack = configPackageDBStack
, beExtraPathDirs = configExtraPathDirs
, beSourcesDir = ideSourceDir ideStaticInfo
, beDistDir = ideDistDir
, beRelativeIncludes = relativeIncludes
, beGhcOpts = ghcOpts'
, beLibDeps = libDeps
, beLoadedMs = loadedMs
, beStdoutLog
, beStderrLog
}
invokeExeCabal ideStaticInfo ideCallbacks (ReqExeBuild beArgs ms) updateStatus
newTS <- nextLogicalTimestamp
exceptionFree $ do
objectPaths <- find always
(fileType ==? RegularFile
&&? (extension ==? ".o"
||? extension ==? ".hi"
||? extension ==? ".a"))
(ideDistDir </> "build")
forM_ objectPaths $ \path -> do
fileStatus <- getFileStatus path
when (modificationTime fileStatus > newTS) $
setFileTimes path newTS newTS
Acc.set ideBuildExeStatus (Just exitCode)
executeBuildDoc :: ExecuteSessionUpdate ()
executeBuildDoc = do
ideStaticInfo@IdeStaticInfo{..} <- asks ideUpdateStaticInfo
let SessionConfig{..} = ideConfig
let srcDir = ideSourceDir ideStaticInfo
updateStatus <- asks ideUpdateStatus
ideCallbacks <- asks ideUpdateCallbacks
mcomputed <- Acc.get ideComputed
ghcOpts <- Acc.get ideGhcOpts
relativeIncludes <- Acc.get ideRelativeIncludes
when (not configGenerateModInfo) $
fail "Features using cabal API require configGenerateModInfo, currently (#86)."
exceptionFree $ Dir.createDirectoryIfMissing False $ ideDistDir </> "doc"
let beStdoutLog = ideDistDir </> "doc/ide-backend-doc.stdout"
beStderrLog = ideDistDir </> "doc/ide-backend-doc.stderr"
errors = case toLazyMaybe mcomputed of
Nothing ->
error "This session state does not admit artifact generation."
Just Computed{computedErrors} -> toLazyList computedErrors
isDummyError err =
errorKind err == KindError
&& errorMsg err == Text.pack "GHC server died (dummy error)"
exitCode <-
if any isDummyError errors then do
exceptionFree $ do
writeFile beStderrLog
"GHC server died. Not attempting to build documentation."
return $ ExitFailure 1
else exceptionFree $ do
(loadedMs, pkgs) <- buildDeps mcomputed
libDeps <- externalDeps pkgs
let beArgs =
BuildExeArgs{ bePackageDBStack = configPackageDBStack
, beExtraPathDirs = configExtraPathDirs
, beSourcesDir =
makeRelative ideSessionDir srcDir
, beDistDir =
makeRelative ideSessionDir ideDistDir
, beRelativeIncludes = relativeIncludes
, beGhcOpts = ghcOpts
, beLibDeps = libDeps
, beLoadedMs = loadedMs
, beStdoutLog
, beStderrLog
}
invokeExeCabal ideStaticInfo ideCallbacks (ReqExeDoc beArgs) updateStatus
Acc.set ideBuildDocStatus (Just exitCode)
executeBuildLicenses :: FilePath -> ExecuteSessionUpdate ()
executeBuildLicenses cabalsDir = do
ideStaticInfo@IdeStaticInfo{..} <- asks ideUpdateStaticInfo
let SessionConfig{configGenerateModInfo} = ideConfig
updateStatus <- asks ideUpdateStatus
ideCallbacks <- asks ideUpdateCallbacks
mcomputed <- Acc.get ideComputed
when (not configGenerateModInfo) $
fail "Features using cabal API require configGenerateModInfo, currently (#86)."
let liStdoutLog = ideDistDir </> "licenses.stdout"
liStderrLog = ideDistDir </> "licenses.stderr"
errors = case toLazyMaybe mcomputed of
Nothing ->
error "This session state does not admit artifact generation."
Just Computed{computedErrors} -> toLazyList computedErrors
exitCode <-
if any (== KindError) $ map errorKind errors then do
exceptionFree $ do
writeFile liStderrLog
"Source or other errors encountered. Not attempting to build licenses."
return $ ExitFailure 1
else exceptionFree $ do
(_, pkgs) <- buildDeps mcomputed
let liArgs =
LicenseArgs{ liPackageDBStack = configPackageDBStack ideConfig
, liExtraPathDirs = configExtraPathDirs ideConfig
, liLicenseExc = configLicenseExc ideConfig
, liDistDir = ideDistDir
, liStdoutLog
, liStderrLog
, licenseFixed = configLicenseFixed ideConfig
, liCabalsDir = cabalsDir
, liPkgs = pkgs
}
invokeExeCabal ideStaticInfo ideCallbacks (ReqExeLic liArgs) updateStatus
Acc.set ideBuildLicensesStatus (Just exitCode)
updateFileTimes :: FilePath -> ExecuteSessionUpdate LogicalTimestamp
updateFileTimes path = do
ts <- nextLogicalTimestamp
exceptionFree $ setFileTimes path ts ts
return ts
nextLogicalTimestamp :: ExecuteSessionUpdate LogicalTimestamp
nextLogicalTimestamp = do
newTS <- Acc.get ideLogicalTimestamp
Acc.modify ideLogicalTimestamp (+ 1)
return newTS
rpcCompile :: ExecuteSessionUpdate GhcCompileResult
rpcCompile = do
IdeIdleState{..} <- get
updateStatus <- asks ideUpdateStatus
sourceDir <- asks $ ideSourceDir . ideUpdateStaticInfo
let targets = case _ideTargets of
TargetsInclude l -> TargetsInclude $ map (sourceDir </>) l
TargetsExclude l -> TargetsExclude $ map (sourceDir </>) l
tryIO $ GHC.rpcCompile _ideGhcServer _ideGenerateCode targets updateStatus
rpcSetEnv :: ExecuteSessionUpdate ()
rpcSetEnv = do
IdeIdleState{..} <- get
tryIO $ GHC.rpcSetEnv _ideGhcServer _ideEnv
rpcSetArgs :: ExecuteSessionUpdate ()
rpcSetArgs = do
IdeIdleState{..} <- get
tryIO $ GHC.rpcSetArgs _ideGhcServer _ideArgs
rpcSetGhcOpts :: ExecuteSessionUpdate [SourceError]
rpcSetGhcOpts = do
IdeIdleState{..} <- get
srcDir <- asks $ ideSourceDir . ideUpdateStaticInfo
let relOpts = relInclToOpts srcDir _ideRelativeIncludes
(leftover, warnings) <- tryIO $ GHC.rpcSetGhcOpts _ideGhcServer (_ideGhcOpts ++ relOpts)
return
[ SourceError {
errorKind = KindWarning
, errorSpan = TextSpan (Text.pack "No location information")
, errorMsg = Text.pack w
}
| w <- warnings ++ map unrecognized leftover
]
where
unrecognized :: String -> String
unrecognized str = "Unrecognized option " ++ show str
rpcUnloadObjectFiles :: [(FilePath, (FilePath, LogicalTimestamp))] -> ExecuteSessionUpdate ()
rpcUnloadObjectFiles objects = do
IdeIdleState{..} <- get
tryIO $ GHC.rpcUnload _ideGhcServer $ map (fst . snd) objects
rpcLoadObjectFiles :: ExecuteSessionUpdate [SourceError]
rpcLoadObjectFiles = do
IdeIdleState{..} <- get
didLoad <- tryIO $ GHC.rpcLoad _ideGhcServer $ map (fst . snd) _ideObjectFiles
case didLoad of
Just err ->
return [ SourceError {
errorKind = KindError
, errorSpan = TextSpan (Text.pack "No location information")
, errorMsg = Text.pack $ "Failure during object loading: " ++ err
}]
Nothing ->
return []
class Dummy a where
dummy :: a
instance Dummy () where
dummy = ()
instance Dummy [a] where
dummy = []
instance (Dummy a, Dummy b) => Dummy (a, b) where
dummy = (dummy, dummy)
instance Dummy (Maybe a) where
dummy = Nothing
instance Dummy (Strict [] a) where
dummy = List.nil
instance Dummy (Strict (Map k) a) where
dummy = Map.empty
instance Dummy (Strict IntMap a) where
dummy = IntMap.empty
instance Dummy ExplicitSharingCache where
dummy = ExplicitSharingCache {
filePathCache = dummy
, idPropCache = dummy
}
instance Dummy GhcCompileResult where
dummy = GhcCompileResult {
ghcCompileLoaded = dummy
, ghcCompileCache = dummy
, ghcCompileFileMap = dummy
, ghcCompileImports = dummy
, ghcCompileAuto = dummy
, ghcCompileSpanInfo = dummy
, ghcCompilePkgDeps = dummy
, ghcCompileExpTypes = dummy
, ghcCompileUseSites = dummy
, ghcCompileErrors = force [SourceError {
errorKind = KindError
, errorSpan = TextSpan (Text.pack "No location information")
, errorMsg = Text.pack "GHC server died (dummy error)"
}]
}
maybeSet :: (MonadState st m, Eq a) => Accessor st a -> Maybe a -> m Bool
maybeSet _ Nothing = return False
maybeSet acc (Just new) = do
old <- Acc.get acc
if old /= new then Acc.set acc new >> return True
else return False