Skip to content

Commit b8b4f6b

Browse files
committed
Add documentation and cleanup
1 parent b0048d0 commit b8b4f6b

File tree

2 files changed

+119
-95
lines changed

2 files changed

+119
-95
lines changed

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

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -287,7 +287,6 @@ completion _ide _ complParams = do
287287
| Just ctx <- context = do
288288
let completer = contextToCompleter ctx
289289
completions <- completer completionContext
290-
-- genPkgDesc <- readGenericPackageDescription silent fp
291290
pure $ J.List $ makeCompletionItems completions
292291
| otherwise = pure $ J.List []
293292
where

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

Lines changed: 119 additions & 94 deletions
Original file line numberDiff line numberDiff line change
@@ -18,6 +18,7 @@ import Distribution.CabalSpecVersion (CabalSpecVersion (CabalSpecV2_
1818
showCabalSpecVersion)
1919
import Distribution.Compat.Lens ((^.))
2020
import Ide.Plugin.Cabal.LicenseSuggest (licenseNames)
21+
import qualified Language.LSP.Types as Compls (CompletionItem (..))
2122
import qualified Language.LSP.Types as J
2223
import qualified Language.LSP.Types.Lens as JL
2324
import qualified Language.LSP.VFS as VFS
@@ -44,16 +45,17 @@ data CabalCompletionItem = CabalCompletionItem
4445

4546
{- | The context a cursor can be in within a cabal file,
4647
we can be in stanzas or the top level,
47-
and additionally we can be in a context where we have already written a keyword
48-
but no value for it yet
48+
and additionally we can be in a context where we have already
49+
written a keyword but no value for it yet
4950
-}
5051
type Context = (LevelContext, KeyWordContext)
5152

5253
-- | Context inside a cabal file, used to decide which keywords to suggest
5354
data LevelContext
5455
= -- | Top level context in a cabal file such as 'author'
5556
TopLevel
56-
| -- | Nested context in a cabal file, such as 'library', which has nested keywords, specific to the stanza
57+
| -- | Nested context in a cabal file, such as 'library',
58+
-- which has nested keywords, specific to the stanza
5759
Stanza T.Text
5860
deriving (Eq, Show, Read)
5961

@@ -62,7 +64,7 @@ data LevelContext
6264
-}
6365
data KeyWordContext
6466
= -- | Key word context, where a keyword
65-
-- occurs right before the current position
67+
-- occurs right before the current position,
6668
-- with no value associated to it
6769
KeyWord T.Text
6870
| -- | Keyword context where no keyword occurs
@@ -113,9 +115,10 @@ contextToCompleter (Stanza s, KeyWord kw) =
113115
Nothing -> noopCompleter
114116
Just l -> l
115117

