{-# LANGUAGE OverloadedLists #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
module Development.IDE.Core.FileExists
( fileExistsRules
, modifyFileExists
, getFileExists
)
where
import Control.Concurrent.Extra
import Control.Exception
import Control.Monad.Extra
import qualified Data.Aeson as A
import Data.Binary
import qualified Data.ByteString as BS
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HashMap
import Data.Maybe
import qualified Data.Text as T
import Development.IDE.Core.FileStore
import Development.IDE.Core.IdeConfiguration
import Development.IDE.Core.Shake
import Development.IDE.Types.Location
import Development.IDE.Types.Logger
import Development.Shake
import Development.Shake.Classes
import GHC.Generics
import Language.Haskell.LSP.Messages
import Language.Haskell.LSP.Types
import Language.Haskell.LSP.Types.Capabilities
import qualified System.Directory as Dir
type FileExistsMap = (HashMap NormalizedFilePath Bool)
newtype FileExistsMapVar = FileExistsMapVar (Var FileExistsMap)
instance IsIdeGlobal FileExistsMapVar
getFileExistsMapUntracked :: Action FileExistsMap
getFileExistsMapUntracked = do
FileExistsMapVar v <- getIdeGlobalAction
liftIO $ readVar v
modifyFileExistsAction :: (FileExistsMap -> IO FileExistsMap) -> Action ()
modifyFileExistsAction f = do
FileExistsMapVar var <- getIdeGlobalAction
liftIO $ modifyVar_ var f
modifyFileExists :: IdeState -> [(NormalizedFilePath, Bool)] -> IO ()
modifyFileExists state changes = do
FileExistsMapVar var <- getIdeGlobalState state
changesMap <- evaluate $ HashMap.fromList changes
mask $ \_ -> do
modifyVar_ var $ evaluate . HashMap.union changesMap
mapM_ (deleteValue state GetFileExists . fst) changes
type instance RuleResult GetFileExists = Bool
data GetFileExists = GetFileExists
deriving (Eq, Show, Typeable, Generic)
instance NFData GetFileExists
instance Hashable GetFileExists
instance Binary GetFileExists
getFileExists :: NormalizedFilePath -> Action Bool
getFileExists fp = use_ GetFileExists fp
fileExistsRules :: IO LspId -> ClientCapabilities -> VFSHandle -> Rules ()
fileExistsRules getLspId ClientCapabilities{_workspace} vfs = do
addIdeGlobal . FileExistsMapVar =<< liftIO (newVar [])
case () of
_ | Just WorkspaceClientCapabilities{_didChangeWatchedFiles} <- _workspace
, Just DidChangeWatchedFilesClientCapabilities{_dynamicRegistration} <- _didChangeWatchedFiles
, Just True <- _dynamicRegistration
-> fileExistsRulesFast getLspId vfs
| otherwise -> do
logger <- logger <$> getShakeExtrasRules
liftIO $ logDebug logger "Warning: Client does not support watched files. Falling back to OS polling"
fileExistsRulesSlow vfs
fileExistsRulesFast :: IO LspId -> VFSHandle -> Rules ()
fileExistsRulesFast getLspId vfs =
defineEarlyCutoff $ \GetFileExists file -> do
isWf <- isWorkspaceFile file
if isWf
then fileExistsFast getLspId vfs file
else fileExistsSlow vfs file
fileExistsFast :: IO LspId -> VFSHandle -> NormalizedFilePath -> Action (Maybe BS.ByteString, ([a], Maybe Bool))
fileExistsFast getLspId vfs file = do
fileExistsMap <- getFileExistsMapUntracked
let mbFilesWatched = HashMap.lookup file fileExistsMap
case mbFilesWatched of
Just fv -> pure (summarizeExists fv, ([], Just fv))
Nothing -> do
exist <- liftIO $ getFileExistsVFS vfs file
ShakeExtras { eventer } <- getShakeExtras
modifyFileExistsAction $ \x -> do
case HashMap.alterF (,Just exist) file x of
(Nothing, x') -> do
addListener eventer file
return x'
(Just _, _) ->
return x
pure (summarizeExists exist, ([], Just exist))
where
addListener eventer fp = do
reqId <- getLspId
let
req = RequestMessage "2.0" reqId ClientRegisterCapability regParams
fpAsId = T.pack $ fromNormalizedFilePath fp
regParams = RegistrationParams (List [registration])
registration = Registration fpAsId
WorkspaceDidChangeWatchedFiles
(Just (A.toJSON regOptions))
regOptions =
DidChangeWatchedFilesRegistrationOptions { _watchers = List [watcher] }
watchKind = WatchKind { _watchCreate = True, _watchChange = False, _watchDelete = True}
watcher = FileSystemWatcher { _globPattern = fromNormalizedFilePath fp
, _kind = Just watchKind
}
eventer $ ReqRegisterCapability req
summarizeExists :: Bool -> Maybe BS.ByteString
summarizeExists x = Just $ if x then BS.singleton 1 else BS.empty
fileExistsRulesSlow:: VFSHandle -> Rules ()
fileExistsRulesSlow vfs =
defineEarlyCutoff $ \GetFileExists file -> fileExistsSlow vfs file
fileExistsSlow :: VFSHandle -> NormalizedFilePath -> Action (Maybe BS.ByteString, ([a], Maybe Bool))
fileExistsSlow vfs file = do
alwaysRerun
exist <- liftIO $ getFileExistsVFS vfs file
pure (summarizeExists exist, ([], Just exist))
getFileExistsVFS :: VFSHandle -> NormalizedFilePath -> IO Bool
getFileExistsVFS vfs file = do
handle (\(_ :: IOException) -> return False) $
(isJust <$> getVirtualFile vfs (filePathToUri' file)) ||^
Dir.doesFileExist (fromNormalizedFilePath file)