Skip to content

Commit 1713969

Browse files
author
kokobd
committed
upgrade lsp to 1.5
1 parent a89ba41 commit 1713969

File tree

16 files changed

+64
-48
lines changed

16 files changed

+64
-48
lines changed

cabal.project

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

4545
write-ghc-environment-files: never
4646

47-
index-state: 2022-06-12T00:00:00Z
47+
index-state: 2022-07-31T21:47:51Z
4848

4949
constraints:
5050
hyphenation +embed,

ghcide/ghcide.cabal

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -46,6 +46,7 @@ library
4646
binary,
4747
bytestring,
4848
case-insensitive,
49+
co-log-core,
4950
containers,
5051
data-default,
5152
deepseq,
@@ -69,8 +70,8 @@ library
6970
lens,
7071
list-t,
7172
hiedb == 0.4.1.*,
72-
lsp-types ^>= 1.4.0.1,
73-
lsp ^>= 1.4.0.0 ,
73+
lsp-types ^>= 1.5.0.0,
74+
lsp ^>= 1.5.0.0 ,
7475
monoid-subclasses,
7576
mtl,
7677
network-uri,
@@ -81,7 +82,7 @@ library
8182
random,
8283
regex-tdfa >= 1.3.1.0,
8384
retrie,
84-
rope-utf16-splay,
85+
text-rope,
8586
safe,
8687
safe-exceptions,
8788
hls-graph ^>= 1.7,

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

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -28,8 +28,8 @@ import Control.Exception
2828
import Control.Monad.Extra
2929
import Control.Monad.IO.Class
3030
import qualified Data.ByteString as BS
31-
import qualified Data.Rope.UTF16 as Rope
3231
import qualified Data.Text as T
32+
import qualified Data.Text.Utf16.Rope as Rope
3333
import Data.Time
3434
import Data.Time.Clock.POSIX
3535
import Development.IDE.Core.FileUtils
@@ -188,7 +188,7 @@ getFileContentsImpl file = do
188188
time <- use_ GetModificationTime file
189189
res <- do
190190
mbVirtual <- getVirtualFile file
191-
pure $ Rope.toText . _text <$> mbVirtual
191+
pure $ Rope.toText . _file_text <$> mbVirtual
192192
pure ([], Just (time, res))
193193

