Skip to content

Commit 27ee748

Browse files
committed
Fix main-is completion not being relative to source dirs
1 parent 3db3c51 commit 27ee748

File tree

8 files changed

+212
-145
lines changed

8 files changed

+212
-145
lines changed

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

+1
Original file line numberDiff line numberDiff line change
@@ -29,6 +29,7 @@ library
2929
Ide.Plugin.Cabal.Diagnostics
3030
Ide.Plugin.Cabal.Completion.Completer.FilePath
3131
Ide.Plugin.Cabal.Completion.Completer.Module
32+
Ide.Plugin.Cabal.Completion.Completer.Paths
3233
Ide.Plugin.Cabal.Completion.Completer.Simple
3334
Ide.Plugin.Cabal.Completion.Completer.Snippet
3435
Ide.Plugin.Cabal.Completion.Completer.Types

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

+37-42
Original file line numberDiff line numberDiff line change
@@ -5,9 +5,11 @@ module Ide.Plugin.Cabal.Completion.Completer.FilePath where
55

66
import Control.Exception (evaluate, try)
77
import Control.Monad (filterM)
8-
import Control.Monad.Extra (forM)
8+
import Control.Monad.Extra (concatForM, forM)
99
import qualified Data.Text as T
10+
import Distribution.PackageDescription (GenericPackageDescription)
1011
import Ide.Logger
12+
import Ide.Plugin.Cabal.Completion.Completer.Paths
1113
import Ide.Plugin.Cabal.Completion.Completer.Simple
1214
import Ide.Plugin.Cabal.Completion.Completer.Types
1315
import Ide.Plugin.Cabal.Completion.Types
@@ -23,7 +25,7 @@ import qualified Text.Fuzzy.Parallel as Fuzzy
2325
filePathCompleter :: Completer
2426
filePathCompleter recorder cData = do
2527
let prefInfo = cabalPrefixInfo cData
26-
complInfo = pathCompletionInfoFromCabalPrefixInfo prefInfo
28+
complInfo = pathCompletionInfoFromCabalPrefixInfo "" prefInfo
2729
filePathCompletions <- listFileCompletions recorder complInfo
2830
let scored =
2931
Fuzzy.simpleFilter
@@ -39,12 +41,44 @@ filePathCompleter recorder cData = do
3941
pure $ mkCompletionItem (completionRange prefInfo) fullFilePath fullFilePath
4042
)
4143

44+
mainIsCompleter :: (Maybe StanzaName -> GenericPackageDescription -> [FilePath]) -> Completer
45+
mainIsCompleter extractionFunction recorder cData = do
46+
mGPD <- getLatestGPD cData
47+
case mGPD of
48+
Just gpd -> do
49+
let srcDirs = extractionFunction sName gpd
50+
concatForM srcDirs
51+
(\dir' -> do
52+
let dir = FP.normalise dir'
53+
let pathInfo = pathCompletionInfoFromCabalPrefixInfo dir prefInfo
54+
completions <- listFileCompletions recorder pathInfo
55+
let scored = Fuzzy.simpleFilter
56+
Fuzzy.defChunkSize
57+
Fuzzy.defMaxResults
58+
(pathSegment pathInfo)
59+
(map T.pack completions)
60+
forM
61+
scored
62+
( \compl' -> do
63+
let compl = Fuzzy.original compl'
64+
fullFilePath <- mkFilePathCompletion pathInfo compl
65+
pure $ mkCompletionItem (completionRange prefInfo) fullFilePath fullFilePath
66+
)
67+
)
68+
Nothing -> do
69+
logWith recorder Debug LogUseWithStaleFastNoResult
70+
pure []
71+
where
72+
sName = stanzaName cData
73+
prefInfo = cabalPrefixInfo cData
74+
75+
4276
-- | Completer to be used when a directory can be completed for the field.
4377
-- Only completes directories.
4478
directoryCompleter :: Completer
4579
directoryCompleter recorder cData = do
4680
let prefInfo = cabalPrefixInfo cData
47-
complInfo = pathCompletionInfoFromCabalPrefixInfo prefInfo
81+
complInfo = pathCompletionInfoFromCabalPrefixInfo "" prefInfo
4882
directoryCompletions <- listDirectoryCompletions recorder complInfo
4983
let scored =
5084
Fuzzy.simpleFilter
@@ -73,33 +107,6 @@ directoryCompleter recorder cData = do
73107
be used for file path completions to be written to the cabal file.
74108
-}
75109

