{-# LANGUAGE OverloadedLists      #-}
{-# LANGUAGE TypeFamilies         #-}
{-# LANGUAGE UndecidableInstances #-}
module Development.IDE.Core.FileExists
  ( fileExistsRules
  , modifyFileExists
  , getFileExists
  , watchedGlobs
  , GetFileExists(..)
  )
where

import           Control.Concurrent.Extra
import           Control.Exception
import           Control.Monad.Extra
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           Development.IDE.Core.FileStore
import           Development.IDE.Core.IdeConfiguration
import           Development.IDE.Core.Shake
import           Development.IDE.Types.Location
import           Development.IDE.Types.Options
import           Development.Shake
import           Development.Shake.Classes
import           GHC.Generics
import           Language.LSP.Server hiding (getVirtualFile)
import           Language.LSP.Types
import           Language.LSP.Types.Capabilities
import qualified System.Directory as Dir
import qualified System.FilePath.Glob as Glob

{- Note [File existence cache and LSP file watchers]
Some LSP servers provide the ability to register file watches with the client, which will then notify
us of file changes. Some clients can do this more efficiently than us, or generally it's a tricky
problem

Here we use this to maintain a quick lookup cache of file existence. How this works is:
- On startup, if the client supports it we ask it to watch some files (see below).
- When those files are created or deleted (we can also see change events, but we don't
care since we're only caching existence here) we get a notification from the client.
- The notification handler calls 'modifyFileExists' to update our cache.

This means that the cache will only ever work for the files we have set up a watcher for.
So we pick the set that we mostly care about and which are likely to change existence
most often: the source files of the project (as determined by the source extensions
we're configured to care about).

For all other files we fall back to the slow path.

There are a few failure modes to think about:

1. The client doesn't send us the notifications we asked for.

There's not much we can do in this case: the whole point is to rely on the client so
we don't do the checking ourselves. If the client lets us down, we will just be wrong.

2. Races between registering watchers, getting notifications, and file changes.

If a file changes status between us asking for notifications and the client actually
setting up the notifications, we might not get told about it. But this is a relatively
small race window around startup, so we just don't worry about it.

3. Using the fast path for files that we aren't watching.

In this case we will fall back to the slow path, but cache that result forever (since
it won't get invalidated by a client notification). To prevent this we guard the
fast path by a check that the path also matches our watching patterns.
-}

-- See Note [File existence cache and LSP file watchers]
-- | A map for tracking the file existence.
-- If a path maps to 'True' then it exists; if it maps to 'False' then it doesn't exist'; and
-- if it's not in the map then we don't know.
type FileExistsMap = (HashMap NormalizedFilePath Bool)

-- | A wrapper around a mutable 'FileExistsState'
newtype FileExistsMapVar = FileExistsMapVar (Var FileExistsMap)

instance IsIdeGlobal FileExistsMapVar

-- | Grab the current global value of 'FileExistsMap' without acquiring a dependency
getFileExistsMapUntracked :: Action FileExistsMap
getFileExistsMapUntracked :: Action FileExistsMap
getFileExistsMapUntracked = do
  FileExistsMapVar Var FileExistsMap
v <- Action FileExistsMapVar
forall a. IsIdeGlobal a => Action a
getIdeGlobalAction
  IO FileExistsMap -> Action FileExistsMap
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FileExistsMap -> Action FileExistsMap)
-> IO FileExistsMap -> Action FileExistsMap
forall a b. (a -> b) -> a -> b
$ Var FileExistsMap -> IO FileExistsMap
forall a. Var a -> IO a
readVar Var FileExistsMap
v

-- | Modify the global store of file exists.
modifyFileExists :: IdeState -> [(NormalizedFilePath, Bool)] -> IO ()
modifyFileExists :: IdeState -> [(NormalizedFilePath, Bool)] -> IO ()
modifyFileExists IdeState
state [(NormalizedFilePath, Bool)]
changes = do
  FileExistsMapVar Var FileExistsMap
var <- IdeState -> IO FileExistsMapVar
forall a. IsIdeGlobal a => IdeState -> IO a
getIdeGlobalState IdeState
state
  FileExistsMap
changesMap           <- FileExistsMap -> IO FileExistsMap
forall a. a -> IO a
evaluate (FileExistsMap -> IO FileExistsMap)
-> FileExistsMap -> IO FileExistsMap
forall a b. (a -> b) -> a -> b
$ [(NormalizedFilePath, Bool)] -> FileExistsMap
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList [(NormalizedFilePath, Bool)]
changes
  -- Masked to ensure that the previous values are flushed together with the map update
  ((forall a. IO a -> IO a) -> IO ()) -> IO ()
forall b. ((forall a. IO a -> IO a) -> IO b) -> IO b
mask (((forall a. IO a -> IO a) -> IO ()) -> IO ())
-> ((forall a. IO a -> IO a) -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \forall a. IO a -> IO a
_ -> do
    -- update the map
    Var FileExistsMap -> (FileExistsMap -> IO FileExistsMap) -> IO ()
forall a. Var a -> (a -> IO a) -> IO ()
modifyVar_ Var FileExistsMap
var ((FileExistsMap -> IO FileExistsMap) -> IO ())
-> (FileExistsMap -> IO FileExistsMap) -> IO ()
forall a b. (a -> b) -> a -> b
$ FileExistsMap -> IO FileExistsMap
forall a. a -> IO a
evaluate (FileExistsMap -> IO FileExistsMap)
-> (FileExistsMap -> FileExistsMap)
-> FileExistsMap
-> IO FileExistsMap
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FileExistsMap -> FileExistsMap -> FileExistsMap
forall k v.
(Eq k, Hashable k) =>
HashMap k v -> HashMap k v -> HashMap k v
HashMap.union FileExistsMap
changesMap
    -- See Note [Invalidating file existence results]
    -- flush previous values
    ((NormalizedFilePath, Bool) -> IO ())
-> [(NormalizedFilePath, Bool)] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (IdeState -> GetFileExists -> NormalizedFilePath -> IO ()
forall k.
(Typeable k, Hashable k, Eq k, Show k) =>
IdeState -> k -> NormalizedFilePath -> IO ()
deleteValue IdeState
state GetFileExists
GetFileExists (NormalizedFilePath -> IO ())
-> ((NormalizedFilePath, Bool) -> NormalizedFilePath)
-> (NormalizedFilePath, Bool)
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (NormalizedFilePath, Bool) -> NormalizedFilePath
forall a b. (a, b) -> a
fst) [(NormalizedFilePath, Bool)]
changes

-------------------------------------------------------------------------------------

type instance RuleResult GetFileExists = Bool

data GetFileExists = GetFileExists
    deriving (GetFileExists -> GetFileExists -> Bool
(GetFileExists -> GetFileExists -> Bool)
-> (GetFileExists -> GetFileExists -> Bool) -> Eq GetFileExists
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetFileExists -> GetFileExists -> Bool
$c/= :: GetFileExists -> GetFileExists -> Bool
== :: GetFileExists -> GetFileExists -> Bool
$c== :: GetFileExists -> GetFileExists -> Bool
Eq, Int -> GetFileExists -> ShowS
[GetFileExists] -> ShowS
GetFileExists -> String
(Int -> GetFileExists -> ShowS)
-> (GetFileExists -> String)
-> ([GetFileExists] -> ShowS)
-> Show GetFileExists
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetFileExists] -> ShowS
$cshowList :: [GetFileExists] -> ShowS
show :: GetFileExists -> String
$cshow :: GetFileExists -> String
showsPrec :: Int -> GetFileExists -> ShowS
$cshowsPrec :: Int -> GetFileExists -> ShowS
Show, Typeable, (forall x. GetFileExists -> Rep GetFileExists x)
-> (forall x. Rep GetFileExists x -> GetFileExists)
-> Generic GetFileExists
forall x. Rep GetFileExists x -> GetFileExists
forall x. GetFileExists -> Rep GetFileExists x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetFileExists x -> GetFileExists
$cfrom :: forall x. GetFileExists -> Rep GetFileExists x
Generic)

instance NFData   GetFileExists
instance Hashable GetFileExists
instance Binary   GetFileExists

-- | Returns True if the file exists
--   Note that a file is not considered to exist unless it is saved to disk.
--   In particular, VFS existence is not enough.
--   Consider the following example:
--     1. The file @A.hs@ containing the line @import B@ is added to the files of interest
--        Since @B.hs@ is neither open nor exists, GetLocatedImports finds Nothing
--     2. The editor creates a new buffer @B.hs@
--        Unless the editor also sends a @DidChangeWatchedFile@ event, ghcide will not pick it up
--        Most editors, e.g. VSCode, only send the event when the file is saved to disk.
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

{- Note [Which files should we watch?]
The watcher system gives us a lot of flexibility: we can set multiple watchers, and they can all watch on glob
patterns.

We used to have a quite precise system, where we would register a watcher for a single file path only (and always)
when we actually looked to see if it existed. The downside of this is that it sends a *lot* of notifications
to the client (thousands on a large project), and this could lock up some clients like emacs
(https://github.com/emacs-lsp/lsp-mode/issues/2165).

Now we take the opposite approach: we register a single, quite general watcher that looks for all files
with a predefined set of extensions. The consequences are:
- The client will have to watch more files. This is usually not too bad, since the pattern is a single glob,
and the clients typically call out to an optimized implementation of file watching that understands globs.
- The client will send us a lot more notifications. This isn't too bad in practice, since although
we're watching a lot of files in principle, they don't get created or destroyed that often.
- We won't ever hit the fast lookup path for files which aren't in our watch pattern, since the only way
files get into our map is when the client sends us a notification about them because we're watching them.
This is fine so long as we're watching the files we check most often, i.e. source files.
-}

-- | The list of file globs that we ask the client to watch.
watchedGlobs :: IdeOptions -> [String]
watchedGlobs :: IdeOptions -> [String]
watchedGlobs IdeOptions
opts = [ String
"**/*." String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
extIncBoot | String
ext <- IdeOptions -> [String]
optExtensions IdeOptions
opts, String
extIncBoot <- [String
Item [String]
ext, String
ext String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"-boot"]]

-- | Installs the 'getFileExists' rules.
--   Provides a fast implementation if client supports dynamic watched files.
--   Creates a global state as a side effect in that case.
fileExistsRules :: Maybe (LanguageContextEnv c) -> VFSHandle -> Rules ()
fileExistsRules :: Maybe (LanguageContextEnv c) -> VFSHandle -> Rules ()
fileExistsRules Maybe (LanguageContextEnv c)
lspEnv VFSHandle
vfs = do
  Bool
supportsWatchedFiles <- case Maybe (LanguageContextEnv c)
lspEnv of
    Just LanguageContextEnv c
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 c -> LspT c IO Bool -> IO Bool
forall config (m :: * -> *) a.
LanguageContextEnv config -> LspT config m a -> m a
runLspT LanguageContextEnv c
lspEnv' (LspT c IO Bool -> IO Bool) -> LspT c IO Bool -> IO Bool
forall a b. (a -> b) -> a -> b
$ do
      ClientCapabilities {Maybe WorkspaceClientCapabilities
$sel:_workspace:ClientCapabilities :: ClientCapabilities -> Maybe WorkspaceClientCapabilities
_workspace :: Maybe WorkspaceClientCapabilities
_workspace} <- LspT c IO ClientCapabilities
forall config (m :: * -> *).
MonadLsp config m =>
m ClientCapabilities
getClientCapabilities
      case () of
        ()
_ | Just WorkspaceClientCapabilities{Maybe DidChangeWatchedFilesClientCapabilities
$sel:_didChangeWatchedFiles:WorkspaceClientCapabilities :: WorkspaceClientCapabilities
-> Maybe DidChangeWatchedFilesClientCapabilities
_didChangeWatchedFiles :: Maybe DidChangeWatchedFilesClientCapabilities
_didChangeWatchedFiles} <- Maybe WorkspaceClientCapabilities
_workspace
          , Just DidChangeWatchedFilesClientCapabilities{Maybe Bool
$sel:_dynamicRegistration:DidChangeWatchedFilesClientCapabilities :: DidChangeWatchedFilesClientCapabilities -> Maybe Bool
_dynamicRegistration :: Maybe Bool
_dynamicRegistration} <- Maybe DidChangeWatchedFilesClientCapabilities
_didChangeWatchedFiles
          , Just Bool
True <- Maybe Bool
_dynamicRegistration
          -> Bool -> LspT c IO Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
True
        ()
_ -> Bool -> LspT c IO Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
False
    Maybe (LanguageContextEnv c)
Nothing -> Bool -> Rules Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
False
  -- Create the global always, although it should only be used if we have fast rules.
  -- But there's a chance someone will send unexpected notifications anyway,
  -- e.g. https://github.com/haskell/ghcide/issues/599
  FileExistsMapVar -> Rules ()
forall a. IsIdeGlobal a => a -> Rules ()
addIdeGlobal (FileExistsMapVar -> Rules ())
-> (Var FileExistsMap -> FileExistsMapVar)
-> Var FileExistsMap
-> Rules ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Var FileExistsMap -> FileExistsMapVar
FileExistsMapVar (Var FileExistsMap -> Rules ())
-> Rules (Var FileExistsMap) -> Rules ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IO (Var FileExistsMap) -> Rules (Var FileExistsMap)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (FileExistsMap -> IO (Var FileExistsMap)
forall a. a -> IO (Var a)
newVar [])

  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

  if Bool
supportsWatchedFiles
    then [String] -> VFSHandle -> Rules ()
fileExistsRulesFast [String]
globs VFSHandle
vfs
    else VFSHandle -> Rules ()
fileExistsRulesSlow VFSHandle
vfs

-- Requires an lsp client that provides WatchedFiles notifications, but assumes that this has already been checked.
fileExistsRulesFast :: [String] -> VFSHandle -> Rules ()
fileExistsRulesFast :: [String] -> VFSHandle -> Rules ()
fileExistsRulesFast [String]
globs VFSHandle
vfs =
    let 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
p -> Pattern -> String -> Bool
Glob.match Pattern
p String
fp) [Pattern]
patterns
    in (GetFileExists
 -> NormalizedFilePath -> Action (Maybe ByteString, IdeResult Bool))
-> Rules ()
forall k v.
IdeRule k v =>
(k -> NormalizedFilePath -> Action (Maybe ByteString, IdeResult v))
-> Rules ()
defineEarlyCutoff ((GetFileExists
  -> NormalizedFilePath -> Action (Maybe ByteString, IdeResult Bool))
 -> Rules ())
-> (GetFileExists
    -> NormalizedFilePath -> Action (Maybe ByteString, IdeResult Bool))
-> Rules ()
forall a b. (a -> b) -> a -> b
$ \GetFileExists
GetFileExists NormalizedFilePath
file -> do
        Bool
isWf <- NormalizedFilePath -> Action Bool
isWorkspaceFile NormalizedFilePath
file
        if Bool
isWf Bool -> Bool -> Bool
&& String -> Bool
fpMatches (NormalizedFilePath -> String
fromNormalizedFilePath NormalizedFilePath
file)
            then VFSHandle
-> NormalizedFilePath -> Action (Maybe ByteString, IdeResult Bool)
forall a.
VFSHandle
-> NormalizedFilePath
-> Action (Maybe ByteString, ([a], Maybe Bool))
fileExistsFast VFSHandle
vfs NormalizedFilePath
file
            else VFSHandle
-> NormalizedFilePath -> Action (Maybe ByteString, IdeResult Bool)
forall a.
VFSHandle
-> NormalizedFilePath
-> Action (Maybe ByteString, ([a], Maybe Bool))
fileExistsSlow VFSHandle
vfs NormalizedFilePath
file

{- Note [Invalidating file existence results]
We have two mechanisms for getting file existence information:
- The file existence cache
- The VFS lookup

Both of these affect the results of the 'GetFileExists' rule, so we need to make sure it
is invalidated properly when things change.

For the file existence cache, we manually flush the results of 'GetFileExists' when we
modify it (i.e. when a notification comes from the client). This is faster than using
'alwaysRerun' in the 'fileExistsFast', and we need it to be as fast as possible.

For the VFS lookup, however, we won't get prompted to flush the result, so instead
we use 'alwaysRerun'.
-}

fileExistsFast :: VFSHandle -> NormalizedFilePath -> Action (Maybe BS.ByteString, ([a], Maybe Bool))
fileExistsFast :: VFSHandle
-> NormalizedFilePath
-> Action (Maybe ByteString, ([a], Maybe Bool))
fileExistsFast VFSHandle
vfs NormalizedFilePath
file = do
    -- Could in principle use 'alwaysRerun' here, but it's too slwo, See Note [Invalidating file existence results]
    FileExistsMap
mp <- Action FileExistsMap
getFileExistsMapUntracked

    let mbFilesWatched :: Maybe Bool
mbFilesWatched = NormalizedFilePath -> FileExistsMap -> Maybe Bool
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.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
      -- We don't know about it: use the slow route.
      -- Note that we do *not* call 'fileExistsSlow', as that would trigger 'alwaysRerun'.
      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, ([a], Maybe Bool))
-> Action (Maybe ByteString, ([a], 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 =
  (GetFileExists
 -> NormalizedFilePath -> Action (Maybe ByteString, IdeResult Bool))
-> Rules ()
forall k v.
IdeRule k v =>
(k -> NormalizedFilePath -> Action (Maybe ByteString, IdeResult v))
-> Rules ()
defineEarlyCutoff ((GetFileExists
  -> NormalizedFilePath -> Action (Maybe ByteString, IdeResult Bool))
 -> Rules ())
-> (GetFileExists
    -> NormalizedFilePath -> Action (Maybe ByteString, IdeResult Bool))
-> Rules ()
forall a b. (a -> b) -> a -> b
$ \GetFileExists
GetFileExists NormalizedFilePath
file -> VFSHandle
-> NormalizedFilePath -> Action (Maybe ByteString, IdeResult Bool)
forall a.
VFSHandle
-> NormalizedFilePath
-> Action (Maybe ByteString, ([a], Maybe Bool))
fileExistsSlow VFSHandle
vfs NormalizedFilePath
file

fileExistsSlow :: VFSHandle -> NormalizedFilePath -> Action (Maybe BS.ByteString, ([a], Maybe Bool))
fileExistsSlow :: VFSHandle
-> NormalizedFilePath
-> Action (Maybe ByteString, ([a], Maybe Bool))
fileExistsSlow VFSHandle
vfs NormalizedFilePath
file = do
    -- See Note [Invalidating file existence results]
    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, ([a], Maybe Bool))
-> Action (Maybe ByteString, ([a], 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
    -- we deliberately and intentionally wrap the file as an FilePath WITHOUT mkAbsolute
    -- so that if the file doesn't exist, is on a shared drive that is unmounted etc we get a properly
    -- cached 'No' rather than an exception in the wrong place
    (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)