1
1
{-# LANGUAGE FlexibleContexts #-}
2
2
{-# LANGUAGE OverloadedStrings #-}
3
3
{-# LANGUAGE TypeFamilies #-}
4
+
4
5
module Ide.PluginUtils
5
6
( -- * LSP Range manipulation functions
6
7
normalize ,
7
8
extendNextLine ,
8
9
extendLineStart ,
10
+ extendToFullLines ,
9
11
WithDeletions (.. ),
10
12
getProcessID ,
11
13
makeDiffTextEdit ,
@@ -19,7 +21,7 @@ module Ide.PluginUtils
19
21
getPluginConfig ,
20
22
configForPlugin ,
21
23
pluginEnabled ,
22
- extractRange ,
24
+ extractTextInRange ,
23
25
fullRange ,
24
26
mkLspCommand ,
25
27
mkLspCmdId ,
@@ -36,12 +38,11 @@ module Ide.PluginUtils
36
38
handleMaybeM ,
37
39
throwPluginError ,
38
40
unescape ,
39
- )
41
+ )
40
42
where
41
43
42
-
43
44
import Control.Arrow ((&&&) )
44
- import Control.Lens (re , (^.) )
45
+ import Control.Lens (_head , _last , re , (%~) , (^.) )
45
46
import Control.Monad.Extra (maybeM )
46
47
import Control.Monad.Trans.Class (lift )
47
48
import Control.Monad.Trans.Except (ExceptT , runExceptT , throwE )
@@ -90,17 +91,33 @@ extendLineStart :: Range -> Range
90
91
extendLineStart (Range (Position sl _) e) =
91
92
Range (Position sl 0 ) e
92
93
94
+ -- | Extend 'Range' to include the start of the first line and start of the next line of the last line.
95
+ --
96
+ -- Caveat: It always extend the last line to the beginning of next line, even when the last position is at column 0.
97
+ -- This is to keep the compatibility with the implementation of old function @extractRange@.
98
+ --
99
+ -- >>> extendToFullLines (Range (Position 5 5) (Position 5 10))
100
+ -- Range (Position 5 0) (Position 6 0)
101
+ --
102
+ -- >>> extendToFullLines (Range (Position 5 5) (Position 7 2))
103
+ -- Range (Position 5 0) (Position 8 0)
104
+ --
105
+ -- >>> extendToFullLines (Range (Position 5 5) (Position 7 0))
106
+ -- Range (Position 5 0) (Position 8 0)
107
+ extendToFullLines :: Range -> Range
108
+ extendToFullLines = extendLineStart . extendNextLine
109
+
110
+
93
111
-- ---------------------------------------------------------------------
94
112
95
113
data WithDeletions = IncludeDeletions | SkipDeletions
96
- deriving Eq
114
+ deriving ( Eq )
97
115
98
116
-- | Generate a 'WorkspaceEdit' value from a pair of source Text
99
- diffText :: ClientCapabilities -> (VersionedTextDocumentIdentifier ,T. Text ) -> T. Text -> WithDeletions -> WorkspaceEdit
117
+ diffText :: ClientCapabilities -> (VersionedTextDocumentIdentifier , T. Text ) -> T. Text -> WithDeletions -> WorkspaceEdit
100
118
diffText clientCaps old new withDeletions =
101
- let
102
- supports = clientSupportsDocumentChanges clientCaps
103
- in diffText' supports old new withDeletions
119
+ let supports = clientSupportsDocumentChanges clientCaps
120
+ in diffText' supports old new withDeletions
104
121
105
122
makeDiffTextEdit :: T. Text -> T. Text -> [TextEdit ]
106
123
makeDiffTextEdit f1 f2 = diffTextEdit f1 f2 IncludeDeletions
@@ -114,13 +131,14 @@ diffTextEdit fText f2Text withDeletions = r
114
131
r = map diffOperationToTextEdit diffOps
115
132
d = getGroupedDiff (lines $ T. unpack fText) (lines $ T. unpack f2Text)
116
133
117
- diffOps = filter (\ x -> (withDeletions == IncludeDeletions ) || not (isDeletion x))
118
- (diffToLineRanges d)
134
+ diffOps =
135
+ filter
136
+ (\ x -> (withDeletions == IncludeDeletions ) || not (isDeletion x))
137
+ (diffToLineRanges d)
119
138
120
139
isDeletion (Deletion _ _) = True
121
140
isDeletion _ = False
122
141
123
-
124
142
diffOperationToTextEdit :: DiffOperation LineRange -> TextEdit
125
143
diffOperationToTextEdit (Change fm to) = TextEdit range nt
126
144
where
@@ -136,17 +154,20 @@ diffTextEdit fText f2Text withDeletions = r
136
154
-}
137
155
diffOperationToTextEdit (Deletion (LineRange (sl, el) _) _) = TextEdit range " "
138
156
where
139
- range = Range (Position (fromIntegral $ sl - 1 ) 0 )
140
- (Position (fromIntegral el) 0 )
141
-
157
+ range =
158
+ Range
159
+ (Position (fromIntegral $ sl - 1 ) 0 )
160
+ (Position (fromIntegral el) 0 )
142
161
diffOperationToTextEdit (Addition fm l) = TextEdit range nt
143
- -- fm has a range wrt to the changed file, which starts in the current file at l + 1
144
- -- So the range has to be shifted to start at l + 1
145
162
where
146
- range = Range (Position (fromIntegral l) 0 )
147
- (Position (fromIntegral l) 0 )
148
- nt = T. pack $ unlines $ lrContents fm
163
+ -- fm has a range wrt to the changed file, which starts in the current file at l + 1
164
+ -- So the range has to be shifted to start at l + 1
149
165
166
+ range =
167
+ Range
168
+ (Position (fromIntegral l) 0 )
169
+ (Position (fromIntegral l) 0 )
170
+ nt = T. pack $ unlines $ lrContents fm
150
171
151
172
calcRange fm = Range s e
152
173
where
@@ -155,20 +176,19 @@ diffTextEdit fText f2Text withDeletions = r
155
176
s = Position (fromIntegral $ sl - 1 ) sc -- Note: zero-based lines
156
177
el = snd $ lrNumbers fm
157
178
ec = fromIntegral $ length $ last $ lrContents fm
158
- e = Position (fromIntegral $ el - 1 ) ec -- Note: zero-based lines
159
-
179
+ e = Position (fromIntegral $ el - 1 ) ec -- Note: zero-based lines
160
180
161
181
-- | A pure version of 'diffText' for testing
162
- diffText' :: Bool -> (VersionedTextDocumentIdentifier ,T. Text ) -> T. Text -> WithDeletions -> WorkspaceEdit
163
- diffText' supports (verTxtDocId,fText) f2Text withDeletions =
182
+ diffText' :: Bool -> (VersionedTextDocumentIdentifier , T. Text ) -> T. Text -> WithDeletions -> WorkspaceEdit
183
+ diffText' supports (verTxtDocId, fText) f2Text withDeletions =
164
184
if supports
165
185
then WorkspaceEdit Nothing (Just docChanges) Nothing
166
186
else WorkspaceEdit (Just h) Nothing Nothing
167
187
where
168
188
diff = diffTextEdit fText f2Text withDeletions
169
189
h = M. singleton (verTxtDocId ^. L. uri) diff
170
190
docChanges = [InL docEdit]
171
- docEdit = TextDocumentEdit (verTxtDocId ^. re _versionedTextDocumentIdentifier) $ fmap InL diff
191
+ docEdit = TextDocumentEdit (verTxtDocId ^. re _versionedTextDocumentIdentifier) $ fmap InL diff
172
192
173
193
-- ---------------------------------------------------------------------
174
194
@@ -179,8 +199,7 @@ clientSupportsDocumentChanges caps =
179
199
wCaps <- mwCaps
180
200
WorkspaceEditClientCapabilities mDc _ _ _ _ <- _workspaceEdit wCaps
181
201
mDc
182
- in
183
- Just True == supports
202
+ in Just True == supports
184
203
185
204
-- ---------------------------------------------------------------------
186
205
@@ -191,22 +210,22 @@ idePluginsToPluginDesc :: IdePlugins ideState -> [PluginDescriptor ideState]
191
210
idePluginsToPluginDesc (IdePlugins pp) = pp
192
211
193
212
-- ---------------------------------------------------------------------
213
+
194
214
-- | Returns the current client configuration. It is not wise to permanently
195
215
-- cache the returned value of this function, as clients can at runtime change
196
216
-- their configuration.
197
- --
198
- getClientConfig :: MonadLsp Config m => m Config
217
+ getClientConfig :: (MonadLsp Config m ) => m Config
199
218
getClientConfig = getConfig
200
219
201
220
-- ---------------------------------------------------------------------
202
221
203
222
-- | Returns the current plugin configuration. It is not wise to permanently
204
223
-- cache the returned value of this function, as clients can change their
205
224
-- configuration at runtime.
206
- getPluginConfig :: MonadLsp Config m => PluginDescriptor c -> m PluginConfig
225
+ getPluginConfig :: ( MonadLsp Config m ) => PluginDescriptor c -> m PluginConfig
207
226
getPluginConfig plugin = do
208
- config <- getClientConfig
209
- return $ configForPlugin config plugin
227
+ config <- getClientConfig
228
+ return $ configForPlugin config plugin
210
229
211
230
-- ---------------------------------------------------------------------
212
231
@@ -223,24 +242,33 @@ usePropertyLsp kn pId p = do
223
242
224
243
-- ---------------------------------------------------------------------
225
244
226
- extractRange :: Range -> T. Text -> T. Text
227
- extractRange (Range (Position sl _) (Position el _)) s = newS
228
- where focusLines = take (fromIntegral $ el- sl+ 1 ) $ drop (fromIntegral sl) $ T. lines s
229
- newS = T. unlines focusLines
245
+ -- | Extracts exact matching text in the range.
246
+ extractTextInRange :: Range -> T. Text -> T. Text
247
+ extractTextInRange (Range (Position sl sc) (Position el ec)) s = newS
248
+ where
249
+ focusLines = take (fromIntegral $ el - sl + 1 ) $ drop (fromIntegral sl) $ T. lines s
250
+ -- NOTE: We have to trim the last line first to handle the single-line case
251
+ newS =
252
+ focusLines
253
+ & _last %~ T. take (fromIntegral ec)
254
+ & _head %~ T. drop (fromIntegral sc)
255
+ -- NOTE: We cannot use unlines here, because we don't want to add trailing newline!
256
+ & T. intercalate " \n "
230
257
231
258
-- | Gets the range that covers the entire text
232
259
fullRange :: T. Text -> Range
233
260
fullRange s = Range startPos endPos
234
- where startPos = Position 0 0
235
- endPos = Position lastLine 0
236
- {-
237
- In order to replace everything including newline characters,
238
- the end range should extend below the last line. From the specification:
239
- "If you want to specify a range that contains a line including
240
- the line ending character(s) then use an end position denoting
241
- the start of the next line"
242
- -}
243
- lastLine = fromIntegral $ length $ T. lines s
261
+ where
262
+ startPos = Position 0 0
263
+ endPos = Position lastLine 0
264
+ {-
265
+ In order to replace everything including newline characters,
266
+ the end range should extend below the last line. From the specification:
267
+ "If you want to specify a range that contains a line including
268
+ the line ending character(s) then use an end position denoting
269
+ the start of the next line"
270
+ -}
271
+ lastLine = fromIntegral $ length $ T. lines s
244
272
245
273
subRange :: Range -> Range -> Bool
246
274
subRange = isSubrangeOf
@@ -249,34 +277,34 @@ subRange = isSubrangeOf
249
277
250
278
allLspCmdIds' :: T. Text -> IdePlugins ideState -> [T. Text ]
251
279
allLspCmdIds' pid (IdePlugins ls) =
252
- allLspCmdIds pid $ map (pluginId &&& pluginCommands) ls
280
+ allLspCmdIds pid $ map (pluginId &&& pluginCommands) ls
253
281
254
282
allLspCmdIds :: T. Text -> [(PluginId , [PluginCommand ideState ])] -> [T. Text ]
255
283
allLspCmdIds pid commands = concatMap go commands
256
284
where
257
285
go (plid, cmds) = map (mkLspCmdId pid plid . commandId) cmds
258
286
259
-
260
287
-- ---------------------------------------------------------------------
261
288
262
- getNormalizedFilePath :: Monad m => Uri -> ExceptT String m NormalizedFilePath
263
- getNormalizedFilePath uri = handleMaybe errMsg
264
- $ uriToNormalizedFilePath
265
- $ toNormalizedUri uri
266
- where
267
- errMsg = T. unpack $ " Failed converting " <> getUri uri <> " to NormalizedFilePath"
289
+ getNormalizedFilePath :: (Monad m ) => Uri -> ExceptT String m NormalizedFilePath
290
+ getNormalizedFilePath uri =
291
+ handleMaybe errMsg $
292
+ uriToNormalizedFilePath $
293
+ toNormalizedUri uri
294
+ where
295
+ errMsg = T. unpack $ " Failed converting " <> getUri uri <> " to NormalizedFilePath"
268
296
269
297
-- ---------------------------------------------------------------------
270
- throwPluginError :: Monad m => String -> ExceptT String m b
298
+ throwPluginError :: ( Monad m ) => String -> ExceptT String m b
271
299
throwPluginError = throwE
272
300
273
- handleMaybe :: Monad m => e -> Maybe b -> ExceptT e m b
301
+ handleMaybe :: ( Monad m ) => e -> Maybe b -> ExceptT e m b
274
302
handleMaybe msg = maybe (throwE msg) return
275
303
276
- handleMaybeM :: Monad m => e -> m (Maybe b ) -> ExceptT e m b
304
+ handleMaybeM :: ( Monad m ) => e -> m (Maybe b ) -> ExceptT e m b
277
305
handleMaybeM msg act = maybeM (throwE msg) return $ lift act
278
306
279
- pluginResponse :: Monad m => ExceptT String m a -> m (Either ResponseError a )
307
+ pluginResponse :: ( Monad m ) => ExceptT String m a -> m (Either ResponseError a )
280
308
pluginResponse =
281
309
fmap (first (\ msg -> ResponseError (InR ErrorCodes_InternalError ) (fromString msg) Nothing ))
282
310
. runExceptT
@@ -290,9 +318,9 @@ type TextParser = P.Parsec Void T.Text
290
318
-- display as is.
291
319
unescape :: T. Text -> T. Text
292
320
unescape input =
293
- case P. runParser escapedTextParser " inline" input of
294
- Left _ -> input
295
- Right strs -> T. pack strs
321
+ case P. runParser escapedTextParser " inline" input of
322
+ Left _ -> input
323
+ Right strs -> T. pack strs
296
324
297
325
-- | Parser for a string that contains double quotes. Returns unescaped string.
298
326
escapedTextParser :: TextParser String
@@ -303,11 +331,11 @@ escapedTextParser = concat <$> P.many (outsideStringLiteral P.<|> stringLiteral)
303
331
304
332
stringLiteral :: TextParser String
305
333
stringLiteral = do
306
- inside <- P. char ' "' >> P. manyTill P. charLiteral (P. char ' "' )
307
- let f ' "' = " \\\" " -- double quote should still be escaped
308
- -- Despite the docs, 'showLitChar' and 'showLitString' from 'Data.Char' DOES ESCAPE unicode printable
309
- -- characters. So we need to call 'isPrint' from 'Data.Char' manually.
310
- f ch = if isPrint ch then [ch] else showLitChar ch " "
311
- inside' = concatMap f inside
312
-
313
- pure $ " \" " <> inside' <> " \" "
334
+ inside <- P. char ' "' >> P. manyTill P. charLiteral (P. char ' "' )
335
+ let f ' "' = " \\\" " -- double quote should still be escaped
336
+ -- Despite the docs, 'showLitChar' and 'showLitString' from 'Data.Char' DOES ESCAPE unicode printable
337
+ -- characters. So we need to call 'isPrint' from 'Data.Char' manually.
338
+ f ch = if isPrint ch then [ch] else showLitChar ch " "
339
+ inside' = concatMap f inside
340
+
341
+ pure $ " \" " <> inside' <> " \" "
0 commit comments