Skip to content

Commit

Permalink
File path completion now considers spaces in filepath names
Browse files Browse the repository at this point in the history
When the completed filepath contains a space, the whole path is
wrapped in apostrophes after completion.
  • Loading branch information
VeryMilkyJoe committed Jul 3, 2023
1 parent f951657 commit 4954c68
Show file tree
Hide file tree
Showing 4 changed files with 37 additions and 24 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -5,22 +5,22 @@

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

import Data.Maybe (fromMaybe)
import qualified Data.Text as T
import Data.Maybe (fromMaybe)
import qualified Data.Text as T
import Ide.Plugin.Cabal.Completion.Completer.Types

import Control.Exception (evaluate, try)
import Control.Monad (filterM)
import Control.Monad.Extra (forM)
import Control.Exception (evaluate, try)
import Control.Monad (filterM)
import Control.Monad.Extra (forM)
import Development.IDE.Types.Logger
import Ide.Plugin.Cabal.Completion.Completer.Simple
import Ide.Plugin.Cabal.Completion.Types
import System.Directory (doesDirectoryExist,
doesFileExist,
listDirectory)
import qualified System.FilePath as FP
import qualified System.FilePath.Posix as Posix
import qualified Text.Fuzzy.Parallel as Fuzzy
import Ide.Plugin.Cabal.Completion.Completer.Simple
import System.Directory (doesDirectoryExist,
doesFileExist,
listDirectory)
import qualified System.FilePath as FP
import qualified System.FilePath.Posix as Posix
import qualified Text.Fuzzy.Parallel as Fuzzy


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

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -3,8 +3,7 @@
module Ide.Plugin.Cabal.Completion.Completer.Module where

import qualified Data.List as List
import Data.Maybe (fromJust,
fromMaybe)
import Data.Maybe (fromMaybe)
import qualified Data.Text as T
import Development.IDE (IdeState (shakeExtras))
import Development.IDE.Core.Shake (runIdeAction,
Expand All @@ -19,7 +18,11 @@ import Distribution.PackageDescription (Benchmark (..),
mkUnqualComponentName,
testBuildInfo)
import Distribution.Utils.Path (getSymbolicPath)
import Ide.Plugin.Cabal.Completion.Completer.FilePath
import Ide.Plugin.Cabal.Completion.Completer.FilePath
( listFileCompletions,
mkCompletionDirectory,
mkPathCompletion,
PathCompletionInfo(..) )
import Ide.Plugin.Cabal.Completion.Completer.Types
import Ide.Plugin.Cabal.Completion.Types

Expand All @@ -33,6 +36,7 @@ import System.Directory (doesFileExist)
import qualified System.FilePath as FP
import qualified System.FilePath.Posix as Posix
import qualified Text.Fuzzy.Parallel as Fuzzy

{- | Completer to be used when module paths can be completed for the field.
Takes an extraction function which extracts the source directories
Expand Down Expand Up @@ -72,10 +76,12 @@ sourceDirsExtractionLibrary gpd =
sourceDirsExtractionExecutable :: Maybe T.Text -> GenericPackageDescription -> [FilePath]
sourceDirsExtractionExecutable Nothing _ = []
sourceDirsExtractionExecutable (Just name) gpd
| exeName executable == (mkUnqualComponentName $ T.unpack name) = map getSymbolicPath $ hsSourceDirs $ buildInfo executable
| Just executable <- executableM
, exeName executable == (mkUnqualComponentName $ T.unpack name) =
map getSymbolicPath $ hsSourceDirs $ buildInfo executable
| otherwise = []
where
executable = condTreeData $ snd $ fromJust res
executableM = fmap (condTreeData . snd) res
execsM = condExecutables gpd
res =
List.find
Expand All @@ -90,10 +96,12 @@ sourceDirsExtractionExecutable (Just name) gpd
sourceDirsExtractionTestSuite :: Maybe T.Text -> GenericPackageDescription -> [FilePath]
sourceDirsExtractionTestSuite Nothing _ = []
sourceDirsExtractionTestSuite (Just name) gpd
| testName testSuite == (mkUnqualComponentName $ T.unpack name) = map getSymbolicPath $ hsSourceDirs $ testBuildInfo testSuite
| Just testSuite <- testSuiteM
, testName testSuite == (mkUnqualComponentName $ T.unpack name) =
map getSymbolicPath $ hsSourceDirs $ testBuildInfo testSuite
| otherwise = []
where
testSuite = condTreeData $ snd $ fromJust res
testSuiteM = fmap (condTreeData . snd) res
testSuitesM = condTestSuites gpd
res =
List.find
Expand All @@ -108,10 +116,12 @@ sourceDirsExtractionTestSuite (Just name) gpd
sourceDirsExtractionBenchmark :: Maybe T.Text -> GenericPackageDescription -> [FilePath]
sourceDirsExtractionBenchmark Nothing _ = []
sourceDirsExtractionBenchmark (Just name) gpd
| benchmarkName bMark == (mkUnqualComponentName $ T.unpack name) = map getSymbolicPath $ hsSourceDirs $ benchmarkBuildInfo bMark
| Just bMark <- bMarkM
, benchmarkName bMark == (mkUnqualComponentName $ T.unpack name) =
map getSymbolicPath $ hsSourceDirs $ benchmarkBuildInfo bMark
| otherwise = []
where
bMark = condTreeData $ snd $ fromJust res
bMarkM = fmap (condTreeData . snd) res
bMarksM = condBenchmarks gpd
res =
List.find
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -15,6 +15,7 @@ import Ide.Plugin.Cabal.Completion.Completer.FilePath
import Ide.Plugin.Cabal.Completion.Completer.Module
import Ide.Plugin.Cabal.Completion.Completer.Simple
import Ide.Plugin.Cabal.Completion.Completer.Types (Completer)

-- ----------------------------------------------------------------
-- Completion Data
-- ----------------------------------------------------------------
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,6 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}


module Ide.Plugin.Cabal.Completion.Types where

import Control.DeepSeq (NFData)
Expand Down

0 comments on commit 4954c68

Please sign in to comment.