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 ,
@@ -19,7 +18,11 @@ import Distribution.PackageDescription (Benchmark (..),
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
22+ ( listFileCompletions ,
23+ mkCompletionDirectory ,
24+ mkPathCompletion ,
25+ PathCompletionInfo (.. ) )
2326import Ide.Plugin.Cabal.Completion.Completer.Types
2427import Ide.Plugin.Cabal.Completion.Types
2528
@@ -33,6 +36,7 @@ import System.Directory (doesFileExist)
3336import qualified System.FilePath as FP
3437import qualified System.FilePath.Posix as Posix
3538import 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 =
7276sourceDirsExtractionExecutable :: Maybe T. Text -> GenericPackageDescription -> [FilePath ]
7377sourceDirsExtractionExecutable Nothing _ = []
7478sourceDirsExtractionExecutable (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
9096sourceDirsExtractionTestSuite :: Maybe T. Text -> GenericPackageDescription -> [FilePath ]
9197sourceDirsExtractionTestSuite Nothing _ = []
9298sourceDirsExtractionTestSuite (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
108116sourceDirsExtractionBenchmark :: Maybe T. Text -> GenericPackageDescription -> [FilePath ]
109117sourceDirsExtractionBenchmark Nothing _ = []
110118sourceDirsExtractionBenchmark (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
0 commit comments