Skip to content

Commit 5940164

Browse files
committed
Update to latest version of lsp libraries
1 parent f47bb47 commit 5940164

File tree

54 files changed

+243
-227
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

54 files changed

+243
-227
lines changed

cabal-ghc901.project

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -37,7 +37,7 @@ package *
3737

3838
write-ghc-environment-files: never
3939

40-
index-state: 2021-11-29T12:30:10Z
40+
index-state: 2021-12-29T12:30:08Z
4141

4242
constraints:
4343
-- These plugins don't work on GHC9 yet

cabal-ghc921.project

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -36,7 +36,7 @@ package *
3636

3737
write-ghc-environment-files: never
3838

39-
index-state: 2021-11-29T12:30:10Z
39+
index-state: 2021-12-29T12:30:08Z
4040

4141
constraints:
4242
-- These plugins doesn't work on GHC92 yet

cabal.project

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -40,7 +40,7 @@ package *
4040

4141
write-ghc-environment-files: never
4242

43-
index-state: 2021-11-29T12:30:10Z
43+
index-state: 2021-12-29T12:30:08Z
4444

4545
constraints:
4646
hyphenation +embed

ghcide/bench/example/HLS

Lines changed: 0 additions & 1 deletion
This file was deleted.

ghcide/bench/lib/Experiments.hs

