{-# LANGUAGE OverloadedLists #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
module Development.IDE.Core.FileExists
( fileExistsRules
, modifyFileExists
, getFileExists
, watchedGlobs
, GetFileExists(..)
, Log(..)
)
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 hiding (Log, LogShake)
import qualified Development.IDE.Core.FileStore as FileStore
import Development.IDE.Core.IdeConfiguration
import Development.IDE.Core.RuleTypes
import Development.IDE.Core.Shake hiding (Log)
import qualified Development.IDE.Core.Shake as Shake
import Development.IDE.Graph
import Development.IDE.Types.Location
import Development.IDE.Types.Options
import qualified Focus
import Ide.Logger (Pretty (pretty),
Recorder, WithPriority,
cmapWithPrio)
import Ide.Plugin.Config (Config)
import Language.LSP.Protocol.Types
import Language.LSP.Server hiding (getVirtualFile)
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
data Log
= LogFileStore FileStore.Log
| LogShake Shake.Log
deriving Int -> Log -> ShowS
[Log] -> ShowS
Log -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Log] -> ShowS
$cshowList :: [Log] -> ShowS
show :: Log -> String
$cshow :: Log -> String
showsPrec :: Int -> Log -> ShowS
$cshowsPrec :: Int -> Log -> ShowS
Show
instance Pretty Log where
pretty :: forall ann. Log -> Doc ann
pretty = \case
LogFileStore Log
msg -> forall a ann. Pretty a => a -> Doc ann
pretty Log
msg
LogShake Log
msg -> forall a ann. Pretty a => a -> Doc ann
pretty Log
msg
getFileExistsMapUntracked :: Action FileExistsMap
getFileExistsMapUntracked :: Action FileExistsMap
getFileExistsMapUntracked = do
FileExistsMapVar FileExistsMap
v <- forall a. (HasCallStack, IsIdeGlobal a) => Action a
getIdeGlobalAction
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 <- forall a. IsIdeGlobal a => IdeState -> IO a
getIdeGlobalState IdeState
state
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join forall a b. (a -> b) -> a -> b
$ forall a. IO a -> IO a
mask_ forall a b. (a -> b) -> a -> b
$ forall a. String -> STM a -> IO a
atomicallyNamed String
"modifyFileExists" forall a b. (a -> b) -> a -> b
$ do
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [(NormalizedFilePath, FileChangeType)]
changes forall a b. (a -> b) -> a -> b
$ \(NormalizedFilePath
f,FileChangeType
c) ->
case FileChangeType -> Maybe Bool
fromChange FileChangeType
c of
Just Bool
c' -> forall key value result.
Hashable key =>
Focus value STM result -> key -> Map key value -> STM result
STM.focus (forall (m :: * -> *) a. Monad m => a -> Focus a m ()
Focus.insert Bool
c') NormalizedFilePath
f FileExistsMap
var
Maybe Bool
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
let ([(NormalizedFilePath, FileChangeType)]
fileModifChanges, [(NormalizedFilePath, FileChangeType)]
fileExistChanges) =
forall a. (a -> Bool) -> [a] -> ([a], [a])
partition ((forall a. Eq a => a -> a -> Bool
== FileChangeType
FileChangeType_Changed) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> b
snd) [(NormalizedFilePath, FileChangeType)]
changes
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (forall k.
ShakeValue k =>
ShakeExtras -> k -> NormalizedFilePath -> STM ()
deleteValue (IdeState -> ShakeExtras
shakeExtras IdeState
state) GetFileExists
GetFileExists forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst) [(NormalizedFilePath, FileChangeType)]
fileExistChanges
IO ()
io1 <- forall k.
ShakeValue k =>
ShakeExtras -> k -> [NormalizedFilePath] -> STM (IO ())
recordDirtyKeys (IdeState -> ShakeExtras
shakeExtras IdeState
state) GetFileExists
GetFileExists forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> a
fst [(NormalizedFilePath, FileChangeType)]
fileExistChanges
IO ()
io2 <- forall k.
ShakeValue k =>
ShakeExtras -> k -> [NormalizedFilePath] -> STM (IO ())
recordDirtyKeys (IdeState -> ShakeExtras
shakeExtras IdeState
state) GetModificationTime
GetModificationTime forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> a
fst [(NormalizedFilePath, FileChangeType)]
fileModifChanges
forall (m :: * -> *) a. Monad m => a -> m a
return (IO ()
io1 forall a. Semigroup a => a -> a -> a
<> IO ()
io2)
fromChange :: FileChangeType -> Maybe Bool
fromChange :: FileChangeType -> Maybe Bool
fromChange FileChangeType
FileChangeType_Created = forall a. a -> Maybe a
Just Bool
True
fromChange FileChangeType
FileChangeType_Deleted = forall a. a -> Maybe a
Just Bool
False
fromChange FileChangeType
FileChangeType_Changed = forall a. Maybe a
Nothing
getFileExists :: NormalizedFilePath -> Action Bool
getFileExists :: NormalizedFilePath -> Action Bool
getFileExists NormalizedFilePath
fp = 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
"**/*." 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
ext, String
ext forall a. [a] -> [a] -> [a]
++ String
"-boot"]]
fileExistsRules :: Recorder (WithPriority Log) -> Maybe (LanguageContextEnv Config) -> Rules ()
fileExistsRules :: Recorder (WithPriority Log)
-> Maybe (LanguageContextEnv Config) -> Rules ()
fileExistsRules Recorder (WithPriority Log)
recorder Maybe (LanguageContextEnv Config)
lspEnv = do
Bool
supportsWatchedFiles <- case Maybe (LanguageContextEnv Config)
lspEnv of
Maybe (LanguageContextEnv Config)
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
False
Just LanguageContextEnv Config
lspEnv' -> forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall config (m :: * -> *) a.
LanguageContextEnv config -> LspT config m a -> m a
runLspT LanguageContextEnv Config
lspEnv' LspT Config IO Bool
isWatchSupported
forall a. IsIdeGlobal a => a -> Rules ()
addIdeGlobal forall b c a. (b -> c) -> (a -> b) -> a -> c
. FileExistsMap -> FileExistsMapVar
FileExistsMapVar forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall key value. IO (Map key value)
STM.newIO
ShakeExtras
extras <- Rules ShakeExtras
getShakeExtrasRules
IdeOptions
opts <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO 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 = 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 = 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
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Bool
isWF Bool -> Bool -> Bool
&& String -> Bool
fpMatches (NormalizedFilePath -> String
fromNormalizedFilePath NormalizedFilePath
f)
else forall a b. a -> b -> a
const forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
False
if Bool
supportsWatchedFiles
then Recorder (WithPriority Log)
-> (NormalizedFilePath -> Action Bool) -> Rules ()
fileExistsRulesFast Recorder (WithPriority Log)
recorder NormalizedFilePath -> Action Bool
isWatched
else Recorder (WithPriority Log) -> Rules ()
fileExistsRulesSlow Recorder (WithPriority Log)
recorder
Recorder (WithPriority Log)
-> (NormalizedFilePath -> Action Bool) -> Rules ()
fileStoreRules (forall a b.
(a -> b) -> Recorder (WithPriority b) -> Recorder (WithPriority a)
cmapWithPrio Log -> Log
LogFileStore Recorder (WithPriority Log)
recorder) NormalizedFilePath -> Action Bool
isWatched
fileExistsRulesFast :: Recorder (WithPriority Log) -> (NormalizedFilePath -> Action Bool) -> Rules ()
fileExistsRulesFast :: Recorder (WithPriority Log)
-> (NormalizedFilePath -> Action Bool) -> Rules ()
fileExistsRulesFast Recorder (WithPriority Log)
recorder NormalizedFilePath -> Action Bool
isWatched =
forall k v.
IdeRule k v =>
Recorder (WithPriority Log) -> RuleBody k v -> Rules ()
defineEarlyCutoff (forall a b.
(a -> b) -> Recorder (WithPriority b) -> Recorder (WithPriority a)
cmapWithPrio Log -> Log
LogShake Recorder (WithPriority Log)
recorder) forall a b. (a -> b) -> a -> b
$ forall k v.
(k -> NormalizedFilePath -> Action (Maybe ByteString, Maybe v))
-> RuleBody k v
RuleNoDiagnostics forall a b. (a -> b) -> a -> b
$ \GetFileExists
GetFileExists NormalizedFilePath
file -> do
Bool
isWF <- NormalizedFilePath -> Action Bool
isWatched NormalizedFilePath
file
if Bool
isWF
then NormalizedFilePath -> Action (Maybe ByteString, Maybe Bool)
fileExistsFast NormalizedFilePath
file
else NormalizedFilePath -> Action (Maybe ByteString, Maybe Bool)
fileExistsSlow NormalizedFilePath
file
fileExistsFast :: NormalizedFilePath -> Action (Maybe BS.ByteString, Maybe Bool)
fileExistsFast :: NormalizedFilePath -> Action (Maybe ByteString, Maybe Bool)
fileExistsFast NormalizedFilePath
file = do
FileExistsMap
mp <- Action FileExistsMap
getFileExistsMapUntracked
Maybe Bool
mbFilesWatched <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a. STM a -> IO a
atomically forall a b. (a -> b) -> a -> b
$ forall key value.
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 -> forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
exist
Maybe Bool
Nothing -> NormalizedFilePath -> Action Bool
getFileExistsVFS NormalizedFilePath
file
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool -> Maybe ByteString
summarizeExists Bool
exist, forall a. a -> Maybe a
Just Bool
exist)
summarizeExists :: Bool -> Maybe BS.ByteString
summarizeExists :: Bool -> Maybe ByteString
summarizeExists Bool
x = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ if Bool
x then Word8 -> ByteString
BS.singleton Word8
1 else ByteString
BS.empty
fileExistsRulesSlow :: Recorder (WithPriority Log) -> Rules ()
fileExistsRulesSlow :: Recorder (WithPriority Log) -> Rules ()
fileExistsRulesSlow Recorder (WithPriority Log)
recorder =
forall k v.
IdeRule k v =>
Recorder (WithPriority Log) -> RuleBody k v -> Rules ()
defineEarlyCutoff (forall a b.
(a -> b) -> Recorder (WithPriority b) -> Recorder (WithPriority a)
cmapWithPrio Log -> Log
LogShake Recorder (WithPriority Log)
recorder) forall a b. (a -> b) -> a -> b
$ forall k v.
(k -> NormalizedFilePath -> Action (Maybe ByteString, Maybe v))
-> RuleBody k v
RuleNoDiagnostics forall a b. (a -> b) -> a -> b
$ \GetFileExists
GetFileExists NormalizedFilePath
file -> NormalizedFilePath -> Action (Maybe ByteString, Maybe Bool)
fileExistsSlow NormalizedFilePath
file
fileExistsSlow :: NormalizedFilePath -> Action (Maybe BS.ByteString, Maybe Bool)
fileExistsSlow :: NormalizedFilePath -> Action (Maybe ByteString, Maybe Bool)
fileExistsSlow NormalizedFilePath
file = do
Action ()
alwaysRerun
Bool
exist <- NormalizedFilePath -> Action Bool
getFileExistsVFS NormalizedFilePath
file
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool -> Maybe ByteString
summarizeExists Bool
exist, forall a. a -> Maybe a
Just Bool
exist)
getFileExistsVFS :: NormalizedFilePath -> Action Bool
getFileExistsVFS :: NormalizedFilePath -> Action Bool
getFileExistsVFS NormalizedFilePath
file = do
Maybe VirtualFile
vf <- NormalizedFilePath -> Action (Maybe VirtualFile)
getVirtualFile NormalizedFilePath
file
if forall a. Maybe a -> Bool
isJust Maybe VirtualFile
vf
then forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
True
else forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall e a. Exception e => (e -> IO a) -> IO a -> IO a
handle (\(IOException
_ :: IOException) -> forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False) forall a b. (a -> b) -> a -> b
$
String -> IO Bool
Dir.doesFileExist (NormalizedFilePath -> String
fromNormalizedFilePath NormalizedFilePath
file)