194194
-- | Returns the modification time and the contents.

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

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -92,7 +92,7 @@ import qualified Data.IntMap.Strict as IntMap
9292
import Data.List
9393
import qualified Data.Map as M
9494
import Data.Maybe
95-
import qualified Data.Rope.UTF16 as Rope
95+
import qualified Data.Text.Utf16.Rope as Rope
9696
import qualified Data.Set as Set
9797
import qualified Data.Text as T
9898
import qualified Data.Text.Encoding as T
@@ -574,10 +574,10 @@ persistentHieFileRule :: Recorder (WithPriority Log) -> Rules ()
574574
persistentHieFileRule recorder = addPersistentRule GetHieAst $ \file -> runMaybeT $ do
575575
res <- readHieFileForSrcFromDisk recorder file
576576
vfsRef <- asks vfsVar
577-
vfsData <- liftIO $ vfsMap <$> readTVarIO vfsRef
577+
vfsData <- liftIO $ _vfsMap <$> readTVarIO vfsRef
578578
(currentSource, ver) <- liftIO $ case M.lookup (filePathToUri' file) vfsData of
579579
Nothing -> (,Nothing) . T.decodeUtf8 <$> BS.readFile (fromNormalizedFilePath file)
580-
Just vf -> pure (Rope.toText $ _text vf, Just $ _lsp_version vf)
580+
Just vf -> pure (Rope.toText $ _file_text vf, Just $ _lsp_version vf)
581581
let refmap = Compat.generateReferencesMap . Compat.getAsts . Compat.hie_asts $ res
582582
del = deltaFromDiff (T.decodeUtf8 $ Compat.hie_hs_src res) currentSource
583583
pure (HAR (Compat.hie_module res) (Compat.hie_asts res) refmap mempty (HieFromDisk res),del,ver)
@@ -1108,8 +1108,8 @@ getLinkableType f = use_ NeedsCompilation f
11081108

11091109
-- needsCompilationRule :: Rules ()
11101110
needsCompilationRule :: NormalizedFilePath -> Action (IdeResultNoDiagnosticsEarlyCutoff (Maybe LinkableType))
1111-
needsCompilationRule file
1112-
| "boot" `isSuffixOf` (fromNormalizedFilePath file) =
1111+
needsCompilationRule file
1112+
| "boot" `isSuffixOf` (fromNormalizedFilePath file) =
11131113
pure (Just $ encodeLinkableType Nothing, Just Nothing)
11141114
needsCompilationRule file = do
11151115
graph <- useNoFile GetModuleGraph

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

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -164,7 +164,7 @@ import qualified Language.LSP.Server as LSP
164164
import Language.LSP.Types
165165
import qualified Language.LSP.Types as LSP
166166
import Language.LSP.Types.Capabilities
167-
import Language.LSP.VFS
167+
import Language.LSP.VFS hiding (start)
168168
import qualified "list-t" ListT
169169
import OpenTelemetry.Eventlog
170170
import qualified StmContainers.Map as STM
@@ -323,7 +323,7 @@ class Typeable a => IsIdeGlobal a where
323323
-- | Read a virtual file from the current snapshot
324324
getVirtualFile :: NormalizedFilePath -> Action (Maybe VirtualFile)
325325
getVirtualFile nf = do
326-
vfs <- fmap vfsMap . liftIO . readTVarIO . vfsVar =<< getShakeExtras
326+
vfs <- fmap _vfsMap . liftIO . readTVarIO . vfsVar =<< getShakeExtras
327327
pure $! Map.lookup (filePathToUri' nf) vfs -- Don't leak a reference to the entire map
328328

329329
-- Take a snapshot of the current LSP VFS

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

Lines changed: 11 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -34,17 +34,16 @@ import UnliftIO.Concurrent
3434
import UnliftIO.Directory
3535
import UnliftIO.Exception
3636

37+
import Control.Monad.IO.Unlift (MonadUnliftIO)
3738
import Development.IDE.Core.IdeConfiguration
38-
import Development.IDE.Core.Shake hiding (Log)
39+
import Development.IDE.Core.Shake hiding (Log, Priority)
3940
import Development.IDE.Core.Tracing
40-
import Development.IDE.Types.Logger
41-
42-
import Control.Monad.IO.Unlift (MonadUnliftIO)
43-
import Data.Kind (Type)
4441
import qualified Development.IDE.Session as Session
42+
import Development.IDE.Types.Logger
4543
import qualified Development.IDE.Types.Logger as Logger
4644
import Development.IDE.Types.Shake (WithHieDb)
4745
import Language.LSP.Server (LanguageContextEnv,
46+
LspServerLog,
4847
type (<~>))
4948
import System.IO.Unsafe (unsafeInterleaveIO)
5049

@@ -55,6 +54,7 @@ data Log
5554
| LogReactorThreadStopped
5655
| LogCancelledRequest !SomeLspId
5756
| LogSession Session.Log
57+
| LogLspServer LspServerLog
5858
deriving Show
5959

6060
instance Pretty Log where
@@ -74,13 +74,15 @@ instance Pretty Log where
7474
LogCancelledRequest requestId ->
7575
"Cancelled request" <+> viaShow requestId
7676
LogSession log -> pretty log
77+
LogLspServer log -> pretty log
7778

7879
-- used to smuggle RankNType WithHieDb through dbMVar
7980
newtype WithHieDbShield = WithHieDbShield WithHieDb
8081

8182
runLanguageServer
8283
:: forall config a m. (Show config)
83-
=> LSP.Options
84+
=> Recorder (WithPriority Log)
85+
-> LSP.Options
8486
-> Handle -- input
8587
-> Handle -- output
8688
-> config
@@ -90,7 +92,7 @@ runLanguageServer
9092
LSP.Handlers (m config),
9193
(LanguageContextEnv config, a) -> m config <~> IO))
9294
-> IO ()
93-
runLanguageServer options inH outH defaultConfig onConfigurationChange setup = do
95+
runLanguageServer recorder options inH outH defaultConfig onConfigurationChange setup = do
9496
-- This MVar becomes full when the server thread exits or we receive exit message from client.
9597
-- LSP server will be canceled when it's full.
9698
clientMsgVar <- newEmptyMVar
@@ -108,6 +110,8 @@ runLanguageServer options inH outH defaultConfig onConfigurationChange setup = d
108110

