Skip to content

Commit c7bd418

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 c7bd418

File tree

5 files changed

+49
-62
lines changed

5 files changed

+49
-62
lines changed

plugins/hls-cabal-plugin/hls-cabal-plugin.cabal

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -27,14 +27,14 @@ library
2727
exposed-modules:
2828
Ide.Plugin.Cabal
2929
Ide.Plugin.Cabal.Diagnostics
30-
Ide.Plugin.Cabal.Completion.Completions
31-
Ide.Plugin.Cabal.Completion.Types
32-
Ide.Plugin.Cabal.Completion.Data
3330
Ide.Plugin.Cabal.Completion.Completer.FilePath
3431
Ide.Plugin.Cabal.Completion.Completer.Module
3532
Ide.Plugin.Cabal.Completion.Completer.Simple
36-
Ide.Plugin.Cabal.Completion.Completer.Types
3733
Ide.Plugin.Cabal.Completion.Completer.Snippet
34+
Ide.Plugin.Cabal.Completion.Completer.Types
35+
Ide.Plugin.Cabal.Completion.Completions
36+
Ide.Plugin.Cabal.Completion.Data
37+
Ide.Plugin.Cabal.Completion.Types
3838
Ide.Plugin.Cabal.LicenseSuggest
3939
Ide.Plugin.Cabal.Parse
4040

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: 27 additions & 43 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,
@@ -15,11 +14,14 @@ import Distribution.PackageDescription (Benchmark (..),
1514
Executable (..),
1615
GenericPackageDescription (..),
1716
Library (..),
18-
TestSuite (testName),
17+
UnqualComponentName,
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 (PathCompletionInfo (..),
22+
listFileCompletions,
23+
mkCompletionDirectory,
24+
mkPathCompletion)
2325
import Ide.Plugin.Cabal.Completion.Completer.Types
2426
import Ide.Plugin.Cabal.Completion.Types
2527

@@ -33,6 +35,7 @@ import System.Directory (doesFileExist)
3335
import qualified System.FilePath as FP
3436
import qualified System.FilePath.Posix as Posix
3537
import qualified Text.Fuzzy.Parallel as Fuzzy
38+
3639
{- | Completer to be used when module paths can be completed for the field.
3740
3841
Takes an extraction function which extracts the source directories
@@ -70,56 +73,37 @@ sourceDirsExtractionLibrary gpd =
7073
{- | Extracts the source directories of the executable stanza with the given name.
7174
-}
7275
sourceDirsExtractionExecutable :: Maybe T.Text -> GenericPackageDescription -> [FilePath]
73-
sourceDirsExtractionExecutable Nothing _ = []
74-
sourceDirsExtractionExecutable (Just name) gpd
75-
| exeName executable == (mkUnqualComponentName $ T.unpack name) = map getSymbolicPath $ hsSourceDirs $ buildInfo executable
76-
| otherwise = []
77-
where
78-
executable = condTreeData $ snd $ fromJust res
79-
execsM = condExecutables gpd
80-
res =
81-
List.find
82-
(\(_, cTree) -> do
83-
let execName = exeName $ condTreeData cTree
84-
execName == (mkUnqualComponentName $ T.unpack name)
85-
)
86-
execsM
76+
sourceDirsExtractionExecutable name gpd = extractRelativeDirsFromStanza name gpd condExecutables buildInfo
8777

8878
{- | Extracts the source directories of the test suite stanza with the given name.
8979
-}
9080
sourceDirsExtractionTestSuite :: Maybe T.Text -> GenericPackageDescription -> [FilePath]
91-
sourceDirsExtractionTestSuite Nothing _ = []
92-
sourceDirsExtractionTestSuite (Just name) gpd
93-
| testName testSuite == (mkUnqualComponentName $ T.unpack name) = map getSymbolicPath $ hsSourceDirs $ testBuildInfo testSuite
94-
| otherwise = []
95-
where
96-
testSuite = condTreeData $ snd $ fromJust res
97-
testSuitesM = condTestSuites gpd
98-
res =
99-
List.find
100-
(\(_, cTree) -> do
101-
let testsName = testName $ condTreeData cTree
102-
testsName == (mkUnqualComponentName $ T.unpack name)
103-
)
104-
testSuitesM
81+
sourceDirsExtractionTestSuite name gpd = extractRelativeDirsFromStanza name gpd condTestSuites testBuildInfo
10582

10683
{- | Extracts the source directories of benchmark stanza with the given name.
10784
-}
10885
sourceDirsExtractionBenchmark :: Maybe T.Text -> GenericPackageDescription -> [FilePath]
109-
sourceDirsExtractionBenchmark Nothing _ = []
110-
sourceDirsExtractionBenchmark (Just name) gpd
111-
| benchmarkName bMark == (mkUnqualComponentName $ T.unpack name) = map getSymbolicPath $ hsSourceDirs $ benchmarkBuildInfo bMark
86+
sourceDirsExtractionBenchmark name gpd = extractRelativeDirsFromStanza name gpd condBenchmarks benchmarkBuildInfo
87+
88+
extractRelativeDirsFromStanza ::
89+
Maybe T.Text ->
90+
GenericPackageDescription ->
91+
(GenericPackageDescription -> [(UnqualComponentName, CondTree b c a)]) ->
92+
(a -> BuildInfo) ->
93+
[FilePath]
94+
extractRelativeDirsFromStanza Nothing _ _ _ = []
95+
extractRelativeDirsFromStanza (Just name) gpd getStanza getBuildInfo
96+
| Just stanza <- stanzaM = map getSymbolicPath $ hsSourceDirs $ getBuildInfo stanza
11297
| otherwise = []
11398
where
114-
bMark = condTreeData $ snd $ fromJust res
115-
bMarksM = condBenchmarks gpd
99+
stanzaM = fmap (condTreeData . snd) res
100+
allStanzasM = getStanza gpd
116101
res =
117-
List.find
118-
(\(_, cTree) -> do
119-
let bMarkName = benchmarkName $ condTreeData cTree
120-
bMarkName == (mkUnqualComponentName $ T.unpack name)
121-
)
122-
bMarksM
102+
List.find
103+
(\(n,_) ->
104+
n == (mkUnqualComponentName $ T.unpack name)
105+
)
106+
allStanzasM
123107

124108
{- | Extracts the source dirs from the library stanza in the cabal file using the GPD
125109
and returns a list of path completions relative to any source dir which fit the passed prefix info.

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)