Skip to content

Commit 201c9b7

Browse files
committed
Move Matcher type to cabal completion module
1 parent 0bf4cb6 commit 201c9b7

File tree

6 files changed

+19
-17
lines changed

6 files changed

+19
-17
lines changed

ghcide/src/Text/Fuzzy/Parallel.hs

Lines changed: 1 addition & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,7 @@ module Text.Fuzzy.Parallel
44
( filter, filter', matchPar,
55
simpleFilter, simpleFilter',
66
match, defChunkSize, defMaxResults,
7-
Scored(..), Matcher (..)
7+
Scored(..)
88
) where
99

1010
import Control.Parallel.Strategies (evalList, parList, rseq, using)
@@ -18,8 +18,6 @@ import Prelude hiding (filter)
1818
data Scored a = Scored {score :: !Int, original:: !a}
1919
deriving (Functor, Show)
2020

21-
newtype Matcher a = Matcher { runMatcher :: T.Text -> [T.Text] -> [Scored a] }
22-
2321
-- | Returns the rendered output and the
2422
-- matching score for a pattern and a text.
2523
-- Two examples are given below:

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

Lines changed: 3 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,6 @@
22
{-# LANGUAGE DuplicateRecordFields #-}
33
{-# LANGUAGE LambdaCase #-}
44
{-# LANGUAGE OverloadedStrings #-}
5-
{-# LANGUAGE PatternSynonyms #-}
65
{-# LANGUAGE TypeFamilies #-}
76

87
module Ide.Plugin.Cabal (descriptor, haskellInteractionDescriptor, Log (..)) where
@@ -237,7 +236,7 @@ fieldSuggestCodeAction recorder ide _ (CodeActionParams _ _ (TextDocumentIdentif
237236
lspPrefixInfo = Ghcide.getCompletionPrefixFromRope fakeLspCursorPosition fileContents
238237
cabalPrefixInfo = Completions.getCabalPrefixInfo fp lspPrefixInfo
239238
completions <- liftIO $ computeCompletionsAt recorder ide cabalPrefixInfo fp cabalFields $
240-
Fuzzy.Matcher $
239+
CompleterTypes.Matcher $
241240
Fuzzy.levenshteinScored Fuzzy.defChunkSize
242241
let completionTexts = fmap (^. JL.label) completions
243242
pure $ FieldSuggest.fieldErrorAction uri fieldName completionTexts _range
@@ -370,7 +369,7 @@ completion recorder ide _ complParams = do
370369
let lspPrefInfo = Ghcide.getCompletionPrefixFromRope position cnts
371370
cabalPrefInfo = Completions.getCabalPrefixInfo path lspPrefInfo
372371
res = computeCompletionsAt recorder ide cabalPrefInfo path fields $
373-
Fuzzy.Matcher $
372+
CompleterTypes.Matcher $
374373
Fuzzy.simpleFilter Fuzzy.defChunkSize Fuzzy.defMaxResults
375374
liftIO $ fmap InL res
376375
Nothing -> pure . InR $ InR Null
@@ -381,7 +380,7 @@ computeCompletionsAt
381380
-> Types.CabalPrefixInfo
382381
-> FilePath
383382
-> [Syntax.Field Syntax.Position]
384-
-> Fuzzy.Matcher T.Text
383+
-> CompleterTypes.Matcher T.Text
385384
-> IO [CompletionItem]
386385
computeCompletionsAt recorder ide prefInfo fp fields matcher = do
387386
runMaybeT (context fields) >>= \case

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

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -48,7 +48,7 @@ filePathsForExposedModules
4848
:: Recorder (WithPriority Log)
4949
-> [FilePath]
5050
-> CabalPrefixInfo
51-
-> Fuzzy.Matcher T.Text
51+
-> Matcher T.Text
5252
-> IO [T.Text]
5353
filePathsForExposedModules recorder srcDirs prefInfo matcher = do
5454
concatForM
@@ -59,7 +59,7 @@ filePathsForExposedModules recorder srcDirs prefInfo matcher = do
5959
completions <- listFileCompletions recorder pathInfo
6060
validExposedCompletions <- filterM (isValidExposedModulePath pathInfo) completions
6161
let toMatch = pathSegment pathInfo
62-
scored = Fuzzy.runMatcher
62+
scored = runMatcher
6363
matcher
6464
toMatch
6565
(map T.pack validExposedCompletions)

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

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -41,7 +41,7 @@ errorNoopCompleter l recorder _ = do
4141
constantCompleter :: [T.Text] -> Completer
4242
constantCompleter completions _ cData = do
4343
let prefInfo = cabalPrefixInfo cData
44-
scored = Fuzzy.runMatcher (matcher cData) (completionPrefix prefInfo) completions
44+
scored = runMatcher (matcher cData) (completionPrefix prefInfo) completions
4545
range = completionRange prefInfo
4646
pure $ map (mkSimpleCompletionItem range . Fuzzy.original) scored
4747

@@ -68,7 +68,7 @@ importCompleter l cData = do
6868
-- it is just forbidden on hackage.
6969
nameCompleter :: Completer
7070
nameCompleter _ cData = do
71-
let scored = Fuzzy.runMatcher (matcher cData) (completionPrefix prefInfo) [completionFileName prefInfo]
71+
let scored = runMatcher (matcher cData) (completionPrefix prefInfo) [completionFileName prefInfo]
7272
prefInfo = cabalPrefixInfo cData
7373
range = completionRange prefInfo
7474
pure $ map (mkSimpleCompletionItem range . Fuzzy.original) scored

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

Lines changed: 6 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -3,18 +3,22 @@
33
module Ide.Plugin.Cabal.Completion.Completer.Types where
44

55
import Data.Text (Text)
6+
import qualified Data.Text as T
67
import Development.IDE as D
78
import qualified Distribution.Fields as Syntax
89
import Distribution.PackageDescription (GenericPackageDescription)
910
import qualified Distribution.Parsec.Position as Syntax
1011
import Ide.Plugin.Cabal.Completion.Types
1112
import Language.LSP.Protocol.Types (CompletionItem)
12-
import qualified Text.Fuzzy.Parallel as Fuzzy
13+
import Text.Fuzzy.Parallel
1314

1415
-- | Takes information needed to build possible completion items
1516
-- and returns the list of possible completion items
1617
type Completer = Recorder (WithPriority Log) -> CompleterData -> IO [CompletionItem]
1718

19+
-- | Type signature of completion functions ranking texts against a pattern.
20+
newtype Matcher a = Matcher { runMatcher :: T.Text -> [T.Text] -> [Scored a] }
21+
1822
-- | Contains information to be used by completers.
1923
data CompleterData = CompleterData
2024
{ -- | Access to the latest available generic package description for the handled cabal file,
@@ -28,5 +32,5 @@ data CompleterData = CompleterData
2832
-- | The name of the stanza in which the completer is applied
2933
stanzaName :: Maybe StanzaName,
3034
-- | The matcher that'll be used to rank the texts against the pattern.
31-
matcher :: Fuzzy.Matcher Text
35+
matcher :: Matcher Text
3236
}

plugins/hls-cabal-plugin/test/Completer.hs

Lines changed: 5 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -21,7 +21,8 @@ import Ide.Plugin.Cabal.Completion.Completer.FilePath
2121
import Ide.Plugin.Cabal.Completion.Completer.Module
2222
import Ide.Plugin.Cabal.Completion.Completer.Paths
2323
import Ide.Plugin.Cabal.Completion.Completer.Simple (importCompleter)
24-
import Ide.Plugin.Cabal.Completion.Completer.Types (CompleterData (..))
24+
import Ide.Plugin.Cabal.Completion.Completer.Types (CompleterData (..),
25+
Matcher (..))
2526
import Ide.Plugin.Cabal.Completion.Completions
2627
import Ide.Plugin.Cabal.Completion.Types (CabalPrefixInfo (..),
2728
StanzaName)
@@ -271,7 +272,7 @@ filePathExposedModulesTests =
271272
callFilePathsForExposedModules :: [FilePath] -> IO [T.Text]
272273
callFilePathsForExposedModules srcDirs = do
273274
let prefInfo = simpleCabalPrefixInfoFromFp "" exposedTestDir
274-
filePathsForExposedModules mempty srcDirs prefInfo $ Fuzzy.Matcher $ Fuzzy.simpleFilter Fuzzy.defChunkSize Fuzzy.defMaxResults
275+
filePathsForExposedModules mempty srcDirs prefInfo $ Matcher $ Fuzzy.simpleFilter Fuzzy.defChunkSize Fuzzy.defMaxResults
275276

276277
exposedModuleCompleterTests :: TestTree
277278
exposedModuleCompleterTests =
@@ -368,7 +369,7 @@ simpleCompleterData sName dir pref = do
368369
pure $ parseGenericPackageDescriptionMaybe cabalContents,
369370
getCabalCommonSections = undefined,
370371
stanzaName = sName,
371-
matcher = Fuzzy.Matcher $ Fuzzy.simpleFilter Fuzzy.defChunkSize Fuzzy.defMaxResults
372+
matcher = Matcher $ Fuzzy.simpleFilter Fuzzy.defChunkSize Fuzzy.defMaxResults
372373
}
373374

374375
mkCompleterData :: CabalPrefixInfo -> CompleterData
@@ -378,7 +379,7 @@ mkCompleterData prefInfo =
378379
getCabalCommonSections = undefined,
379380
cabalPrefixInfo = prefInfo,
380381
stanzaName = Nothing,
381-
matcher = Fuzzy.Matcher $ Fuzzy.simpleFilter Fuzzy.defChunkSize Fuzzy.defMaxResults
382+
matcher = Matcher $ Fuzzy.simpleFilter Fuzzy.defChunkSize Fuzzy.defMaxResults
382383
}
383384

384385
exposedTestDir :: FilePath

0 commit comments

Comments
 (0)