Skip to content

Commit 4954c68

Browse files
committed
File path completion now considers spaces in filepath names
When the completed filepath contains a space, the whole path is wrapped in apostrophes after completion.
1 parent f951657 commit 4954c68

File tree

4 files changed

+37
-24
lines changed

4 files changed

+37
-24
lines changed

plugins/hls-cabal-plugin/src/Ide/Plugin/Cabal/Completion/Completer/FilePath.hs

Lines changed: 17 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -5,22 +5,22 @@
55

66
module Ide.Plugin.Cabal.Completion.Completer.FilePath where
77

8-
import Data.Maybe (fromMaybe)
9-
import qualified Data.Text as T
8+
import Data.Maybe (fromMaybe)
9+
import qualified Data.Text as T
1010
import Ide.Plugin.Cabal.Completion.Completer.Types
1111

12-
import Control.Exception (evaluate, try)
13-
import Control.Monad (filterM)
14-
import Control.Monad.Extra (forM)
12+
import Control.Exception (evaluate, try)
13+
import Control.Monad (filterM)
14+
import Control.Monad.Extra (forM)
1515
import Development.IDE.Types.Logger
16+
import Ide.Plugin.Cabal.Completion.Completer.Simple
1617
import Ide.Plugin.Cabal.Completion.Types
17-
import System.Directory (doesDirectoryExist,
18-
doesFileExist,
19-
listDirectory)
20-
import qualified System.FilePath as FP
21-
import qualified System.FilePath.Posix as Posix
22-
import qualified Text.Fuzzy.Parallel as Fuzzy
23-
import Ide.Plugin.Cabal.Completion.Completer.Simple
18+
import System.Directory (doesDirectoryExist,
19+
doesFileExist,
20+
listDirectory)
21+
import qualified System.FilePath as FP
22+
import qualified System.FilePath.Posix as Posix
23+
import qualified Text.Fuzzy.Parallel as Fuzzy
2424

2525

