{-# LANGUAGE OverloadedStrings #-}
module Ide.Plugin.Cabal.Completion.Completer.Module where
import Control.Monad (filterM)
import Control.Monad.Extra (concatForM,
forM)
import Data.List (stripPrefix)
import Data.Maybe (fromMaybe)
import qualified Data.Text as T
import Distribution.PackageDescription (GenericPackageDescription)
import Ide.Logger (Priority (..),
Recorder,
WithPriority,
logWith)
import Ide.Plugin.Cabal.Completion.Completer.FilePath (listFileCompletions,
mkCompletionDirectory)
import Ide.Plugin.Cabal.Completion.Completer.Paths
import Ide.Plugin.Cabal.Completion.Completer.Simple
import Ide.Plugin.Cabal.Completion.Completer.Types
import Ide.Plugin.Cabal.Completion.Types
import System.Directory (doesFileExist)
import qualified System.FilePath as FP
import qualified Text.Fuzzy.Parallel as Fuzzy
modulesCompleter :: (Maybe StanzaName -> GenericPackageDescription -> [FilePath]) -> Completer
modulesCompleter :: (Maybe Text -> GenericPackageDescription -> [String]) -> Completer
modulesCompleter Maybe Text -> GenericPackageDescription -> [String]
extractionFunction Recorder (WithPriority Log)
recorder CompleterData
cData = do
Maybe GenericPackageDescription
mGPD <- CompleterData -> IO (Maybe GenericPackageDescription)
getLatestGPD CompleterData
cData
case Maybe GenericPackageDescription
mGPD of
Just GenericPackageDescription
gpd -> do
let sourceDirs :: [String]
sourceDirs = Maybe Text -> GenericPackageDescription -> [String]
extractionFunction Maybe Text
sName GenericPackageDescription
gpd
[Text]
filePathCompletions <-
Recorder (WithPriority Log)
-> [String] -> CabalPrefixInfo -> IO [Text]
filePathsForExposedModules Recorder (WithPriority Log)
recorder [String]
sourceDirs CabalPrefixInfo
prefInfo
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (\Text
compl -> Range -> Text -> CompletionItem
mkSimpleCompletionItem (CabalPrefixInfo -> Range
completionRange CabalPrefixInfo
prefInfo) Text
compl) [Text]
filePathCompletions
Maybe GenericPackageDescription
Nothing -> do
forall (m :: * -> *) msg.
(HasCallStack, MonadIO m) =>
Recorder (WithPriority msg) -> Priority -> msg -> m ()
logWith Recorder (WithPriority Log)
recorder Priority
Debug Log
LogUseWithStaleFastNoResult
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
where
sName :: Maybe Text
sName = CompleterData -> Maybe Text
stanzaName CompleterData
cData
prefInfo :: CabalPrefixInfo
prefInfo = CompleterData -> CabalPrefixInfo
cabalPrefixInfo CompleterData
cData
filePathsForExposedModules :: Recorder (WithPriority Log) -> [FilePath] -> CabalPrefixInfo -> IO [T.Text]
filePathsForExposedModules :: Recorder (WithPriority Log)
-> [String] -> CabalPrefixInfo -> IO [Text]
filePathsForExposedModules Recorder (WithPriority Log)
recorder [String]
srcDirs CabalPrefixInfo
prefInfo = do
forall (m :: * -> *) a b. Monad m => [a] -> (a -> m [b]) -> m [b]
concatForM
[String]
srcDirs
( \String
dir' -> do
let dir :: String
dir = String -> String
FP.normalise String
dir'
pathInfo :: PathCompletionInfo
pathInfo = String -> CabalPrefixInfo -> PathCompletionInfo
pathCompletionInfoFromCabalPrefixInfo String
dir CabalPrefixInfo
modPrefInfo
[String]
completions <- Recorder (WithPriority Log) -> PathCompletionInfo -> IO [String]
listFileCompletions Recorder (WithPriority Log)
recorder PathCompletionInfo
pathInfo
[String]
validExposedCompletions <- forall (m :: * -> *) a.
Applicative m =>
(a -> m Bool) -> [a] -> m [a]
filterM (PathCompletionInfo -> String -> IO Bool
isValidExposedModulePath PathCompletionInfo
pathInfo) [String]
completions
let toMatch :: Text
toMatch = PathCompletionInfo -> Text
pathSegment PathCompletionInfo
pathInfo
scored :: [Scored Text]
scored = Int -> Int -> Text -> [Text] -> [Scored Text]
Fuzzy.simpleFilter
Int
Fuzzy.defChunkSize
Int
Fuzzy.defMaxResults
Text
toMatch
(forall a b. (a -> b) -> [a] -> [b]
map String -> Text
T.pack [String]
validExposedCompletions)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM
[Scored Text]
scored
( \Scored Text
compl' -> do
let compl :: Text
compl = forall a. Scored a -> a
Fuzzy.original Scored Text
compl'
Text
fullFilePath <- PathCompletionInfo -> String -> IO Text
mkExposedModulePathCompletion PathCompletionInfo
pathInfo forall a b. (a -> b) -> a -> b
$ Text -> String
T.unpack Text
compl
forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
fullFilePath
)
)
where
prefix :: Text
prefix =
String -> Text
T.pack forall a b. (a -> b) -> a -> b
$ Text -> String
exposedModulePathToFp forall a b. (a -> b) -> a -> b
$
CabalPrefixInfo -> Text
completionPrefix CabalPrefixInfo
prefInfo
modPrefInfo :: CabalPrefixInfo
modPrefInfo = CabalPrefixInfo
prefInfo{completionPrefix :: Text
completionPrefix=Text
prefix}
isValidExposedModulePath :: PathCompletionInfo -> FilePath -> IO Bool
isValidExposedModulePath :: PathCompletionInfo -> String -> IO Bool
isValidExposedModulePath PathCompletionInfo
pInfo String
path = do
let dir :: String
dir = PathCompletionInfo -> String
mkCompletionDirectory PathCompletionInfo
pInfo
Bool
fileExists <- String -> IO Bool
doesFileExist (String
dir String -> String -> String
FP.</> String
path)
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not Bool
fileExists Bool -> Bool -> Bool
|| String -> String
FP.takeExtension String
path forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String
".hs", String
".lhs"]
mkExposedModulePathCompletion :: PathCompletionInfo -> FilePath -> IO T.Text
mkExposedModulePathCompletion :: PathCompletionInfo -> String -> IO Text
mkExposedModulePathCompletion PathCompletionInfo
complInfo String
completion = do
let combinedPath :: String
combinedPath = PathCompletionInfo -> String
queryDirectory PathCompletionInfo
complInfo String -> String -> String
FP.</> String
completion
Bool
isFilePath <- String -> IO Bool
doesFileExist (PathCompletionInfo -> String
workingDirectory PathCompletionInfo
complInfo String -> String -> String
FP.</> String
combinedPath)
let addTrailingDot :: p -> p
addTrailingDot p
modPath = if Bool
isFilePath then p
modPath else p
modPath forall a. Semigroup a => a -> a -> a
<> p
"."
let exposedPath :: String
exposedPath = String -> String -> String
FP.makeRelative String
"." String
combinedPath
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall {p}. (Semigroup p, IsString p) => p -> p
addTrailingDot forall a b. (a -> b) -> a -> b
$ String -> String -> Text
fpToExposedModulePath String
"" String
exposedPath
fpToExposedModulePath :: FilePath -> FilePath -> T.Text
fpToExposedModulePath :: String -> String -> Text
fpToExposedModulePath String
sourceDir String
modPath =
Text -> [Text] -> Text
T.intercalate Text
"." forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Text
T.pack forall a b. (a -> b) -> a -> b
$ String -> [String]
FP.splitDirectories forall a b. (a -> b) -> a -> b
$ String -> String
FP.dropExtension String
fp
where
fp :: String
fp = forall a. a -> Maybe a -> a
fromMaybe String
modPath forall a b. (a -> b) -> a -> b
$ forall a. Eq a => [a] -> [a] -> Maybe [a]
stripPrefix String
sourceDir String
modPath
exposedModulePathToFp :: T.Text -> FilePath
exposedModulePathToFp :: Text -> String
exposedModulePathToFp Text
fp = Text -> String
T.unpack forall a b. (a -> b) -> a -> b
$ Text -> Text -> Text -> Text
T.replace Text
"." (Char -> Text
T.singleton Char
FP.pathSeparator) Text
fp