@@ -18,6 +18,7 @@ import Distribution.CabalSpecVersion (CabalSpecVersion (CabalSpecV2_
18
18
showCabalSpecVersion )
19
19
import Distribution.Compat.Lens ((^.) )
20
20
import Ide.Plugin.Cabal.LicenseSuggest (licenseNames )
21
+ import qualified Language.LSP.Types as Compls (CompletionItem (.. ))
21
22
import qualified Language.LSP.Types as J
22
23
import qualified Language.LSP.Types.Lens as JL
23
24
import qualified Language.LSP.VFS as VFS
@@ -44,16 +45,17 @@ data CabalCompletionItem = CabalCompletionItem
44
45
45
46
{- | The context a cursor can be in within a cabal file,
46
47
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
49
50
-}
50
51
type Context = (LevelContext , KeyWordContext )
51
52
52
53
-- | Context inside a cabal file, used to decide which keywords to suggest
53
54
data LevelContext
54
55
= -- | Top level context in a cabal file such as 'author'
55
56
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
57
59
Stanza T. Text
58
60
deriving (Eq , Show , Read )
59
61
@@ -62,7 +64,7 @@ data LevelContext
62
64
-}
63
65
data KeyWordContext
64
66
= -- | Key word context, where a keyword
65
- -- occurs right before the current position
67
+ -- occurs right before the current position,
66
68
-- with no value associated to it
67
69
KeyWord T. Text
68
70
| -- | Keyword context where no keyword occurs
@@ -113,9 +115,10 @@ contextToCompleter (Stanza s, KeyWord kw) =
113
115
Nothing -> noopCompleter
114
116
Just l -> l
115
117
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
119
122
-}
120
123
makeCompletionItems :: [CabalCompletionItem ] -> [J. CompletionItem ]
121
124
makeCompletionItems l = map buildCompletion l
@@ -139,15 +142,18 @@ getContext pos ls =
139
142
kwContext <- getKeyWordContext pos ls m
140
143
pure (Stanza s, kwContext)
141
144
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)
143
149
144
150
-- ----------------------------------------------------------------
145
151
-- Helper Functions
146
152
-- ----------------------------------------------------------------
147
153
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
151
157
-}
152
158
getKeyWordContext :: Position -> [T. Text ] -> Map T. Text a -> Maybe KeyWordContext
153
159
getKeyWordContext pos ls keywords = do
@@ -157,42 +163,58 @@ getKeyWordContext pos ls keywords = do
157
163
let (whiteSpaces, lastLine) = T. span (== ' ' ) lastLine'
158
164
let keywordIndentation = T. length whiteSpaces
159
165
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
161
168
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
163
171
case List. find (`T.isPrefixOf` lastLine) (Map. keys keywords) of
164
172
Nothing -> Just None
165
173
Just kw -> Just $ KeyWord kw
166
174
else Just None
167
175
where
168
176
lastNonEmptyLineM = do
169
177
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
171
179
currentLineM = ls Extra. !? (fromIntegral $ pos ^. JL. line)
172
180
173
181
{- | Parse the given set of lines (starting before current cursor position
174
182
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
176
184
-}
177
- findCurrentLevel :: [T. Text ] -> LevelContext
178
- findCurrentLevel [] = TopLevel
179
- findCurrentLevel (cur : xs)
185
+ currentLevel :: [T. Text ] -> LevelContext
186
+ currentLevel [] = TopLevel
187
+ currentLevel (cur : xs)
180
188
| Just s <- stanza = Stanza s
181
- | otherwise = findCurrentLevel xs
189
+ | otherwise = currentLevel xs
182
190
where
183
191
stanza = List. find (`T.isPrefixOf` cur) (Map. keys stanzaKeywordMap)
184
192
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
+
185
207
{- | 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
187
209
-}
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
190
212
where
191
213
currentLine = pos ^. JL. line
192
214
193
215
{- | Takes information about the current file's file path,
194
216
the current cursor position in the file
195
- and its contents and builds a CabalCompletionItem
217
+ and its contents; and builds a CabalCompletionItem
196
218
with the prefix up to that cursor position,
197
219
checks whether a suffix needs to be completed,
198
220
and calculates the range in the document in which to complete
@@ -207,56 +229,54 @@ getFilePathCompletionContext dir prefixInfo =
207
229
}
208
230
where
209
231
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 ' '
214
246
cursorColumn = fromIntegral $ VFS. cursorPos prefixInfo ^. JL. character
215
247
-- 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
218
249
stopConditionChars = apostropheOrSpaceSeparator : [' ,' ]
219
250
220
251
buildCompletion :: CabalCompletionItem -> J. CompletionItem
221
252
buildCompletion completionItem =
222
253
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
+ }
240
273
where
241
274
toDisplay = fromMaybe (itemInsert completionItem) (itemDisplay completionItem)
242
275
243
276
-- ----------------------------------------------------------------
244
- -- Completor API
277
+ -- Completer API
245
278
-- ----------------------------------------------------------------
246
279
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
-
260
280
{- | Completer to be used when no completion suggestions
261
281
are implemented for the field
262
282
-}
@@ -272,9 +292,8 @@ constantCompleter completions ctxInfo = do
272
292
let range = completionRange ctxInfo
273
293
pure $ map (makeSimpleCabalCompletionItem range . Fuzzy. original) scored
274
294
275
-
276
295
{- | 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,
278
297
completes file paths as well as directories
279
298
-}
280
299
filePathCompleter :: Completer
@@ -290,9 +309,9 @@ filePathCompleter ctx = do
290
309
fullFilePath <- makeFullFilePath suffix compl complInfo
291
310
pure $ makeCabalCompletionItem (completionRange ctx) fullFilePath fullFilePath
292
311
)
293
- where
312
+ where
294
313
-- | 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
296
315
-- and the suffix in case the completed path is a filepath
297
316
makeFullFilePath :: T. Text -> T. Text -> PathCompletionInfo -> IO T. Text
298
317
makeFullFilePath suffix' completion' complInfo = do
@@ -301,30 +320,6 @@ filePathCompleter ctx = do
301
320
let fullPath = if isFilePath then fullPath' ++ T. unpack suffix' else fullPath'
302
321
pure $ T. pack fullPath
303
322
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
-
328
323
{- | Completer to be used when a directory can be completed for the field,
329
324
takes the file path of the directory to start from,
330
325
only completes directories
@@ -342,13 +337,36 @@ directoryCompleter ctx = do
342
337
pure $ makeCabalCompletionItem (completionRange ctx) fullDirPath fullDirPath
343
338
)
344
339
where
345
- -- | Takes a directory and PathCompletionInfo and
340
+ -- | Takes a directory and PathCompletionInfo and
346
341
-- returns the whole path including the prefix that was already written
347
342
makeFullDirPath :: T. Text -> PathCompletionInfo -> IO T. Text
348
343
makeFullDirPath completion' complInfo = do
349
344
let fullPath = prefixPathInfo complInfo Posix. </> T. unpack completion'
350
345
pure $ T. pack fullPath
351
346
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
352
370
353
371
pathCompletionInfoFromCompletionContext :: CabalCompletionContext -> PathCompletionInfo
354
372
pathCompletionInfoFromCompletionContext ctx = PathCompletionInfo
@@ -360,14 +378,23 @@ pathCompletionInfoFromCompletionContext ctx = PathCompletionInfo
360
378
dirNamePrefix = T. pack $ Posix. takeFileName prefix
361
379
fp = Posix. takeDirectory $ completionCabalFilePath ctx
362
380
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
364
384
-}
365
385
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)
367
389
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
+ -}
368
394
mkDirFromCWD :: PathCompletionInfo -> FilePath -> FilePath
369
395
mkDirFromCWD complInfo fp = Posix. addTrailingPathSeparator $ mkCompletionDirectory complInfo Posix. </> Posix. normalise fp
370
396
397
+ -- | Information used to query and build file path/directory completions
371
398
data PathCompletionInfo = PathCompletionInfo
372
399
{ prefixLeftOver :: T. Text
373
400
-- ^ partly written start of next part of path
@@ -389,10 +416,8 @@ cabalVersionKeyword =
389
416
constantCompleter $
390
417
map (T. pack . showCabalSpecVersion) [CabalSpecV2_2 .. maxBound ]
391
418
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
-
395
419
-- | 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
396
421
cabalKeywords :: Map T. Text Completer
397
422
cabalKeywords =
398
423
Map. fromList
0 commit comments