2626
{- | Completer to be used when a file path can be
@@ -30,7 +30,7 @@ import Ide.Plugin.Cabal.Completion.Completer.Simple
3030
filePathCompleter :: Completer
3131
filePathCompleter recorder cData = do
3232
let prefInfo = cabalPrefixInfo cData
33-
suffix = fromMaybe "" $ completionSuffix prefInfo
33+
suffix' = fromMaybe "" $ completionSuffix prefInfo
3434
complInfo = pathCompletionInfoFromCabalPrefixInfo prefInfo
3535
toMatch = fromMaybe (partialFileName complInfo) $ T.stripPrefix "./" $ partialFileName complInfo
3636
filePathCompletions <- listFileCompletions recorder complInfo
@@ -39,7 +39,10 @@ filePathCompleter recorder cData = do
3939
scored
4040
( \compl' -> do
4141
let compl = Fuzzy.original compl'
42-
fullFilePath <- mkFilePathCompletion suffix compl complInfo
42+
suffix = if ' ' `T.elem` compl then "\"" else suffix'
43+
fullFilePath' <- mkFilePathCompletion suffix compl complInfo
44+
-- if we complete a filepath name which contains a space then we need to wrap the path in apostrophes
45+
let fullFilePath = if ' ' `T.elem` fullFilePath' then T.append "\"" fullFilePath' else fullFilePath'
4346
pure $ mkCompletionItem (completionRange prefInfo) fullFilePath fullFilePath
4447
)
4548

plugins/hls-cabal-plugin/src/Ide/Plugin/Cabal/Completion/Completer/Module.hs

Lines changed: 19 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -3,8 +3,7 @@
33
module Ide.Plugin.Cabal.Completion.Completer.Module where
44

55
import qualified Data.List as List
6-
import Data.Maybe (fromJust,
7-
fromMaybe)
6+
import Data.Maybe (fromMaybe)
87
import qualified Data.Text as T
98
import Development.IDE (IdeState (shakeExtras))
109
import Development.IDE.Core.Shake (runIdeAction,
@@ -19,7 +18,11 @@ import Distribution.PackageDescription (Benchmark (..),
1918
mkUnqualComponentName,
2019
testBuildInfo)
2120
import Distribution.Utils.Path (getSymbolicPath)
22-
import Ide.Plugin.Cabal.Completion.Completer.FilePath
21+
import Ide.Plugin.Cabal.Completion.Completer.FilePath
22+
( listFileCompletions,
23+
mkCompletionDirectory,
24+
mkPathCompletion,
25+
PathCompletionInfo(..) )
2326
import Ide.Plugin.Cabal.Completion.Completer.Types
2427
import Ide.Plugin.Cabal.Completion.Types
2528

@@ -33,6 +36,7 @@ import System.Directory (doesFileExist)
3336
import qualified System.FilePath as FP
3437
import qualified System.FilePath.Posix as Posix
3538
import qualified Text.Fuzzy.Parallel as Fuzzy
39+
3640
{- | Completer to be used when module paths can be completed for the field.
3741
3842
Takes an extraction function which extracts the source directories
@@ -72,10 +76,12 @@ sourceDirsExtractionLibrary gpd =
7276
sourceDirsExtractionExecutable :: Maybe T.Text -> GenericPackageDescription -> [FilePath]
7377
sourceDirsExtractionExecutable Nothing _ = []
7478
sourceDirsExtractionExecutable (Just name) gpd
75-
| exeName executable == (mkUnqualComponentName $ T.unpack name) = map getSymbolicPath $ hsSourceDirs $ buildInfo executable
79+
| Just executable <- executableM
80+
, exeName executable == (mkUnqualComponentName $ T.unpack name) =
81+
map getSymbolicPath $ hsSourceDirs $ buildInfo executable
7682
| otherwise = []
7783
where
78-
executable = condTreeData $ snd $ fromJust res
84+
executableM = fmap (condTreeData . snd) res
7985
execsM = condExecutables gpd
8086
res =
8187
List.find
@@ -90,10 +96,12 @@ sourceDirsExtractionExecutable (Just name) gpd
9096
sourceDirsExtractionTestSuite :: Maybe T.Text -> GenericPackageDescription -> [FilePath]
9197
sourceDirsExtractionTestSuite Nothing _ = []
9298
sourceDirsExtractionTestSuite (Just name) gpd
93-
| testName testSuite == (mkUnqualComponentName $ T.unpack name) = map getSymbolicPath $ hsSourceDirs $ testBuildInfo testSuite
99+
| Just testSuite <- testSuiteM
100+
, testName testSuite == (mkUnqualComponentName $ T.unpack name) =
101+
map getSymbolicPath $ hsSourceDirs $ testBuildInfo testSuite
94102
| otherwise = []
95103
where
96-
testSuite = condTreeData $ snd $ fromJust res
104+
testSuiteM = fmap (condTreeData . snd) res
97105
testSuitesM = condTestSuites gpd
98106
res =
99107
List.find
@@ -108,10 +116,12 @@ sourceDirsExtractionTestSuite (Just name) gpd
108116
sourceDirsExtractionBenchmark :: Maybe T.Text -> GenericPackageDescription -> [FilePath]
109117
sourceDirsExtractionBenchmark Nothing _ = []
110118
sourceDirsExtractionBenchmark (Just name) gpd
111-
| benchmarkName bMark == (mkUnqualComponentName $ T.unpack name) = map getSymbolicPath $ hsSourceDirs $ benchmarkBuildInfo bMark
119+
| Just bMark <- bMarkM
120+
, benchmarkName bMark == (mkUnqualComponentName $ T.unpack name) =
121+
map getSymbolicPath $ hsSourceDirs $ benchmarkBuildInfo bMark
112122
| otherwise = []
113123
where
114-
bMark = condTreeData $ snd $ fromJust res
124+
bMarkM = fmap (condTreeData . snd) res
115125
bMarksM = condBenchmarks gpd
116126
res =
117127
List.find

plugins/hls-cabal-plugin/src/Ide/Plugin/Cabal/Completion/Data.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -15,6 +15,7 @@ import Ide.Plugin.Cabal.Completion.Completer.FilePath
1515
import Ide.Plugin.Cabal.Completion.Completer.Module
1616
import Ide.Plugin.Cabal.Completion.Completer.Simple
1717
import Ide.Plugin.Cabal.Completion.Completer.Types (Completer)
18+
1819
-- ----------------------------------------------------------------
1920
-- Completion Data
2021
-- ----------------------------------------------------------------

plugins/hls-cabal-plugin/src/Ide/Plugin/Cabal/Completion/Types.hs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,6 @@
44
{-# LANGUAGE ScopedTypeVariables #-}
55
{-# LANGUAGE TypeFamilies #-}
66

7-
87
module Ide.Plugin.Cabal.Completion.Types where
98

109
import Control.DeepSeq (NFData)

0 commit comments

Comments
 (0)