76-
-- | Information used to query and build path completions.
77-
--
78-
-- Note that pathSegment combined with queryDirectory results in
79-
-- the original prefix.
80-
--
81-
-- Example:
82-
-- When given the written prefix, @dir1\/dir2\/fi@, the
83-
-- resulting PathCompletionInfo would be:
84-
--
85-
-- @
86-
-- pathSegment = "fi"
87-
-- queryDirectory = "dir1\/dir2\/fi"
88-
-- ...
89-
-- @
90-
data PathCompletionInfo = PathCompletionInfo
91-
{ -- | partly written segment of the next part of the path
92-
pathSegment :: T.Text,
93-
-- | written part of path, platform dependent
94-
queryDirectory :: FilePath,
95-
-- | directory relative to which relative paths are interpreted, platform dependent
96-
workingDirectory :: FilePath,
97-
-- | Did the completion happen in the context of a string notation,
98-
-- if yes, contains the state of the string notation
99-
isStringNotationPath :: Maybe Apostrophe
100-
}
101-
deriving (Eq, Show)
102-
103110
-- | Takes a PathCompletionInfo and returns the list of files and directories
104111
-- in the directory which match the path completion info in posix style.
105112
--
@@ -126,18 +133,6 @@ listDirectoryCompletions recorder complInfo = do
126133
filepaths <- listFileCompletions recorder complInfo
127134
filterM (doesDirectoryExist . mkDirFromCWD complInfo) filepaths
128135

129-
pathCompletionInfoFromCabalPrefixInfo :: CabalPrefixInfo -> PathCompletionInfo
130-
pathCompletionInfoFromCabalPrefixInfo ctx =
131-
PathCompletionInfo
132-
{ pathSegment = T.pack pathSegment',
133-
queryDirectory = queryDirectory',
134-
workingDirectory = completionWorkingDir ctx,
135-
isStringNotationPath = isStringNotation ctx
136-
}
137-
where
138-
prefix = T.unpack $ completionPrefix ctx
139-
(queryDirectory', pathSegment') = Posix.splitFileName prefix
140-
141136
-- | Returns the directory where files and directories can be queried from
142137
-- for the passed PathCompletionInfo.
143138
--

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

