33module Ide.Plugin.Cabal.Completion.Completer.Module where
44
55import qualified Data.List as List
6- import Data.Maybe (fromJust ,
7- fromMaybe )
6+ import Data.Maybe (fromMaybe )
87import qualified Data.Text as T
98import Development.IDE (IdeState (shakeExtras ))
109import 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 )
2120import 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 )
2325import Ide.Plugin.Cabal.Completion.Completer.Types
2426import Ide.Plugin.Cabal.Completion.Types
2527
@@ -33,6 +35,7 @@ import System.Directory (doesFileExist)
3335import qualified System.FilePath as FP
3436import qualified System.FilePath.Posix as Posix
3537import 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-}
7275sourceDirsExtractionExecutable :: 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-}
9080sourceDirsExtractionTestSuite :: 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-}
10885sourceDirsExtractionBenchmark :: 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.
0 commit comments