Skip to content

Commit

Permalink
Remove Language.LSP.Types.Synonyms
Browse files Browse the repository at this point in the history
Not used much and was out of date
  • Loading branch information
lukel97 committed Oct 15, 2020
1 parent d34fcde commit cedf0a4
Show file tree
Hide file tree
Showing 7 changed files with 10 additions and 189 deletions.
1 change: 0 additions & 1 deletion lsp-types/lsp-types.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -56,7 +56,6 @@ library
, Language.LSP.Types.ServerCapabilities
, Language.LSP.Types.SignatureHelp
, Language.LSP.Types.StaticRegistrationOptions
, Language.LSP.Types.Synonyms
, Language.LSP.Types.TextDocument
, Language.LSP.Types.TypeDefinition
, Language.LSP.Types.Uri
Expand Down
2 changes: 0 additions & 2 deletions lsp-types/src/Language/LSP/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,6 @@ module Language.LSP.Types
, module Language.LSP.Types.SignatureHelp
, module Language.LSP.Types.StaticRegistrationOptions
, module Language.LSP.Types.SelectionRange
, module Language.LSP.Types.Synonyms
, module Language.LSP.Types.TextDocument
, module Language.LSP.Types.TypeDefinition
, module Language.LSP.Types.Uri
Expand Down Expand Up @@ -75,7 +74,6 @@ import Language.LSP.Types.Rename
import Language.LSP.Types.SelectionRange
import Language.LSP.Types.SignatureHelp
import Language.LSP.Types.StaticRegistrationOptions
import Language.LSP.Types.Synonyms
import Language.LSP.Types.TextDocument
import Language.LSP.Types.TypeDefinition
import Language.LSP.Types.Uri
Expand Down
177 changes: 0 additions & 177 deletions lsp-types/src/Language/LSP/Types/Synonyms.hs

This file was deleted.

11 changes: 6 additions & 5 deletions lsp-types/src/Language/LSP/VFS.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE DataKinds #-}

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

-- ---------------------------------------------------------------------

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

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

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

-- ---------------------------------------------------------------------

closeVFS :: VFS -> J.DidCloseTextDocumentNotification -> (VFS, [String])
closeVFS :: VFS -> J.Message 'J.TextDocumentDidClose -> (VFS, [String])
closeVFS vfs (J.NotificationMessage _ _ params) =
let J.DidCloseTextDocumentParams (J.TextDocumentIdentifier uri) = params
in (updateVFS (Map.delete (J.toNormalizedUri uri)) vfs,["Closed: " ++ show uri])
Expand Down
2 changes: 1 addition & 1 deletion src/Language/LSP/Server/Core.hs
Original file line number Diff line number Diff line change
Expand Up @@ -276,7 +276,7 @@ data ServerDefinition config = forall m a.
-- callback should return either the parsed configuration data or an error
-- indicating what went wrong. The parsed configuration object will be
-- stored internally and can be accessed via 'config'.
, doInitialize :: LanguageContextEnv config -> InitializeRequest -> IO (Either ResponseError a)
, doInitialize :: LanguageContextEnv config -> Message Initialize -> IO (Either ResponseError a)
-- ^ Called *after* receiving the @initialize@ request and *before*
-- returning the response. This callback will be invoked to offer the
-- language server implementation the chance to create any processes or
Expand Down
4 changes: 2 additions & 2 deletions src/Language/LSP/Server/Processing.hs
Original file line number Diff line number Diff line change
Expand Up @@ -320,7 +320,7 @@ handle' mAction m msg = do
| "$/" `T.isPrefixOf` method = True
isOptionalNotification _ = False

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



handleConfigChange :: DidChangeConfigurationNotification -> LspM config ()
handleConfigChange :: Message WorkspaceDidChangeConfiguration -> LspM config ()
handleConfigChange req = do
parseConfig <- LspT $ asks resParseConfig
res <- liftIO $ parseConfig (req ^. LSP.params . LSP.settings)
Expand Down
2 changes: 1 addition & 1 deletion test/JsonSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -50,7 +50,7 @@ jsonSpec = do
-- (propertyJsonRoundtrip :: ResponseMessage J.Value -> Property)
describe "JSON decoding regressions" $
it "CompletionItem" $
(J.decode "{\"jsonrpc\":\"2.0\",\"result\":[{\"label\":\"raisebox\"}],\"id\":1}" :: Maybe CompletionResponse)
(J.decode "{\"jsonrpc\":\"2.0\",\"result\":[{\"label\":\"raisebox\"}],\"id\":1}" :: Maybe (ResponseMessage 'TextDocumentCompletion))
`shouldNotBe` Nothing


Expand Down

0 comments on commit cedf0a4

Please sign in to comment.