+20-78
Original file line numberDiff line numberDiff line change
@@ -6,26 +6,16 @@ import Control.Monad (filterM)
66
import Control.Monad.Extra (concatForM,
77
forM)
88
import Data.List (stripPrefix)
9-
import qualified Data.List as List
109
import Data.Maybe (fromMaybe)
1110
import qualified Data.Text as T
12-
import Distribution.PackageDescription (Benchmark (..),
13-
BuildInfo (..),
14-
CondTree (condTreeData),
15-
Executable (..),
16-
GenericPackageDescription (..),
17-
Library (..),
18-
UnqualComponentName,
19-
mkUnqualComponentName,
20-
testBuildInfo)
21-
import Distribution.Utils.Path (getSymbolicPath)
11+
import Distribution.PackageDescription (GenericPackageDescription)
2212
import Ide.Logger (Priority (..),
2313
Recorder,
2414
WithPriority,
2515
logWith)
26-
import Ide.Plugin.Cabal.Completion.Completer.FilePath (PathCompletionInfo (..),
27-
listFileCompletions,
16+
import Ide.Plugin.Cabal.Completion.Completer.FilePath (listFileCompletions,
2817
mkCompletionDirectory)
18+
import Ide.Plugin.Cabal.Completion.Completer.Paths
2919
import Ide.Plugin.Cabal.Completion.Completer.Simple
3020
import Ide.Plugin.Cabal.Completion.Completer.Types
3121
import Ide.Plugin.Cabal.Completion.Types
@@ -53,56 +43,6 @@ modulesCompleter extractionFunction recorder cData = do
5343
sName = stanzaName cData
5444
prefInfo = cabalPrefixInfo cData
5545

56-
-- | Extracts the source directories of the library stanza.
57-
sourceDirsExtractionLibrary :: Maybe StanzaName -> GenericPackageDescription -> [FilePath]
58-
sourceDirsExtractionLibrary Nothing gpd =
59-
-- we use condLibrary to get the information contained in the library stanza
60-
-- since the library in PackageDescription is not populated by us
61-
case libM of
62-
Just lib -> do
63-
map getSymbolicPath $ hsSourceDirs $ libBuildInfo $ condTreeData lib
64-
Nothing -> []
65-
where
66-
libM = condLibrary gpd
67-
sourceDirsExtractionLibrary name gpd = extractRelativeDirsFromStanza name gpd condSubLibraries libBuildInfo
68-
69-
-- | Extracts the source directories of the executable stanza with the given name.
70-
sourceDirsExtractionExecutable :: Maybe StanzaName -> GenericPackageDescription -> [FilePath]
71-
sourceDirsExtractionExecutable name gpd = extractRelativeDirsFromStanza name gpd condExecutables buildInfo
72-
73-
-- | Extracts the source directories of the test suite stanza with the given name.
74-
sourceDirsExtractionTestSuite :: Maybe StanzaName -> GenericPackageDescription -> [FilePath]
75-
sourceDirsExtractionTestSuite name gpd = extractRelativeDirsFromStanza name gpd condTestSuites testBuildInfo
76-
77-
-- | Extracts the source directories of benchmark stanza with the given name.
78-
sourceDirsExtractionBenchmark :: Maybe StanzaName -> GenericPackageDescription -> [FilePath]
79-
sourceDirsExtractionBenchmark name gpd = extractRelativeDirsFromStanza name gpd condBenchmarks benchmarkBuildInfo
80-
81-
-- | Takes a possible stanza name, a GenericPackageDescription,
82-
-- a function to access the stanza information we are interested in
83-
-- and a function to access the build info from the specific stanza.
84-
--
85-
-- Returns a list of relative source directory paths specified for the extracted stanza.
86-
extractRelativeDirsFromStanza ::
87-
Maybe StanzaName ->
88-
GenericPackageDescription ->
89-
(GenericPackageDescription -> [(UnqualComponentName, CondTree b c a)]) ->
90-
(a -> BuildInfo) ->
91-
[FilePath]
92-
extractRelativeDirsFromStanza Nothing _ _ _ = []
93-
extractRelativeDirsFromStanza (Just name) gpd getStanza getBuildInfo
94-
| Just stanza <- stanzaM = map getSymbolicPath $ hsSourceDirs $ getBuildInfo stanza
95-
| otherwise = []
96-
where
97-
stanzaM = fmap (condTreeData . snd) res
98-
allStanzasM = getStanza gpd
99-
res =
100-
List.find
101-
( \(n, _) ->
102-
n == mkUnqualComponentName (T.unpack name)
103-
)
104-
allStanzasM
105-
10646
-- | Takes a list of source directories and returns a list of path completions
10747
-- relative to any of the passed source directories which fit the passed prefix info.
10848
filePathsForExposedModules :: Recorder (WithPriority Log) -> [FilePath] -> CabalPrefixInfo -> IO [T.Text]
@@ -111,34 +51,36 @@ filePathsForExposedModules recorder srcDirs prefInfo = do
11151
srcDirs
11252
( \dir' -> do
11353
let dir = FP.normalise dir'
114-
let pInfo =
115-
PathCompletionInfo
116-
{ isStringNotationPath = Nothing,
117-
pathSegment = T.pack $ FP.takeFileName prefix,
118-
queryDirectory = FP.addTrailingPathSeparator $ FP.takeDirectory prefix,
119-
workingDirectory = completionWorkingDir prefInfo FP.</> dir
120-
}
121-
completions <- listFileCompletions recorder pInfo
122-
validExposedCompletions <- filterM (isValidExposedModulePath pInfo) completions
123-
let toMatch = pathSegment pInfo
124-
scored = Fuzzy.simpleFilter Fuzzy.defChunkSize Fuzzy.defMaxResults toMatch (map T.pack validExposedCompletions)
54+
pathInfo = pathCompletionInfoFromCabalPrefixInfo dir modPrefInfo
55+
completions <- listFileCompletions recorder pathInfo
56+
validExposedCompletions <- filterM (isValidExposedModulePath pathInfo) completions
57+
let toMatch = pathSegment pathInfo
58+
scored = Fuzzy.simpleFilter
59+
Fuzzy.defChunkSize
60+
Fuzzy.defMaxResults
61+
toMatch
62+
(map T.pack validExposedCompletions)
12563
forM
12664
scored
12765
( \compl' -> do
12866
let compl = Fuzzy.original compl'
129-
fullFilePath <- mkExposedModulePathCompletion pInfo $ T.unpack compl
67+
fullFilePath <- mkExposedModulePathCompletion pathInfo $ T.unpack compl
13068
pure fullFilePath
13169
)
13270
)
13371
where
13472
prefix =
135-
exposedModulePathToFp $
73+
T.pack $ exposedModulePathToFp $
13674
completionPrefix prefInfo
137-
-- \| Takes a PathCompletionInfo and a path segment and checks whether
75+
-- build completion info relative to the source dir,
76+
-- we overwrite the prefix written in the cabal file with its translation
77+
-- to filepath syntax, since it is in exposed module syntax
78+
modPrefInfo = prefInfo{completionPrefix=prefix}
79+
80+
-- Takes a PathCompletionInfo and a path segment and checks whether
13881
-- the path segment can be completed for an exposed module.
13982
--
14083
-- This is the case if the segment represents either a directory or a Haskell file.
141-
--
14284
isValidExposedModulePath :: PathCompletionInfo -> FilePath -> IO Bool
14385
isValidExposedModulePath pInfo path = do
14486
let dir = mkCompletionDirectory pInfo
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,107 @@
1+
module Ide.Plugin.Cabal.Completion.Completer.Paths where
2+
3+
import qualified Data.List as List
4+
import qualified Data.Text as T
5+
import Distribution.PackageDescription (Benchmark (..),
6+
BuildInfo (..),
7+
CondTree (condTreeData),
8+
Executable (..),
9+
GenericPackageDescription (..),
10+
Library (..),
11+
UnqualComponentName,
12+
mkUnqualComponentName,
13+
testBuildInfo)
14+
import Distribution.Utils.Path (getSymbolicPath)
15+
import Ide.Plugin.Cabal.Completion.Types
16+
import qualified System.FilePath as FP
17+
import qualified System.FilePath.Posix as Posix
18+
19+
20+
-- | Information used to query and build path completions.
21+
--
22+
-- Note that pathSegment combined with queryDirectory results in
23+
-- the original prefix.
24+
--
25+
-- Example:
26+
-- When given the written prefix, @dir1\/dir2\/fi@, the
27+
-- resulting PathCompletionInfo would be:
28+
--
29+
-- @
30+
-- pathSegment = "fi"
31+
-- queryDirectory = "dir1\/dir2\/fi"
32+
-- ...
33+
-- @
34+
data PathCompletionInfo = PathCompletionInfo
35+
{ -- | partly written segment of the next part of the path
36+
pathSegment :: T.Text,
37+
-- | written part of path, platform dependent
38+
queryDirectory :: FilePath,
39+
-- | directory relative to which relative paths are interpreted, platform dependent
40+
workingDirectory :: FilePath,
41+
-- | Did the completion happen in the context of a string notation,
42+
-- if yes, contains the state of the string notation
43+
isStringNotationPath :: Maybe Apostrophe
44+
}
45+
deriving (Eq, Show)
46+
47+
pathCompletionInfoFromCabalPrefixInfo :: FilePath -> CabalPrefixInfo -> PathCompletionInfo
48+
pathCompletionInfoFromCabalPrefixInfo fp prefInfo =
49+
PathCompletionInfo
50+
{ pathSegment = T.pack pathSegment',
51+
queryDirectory = queryDirectory',
52+
workingDirectory = completionWorkingDir prefInfo FP.</> fp,
53+
isStringNotationPath = isStringNotation prefInfo
54+
}
55+
where
56+
prefix = T.unpack $ completionPrefix prefInfo
57+
(queryDirectory', pathSegment') = Posix.splitFileName prefix
58+
59+
-- | Extracts the source directories of the library stanza.
60+
sourceDirsExtractionLibrary :: Maybe StanzaName -> GenericPackageDescription -> [FilePath]
61+
sourceDirsExtractionLibrary Nothing gpd =
62+
-- we use condLibrary to get the information contained in the library stanza
63+
-- since the library in PackageDescription is not populated by us
64+
case libM of
65+
Just lib -> do
66+
map getSymbolicPath $ hsSourceDirs $ libBuildInfo $ condTreeData lib
67+
Nothing -> []
68+
where
69+
libM = condLibrary gpd
70+
sourceDirsExtractionLibrary name gpd = extractRelativeDirsFromStanza name gpd condSubLibraries libBuildInfo
71+
72+
-- | Extracts the source directories of the executable stanza with the given name.
73+
sourceDirsExtractionExecutable :: Maybe StanzaName -> GenericPackageDescription -> [FilePath]
74+
sourceDirsExtractionExecutable name gpd = extractRelativeDirsFromStanza name gpd condExecutables buildInfo
75+
76+
-- | Extracts the source directories of the test suite stanza with the given name.
77+
sourceDirsExtractionTestSuite :: Maybe StanzaName -> GenericPackageDescription -> [FilePath]
78+
sourceDirsExtractionTestSuite name gpd = extractRelativeDirsFromStanza name gpd condTestSuites testBuildInfo
79+
80+
-- | Extracts the source directories of benchmark stanza with the given name.
81+
sourceDirsExtractionBenchmark :: Maybe StanzaName -> GenericPackageDescription -> [FilePath]
82+
sourceDirsExtractionBenchmark name gpd = extractRelativeDirsFromStanza name gpd condBenchmarks benchmarkBuildInfo
83+
84+
-- | Takes a possible stanza name, a GenericPackageDescription,
85+
-- a function to access the stanza information we are interested in
86+
-- and a function to access the build info from the specific stanza.
87+
--
88+
-- Returns a list of relative source directory paths specified for the extracted stanza.
89+
extractRelativeDirsFromStanza ::
90+
Maybe StanzaName ->
91+
GenericPackageDescription ->
92+
(GenericPackageDescription -> [(UnqualComponentName, CondTree b c a)]) ->
93+
(a -> BuildInfo) ->
94+
[FilePath]
95+
extractRelativeDirsFromStanza Nothing _ _ _ = []
96+
extractRelativeDirsFromStanza (Just name) gpd getStanza getBuildInfo
97+
| Just stanza <- stanzaM = map getSymbolicPath $ hsSourceDirs $ getBuildInfo stanza
98+
| otherwise = []
99+
where
100+
stanzaM = fmap (condTreeData . snd) res
101+
allStanzasM = getStanza gpd
102+
res =
103+
List.find
104+
( \(n, _) ->
105+
n == mkUnqualComponentName (T.unpack name)
106+
)
107+
allStanzasM

0 commit comments

Comments
 (0)