Skip to content

Commit cedf0a4

Browse files
committed
Remove Language.LSP.Types.Synonyms
Not used much and was out of date
1 parent d34fcde commit cedf0a4

File tree

7 files changed

+10
-189
lines changed

7 files changed

+10
-189
lines changed

lsp-types/lsp-types.cabal

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -56,7 +56,6 @@ library
5656
, Language.LSP.Types.ServerCapabilities
5757
, Language.LSP.Types.SignatureHelp
5858
, Language.LSP.Types.StaticRegistrationOptions
59-
, Language.LSP.Types.Synonyms
6059
, Language.LSP.Types.TextDocument
6160
, Language.LSP.Types.TypeDefinition
6261
, Language.LSP.Types.Uri

lsp-types/src/Language/LSP/Types.hs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -31,7 +31,6 @@ module Language.LSP.Types
3131
, module Language.LSP.Types.SignatureHelp
3232
, module Language.LSP.Types.StaticRegistrationOptions
3333
, module Language.LSP.Types.SelectionRange
34-
, module Language.LSP.Types.Synonyms
3534
, module Language.LSP.Types.TextDocument
3635
, module Language.LSP.Types.TypeDefinition
3736
, module Language.LSP.Types.Uri
@@ -75,7 +74,6 @@ import Language.LSP.Types.Rename
7574
import Language.LSP.Types.SelectionRange
7675
import Language.LSP.Types.SignatureHelp
7776
import Language.LSP.Types.StaticRegistrationOptions
78-
import Language.LSP.Types.Synonyms
7977
import Language.LSP.Types.TextDocument
8078
import Language.LSP.Types.TypeDefinition
8179
import Language.LSP.Types.Uri

lsp-types/src/Language/LSP/Types/Synonyms.hs

Lines changed: 0 additions & 177 deletions
This file was deleted.

lsp-types/src/Language/LSP/VFS.hs

Lines changed: 6 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,7 @@
55
{-# LANGUAGE ScopedTypeVariables #-}
66
{-# LANGUAGE ViewPatterns #-}
77
{-# LANGUAGE NamedFieldPuns #-}
8+
{-# LANGUAGE DataKinds #-}
89

910
{-|
1011
Handles the "Language.LSP.Types.TextDocumentDidChange" \/
@@ -95,8 +96,8 @@ initVFS k = withSystemTempDirectory "haskell-lsp" $ \temp_dir -> k (VFS mempty t
9596

9697
-- ---------------------------------------------------------------------
9798

98-
-- ^ Applies the changes from a 'DidOpenTextDocumentNotification' to the 'VFS'
99-
openVFS :: VFS -> J.DidOpenTextDocumentNotification -> (VFS, [String])
99+
-- | Applies the changes from a 'J.DidOpenTextDocument' to the 'VFS'
100+
openVFS :: VFS -> J.Message 'J.TextDocumentDidOpen -> (VFS, [String])
100101
openVFS vfs (J.NotificationMessage _ _ params) =
101102
let J.DidOpenTextDocumentParams
102103
(J.TextDocumentItem uri _ version text) = params
@@ -107,7 +108,7 @@ openVFS vfs (J.NotificationMessage _ _ params) =
107108
-- ---------------------------------------------------------------------
108109

109110
-- ^ Applies a 'DidChangeTextDocumentNotification' to the 'VFS'
110-
changeFromClientVFS :: VFS -> J.DidChangeTextDocumentNotification -> (VFS,[String])
111+
changeFromClientVFS :: VFS -> J.Message 'J.TextDocumentDidChange -> (VFS,[String])
111112
changeFromClientVFS vfs (J.NotificationMessage _ _ params) =
112113
let
113114
J.DidChangeTextDocumentParams vid (J.List changes) = params
@@ -129,7 +130,7 @@ updateVFS f vfs@VFS{vfsMap} = vfs { vfsMap = f vfsMap }
129130
-- ---------------------------------------------------------------------
130131

131132
-- ^ Applies the changes from a 'ApplyWorkspaceEditRequest' to the 'VFS'
132-
changeFromServerVFS :: VFS -> J.ApplyWorkspaceEditRequest -> IO VFS
133+
changeFromServerVFS :: VFS -> J.Message 'J.WorkspaceApplyEdit -> IO VFS
133134
changeFromServerVFS initVfs (J.RequestMessage _ _ _ params) = do
134135
let J.ApplyWorkspaceEditParams _label edit = params
135136
J.WorkspaceEdit mChanges mDocChanges = edit
@@ -201,7 +202,7 @@ persistFileVFS vfs uri =
201202

202203
-- ---------------------------------------------------------------------
203204

204-
closeVFS :: VFS -> J.DidCloseTextDocumentNotification -> (VFS, [String])
205+
closeVFS :: VFS -> J.Message 'J.TextDocumentDidClose -> (VFS, [String])
205206
closeVFS vfs (J.NotificationMessage _ _ params) =
206207
let J.DidCloseTextDocumentParams (J.TextDocumentIdentifier uri) = params
207208
in (updateVFS (Map.delete (J.toNormalizedUri uri)) vfs,["Closed: " ++ show uri])

src/Language/LSP/Server/Core.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -276,7 +276,7 @@ data ServerDefinition config = forall m a.
276276
-- callback should return either the parsed configuration data or an error
277277
-- indicating what went wrong. The parsed configuration object will be
278278
-- stored internally and can be accessed via 'config'.
279-
, doInitialize :: LanguageContextEnv config -> InitializeRequest -> IO (Either ResponseError a)
279+
, doInitialize :: LanguageContextEnv config -> Message Initialize -> IO (Either ResponseError a)
280280
-- ^ Called *after* receiving the @initialize@ request and *before*
281281
-- returning the response. This callback will be invoked to offer the
282282
-- language server implementation the chance to create any processes or

src/Language/LSP/Server/Processing.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -320,7 +320,7 @@ handle' mAction m msg = do
320320
| "$/" `T.isPrefixOf` method = True
321321
isOptionalNotification _ = False
322322

323-
progressCancelHandler :: WorkDoneProgressCancelNotification -> LspM config ()
323+
progressCancelHandler :: Message WindowWorkDoneProgressCancel -> LspM config ()
324324
progressCancelHandler (NotificationMessage _ _ (WorkDoneProgressCancelParams tid)) = do
325325
mact <- getsState $ Map.lookup tid . progressCancel . resProgressData
326326
case mact of
@@ -339,7 +339,7 @@ shutdownRequestHandler = \_req k -> do
339339

340340

341341

342-
handleConfigChange :: DidChangeConfigurationNotification -> LspM config ()
342+
handleConfigChange :: Message WorkspaceDidChangeConfiguration -> LspM config ()
343343
handleConfigChange req = do
344344
parseConfig <- LspT $ asks resParseConfig
345345
res <- liftIO $ parseConfig (req ^. LSP.params . LSP.settings)

test/JsonSpec.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -50,7 +50,7 @@ jsonSpec = do
5050
-- (propertyJsonRoundtrip :: ResponseMessage J.Value -> Property)
5151
describe "JSON decoding regressions" $
5252
it "CompletionItem" $
53-
(J.decode "{\"jsonrpc\":\"2.0\",\"result\":[{\"label\":\"raisebox\"}],\"id\":1}" :: Maybe CompletionResponse)
53+
(J.decode "{\"jsonrpc\":\"2.0\",\"result\":[{\"label\":\"raisebox\"}],\"id\":1}" :: Maybe (ResponseMessage 'TextDocumentCompletion))
5454
`shouldNotBe` Nothing
5555

5656

0 commit comments

Comments
 (0)