109111
void $ untilMVar clientMsgVar $
110112
void $ LSP.runServerWithHandles
113+
(toCologActionWithPrio (cmapWithPrio LogLspServer recorder))
114+
(toCologActionWithPrio (cmapWithPrio LogLspServer recorder))
111115
inH
112116
outH
113117
serverDefinition

ghcide/src/Development/IDE/Main.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -385,7 +385,7 @@ defaultMain recorder Arguments{..} = withHeapStats (cmapWithPrio LogHeapStats re
385385

386386
let setup = setupLSP (cmapWithPrio LogLanguageServer recorder) argsGetHieDbLoc (pluginHandlers plugins) getIdeState
387387

388-
runLanguageServer options inH outH argsDefaultHlsConfig argsOnConfigChange setup
388+
runLanguageServer (cmapWithPrio LogLanguageServer recorder) options inH outH argsDefaultHlsConfig argsOnConfigChange setup
389389
dumpSTMStats
390390
Check argFiles -> do
391391
dir <- maybe IO.getCurrentDirectory return argsProjectRoot

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

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -36,9 +36,9 @@ import qualified Data.List.NonEmpty as NE
3636
import qualified Data.Map.Strict as M
3737
import Data.Maybe
3838
import Data.Ord (comparing)
39-
import qualified Data.Rope.UTF16 as Rope
4039
import qualified Data.Set as S
4140
import qualified Data.Text as T
41+
import qualified Data.Text.Utf16.Rope as Rope
4242
import Data.Tuple.Extra (fst3)
4343
import Development.IDE.Core.Rules
4444
import Development.IDE.Core.RuleTypes
@@ -75,7 +75,8 @@ import Language.LSP.Types (CodeAction (
7575
WorkspaceEdit (WorkspaceEdit, _changeAnnotations, _changes, _documentChanges),
7676
type (|?) (InR),
7777
uriToFilePath)
78-
import Language.LSP.VFS
78+
import Language.LSP.VFS (VirtualFile,
79+
_file_text)
7980
import Text.Regex.TDFA (mrAfter,
8081
(=~), (=~~))
8182
#if MIN_VERSION_ghc(9,2,0)
@@ -109,7 +110,7 @@ codeAction
109110
codeAction state _ (CodeActionParams _ _ (TextDocumentIdentifier uri) _range CodeActionContext{_diagnostics=List xs}) = do
110111
contents <- LSP.getVirtualFile $ toNormalizedUri uri
111112
liftIO $ do
112-
let text = Rope.toText . (_text :: VirtualFile -> Rope.Rope) <$> contents
113+
let text = Rope.toText . (_file_text :: VirtualFile -> Rope.Rope) <$> contents
113114
mbFile = toNormalizedFilePath' <$> uriToFilePath uri
114115
diag <- atomically $ fmap (\(_, _, d) -> d) . filter (\(p, _, _) -> mbFile == Just p) <$> getDiagnostics state
115116
(join -> parsedModule) <- runAction "GhcideCodeActions.getParsedModule" state $ getParsedModule `traverse` mbFile

ghcide/src/Development/IDE/Types/Logger.hs

Lines changed: 17 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -27,6 +27,7 @@ module Development.IDE.Types.Logger
2727
, lspClientLogRecorder
2828
, module PrettyPrinterModule
2929
, renderStrict
30+
, toCologActionWithPrio
3031
) where
3132

3233
import Control.Concurrent (myThreadId)
@@ -59,7 +60,6 @@ import Language.LSP.Server
5960
import qualified Language.LSP.Server as LSP
6061
import Language.LSP.Types (LogMessageParams (..),
6162
MessageType (..),
62-
ResponseError,
6363
SMethod (SWindowLogMessage, SWindowShowMessage),
6464
ShowMessageParams (..))
6565
#if MIN_VERSION_prettyprinter(1,7,0)
@@ -69,11 +69,10 @@ import Prettyprinter.Render.Text (renderStrict)
6969
import Data.Text.Prettyprint.Doc as PrettyPrinterModule
7070
import Data.Text.Prettyprint.Doc.Render.Text (renderStrict)
7171
#endif
72-
import Control.Lens ((^.))
73-
import Ide.Types (CommandId (CommandId),
74-
PluginId (PluginId))
75-
import Language.LSP.Types.Lens (HasCode (code),
76-
HasMessage (message))
72+
import Colog.Core (LogAction (..),
73+
Severity,
74+
WithSeverity (..))
75+
import qualified Colog.Core as Colog
7776
import System.IO (Handle,
7877
IOMode (AppendMode),
7978
hClose, hFlush,
@@ -381,3 +380,15 @@ priorityToLsp =
381380
Info -> MtInfo
382381
Warning -> MtWarning
383382
Error -> MtError
383+
384+
toCologActionWithPrio :: (MonadIO m, HasCallStack) => Recorder (WithPriority msg) -> LogAction m (WithSeverity msg)
385+
toCologActionWithPrio (Recorder _logger) = LogAction $ \WithSeverity{..} -> do
386+
let priority = severityToPriority getSeverity
387+
_logger $ WithPriority priority callStack getMsg
388+
undefined
389+
where
390+
severityToPriority :: Severity -> Priority
391+
severityToPriority Colog.Debug = Debug
392+
severityToPriority Colog.Info = Info
393+
severityToPriority Colog.Warning = Warning
394+
severityToPriority Colog.Error = Error

ghcide/test/exe/Main.hs

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -28,8 +28,8 @@ import Data.Default
2828
import Data.Foldable
2929
import Data.List.Extra
3030
import Data.Maybe
31-
import Data.Rope.UTF16 (Rope)
32-
import qualified Data.Rope.UTF16 as Rope
31+
import Data.Text.Utf16.Rope (Rope)
32+
import qualified Data.Text.Utf16.Rope as Rope
3333
import qualified Data.Set as Set
3434
import qualified Data.Text as T
3535
import Development.IDE.Core.PositionMapping (PositionResult (..),
@@ -4357,12 +4357,12 @@ findDefinitionAndHoverTests = let
43574357

43584358
typeDefinitionTests = [ tst (getTypeDefinitions, checkDefs) aaaL14 sourceFilePath (pure tcData) "Saturated data con"
43594359
, tst (getTypeDefinitions, checkDefs) aL20 sourceFilePath (pure [ExpectNoDefinitions]) "Polymorphic variable"]
4360-
4361-
recordDotSyntaxTests
4360+
4361+
recordDotSyntaxTests
43624362
| ghcVersion >= GHC92 =
4363-
[ tst (getHover, checkHover) (Position 19 24) (T.unpack "RecordDotSyntax.hs") (pure [ExpectHoverText ["x :: MyRecord"]]) "hover over parent"
4364-
, tst (getHover, checkHover) (Position 19 25) (T.unpack "RecordDotSyntax.hs") (pure [ExpectHoverText ["_ :: MyChild"]]) "hover over dot shows child"
4365-
, tst (getHover, checkHover) (Position 19 26) (T.unpack "RecordDotSyntax.hs") (pure [ExpectHoverText ["_ :: MyChild"]]) "hover over child"
4363+
[ tst (getHover, checkHover) (Position 19 24) (T.unpack "RecordDotSyntax.hs") (pure [ExpectHoverText ["x :: MyRecord"]]) "hover over parent"
4364+
, tst (getHover, checkHover) (Position 19 25) (T.unpack "RecordDotSyntax.hs") (pure [ExpectHoverText ["_ :: MyChild"]]) "hover over dot shows child"
4365+
, tst (getHover, checkHover) (Position 19 26) (T.unpack "RecordDotSyntax.hs") (pure [ExpectHoverText ["_ :: MyChild"]]) "hover over child"
43664366
]
43674367
| otherwise = []
43684368

hls-plugin-api/hls-plugin-api.cabal

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -49,7 +49,7 @@ library
4949
, hls-graph ^>= 1.7
5050
, lens
5151
, lens-aeson
52-
, lsp >=1.4.0.0 && < 1.6
52+
, lsp ^>=1.5.0.0
5353
, opentelemetry >=0.4
5454
, optparse-applicative
5555
, process

hls-test-utils/hls-test-utils.cabal

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -45,9 +45,9 @@ library
4545
, hls-graph
4646
, hls-plugin-api ^>=1.3 || ^>=1.4
4747
, lens
48-
, lsp ^>=1.4
48+
, lsp ^>=1.5.0.0
4949
, lsp-test ^>=0.14
50-
, lsp-types ^>=1.4.0.1
50+
, lsp-types ^>=1.5.0.0
5151
, tasty
5252
, tasty-expected-failure
5353
, tasty-golden

plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs

Lines changed: 0 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -48,10 +48,6 @@ import Ide.Types
4848
import Language.LSP.Server
4949
import Language.LSP.Types
5050

51-
instance Hashable Location
52-
instance Hashable Range
53-
instance Hashable Position
54-
instance Hashable UInt
5551
instance Hashable (Mod a) where hash n = hash (unMod n)
5652

5753
descriptor :: PluginId -> PluginDescriptor IdeState

stack-lts16.yaml

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -84,9 +84,9 @@ extra-deps:
8484
- constraints-extras-0.3.0.2@sha256:013b8d0392582c6ca068e226718a4fe8be8e22321cc0634f6115505bf377ad26,1853
8585
- some-1.0.1@sha256:26e5bab7276f48b25ea8660d3fd1166c0f20fd497dac879a40f408e23211f93e,2055
8686
- unliftio-core-0.2.0.1@sha256:9b3e44ea9aacacbfc35b3b54015af450091916ac3618a41868ebf6546977659a,1082
87-
- lsp-1.4.0.0
88-
- lsp-types-1.4.0.1
89-
- lsp-test-0.14.0.2
87+
- lsp-1.5.0.0
88+
- lsp-types-1.5.0.0
89+
- lsp-test-0.14.0.3
9090
- stm-containers-1.1.0.4
9191
- stm-hamt-1.2.0.6@sha256:fba86ccb4b45c5706c19b0e1315ba63dcac3b5d71de945ec001ba921fae80061,3972
9292
- primitive-extras-0.10.1

stack-lts19.yaml

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -52,6 +52,9 @@ extra-deps:
5252
- refinery-0.4.0.0@sha256:fe3a43add8ff1db5cfffee7e7694c86128b1dfe62c541f26e25a8eadf9585610,1663
5353
- retrie-1.1.0.0
5454
- stylish-haskell-0.14.2.0@sha256:fffe1c13ad4c2678cf28a7470cac5d3bf20c71c36f09969e3e5f186787cceb7c,4321
55+
- lsp-1.5.0.0
56+
- lsp-types-1.5.0.0
57+
- lsp-test-0.14.0.3
5558

5659
configure-options:
5760
ghcide:

stack.yaml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
1-
resolver: nightly-2022-06-10
1+
resolver: nightly-2022-07-31
22

33
packages:
44
- .

0 commit comments

Comments
 (0)