{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Ide.Plugin.Cabal.Completion.Completer.FilePath where
import Control.Exception (evaluate, try)
import Control.Monad (filterM)
import Control.Monad.Extra (concatForM, forM)
import qualified Data.Text as T
import Distribution.PackageDescription (GenericPackageDescription)
import Ide.Logger
import Ide.Plugin.Cabal.Completion.Completer.Paths
import Ide.Plugin.Cabal.Completion.Completer.Simple
import Ide.Plugin.Cabal.Completion.Completer.Types
import Ide.Plugin.Cabal.Completion.Types
import System.Directory (doesDirectoryExist,
doesFileExist,
listDirectory)
import qualified System.FilePath as FP
import qualified System.FilePath.Posix as Posix
import qualified Text.Fuzzy.Parallel as Fuzzy
filePathCompleter :: Completer
filePathCompleter :: Completer
filePathCompleter Recorder (WithPriority Log)
recorder CompleterData
cData = do
let prefInfo :: CabalPrefixInfo
prefInfo = CompleterData -> CabalPrefixInfo
cabalPrefixInfo CompleterData
cData
complInfo :: PathCompletionInfo
complInfo = FilePath -> CabalPrefixInfo -> PathCompletionInfo
pathCompletionInfoFromCabalPrefixInfo FilePath
"" CabalPrefixInfo
prefInfo
[FilePath]
filePathCompletions <- Recorder (WithPriority Log) -> PathCompletionInfo -> IO [FilePath]
listFileCompletions Recorder (WithPriority Log)
recorder PathCompletionInfo
complInfo
let scored :: [Scored Text]
scored =
Int -> Int -> Text -> [Text] -> [Scored Text]
Fuzzy.simpleFilter
Int
Fuzzy.defChunkSize
Int
Fuzzy.defMaxResults
(PathCompletionInfo -> Text
pathSegment PathCompletionInfo
complInfo)
(forall a b. (a -> b) -> [a] -> [b]
map FilePath -> Text
T.pack [FilePath]
filePathCompletions)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM
[Scored Text]
scored
( \Scored Text
compl' -> do
let compl :: Text
compl = forall a. Scored a -> a
Fuzzy.original Scored Text
compl'
Text
fullFilePath <- PathCompletionInfo -> Text -> IO Text
mkFilePathCompletion PathCompletionInfo
complInfo Text
compl
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Range -> Text -> Text -> CompletionItem
mkCompletionItem (CabalPrefixInfo -> Range
completionRange CabalPrefixInfo
prefInfo) Text
fullFilePath Text
fullFilePath
)
mainIsCompleter :: (Maybe StanzaName -> GenericPackageDescription -> [FilePath]) -> Completer
mainIsCompleter :: (Maybe Text -> GenericPackageDescription -> [FilePath])
-> Completer
mainIsCompleter Maybe Text -> GenericPackageDescription -> [FilePath]
extractionFunction Recorder (WithPriority Log)
recorder CompleterData
cData = do
Maybe GenericPackageDescription
mGPD <- CompleterData -> IO (Maybe GenericPackageDescription)
getLatestGPD CompleterData
cData
case Maybe GenericPackageDescription
mGPD of
Just GenericPackageDescription
gpd -> do
let srcDirs :: [FilePath]
srcDirs = Maybe Text -> GenericPackageDescription -> [FilePath]
extractionFunction Maybe Text
sName GenericPackageDescription
gpd
forall (m :: * -> *) a b. Monad m => [a] -> (a -> m [b]) -> m [b]
concatForM [FilePath]
srcDirs
(\FilePath
dir' -> do
let dir :: FilePath
dir = FilePath -> FilePath
FP.normalise FilePath
dir'
let pathInfo :: PathCompletionInfo
pathInfo = FilePath -> CabalPrefixInfo -> PathCompletionInfo
pathCompletionInfoFromCabalPrefixInfo FilePath
dir CabalPrefixInfo
prefInfo
[FilePath]
completions <- Recorder (WithPriority Log) -> PathCompletionInfo -> IO [FilePath]
listFileCompletions Recorder (WithPriority Log)
recorder PathCompletionInfo
pathInfo
let scored :: [Scored Text]
scored = Int -> Int -> Text -> [Text] -> [Scored Text]
Fuzzy.simpleFilter
Int
Fuzzy.defChunkSize
Int
Fuzzy.defMaxResults
(PathCompletionInfo -> Text
pathSegment PathCompletionInfo
pathInfo)
(forall a b. (a -> b) -> [a] -> [b]
map FilePath -> Text
T.pack [FilePath]
completions)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM
[Scored Text]
scored
( \Scored Text
compl' -> do
let compl :: Text
compl = forall a. Scored a -> a
Fuzzy.original Scored Text
compl'
Text
fullFilePath <- PathCompletionInfo -> Text -> IO Text
mkFilePathCompletion PathCompletionInfo
pathInfo Text
compl
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Range -> Text -> Text -> CompletionItem
mkCompletionItem (CabalPrefixInfo -> Range
completionRange CabalPrefixInfo
prefInfo) Text
fullFilePath Text
fullFilePath
)
)
Maybe GenericPackageDescription
Nothing -> do
forall (m :: * -> *) msg.
(HasCallStack, MonadIO m) =>
Recorder (WithPriority msg) -> Priority -> msg -> m ()
logWith Recorder (WithPriority Log)
recorder Priority
Debug Log
LogUseWithStaleFastNoResult
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
where
sName :: Maybe Text
sName = CompleterData -> Maybe Text
stanzaName CompleterData
cData
prefInfo :: CabalPrefixInfo
prefInfo = CompleterData -> CabalPrefixInfo
cabalPrefixInfo CompleterData
cData
directoryCompleter :: Completer
directoryCompleter :: Completer
directoryCompleter Recorder (WithPriority Log)
recorder CompleterData
cData = do
let prefInfo :: CabalPrefixInfo
prefInfo = CompleterData -> CabalPrefixInfo
cabalPrefixInfo CompleterData
cData
complInfo :: PathCompletionInfo
complInfo = FilePath -> CabalPrefixInfo -> PathCompletionInfo
pathCompletionInfoFromCabalPrefixInfo FilePath
"" CabalPrefixInfo
prefInfo
[FilePath]
directoryCompletions <- Recorder (WithPriority Log) -> PathCompletionInfo -> IO [FilePath]
listDirectoryCompletions Recorder (WithPriority Log)
recorder PathCompletionInfo
complInfo
let scored :: [Scored Text]
scored =
Int -> Int -> Text -> [Text] -> [Scored Text]
Fuzzy.simpleFilter
Int
Fuzzy.defChunkSize
Int
Fuzzy.defMaxResults
(PathCompletionInfo -> Text
pathSegment PathCompletionInfo
complInfo)
(forall a b. (a -> b) -> [a] -> [b]
map FilePath -> Text
T.pack [FilePath]
directoryCompletions)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM
[Scored Text]
scored
( \Scored Text
compl' -> do
let compl :: Text
compl = forall a. Scored a -> a
Fuzzy.original Scored Text
compl'
let fullDirPath :: Text
fullDirPath = PathCompletionInfo -> Text -> Text
mkPathCompletionDir PathCompletionInfo
complInfo Text
compl
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Range -> Text -> Text -> CompletionItem
mkCompletionItem (CabalPrefixInfo -> Range
completionRange CabalPrefixInfo
prefInfo) Text
fullDirPath Text
fullDirPath
)
listFileCompletions :: Recorder (WithPriority Log) -> PathCompletionInfo -> IO [FilePath]
listFileCompletions :: Recorder (WithPriority Log) -> PathCompletionInfo -> IO [FilePath]
listFileCompletions Recorder (WithPriority Log)
recorder PathCompletionInfo
complInfo = do
let complDir :: FilePath
complDir = PathCompletionInfo -> FilePath
mkCompletionDirectory PathCompletionInfo
complInfo
forall e a. Exception e => IO a -> IO (Either e a)
try (forall a. a -> IO a
evaluate forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< FilePath -> IO [FilePath]
listDirectory FilePath
complDir) forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Right [FilePath]
dirs -> do
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [FilePath]
dirs forall a b. (a -> b) -> a -> b
$ \FilePath
d -> do
Bool
isDir <- FilePath -> IO Bool
doesDirectoryExist forall a b. (a -> b) -> a -> b
$ PathCompletionInfo -> FilePath -> FilePath
mkDirFromCWD PathCompletionInfo
complInfo FilePath
d
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ if Bool
isDir then FilePath -> FilePath
Posix.addTrailingPathSeparator FilePath
d else FilePath
d
Left (IOError
err :: IOError) -> do
forall (m :: * -> *) msg.
(HasCallStack, MonadIO m) =>
Recorder (WithPriority msg) -> Priority -> msg -> m ()
logWith Recorder (WithPriority Log)
recorder Priority
Warning forall a b. (a -> b) -> a -> b
$ FilePath -> IOError -> Log
LogFilePathCompleterIOError FilePath
complDir IOError
err
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
listDirectoryCompletions :: Recorder (WithPriority Log) -> PathCompletionInfo -> IO [FilePath]
listDirectoryCompletions :: Recorder (WithPriority Log) -> PathCompletionInfo -> IO [FilePath]
listDirectoryCompletions Recorder (WithPriority Log)
recorder PathCompletionInfo
complInfo = do
[FilePath]
filepaths <- Recorder (WithPriority Log) -> PathCompletionInfo -> IO [FilePath]
listFileCompletions Recorder (WithPriority Log)
recorder PathCompletionInfo
complInfo
forall (m :: * -> *) a.
Applicative m =>
(a -> m Bool) -> [a] -> m [a]
filterM (FilePath -> IO Bool
doesDirectoryExist forall b c a. (b -> c) -> (a -> b) -> a -> c
. PathCompletionInfo -> FilePath -> FilePath
mkDirFromCWD PathCompletionInfo
complInfo) [FilePath]
filepaths
mkCompletionDirectory :: PathCompletionInfo -> FilePath
mkCompletionDirectory :: PathCompletionInfo -> FilePath
mkCompletionDirectory PathCompletionInfo
complInfo =
FilePath -> FilePath
FP.addTrailingPathSeparator forall a b. (a -> b) -> a -> b
$
PathCompletionInfo -> FilePath
workingDirectory PathCompletionInfo
complInfo FilePath -> FilePath -> FilePath
FP.</> (FilePath -> FilePath
FP.normalise forall a b. (a -> b) -> a -> b
$ PathCompletionInfo -> FilePath
queryDirectory PathCompletionInfo
complInfo)
mkDirFromCWD :: PathCompletionInfo -> FilePath -> FilePath
mkDirFromCWD :: PathCompletionInfo -> FilePath -> FilePath
mkDirFromCWD PathCompletionInfo
complInfo FilePath
fp =
FilePath -> FilePath
FP.addTrailingPathSeparator forall a b. (a -> b) -> a -> b
$
PathCompletionInfo -> FilePath
mkCompletionDirectory PathCompletionInfo
complInfo FilePath -> FilePath -> FilePath
FP.</> FilePath -> FilePath
FP.normalise FilePath
fp
mkPathCompletionDir :: PathCompletionInfo -> T.Text -> T.Text
mkPathCompletionDir :: PathCompletionInfo -> Text -> Text
mkPathCompletionDir PathCompletionInfo
complInfo Text
completion =
FilePath -> Text
T.pack forall a b. (a -> b) -> a -> b
$
PathCompletionInfo -> FilePath
queryDirectory PathCompletionInfo
complInfo FilePath -> FilePath -> FilePath
Posix.</> Text -> FilePath
T.unpack Text
completion
mkFilePathCompletion :: PathCompletionInfo -> T.Text -> IO T.Text
mkFilePathCompletion :: PathCompletionInfo -> Text -> IO Text
mkFilePathCompletion PathCompletionInfo
complInfo Text
completion = do
let combinedPath :: Text
combinedPath = PathCompletionInfo -> Text -> Text
mkPathCompletionDir PathCompletionInfo
complInfo Text
completion
Bool
isFilePath <- FilePath -> IO Bool
doesFileExist forall a b. (a -> b) -> a -> b
$ Text -> FilePath
T.unpack Text
combinedPath
let completedPath :: Text
completedPath = if Bool
isFilePath then Maybe Apostrophe -> Text -> Text
applyStringNotation (PathCompletionInfo -> Maybe Apostrophe
isStringNotationPath PathCompletionInfo
complInfo) Text
combinedPath else Text
combinedPath
forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
completedPath