Lines changed: 6 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -194,7 +194,7 @@ experiments =
194194
let edit :: TextDocumentContentChangeEvent =TextDocumentContentChangeEvent
195195
{ _range = Just Range {_start = bottom, _end = bottom}
196196
, _rangeLength = Nothing, _text = t}
197-
bottom = Position maxBoundUinteger 0
197+
bottom = Position maxBound 0
198198
t = T.unlines
199199
[""
200200
,"holef :: [Int] -> [Int]"
@@ -213,7 +213,7 @@ experiments =
213213
flip allM docs $ \DocumentPositions{..} -> do
214214
bottom <- pred . length . T.lines <$> documentContents doc
215215
diags <- getCurrentDiagnostics doc
216-
case requireDiagnostic diags (DsError, (bottom, 8), "Found hole", Nothing) of
216+
case requireDiagnostic diags (DsError, (fromIntegral bottom, 8), "Found hole", Nothing) of
217217
Nothing -> pure True
218218
Just _err -> pure False
219219
)
@@ -404,7 +404,7 @@ runBenchmarksFun dir allBenchmarks = do
404404
++ ["--verbose" | verbose ?config]
405405
++ ["--ot-memory-profiling" | Just _ <- [otMemoryProfiling ?config]]
406406
lspTestCaps =
407-
fullCaps {_window = Just $ WindowClientCapabilities $ Just True}
407+
fullCaps {_window = Just $ WindowClientCapabilities (Just True) Nothing Nothing }
408408
conf =
409409
defaultConfig
410410
{ logStdErr = verbose ?config,
@@ -585,7 +585,7 @@ setupDocumentContents config =
585585
doc <- openDoc m "haskell"
586586

587587
-- Setup the special positions used by the experiments
588-
lastLine <- length . T.lines <$> documentContents doc
588+
lastLine <- fromIntegral . length . T.lines <$> documentContents doc
589589
changeDoc doc [TextDocumentContentChangeEvent
590590
{ _range = Just (Range (Position lastLine 0) (Position lastLine 0))
591591
, _rangeLength = Nothing
@@ -638,9 +638,9 @@ searchSymbol doc@TextDocumentIdentifier{_uri} fileContents pos = do
638638
return res
639639
where
640640
loop pos
641-
| _line pos >= lll =
641+
| (fromIntegral $ _line pos) >= lll =
642642
return Nothing
643-
| _character pos >= lengthOfLine (_line pos) =
643+
| (fromIntegral $ _character pos) >= lengthOfLine (fromIntegral $ _line pos) =
644644
loop (nextLine pos)
645645
| otherwise = do
646646
checks <- checkDefinitions pos &&^ checkCompletions pos
@@ -663,7 +663,3 @@ searchSymbol doc@TextDocumentIdentifier{_uri} fileContents pos = do
663663
checkCompletions pos =
664664
not . null <$> getCompletions doc pos
665665

666-
-- | We don't have a uinteger type yet. So hardcode the maxBound of uinteger, 2 ^ 31 - 1
667-
-- as a constant.
668-
maxBoundUinteger :: Int
669-
maxBoundUinteger = 2147483647

ghcide/ghcide.cabal

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -65,8 +65,8 @@ library
6565
lens,
6666
list-t,
6767
hiedb == 0.4.1.*,
68-
lsp-types >= 1.3.0.1 && < 1.4,
69-
lsp == 1.2.*,
68+
lsp-types ^>= 1.4.0.0,
69+
lsp ^>= 1.4.0.0 ,
7070
monoid-subclasses,
7171
mtl,
7272
network-uri,

ghcide/src/Development/IDE/Core/Compile.hs

Lines changed: 6 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -564,6 +564,11 @@ indexHieFile se mod_summary srcPath !hash hf = do
564564
done <- readTVar indexCompleted
565565
remaining <- HashMap.size <$> readTVar indexPending
566566
pure (done, remaining)
567+
let
568+
progressFrac :: Double
569+
progressFrac = fromIntegral done / fromIntegral (done + remaining)
570+
progressPct :: LSP.UInt
571+
progressPct = floor $ 100 * progressFrac
567572

568573
whenJust (lspEnv se) $ \env -> whenJust tok $ \tok -> LSP.runLspT env $
569574
LSP.sendNotification LSP.SProgress $ LSP.ProgressParams tok $
@@ -572,7 +577,7 @@ indexHieFile se mod_summary srcPath !hash hf = do
572577
Percentage -> LSP.WorkDoneProgressReportParams
573578
{ _cancellable = Nothing
574579
, _message = Nothing
575-
, _percentage = Just (100 * fromIntegral done / fromIntegral (done + remaining) )
580+
, _percentage = Just progressPct
576581
}
577582
Explicit -> LSP.WorkDoneProgressReportParams
578583
{ _cancellable = Nothing

ghcide/src/Development/IDE/Core/PositionMapping.hs

Lines changed: 28 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -31,7 +31,8 @@ import Data.List
3131
import qualified Data.Text as T
3232
import qualified Data.Vector.Unboxed as V
3333
import Language.LSP.Types (Position (Position), Range (Range),
34-
TextDocumentContentChangeEvent (TextDocumentContentChangeEvent))
34+
TextDocumentContentChangeEvent (TextDocumentContentChangeEvent),
35+
UInt)
3536

3637
-- | Either an exact position, or the range of text that was substituted
3738
data PositionResult a
@@ -140,14 +141,17 @@ toCurrent (Range start@(Position startLine startColumn) end@(Position endLine en
140141
where
141142
lineDiff = linesNew - linesOld
142143
linesNew = T.count "\n" t
143-
linesOld = endLine - startLine
144+
linesOld = fromIntegral endLine - fromIntegral startLine
145+
newEndColumn :: UInt
144146
newEndColumn
145-
| linesNew == 0 = startColumn + T.length t
146-
| otherwise = T.length $ T.takeWhileEnd (/= '\n') t
147+
| linesNew == 0 = fromIntegral $ fromIntegral startColumn + T.length t
148+
| otherwise = fromIntegral $ T.length $ T.takeWhileEnd (/= '\n') t
149+
newColumn :: UInt
147150
newColumn
148-
| line == endLine = column + newEndColumn - endColumn
151+
| line == endLine = fromIntegral $ (fromIntegral column + newEndColumn) - fromIntegral endColumn
149152
| otherwise = column
150-
newLine = line + lineDiff
153+
newLine :: UInt
154+
newLine = fromIntegral $ fromIntegral line + lineDiff
151155

152156
fromCurrent :: Range -> T.Text -> Position -> PositionResult Position
153157
fromCurrent (Range start@(Position startLine startColumn) end@(Position endLine endColumn)) t (Position line column)
@@ -163,19 +167,23 @@ fromCurrent (Range start@(Position startLine startColumn) end@(Position endLine
163167
where
164168
lineDiff = linesNew - linesOld
165169
linesNew = T.count "\n" t
166-
linesOld = endLine - startLine
167-
newEndLine = endLine + lineDiff
170+
linesOld = fromIntegral endLine - fromIntegral startLine
171+
newEndLine :: UInt
172+
newEndLine = fromIntegral $ fromIntegral endLine + lineDiff
173+
newEndColumn :: UInt
168174
newEndColumn
169-
| linesNew == 0 = startColumn + T.length t
170-
| otherwise = T.length $ T.takeWhileEnd (/= '\n') t
175+
| linesNew == 0 = fromIntegral $ fromIntegral startColumn + T.length t
176+
| otherwise = fromIntegral $ T.length $ T.takeWhileEnd (/= '\n') t
177+
newColumn :: UInt
171178
newColumn
172-
| line == newEndLine = column - (newEndColumn - endColumn)
179+
| line == newEndLine = fromIntegral $ (fromIntegral column + fromIntegral endColumn) - newEndColumn
173180
| otherwise = column
174-
newLine = line - lineDiff
181+
newLine :: UInt
182+
newLine = fromIntegral $ fromIntegral line - lineDiff
175183

176184
deltaFromDiff :: T.Text -> T.Text -> PositionDelta
177185
deltaFromDiff (T.lines -> old) (T.lines -> new) =
178-
PositionDelta (lookupPos lnew o2nPrevs o2nNexts old2new) (lookupPos lold n2oPrevs n2oNexts new2old)
186+
PositionDelta (lookupPos (fromIntegral lnew) o2nPrevs o2nNexts old2new) (lookupPos (fromIntegral lold) n2oPrevs n2oNexts new2old)
179187
where
180188
!lnew = length new
181189
!lold = length old
@@ -194,17 +202,16 @@ deltaFromDiff (T.lines -> old) (T.lines -> new) =
194202
f :: Int -> Int -> Int
195203
f !a !b = if b == -1 then a else b
196204

197-
lookupPos :: Int -> V.Vector Int -> V.Vector Int -> V.Vector Int -> Position -> PositionResult Position
205+
lookupPos :: UInt -> V.Vector Int -> V.Vector Int -> V.Vector Int -> Position -> PositionResult Position
198206
lookupPos end prevs nexts xs (Position line col)
199-
| line < 0 = PositionRange (Position 0 0) (Position 0 0)
200-
| line >= V.length xs = PositionRange (Position end 0) (Position end 0)
201-
| otherwise = case V.unsafeIndex xs line of
207+
| line >= fromIntegral (V.length xs) = PositionRange (Position end 0) (Position end 0)
208+
| otherwise = case V.unsafeIndex xs (fromIntegral line) of
202209
-1 ->
203210
-- look for the previous and next lines that mapped successfully
204-
let !prev = 1 + V.unsafeIndex prevs line
205-
!next = V.unsafeIndex nexts line
206-
in PositionRange (Position prev 0) (Position next 0)
207-
line' -> PositionExact (Position line' col)
211+
let !prev = 1 + V.unsafeIndex prevs (fromIntegral line)
212+
!next = V.unsafeIndex nexts (fromIntegral line)
213+
in PositionRange (Position (fromIntegral prev) 0) (Position (fromIntegral next) 0)
214+
line' -> PositionExact (Position (fromIntegral line') col)
208215

209216
-- Construct a mapping between lines in the diff
210217
-- -1 for unsucessful mapping

ghcide/src/Development/IDE/Core/ProgressReporting.hs

Lines changed: 9 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -152,13 +152,17 @@ delayedProgressReporting before after lspEnv optProgressStyle = do
152152
}
153153
loop _ _ | optProgressStyle == NoProgress =
154154
forever $ liftIO $ threadDelay maxBound
155-
loop id prev = do
155+
loop id prevPct = do
156156
done <- liftIO $ readTVarIO doneVar
157157
todo <- liftIO $ readTVarIO todoVar
158158
liftIO $ sleep after
159159
if todo == 0 then loop id 0 else do
160-
let next = 100 * fromIntegral done / fromIntegral todo
161-
when (next /= prev) $
160+
let
161+
nextFrac :: Double
162+
nextFrac = fromIntegral done / fromIntegral todo
163+
nextPct :: UInt
164+
nextPct = floor $ 100 * nextFrac
165+
when (nextPct /= prevPct) $
162166
LSP.sendNotification LSP.SProgress $
163167
LSP.ProgressParams
164168
{ _token = id
@@ -171,11 +175,11 @@ delayedProgressReporting before after lspEnv optProgressStyle = do
171175
Percentage -> LSP.WorkDoneProgressReportParams
172176
{ _cancellable = Nothing
173177
, _message = Nothing
174-
, _percentage = Just next
178+
, _percentage = Just nextPct
175179
}
176180
NoProgress -> error "unreachable"
177181
}
178-
loop id next
182+
loop id nextPct
179183

180184
updateStateForFile inProgress file = actionBracket (f succ) (const $ f pred) . const
181185
-- This functions are deliberately eta-expanded to avoid space leaks.

ghcide/src/Development/IDE/Core/RuleTypes.hs

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -43,7 +43,8 @@ import Development.IDE.Spans.Common
4343
import Development.IDE.Spans.LocalBindings
4444
import Development.IDE.Types.Diagnostics
4545
import GHC.Serialized (Serialized)
46-
import Language.LSP.Types (NormalizedFilePath)
46+
import Language.LSP.Types (Int32,
47+
NormalizedFilePath)
4748

4849
data LinkableType = ObjectLinkable | BCOLinkable
4950
deriving (Eq,Ord,Show, Generic)
@@ -290,13 +291,13 @@ pattern GetModificationTime = GetModificationTime_ {missingFileDiagnostics=True}
290291
type instance RuleResult GetModificationTime = FileVersion
291292

292293
data FileVersion
293-
= VFSVersion !Int
294+
= VFSVersion !Int32
294295
| ModificationTime !POSIXTime
295296
deriving (Show, Generic)
296297

297298
instance NFData FileVersion
298299

299-
vfsVersion :: FileVersion -> Maybe Int
300+
vfsVersion :: FileVersion -> Maybe Int32
300301
vfsVersion (VFSVersion i) = Just i
301302
vfsVersion ModificationTime{} = Nothing
302303

ghcide/src/Development/IDE/Core/Shake.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1176,7 +1176,7 @@ updateFileDiagnostics fp k ShakeExtras{logger, diagnostics, hiddenDiagnostics, p
11761176
logInfo logger $ showDiagnosticsColored $ map (fp,ShowDiag,) newDiags
11771177
Just env -> LSP.runLspT env $
11781178
LSP.sendNotification LSP.STextDocumentPublishDiagnostics $
1179-
LSP.PublishDiagnosticsParams (fromNormalizedUri uri) ver (List newDiags)
1179+
LSP.PublishDiagnosticsParams (fromNormalizedUri uri) (fmap fromIntegral ver) (List newDiags)
11801180
return action
11811181

11821182
newtype Priority = Priority Double

ghcide/src/Development/IDE/GHC/Error.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -79,7 +79,7 @@ realSrcSpanToRange real =
7979

8080
realSrcLocToPosition :: RealSrcLoc -> Position
8181
realSrcLocToPosition real =
82-
Position (srcLocLine real - 1) (srcLocCol real - 1)
82+
Position (fromIntegral $ srcLocLine real - 1) (fromIntegral $ srcLocCol real - 1)
8383

8484
-- | Extract a file name from a GHC SrcSpan (use message for unhelpful ones)
8585
-- FIXME This may not be an _absolute_ file name, needs fixing.
@@ -111,7 +111,7 @@ rangeToRealSrcSpan nfp =
111111

112112
positionToRealSrcLoc :: NormalizedFilePath -> Position -> RealSrcLoc
113113
positionToRealSrcLoc nfp (Position l c)=
114-
Compat.mkRealSrcLoc (fromString $ fromNormalizedFilePath nfp) (l + 1) (c + 1)
114+
Compat.mkRealSrcLoc (fromString $ fromNormalizedFilePath nfp) (fromIntegral $ l + 1) (fromIntegral $ c + 1)
115115

116116
isInsideSrcSpan :: Position -> SrcSpan -> Bool
117117
p `isInsideSrcSpan` r = case srcSpanToRange r of

ghcide/src/Development/IDE/LSP/Outline.hs

Lines changed: 1 addition & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -46,13 +46,7 @@ moduleOutline ideState DocumentSymbolParams{ _textDocument = TextDocumentIdentif
4646
(defDocumentSymbol l :: DocumentSymbol)
4747
{ _name = pprText m
4848
, _kind = SkFile
49-
, _range = Range (Position 0 0) (Position 2147483647 0) -- _ltop is 0 0 0 0
50-
-- In the lsp spec from 3.16 Position takes a uinteger,
51-
-- where uinteger is 0 - 2^31 - 1. lsp-types currently has the type of line
52-
-- as Int. So instead of using `maxBound :: Int` we hardcode the maxBound of
53-
-- uinteger. 2 ^ 31 - 1 == 2147483647
54-
-- Check this issue for tracking https://github.com/haskell/lsp/issues/354
55-
-- the change in lsp-types.
49+
, _range = Range (Position 0 0) (Position maxBound 0) -- _ltop is 0 0 0 0
5650
}
5751
_ -> Nothing
5852
importSymbols = maybe [] pure $

ghcide/src/Development/IDE/Plugin/CodeAction.hs

Lines changed: 7 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -71,6 +71,7 @@ import Language.LSP.Types (CodeAction (
7171
SMethod (STextDocumentCodeAction),
7272
TextDocumentIdentifier (TextDocumentIdentifier),
7373
TextEdit (TextEdit),
74+
UInt,
7475
WorkspaceEdit (WorkspaceEdit, _changeAnnotations, _changes, _documentChanges),
7576
type (|?) (InR),
7677
uriToFilePath)
@@ -1095,8 +1096,8 @@ suggestInstanceConstraint df (L _ HsModule {hsmodDecls}) Diagnostic {..} missing
10951096
| otherwise
10961097
= Nothing
10971098

1098-
readPositionNumber :: T.Text -> Int
1099-
readPositionNumber = T.unpack >>> read
1099+
readPositionNumber :: T.Text -> UInt
1100+
readPositionNumber = T.unpack >>> read @Integer >>> fromIntegral
11001101

11011102
actionTitle :: T.Text -> T.Text
11021103
actionTitle constraint = "Add `" <> constraint
@@ -1305,9 +1306,10 @@ newImportToEdit (unNewImport -> imp) ps fileContents
13051306
-- * otherwise inserted one line after the last file-header pragma
13061307
newImportInsertRange :: ParsedSource -> T.Text -> Maybe (Range, Int)
13071308
newImportInsertRange (L _ HsModule {..}) fileContents
1308-
| Just (uncurry Position -> insertPos, col) <- case hsmodImports of
1309+
| Just ((l, c), col) <- case hsmodImports of
13091310
[] -> findPositionNoImports hsmodName hsmodExports fileContents
13101311
_ -> findPositionFromImportsOrModuleDecl hsmodImports last True
1312+
, let insertPos = Position (fromIntegral l) (fromIntegral c)
13111313
= Just (Range insertPos insertPos, col)
13121314
| otherwise = Nothing
13131315

@@ -1505,15 +1507,15 @@ extendToWholeLineIfPossible contents range@Range{..} =
15051507
in if extend then Range _start (Position (_line _end + 1) 0) else range
15061508

15071509
splitTextAtPosition :: Position -> T.Text -> (T.Text, T.Text)
1508-
splitTextAtPosition (Position row col) x
1510+
splitTextAtPosition (Position (fromIntegral -> row) (fromIntegral -> col)) x
15091511
| (preRow, mid:postRow) <- splitAt row $ T.splitOn "\n" x
15101512
, (preCol, postCol) <- T.splitAt col mid
15111513
= (T.intercalate "\n" $ preRow ++ [preCol], T.intercalate "\n" $ postCol : postRow)
15121514
| otherwise = (x, T.empty)
15131515

15141516
-- | Returns [start .. end[
15151517
textInRange :: Range -> T.Text -> T.Text
1516-
textInRange (Range (Position startRow startCol) (Position endRow endCol)) text =
1518+
textInRange (Range (Position (fromIntegral -> startRow) (fromIntegral -> startCol)) (Position (fromIntegral -> endRow) (fromIntegral -> endCol))) text =
15171519
case compare startRow endRow of
15181520
LT ->
15191521
let (linesInRangeBeforeEndLine, endLineAndFurtherLines) = splitAt (endRow - startRow) linesBeginningWithStartLine

ghcide/src/Development/IDE/Plugin/Completions/Logic.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -696,8 +696,8 @@ uniqueCompl candidate unique =
696696
-- ---------------------------------------------------------------------
697697

698698
hasTrailingBacktick :: T.Text -> Position -> Bool
699-
hasTrailingBacktick line Position { _character }
700-
| T.length line > _character = (line `T.index` _character) == '`'
699+
hasTrailingBacktick line Position { _character=(fromIntegral -> c) }
700+
| T.length line > c = (line `T.index` c) == '`'
701701
| otherwise = False
702702

703703
isUsedAsInfix :: T.Text -> T.Text -> T.Text -> Position -> Maybe Backtick
@@ -710,7 +710,7 @@ isUsedAsInfix line prefixMod prefixText pos
710710
hasClosingBacktick = hasTrailingBacktick line pos
711711

712712
openingBacktick :: T.Text -> T.Text -> T.Text -> Position -> Bool
713-
openingBacktick line prefixModule prefixText Position { _character }
713+
openingBacktick line prefixModule prefixText Position { _character=(fromIntegral -> c) }
714714
| backtickIndex < 0 || backtickIndex > T.length line = False
715715
| otherwise = (line `T.index` backtickIndex) == '`'
716716
where
@@ -723,7 +723,7 @@ openingBacktick line prefixModule prefixText Position { _character }
723723
else T.length prefixModule + 1 {- Because of "." -}
724724
in
725725
-- Points to the first letter of either the module or prefix text
726-
_character - (prefixLength + moduleLength) - 1
726+
c - (prefixLength + moduleLength) - 1
727727

728728

729729
-- ---------------------------------------------------------------------

ghcide/src/Development/IDE/Plugin/TypeLenses.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -174,7 +174,7 @@ suggestLocalSignature isQuickFix mTmr mBindings Diagnostic{_message, _range = _r
174174
, startOfLine <- Position (_line _start) startCharacter
175175
, beforeLine <- Range startOfLine startOfLine
176176
, title <- if isQuickFix then "add signature: " <> signature else signature
177-
, action <- TextEdit beforeLine $ signature <> "\n" <> T.replicate startCharacter " " =
177+
, action <- TextEdit beforeLine $ signature <> "\n" <> T.replicate (fromIntegral startCharacter) " " =
178178
[(title, [action])]
179179
| otherwise = []
180180

0 commit comments

Comments
 (0)