116-
{- | Takes info about the current cursor position, information
117-
about the handled cabal file and a set of possible keywords
118-
and creates completion suggestions that fit the current input from the given list
118+
{- | Takes info about the current cursor position,
119+
the handled cabal file and a set of possible keywords
120+
and creates completion suggestions that fit the current input
121+
from the given list
119122
-}
120123
makeCompletionItems :: [CabalCompletionItem] -> [J.CompletionItem]
121124
makeCompletionItems l = map buildCompletion l
@@ -139,15 +142,18 @@ getContext pos ls =
139142
kwContext <- getKeyWordContext pos ls m
140143
pure (Stanza s, kwContext)
141144
where
142-
lvlContext = if pos ^. JL.character == 0 then TopLevel else findCurrentLevel (getPreviousLines pos ls)
145+
lvlContext =
146+
if pos ^. JL.character == 0
147+
then TopLevel
148+
else currentLevel (previousLines pos ls)
143149

144150
-- ----------------------------------------------------------------
145151
-- Helper Functions
146152
-- ----------------------------------------------------------------
147153

148-
{- | Takes a position, a list of lines (representing a file) and a map of keywords as keys
149-
and returns a keyword context if there is a keyword from the map before the current position
150-
in the given line list
154+
{- | Takes a position, a list of lines (representing a file)
155+
and a map of keywords and returns a keyword context if the
156+
previously written keyword matches one in the map
151157
-}
152158
getKeyWordContext :: Position -> [T.Text] -> Map T.Text a -> Maybe KeyWordContext
153159
getKeyWordContext pos ls keywords = do
@@ -157,42 +163,58 @@ getKeyWordContext pos ls keywords = do
157163
let (whiteSpaces, lastLine) = T.span (== ' ') lastLine'
158164
let keywordIndentation = T.length whiteSpaces
159165
let cursorIndentation = fromIntegral (pos ^. JL.character)
160-
-- in order to be in a keyword context the cursor needs to be indented more than the keyword
166+
-- in order to be in a keyword context the cursor needs
167+
-- to be indented more than the keyword
161168
if cursorIndentation > keywordIndentation
162-
then -- if the last thing written was a keyword without a value
169+
then
170+
-- if the last thing written was a keyword without a value
163171
case List.find (`T.isPrefixOf` lastLine) (Map.keys keywords) of
164172
Nothing -> Just None
165173
Just kw -> Just $ KeyWord kw
166174
else Just None
167175
where
168176
lastNonEmptyLineM = do
169177
cur <- currentLineM
170-
List.find (not . T.null . T.stripEnd) $ cur : getPreviousLines pos ls
178+
List.find (not . T.null . T.stripEnd) $ cur : previousLines pos ls
171179
currentLineM = ls Extra.!? (fromIntegral $ pos ^. JL.line)
172180

173181
{- | Parse the given set of lines (starting before current cursor position
174182
up to the start of the file) to find the nearest stanza declaration,
175-
if none is found we are in the top level
183+
if none is found we are in the top level context
176184
-}
177-
findCurrentLevel :: [T.Text] -> LevelContext
178-
findCurrentLevel [] = TopLevel
179-
findCurrentLevel (cur : xs)
185+
currentLevel :: [T.Text] -> LevelContext
186+
currentLevel [] = TopLevel
187+
currentLevel (cur : xs)
180188
| Just s <- stanza = Stanza s
181-
| otherwise = findCurrentLevel xs
189+
| otherwise = currentLevel xs
182190
where
183191
stanza = List.find (`T.isPrefixOf` cur) (Map.keys stanzaKeywordMap)
184192

193+
{- | Returns a CabalCompletionItem with the given starting position
194+
and text to be inserted,
195+
where the displayed text is the same as the inserted text
196+
-}
197+
makeSimpleCabalCompletionItem :: Range -> T.Text -> CabalCompletionItem
198+
makeSimpleCabalCompletionItem r txt = CabalCompletionItem txt Nothing r
199+
200+
{- | Returns a CabalCompletionItem with the given starting position,
201+
text to be inserted and text to be displayed in the completion suggestion
202+
-}
203+
makeCabalCompletionItem :: Range -> T.Text -> T.Text -> CabalCompletionItem
204+
makeCabalCompletionItem r insertTxt displayTxt =
205+
CabalCompletionItem insertTxt (Just displayTxt) r
206+
185207
{- | Get all lines before the given cursor position in the given file
186-
and reverse them in order to traverse backwards starting from the current position
208+
and reverse their order to traverse backwards starting from the current position
187209
-}
188-
getPreviousLines :: Position -> [T.Text] -> [T.Text]
189-
getPreviousLines pos ls = reverse $ take (fromIntegral currentLine) ls
210+
previousLines :: Position -> [T.Text] -> [T.Text]
211+
previousLines pos ls = reverse $ take (fromIntegral currentLine) ls
190212
where
191213
currentLine = pos ^. JL.line
192214

193215
{- | Takes information about the current file's file path,
194216
the current cursor position in the file
195-
and its contents and builds a CabalCompletionItem
217+
and its contents; and builds a CabalCompletionItem
196218
with the prefix up to that cursor position,
197219
checks whether a suffix needs to be completed,
198220
and calculates the range in the document in which to complete
@@ -207,56 +229,54 @@ getFilePathCompletionContext dir prefixInfo =
207229
}
208230
where
209231
completionEnd = VFS.cursorPos prefixInfo
210-
completionStart = Position (_line completionEnd) (_character completionEnd - (fromIntegral $ T.length filepathPrefix))
211-
filepathPrefix = T.takeWhileEnd (not . (`elem` stopConditionChars)) prevLineText
212-
(prevLineText, endLineText) = T.splitAt cursorColumn $ VFS.fullLine prefixInfo
213-
suffix = if (apostropheOrSpaceSeparator == '\"') && even (T.count "\"" endLineText) then "\"" else ""
232+
completionStart =
233+
Position
234+
(_line completionEnd)
235+
(_character completionEnd - (fromIntegral $ T.length filepathPrefix))
236+
filepathPrefix = T.takeWhileEnd (not . (`elem` stopConditionChars)) beforeCursorText
237+
(beforeCursorText, afterCursorText) = T.splitAt cursorColumn $ VFS.fullLine prefixInfo
238+
suffix =
239+
if apostropheOrSpaceSeparator == '\"' && even (T.count "\"" afterCursorText)
240+
then "\""
241+
else ""
242+
apostropheOrSpaceSeparator =
243+
if odd $ T.count "\"" beforeCursorText
244+
then '\"'
245+
else ' '
214246
cursorColumn = fromIntegral $ VFS.cursorPos prefixInfo ^. JL.character
215247
-- if the filepath is inside apostrophes, we parse until the apostrophe,
216-
-- otherwise space is a separator
217-
apostropheOrSpaceSeparator = if odd $ T.count "\"" prevLineText then '\"' else ' '
248+
-- otherwise we parse until a space occurs
218249
stopConditionChars = apostropheOrSpaceSeparator : [',']
219250

220251
buildCompletion :: CabalCompletionItem -> J.CompletionItem
221252
buildCompletion completionItem =
222253
J.CompletionItem
223-
toDisplay
224-
(Just J.CiKeyword)
225-
Nothing
226-
Nothing
227-
Nothing
228-
Nothing
229-
Nothing
230-
Nothing
231-
Nothing
232-
Nothing
233-
Nothing
234-
Nothing
235-
(Just $ J.CompletionEditText (J.TextEdit (itemRange completionItem) $ itemInsert completionItem))
236-
Nothing
237-
Nothing
238-
Nothing
239-
Nothing
254+
{
255+
Compls._label = toDisplay,
256+
Compls._kind = Just J.CiKeyword,
257+
Compls._tags = Nothing,
258+
Compls._detail = Nothing,
259+
Compls._documentation = Nothing,
260+
Compls._deprecated = Nothing,
261+
Compls._preselect = Nothing,
262+
Compls._sortText = Nothing,
263+
Compls._filterText = Nothing,
264+
Compls._insertText = Nothing,
265+
Compls._insertTextFormat = Nothing,
266+
Compls._insertTextMode = Nothing,
267+
Compls._textEdit = Just $ J.CompletionEditText (J.TextEdit (itemRange completionItem) $ itemInsert completionItem),
268+
Compls._additionalTextEdits = Nothing,
269+
Compls._commitCharacters = Nothing,
270+
Compls._command = Nothing,
271+
Compls._xdata = Nothing
272+
}
240273
where
241274
toDisplay = fromMaybe (itemInsert completionItem) (itemDisplay completionItem)
242275

243276
-- ----------------------------------------------------------------
244-
-- Completor API
277+
-- Completer API
245278
-- ----------------------------------------------------------------
246279

247-
{- | Returns a CabalCompletionItem with the given starting position
248-
and text to be inserted where the displayed text is the same as the inserted text
249-
after the inserted text
250-
-}
251-
makeSimpleCabalCompletionItem :: Range -> T.Text -> CabalCompletionItem
252-
makeSimpleCabalCompletionItem r txt = CabalCompletionItem txt Nothing r
253-
254-
{- | Returns a CabalCompletionItem with the given starting position,
255-
text to be inserted and text to be displayed in the completion suggestion
256-
-}
257-
makeCabalCompletionItem :: Range -> T.Text -> T.Text -> CabalCompletionItem
258-
makeCabalCompletionItem r insertTxt displayTxt = CabalCompletionItem insertTxt (Just displayTxt) r
259-
260280
{- | Completer to be used when no completion suggestions
261281
are implemented for the field
262282
-}
@@ -272,9 +292,8 @@ constantCompleter completions ctxInfo = do
272292
let range = completionRange ctxInfo
273293
pure $ map (makeSimpleCabalCompletionItem range . Fuzzy.original) scored
274294

275-
276295
{- | Completer to be used when a file path can be
277-
completed for the field, takes the file path of the directory to start from,
296+
completed for a field, takes the file path of the directory to start from,
278297
completes file paths as well as directories
279298
-}
280299
filePathCompleter :: Completer
@@ -290,9 +309,9 @@ filePathCompleter ctx = do
290309
fullFilePath <- makeFullFilePath suffix compl complInfo
291310
pure $ makeCabalCompletionItem (completionRange ctx) fullFilePath fullFilePath
292311
)
293-
where
312+
where
294313
-- | Takes a suffix, a completed path and a pathCompletionInfo and
295-
-- generates the whole filepath including the already written prefix
314+
-- generates the whole filepath including the already written prefix
296315
-- and the suffix in case the completed path is a filepath
297316
makeFullFilePath :: T.Text -> T.Text -> PathCompletionInfo -> IO T.Text
298317
makeFullFilePath suffix' completion' complInfo = do
@@ -301,30 +320,6 @@ filePathCompleter ctx = do
301320
let fullPath = if isFilePath then fullPath' ++ T.unpack suffix' else fullPath'
302321
pure $ T.pack fullPath
303322

304-
{- | Takes a path completion info and returns the list of files
305-
in the directory the path completion info describes
306-
-}
307-
listFileCompletions :: PathCompletionInfo -> IO [FilePath]
308-
listFileCompletions complInfo = do
309-
try (evaluate =<< listDirectory (mkCompletionDirectory complInfo)) >>= \case
310-
Right dirs -> do
311-
fixedDirs <- mapM
312-
(\d -> do
313-
isDir <- doesDirectoryExist $ mkDirFromCWD complInfo d
314-
pure $ if isDir then Posix.addTrailingPathSeparator d else d
315-
)
316-
dirs
317-
pure fixedDirs
318-
Left (_::IOError) -> pure []
319-
320-
{- | Returns a list of all directories in the directory
321-
described by path completion info
322-
-}
323-
listDirectoryCompletions :: PathCompletionInfo -> IO [FilePath]
324-
listDirectoryCompletions complInfo = do
325-
filepaths <- listFileCompletions complInfo
326-
filterM (doesDirectoryExist . mkDirFromCWD complInfo) filepaths
327-
328323
{- | Completer to be used when a directory can be completed for the field,
329324
takes the file path of the directory to start from,
330325
only completes directories
@@ -342,13 +337,36 @@ directoryCompleter ctx = do
342337
pure $ makeCabalCompletionItem (completionRange ctx) fullDirPath fullDirPath
343338
)
344339
where
345-
-- | Takes a directory and PathCompletionInfo and
340+
-- | Takes a directory and PathCompletionInfo and
346341
-- returns the whole path including the prefix that was already written
347342
makeFullDirPath :: T.Text -> PathCompletionInfo -> IO T.Text
348343
makeFullDirPath completion' complInfo = do
349344
let fullPath = prefixPathInfo complInfo Posix.</> T.unpack completion'
350345
pure $ T.pack fullPath
351346

347+
{- | Takes a path completion info and returns the list of files
348+
in the directory the path completion info describes
349+
-}
350+
listFileCompletions :: PathCompletionInfo -> IO [FilePath]
351+
listFileCompletions complInfo = do
352+
try (evaluate =<< listDirectory (mkCompletionDirectory complInfo)) >>= \case
353+
Right dirs -> do
354+
fixedDirs <- mapM
355+
(\d -> do
356+
isDir <- doesDirectoryExist $ mkDirFromCWD complInfo d
357+
pure $ if isDir then Posix.addTrailingPathSeparator d else d
358+
)
359+
dirs
360+
pure fixedDirs
361+
Left (_::IOError) -> pure []
362+
363+
{- | Returns a list of all (and only) directories in the
364+
directory described by path completion info
365+
-}
366+
listDirectoryCompletions :: PathCompletionInfo -> IO [FilePath]
367+
listDirectoryCompletions complInfo = do
368+
filepaths <- listFileCompletions complInfo
369+
filterM (doesDirectoryExist . mkDirFromCWD complInfo) filepaths
352370

353371
pathCompletionInfoFromCompletionContext :: CabalCompletionContext -> PathCompletionInfo
354372
pathCompletionInfoFromCompletionContext ctx = PathCompletionInfo
@@ -360,14 +378,23 @@ pathCompletionInfoFromCompletionContext ctx = PathCompletionInfo
360378
dirNamePrefix = T.pack $ Posix.takeFileName prefix
361379
fp = Posix.takeDirectory $ completionCabalFilePath ctx
362380

363-
{- | Returns
381+
{- | Returns the directory, the currently handled cabal file is in,
382+
we let System.FilePath handle the separator syntax since this is used
383+
to query filepaths from the system
364384
-}
365385
mkCompletionDirectory :: PathCompletionInfo -> FilePath
366-
mkCompletionDirectory complInfo = FP.addTrailingPathSeparator $ cabalFilePathInfo complInfo FP.</> (FP.normalise $ prefixPathInfo complInfo)
386+
mkCompletionDirectory complInfo =
387+
FP.addTrailingPathSeparator
388+
$ cabalFilePathInfo complInfo FP.</> (FP.normalise $ prefixPathInfo complInfo)
367389

390+
{- | Returns the complete filepath for the given filepath,
391+
since cabal files only use posix syntax, and this is used for completions
392+
we use posix separators here
393+
-}
368394
mkDirFromCWD :: PathCompletionInfo -> FilePath -> FilePath
369395
mkDirFromCWD complInfo fp = Posix.addTrailingPathSeparator $ mkCompletionDirectory complInfo Posix.</> Posix.normalise fp
370396

397+
-- | Information used to query and build file path/directory completions
371398
data PathCompletionInfo = PathCompletionInfo
372399
{ prefixLeftOver :: T.Text
373400
-- ^ partly written start of next part of path
@@ -389,10 +416,8 @@ cabalVersionKeyword =
389416
constantCompleter $
390417
map (T.pack . showCabalSpecVersion) [CabalSpecV2_2 .. maxBound]
391418

392-
-- todo: we could add file path completion for file path fields
393-
-- we could add descriptions of field values and then show them when inside the field's context
394-
395419
-- | Top level keywords of a cabal file
420+
-- TODO: we could add descriptions of field values and then show them when inside the field's context
396421
cabalKeywords :: Map T.Text Completer
397422
cabalKeywords =
398423
Map.fromList

0 commit comments

Comments
 (0)