{-# LANGUAGE OverloadedLists #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
module Development.IDE.Core.FileExists
( fileExistsRules
, modifyFileExists
, getFileExists
, watchedGlobs
, GetFileExists(..)
)
where
import Control.Concurrent.STM.Stats (atomically,
atomicallyNamed)
import Control.Exception
import Control.Monad.Extra
import Control.Monad.IO.Class
import qualified Data.ByteString as BS
import Data.List (partition)
import Data.Maybe
import Development.IDE.Core.FileStore
import Development.IDE.Core.IdeConfiguration
import Development.IDE.Core.RuleTypes
import Development.IDE.Core.Shake
import Development.IDE.Graph
import Development.IDE.Types.Location
import Development.IDE.Types.Options
import qualified Focus
import Ide.Plugin.Config (Config)
import Language.LSP.Server hiding (getVirtualFile)
import Language.LSP.Types
import qualified StmContainers.Map as STM
import qualified System.Directory as Dir
import qualified System.FilePath.Glob as Glob
type FileExistsMap = STM.Map NormalizedFilePath Bool
newtype FileExistsMapVar = FileExistsMapVar FileExistsMap
instance IsIdeGlobal FileExistsMapVar
getFileExistsMapUntracked :: Action FileExistsMap
getFileExistsMapUntracked :: Action FileExistsMap
getFileExistsMapUntracked = do
FileExistsMapVar FileExistsMap
v <- Action FileExistsMapVar
forall a. IsIdeGlobal a => Action a
getIdeGlobalAction
FileExistsMap -> Action FileExistsMap
forall (m :: * -> *) a. Monad m => a -> m a
return FileExistsMap
v
modifyFileExists :: IdeState -> [(NormalizedFilePath, FileChangeType)] -> IO ()
modifyFileExists :: IdeState -> [(NormalizedFilePath, FileChangeType)] -> IO ()
modifyFileExists IdeState
state [(NormalizedFilePath, FileChangeType)]
changes = do
FileExistsMapVar FileExistsMap
var <- IdeState -> IO FileExistsMapVar
forall a. IsIdeGlobal a => IdeState -> IO a
getIdeGlobalState IdeState
state
IO () -> IO ()
forall a. IO a -> IO a
mask_ (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ IO (IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (IO (IO ()) -> IO ()) -> IO (IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> STM (IO ()) -> IO (IO ())
forall a. String -> STM a -> IO a
atomicallyNamed String
"modifyFileExists" (STM (IO ()) -> IO (IO ())) -> STM (IO ()) -> IO (IO ())
forall a b. (a -> b) -> a -> b
$ do
[(NormalizedFilePath, FileChangeType)]
-> ((NormalizedFilePath, FileChangeType) -> STM ()) -> STM ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [(NormalizedFilePath, FileChangeType)]
changes (((NormalizedFilePath, FileChangeType) -> STM ()) -> STM ())
-> ((NormalizedFilePath, FileChangeType) -> STM ()) -> STM ()
forall a b. (a -> b) -> a -> b
$ \(NormalizedFilePath
f,FileChangeType
c) ->
case FileChangeType -> Maybe Bool
fromChange FileChangeType
c of
Just Bool
c' -> Focus Bool STM () -> NormalizedFilePath -> FileExistsMap -> STM ()
forall key value result.
(Eq key, Hashable key) =>
Focus value STM result -> key -> Map key value -> STM result
STM.focus (Bool -> Focus Bool STM ()
forall (m :: * -> *) a. Monad m => a -> Focus a m ()
Focus.insert Bool
c') NormalizedFilePath
f FileExistsMap
var
Maybe Bool
Nothing -> () -> STM ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
let ([(NormalizedFilePath, FileChangeType)]
fileModifChanges, [(NormalizedFilePath, FileChangeType)]
fileExistChanges) =
((NormalizedFilePath, FileChangeType) -> Bool)
-> [(NormalizedFilePath, FileChangeType)]
-> ([(NormalizedFilePath, FileChangeType)],
[(NormalizedFilePath, FileChangeType)])
forall a. (a -> Bool) -> [a] -> ([a], [a])
partition ((FileChangeType -> FileChangeType -> Bool
forall a. Eq a => a -> a -> Bool
== FileChangeType
FcChanged) (FileChangeType -> Bool)
-> ((NormalizedFilePath, FileChangeType) -> FileChangeType)
-> (NormalizedFilePath, FileChangeType)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (NormalizedFilePath, FileChangeType) -> FileChangeType
forall a b. (a, b) -> b
snd) [(NormalizedFilePath, FileChangeType)]
changes
((NormalizedFilePath, FileChangeType) -> STM ())
-> [(NormalizedFilePath, FileChangeType)] -> STM ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (ShakeExtras -> GetFileExists -> NormalizedFilePath -> STM ()
forall k.
ShakeValue k =>
ShakeExtras -> k -> NormalizedFilePath -> STM ()
deleteValue (IdeState -> ShakeExtras
shakeExtras IdeState
state) GetFileExists
GetFileExists (NormalizedFilePath -> STM ())
-> ((NormalizedFilePath, FileChangeType) -> NormalizedFilePath)
-> (NormalizedFilePath, FileChangeType)
-> STM ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (NormalizedFilePath, FileChangeType) -> NormalizedFilePath
forall a b. (a, b) -> a
fst) [(NormalizedFilePath, FileChangeType)]
fileExistChanges
IO ()
io1 <- ShakeExtras -> GetFileExists -> [NormalizedFilePath] -> STM (IO ())
forall k.
ShakeValue k =>
ShakeExtras -> k -> [NormalizedFilePath] -> STM (IO ())
recordDirtyKeys (IdeState -> ShakeExtras
shakeExtras IdeState
state) GetFileExists
GetFileExists ([NormalizedFilePath] -> STM (IO ()))
-> [NormalizedFilePath] -> STM (IO ())
forall a b. (a -> b) -> a -> b
$ ((NormalizedFilePath, FileChangeType) -> NormalizedFilePath)
-> [(NormalizedFilePath, FileChangeType)] -> [NormalizedFilePath]
forall a b. (a -> b) -> [a] -> [b]
map (NormalizedFilePath, FileChangeType) -> NormalizedFilePath
forall a b. (a, b) -> a
fst [(NormalizedFilePath, FileChangeType)]
fileExistChanges
IO ()
io2 <- ShakeExtras
-> GetModificationTime -> [NormalizedFilePath] -> STM (IO ())
forall k.
ShakeValue k =>
ShakeExtras -> k -> [NormalizedFilePath] -> STM (IO ())
recordDirtyKeys (IdeState -> ShakeExtras
shakeExtras IdeState
state) GetModificationTime
GetModificationTime ([NormalizedFilePath] -> STM (IO ()))
-> [NormalizedFilePath] -> STM (IO ())
forall a b. (a -> b) -> a -> b
$ ((NormalizedFilePath, FileChangeType) -> NormalizedFilePath)
-> [(NormalizedFilePath, FileChangeType)] -> [NormalizedFilePath]
forall a b. (a -> b) -> [a] -> [b]
map (NormalizedFilePath, FileChangeType) -> NormalizedFilePath
forall a b. (a, b) -> a
fst [(NormalizedFilePath, FileChangeType)]
fileModifChanges
IO () -> STM (IO ())
forall (m :: * -> *) a. Monad m => a -> m a
return (IO ()
io1 IO () -> IO () -> IO ()
forall a. Semigroup a => a -> a -> a
<> IO ()
io2)
fromChange :: FileChangeType -> Maybe Bool
fromChange :: FileChangeType -> Maybe Bool
fromChange FileChangeType
FcCreated = Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
True
fromChange FileChangeType
FcDeleted = Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
False
fromChange FileChangeType
FcChanged = Maybe Bool
forall a. Maybe a
Nothing
getFileExists :: NormalizedFilePath -> Action Bool
getFileExists :: NormalizedFilePath -> Action Bool
getFileExists NormalizedFilePath
fp = GetFileExists -> NormalizedFilePath -> Action Bool
forall k v. IdeRule k v => k -> NormalizedFilePath -> Action v
use_ GetFileExists
GetFileExists NormalizedFilePath
fp
watchedGlobs :: IdeOptions -> [String]
watchedGlobs :: IdeOptions -> [String]
watchedGlobs IdeOptions
opts = [ String
"**/*." String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
ext | String
ext <- IdeOptions -> [String]
allExtensions IdeOptions
opts]
allExtensions :: IdeOptions -> [String]
allExtensions :: IdeOptions -> [String]
allExtensions IdeOptions
opts = [String
extIncBoot | String
ext <- IdeOptions -> [String]
optExtensions IdeOptions
opts, String
extIncBoot <- [String
Item [String]
ext, String
ext String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"-boot"]]
fileExistsRules :: Maybe (LanguageContextEnv Config) -> VFSHandle -> Rules ()
fileExistsRules :: Maybe (LanguageContextEnv Config) -> VFSHandle -> Rules ()
fileExistsRules Maybe (LanguageContextEnv Config)
lspEnv VFSHandle
vfs = do
Bool
supportsWatchedFiles <- case Maybe (LanguageContextEnv Config)
lspEnv of
Maybe (LanguageContextEnv Config)
Nothing -> Bool -> Rules Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
False
Just LanguageContextEnv Config
lspEnv' -> IO Bool -> Rules Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> Rules Bool) -> IO Bool -> Rules Bool
forall a b. (a -> b) -> a -> b
$ LanguageContextEnv Config -> LspT Config IO Bool -> IO Bool
forall config (m :: * -> *) a.
LanguageContextEnv config -> LspT config m a -> m a
runLspT LanguageContextEnv Config
lspEnv' LspT Config IO Bool
isWatchSupported
FileExistsMapVar -> Rules ()
forall a. IsIdeGlobal a => a -> Rules ()
addIdeGlobal (FileExistsMapVar -> Rules ())
-> (FileExistsMap -> FileExistsMapVar) -> FileExistsMap -> Rules ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FileExistsMap -> FileExistsMapVar
FileExistsMapVar (FileExistsMap -> Rules ()) -> Rules FileExistsMap -> Rules ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IO FileExistsMap -> Rules FileExistsMap
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO FileExistsMap
forall key value. IO (Map key value)
STM.newIO
ShakeExtras
extras <- Rules ShakeExtras
getShakeExtrasRules
IdeOptions
opts <- IO IdeOptions -> Rules IdeOptions
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO IdeOptions -> Rules IdeOptions)
-> IO IdeOptions -> Rules IdeOptions
forall a b. (a -> b) -> a -> b
$ ShakeExtras -> IO IdeOptions
getIdeOptionsIO ShakeExtras
extras
let globs :: [String]
globs = IdeOptions -> [String]
watchedGlobs IdeOptions
opts
patterns :: [Pattern]
patterns = (String -> Pattern) -> [String] -> [Pattern]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Pattern
Glob.compile [String]
globs
fpMatches :: String -> Bool
fpMatches String
fp = (Pattern -> Bool) -> [Pattern] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Pattern -> String -> Bool
`Glob.match`String
fp) [Pattern]
patterns
isWatched :: NormalizedFilePath -> Action Bool
isWatched = if Bool
supportsWatchedFiles
then \NormalizedFilePath
f -> do
Bool
isWF <- NormalizedFilePath -> Action Bool
isWorkspaceFile NormalizedFilePath
f
Bool -> Action Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> Action Bool) -> Bool -> Action Bool
forall a b. (a -> b) -> a -> b
$ Bool
isWF Bool -> Bool -> Bool
&& String -> Bool
fpMatches (NormalizedFilePath -> String
fromNormalizedFilePath NormalizedFilePath
f)
else Action Bool -> NormalizedFilePath -> Action Bool
forall a b. a -> b -> a
const (Action Bool -> NormalizedFilePath -> Action Bool)
-> Action Bool -> NormalizedFilePath -> Action Bool
forall a b. (a -> b) -> a -> b
$ Bool -> Action Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
False
if Bool
supportsWatchedFiles
then (NormalizedFilePath -> Action Bool) -> VFSHandle -> Rules ()
fileExistsRulesFast NormalizedFilePath -> Action Bool
isWatched VFSHandle
vfs
else VFSHandle -> Rules ()
fileExistsRulesSlow VFSHandle
vfs
VFSHandle -> (NormalizedFilePath -> Action Bool) -> Rules ()
fileStoreRules VFSHandle
vfs NormalizedFilePath -> Action Bool
isWatched
fileExistsRulesFast :: (NormalizedFilePath -> Action Bool) -> VFSHandle -> Rules ()
fileExistsRulesFast :: (NormalizedFilePath -> Action Bool) -> VFSHandle -> Rules ()
fileExistsRulesFast NormalizedFilePath -> Action Bool
isWatched VFSHandle
vfs =
RuleBody GetFileExists Bool -> Rules ()
forall k v. IdeRule k v => RuleBody k v -> Rules ()
defineEarlyCutoff (RuleBody GetFileExists Bool -> Rules ())
-> RuleBody GetFileExists Bool -> Rules ()
forall a b. (a -> b) -> a -> b
$ (GetFileExists
-> NormalizedFilePath -> Action (Maybe ByteString, Maybe Bool))
-> RuleBody GetFileExists Bool
forall k v.
(k -> NormalizedFilePath -> Action (Maybe ByteString, Maybe v))
-> RuleBody k v
RuleNoDiagnostics ((GetFileExists
-> NormalizedFilePath -> Action (Maybe ByteString, Maybe Bool))
-> RuleBody GetFileExists Bool)
-> (GetFileExists
-> NormalizedFilePath -> Action (Maybe ByteString, Maybe Bool))
-> RuleBody GetFileExists Bool
forall a b. (a -> b) -> a -> b
$ \GetFileExists
GetFileExists NormalizedFilePath
file -> do
Bool
isWF <- NormalizedFilePath -> Action Bool
isWatched NormalizedFilePath
file
if Bool
isWF
then VFSHandle
-> NormalizedFilePath -> Action (Maybe ByteString, Maybe Bool)
fileExistsFast VFSHandle
vfs NormalizedFilePath
file
else VFSHandle
-> NormalizedFilePath -> Action (Maybe ByteString, Maybe Bool)
fileExistsSlow VFSHandle
vfs NormalizedFilePath
file
fileExistsFast :: VFSHandle -> NormalizedFilePath -> Action (Maybe BS.ByteString, Maybe Bool)
fileExistsFast :: VFSHandle
-> NormalizedFilePath -> Action (Maybe ByteString, Maybe Bool)
fileExistsFast VFSHandle
vfs NormalizedFilePath
file = do
FileExistsMap
mp <- Action FileExistsMap
getFileExistsMapUntracked
Maybe Bool
mbFilesWatched <- IO (Maybe Bool) -> Action (Maybe Bool)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Bool) -> Action (Maybe Bool))
-> IO (Maybe Bool) -> Action (Maybe Bool)
forall a b. (a -> b) -> a -> b
$ STM (Maybe Bool) -> IO (Maybe Bool)
forall a. STM a -> IO a
atomically (STM (Maybe Bool) -> IO (Maybe Bool))
-> STM (Maybe Bool) -> IO (Maybe Bool)
forall a b. (a -> b) -> a -> b
$ NormalizedFilePath -> FileExistsMap -> STM (Maybe Bool)
forall key value.
(Eq key, Hashable key) =>
key -> Map key value -> STM (Maybe value)
STM.lookup NormalizedFilePath
file FileExistsMap
mp
Bool
exist <- case Maybe Bool
mbFilesWatched of
Just Bool
exist -> Bool -> Action Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
exist
Maybe Bool
Nothing -> IO Bool -> Action Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> Action Bool) -> IO Bool -> Action Bool
forall a b. (a -> b) -> a -> b
$ VFSHandle -> NormalizedFilePath -> IO Bool
getFileExistsVFS VFSHandle
vfs NormalizedFilePath
file
(Maybe ByteString, Maybe Bool)
-> Action (Maybe ByteString, Maybe Bool)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool -> Maybe ByteString
summarizeExists Bool
exist, Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
exist)
summarizeExists :: Bool -> Maybe BS.ByteString
summarizeExists :: Bool -> Maybe ByteString
summarizeExists Bool
x = ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString) -> ByteString -> Maybe ByteString
forall a b. (a -> b) -> a -> b
$ if Bool
x then Word8 -> ByteString
BS.singleton Word8
1 else ByteString
BS.empty
fileExistsRulesSlow :: VFSHandle -> Rules ()
fileExistsRulesSlow :: VFSHandle -> Rules ()
fileExistsRulesSlow VFSHandle
vfs =
RuleBody GetFileExists Bool -> Rules ()
forall k v. IdeRule k v => RuleBody k v -> Rules ()
defineEarlyCutoff (RuleBody GetFileExists Bool -> Rules ())
-> RuleBody GetFileExists Bool -> Rules ()
forall a b. (a -> b) -> a -> b
$ (GetFileExists
-> NormalizedFilePath -> Action (Maybe ByteString, Maybe Bool))
-> RuleBody GetFileExists Bool
forall k v.
(k -> NormalizedFilePath -> Action (Maybe ByteString, Maybe v))
-> RuleBody k v
RuleNoDiagnostics ((GetFileExists
-> NormalizedFilePath -> Action (Maybe ByteString, Maybe Bool))
-> RuleBody GetFileExists Bool)
-> (GetFileExists
-> NormalizedFilePath -> Action (Maybe ByteString, Maybe Bool))
-> RuleBody GetFileExists Bool
forall a b. (a -> b) -> a -> b
$ \GetFileExists
GetFileExists NormalizedFilePath
file -> VFSHandle
-> NormalizedFilePath -> Action (Maybe ByteString, Maybe Bool)
fileExistsSlow VFSHandle
vfs NormalizedFilePath
file
fileExistsSlow :: VFSHandle -> NormalizedFilePath -> Action (Maybe BS.ByteString, Maybe Bool)
fileExistsSlow :: VFSHandle
-> NormalizedFilePath -> Action (Maybe ByteString, Maybe Bool)
fileExistsSlow VFSHandle
vfs NormalizedFilePath
file = do
Action ()
alwaysRerun
Bool
exist <- IO Bool -> Action Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> Action Bool) -> IO Bool -> Action Bool
forall a b. (a -> b) -> a -> b
$ VFSHandle -> NormalizedFilePath -> IO Bool
getFileExistsVFS VFSHandle
vfs NormalizedFilePath
file
(Maybe ByteString, Maybe Bool)
-> Action (Maybe ByteString, Maybe Bool)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool -> Maybe ByteString
summarizeExists Bool
exist, Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
exist)
getFileExistsVFS :: VFSHandle -> NormalizedFilePath -> IO Bool
getFileExistsVFS :: VFSHandle -> NormalizedFilePath -> IO Bool
getFileExistsVFS VFSHandle
vfs NormalizedFilePath
file = do
(IOException -> IO Bool) -> IO Bool -> IO Bool
forall e a. Exception e => (e -> IO a) -> IO a -> IO a
handle (\(IOException
_ :: IOException) -> Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False) (IO Bool -> IO Bool) -> IO Bool -> IO Bool
forall a b. (a -> b) -> a -> b
$
(Maybe VirtualFile -> Bool
forall a. Maybe a -> Bool
isJust (Maybe VirtualFile -> Bool) -> IO (Maybe VirtualFile) -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> VFSHandle -> NormalizedUri -> IO (Maybe VirtualFile)
getVirtualFile VFSHandle
vfs (NormalizedFilePath -> NormalizedUri
filePathToUri' NormalizedFilePath
file)) IO Bool -> IO Bool -> IO Bool
forall (m :: * -> *). Monad m => m Bool -> m Bool -> m Bool
||^
String -> IO Bool
Dir.doesFileExist (NormalizedFilePath -> String
fromNormalizedFilePath NormalizedFilePath
file)