diff --git a/.azure/linux-stack.yml b/.azure/linux-stack.yml index b08e073e4..aad4722ef 100644 --- a/.azure/linux-stack.yml +++ b/.azure/linux-stack.yml @@ -59,7 +59,7 @@ jobs: displayName: Build `haskell-lsp` - bash: | source .azure/linux-stack.bashrc - stack build --stack-yaml $(YAML_FILE) :lsp-hello --flag haskell-lsp:demo + stack build --stack-yaml $(YAML_FILE) --flag haskell-lsp:demo displayName: Build language server example - bash: | source .azure/linux-stack.bashrc diff --git a/.azure/macos-stack.yml b/.azure/macos-stack.yml index 71fe8c4b6..22a66c466 100644 --- a/.azure/macos-stack.yml +++ b/.azure/macos-stack.yml @@ -60,7 +60,7 @@ jobs: displayName: Build `haskell-lsp` - bash: | source .azure/macos-stack.bashrc - stack build --stack-yaml $(YAML_FILE) :lsp-hello --flag haskell-lsp:demo + stack build --stack-yaml $(YAML_FILE) --flag haskell-lsp:demo displayName: Build language server example - bash: | source .azure/macos-stack.bashrc diff --git a/.azure/windows-stack.yml b/.azure/windows-stack.yml index 08a888709..028182974 100644 --- a/.azure/windows-stack.yml +++ b/.azure/windows-stack.yml @@ -61,7 +61,7 @@ jobs: displayName: Build `haskell-lsp` - bash: | source .azure/windows-stack.bashrc - stack build --stack-yaml $(YAML_FILE) :lsp-hello --flag haskell-lsp:demo + stack build --stack-yaml $(YAML_FILE) --flag haskell-lsp:demo displayName: Build language server example - bash: | source .azure/windows-stack.bashrc diff --git a/.gitignore b/.gitignore index 01e89fb2c..99b15dcfc 100644 --- a/.gitignore +++ b/.gitignore @@ -14,6 +14,7 @@ stack*.yaml.lock /haskell-lsp-types/cabal.project.local~ *.swp *.swo +*.orig *.DS_Store .hspec-failures /haskell-lsp-types/dist/ @@ -21,3 +22,4 @@ stack*.yaml.lock /haskell-lsp-types/TAGS /haskell-lsp-types/tags /haskell-lsp-types/ctags +.hie diff --git a/README.md b/README.md index 025e3f656..8ee255726 100644 --- a/README.md +++ b/README.md @@ -36,14 +36,14 @@ It can also be used with emacs, see https://github.com/emacs-lsp/lsp-haskell ## Using the example server - stack install :lsp-hello --flag haskell-lsp:demo + stack install :lsp-demo-reactor-server --flag haskell-lsp:demo -will generate a `lsp-hello` executable. +will generate a `:lsp-demo-reactor-server` executable. -Changing the server to be called in the [`vscode-hie-server`](https://github.com/alanz/vscode-hie-server/blob/master/hie-vscode.sh#L21) plugin from `hie` to -`lsp-hello` will run the example server instead of hie. +Changing the server executable in the [`vscode-haskell`](https://github.com/haskell/vscode-haskell) plugin to +`lsp-demo-reactor-server` to test it out. -Likewise, changing the executable in `lsp-haskell` for emacs. +Likewise, you can change the executable in `lsp-haskell` for emacs. ## Useful links diff --git a/cabal.project b/cabal.project index ad2012d88..72dd1e669 100644 --- a/cabal.project +++ b/cabal.project @@ -1,3 +1,15 @@ packages: ./ ./haskell-lsp-types/ + ./func-test/ + +package haskell-lsp + flags: +demo + + +source-repository-package + type: git + location: https://github.com/wz1000/lsp-test.git + tag: e251176a4b2ff4dead7846fe5d0a4e1dbea69fd4 + +tests: True diff --git a/example/Main.hs b/example/Main.hs deleted file mode 100644 index c028bd204..000000000 --- a/example/Main.hs +++ /dev/null @@ -1,375 +0,0 @@ -{-# LANGUAGE CPP #-} -{-# LANGUAGE FlexibleContexts #-} -{-# LANGUAGE LambdaCase #-} -{-# LANGUAGE MultiWayIf #-} -{-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE ScopedTypeVariables #-} - -module Main (main) where - -import Control.Concurrent -import Control.Concurrent.STM.TChan -import qualified Control.Exception as E -import Control.Lens -import Control.Monad -import Control.Monad.IO.Class -import Control.Monad.Reader -import Control.Monad.STM -import qualified Data.Aeson as J -import Data.Default -import qualified Data.HashMap.Strict as H -#if __GLASGOW_HASKELL__ < 804 -import Data.Monoid -#endif -import qualified Data.Text as T -import qualified Language.Haskell.LSP.Control as CTRL -import qualified Language.Haskell.LSP.Core as Core -import Language.Haskell.LSP.Diagnostics -import Language.Haskell.LSP.Messages -import qualified Language.Haskell.LSP.Types as J -import qualified Language.Haskell.LSP.Types.Lens as J -import qualified Language.Haskell.LSP.Utility as U -import Language.Haskell.LSP.VFS -import System.Exit -import qualified System.Log.Logger as L - - --- --------------------------------------------------------------------- -{-# ANN module ("HLint: ignore Eta reduce" :: String) #-} -{-# ANN module ("HLint: ignore Redundant do" :: String) #-} -{-# ANN module ("HLint: ignore Reduce duplication" :: String) #-} --- --------------------------------------------------------------------- --- - -main :: IO () -main = do - run (return ()) >>= \case - 0 -> exitSuccess - c -> exitWith . ExitFailure $ c - --- --------------------------------------------------------------------- - -run :: IO () -> IO Int -run dispatcherProc = flip E.catches handlers $ do - - rin <- atomically newTChan :: IO (TChan ReactorInput) - - let - dp lf = do - liftIO $ U.logs "main.run:dp entered" - _rpid <- forkIO $ reactor lf rin - liftIO $ U.logs "main.run:dp tchan" - dispatcherProc - liftIO $ U.logs "main.run:dp after dispatcherProc" - return Nothing - - callbacks = Core.InitializeCallbacks - { Core.onInitialConfiguration = const $ Right () - , Core.onConfigurationChange = const $ Right () - , Core.onStartup = dp - } - - flip E.finally finalProc $ do - Core.setupLogger (Just "/tmp/lsp-hello.log") [] L.DEBUG - CTRL.run callbacks (lspHandlers rin) lspOptions (Just "/tmp/lsp-hello-session.log") - - where - handlers = [ E.Handler ioExcept - , E.Handler someExcept - ] - finalProc = L.removeAllHandlers - ioExcept (e :: E.IOException) = print e >> return 1 - someExcept (e :: E.SomeException) = print e >> return 1 - --- --------------------------------------------------------------------- - --- The reactor is a process that serialises and buffers all requests from the --- LSP client, so they can be sent to the backend compiler one at a time, and a --- reply sent. - -data ReactorInput - = HandlerRequest FromClientMessage - -- ^ injected into the reactor input by each of the individual callback handlers - --- --------------------------------------------------------------------- - --- | The monad used in the reactor -type R c a = ReaderT (Core.LspFuncs c) IO a - --- --------------------------------------------------------------------- --- reactor monad functions --- --------------------------------------------------------------------- - --- --------------------------------------------------------------------- - -reactorSend :: FromServerMessage -> R () () -reactorSend msg = do - lf <- ask - liftIO $ Core.sendFunc lf msg - --- --------------------------------------------------------------------- - -publishDiagnostics :: Int -> J.NormalizedUri -> J.TextDocumentVersion -> DiagnosticsBySource -> R () () -publishDiagnostics maxToPublish uri v diags = do - lf <- ask - liftIO $ Core.publishDiagnosticsFunc lf maxToPublish uri v diags - --- --------------------------------------------------------------------- - -nextLspReqId :: R () J.LspId -nextLspReqId = do - f <- asks Core.getNextReqId - liftIO f - --- --------------------------------------------------------------------- - --- | The single point that all events flow through, allowing management of state --- to stitch replies and requests together from the two asynchronous sides: lsp --- server and backend compiler -reactor :: Core.LspFuncs () -> TChan ReactorInput -> IO () -reactor lf inp = do - liftIO $ U.logs "reactor:entered" - flip runReaderT lf $ forever $ do - inval <- liftIO $ atomically $ readTChan inp - case inval of - - -- Handle any response from a message originating at the server, such as - -- "workspace/applyEdit" - HandlerRequest (RspFromClient rm) -> do - liftIO $ U.logs $ "reactor:got RspFromClient:" ++ show rm - - -- ------------------------------- - - HandlerRequest (NotInitialized _notification) -> do - liftIO $ U.logm "****** reactor: processing Initialized Notification" - -- Server is ready, register any specific capabilities we need - - {- - Example: - { - "method": "client/registerCapability", - "params": { - "registrations": [ - { - "id": "79eee87c-c409-4664-8102-e03263673f6f", - "method": "textDocument/willSaveWaitUntil", - "registerOptions": { - "documentSelector": [ - { "language": "javascript" } - ] - } - } - ] - } - } - -} - let - registration = J.Registration "lsp-hello-registered" J.WorkspaceExecuteCommand Nothing - let registrations = J.RegistrationParams (J.List [registration]) - rid <- nextLspReqId - - reactorSend $ ReqRegisterCapability $ fmServerRegisterCapabilityRequest rid registrations - - -- example of showMessageRequest - let - params = J.ShowMessageRequestParams J.MtWarning "choose an option for XXX" - (Just [J.MessageActionItem "option a", J.MessageActionItem "option b"]) - rid1 <- nextLspReqId - - reactorSend $ ReqShowMessage $ fmServerShowMessageRequest rid1 params - - -- ------------------------------- - - HandlerRequest (NotDidOpenTextDocument notification) -> do - liftIO $ U.logm "****** reactor: processing NotDidOpenTextDocument" - let - doc = notification ^. J.params - . J.textDocument - . J.uri - fileName = J.uriToFilePath doc - liftIO $ U.logs $ "********* fileName=" ++ show fileName - sendDiagnostics (J.toNormalizedUri doc) (Just 0) - - -- ------------------------------- - - HandlerRequest (NotDidChangeTextDocument notification) -> do - let doc :: J.NormalizedUri - doc = notification ^. J.params - . J.textDocument - . J.uri - . to J.toNormalizedUri - mdoc <- liftIO $ Core.getVirtualFileFunc lf doc - case mdoc of - Just (VirtualFile _version str _) -> do - liftIO $ U.logs $ "reactor:processing NotDidChangeTextDocument: vf got:" ++ show str - Nothing -> do - liftIO $ U.logs "reactor:processing NotDidChangeTextDocument: vf returned Nothing" - - liftIO $ U.logs $ "reactor:processing NotDidChangeTextDocument: uri=" ++ show doc - - -- ------------------------------- - - HandlerRequest (NotDidSaveTextDocument notification) -> do - liftIO $ U.logm "****** reactor: processing NotDidSaveTextDocument" - let - doc = notification ^. J.params - . J.textDocument - . J.uri - fileName = J.uriToFilePath doc - liftIO $ U.logs $ "********* fileName=" ++ show fileName - sendDiagnostics (J.toNormalizedUri doc) Nothing - - -- ------------------------------- - - HandlerRequest (ReqRename req) -> do - liftIO $ U.logs $ "reactor:got RenameRequest:" ++ show req - let - _params = req ^. J.params - _doc = _params ^. J.textDocument . J.uri - J.Position _l _c' = _params ^. J.position - _newName = _params ^. J.newName - - let we = J.WorkspaceEdit - Nothing -- "changes" field is deprecated - (Just (J.List [])) -- populate with actual changes from the rename - let rspMsg = Core.makeResponseMessage req we - reactorSend $ RspRename rspMsg - - -- ------------------------------- - - HandlerRequest (ReqHover req) -> do - liftIO $ U.logs $ "reactor:got HoverRequest:" ++ show req - let J.TextDocumentPositionParams _doc pos _workDoneToken = req ^. J.params - J.Position _l _c' = pos - - let - ht = Just $ J.Hover ms (Just range) - ms = J.HoverContents $ J.markedUpContent "lsp-hello" "TYPE INFO" - range = J.Range pos pos - reactorSend $ RspHover $ Core.makeResponseMessage req ht - - -- ------------------------------- - - HandlerRequest (ReqCodeAction req) -> do - liftIO $ U.logs $ "reactor:got CodeActionRequest:" ++ show req - let params = req ^. J.params - doc = params ^. J.textDocument - -- fileName = drop (length ("file://"::String)) doc - -- J.Range from to = J._range (params :: J.CodeActionParams) - (J.List diags) = params ^. J.context . J.diagnostics - - let - -- makeCommand only generates commands for diagnostics whose source is us - makeCommand (J.Diagnostic (J.Range start _) _s _c (Just "lsp-hello") _m _t _l) = [J.Command title cmd cmdparams] - where - title = "Apply LSP hello command:" <> head (T.lines _m) - -- NOTE: the cmd needs to be registered via the InitializeResponse message. See lspOptions above - cmd = "lsp-hello-command" - -- need 'file' and 'start_pos' - args = J.List - [ J.Object $ H.fromList [("file", J.Object $ H.fromList [("textDocument",J.toJSON doc)])] - , J.Object $ H.fromList [("start_pos",J.Object $ H.fromList [("position", J.toJSON start)])] - ] - cmdparams = Just args - makeCommand (J.Diagnostic _r _s _c _source _m _t _l) = [] - let body = J.List $ map J.CACommand $ concatMap makeCommand diags - rsp = Core.makeResponseMessage req body - reactorSend $ RspCodeAction rsp - - -- ------------------------------- - - HandlerRequest (ReqExecuteCommand req) -> do - liftIO $ U.logs "reactor:got ExecuteCommandRequest:" -- ++ show req - let params = req ^. J.params - margs = params ^. J.arguments - - liftIO $ U.logs $ "reactor:ExecuteCommandRequest:margs=" ++ show margs - - let - reply v = reactorSend $ RspExecuteCommand $ Core.makeResponseMessage req v - -- When we get a RefactorResult or HieDiff, we need to send a - -- separate WorkspaceEdit Notification - r = J.List [] :: J.List Int - liftIO $ U.logs $ "ExecuteCommand response got:r=" ++ show r - case toWorkspaceEdit r of - Just we -> do - reply (J.Object mempty) - lid <- nextLspReqId - -- reactorSend $ J.RequestMessage "2.0" lid "workspace/applyEdit" (Just we) - reactorSend $ ReqApplyWorkspaceEdit $ fmServerApplyWorkspaceEditRequest lid we - Nothing -> - reply (J.Object mempty) - - -- ------------------------------- - - HandlerRequest om -> do - liftIO $ U.logs $ "reactor:got HandlerRequest:" ++ show om - --- --------------------------------------------------------------------- - -toWorkspaceEdit :: t -> Maybe J.ApplyWorkspaceEditParams -toWorkspaceEdit _ = Nothing - --- --------------------------------------------------------------------- - --- | Analyze the file and send any diagnostics to the client in a --- "textDocument/publishDiagnostics" notification -sendDiagnostics :: J.NormalizedUri -> Maybe Int -> R () () -sendDiagnostics fileUri version = do - let - diags = [J.Diagnostic - (J.Range (J.Position 0 1) (J.Position 0 5)) - (Just J.DsWarning) -- severity - Nothing -- code - (Just "lsp-hello") -- source - "Example diagnostic message" - Nothing -- tags - (Just (J.List [])) - ] - -- reactorSend $ J.NotificationMessage "2.0" "textDocument/publishDiagnostics" (Just r) - publishDiagnostics 100 fileUri version (partitionBySource diags) - --- --------------------------------------------------------------------- - -syncOptions :: J.TextDocumentSyncOptions -syncOptions = J.TextDocumentSyncOptions - { J._openClose = Just True - , J._change = Just J.TdSyncIncremental - , J._willSave = Just False - , J._willSaveWaitUntil = Just False - , J._save = Just $ J.SaveOptions $ Just False - } - -lspOptions :: Core.Options -lspOptions = def { Core.textDocumentSync = Just syncOptions - , Core.executeCommandCommands = Just ["lsp-hello-command"] - } - -lspHandlers :: TChan ReactorInput -> Core.Handlers -lspHandlers rin - = def { Core.initializedHandler = Just $ passHandler rin NotInitialized - , Core.renameHandler = Just $ passHandler rin ReqRename - , Core.hoverHandler = Just $ passHandler rin ReqHover - , Core.didOpenTextDocumentNotificationHandler = Just $ passHandler rin NotDidOpenTextDocument - , Core.didSaveTextDocumentNotificationHandler = Just $ passHandler rin NotDidSaveTextDocument - , Core.didChangeTextDocumentNotificationHandler = Just $ passHandler rin NotDidChangeTextDocument - , Core.didCloseTextDocumentNotificationHandler = Just $ passHandler rin NotDidCloseTextDocument - , Core.cancelNotificationHandler = Just $ passHandler rin NotCancelRequestFromClient - , Core.responseHandler = Just $ responseHandlerCb rin - , Core.codeActionHandler = Just $ passHandler rin ReqCodeAction - , Core.executeCommandHandler = Just $ passHandler rin ReqExecuteCommand - } - --- --------------------------------------------------------------------- - -passHandler :: TChan ReactorInput -> (a -> FromClientMessage) -> Core.Handler a -passHandler rin c notification = do - atomically $ writeTChan rin (HandlerRequest (c notification)) - --- --------------------------------------------------------------------- - -responseHandlerCb :: TChan ReactorInput -> Core.Handler J.BareResponseMessage -responseHandlerCb _rin resp = do - U.logs $ "******** got ResponseMessage, ignoring:" ++ show resp - --- --------------------------------------------------------------------- diff --git a/example/Reactor.hs b/example/Reactor.hs new file mode 100644 index 000000000..5d8b81e94 --- /dev/null +++ b/example/Reactor.hs @@ -0,0 +1,274 @@ +{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE DeriveAnyClass #-} +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE GADTs #-} +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE DuplicateRecordFields #-} + +{- | +This is an example language server built with haskell-lsp using a 'Reactor' +design. With a 'Reactor' all requests are handled on a /single thread/. +A thread is spun up for it, which repeatedly reads from a 'TChan' of +'ReactorInput's. +The `haskell-lsp` handlers then simply pass on all the requests and +notifications onto the channel via 'ReactorInput's. + +To try out this server, install it with +> cabal install lsp-demo-reactor-server -fdemo +and plug it into your client of choice. +-} +module Main (main) where +import Control.Concurrent.STM.TChan +import qualified Control.Exception as E +import Control.Lens hiding (Iso) +import Control.Monad +import Control.Monad.IO.Class +import Control.Monad.STM +import qualified Data.Aeson as J +import Data.Default +import qualified Data.HashMap.Strict as H +import qualified Data.Text as T +import GHC.Generics (Generic) +import qualified Language.Haskell.LSP.Control as CTRL +import Language.Haskell.LSP.Core +import Language.Haskell.LSP.Diagnostics +import qualified Language.Haskell.LSP.Types as J +import qualified Language.Haskell.LSP.Types.Lens as J +import Language.Haskell.LSP.VFS +import System.Exit +import System.Log.Logger +import Control.Concurrent + + +-- --------------------------------------------------------------------- +{-# ANN module ("HLint: ignore Eta reduce" :: String) #-} +{-# ANN module ("HLint: ignore Redundant do" :: String) #-} +{-# ANN module ("HLint: ignore Reduce duplication" :: String) #-} +-- --------------------------------------------------------------------- +-- + +main :: IO () +main = do + run >>= \case + 0 -> exitSuccess + c -> exitWith . ExitFailure $ c + +-- --------------------------------------------------------------------- + +data Config = Config { fooTheBar :: Bool, wibbleFactor :: Int } + deriving (Generic, J.ToJSON, J.FromJSON) + +run :: IO Int +run = flip E.catches handlers $ do + + rin <- atomically newTChan :: IO (TChan ReactorInput) + + let + callbacks = InitializeCallbacks + { onConfigurationChange = \v -> case J.fromJSON v of + J.Error e -> pure $ Left (T.pack e) + J.Success cfg -> do + sendNotification J.SWindowShowMessage $ + J.ShowMessageParams J.MtInfo $ "Wibble factor set to " <> T.pack (show (wibbleFactor cfg)) + pure $ Right cfg + , doInitialize = \env _ -> forkIO (reactor rin) >> pure (Right env) + , staticHandlers = lspHandlers rin + , interpretHandler = \env -> Iso (runLspT env) liftIO + } + + flip E.finally finalProc $ do + setupLogger Nothing ["reactor"] DEBUG + CTRL.run callbacks lspOptions + + where + handlers = [ E.Handler ioExcept + , E.Handler someExcept + ] + finalProc = removeAllHandlers + ioExcept (e :: E.IOException) = print e >> return 1 + someExcept (e :: E.SomeException) = print e >> return 1 + +-- --------------------------------------------------------------------- + +syncOptions :: J.TextDocumentSyncOptions +syncOptions = J.TextDocumentSyncOptions + { J._openClose = Just True + , J._change = Just J.TdSyncIncremental + , J._willSave = Just False + , J._willSaveWaitUntil = Just False + , J._save = Just $ J.InR $ J.SaveOptions $ Just False + } + +lspOptions :: Options +lspOptions = def { textDocumentSync = Just syncOptions + , executeCommandCommands = Just ["lsp-hello-command"] + } + +-- --------------------------------------------------------------------- + +-- The reactor is a process that serialises and buffers all requests from the +-- LSP client, so they can be sent to the backend compiler one at a time, and a +-- reply sent. + +newtype ReactorInput + = ReactorAction (IO ()) + +-- | Analyze the file and send any diagnostics to the client in a +-- "textDocument/publishDiagnostics" notification +sendDiagnostics :: J.NormalizedUri -> Maybe Int -> LspM Config () +sendDiagnostics fileUri version = do + let + diags = [J.Diagnostic + (J.Range (J.Position 0 1) (J.Position 0 5)) + (Just J.DsWarning) -- severity + Nothing -- code + (Just "lsp-hello") -- source + "Example diagnostic message" + Nothing -- tags + (Just (J.List [])) + ] + publishDiagnostics 100 fileUri version (partitionBySource diags) + +-- --------------------------------------------------------------------- + +-- | The single point that all events flow through, allowing management of state +-- to stitch replies and requests together from the two asynchronous sides: lsp +-- server and backend compiler +reactor :: TChan ReactorInput -> IO () +reactor inp = do + debugM "reactor" "Started the reactor" + forever $ do + ReactorAction act <- atomically $ readTChan inp + act + +-- | Check if we have a handler, and if we create a haskell-lsp handler to pass it as +-- input into the reactor +lspHandlers :: TChan ReactorInput -> Handlers (LspM Config) +lspHandlers rin = mapHandlers goReq goNot handle + where + goReq :: forall (a :: J.Method J.FromClient J.Request). Handler (LspM Config) a -> Handler (LspM Config) a + goReq f = \msg k -> do + env <- getLspEnv + liftIO $ atomically $ writeTChan rin $ ReactorAction (runLspT env $ f msg k) + + goNot :: forall (a :: J.Method J.FromClient J.Notification). Handler (LspM Config) a -> Handler (LspM Config) a + goNot f = \msg -> do + env <- getLspEnv + liftIO $ atomically $ writeTChan rin $ ReactorAction (runLspT env $ f msg) + +-- | Where the actual logic resides for handling requests and notifications. +handle :: Handlers (LspM Config) +handle = mconcat + [ notificationHandler J.SInitialized $ \_msg -> do + liftIO $ debugM "reactor.handle" "Processing the Initialized notification" + + -- We're initialized! Lets send a showMessageRequest now + let params = J.ShowMessageRequestParams + J.MtWarning + "What's your favourite language extension?" + (Just [J.MessageActionItem "Rank2Types", J.MessageActionItem "NPlusKPatterns"]) + + void $ sendRequest J.SWindowShowMessageRequest params $ \res -> + case res of + Left e -> liftIO $ errorM "reactor.handle" $ "Got an error: " ++ show e + Right _ -> do + sendNotification J.SWindowShowMessage (J.ShowMessageParams J.MtInfo "Excellent choice") + + -- We can dynamically register a capability once the user accepts it + sendNotification J.SWindowShowMessage (J.ShowMessageParams J.MtInfo "Turning on code lenses dynamically") + + let regOpts = J.CodeLensRegistrationOptions Nothing Nothing (Just False) + + void $ registerCapability J.STextDocumentCodeLens regOpts $ \_req responder -> do + liftIO $ debugM "reactor.handle" "Processing a textDocument/codeLens request" + let cmd = J.Command "Say hello" "lsp-hello-command" Nothing + rsp = J.List [J.CodeLens (J.mkRange 0 0 0 100) (Just cmd) Nothing] + responder (Right rsp) + + , notificationHandler J.STextDocumentDidOpen $ \msg -> do + let doc = msg ^. J.params . J.textDocument . J.uri + fileName = J.uriToFilePath doc + liftIO $ debugM "reactor.handle" $ "Processing DidOpenTextDocument for: " ++ show fileName + sendDiagnostics (J.toNormalizedUri doc) (Just 0) + + , notificationHandler J.STextDocumentDidChange $ \msg -> do + let doc = msg ^. J.params + . J.textDocument + . J.uri + . to J.toNormalizedUri + liftIO $ debugM "reactor.handle" $ "Processing DidChangeTextDocument for: " ++ show doc + mdoc <- getVirtualFile doc + case mdoc of + Just (VirtualFile _version str _) -> do + liftIO $ debugM "reactor.handle" $ "Found the virtual file: " ++ show str + Nothing -> do + liftIO $ debugM "reactor.handle" $ "Didn't find anything in the VFS for: " ++ show doc + + , notificationHandler J.STextDocumentDidSave $ \msg -> do + let doc = msg ^. J.params . J.textDocument . J.uri + fileName = J.uriToFilePath doc + liftIO $ debugM "reactor.handle" $ "Processing DidSaveTextDocument for: " ++ show fileName + sendDiagnostics (J.toNormalizedUri doc) Nothing + + , requestHandler J.STextDocumentRename $ \req responder -> do + liftIO $ debugM "reactor.handle" "Processing a textDocument/rename request" + let params = req ^. J.params + J.Position l c = params ^. J.position + newName = params ^. J.newName + vdoc <- getVersionedTextDoc (params ^. J.textDocument) + -- Replace some text at the position with what the user entered + let edit = J.TextEdit (J.mkRange l c l (c + T.length newName)) newName + tde = J.TextDocumentEdit vdoc (J.List [edit]) + -- "documentChanges" field is preferred over "changes" + rsp = J.WorkspaceEdit Nothing (Just (J.List [tde])) + responder (Right rsp) + + , requestHandler J.STextDocumentHover $ \req responder -> do + liftIO $ debugM "reactor.handle" "Processing a textDocument/hover request" + let J.HoverParams _doc pos _workDone = req ^. J.params + J.Position _l _c' = pos + rsp = J.Hover ms (Just range) + ms = J.HoverContents $ J.markedUpContent "lsp-hello" "Your type info here!" + range = J.Range pos pos + responder (Right $ Just rsp) + + , requestHandler J.STextDocumentCodeAction $ \req responder -> do + liftIO $ debugM "reactor.handle" $ "Processing a textDocument/codeAction request" + let params = req ^. J.params + doc = params ^. J.textDocument + (J.List diags) = params ^. J.context . J.diagnostics + -- makeCommand only generates commands for diagnostics whose source is us + makeCommand (J.Diagnostic (J.Range start _) _s _c (Just "lsp-hello") _m _t _l) = [J.Command title cmd cmdparams] + where + title = "Apply LSP hello command:" <> head (T.lines _m) + -- NOTE: the cmd needs to be registered via the InitializeResponse message. See lspOptions above + cmd = "lsp-hello-command" + -- need 'file' and 'start_pos' + args = J.List + [ J.Object $ H.fromList [("file", J.Object $ H.fromList [("textDocument",J.toJSON doc)])] + , J.Object $ H.fromList [("start_pos",J.Object $ H.fromList [("position", J.toJSON start)])] + ] + cmdparams = Just args + makeCommand (J.Diagnostic _r _s _c _source _m _t _l) = [] + rsp = J.List $ map J.InL $ concatMap makeCommand diags + responder (Right rsp) + + , requestHandler J.SWorkspaceExecuteCommand $ \req responder -> do + liftIO $ debugM "reactor.handle" "Processing a workspace/executeCommand request" + let params = req ^. J.params + margs = params ^. J.arguments + + liftIO $ debugM "reactor.handle" $ "The arguments are: " ++ show margs + responder (Right (J.Object mempty)) -- respond to the request + + void $ withProgress "Executing some long running command" Cancellable $ \update -> + forM [(0 :: Double)..10] $ \i -> do + update (ProgressAmount (Just (i * 10)) (Just "Doing stuff")) + liftIO $ threadDelay (1 * 1000000) + ] + +-- --------------------------------------------------------------------- diff --git a/example/Simple.hs b/example/Simple.hs new file mode 100644 index 000000000..abff92098 --- /dev/null +++ b/example/Simple.hs @@ -0,0 +1,49 @@ +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE TypeFamilies #-} + +import Data.Default +import Language.Haskell.LSP.Control +import Language.Haskell.LSP.Core +import Language.Haskell.LSP.Types +import Control.Monad.IO.Class +import qualified Data.Text as T + +handlers :: Handlers (LspM ()) +handlers = mconcat + [ notificationHandler SInitialized $ \_not -> do + let params = ShowMessageRequestParams MtInfo "Turn on code lenses?" + (Just [MessageActionItem "Turn on", MessageActionItem "Don't"]) + _ <- sendRequest SWindowShowMessageRequest params $ \res -> + case res of + Right (Just (MessageActionItem "Turn on")) -> do + let regOpts = CodeLensRegistrationOptions Nothing Nothing (Just False) + + _ <- registerCapability STextDocumentCodeLens regOpts $ \_req responder -> do + let cmd = Command "Say hello" "lsp-hello-command" Nothing + rsp = List [CodeLens (mkRange 0 0 0 100) (Just cmd) Nothing] + responder (Right rsp) + pure () + Right _ -> + sendNotification SWindowShowMessage (ShowMessageParams MtInfo "Not turning on code lenses") + Left err -> + sendNotification SWindowShowMessage (ShowMessageParams MtError $ "Something went wrong!\n" <> T.pack (show err)) + pure () + , requestHandler STextDocumentHover $ \req responder -> do + let RequestMessage _ _ _ (HoverParams _doc pos _workDone) = req + Position _l _c' = pos + rsp = Hover ms (Just range) + ms = HoverContents $ markedUpContent "lsp-demo-simple-server" "Hello world" + range = Range pos pos + responder (Right $ Just rsp) + ] + +initCallbacks :: InitializeCallbacks () +initCallbacks = InitializeCallbacks + { onConfigurationChange = const $ pure $ Right () + , doInitialize = \env _req -> pure $ Right env + , staticHandlers = handlers + , interpretHandler = \env -> Iso (runLspT env) liftIO + } + +main :: IO Int +main = run initCallbacks def diff --git a/func-test/FuncTest.hs b/func-test/FuncTest.hs new file mode 100644 index 000000000..9580c1d11 --- /dev/null +++ b/func-test/FuncTest.hs @@ -0,0 +1,123 @@ +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE GADTs, OverloadedStrings #-} +module Main where + +import Data.Default +import Language.Haskell.LSP.Core +import Language.Haskell.LSP.Control +import qualified Language.Haskell.LSP.Test as Test +import Language.Haskell.LSP.Types +import Language.Haskell.LSP.Types.Lens +import Control.Monad.IO.Class +import System.IO +import Control.Concurrent +import Control.Monad +import System.Process +import Control.Applicative.Combinators +import Control.Monad.Trans.Control +import Control.Lens hiding (List) +import Test.Hspec +import Data.Maybe +import Control.Concurrent.Async +import Control.Exception +import System.Exit + +main :: IO () +main = hspec $ do + describe "progress reporting" $ + it "sends end notification if thread is killed" $ do + (hinRead, hinWrite) <- createPipe + (houtRead, houtWrite) <- createPipe + + killVar <- newEmptyMVar + + let initCallbacks = InitializeCallbacks + { onConfigurationChange = const $ pure $ Right () + , doInitialize = const $ pure Nothing + } + + handlers :: MVar () -> Handlers () + handlers killVar SInitialized = Just $ \noti -> do + tid <- liftBaseDiscard forkIO $ + withProgress "Doing something" NotCancellable $ \updater -> + liftIO $ threadDelay (1 * 1000000) + liftIO $ void $ forkIO $ do + takeMVar killVar + killThread tid + handlers _ _ = Nothing + + forkIO $ void $ runWithHandles hinRead houtWrite initCallbacks (handlers killVar) def + + Test.runSessionWithHandles hinWrite houtRead Test.defaultConfig Test.fullCaps "." $ do + -- First make sure that we get a $/progress begin notification + skipManyTill Test.anyMessage $ do + x <- Test.message SProgress + let isBegin (Begin _) = True + isBegin _ = False + guard $ isBegin $ x ^. params . value + + -- Then kill the thread + liftIO $ putMVar killVar () + + -- Then make sure we still get a $/progress end notification + skipManyTill Test.anyMessage $ do + x <- Test.message SProgress + let isEnd (End _) = True + isEnd _ = False + guard $ isEnd $ x ^. params . value + + describe "workspace folders" $ + it "keeps track of open workspace folders" $ do + (hinRead, hinWrite) <- createPipe + (houtRead, houtWrite) <- createPipe + + countVar <- newMVar 0 + + let wf0 = WorkspaceFolder "one" "Starter workspace" + wf1 = WorkspaceFolder "/foo/bar" "My workspace" + wf2 = WorkspaceFolder "/foo/baz" "My other workspace" + + initCallbacks = InitializeCallbacks + { onConfigurationChange = const $ pure $ Right () + , doInitialize = const $ pure Nothing + } + + handlers :: Handlers () + handlers SInitialized = Just $ \noti -> do + wfs <- fromJust <$> getWorkspaceFolders + liftIO $ wfs `shouldContain` [wf0] + handlers SWorkspaceDidChangeWorkspaceFolders = Just $ \noti -> do + i <- liftIO $ modifyMVar countVar (\i -> pure (i + 1, i)) + wfs <- fromJust <$> getWorkspaceFolders + liftIO $ case i of + 0 -> do + wfs `shouldContain` [wf1] + wfs `shouldContain` [wf0] + 1 -> do + wfs `shouldNotContain` [wf1] + wfs `shouldContain` [wf0] + wfs `shouldContain` [wf2] + _ -> error "Shouldn't be here" + handlers _ = Nothing + + + server <- async $ void $ runWithHandles hinRead houtWrite initCallbacks handlers def + + let config = Test.defaultConfig + { Test.initialWorkspaceFolders = Just [wf0] + } + + changeFolders add rmv = + let addedFolders = List add + removedFolders = List rmv + ev = WorkspaceFoldersChangeEvent addedFolders removedFolders + ps = DidChangeWorkspaceFoldersParams ev + in Test.sendNotification SWorkspaceDidChangeWorkspaceFolders ps + + Test.runSessionWithHandles hinWrite houtRead config Test.fullCaps "." $ do + changeFolders [wf1] [] + changeFolders [wf2] [wf1] + + Left e <- waitCatch server + fromException e `shouldBe` Just ExitSuccess + \ No newline at end of file diff --git a/func-test/func-test.cabal b/func-test/func-test.cabal new file mode 100644 index 000000000..654cafb6f --- /dev/null +++ b/func-test/func-test.cabal @@ -0,0 +1,18 @@ +cabal-version: >=1.10 +name: func-test +version: 0.1.0.0 +build-type: Simple + +test-suite func-test + main-is: FuncTest.hs + type: exitcode-stdio-1.0 + build-depends: base <4.15 + , lsp-test + , haskell-lsp + , data-default + , process + , lens + , monad-control + , hspec + , async + default-language: Haskell2010 diff --git a/haskell-lsp-types/haskell-lsp-types.cabal b/haskell-lsp-types/haskell-lsp-types.cabal index 6a24bb147..d0db9d78c 100644 --- a/haskell-lsp-types/haskell-lsp-types.cabal +++ b/haskell-lsp-types/haskell-lsp-types.cabal @@ -19,38 +19,59 @@ cabal-version: >=1.10 library exposed-modules: Language.Haskell.LSP.Types , Language.Haskell.LSP.Types.Capabilities - , Language.Haskell.LSP.Types.Constants , Language.Haskell.LSP.Types.Lens - , Language.Haskell.LSP.Types.MessageFuncs - , Language.Haskell.LSP.Types.Utils - other-modules: Language.Haskell.LSP.Types.ClientCapabilities + , Data.IxMap + other-modules: Language.Haskell.LSP.Types.Cancellation + , Language.Haskell.LSP.Types.ClientCapabilities , Language.Haskell.LSP.Types.CodeAction - , Language.Haskell.LSP.Types.Color + , Language.Haskell.LSP.Types.CodeLens , Language.Haskell.LSP.Types.Command + , Language.Haskell.LSP.Types.Common , Language.Haskell.LSP.Types.Completion - , Language.Haskell.LSP.Types.DataTypesJSON + , Language.Haskell.LSP.Types.Configuration + , Language.Haskell.LSP.Types.Declaration + , Language.Haskell.LSP.Types.Definition , Language.Haskell.LSP.Types.Diagnostic + , Language.Haskell.LSP.Types.DocumentColor , Language.Haskell.LSP.Types.DocumentFilter + , Language.Haskell.LSP.Types.DocumentHighlight + , Language.Haskell.LSP.Types.DocumentLink + , Language.Haskell.LSP.Types.DocumentSymbol , Language.Haskell.LSP.Types.FoldingRange + , Language.Haskell.LSP.Types.Formatting , Language.Haskell.LSP.Types.Hover - , Language.Haskell.LSP.Types.List + , Language.Haskell.LSP.Types.Implementation + , Language.Haskell.LSP.Types.Initialize , Language.Haskell.LSP.Types.Location + , Language.Haskell.LSP.Types.LspId , Language.Haskell.LSP.Types.MarkupContent + , Language.Haskell.LSP.Types.Method , Language.Haskell.LSP.Types.Message , Language.Haskell.LSP.Types.Progress - , Language.Haskell.LSP.Types.Symbol + , Language.Haskell.LSP.Types.Registration + , Language.Haskell.LSP.Types.References + , Language.Haskell.LSP.Types.Rename + , Language.Haskell.LSP.Types.SelectionRange + , Language.Haskell.LSP.Types.ServerCapabilities + , Language.Haskell.LSP.Types.SignatureHelp + , Language.Haskell.LSP.Types.StaticRegistrationOptions + , Language.Haskell.LSP.Types.Synonyms , Language.Haskell.LSP.Types.TextDocument + , Language.Haskell.LSP.Types.TypeDefinition , Language.Haskell.LSP.Types.Uri + , Language.Haskell.LSP.Types.Utils , Language.Haskell.LSP.Types.Window + , Language.Haskell.LSP.Types.WatchedFiles , Language.Haskell.LSP.Types.WorkspaceEdit , Language.Haskell.LSP.Types.WorkspaceFolders + , Language.Haskell.LSP.Types.WorkspaceSymbol -- other-extensions: ghc-options: -Wall - -- ghc-options: -Werror build-depends: base >= 4.9 && < 4.15 , aeson >=1.2.2.0 , binary , bytestring + , containers , data-default , deepseq , filepath @@ -58,7 +79,10 @@ library , lens >= 4.15.2 , network-uri , scientific + , some + , dependent-sum-template , text + , template-haskell , unordered-containers hs-source-dirs: src default-language: Haskell2010 diff --git a/haskell-lsp-types/src/Data/IxMap.hs b/haskell-lsp-types/src/Data/IxMap.hs new file mode 100644 index 000000000..699dd559b --- /dev/null +++ b/haskell-lsp-types/src/Data/IxMap.hs @@ -0,0 +1,40 @@ +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE TypeInType #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE ViewPatterns #-} + +module Data.IxMap where + +import qualified Data.Map as M +import Data.Some +import Data.Kind +import Unsafe.Coerce + +-- a `compare` b <=> toBase a `compare` toBase b +-- toBase (i :: f a) == toBase (j :: f b) <=> a ~ b +class Ord (Base f) => IxOrd f where + type Base f + toBase :: forall a. f a -> Base f + +newtype IxMap (k :: a -> Type) (f :: a -> Type) = IxMap { getMap :: M.Map (Base k) (Some f) } + +emptyIxMap :: IxMap k f +emptyIxMap = IxMap M.empty + +insertIxMap :: IxOrd k => k m -> f m -> IxMap k f -> Maybe (IxMap k f) +insertIxMap (toBase -> i) x (IxMap m) + | M.notMember i m = Just $ IxMap $ M.insert i (mkSome x) m + | otherwise = Nothing + +lookupIxMap :: IxOrd k => k m -> IxMap k f -> Maybe (f m) +lookupIxMap i (IxMap m) = + case M.lookup (toBase i) m of + Just (Some v) -> Just $ unsafeCoerce v + Nothing -> Nothing + +pickFromIxMap :: IxOrd k => k m -> IxMap k f -> (Maybe (f m), IxMap k f) +pickFromIxMap i (IxMap m) = + case M.updateLookupWithKey (\_ _ -> Nothing) (toBase i) m of + (Nothing,m') -> (Nothing,IxMap m') + (Just (Some k),m') -> (Just (unsafeCoerce k),IxMap m') diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types.hs index 1108f03db..533dceb1f 100644 --- a/haskell-lsp-types/src/Language/Haskell/LSP/Types.hs +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types.hs @@ -1,44 +1,86 @@ module Language.Haskell.LSP.Types - ( module Language.Haskell.LSP.Types.DataTypesJSON + ( module Language.Haskell.LSP.Types.Cancellation , module Language.Haskell.LSP.Types.CodeAction - , module Language.Haskell.LSP.Types.Color + , module Language.Haskell.LSP.Types.CodeLens , module Language.Haskell.LSP.Types.Command + , module Language.Haskell.LSP.Types.Common , module Language.Haskell.LSP.Types.Completion + , module Language.Haskell.LSP.Types.Configuration + , module Language.Haskell.LSP.Types.Declaration + , module Language.Haskell.LSP.Types.Definition , module Language.Haskell.LSP.Types.Diagnostic + , module Language.Haskell.LSP.Types.DocumentColor , module Language.Haskell.LSP.Types.DocumentFilter + , module Language.Haskell.LSP.Types.DocumentHighlight + , module Language.Haskell.LSP.Types.DocumentLink + , module Language.Haskell.LSP.Types.DocumentSymbol , module Language.Haskell.LSP.Types.FoldingRange + , module Language.Haskell.LSP.Types.Formatting , module Language.Haskell.LSP.Types.Hover - , module Language.Haskell.LSP.Types.List + , module Language.Haskell.LSP.Types.Implementation + , module Language.Haskell.LSP.Types.Initialize , module Language.Haskell.LSP.Types.Location + , module Language.Haskell.LSP.Types.LspId , module Language.Haskell.LSP.Types.MarkupContent + , module Language.Haskell.LSP.Types.Method , module Language.Haskell.LSP.Types.Message , module Language.Haskell.LSP.Types.Progress - , module Language.Haskell.LSP.Types.Symbol + , module Language.Haskell.LSP.Types.References + , module Language.Haskell.LSP.Types.Registration + , module Language.Haskell.LSP.Types.Rename + , module Language.Haskell.LSP.Types.SignatureHelp + , module Language.Haskell.LSP.Types.StaticRegistrationOptions + , module Language.Haskell.LSP.Types.SelectionRange + , module Language.Haskell.LSP.Types.Synonyms , module Language.Haskell.LSP.Types.TextDocument + , module Language.Haskell.LSP.Types.TypeDefinition , module Language.Haskell.LSP.Types.Uri + , module Language.Haskell.LSP.Types.WatchedFiles , module Language.Haskell.LSP.Types.Window , module Language.Haskell.LSP.Types.WorkspaceEdit , module Language.Haskell.LSP.Types.WorkspaceFolders + , module Language.Haskell.LSP.Types.WorkspaceSymbol ) where -import Language.Haskell.LSP.Types.DataTypesJSON +import Language.Haskell.LSP.Types.Cancellation import Language.Haskell.LSP.Types.CodeAction -import Language.Haskell.LSP.Types.Color +import Language.Haskell.LSP.Types.CodeLens import Language.Haskell.LSP.Types.Command +import Language.Haskell.LSP.Types.Common import Language.Haskell.LSP.Types.Completion +import Language.Haskell.LSP.Types.Configuration +import Language.Haskell.LSP.Types.Declaration +import Language.Haskell.LSP.Types.Definition import Language.Haskell.LSP.Types.Diagnostic +import Language.Haskell.LSP.Types.DocumentColor import Language.Haskell.LSP.Types.DocumentFilter +import Language.Haskell.LSP.Types.DocumentHighlight +import Language.Haskell.LSP.Types.DocumentLink +import Language.Haskell.LSP.Types.DocumentSymbol import Language.Haskell.LSP.Types.FoldingRange +import Language.Haskell.LSP.Types.Formatting import Language.Haskell.LSP.Types.Hover -import Language.Haskell.LSP.Types.List +import Language.Haskell.LSP.Types.Implementation +import Language.Haskell.LSP.Types.Initialize import Language.Haskell.LSP.Types.Location +import Language.Haskell.LSP.Types.LspId import Language.Haskell.LSP.Types.MarkupContent +import Language.Haskell.LSP.Types.Method import Language.Haskell.LSP.Types.Message import Language.Haskell.LSP.Types.Progress -import Language.Haskell.LSP.Types.Symbol +import Language.Haskell.LSP.Types.References +import Language.Haskell.LSP.Types.Registration +import Language.Haskell.LSP.Types.Rename +import Language.Haskell.LSP.Types.SelectionRange +import Language.Haskell.LSP.Types.SignatureHelp +import Language.Haskell.LSP.Types.StaticRegistrationOptions +import Language.Haskell.LSP.Types.Synonyms import Language.Haskell.LSP.Types.TextDocument +import Language.Haskell.LSP.Types.TypeDefinition import Language.Haskell.LSP.Types.Uri +import Language.Haskell.LSP.Types.WatchedFiles import Language.Haskell.LSP.Types.Window import Language.Haskell.LSP.Types.WorkspaceEdit import Language.Haskell.LSP.Types.WorkspaceFolders +import Language.Haskell.LSP.Types.WorkspaceSymbol diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/Cancellation.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Cancellation.hs new file mode 100644 index 000000000..0638da23b --- /dev/null +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Cancellation.hs @@ -0,0 +1,27 @@ +{-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE GADTs #-} +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE StandaloneDeriving #-} +{-# LANGUAGE DuplicateRecordFields #-} +module Language.Haskell.LSP.Types.Cancellation where + +import Data.Aeson.TH +import Language.Haskell.LSP.Types.LspId +import Language.Haskell.LSP.Types.Utils + +data CancelParams = forall m. + CancelParams + { -- | The request id to cancel. + _id :: LspId m + } + +deriving instance Read CancelParams +deriving instance Show CancelParams +instance Eq CancelParams where + (CancelParams a) == CancelParams b = + case (a,b) of + (IdInt x, IdInt y) -> x == y + (IdString x, IdString y) -> x == y + _ -> False + +deriveJSON lspOptions ''CancelParams diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/Capabilities.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Capabilities.hs index 24a695a56..14ff46877 100644 --- a/haskell-lsp-types/src/Language/Haskell/LSP/Types/Capabilities.hs +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Capabilities.hs @@ -1,6 +1,8 @@ module Language.Haskell.LSP.Types.Capabilities ( module Language.Haskell.LSP.Types.ClientCapabilities + , module Language.Haskell.LSP.Types.ServerCapabilities + , module Language.Haskell.LSP.Types.WorkspaceEdit , fullCaps , LSPVersion(..) , capsForVersion @@ -8,10 +10,11 @@ module Language.Haskell.LSP.Types.Capabilities import Prelude hiding (min) import Language.Haskell.LSP.Types.ClientCapabilities +import Language.Haskell.LSP.Types.ServerCapabilities +import Language.Haskell.LSP.Types.WorkspaceEdit import Language.Haskell.LSP.Types --- | The whole shebang. The real deal. --- Capabilities for full conformance to the current (v3.10) LSP specification. +-- | Capabilities for full conformance to the current (v3.15) LSP specification. fullCaps :: ClientCapabilities fullCaps = capsForVersion (LSPVersion maxBound maxBound) @@ -31,24 +34,33 @@ data LSPVersion = LSPVersion Int Int -- ^ Construct a major.minor version -- * 3.4 extended completion item and symbol item kinds -- * 3.0 dynamic registration capsForVersion :: LSPVersion -> ClientCapabilities -capsForVersion (LSPVersion maj min) = ClientCapabilities (Just w) (Just td) Nothing Nothing +capsForVersion (LSPVersion maj min) = ClientCapabilities (Just w) (Just td) (Just window) Nothing where w = WorkspaceClientCapabilities (Just True) - (Just (WorkspaceEditClientCapabilities (Just True))) + (Just (WorkspaceEditClientCapabilities + (Just True) + (since 3 13 resourceOperations) + Nothing)) (Just (DidChangeConfigurationClientCapabilities dynamicReg)) (Just (DidChangeWatchedFilesClientCapabilities dynamicReg)) (Just symbolCapabilities) - (Just (ExecuteClientCapabilities dynamicReg)) + (Just (ExecuteCommandClientCapabilities dynamicReg)) (since 3 6 True) (since 3 6 True) - - symbolCapabilities = SymbolClientCapabilities + + resourceOperations = List + [ ResourceOperationCreate + , ResourceOperationDelete + , ResourceOperationRename + ] + + symbolCapabilities = WorkspaceSymbolClientCapabilities dynamicReg (since 3 4 symbolKindCapabilities) symbolKindCapabilities = - SymbolKindClientCapabilities (Just sKs) + WorkspaceSymbolKindClientCapabilities (Just sKs) sKs | maj >= 3 && min >= 4 = List (oldSKs ++ newSKs) @@ -92,21 +104,23 @@ capsForVersion (LSPVersion maj min) = ClientCapabilities (Just w) (Just td) Noth (Just (ReferencesClientCapabilities dynamicReg)) (Just (DocumentHighlightClientCapabilities dynamicReg)) (Just documentSymbolCapability) - (Just (FormattingClientCapabilities (Just True))) - (Just (RangeFormattingClientCapabilities dynamicReg)) - (Just (OnTypeFormattingClientCapabilities dynamicReg)) - (Just (DefinitionClientCapabilities dynamicReg)) - (since 3 6 (TypeDefinitionClientCapabilities dynamicReg)) - (since 3 6 (ImplementationClientCapabilities dynamicReg)) + (Just (DocumentFormattingClientCapabilities dynamicReg)) + (Just (DocumentRangeFormattingClientCapabilities dynamicReg)) + (Just (DocumentOnTypeFormattingClientCapabilities dynamicReg)) + (since 3 14 (DeclarationClientCapabilities dynamicReg (Just True))) + (Just (DefinitionClientCapabilities dynamicReg (since 3 14 True))) + (since 3 6 (TypeDefinitionClientCapabilities dynamicReg (since 3 14 True))) + (since 3 6 (ImplementationClientCapabilities dynamicReg (since 3 14 True))) (Just codeActionCapability) (Just (CodeLensClientCapabilities dynamicReg)) - (Just (DocumentLinkClientCapabilities dynamicReg)) - (since 3 6 (ColorProviderClientCapabilities dynamicReg)) + (Just (DocumentLinkClientCapabilities dynamicReg (since 3 15 True))) + (since 3 6 (DocumentColorClientCapabilities dynamicReg)) (Just (RenameClientCapabilities dynamicReg (since 3 12 True))) (Just publishDiagnosticsCapabilities) (since 3 10 foldingRangeCapability) + (since 3 5 (SelectionRangeClientCapabilities dynamicReg)) sync = - SynchronizationTextDocumentClientCapabilities + TextDocumentSyncClientCapabilities dynamicReg (Just True) (Just True) @@ -175,6 +189,7 @@ capsForVersion (LSPVersion maj min) = ClientCapabilities (Just w) (Just td) Noth = CodeActionClientCapabilities dynamicReg (since 3 8 (CodeActionLiteralSupport caKs)) + (since 3 15 True) caKs = CodeActionKindClientCapabilities (List [ CodeActionQuickFix , CodeActionRefactor @@ -189,10 +204,11 @@ capsForVersion (LSPVersion maj min) = ClientCapabilities (Just w) (Just td) Noth SignatureHelpClientCapabilities dynamicReg (Just signatureInformationCapability) + Nothing signatureInformationCapability = - SignatureInformationClientCapabilities - (Just (List [MkPlainText, MkMarkdown])) + SignatureHelpSignatureInformation + (Just (List [MkPlainText, MkMarkdown])) Nothing documentSymbolCapability = DocumentSymbolClientCapabilities @@ -214,6 +230,7 @@ capsForVersion (LSPVersion maj min) = ClientCapabilities (Just w) (Just td) Noth PublishDiagnosticsClientCapabilities (since 3 7 True) (since 3 15 publishDiagnosticsTagsCapabilities) + (since 3 15 True) publishDiagnosticsTagsCapabilities = PublishDiagnosticsTagsClientCapabilities @@ -225,3 +242,5 @@ capsForVersion (LSPVersion maj min) = ClientCapabilities (Just w) (Just td) Noth since x y a | maj >= x && min >= y = Just a | otherwise = Nothing + + window = WindowClientCapabilities (since 3 15 True) diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/ClientCapabilities.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/ClientCapabilities.hs index 27afb2231..6ad409f84 100644 --- a/haskell-lsp-types/src/Language/Haskell/LSP/Types/ClientCapabilities.hs +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/ClientCapabilities.hs @@ -6,203 +6,33 @@ module Language.Haskell.LSP.Types.ClientCapabilities where import Data.Aeson.TH import qualified Data.Aeson as A import Data.Default -import Language.Haskell.LSP.Types.Constants import Language.Haskell.LSP.Types.CodeAction +import Language.Haskell.LSP.Types.CodeLens +import Language.Haskell.LSP.Types.Command import Language.Haskell.LSP.Types.Completion +import Language.Haskell.LSP.Types.Configuration import Language.Haskell.LSP.Types.Diagnostic -import Language.Haskell.LSP.Types.List -import Language.Haskell.LSP.Types.MarkupContent -import Language.Haskell.LSP.Types.Symbol +import Language.Haskell.LSP.Types.Declaration +import Language.Haskell.LSP.Types.Definition +import Language.Haskell.LSP.Types.DocumentColor +import Language.Haskell.LSP.Types.DocumentHighlight +import Language.Haskell.LSP.Types.DocumentLink +import Language.Haskell.LSP.Types.DocumentSymbol +import Language.Haskell.LSP.Types.FoldingRange +import Language.Haskell.LSP.Types.Formatting +import Language.Haskell.LSP.Types.Hover +import Language.Haskell.LSP.Types.Implementation +import Language.Haskell.LSP.Types.References +import Language.Haskell.LSP.Types.Rename +import Language.Haskell.LSP.Types.SelectionRange +import Language.Haskell.LSP.Types.SignatureHelp +import Language.Haskell.LSP.Types.TextDocument +import Language.Haskell.LSP.Types.TypeDefinition +import Language.Haskell.LSP.Types.Utils +import Language.Haskell.LSP.Types.WatchedFiles +import Language.Haskell.LSP.Types.WorkspaceEdit +import Language.Haskell.LSP.Types.WorkspaceSymbol --- --------------------------------------------------------------------- -{- -New in 3.0 ----------- - -/** - * Workspace specific client capabilities. - */ -export interface WorkspaceClientCapabilities { - /** - * The client supports applying batch edits to the workspace by supporting - * the request 'workspace/applyEdit' - */ - applyEdit?: boolean; - - /** - * Capabilities specific to `WorkspaceEdit`s - */ - workspaceEdit?: { - /** - * The client supports versioned document changes in `WorkspaceEdit`s - */ - documentChanges?: boolean; - }; - - /** - * Capabilities specific to the `workspace/didChangeConfiguration` notification. - */ - didChangeConfiguration?: { - /** - * Did change configuration notification supports dynamic registration. - */ - dynamicRegistration?: boolean; - }; - - /** - * Capabilities specific to the `workspace/didChangeWatchedFiles` notification. - */ - didChangeWatchedFiles?: { - /** - * Did change watched files notification supports dynamic registration. - */ - dynamicRegistration?: boolean; - }; - - /** - * Capabilities specific to the `workspace/symbol` request. - */ - symbol?: { - /** - * Symbol request supports dynamic registration. - */ - dynamicRegistration?: boolean; - - /** - * Specific capabilities for the `SymbolKind` in the `workspace/symbol` request. - */ - symbolKind?: { - /** - * The symbol kind values the client supports. When this - * property exists the client also guarantees that it will - * handle values outside its set gracefully and falls back - * to a default value when unknown. - * - * If this property is not present the client only supports - * the symbol kinds from `File` to `Array` as defined in - * the initial version of the protocol. - */ - valueSet?: SymbolKind[]; - } - }; - - /** - * Capabilities specific to the `workspace/executeCommand` request. - */ - executeCommand?: { - /** - * Execute command supports dynamic registration. - */ - dynamicRegistration?: boolean; - }; - - /** - * The client has support for workspace folders. - * - * Since 3.6.0 - */ - workspaceFolders?: boolean; - - /** - * The client supports `workspace/configuration` requests. - * - * Since 3.6.0 - */ - configuration?: boolean; -} --} - --- ------------------------------------- - -data WorkspaceEditClientCapabilities = - WorkspaceEditClientCapabilities - { _documentChanges :: Maybe Bool -- ^The client supports versioned document - -- changes in `WorkspaceEdit`s - } deriving (Show, Read, Eq) - -$(deriveJSON lspOptions ''WorkspaceEditClientCapabilities) - --- ------------------------------------- - -data DidChangeConfigurationClientCapabilities = - DidChangeConfigurationClientCapabilities - { _dynamicRegistration :: Maybe Bool -- ^Did change configuration - -- notification supports dynamic - -- registration. - } deriving (Show, Read, Eq) - -$(deriveJSON lspOptions ''DidChangeConfigurationClientCapabilities) - --- ------------------------------------- - -data DidChangeWatchedFilesClientCapabilities = - DidChangeWatchedFilesClientCapabilities - { _dynamicRegistration :: Maybe Bool -- ^Did change watched files - -- notification supports dynamic - -- registration. - } deriving (Show, Read, Eq) - -$(deriveJSON lspOptions ''DidChangeWatchedFilesClientCapabilities) - --- ------------------------------------- - -data SymbolKindClientCapabilities = - SymbolKindClientCapabilities - { -- | The symbol kind values the client supports. When this - -- property exists the client also guarantees that it will - -- handle values outside its set gracefully and falls back - -- to a default value when unknown. - -- - -- If this property is not present the client only supports - -- the symbol kinds from `File` to `Array` as defined in - -- the initial version of the protocol. - _valueSet :: Maybe (List SymbolKind) - } deriving (Show, Read, Eq) - -$(deriveJSON lspOptions ''SymbolKindClientCapabilities) - -instance Default SymbolKindClientCapabilities where - def = SymbolKindClientCapabilities (Just $ List allKinds) - where allKinds = [ SkFile - , SkModule - , SkNamespace - , SkPackage - , SkClass - , SkMethod - , SkProperty - , SkField - , SkConstructor - , SkEnum - , SkInterface - , SkFunction - , SkVariable - , SkConstant - , SkString - , SkNumber - , SkBoolean - , SkArray - ] - -data SymbolClientCapabilities = - SymbolClientCapabilities - { _dynamicRegistration :: Maybe Bool -- ^Symbol request supports dynamic - -- registration. - , _symbolKind :: Maybe SymbolKindClientCapabilities -- ^ Specific capabilities for the `SymbolKind`. - } deriving (Show, Read, Eq) - -$(deriveJSON lspOptions ''SymbolClientCapabilities) - --- ------------------------------------- - -data ExecuteClientCapabilities = - ExecuteClientCapabilities - { _dynamicRegistration :: Maybe Bool -- ^Execute command supports dynamic - -- registration. - } deriving (Show, Read, Eq) - -$(deriveJSON lspOptions ''ExecuteClientCapabilities) - --- ------------------------------------- data WorkspaceClientCapabilities = WorkspaceClientCapabilities @@ -220,10 +50,10 @@ data WorkspaceClientCapabilities = , _didChangeWatchedFiles :: Maybe DidChangeWatchedFilesClientCapabilities -- | Capabilities specific to the `workspace/symbol` request. - , _symbol :: Maybe SymbolClientCapabilities + , _symbol :: Maybe WorkspaceSymbolClientCapabilities -- | Capabilities specific to the `workspace/executeCommand` request. - , _executeCommand :: Maybe ExecuteClientCapabilities + , _executeCommand :: Maybe ExecuteCommandClientCapabilities -- | The client has support for workspace folders. , _workspaceFolders :: Maybe Bool @@ -232,745 +62,16 @@ data WorkspaceClientCapabilities = , _configuration :: Maybe Bool } deriving (Show, Read, Eq) -$(deriveJSON lspOptions ''WorkspaceClientCapabilities) +deriveJSON lspOptions ''WorkspaceClientCapabilities instance Default WorkspaceClientCapabilities where def = WorkspaceClientCapabilities def def def def def def def def --- --------------------------------------------------------------------- -{- -New in 3.0 ----------- -/** - * Text document specific client capabilities. - */ -export interface TextDocumentClientCapabilities { - - synchronization?: { - /** - * Whether text document synchronization supports dynamic registration. - */ - dynamicRegistration?: boolean; - - /** - * The client supports sending will save notifications. - */ - willSave?: boolean; - - /** - * The client supports sending a will save request and - * waits for a response providing text edits which will - * be applied to the document before it is saved. - */ - willSaveWaitUntil?: boolean; - - /** - * The client supports did save notifications. - */ - didSave?: boolean; - } - - /** - * Capabilities specific to the `textDocument/completion` - */ - completion?: { - /** - * Whether completion supports dynamic registration. - */ - dynamicRegistration?: boolean; - - /** - * The client supports the following `CompletionItem` specific - * capabilities. - */ - completionItem?: { - /** - * Client supports snippets as insert text. - * - * A snippet can define tab stops and placeholders with `$1`, `$2` - * and `${3:foo}`. `$0` defines the final tab stop, it defaults to - * the end of the snippet. Placeholders with equal identifiers are linked, - * that is typing in one will update others too. - */ - snippetSupport?: boolean; - - /** - * Client supports commit characters on a completion item. - */ - commitCharactersSupport?: boolean - - /** - * Client supports the follow content formats for the documentation - * property. The order describes the preferred format of the client. - */ - documentationFormat?: MarkupKind[]; - - /** - * Client supports the deprecated property on a completion item. - */ - deprecatedSupport?: boolean; - - /** - * Client supports the preselect property on a completion item. - */ - preselectSupport?: boolean; - } - - completionItemKind?: { - /** - * The completion item kind values the client supports. When this - * property exists the client also guarantees that it will - * handle values outside its set gracefully and falls back - * to a default value when unknown. - * - * If this property is not present the client only supports - * the completion items kinds from `Text` to `Reference` as defined in - * the initial version of the protocol. - */ - valueSet?: CompletionItemKind[]; - }, - - /** - * The client supports to send additional context information for a - * `textDocument/completion` request. - */ - contextSupport?: boolean; - }; - - /** - * Capabilities specific to the `textDocument/hover` - */ - hover?: { - /** - * Whether hover supports dynamic registration. - */ - dynamicRegistration?: boolean; - - /** - * Client supports the follow content formats for the content - * property. The order describes the preferred format of the client. - */ - contentFormat?: MarkupKind[]; - }; - - /** - * Capabilities specific to the `textDocument/signatureHelp` - */ - signatureHelp?: { - /** - * Whether signature help supports dynamic registration. - */ - dynamicRegistration?: boolean; - - /** - * The client supports the following `SignatureInformation` - * specific properties. - */ - signatureInformation?: { - /** - * Client supports the follow content formats for the documentation - * property. The order describes the preferred format of the client. - */ - documentationFormat?: MarkupKind[]; - }; - }; - - /** - * Capabilities specific to the `textDocument/references` - */ - references?: { - /** - * Whether references supports dynamic registration. - */ - dynamicRegistration?: boolean; - }; - - /** - * Capabilities specific to the `textDocument/documentHighlight` - */ - documentHighlight?: { - /** - * Whether document highlight supports dynamic registration. - */ - dynamicRegistration?: boolean; - }; - - /** - * Capabilities specific to the `textDocument/documentSymbol` - */ - documentSymbol?: { - /** - * Whether document symbol supports dynamic registration. - */ - dynamicRegistration?: boolean; - - /** - * Specific capabilities for the `SymbolKind`. - */ - symbolKind?: { - /** - * The symbol kind values the client supports. When this - * property exists the client also guarantees that it will - * handle values outside its set gracefully and falls back - * to a default value when unknown. - * - * If this property is not present the client only supports - * the symbol kinds from `File` to `Array` as defined in - * the initial version of the protocol. - */ - valueSet?: SymbolKind[]; - } - }; - - /** - * Capabilities specific to the `textDocument/formatting` - */ - formatting?: { - /** - * Whether formatting supports dynamic registration. - */ - dynamicRegistration?: boolean; - }; - - /** - * Capabilities specific to the `textDocument/rangeFormatting` - */ - rangeFormatting?: { - /** - * Whether range formatting supports dynamic registration. - */ - dynamicRegistration?: boolean; - }; - - /** - * Capabilities specific to the `textDocument/onTypeFormatting` - */ - onTypeFormatting?: { - /** - * Whether on type formatting supports dynamic registration. - */ - dynamicRegistration?: boolean; - }; - - /** - * Capabilities specific to the `textDocument/definition` - */ - definition?: { - /** - * Whether definition supports dynamic registration. - */ - dynamicRegistration?: boolean; - }; - - /** - * Capabilities specific to the `textDocument/typeDefinition` - * - * Since 3.6.0 - */ - typeDefinition?: { - /** - * Whether typeDefinition supports dynamic registration. If this is set to `true` - * the client supports the new `(TextDocumentRegistrationOptions & StaticRegistrationOptions)` - * return value for the corresponding server capability as well. - */ - dynamicRegistration?: boolean; - }; - - /** - * Capabilities specific to the `textDocument/implementation`. - * - * Since 3.6.0 - */ - implementation?: { - /** - * Whether implementation supports dynamic registration. If this is set to `true` - * the client supports the new `(TextDocumentRegistrationOptions & StaticRegistrationOptions)` - * return value for the corresponding server capability as well. - */ - dynamicRegistration?: boolean; - }; - - /** - * Capabilities specific to the `textDocument/codeAction` - */ - codeAction?: { - /** - * Whether code action supports dynamic registration. - */ - dynamicRegistration?: boolean; - /** - * The client support code action literals as a valid - * response of the `textDocument/codeAction` request. - * - * Since 3.8.0 - */ - codeActionLiteralSupport?: { - /** - * The code action kind is support with the following value - * set. - */ - codeActionKind: { - - /** - * The code action kind values the client supports. When this - * property exists the client also guarantees that it will - * handle values outside its set gracefully and falls back - * to a default value when unknown. - */ - valueSet: CodeActionKind[]; - }; - }; - }; - - /** - * Capabilities specific to the `textDocument/codeLens` - */ - codeLens?: { - /** - * Whether code lens supports dynamic registration. - */ - dynamicRegistration?: boolean; - }; - - /** - * Capabilities specific to the `textDocument/documentLink` - */ - documentLink?: { - /** - * Whether document link supports dynamic registration. - */ - dynamicRegistration?: boolean; - }; - - /** - * Capabilities specific to the `textDocument/documentColor` and the - * `textDocument/colorPresentation` request. - * - * Since 3.6.0 - */ - colorProvider?: { - /** - * Whether colorProvider supports dynamic registration. If this is set to `true` - * the client supports the new `(ColorProviderOptions & TextDocumentRegistrationOptions & StaticRegistrationOptions)` - * return value for the corresponding server capability as well. - */ - dynamicRegistration?: boolean; - } - - /** - * Capabilities specific to the `textDocument/rename` - */ - rename?: { - /** - * Whether rename supports dynamic registration. - */ - dynamicRegistration?: boolean; - /** - * The client supports testing for validity of rename operations - * before execution. - * - * Since 3.12.0 - */ - prepareSupport?: boolean; - }; - - /** - * Capabilities specific to `textDocument/publishDiagnostics`. - */ - publishDiagnostics?: { - /** - * Whether the clients accepts diagnostics with related information. - */ - relatedInformation?: boolean; - }; - - /** - * Capabilities specific to `textDocument/foldingRange` requests. - * - * Since 3.10.0 - */ - foldingRange?: { - /** - * Whether implementation supports dynamic registration for folding range providers. If this is set to `true` - * the client supports the new `(FoldingRangeProviderOptions & TextDocumentRegistrationOptions & StaticRegistrationOptions)` - * return value for the corresponding server capability as well. - */ - dynamicRegistration?: boolean; - /** - * The maximum number of folding ranges that the client prefers to receive per document. The value serves as a - * hint, servers are free to follow the limit. - */ - rangeLimit?: number; - /** - * If set, the client signals that it only supports folding complete lines. If set, client will - * ignore specified `startCharacter` and `endCharacter` properties in a FoldingRange. - */ - lineFoldingOnly?: boolean; - }; -} - --} - --- ------------------------------------- - --- TODO:AZ: this name is Java-ridiculously long -data SynchronizationTextDocumentClientCapabilities = - SynchronizationTextDocumentClientCapabilities - { -- | Whether text document synchronization supports dynamic registration. - _dynamicRegistration :: Maybe Bool - - -- | The client supports sending will save notifications. - , _willSave :: Maybe Bool - - -- | The client supports sending a will save request and waits for a - -- response providing text edits which will be applied to the document - -- before it is saved. - , _willSaveWaitUntil :: Maybe Bool - - -- | The client supports did save notifications. - , _didSave :: Maybe Bool - } deriving (Show, Read, Eq) - -$(deriveJSON lspOptions ''SynchronizationTextDocumentClientCapabilities) - -instance Default SynchronizationTextDocumentClientCapabilities where - def = SynchronizationTextDocumentClientCapabilities def def def def - --- ------------------------------------- - -data CompletionItemTagsClientCapabilities = - CompletionItemTagsClientCapabilities - { -- | The tag supported by the client. - _valueSet :: List CompletionItemTag - } deriving (Show, Read, Eq) - -$(deriveJSON lspOptions ''CompletionItemTagsClientCapabilities) - -data CompletionItemClientCapabilities = - CompletionItemClientCapabilities - { -- | Client supports snippets as insert text. - -- - -- A snippet can define tab stops and placeholders with `$1`, `$2` and - -- `${3:foo}`. `$0` defines the final tab stop, it defaults to the end of - -- the snippet. Placeholders with equal identifiers are linked, that is - -- typing in one will update others too. - _snippetSupport :: Maybe Bool - - -- | Client supports commit characters on a completion item. - , _commitCharactersSupport :: Maybe Bool - - -- | Client supports the follow content formats for the documentation - -- property. The order describes the preferred format of the client. - , _documentationFormat :: Maybe (List MarkupKind) - - -- | Client supports the deprecated property on a completion item. - , _deprecatedSupport :: Maybe Bool - - -- | Client supports the preselect property on a completion item. - , _preselectSupport :: Maybe Bool - - -- | Client supports the tag property on a completion item. Clients - -- supporting tags have to handle unknown tags gracefully. Clients - -- especially need to preserve unknown tags when sending a - -- completion item back to the server in a resolve call. - , _tagSupport :: Maybe CompletionItemTagsClientCapabilities - } deriving (Show, Read, Eq) - -$(deriveJSON lspOptions ''CompletionItemClientCapabilities) - -data CompletionItemKindClientCapabilities = - CompletionItemKindClientCapabilities - { -- | The completion item kind values the client supports. When this - -- property exists the client also guarantees that it will - -- handle values outside its set gracefully and falls back - -- to a default value when unknown. - _valueSet :: Maybe (List CompletionItemKind) - } - deriving (Show, Read, Eq) - -$(deriveJSON lspOptions ''CompletionItemKindClientCapabilities) - -data CompletionClientCapabilities = - CompletionClientCapabilities - { _dynamicRegistration :: Maybe Bool -- ^Whether completion supports dynamic - -- registration. - , _completionItem :: Maybe CompletionItemClientCapabilities - , _completionItemKind :: Maybe CompletionItemKindClientCapabilities - , _contextSupport :: Maybe Bool - } deriving (Show, Read, Eq) - -$(deriveJSON lspOptions ''CompletionClientCapabilities) - --- ------------------------------------- - -data HoverClientCapabilities = - HoverClientCapabilities - { _dynamicRegistration :: Maybe Bool - , _contentFormat :: Maybe (List MarkupKind) - } deriving (Show, Read, Eq) - -$(deriveJSON lspOptions ''HoverClientCapabilities) - --- ------------------------------------- - -data SignatureInformationClientCapabilities = - SignatureInformationClientCapabilities - { -- | Client supports the follow content formats for the documentation - -- property. The order describes the preferred format of the client. - documentationFormat :: Maybe (List MarkupKind) - } - deriving (Show, Read, Eq) - -$(deriveJSON lspOptions ''SignatureInformationClientCapabilities) - -data SignatureHelpClientCapabilities = - SignatureHelpClientCapabilities - { -- | Whether signature help supports dynamic registration. - _dynamicRegistration :: Maybe Bool - - -- | The client supports the following `SignatureInformation` - -- specific properties. - , _signatureInformation :: Maybe SignatureInformationClientCapabilities - } deriving (Show, Read, Eq) - -$(deriveJSON lspOptions ''SignatureHelpClientCapabilities) - --- ------------------------------------- - -data ReferencesClientCapabilities = - ReferencesClientCapabilities - { _dynamicRegistration :: Maybe Bool - } deriving (Show, Read, Eq) - -$(deriveJSON lspOptions ''ReferencesClientCapabilities) - --- ------------------------------------- - -data DocumentHighlightClientCapabilities = - DocumentHighlightClientCapabilities - { _dynamicRegistration :: Maybe Bool - } deriving (Show, Read, Eq) - -$(deriveJSON lspOptions ''DocumentHighlightClientCapabilities) - --- ------------------------------------- - -data DocumentSymbolKindClientCapabilities = - DocumentSymbolKindClientCapabilities - { -- | The symbol kind values the client supports. When this - -- property exists the client also guarantees that it will - -- handle values outside its set gracefully and falls back - -- to a default value when unknown. - -- - -- If this property is not present the client only supports - -- the symbol kinds from `File` to `Array` as defined in - -- the initial version of the protocol. - _valueSet :: Maybe (List SymbolKind) - } - deriving (Show, Read, Eq) - -$(deriveJSON lspOptions ''DocumentSymbolKindClientCapabilities) - -data DocumentSymbolClientCapabilities = - DocumentSymbolClientCapabilities - { -- | Whether document symbol supports dynamic registration. - _dynamicRegistration :: Maybe Bool - -- | Specific capabilities for the `SymbolKind`. - , _symbolKind :: Maybe DocumentSymbolKindClientCapabilities - , _hierarchicalDocumentSymbolSupport :: Maybe Bool - } deriving (Show, Read, Eq) - -$(deriveJSON lspOptions ''DocumentSymbolClientCapabilities) - --- ------------------------------------- - -data FormattingClientCapabilities = - FormattingClientCapabilities - { _dynamicRegistration :: Maybe Bool - } deriving (Show, Read, Eq) - -$(deriveJSON lspOptions ''FormattingClientCapabilities) - --- ------------------------------------- - -data RangeFormattingClientCapabilities = - RangeFormattingClientCapabilities - { _dynamicRegistration :: Maybe Bool - } deriving (Show, Read, Eq) - -$(deriveJSON lspOptions ''RangeFormattingClientCapabilities) - --- ------------------------------------- - -data OnTypeFormattingClientCapabilities = - OnTypeFormattingClientCapabilities - { _dynamicRegistration :: Maybe Bool - } deriving (Show, Read, Eq) - -$(deriveJSON lspOptions ''OnTypeFormattingClientCapabilities) - --- ------------------------------------- - -data DefinitionClientCapabilities = - DefinitionClientCapabilities - { _dynamicRegistration :: Maybe Bool - } deriving (Show, Read, Eq) - -$(deriveJSON lspOptions ''DefinitionClientCapabilities) - --- ------------------------------------- - -data TypeDefinitionClientCapabilities = - TypeDefinitionClientCapabilities - { -- | Whether typeDefinition supports dynamic registration. If this is set to `true` - -- the client supports the new `(TextDocumentRegistrationOptions & StaticRegistrationOptions)` - -- return value for the corresponding server capability as well. - _dynamicRegistration :: Maybe Bool - } deriving (Show, Read, Eq) - -$(deriveJSON lspOptions ''TypeDefinitionClientCapabilities) - --- ------------------------------------- --- -data ImplementationClientCapabilities = - ImplementationClientCapabilities - { -- | Whether implementation supports dynamic registration. If this is set to `true` - -- the client supports the new `(TextDocumentRegistrationOptions & StaticRegistrationOptions)` - -- return value for the corresponding server capability as well. - _dynamicRegistration :: Maybe Bool - } deriving (Show, Read, Eq) - -$(deriveJSON lspOptions ''ImplementationClientCapabilities) - --- ------------------------------------- - -data CodeActionKindClientCapabilities = - CodeActionKindClientCapabilities - { -- | The code action kind values the client supports. When this - -- property exists the client also guarantees that it will - -- handle values outside its set gracefully and falls back - -- to a default value when unknown. - _valueSet :: List CodeActionKind - } deriving (Show, Read, Eq) - -$(deriveJSON lspOptions ''CodeActionKindClientCapabilities) - -instance Default CodeActionKindClientCapabilities where - def = CodeActionKindClientCapabilities (List allKinds) - where allKinds = [ CodeActionQuickFix - , CodeActionRefactor - , CodeActionRefactorExtract - , CodeActionRefactorInline - , CodeActionRefactorRewrite - , CodeActionSource - , CodeActionSourceOrganizeImports - ] - -data CodeActionLiteralSupport = - CodeActionLiteralSupport - { _codeActionKind :: CodeActionKindClientCapabilities -- ^ The code action kind is support with the following value set. - } deriving (Show, Read, Eq) - -$(deriveJSON lspOptions ''CodeActionLiteralSupport) - -data CodeActionClientCapabilities = - CodeActionClientCapabilities - { _dynamicRegistration :: Maybe Bool -- ^ Whether code action supports dynamic registration. - , _codeActionLiteralSupport :: Maybe CodeActionLiteralSupport -- ^ The client support code action literals as a valid response - -- of the `textDocument/codeAction` request. - -- Since 3.8.0 - } deriving (Show, Read, Eq) - -$(deriveJSON lspOptions ''CodeActionClientCapabilities) - --- ------------------------------------- - -data CodeLensClientCapabilities = - CodeLensClientCapabilities - { _dynamicRegistration :: Maybe Bool - } deriving (Show, Read, Eq) - -$(deriveJSON lspOptions ''CodeLensClientCapabilities) - --- ------------------------------------- - -data DocumentLinkClientCapabilities = - DocumentLinkClientCapabilities - { _dynamicRegistration :: Maybe Bool - } deriving (Show, Read, Eq) - -$(deriveJSON lspOptions ''DocumentLinkClientCapabilities) - --- ------------------------------------- - -data ColorProviderClientCapabilities = - ColorProviderClientCapabilities - { -- | Whether colorProvider supports dynamic registration. If this is set to `true` - -- the client supports the new `(ColorProviderOptions & TextDocumentRegistrationOptions & StaticRegistrationOptions)` - -- return value for the corresponding server capability as well. - _dynamicRegistration :: Maybe Bool - } deriving (Show, Read, Eq) - -$(deriveJSON lspOptions ''ColorProviderClientCapabilities) - --- ------------------------------------- - -data RenameClientCapabilities = - RenameClientCapabilities - { _dynamicRegistration :: Maybe Bool - , _prepareSupport :: Maybe Bool - } deriving (Show, Read, Eq) - -$(deriveJSON lspOptions ''RenameClientCapabilities) - --- ------------------------------------- - -data PublishDiagnosticsTagsClientCapabilities = - PublishDiagnosticsTagsClientCapabilities - { -- | The tags supported by the client. - _valueSet :: List DiagnosticTag - } deriving (Show, Read, Eq) - -$(deriveJSON lspOptions ''PublishDiagnosticsTagsClientCapabilities) - -data PublishDiagnosticsClientCapabilities = - PublishDiagnosticsClientCapabilities - { -- | Whether the clients accepts diagnostics with related information. - _relatedInformation :: Maybe Bool - -- | Client supports the tag property to provide metadata about a - -- diagnostic. - -- - -- Clients supporting tags have to handle unknown tags gracefully. - , _tagSupport :: Maybe PublishDiagnosticsTagsClientCapabilities - } deriving (Show, Read, Eq) - -$(deriveJSON lspOptions ''PublishDiagnosticsClientCapabilities) - --- ------------------------------------- - -data FoldingRangeClientCapabilities = - FoldingRangeClientCapabilities - { -- | Whether implementation supports dynamic registration for folding range - -- providers. If this is set to `true` the client supports the new - -- `(FoldingRangeProviderOptions & TextDocumentRegistrationOptions & StaticRegistrationOptions)` - -- return value for the corresponding server capability as well. - _dynamicRegistration :: Maybe Bool - -- | The maximum number of folding ranges that the client prefers to receive - -- per document. The value serves as a hint, servers are free to follow the limit. - , _rangeLimit :: Maybe Int - -- | If set, the client signals that it only supports folding complete lines. If set, - -- client will ignore specified `startCharacter` and `endCharacter` properties in a - -- FoldingRange. - , _lineFoldingOnly :: Maybe Bool - } deriving (Show, Read, Eq) - -$(deriveJSON lspOptions ''FoldingRangeClientCapabilities) - -- ------------------------------------- data TextDocumentClientCapabilities = TextDocumentClientCapabilities - { _synchronization :: Maybe SynchronizationTextDocumentClientCapabilities + { _synchronization :: Maybe TextDocumentSyncClientCapabilities -- | Capabilities specific to the `textDocument/completion` , _completion :: Maybe CompletionClientCapabilities @@ -991,13 +92,18 @@ data TextDocumentClientCapabilities = , _documentSymbol :: Maybe DocumentSymbolClientCapabilities -- | Capabilities specific to the `textDocument/formatting` - , _formatting :: Maybe FormattingClientCapabilities + , _formatting :: Maybe DocumentFormattingClientCapabilities -- | Capabilities specific to the `textDocument/rangeFormatting` - , _rangeFormatting :: Maybe RangeFormattingClientCapabilities + , _rangeFormatting :: Maybe DocumentRangeFormattingClientCapabilities -- | Capabilities specific to the `textDocument/onTypeFormatting` - , _onTypeFormatting :: Maybe OnTypeFormattingClientCapabilities + , _onTypeFormatting :: Maybe DocumentOnTypeFormattingClientCapabilities + + -- | Capabilities specific to the `textDocument/declaration` request. + -- + -- Since LSP 3.14.0 + , _declaration :: Maybe DeclarationClientCapabilities -- | Capabilities specific to the `textDocument/definition` , _definition :: Maybe DefinitionClientCapabilities @@ -1019,7 +125,7 @@ data TextDocumentClientCapabilities = -- | Capabilities specific to the `textDocument/documentColor` and the -- `textDocument/colorPresentation` request - , _colorProvider :: Maybe ColorProviderClientCapabilities + , _colorProvider :: Maybe DocumentColorClientCapabilities -- | Capabilities specific to the `textDocument/rename` , _rename :: Maybe RenameClientCapabilities @@ -1027,81 +133,38 @@ data TextDocumentClientCapabilities = -- | Capabilities specific to `textDocument/publishDiagnostics` , _publishDiagnostics :: Maybe PublishDiagnosticsClientCapabilities - -- | Capabilities specific to `textDocument/foldingRange` requests. Since LSP 3.10. + -- | Capabilities specific to the `textDocument/foldingRange` request. + -- Since LSP 3.10. -- -- @since 0.7.0.0 , _foldingRange :: Maybe FoldingRangeClientCapabilities + + -- | Capabilities specific to the `textDocument/selectionRange` request. + -- Since LSP 3.15.0 + , _selectionRange :: Maybe SelectionRangeClientCapabilities } deriving (Show, Read, Eq) -$(deriveJSON lspOptions ''TextDocumentClientCapabilities) +deriveJSON lspOptions ''TextDocumentClientCapabilities instance Default TextDocumentClientCapabilities where def = TextDocumentClientCapabilities def def def def def def def def def def def def def def def def - def def def def + def def def def def def -- --------------------------------------------------------------------- -- | Window specific client capabilities. -data WindowClientCapabilities = +data WindowClientCapabilities = WindowClientCapabilities { -- | Whether client supports handling progress notifications. _workDoneProgress :: Maybe Bool } deriving (Show, Read, Eq) -$(deriveJSON lspOptions ''WindowClientCapabilities) +deriveJSON lspOptions ''WindowClientCapabilities instance Default WindowClientCapabilities where def = WindowClientCapabilities def --- --------------------------------------------------------------------- -{- -New in 3.0 - ------------ - -ClientCapabilities - -now define capabilities for dynamic registration, workspace and text document -features the client supports. The experimental can be used to pass experimential -capabilities under development. For future compatibility a ClientCapabilities -object literal can have more properties set than currently defined. Servers -receiving a ClientCapabilities object literal with unknown properties should -ignore these properties. A missing property should be interpreted as an absence -of the capability. If a property is missing that defines sub properties all sub -properties should be interpreted as an absence of the capability. - -Client capabilities got introduced with the version 3.0 of the protocol. They -therefore only describe capabilities that got introduced in 3.x or later. -Capabilities that existed in the 2.x version of the protocol are still mandatory -for clients. Clients cannot opt out of providing them. So even if a client omits -the ClientCapabilities.textDocument.synchronization it is still required that -the client provides text document synchronization (e.g. open, changed and close -notifications). - -interface ClientCapabilities { - /** - * Workspace specific client capabilities. - */ - workspace?: WorkspaceClientCapabilities; - - /** - * Text document specific client capabilities. - */ - textDocument?: TextDocumentClientCapabilities; - - /** - * Experimental client capabilities. - */ - experimental?: any; - - /** - * Window specific client capabilities. - */ - window?: WindowClientCapabilities; -} --} - data ClientCapabilities = ClientCapabilities { _workspace :: Maybe WorkspaceClientCapabilities @@ -1113,7 +176,7 @@ data ClientCapabilities = , _experimental :: Maybe A.Object } deriving (Show, Read, Eq) -$(deriveJSON lspOptions ''ClientCapabilities) +deriveJSON lspOptions ''ClientCapabilities instance Default ClientCapabilities where def = ClientCapabilities def def def def diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/CodeAction.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/CodeAction.hs index d4017e8f4..27c3739f1 100644 --- a/haskell-lsp-types/src/Language/Haskell/LSP/Types/CodeAction.hs +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/CodeAction.hs @@ -3,225 +3,67 @@ {-# LANGUAGE TemplateHaskell #-} module Language.Haskell.LSP.Types.CodeAction where -import Control.Applicative import Data.Aeson.TH import Data.Aeson.Types +import Data.Default import Data.Text ( Text ) import Language.Haskell.LSP.Types.Command -import Language.Haskell.LSP.Types.Constants import Language.Haskell.LSP.Types.Diagnostic -import Language.Haskell.LSP.Types.List +import Language.Haskell.LSP.Types.Common import Language.Haskell.LSP.Types.Location -import Language.Haskell.LSP.Types.Message import Language.Haskell.LSP.Types.Progress import Language.Haskell.LSP.Types.TextDocument +import Language.Haskell.LSP.Types.Utils import Language.Haskell.LSP.Types.WorkspaceEdit -{- -Code Action Request - -https://github.com/Microsoft/language-server-protocol/blob/master/protocol.md#code-action-request - -The code action request is sent from the client to the server to compute commands -for a given text document and range. These commands are typically code fixes to -either fix problems or to beautify/refactor code. The result of a -textDocument/codeAction request is an array of Command literals which are -typically presented in the user interface. When the command is selected the -server should be contacted again (via the workspace/executeCommand) request to -execute the command. - -Since version 3.8.0: support for CodeAction litarals to enable the following -scenarios: - -the ability to directly return a workspace edit from e code action request. This -avoids having another server roundtrip to execute an actual code action. However -server providers should be aware that if the code action is expensive to compute -or the edits are huge it might still be beneficial if the result is imply a -command and the actual edit is only computed when needed. the ability to group -code actions using a kind. Clients are allowed to ignore that information. -However it allows them to better group code action for example into -corresponding menus (e.g. all refactor code actions into a refactor menu). -Clients need to announce there support code action literals and code action -kinds via the corresponding client capability -textDocument.codeAction.codeActionLiteralSupport. - -Request - - method: 'textDocument/codeAction' - params: CodeActionParams defined as follows: - -/** - * Params for the CodeActionRequest - */ -interface CodeActionParams { - /** - * The document in which the command was invoked. - */ - textDocument: TextDocumentIdentifier; - - /** - * The range for which the command was invoked. - */ - range: Range; - - /** - * Context carrying additional information. - */ - context: CodeActionContext; -} - -/** - * The kind of a code action. - * - * Kinds are a hierarchical list of identifiers separated by `.`, e.g. `"refactor.extract.function"`. - * - * The set of kinds is open and client needs to announce the kinds it supports to the server during - * initialization. - */ -export type CodeActionKind = string; - -/** - * A set of predefined code action kinds - */ -export namespace CodeActionKind { - /** - * Base kind for quickfix actions: 'quickfix' - */ - export const QuickFix: CodeActionKind = 'quickfix'; - - /** - * Base kind for refactoring actions: 'refactor' - */ - export const Refactor: CodeActionKind = 'refactor'; - - /** - * Base kind for refactoring extraction actions: 'refactor.extract' - * - * Example extract actions: - * - * - Extract method - * - Extract function - * - Extract variable - * - Extract interface from class - * - ... - */ - export const RefactorExtract: CodeActionKind = 'refactor.extract'; - - /** - * Base kind for refactoring inline actions: 'refactor.inline' - * - * Example inline actions: - * - * - Inline function - * - Inline variable - * - Inline constant - * - ... - */ - export const RefactorInline: CodeActionKind = 'refactor.inline'; - - /** - * Base kind for refactoring rewrite actions: 'refactor.rewrite' - * - * Example rewrite actions: - * - * - Convert JavaScript function to class - * - Add or remove parameter - * - Encapsulate field - * - Make method static - * - Move method to base class - * - ... - */ - export const RefactorRewrite: CodeActionKind = 'refactor.rewrite'; - - /** - * Base kind for source actions: `source` - * - * Source code actions apply to the entire file. - */ - export const Source: CodeActionKind = 'source'; - - /** - * Base kind for an organize imports source action: `source.organizeImports` - */ - export const SourceOrganizeImports: CodeActionKind = 'source.organizeImports'; -} - -/** - * Contains additional diagnostic information about the context in which - * a code action is run. - */ -interface CodeActionContext { - /** - * An array of diagnostics. - */ - diagnostics: Diagnostic[]; - - /** - * Requested kind of actions to return. - * - * Actions not of this kind are filtered out by the client before being shown. So servers - * can omit computing them. - */ - only?: CodeActionKind[]; -} - -Response - - result: (Command | CodeAction)[] | null where CodeAction is defined as follows: - /** - * A code action represents a change that can be performed in code, e.g. to fix a problem or - * to refactor code. - * - * A CodeAction must set either `edit` and/or a `command`. If both are supplied, the `edit` is applied first, then the `command` is executed. - */ - export interface CodeAction { - - /** - * A short, human-readable, title for this code action. - */ - title: string; - - /** - * The kind of the code action. - * - * Used to filter code actions. - */ - kind?: CodeActionKind; - - /** - * The diagnostics that this code action resolves. - */ - diagnostics?: Diagnostic[]; - - /** - * The workspace edit this code action performs. - */ - edit?: WorkspaceEdit; - - /** - * A command this code action executes. If a code action - * provides an edit and a command, first the edit is - * executed and then the command. - */ - command?: Command; - } - error: code and message set in case an exception happens during the code - action request. - --} - -data CodeActionKind = CodeActionQuickFix - | CodeActionRefactor - | CodeActionRefactorExtract - | CodeActionRefactorInline - | CodeActionRefactorRewrite - | CodeActionSource - | CodeActionSourceOrganizeImports - | CodeActionUnknown Text - deriving (Read,Show,Eq) +data CodeActionKind + = -- | Empty kind. + CodeActionEmpty + | -- | Base kind for quickfix actions: @quickfix@. + CodeActionQuickFix + | -- | Base kind for refactoring actions: @refactor@. + CodeActionRefactor + | -- | Base kind for refactoring extraction actions: @refactor.extract@. + -- Example extract actions: + -- + -- - Extract method + -- - Extract function + -- - Extract variable + -- - Extract interface from class + -- - ... + CodeActionRefactorExtract + | -- | Base kind for refactoring inline actions: @refactor.inline@. + -- + -- Example inline actions: + -- + -- - Inline function + -- - Inline variable + -- - Inline constant + -- - ... + CodeActionRefactorInline + | -- | Base kind for refactoring rewrite actions: @refactor.rewrite@. + -- + -- Example rewrite actions: + -- + -- - Convert JavaScript function to class + -- - Add or remove parameter + -- - Encapsulate field + -- - Make method static + -- - Move method to base class + -- - ... + CodeActionRefactorRewrite + | -- | Base kind for source actions: @source@. + -- + -- Source code actions apply to the entire file. + CodeActionSource + | -- | Base kind for an organize imports source action: @source.organizeImports@. + CodeActionSourceOrganizeImports + | CodeActionUnknown Text + deriving (Read, Show, Eq) instance ToJSON CodeActionKind where + toJSON CodeActionEmpty = String "" toJSON CodeActionQuickFix = String "quickfix" toJSON CodeActionRefactor = String "refactor" toJSON CodeActionRefactorExtract = String "refactor.extract" @@ -232,6 +74,7 @@ instance ToJSON CodeActionKind where toJSON (CodeActionUnknown s) = String s instance FromJSON CodeActionKind where + parseJSON (String "") = pure CodeActionEmpty parseJSON (String "quickfix") = pure CodeActionQuickFix parseJSON (String "refactor") = pure CodeActionRefactor parseJSON (String "refactor.extract") = pure CodeActionRefactorExtract @@ -241,54 +84,122 @@ instance FromJSON CodeActionKind where parseJSON (String "source.organizeImports") = pure CodeActionSourceOrganizeImports parseJSON (String s) = pure (CodeActionUnknown s) parseJSON _ = mempty - -data CodeActionContext = - CodeActionContext - { _diagnostics :: List Diagnostic - , only :: Maybe (List CodeActionKind) - } deriving (Read,Show,Eq) + +-- ------------------------------------- + +data CodeActionKindClientCapabilities = + CodeActionKindClientCapabilities + { -- | The code action kind values the client supports. When this + -- property exists the client also guarantees that it will + -- handle values outside its set gracefully and falls back + -- to a default value when unknown. + _valueSet :: List CodeActionKind + } deriving (Show, Read, Eq) + +deriveJSON lspOptions ''CodeActionKindClientCapabilities + +instance Default CodeActionKindClientCapabilities where + def = CodeActionKindClientCapabilities (List allKinds) + where allKinds = [ CodeActionQuickFix + , CodeActionRefactor + , CodeActionRefactorExtract + , CodeActionRefactorInline + , CodeActionRefactorRewrite + , CodeActionSource + , CodeActionSourceOrganizeImports + ] + +data CodeActionLiteralSupport = + CodeActionLiteralSupport + { _codeActionKind :: CodeActionKindClientCapabilities -- ^ The code action kind is support with the following value set. + } deriving (Show, Read, Eq) + +deriveJSON lspOptions ''CodeActionLiteralSupport + +data CodeActionClientCapabilities = CodeActionClientCapabilities + { -- | Whether code action supports dynamic registration. + _dynamicRegistration :: Maybe Bool, + -- | The client support code action literals as a valid response + -- of the `textDocument/codeAction` request. + -- Since 3.8.0 + _codeActionLiteralSupport :: Maybe CodeActionLiteralSupport, + -- | Whether code action supports the `isPreferred` property. Since LSP 3.15.0 + _isPreferredSupport :: Maybe Bool + } + deriving (Show, Read, Eq) + +deriveJSON lspOptions ''CodeActionClientCapabilities + +-- ------------------------------------- + +makeExtendingDatatype "CodeActionOptions" [''WorkDoneProgressOptions] + [("_codeActionKinds", [t| Maybe (List CodeActionKind) |])] +deriveJSON lspOptions ''CodeActionOptions + +makeExtendingDatatype "CodeActionRegistrationOptions" + [ ''TextDocumentRegistrationOptions + , ''CodeActionOptions + ] [] +deriveJSON lspOptions ''CodeActionRegistrationOptions + +-- ------------------------------------- + +-- | Contains additional diagnostic information about the context in which a +-- code action is run. +data CodeActionContext = CodeActionContext + { -- | An array of diagnostics known on the client side overlapping the range provided to the + -- @textDocument/codeAction@ request. They are provided so that the server knows which + -- errors are currently presented to the user for the given range. There is no guarantee + -- that these accurately reflect the error state of the resource. The primary parameter + -- to compute code actions is the provided range. + _diagnostics :: List Diagnostic + -- | Requested kind of actions to return. + -- + -- Actions not of this kind are filtered out by the client before being shown. So servers + -- can omit computing them. + , _only :: Maybe (List CodeActionKind) + } + deriving (Read, Show, Eq) deriveJSON lspOptions ''CodeActionContext - -data CodeActionParams = - CodeActionParams - { _textDocument :: TextDocumentIdentifier - , _range :: Range - , _context :: CodeActionContext - , _workDoneToken :: Maybe ProgressToken -- ^ An optional token that a server can use to report work done progress. - } deriving (Read,Show,Eq) - +makeExtendingDatatype "CodeActionParams" + [ ''WorkDoneProgressParams + , ''PartialResultParams + ] + [ ("_textDocument", [t|TextDocumentIdentifier|]), + ("_range", [t|Range|]), + ("_context", [t|CodeActionContext|]) + ] deriveJSON lspOptions ''CodeActionParams +-- | A code action represents a change that can be performed in code, e.g. to fix a problem or +-- to refactor code. +-- +-- A CodeAction must set either '_edit' and/or a '_command'. If both are supplied, +-- the '_edit' is applied first, then the '_command' is executed. data CodeAction = - -- | A code action represents a change that can be performed in code, e.g. to fix a problem or - -- to refactor code. - -- - -- A CodeAction must set either '_edit' and/or a '_command'. If both are supplied, - -- the '_edit' is applied first, then the '_command' is executed. CodeAction - { _title :: Text -- ^ A short, human-readable, title for this code action. - , _kind :: Maybe CodeActionKind -- ^ The kind of the code action. Used to filter code actions. - , _diagnostics :: Maybe (List Diagnostic) -- ^ The diagnostics that this code action resolves. - , _edit :: Maybe WorkspaceEdit -- ^ The workspace edit this code action performs. - , _command :: Maybe Command -- ^ A command this code action executes. If a code action - -- provides an edit and a command, first the edit is - -- executed and then the command. - } deriving (Read,Show,Eq) - + { -- | A short, human-readable, title for this code action. + _title :: Text, + -- | The kind of the code action. Used to filter code actions. + _kind :: Maybe CodeActionKind, + -- | The diagnostics that this code action resolves. + _diagnostics :: Maybe (List Diagnostic), + -- | Marks this as a preferred action. Preferred actions are used by the `auto fix` command and can be targeted + -- by keybindings. + -- + -- A quick fix should be marked preferred if it properly addresses the underlying error. + -- A refactoring should be marked preferred if it is the most reasonable choice of actions to take. + -- + -- Since LSP 3.15.0 + _isPreferred :: Maybe Bool, + -- | The workspace edit this code action performs. + _edit :: Maybe WorkspaceEdit, + -- | A command this code action executes. If a code action + -- provides an edit and a command, first the edit is + -- executed and then the command. + _command :: Maybe Command + } + deriving (Read, Show, Eq) deriveJSON lspOptions ''CodeAction - -data CAResult = CACommand Command - | CACodeAction CodeAction - deriving (Read,Show,Eq) - -instance FromJSON CAResult where - parseJSON x = CACommand <$> parseJSON x <|> CACodeAction <$> parseJSON x - -instance ToJSON CAResult where - toJSON (CACommand x) = toJSON x - toJSON (CACodeAction x) = toJSON x - -type CodeActionRequest = RequestMessage ClientMethod CodeActionParams (List CAResult) -type CodeActionResponse = ResponseMessage (List CAResult) diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/CodeLens.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/CodeLens.hs new file mode 100644 index 000000000..02a66cd8f --- /dev/null +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/CodeLens.hs @@ -0,0 +1,64 @@ +{-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE DuplicateRecordFields #-} + +module Language.Haskell.LSP.Types.CodeLens where + +import Data.Aeson +import Data.Aeson.TH +import Language.Haskell.LSP.Types.Command +import Language.Haskell.LSP.Types.Location +import Language.Haskell.LSP.Types.Progress +import Language.Haskell.LSP.Types.TextDocument +import Language.Haskell.LSP.Types.Utils + +-- ------------------------------------- + +data CodeLensClientCapabilities = + CodeLensClientCapabilities + { -- | Whether code lens supports dynamic registration. + _dynamicRegistration :: Maybe Bool + } deriving (Show, Read, Eq) + +deriveJSON lspOptions ''CodeLensClientCapabilities + +-- ------------------------------------- + +makeExtendingDatatype "CodeLensOptions" [''WorkDoneProgressOptions] + [ ("_resolveProvider", [t| Maybe Bool |] )] +deriveJSON lspOptions ''CodeLensOptions + +makeExtendingDatatype "CodeLensRegistrationOptions" + [ ''TextDocumentRegistrationOptions + , ''CodeLensOptions + ] [] +deriveJSON lspOptions ''CodeLensRegistrationOptions + +-- ------------------------------------- + +makeExtendingDatatype "CodeLensParams" + [ ''WorkDoneProgressParams, + ''PartialResultParams + ] + [("_textDocument", [t|TextDocumentIdentifier|])] +deriveJSON lspOptions ''CodeLensParams + +-- ------------------------------------- + +-- | A code lens represents a command that should be shown along with source +-- text, like the number of references, a way to run tests, etc. +-- +-- A code lens is _unresolved_ when no command is associated to it. For +-- performance reasons the creation of a code lens and resolving should be done +-- in two stages. +data CodeLens = + CodeLens + { -- | The range in which this code lens is valid. Should only span a single line. + _range :: Range + , -- | The command this code lens represents. + _command :: Maybe Command + , -- | A data entry field that is preserved on a code lens item between + -- a code lens and a code lens resolve request. + _xdata :: Maybe Value + } deriving (Read,Show,Eq) + +deriveJSON lspOptions ''CodeLens diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/Color.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Color.hs deleted file mode 100644 index 42d641677..000000000 --- a/haskell-lsp-types/src/Language/Haskell/LSP/Types/Color.hs +++ /dev/null @@ -1,203 +0,0 @@ -{-# LANGUAGE DuplicateRecordFields #-} -{-# LANGUAGE TemplateHaskell #-} -module Language.Haskell.LSP.Types.Color where - -import Data.Aeson.TH -import Data.Text ( Text ) -import Language.Haskell.LSP.Types.Constants -import Language.Haskell.LSP.Types.List -import Language.Haskell.LSP.Types.Location -import Language.Haskell.LSP.Types.Message -import Language.Haskell.LSP.Types.Progress -import Language.Haskell.LSP.Types.TextDocument -import Language.Haskell.LSP.Types.WorkspaceEdit - -{- -Document Color Request (:leftwards_arrow_with_hook:) -Since version 3.6.0 - -The document color request is sent from the client to the server to list all -color references found in a given text document. Along with the range, a color -value in RGB is returned. - -Clients can use the result to decorate color references in an editor. For example: - -Color boxes showing the actual color next to the reference -Show a color picker when a color reference is edited -Request: - -method: ‘textDocument/documentColor’ -params: DocumentColorParams defined as follows -interface DocumentColorParams { - /** - * The text document. - */ - textDocument: TextDocumentIdentifier; -} -Response: - -result: ColorInformation[] defined as follows: -interface ColorInformation { - /** - * The range in the document where this color appears. - */ - range: Range; - - /** - * The actual color value for this color range. - */ - color: Color; -} - -/** - * Represents a color in RGBA space. - */ -interface Color { - - /** - * The red component of this color in the range [0-1]. - */ - readonly red: number; - - /** - * The green component of this color in the range [0-1]. - */ - readonly green: number; - - /** - * The blue component of this color in the range [0-1]. - */ - readonly blue: number; - - /** - * The alpha component of this color in the range [0-1]. - */ - readonly alpha: number; -} -error: code and message set in case an exception happens during the -‘textDocument/documentColor’ request --} - --- | Represents a color in RGBA space. -data Color = - Color - { _red :: Int -- ^ The red component of this color in the range [0-1]. - , _green :: Int -- ^ The green component of this color in the range [0-1]. - , _blue :: Int -- ^ The blue component of this color in the range [0-1]. - , _alpha :: Int -- ^ The alpha component of this color in the range [0-1]. - } deriving (Read, Show, Eq) - -deriveJSON lspOptions ''Color - -data ColorInformation = - ColorInformation - { _range :: Range -- ^ The range in the document where this color appears. - , _color :: Color -- ^ The actual color value for this color range. - } deriving (Read, Show, Eq) - -deriveJSON lspOptions ''ColorInformation - -data DocumentColorParams = - DocumentColorParams - { _textDocument :: TextDocumentIdentifier -- ^ The text document. - , _workDoneToken :: Maybe ProgressToken -- ^ An optional token that a server can use to report work done progress. - } deriving (Read, Show, Eq) - -deriveJSON lspOptions ''DocumentColorParams - -type DocumentColorRequest = - RequestMessage ClientMethod DocumentColorParams (List ColorInformation) -type DocumentColorResponse = ResponseMessage (List ColorInformation) - -{- -Color Presentation Request (:leftwards_arrow_with_hook:) -Since version 3.6.0 - -The color presentation request is sent from the client to the server to obtain a list of -presentations for a color value at a given location. Clients can use the result to - -modify a color reference. -show in a color picker and let users pick one of the presentations -Request: - -method: ‘textDocument/colorPresentation’ -params: DocumentColorParams defined as follows -interface ColorPresentationParams { - /** - * The text document. - */ - textDocument: TextDocumentIdentifier; - - /** - * The color information to request presentations for. - */ - color: Color; - - /** - * The range where the color would be inserted. Serves as a context. - */ - range: Range; -} -Response: - -result: ColorPresentation[] defined as follows: -interface ColorPresentation { - /** - * The label of this color presentation. It will be shown - * on the color picker header. By default this is also the - * text that is inserted when selecting - * this color presentation. - */ - label: string; - /** - * An [edit](#TextEdit) which is applied to a document when selecting - * this presentation for the color. - * When `falsy` the [label](#ColorPresentation.label) is used. - */ - textEdit?: TextEdit; - /** - * An optional array of additional [text edits](#TextEdit) that are applied when - * selecting this color presentation. Edits must not overlap with the main - * [edit](#ColorPresentation.textEdit) nor with themselves. - */ - additionalTextEdits?: TextEdit[]; -} -error: code and message set in case an exception happens during the -‘textDocument/colorPresentation’ request --} - -data ColorPresentationParams = - ColorPresentationParams - { -- | The text document. - _textDocument :: TextDocumentIdentifier - -- | The color information to request presentations for. - , _color :: Color - -- | The range where the color would be inserted. - -- Serves as a context. - , _range :: Range - , _workDoneToken :: Maybe ProgressToken -- ^ An optional token that a server can use to report work done progress. - } deriving (Read, Show, Eq) - -deriveJSON lspOptions ''ColorPresentationParams - -data ColorPresentation = - ColorPresentation - { -- | The label of this color presentation. It will be shown on the color - -- picker header. By default this is also the text that is inserted when selecting - -- this color presentation. - _label :: Text - -- | A 'TextEdit' which is applied to a document when selecting - -- this presentation for the color. When `falsy` the '_label' - -- is used. - , _textEdit :: Maybe TextEdit - -- | An optional array of additional 'TextEdit's that are applied when - -- selecting this color presentation. Edits must not overlap with the main - -- '_textEdit' nor with themselves. - , _additionalTextEdits :: Maybe (List TextEdit) - } deriving (Read, Show, Eq) - -deriveJSON lspOptions ''ColorPresentation - -type ColorPresentationRequest = - RequestMessage ClientMethod ColorPresentationParams (List ColorPresentation) -type ColorPresentationResponse = ResponseMessage (List ColorPresentation) diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/Command.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Command.hs index e06d8b0ea..396079784 100644 --- a/haskell-lsp-types/src/Language/Haskell/LSP/Types/Command.hs +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Command.hs @@ -1,45 +1,51 @@ {-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE DuplicateRecordFields #-} module Language.Haskell.LSP.Types.Command where import Data.Aeson import Data.Aeson.TH import Data.Text -import Language.Haskell.LSP.Types.Constants -import Language.Haskell.LSP.Types.List --- --------------------------------------------------------------------- -{- -Command - -https://github.com/Microsoft/language-server-protocol/blob/master/protocol.md#command - -Represents a reference to a command. Provides a title which will be used to -represent a command in the UI. Commands are identitifed using a string -identifier and the protocol currently doesn't specify a set of well known -commands. So executing a command requires some tool extension code. - -interface Command { - /** - * Title of the command, like `save`. - */ - title: string; - /** - * The identifier of the actual command handler. - */ - command: string; - /** - * Arguments that the command handler should be - * invoked with. - */ - arguments?: any[]; -} --} +import Language.Haskell.LSP.Types.Common +import Language.Haskell.LSP.Types.Progress +import Language.Haskell.LSP.Types.Utils + +-- ------------------------------------- + +data ExecuteCommandClientCapabilities = + ExecuteCommandClientCapabilities + { _dynamicRegistration :: Maybe Bool -- ^Execute command supports dynamic + -- registration. + } deriving (Show, Read, Eq) + +deriveJSON lspOptions ''ExecuteCommandClientCapabilities + +-- ------------------------------------- + +makeExtendingDatatype "ExecuteCommandOptions" [''WorkDoneProgressOptions] + [("_commands", [t| List Text |])] +deriveJSON lspOptions ''ExecuteCommandOptions + +makeExtendingDatatype "ExecuteCommandRegistrationOptions" [''ExecuteCommandOptions] [] +deriveJSON lspOptions ''ExecuteCommandRegistrationOptions + +-- ------------------------------------- + +makeExtendingDatatype "ExecuteCommandParams" [''WorkDoneProgressParams] + [ ("_command", [t| Text |]) + , ("_arguments", [t| Maybe (List Value) |]) + ] +deriveJSON lspOptions ''ExecuteCommandParams data Command = Command - { _title :: Text - , _command :: Text - , _arguments :: Maybe (List Value) + { -- | Title of the command, like @save@. + _title :: Text + , -- | The identifier of the actual command handler. + _command :: Text + , -- | Arguments that the command handler should be invoked with. + _arguments :: Maybe (List Value) } deriving (Show, Read, Eq) deriveJSON lspOptions ''Command + diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/Common.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Common.hs new file mode 100644 index 000000000..ef08acd09 --- /dev/null +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Common.hs @@ -0,0 +1,57 @@ +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE DeriveTraversable #-} +{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE TypeOperators #-} + +-- | Common types that aren't in the specification +module Language.Haskell.LSP.Types.Common where + +import Control.Applicative +import Control.DeepSeq +import Data.Aeson +import GHC.Generics + +-- | A terser, isomorphic data type for 'Either', that does not get tagged when +-- converting to and from JSON. +data a |? b = InL a + | InR b + deriving (Read,Show,Eq,Ord,Generic) +infixr |? + +toEither :: a |? b -> Either a b +toEither (InL a) = Left a +toEither (InR b) = Right b + +instance (ToJSON a, ToJSON b) => ToJSON (a |? b) where + toJSON (InL x) = toJSON x + toJSON (InR x) = toJSON x + +instance (FromJSON a, FromJSON b) => FromJSON (a |? b) where + -- Important: Try to parse the **rightmost** type first, as in the specification + -- the more complex types tend to appear on the right of the |, i.e. + -- @colorProvider?: boolean | DocumentColorOptions | DocumentColorRegistrationOptions;@ + parseJSON v = InR <$> parseJSON v <|> InL <$> parseJSON v + +instance (NFData a, NFData b) => NFData (a |? b) + +-- | All LSP types representing a list **must** use this type rather than '[]'. +-- In particular this is necessary to change the 'FromJSON' instance to be compatible +-- with Elisp (where empty lists show up as 'null') +newtype List a = List [a] + deriving (Show,Read,Eq,Ord,Semigroup,Monoid,Functor,Foldable,Traversable,Generic) + +instance NFData a => NFData (List a) + +instance (ToJSON a) => ToJSON (List a) where + toJSON (List ls) = toJSON ls + +instance (FromJSON a) => FromJSON (List a) where + parseJSON Null = return (List []) + parseJSON v = List <$> parseJSON v + +data Empty = Empty deriving (Eq,Ord,Show) +instance ToJSON Empty where + toJSON Empty = Null +instance FromJSON Empty where + parseJSON Null = pure Empty + parseJSON _ = mempty diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/Completion.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Completion.hs index a7259a019..091588661 100644 --- a/haskell-lsp-types/src/Language/Haskell/LSP/Types/Completion.hs +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Completion.hs @@ -9,12 +9,8 @@ import Data.Aeson.TH import Data.Scientific ( Scientific ) import Data.Text ( Text ) import Language.Haskell.LSP.Types.Command -import Language.Haskell.LSP.Types.Constants -import Language.Haskell.LSP.Types.DocumentFilter -import Language.Haskell.LSP.Types.List -import Language.Haskell.LSP.Types.Location +import Language.Haskell.LSP.Types.Common import Language.Haskell.LSP.Types.MarkupContent -import Language.Haskell.LSP.Types.Message import Language.Haskell.LSP.Types.Progress import Language.Haskell.LSP.Types.TextDocument import Language.Haskell.LSP.Types.Utils @@ -114,191 +110,68 @@ instance A.FromJSON CompletionItemTag where parseJSON (A.Number 1) = pure CtDeprecated parseJSON _ = mempty --- --------------------------------------------------------------------- -{- -Completion Request +data CompletionItemTagsClientCapabilities = + CompletionItemTagsClientCapabilities + { -- | The tag supported by the client. + _valueSet :: List CompletionItemTag + } deriving (Show, Read, Eq) -The Completion request is sent from the client to the server to compute -completion items at a given cursor position. Completion items are presented in -the IntelliSense user interface. If computing full completion items is -expensive, servers can additionally provide a handler for the completion item -resolve request ('completionItem/resolve'). This request is sent when a -completion item is selected in the user interface. A typically use case is for -example: the 'textDocument/completion' request doesn't fill in the documentation -property for returned completion items since it is expensive to compute. When -the item is selected in the user interface then a 'completionItem/resolve' -request is sent with the selected completion item as a param. The returned -completion item should have the documentation property filled in. +deriveJSON lspOptions ''CompletionItemTagsClientCapabilities - Changed: In 2.0 the request uses TextDocumentPositionParams with a proper - textDocument and position property. In 1.0 the uri of the referenced text - document was inlined into the params object. +data CompletionItemClientCapabilities = + CompletionItemClientCapabilities + { -- | Client supports snippets as insert text. + -- + -- A snippet can define tab stops and placeholders with `$1`, `$2` and + -- `${3:foo}`. `$0` defines the final tab stop, it defaults to the end of + -- the snippet. Placeholders with equal identifiers are linked, that is + -- typing in one will update others too. + _snippetSupport :: Maybe Bool + + -- | Client supports commit characters on a completion item. + , _commitCharactersSupport :: Maybe Bool + + -- | Client supports the follow content formats for the documentation + -- property. The order describes the preferred format of the client. + , _documentationFormat :: Maybe (List MarkupKind) + + -- | Client supports the deprecated property on a completion item. + , _deprecatedSupport :: Maybe Bool + + -- | Client supports the preselect property on a completion item. + , _preselectSupport :: Maybe Bool + + -- | Client supports the tag property on a completion item. Clients + -- supporting tags have to handle unknown tags gracefully. Clients + -- especially need to preserve unknown tags when sending a + -- completion item back to the server in a resolve call. + , _tagSupport :: Maybe CompletionItemTagsClientCapabilities + } deriving (Show, Read, Eq) -Request +deriveJSON lspOptions ''CompletionItemClientCapabilities - method: 'textDocument/completion' - params: TextDocumentPositionParams --} +data CompletionItemKindClientCapabilities = + CompletionItemKindClientCapabilities + { -- | The completion item kind values the client supports. When this + -- property exists the client also guarantees that it will + -- handle values outside its set gracefully and falls back + -- to a default value when unknown. + _valueSet :: Maybe (List CompletionItemKind) + } + deriving (Show, Read, Eq) --- ------------------------------------- +deriveJSON lspOptions ''CompletionItemKindClientCapabilities + +data CompletionClientCapabilities = + CompletionClientCapabilities + { _dynamicRegistration :: Maybe Bool -- ^ Whether completion supports dynamic + -- registration. + , _completionItem :: Maybe CompletionItemClientCapabilities + , _completionItemKind :: Maybe CompletionItemKindClientCapabilities + , _contextSupport :: Maybe Bool + } deriving (Show, Read, Eq) -{- - -Response - - result: CompletionItem[] | CompletionList - -/** - * Represents a collection of [completion items](#CompletionItem) to be presented - * in the editor. - */ -interface CompletionList { - /** - * This list it not complete. Further typing should result in recomputing - * this list. - */ - isIncomplete: boolean; - /** - * The completion items. - */ - items: CompletionItem[]; -} - - -New in 3.0 : InsertTextFormat - -/** - * Defines whether the insert text in a completion item should be interpreted as - * plain text or a snippet. - */ -namespace InsertTextFormat { - /** - * The primary text to be inserted is treated as a plain string. - */ - export const PlainText = 1; - - /** - * The primary text to be inserted is treated as a snippet. - * - * A snippet can define tab stops and placeholders with `$1`, `$2` - * and `${3:foo}`. `$0` defines the final tab stop, it defaults to - * the end of the snippet. Placeholders with equal identifiers are linked, - * that is typing in one will update others too. - * - * See also: https://github.com/Microsoft/vscode/blob/master/src/vs/editor/contrib/snippet/common/snippet.md - */ - export const Snippet = 2; -} - - - -interface CompletionItem { - /** - * The label of this completion item. By default - * also the text that is inserted when selecting - * this completion. - */ - label: string; - /** - * The kind of this completion item. Based of the kind - * an icon is chosen by the editor. - */ - kind?: number; - /** - * Tags for this completion item. - */ - tags?: CompletionItemTag[]; - /** - * A human-readable string with additional information - * about this item, like type or symbol information. - */ - detail?: string; - /** - * A human-readable string that represents a doc-comment. - */ - documentation?: string; - /** - * A string that shoud be used when comparing this item - * with other items. When `falsy` the label is used. - */ - sortText?: string; - /** - * A string that should be used when filtering a set of - * completion items. When `falsy` the label is used. - */ - filterText?: string; - /** - * A string that should be inserted a document when selecting - * this completion. When `falsy` the label is used. - */ - insertText?: string; - -- Following field is new in 3.0 - /** - * The format of the insert text. The format applies to both the `insertText` property - * and the `newText` property of a provided `textEdit`. - */ - insertTextFormat?: InsertTextFormat; - /** - * An edit which is applied to a document when selecting this completion. When an edit is provided the value of - * `insertText` is ignored. - * - * *Note:* The range of the edit must be a single line range and it must contain the position at which completion - * has been requested. - */ - - textEdit?: TextEdit; - - -- Following field is new in 3.0 - /** - * An optional array of additional text edits that are applied when - * selecting this completion. Edits must not overlap with the main edit - * nor with themselves. - */ - additionalTextEdits?: TextEdit[]; - -- Following field is new in 3.0 - /** - * An optional command that is executed *after* inserting this completion. *Note* that - * additional modifications to the current document should be described with the - * additionalTextEdits-property. - */ - - command?: Command; - /** - * An data entry field that is preserved on a completion item between - * a completion and a completion resolve request. - */ - - data?: any -} - -Where CompletionItemKind is defined as follows: - -/** - * The kind of a completion entry. - */ -enum CompletionItemKind { - Text = 1, - Method = 2, - Function = 3, - Constructor = 4, - Field = 5, - Variable = 6, - Class = 7, - Interface = 8, - Module = 9, - Property = 10, - Unit = 11, - Value = 12, - Enum = 13, - Keyword = 14, - Snippet = 15, - Color = 16, - File = 17, - Reference = 18 -} - - error: code and message set in case an exception happens during the completion request. --} +deriveJSON lspOptions ''CompletionClientCapabilities -- ------------------------------------- @@ -391,22 +264,17 @@ data CompletionItem = -- completion resolve request. } deriving (Read,Show,Eq) -deriveJSON lspOptions{ fieldLabelModifier = customModifier } ''CompletionItem +deriveJSON lspOptions ''CompletionItem -data CompletionListType = - CompletionListType - { _isIncomplete :: Bool - , _items :: List CompletionItem +-- | Represents a collection of 'CompletionItem's to be presented in the editor. +data CompletionList = + CompletionList + { _isIncomplete :: Bool -- ^ This list it not complete. Further typing + -- should result in recomputing this list. + , _items :: List CompletionItem -- ^ The completion items. } deriving (Read,Show,Eq) -deriveJSON lspOptions ''CompletionListType - -data CompletionResponseResult - = CompletionList CompletionListType - | Completions (List CompletionItem) - deriving (Read,Show,Eq) - -deriveJSON defaultOptions { fieldLabelModifier = rdrop (length ("CompletionResponseResult"::String)), sumEncoding = UntaggedValue } ''CompletionResponseResult +deriveJSON lspOptions ''CompletionList -- | How a completion was triggered data CompletionTriggerKind = -- | Completion was triggered by typing an identifier (24x7 code @@ -434,6 +302,20 @@ instance A.FromJSON CompletionTriggerKind where parseJSON (A.Number x) = pure (CtUnknown x) parseJSON _ = mempty +makeExtendingDatatype "CompletionOptions" [''WorkDoneProgressOptions] + [ ("_triggerCharacters", [t| Maybe [String] |]) + , ("_allCommitCharacters", [t| Maybe [String] |]) + , ("_resolveProvider", [t| Maybe Bool|]) + ] +deriveJSON lspOptions ''CompletionOptions + +makeExtendingDatatype "CompletionRegistrationOptions" + [ ''TextDocumentRegistrationOptions + , ''CompletionOptions + ] + [] +deriveJSON lspOptions ''CompletionRegistrationOptions + data CompletionContext = CompletionContext { _triggerKind :: CompletionTriggerKind -- ^ How the completion was triggered. @@ -445,70 +327,11 @@ data CompletionContext = deriveJSON lspOptions ''CompletionContext -data CompletionParams = - CompletionParams - { _textDocument :: TextDocumentIdentifier -- ^ The text document. - , _position :: Position -- ^ The position inside the text document. - , _context :: Maybe CompletionContext - -- ^ The completion context. This is only available if the client specifies - -- to send this using `ClientCapabilities.textDocument.completion.contextSupport === true` - , _workDoneToken :: Maybe ProgressToken -- ^ An optional token that a server can use to report work done progress. - } - deriving (Read, Show, Eq) - +makeExtendingDatatype "CompletionParams" + [ ''TextDocumentPositionParams + , ''WorkDoneProgressParams + , ''PartialResultParams + ] + [ ("_context", [t| Maybe CompletionContext |]) ] deriveJSON lspOptions ''CompletionParams -type CompletionResponse = ResponseMessage CompletionResponseResult -type CompletionRequest = RequestMessage ClientMethod CompletionParams CompletionResponseResult - --- ------------------------------------- -{- -New in 3.0 ------------ -Registration Options: CompletionRegistrationOptions options defined as follows: - -export interface CompletionRegistrationOptions extends TextDocumentRegistrationOptions { - /** - * The characters that trigger completion automatically. - */ - triggerCharacters?: string[]; - - /** - * The server provides support to resolve additional - * information for a completion item. - */ - resolveProvider?: boolean; -} --} - -data CompletionRegistrationOptions = - CompletionRegistrationOptions - { _documentSelector :: Maybe DocumentSelector - , _triggerCharacters :: Maybe (List String) - , _resolveProvider :: Maybe Bool - } deriving (Show, Read, Eq) - -deriveJSON lspOptions ''CompletionRegistrationOptions - --- --------------------------------------------------------------------- -{- -Completion Item Resolve Request - -https://github.com/Microsoft/language-server-protocol/blob/master/protocol.md#completion-item-resolve-request - -The request is sent from the client to the server to resolve additional -information for a given completion item. - -Request - - method: 'completionItem/resolve' - params: CompletionItem - -Response - - result: CompletionItem - error: code and message set in case an exception happens during the completion resolve request. --} - -type CompletionItemResolveRequest = RequestMessage ClientMethod CompletionItem CompletionItem -type CompletionItemResolveResponse = ResponseMessage CompletionItem diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/Configuration.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Configuration.hs new file mode 100644 index 000000000..29db71f51 --- /dev/null +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Configuration.hs @@ -0,0 +1,42 @@ +{-# LANGUAGE TemplateHaskell #-} +module Language.Haskell.LSP.Types.Configuration where + +import Data.Aeson +import Data.Aeson.TH +import Data.Text (Text) +import Language.Haskell.LSP.Types.Common +import Language.Haskell.LSP.Types.Utils + +-- ------------------------------------- + +data DidChangeConfigurationClientCapabilities = + DidChangeConfigurationClientCapabilities + { _dynamicRegistration :: Maybe Bool -- ^Did change configuration + -- notification supports dynamic + -- registration. + } deriving (Show, Read, Eq) + +deriveJSON lspOptions ''DidChangeConfigurationClientCapabilities + +data DidChangeConfigurationParams = + DidChangeConfigurationParams + { _settings :: Value -- ^ The actual changed settings + } deriving (Show, Read, Eq) + +deriveJSON lspOptions ''DidChangeConfigurationParams + +-- --------------------------------------------------------------------- + +data ConfigurationItem = + ConfigurationItem + { _scopeUri :: Maybe Text -- ^ The scope to get the configuration section for. + , _section :: Maybe Text -- ^ The configuration section asked for. + } deriving (Show, Read, Eq) + +deriveJSON lspOptions ''ConfigurationItem + +data ConfigurationParams = + ConfigurationParams + { _items :: List ConfigurationItem + } deriving (Show, Read, Eq) +deriveJSON lspOptions ''ConfigurationParams diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/Constants.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Constants.hs deleted file mode 100644 index bd985c175..000000000 --- a/haskell-lsp-types/src/Language/Haskell/LSP/Types/Constants.hs +++ /dev/null @@ -1,17 +0,0 @@ - -module Language.Haskell.LSP.Types.Constants where - -import Data.Aeson.TH - --- --------------------------------------------------------------------- - --- | Standard options for use when generating JSON instances -lspOptions :: Options -lspOptions = defaultOptions { omitNothingFields = True, fieldLabelModifier = drop 1 } - -- NOTE: This needs to be in a separate file because of the TH stage restriction - -customModifier :: String -> String -customModifier "_xdata" = "data" -customModifier "_xtype" = "type" -customModifier xs = drop 1 xs - diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/DataTypesJSON.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/DataTypesJSON.hs deleted file mode 100644 index a18bc82c7..000000000 --- a/haskell-lsp-types/src/Language/Haskell/LSP/Types/DataTypesJSON.hs +++ /dev/null @@ -1,2830 +0,0 @@ -{-# LANGUAGE DeriveGeneric #-} -{-# LANGUAGE DeriveTraversable #-} -{-# LANGUAGE DuplicateRecordFields #-} -{-# LANGUAGE FlexibleInstances #-} -{-# LANGUAGE FunctionalDependencies #-} -{-# LANGUAGE GeneralizedNewtypeDeriving #-} -{-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE TemplateHaskell #-} -{-# LANGUAGE TypeSynonymInstances #-} -{-# LANGUAGE ScopedTypeVariables #-} - -module Language.Haskell.LSP.Types.DataTypesJSON where - -import Control.Applicative -import qualified Data.Aeson as A -import Data.Aeson.TH -import Data.Aeson.Types -import Data.Bits (testBit) -import Data.Scientific (floatingOrInteger) -import Data.Text (Text) -import qualified Data.Text as T -import Language.Haskell.LSP.Types.ClientCapabilities -import Language.Haskell.LSP.Types.CodeAction -import Language.Haskell.LSP.Types.Command -import Language.Haskell.LSP.Types.Constants -import Language.Haskell.LSP.Types.Diagnostic -import Language.Haskell.LSP.Types.DocumentFilter -import Language.Haskell.LSP.Types.List -import Language.Haskell.LSP.Types.Location -import Language.Haskell.LSP.Types.Message -import Language.Haskell.LSP.Types.Progress -import Language.Haskell.LSP.Types.Symbol -import Language.Haskell.LSP.Types.TextDocument -import Language.Haskell.LSP.Types.Uri -import Language.Haskell.LSP.Types.WorkspaceEdit -import Language.Haskell.LSP.Types.WorkspaceFolders - --- ===================================================================== --- ACTUAL PROTOCOL ----------------------------------------------------- --- ===================================================================== - --- --------------------------------------------------------------------- --- Initialize Request --- --------------------------------------------------------------------- -{- -Initialize Request - -https://github.com/Microsoft/language-server-protocol/blob/master/protocol.md#initialize-request - -The initialize request is sent as the first request from the client to the server. - -Request - - method: 'initialize' - params: InitializeParams defined as follows: - -interface InitializeParams { - /** - * The process Id of the parent process that started - * the server. Is null if the process has not been started by another process. - * If the parent process is not alive then the server should exit (see exit notification) its process. - */ - processId: number | null; - - /** - * The rootPath of the workspace. Is null - * if no folder is open. - * - * @deprecated in favour of rootUri. - */ - rootPath?: string | null; - - /** - * The rootUri of the workspace. Is null if no - * folder is open. If both `rootPath` and `rootUri` are set - * `rootUri` wins. - */ - rootUri: DocumentUri | null; - - /** - * User provided initialization options. - */ - initializationOptions?: any; - - /** - * The capabilities provided by the client (editor or tool) - */ - capabilities: ClientCapabilities; - - /** - * The initial trace setting. If omitted trace is disabled ('off'). - */ - trace?: 'off' | 'messages' | 'verbose'; -} --} - -data Trace = TraceOff | TraceMessages | TraceVerbose - deriving (Show, Read, Eq) - -instance A.ToJSON Trace where - toJSON TraceOff = A.String (T.pack "off") - toJSON TraceMessages = A.String (T.pack "messages") - toJSON TraceVerbose = A.String (T.pack "verbose") - -instance A.FromJSON Trace where - parseJSON (A.String s) = case T.unpack s of - "off" -> return TraceOff - "messages" -> return TraceMessages - "verbose" -> return TraceVerbose - _ -> mempty - parseJSON _ = mempty - -data InitializeParams = - InitializeParams { - _processId :: Maybe Int - , _rootPath :: Maybe Text -- ^ Deprecated in favour of _rootUri - , _rootUri :: Maybe Uri - , _initializationOptions :: Maybe A.Value - , _capabilities :: ClientCapabilities - , _trace :: Maybe Trace - -- | The workspace folders configured in the client when the server starts. - -- This property is only available if the client supports workspace folders. - -- It can be `null` if the client supports workspace folders but none are - -- configured. - -- Since LSP 3.6 - -- - -- @since 0.7.0.0 - , _workspaceFolders :: Maybe (List WorkspaceFolder) - } deriving (Show, Read, Eq) - -{-# DEPRECATED _rootPath "Use _rootUri" #-} - -deriveJSON lspOptions ''InitializeParams - --- --------------------------------------------------------------------- --- Initialize Response --- --------------------------------------------------------------------- -{- - - error.data: - -interface InitializeError { - /** - * Indicates whether the client should retry to send the - * initilize request after showing the message provided - * in the ResponseError. - */ - retry: boolean; -- --} -data InitializeError = - InitializeError - { _retry :: Bool - } deriving (Read, Show, Eq) - -deriveJSON lspOptions ''InitializeError - --- --------------------------------------------------------------------- -{- -The server can signal the following capabilities: - -/** - * Defines how the host (editor) should sync document changes to the language server. - */ -enum TextDocumentSyncKind { - /** - * Documents should not be synced at all. - */ - None = 0, - /** - * Documents are synced by always sending the full content of the document. - */ - Full = 1, - /** - * Documents are synced by sending the full content on open. After that only incremental - * updates to the document are sent. - */ - Incremental = 2 -} --} - --- ^ Note: Omitting this parameter from the capabilities is effectively a fourth --- state, where DidSave events are generated without sending document contents. -data TextDocumentSyncKind = TdSyncNone - | TdSyncFull - | TdSyncIncremental - deriving (Read,Eq,Show) - -instance A.ToJSON TextDocumentSyncKind where - toJSON TdSyncNone = A.Number 0 - toJSON TdSyncFull = A.Number 1 - toJSON TdSyncIncremental = A.Number 2 - -instance A.FromJSON TextDocumentSyncKind where - parseJSON (A.Number 0) = pure TdSyncNone - parseJSON (A.Number 1) = pure TdSyncFull - parseJSON (A.Number 2) = pure TdSyncIncremental - parseJSON _ = mempty - --- --------------------------------------------------------------------- -{- -/** - * Completion options. - */ -interface CompletionOptions { - /** - * The server provides support to resolve additional information for a completion item. - */ - resolveProvider?: boolean; - - /** - * The characters that trigger completion automatically. - */ - triggerCharacters?: string[]; - - /** - * The list of all possible characters that commit a completion. This field can be used - * if clients don't support individual commmit characters per completion item. See - * `ClientCapabilities.textDocument.completion.completionItem.commitCharactersSupport`. - * - * If a server provides both `allCommitCharacters` and commit characters on an individual - * completion item the once on the completion item win. - * - * @since 3.2.0 - */ - allCommitCharacters?: string[]; -} --} - -data CompletionOptions = - CompletionOptions - { _resolveProvider :: Maybe Bool - -- | The characters that trigger completion automatically. - , _triggerCharacters :: Maybe [String] - -- | The list of all possible characters that commit a completion. This field can be used - -- if clients don't support individual commmit characters per completion item. See - -- `_commitCharactersSupport`. - -- Since LSP 3.2.0 - -- @since 0.18.0.0 - , _allCommitCharacters :: Maybe [String] - } deriving (Read,Show,Eq) - -deriveJSON lspOptions {omitNothingFields = True } ''CompletionOptions - --- --------------------------------------------------------------------- -{- -/** - * Signature help options. - */ -interface SignatureHelpOptions { - /** - * The characters that trigger signature help automatically. - */ - triggerCharacters?: string[]; - /** - * List of characters that re-trigger signature help. - * - * These trigger characters are only active when signature help is already showing. All trigger characters - * are also counted as re-trigger characters. - * - * @since 3.15.0 - */ --} - -data SignatureHelpOptions = - SignatureHelpOptions - { -- | The characters that trigger signature help automatically. - _triggerCharacters :: Maybe [String] - - -- | List of characters that re-trigger signature help. - -- These trigger characters are only active when signature help is already showing. All trigger characters - -- are also counted as re-trigger characters. - -- - -- Since LSP 3.15.0 - -- @since 0.18.0.0 - , _retriggerCharacters :: Maybe [String] - } deriving (Read,Show,Eq) - -deriveJSON lspOptions ''SignatureHelpOptions - --- --------------------------------------------------------------------- -{- -/** - * Code Lens options. - */ -interface CodeLensOptions { - /** - * Code lens has a resolve provider as well. - */ - resolveProvider?: boolean; -} --} - -data CodeLensOptions = - CodeLensOptions - { _resolveProvider :: Maybe Bool - } deriving (Read,Show,Eq) - -deriveJSON lspOptions ''CodeLensOptions - --- --------------------------------------------------------------------- -{- -/** - * Code Action options. - */ -export interface CodeActionOptions { - /** - * CodeActionKinds that this server may return. - * - * The list of kinds may be generic, such as `CodeActionKind.Refactor`, or the server - * may list out every specific kind they provide. - */ - codeActionKinds?: CodeActionKind[]; -} --} - -data CodeActionOptions = - CodeActionOptionsStatic Bool - | CodeActionOptions - { _codeActionKinds :: Maybe [CodeActionKind] - } deriving (Read,Show,Eq) - -deriveJSON (lspOptions { sumEncoding = A.UntaggedValue }) ''CodeActionOptions - --- --------------------------------------------------------------------- -{- -/** - * Format document on type options - */ -interface DocumentOnTypeFormattingOptions { - /** - * A character on which formatting should be triggered, like `}`. - */ - firstTriggerCharacter: string; - /** - * More trigger characters. - */ - moreTriggerCharacter?: string[] -} --} -data DocumentOnTypeFormattingOptions = - DocumentOnTypeFormattingOptions - { _firstTriggerCharacter :: Text - , _moreTriggerCharacter :: Maybe [Text] - } deriving (Read,Show,Eq) - -deriveJSON lspOptions ''DocumentOnTypeFormattingOptions - --- --------------------------------------------------------------------- -{- -New in 3.0 ----------- - -/** - * Document link options - */ -export interface DocumentLinkOptions { - /** - * Document links have a resolve provider as well. - */ - resolveProvider?: boolean; -} --} - -data DocumentLinkOptions = - DocumentLinkOptions - { -- | Document links have a resolve provider as well. - _resolveProvider :: Maybe Bool - } deriving (Show, Read, Eq) - -deriveJSON lspOptions ''DocumentLinkOptions - --- --------------------------------------------------------------------- -{- -New in 3.12 ----------- - -/** - * Rename options - */ -export interface RenameOptions { - /** - * Renames should be checked and tested before being executed. - */ - prepareProvider?: boolean; -} --} - -data RenameOptions = - RenameOptionsStatic Bool - | RenameOptions - { -- | Renames should be checked and tested before being executed. - _prepareProvider :: Maybe Bool - } deriving (Show, Read, Eq) - -deriveJSON lspOptions { sumEncoding = A.UntaggedValue } ''RenameOptions - --- --------------------------------------------------------------------- - -{- -New in 3.0 ------------ - -/** - * Execute command options. - */ -export interface ExecuteCommandOptions { - /** - * The commands to be executed on the server - */ - commands: string[] -} --} - -data ExecuteCommandOptions = - ExecuteCommandOptions - { -- | The commands to be executed on the server - _commands :: List Text - } deriving (Show, Read, Eq) - -deriveJSON lspOptions ''ExecuteCommandOptions - --- --------------------------------------------------------------------- -{- -New in 3.0 ----------- -/** - * Save options. - */ -export interface SaveOptions { - /** - * The client is supposed to include the content on save. - */ - includeText?: boolean; -} --} -data SaveOptions = - SaveOptions - { -- |The client is supposed to include the content on save. - _includeText :: Maybe Bool - } deriving (Show, Read, Eq) - -deriveJSON lspOptions ''SaveOptions - --- --------------------------------------------------------------------- -{- -New in 3.0 ----------- - -export interface TextDocumentSyncOptions { - /** - * Open and close notifications are sent to the server. - */ - openClose?: boolean; - /** - * Change notificatins are sent to the server. See TextDocumentSyncKind.None, TextDocumentSyncKind.Full - * and TextDocumentSyncKindIncremental. - */ - change?: number; - /** - * Will save notifications are sent to the server. - */ - willSave?: boolean; - /** - * Will save wait until requests are sent to the server. - */ - willSaveWaitUntil?: boolean; - /** - * Save notifications are sent to the server. - */ - save?: SaveOptions; -} --} - -data TextDocumentSyncOptions = - TextDocumentSyncOptions - { -- | Open and close notifications are sent to the server. - _openClose :: Maybe Bool - - -- | Change notificatins are sent to the server. See - -- TextDocumentSyncKind.None, TextDocumentSyncKind.Full and - -- TextDocumentSyncKindIncremental. - , _change :: Maybe TextDocumentSyncKind - - -- | Will save notifications are sent to the server. - , _willSave :: Maybe Bool - - -- | Will save wait until requests are sent to the server. - , _willSaveWaitUntil :: Maybe Bool - - -- | Save notifications are sent to the server. - , _save :: Maybe SaveOptions - } deriving (Show, Read, Eq) - -deriveJSON lspOptions ''TextDocumentSyncOptions - --- --------------------------------------------------------------------- -{- - -Extended in 3.0 ---------------- - -interface ServerCapabilities { - /** - * Defines how text documents are synced. Is either a detailed structure defining each notification or - * for backwards compatibility the TextDocumentSyncKind number. If omitted it defaults to `TextDocumentSyncKind.None`. - */ - textDocumentSync?: TextDocumentSyncOptions | number; - /** - * The server provides hover support. - */ - hoverProvider?: boolean; - /** - * The server provides completion support. - */ - completionProvider?: CompletionOptions; - /** - * The server provides signature help support. - */ - signatureHelpProvider?: SignatureHelpOptions; - /** - * The server provides goto definition support. - */ - definitionProvider?: boolean; - /** - * The server provides Goto Type Definition support. - * - * Since 3.6.0 - */ - typeDefinitionProvider?: boolean | (TextDocumentRegistrationOptions & StaticRegistrationOptions); - /** - * The server provides Goto Implementation support. - * - * Since 3.6.0 - */ - implementationProvider?: boolean | (TextDocumentRegistrationOptions & StaticRegistrationOptions); - /** - * The server provides find references support. - */ - referencesProvider?: boolean; - /** - * The server provides document highlight support. - */ - documentHighlightProvider?: boolean; - /** - * The server provides document symbol support. - */ - documentSymbolProvider?: boolean; - /** - * The server provides workspace symbol support. - */ - workspaceSymbolProvider?: boolean; - /** - * The server provides code actions. The `CodeActionOptions` return type is only - * valid if the client signals code action literal support via the property - * `textDocument.codeAction.codeActionLiteralSupport`. - */ - codeActionProvider?: boolean | CodeActionOptions; - /** - * The server provides code lens. - */ - codeLensProvider?: CodeLensOptions; - /** - * The server provides document formatting. - */ - documentFormattingProvider?: boolean; - /** - * The server provides document range formatting. - */ - documentRangeFormattingProvider?: boolean; - /** - * The server provides document formatting on typing. - */ - documentOnTypeFormattingProvider?: DocumentOnTypeFormattingOptions; - /** - * The server provides rename support. - */ - renameProvider?: boolean; - /** - * The server provides document link support. - */ - documentLinkProvider?: DocumentLinkOptions; - /** - * The server provides color provider support. - * - * Since 3.6.0 - */ - colorProvider?: boolean | ColorProviderOptions | (ColorProviderOptions & TextDocumentRegistrationOptions & StaticRegistrationOptions); - /** - * The server provides folding provider support. - * - * Since 3.10.0 - */ - foldingRangeProvider?: boolean | FoldingRangeProviderOptions | (FoldingRangeProviderOptions & TextDocumentRegistrationOptions & StaticRegistrationOptions); - /** - * The server provides execute command support. - */ - executeCommandProvider?: ExecuteCommandOptions; - /** - * Workspace specific server capabilities - */ - workspace?: { - /** - * The server supports workspace folder. - * - * Since 3.6.0 - */ - workspaceFolders?: { - /** - * The server has support for workspace folders - */ - supported?: boolean; - /** - * Whether the server wants to receive workspace folder - * change notifications. - * - * If a strings is provided the string is treated as a ID - * under which the notification is registered on the client - * side. The ID can be used to unregister for these events - * using the `client/unregisterCapability` request. - */ - changeNotifications?: string | boolean; - } - } - /** - * Experimental server capabilities. - */ - experimental?: any; -} --} - --- | Wrapper for TextDocumentSyncKind fallback. -data TDS = TDSOptions TextDocumentSyncOptions - | TDSKind TextDocumentSyncKind - deriving (Show, Read, Eq) - -instance FromJSON TDS where - parseJSON x = TDSOptions <$> parseJSON x <|> TDSKind <$> parseJSON x - -instance ToJSON TDS where - toJSON (TDSOptions x) = toJSON x - toJSON (TDSKind x) = toJSON x - -data GotoOptions = GotoOptionsStatic Bool - | GotoOptionsDynamic - { -- | A document selector to identify the scope of the registration. If set to null - -- the document selector provided on the client side will be used. - _documentSelector :: Maybe DocumentSelector - -- | The id used to register the request. The id can be used to deregister - -- the request again. See also Registration#id. - , _id :: Maybe Text - } - deriving (Show, Read, Eq) - -deriveJSON lspOptions { sumEncoding = A.UntaggedValue } ''GotoOptions --- TODO: Figure out how to make Lens', not Traversal', for sum types ---makeFieldsNoPrefix ''GotoOptions - -data ColorOptions = ColorOptionsStatic Bool - | ColorOptionsDynamic - | ColorOptionsDynamicDocument - { -- | A document selector to identify the scope of the registration. If set to null - -- the document selector provided on the client side will be used. - _documentSelector :: Maybe DocumentSelector - -- | The id used to register the request. The id can be used to deregister - -- the request again. See also Registration#id. - , _id :: Maybe Text - } - deriving (Show, Read, Eq) - -deriveJSON lspOptions { sumEncoding = A.UntaggedValue } ''ColorOptions --- makeFieldsNoPrefix ''ColorOptions - -data FoldingRangeOptions = FoldingRangeOptionsStatic Bool - | FoldingRangeOptionsDynamic - | FoldingRangeOptionsDynamicDocument - { -- | A document selector to identify the scope of the registration. If set to null - -- the document selector provided on the client side will be used. - _documentSelector :: Maybe DocumentSelector - -- | The id used to register the request. The id can be used to deregister - -- the request again. See also Registration#id. - , _id :: Maybe Text - } - deriving (Show, Read, Eq) - -deriveJSON lspOptions { sumEncoding = A.UntaggedValue } ''FoldingRangeOptions --- makeFieldsNoPrefix ''FoldingRangeOptions - -data WorkspaceFolderChangeNotifications = WorkspaceFolderChangeNotificationsString Text - | WorkspaceFolderChangeNotificationsBool Bool - deriving (Show, Read, Eq) - -deriveJSON lspOptions{ sumEncoding = A.UntaggedValue } ''WorkspaceFolderChangeNotifications - -data WorkspaceFolderOptions = - WorkspaceFolderOptions - { -- | The server has support for workspace folders - _supported :: Maybe Bool - -- | Whether the server wants to receive workspace folder - -- change notifications. - -- If a strings is provided the string is treated as a ID - -- under which the notification is registered on the client - -- side. The ID can be used to unregister for these events - -- using the `client/unregisterCapability` request. - , _changeNotifications :: Maybe WorkspaceFolderChangeNotifications - } - deriving (Show, Read, Eq) - -deriveJSON lspOptions ''WorkspaceFolderOptions - -data WorkspaceOptions = - WorkspaceOptions - { -- | The server supports workspace folder. Since LSP 3.6 - -- - -- @since 0.7.0.0 - _workspaceFolders :: Maybe WorkspaceFolderOptions - } - deriving (Show, Read, Eq) - -deriveJSON lspOptions ''WorkspaceOptions - -data InitializeResponseCapabilitiesInner = - InitializeResponseCapabilitiesInner - { -- | Defines how text documents are synced. Is either a detailed structure - -- defining each notification or for backwards compatibility the - -- 'TextDocumentSyncKind' number. - -- If omitted it defaults to 'TdSyncNone'. - _textDocumentSync :: Maybe TDS - -- | The server provides hover support. - , _hoverProvider :: Maybe Bool - -- | The server provides completion support. - , _completionProvider :: Maybe CompletionOptions - -- | The server provides signature help support. - , _signatureHelpProvider :: Maybe SignatureHelpOptions - -- | The server provides goto definition support. - , _definitionProvider :: Maybe Bool - -- | The server provides Goto Type Definition support. Since LSP 3.6 - -- - -- @since 0.7.0.0 - , _typeDefinitionProvider :: Maybe GotoOptions - -- | The server provides Goto Implementation support. - -- Since LSP 3.6 - -- - -- @since 0.7.0.0 - , _implementationProvider :: Maybe GotoOptions - -- | The server provides find references support. - , _referencesProvider :: Maybe Bool - -- | The server provides document highlight support. - , _documentHighlightProvider :: Maybe Bool - -- | The server provides document symbol support. - , _documentSymbolProvider :: Maybe Bool - -- | The server provides workspace symbol support. - , _workspaceSymbolProvider :: Maybe Bool - -- | The server provides code actions. - , _codeActionProvider :: Maybe CodeActionOptions - -- | The server provides code lens. - , _codeLensProvider :: Maybe CodeLensOptions - -- | The server provides document formatting. - , _documentFormattingProvider :: Maybe Bool - -- | The server provides document range formatting. - , _documentRangeFormattingProvider :: Maybe Bool - -- | The server provides document formatting on typing. - , _documentOnTypeFormattingProvider :: Maybe DocumentOnTypeFormattingOptions - -- | The server provides rename support. - , _renameProvider :: Maybe RenameOptions - -- | The server provides document link support. - , _documentLinkProvider :: Maybe DocumentLinkOptions - -- | The server provides color provider support. Since LSP 3.6 - -- - -- @since 0.7.0.0 - , _colorProvider :: Maybe ColorOptions - -- | The server provides folding provider support. Since LSP 3.10 - -- - -- @since 0.7.0.0 - , _foldingRangeProvider :: Maybe FoldingRangeOptions - -- | The server provides execute command support. - , _executeCommandProvider :: Maybe ExecuteCommandOptions - -- | Workspace specific server capabilities - , _workspace :: Maybe WorkspaceOptions - -- | Experimental server capabilities. - , _experimental :: Maybe A.Value - } deriving (Show, Read, Eq) - -deriveJSON lspOptions ''InitializeResponseCapabilitiesInner - --- --------------------------------------------------------------------- --- | --- Information about the capabilities of a language server --- -data InitializeResponseCapabilities = - InitializeResponseCapabilities { - _capabilities :: InitializeResponseCapabilitiesInner - } deriving (Show, Read, Eq) - -deriveJSON lspOptions ''InitializeResponseCapabilities - --- --------------------------------------------------------------------- - -type InitializeResponse = ResponseMessage InitializeResponseCapabilities - -type InitializeRequest = RequestMessage ClientMethod InitializeParams InitializeResponseCapabilities - -{- - error.code: - -/** - * Known error codes for an `InitializeError`; - */ -export namespace InitializeError { - /** - * If the protocol version provided by the client can't be handled by the server. - * @deprecated This initialize error got replaced by client capabilities. There is - * no version handshake in version 3.0x - */ - export const unknownProtocolVersion: number = 1; -} - - error.data: - -interface InitializeError { - /** - * Indicates whether the client execute the following retry logic: - * (1) show the message provided by the ResponseError to the user - * (2) user selects retry or cancel - * (3) if user selected retry the initialize method is sent again. - */ - retry: boolean; -} --} - --- --------------------------------------------------------------------- - -{- -New in 3.0 ----------- -Initialized Notification - -The initialized notification is sent from the client to the server after the -client is fully initialized and is able to listen to arbritary requests and -notifications sent from the server. - -Notification: - - method: 'initialized' - params: void - --} - -data InitializedParams = - InitializedParams - { - } deriving (Show, Read, Eq) - -instance A.FromJSON InitializedParams where - parseJSON (A.Object _) = pure InitializedParams - parseJSON _ = mempty - -instance A.ToJSON InitializedParams where - toJSON InitializedParams = A.Object mempty - -type InitializedNotification = NotificationMessage ClientMethod (Maybe InitializedParams) - --- --------------------------------------------------------------------- -{- -Shutdown Request - -https://github.com/Microsoft/language-server-protocol/blob/master/protocol.md#shutdown-request - -The shutdown request is sent from the client to the server. It asks the server -to shut down, but to not exit (otherwise the response might not be delivered -correctly to the client). There is a separate exit notification that asks the -server to exit. - -Request - - method: 'shutdown' - params: undefined - -Response - - result: undefined - error: code and message set in case an exception happens during shutdown request. - - --} - -type ShutdownRequest = RequestMessage ClientMethod (Maybe A.Value) (Maybe ()) -type ShutdownResponse = ResponseMessage (Maybe ()) - --- --------------------------------------------------------------------- -{- -Exit Notification - -https://github.com/Microsoft/language-server-protocol/blob/master/protocol.md#exit-notification - -A notification to ask the server to exit its process. - -Notification - - method: 'exit' - --} - --- | --- Notification from the server to actually exit now, after shutdown acked --- -data ExitParams = - ExitParams - { - } deriving (Show, Read, Eq) - -deriveJSON defaultOptions ''ExitParams - -type ExitNotification = NotificationMessage ClientMethod (Maybe ExitParams) - --- --------------------------------------------------------------------- -{- -Telemetry Notification - -https://github.com/Microsoft/language-server-protocol/blob/master/protocol.md#telemetry-notification - - New: The telemetry notification is sent from the server to the client to ask - the client to log a telemetry event. - -Notification: - - method: 'telemetry/event' - params: 'any' --} - - -type TelemetryNotification = NotificationMessage ServerMethod A.Value - -type CustomClientNotification = NotificationMessage ClientMethod A.Value -type CustomServerNotification = NotificationMessage ServerMethod A.Value - -type CustomClientRequest = RequestMessage ClientMethod A.Value A.Value -type CustomServerRequest = RequestMessage ServerMethod A.Value A.Value - -type CustomResponse = ResponseMessage A.Value - --- --------------------------------------------------------------------- -{- -New in 3.0 ----------- - -Register Capability - -The client/registerCapability request is sent from the server to the client to -register for a new capability on the client side. Not all clients need to -support dynamic capability registration. A client opts in via the -ClientCapabilities.dynamicRegistration property. - -Request: - - method: 'client/registerCapability' - params: RegistrationParams - -Where RegistrationParams are defined as follows: - -/** - * General paramters to to regsiter for a capability. - */ -export interface Registration { - /** - * The id used to register the request. The id can be used to deregister - * the request again. - */ - id: string; - - /** - * The method / capability to register for. - */ - method: string; - - /** - * Options necessary for the registration. - */ - registerOptions?: any; -} - -export interface RegistrationParams { - registrations: Registration[]; -} --} - -data Registration = - Registration - { -- |The id used to register the request. The id can be used to deregister - -- the request again. - _id :: Text - - -- | The method / capability to register for. - , _method :: ClientMethod - - -- | Options necessary for the registration. - , _registerOptions :: Maybe A.Value - } deriving (Show, Read, Eq) - -deriveJSON lspOptions ''Registration - -data RegistrationParams = - RegistrationParams - { _registrations :: List Registration - } deriving (Show, Read, Eq) - -deriveJSON lspOptions ''RegistrationParams - --- |Note: originates at the server -type RegisterCapabilityRequest = RequestMessage ServerMethod RegistrationParams () - -type RegisterCapabilityResponse = ResponseMessage () - --- ------------------------------------- - -{- -Since most of the registration options require to specify a document selector -there is a base interface that can be used. - -export interface TextDocumentRegistrationOptions { - /** - * A document selector to identify the scope of the registration. If set to null - * the document selector provided on the client side will be used. - */ - documentSelector: DocumentSelector | null; -} --} - -data TextDocumentRegistrationOptions = - TextDocumentRegistrationOptions - { _documentSelector :: Maybe DocumentSelector - } deriving (Show, Read, Eq) - -deriveJSON lspOptions ''TextDocumentRegistrationOptions - --- --------------------------------------------------------------------- -{- -New in 3.0 ----------- - -Unregister Capability - -The client/unregisterCapability request is sent from the server to the client to -unregister a previously register capability. - -Request: - - method: 'client/unregisterCapability' - params: UnregistrationParams - -Where UnregistrationParams are defined as follows: - -/** - * General parameters to unregister a capability. - */ -export interface Unregistration { - /** - * The id used to unregister the request or notification. Usually an id - * provided during the register request. - */ - id: string; - - /** - * The method / capability to unregister for. - */ - method: string; -} - -export interface UnregistrationParams { - unregisterations: Unregistration[]; -} --} - -data Unregistration = - Unregistration - { -- | The id used to unregister the request or notification. Usually an id - -- provided during the register request. - _id :: Text - - -- |The method / capability to unregister for. - , _method :: Text - } deriving (Show, Read, Eq) - -deriveJSON lspOptions ''Unregistration - -data UnregistrationParams = - UnregistrationParams - { _unregistrations :: List Unregistration - } deriving (Show, Read, Eq) - -deriveJSON lspOptions ''UnregistrationParams - -type UnregisterCapabilityRequest = RequestMessage ServerMethod UnregistrationParams () - -type UnregisterCapabilityResponse = ResponseMessage () - --- --------------------------------------------------------------------- - --- /** --- * Describe options to be used when registering for file system change events. --- */ --- export interface DidChangeWatchedFilesRegistrationOptions { --- /** --- * The watchers to register. --- */ --- watchers: FileSystemWatcher[]; --- } --- --- export interface FileSystemWatcher { --- /** --- * The glob pattern to watch. --- * --- * Glob patterns can have the following syntax: --- * - `*` to match one or more characters in a path segment --- * - `?` to match on one character in a path segment --- * - `**` to match any number of path segments, including none --- * - `{}` to group conditions (e.g. `**​/*.{ts,js}` matches all TypeScript and JavaScript files) --- * - `[]` to declare a range of characters to match in a path segment (e.g., `example.[0-9]` to match on `example.0`, `example.1`, …) --- * - `[!...]` to negate a range of characters to match in a path segment (e.g., `example.[!0-9]` to match on `example.a`, `example.b`, but not `example.0`) --- */ --- globPattern: string; --- --- /** --- * The kind of events of interest. If omitted it defaults --- * to WatchKind.Create | WatchKind.Change | WatchKind.Delete --- * which is 7. --- */ --- kind?: number; --- } --- --- export namespace WatchKind { --- /** --- * Interested in create events. --- */ --- export const Create = 1; --- --- /** --- * Interested in change events --- */ --- export const Change = 2; --- --- /** --- * Interested in delete events --- */ --- export const Delete = 4; --- } - -data DidChangeWatchedFilesRegistrationOptions = - DidChangeWatchedFilesRegistrationOptions { - _watchers :: List FileSystemWatcher - } deriving (Show, Read, Eq) - -data FileSystemWatcher = - FileSystemWatcher { - _globPattern :: String, - _kind :: Maybe WatchKind - } deriving (Show, Read, Eq) - -data WatchKind = - WatchKind { - -- | Watch for create events - _watchCreate :: Bool, - -- | Watch for change events - _watchChange :: Bool, - -- | Watch for delete events - _watchDelete :: Bool - } deriving (Show, Read, Eq) - -instance A.ToJSON WatchKind where - toJSON wk = A.Number (createNum + changeNum + deleteNum) - where - createNum = if _watchCreate wk then 0x1 else 0x0 - changeNum = if _watchChange wk then 0x2 else 0x0 - deleteNum = if _watchDelete wk then 0x4 else 0x0 - -instance A.FromJSON WatchKind where - parseJSON (A.Number n) - | Right i <- floatingOrInteger n :: Either Double Int - , 0 <= i && i <= 7 = - pure $ WatchKind (testBit i 0x0) (testBit i 0x1) (testBit i 0x2) - | otherwise = mempty - parseJSON _ = mempty - -deriveJSON lspOptions ''FileSystemWatcher -deriveJSON lspOptions ''DidChangeWatchedFilesRegistrationOptions - --- --------------------------------------------------------------------- -{- -DidChangeConfiguration Notification - -https://github.com/Microsoft/language-server-protocol/blob/master/protocol.md#didchangeconfiguration-notification - -A notification sent from the client to the server to signal the change of -configuration settings. - -Notification: - - method: 'workspace/didChangeConfiguration', - params: DidChangeConfigurationParams defined as follows: - -interface DidChangeConfigurationParams { - /** - * The actual changed settings - */ - settings: any; -} --} - -data DidChangeConfigurationParams = - DidChangeConfigurationParams { - _settings :: A.Value - } deriving (Show, Read, Eq) - -deriveJSON lspOptions ''DidChangeConfigurationParams - --- --------------------------------------------------------------------- - -type DidChangeConfigurationNotification = NotificationMessage ClientMethod DidChangeConfigurationParams - -{- -Configuration Request (:arrow_right_hook:) -Since version 3.6.0 - -The workspace/configuration request is sent from the server to the client to -fetch configuration settings from the client. The request can fetch n -configuration settings in one roundtrip. The order of the returned configuration -settings correspond to the order of the passed ConfigurationItems (e.g. the -first item in the response is the result for the first configuration item in the -params). - -A ConfigurationItem consist of the configuration section to ask for and an -additional scope URI. The configuration section ask for is defined by the server -and doesn’t necessarily need to correspond to the configuration store used be -the client. So a server might ask for a configuration cpp.formatterOptions but -the client stores the configuration in a XML store layout differently. It is up -to the client to do the necessary conversion. If a scope URI is provided the -client should return the setting scoped to the provided resource. If the client -for example uses EditorConfig to manage its settings the configuration should be -returned for the passed resource URI. If the client can’t provide a -configuration setting for a given scope then null need to be present in the -returned array. - -Request: - -method: ‘workspace/configuration’ -params: ConfigurationParams defined as follows -export interface ConfigurationParams { - items: ConfigurationItem[]; -} - -export interface ConfigurationItem { - /** - * The scope to get the configuration section for. - */ - scopeUri?: string; - - /** - * The configuration section asked for. - */ - section?: string; -} -Response: - -result: any[] -error: code and message set in case an exception happens during the -‘workspace/configuration’ request --} - -data ConfigurationItem = - ConfigurationItem - { _scopeUri :: Maybe Text -- ^ The scope to get the configuration section for. - , _section :: Maybe Text -- ^ The configuration section asked for. - } deriving (Show, Read, Eq) - -deriveJSON lspOptions ''ConfigurationItem - -data ConfigurationParams = - ConfigurationParams - { _items :: List ConfigurationItem - } deriving (Show, Read, Eq) - -deriveJSON lspOptions ''ConfigurationParams - -type ConfigurationRequest = RequestMessage ServerMethod ConfigurationParams (List A.Value) -type ConfigurationResponse = ResponseMessage (List A.Value) - --- --------------------------------------------------------------------- -{- -DidOpenTextDocument Notification - -https://github.com/Microsoft/language-server-protocol/blob/master/protocol.md#didopentextdocument-notification - -The document open notification is sent from the client to the server to signal -newly opened text documents. The document's truth is now managed by the client -and the server must not try to read the document's truth using the document's -uri. - -Notification: - - method: 'textDocument/didOpen' - params: DidOpenTextDocumentParams defined as follows: - -interface DidOpenTextDocumentParams { - /** - * The document that was opened. - */ - textDocument: TextDocumentItem; -} - -Registration Options: TextDocumentRegistrationOptions --} - -data DidOpenTextDocumentParams = - DidOpenTextDocumentParams { - _textDocument :: TextDocumentItem - } deriving (Show, Read, Eq) - -deriveJSON lspOptions ''DidOpenTextDocumentParams - -type DidOpenTextDocumentNotification = NotificationMessage ClientMethod DidOpenTextDocumentParams - --- --------------------------------------------------------------------- -{- -DidChangeTextDocument Notification - -https://github.com/Microsoft/language-server-protocol/blob/master/protocol.md#didchangetextdocument-notification - - Changed: The document change notification is sent from the client to the - server to signal changes to a text document. In 2.0 the shape of the params - has changed to include proper version numbers and language ids. - -Notification: - - method: 'textDocument/didChange' - params: DidChangeTextDocumentParams defined as follows: - -interface DidChangeTextDocumentParams { - /** - * The document that did change. The version number points - * to the version after all provided content changes have - * been applied. - */ - textDocument: VersionedTextDocumentIdentifier; - - /** - * The actual content changes. - */ - contentChanges: TextDocumentContentChangeEvent[]; -} - -/** - * An event describing a change to a text document. If range and rangeLength are omitted - * the new text is considered to be the full content of the document. - */ -interface TextDocumentContentChangeEvent { - /** - * The range of the document that changed. - */ - range?: Range; - - /** - * The length of the range that got replaced. - */ - rangeLength?: number; - - /** - * The new text of the document. - */ - text: string; -} --} -data TextDocumentContentChangeEvent = - TextDocumentContentChangeEvent - { _range :: Maybe Range - , _rangeLength :: Maybe Int - , _text :: Text - } deriving (Read,Show,Eq) - -deriveJSON lspOptions { omitNothingFields = True } ''TextDocumentContentChangeEvent - --- ------------------------------------- - -data DidChangeTextDocumentParams = - DidChangeTextDocumentParams - { _textDocument :: VersionedTextDocumentIdentifier - , _contentChanges :: List TextDocumentContentChangeEvent - } deriving (Show,Read,Eq) - -deriveJSON lspOptions ''DidChangeTextDocumentParams - -type DidChangeTextDocumentNotification = NotificationMessage ClientMethod DidChangeTextDocumentParams -{- -New in 3.0 ----------- - -Registration Options: TextDocumentChangeRegistrationOptions defined as follows: - -/** - * Descibe options to be used when registered for text document change events. - */ -export interface TextDocumentChangeRegistrationOptions extends TextDocumentRegistrationOptions { - /** - * How documents are synced to the server. See TextDocumentSyncKind.Full - * and TextDocumentSyncKindIncremental. - */ - syncKind: number; -} --} - -data TextDocumentChangeRegistrationOptions = - TextDocumentChangeRegistrationOptions - { _documentSelector :: Maybe DocumentSelector - , _syncKind :: TextDocumentSyncKind - } deriving (Show, Read, Eq) - -deriveJSON lspOptions ''TextDocumentChangeRegistrationOptions - --- --------------------------------------------------------------------- -{- - -New in 3.0 ----------- - -WillSaveTextDocument Notification - -The document will save notification is sent from the client to the server before -the document is actually saved. - -Notification: - - method: 'textDocument/willSave' - params: WillSaveTextDocumentParams defined as follows: - -/** - * The parameters send in a will save text document notification. - */ -export interface WillSaveTextDocumentParams { - /** - * The document that will be saved. - */ - textDocument: TextDocumentIdentifier; - - /** - * The 'TextDocumentSaveReason'. - */ - reason: number; -} - -/** - * Represents reasons why a text document is saved. - */ -export namespace TextDocumentSaveReason { - - /** - * Manually triggered, e.g. by the user pressing save, by starting debugging, - * or by an API call. - */ - export const Manual = 1; - - /** - * Automatic after a delay. - */ - export const AfterDelay = 2; - - /** - * When the editor lost focus. - */ - export const FocusOut = 3; -} -Registration Options: TextDocumentRegistrationOptions --} - -data TextDocumentSaveReason - = SaveManual - -- ^ Manually triggered, e.g. by the user pressing save, by starting - -- debugging, or by an API call. - | SaveAfterDelay -- ^ Automatic after a delay - | SaveFocusOut -- ^ When the editor lost focus - deriving (Show, Read, Eq) - -instance A.ToJSON TextDocumentSaveReason where - toJSON SaveManual = A.Number 1 - toJSON SaveAfterDelay = A.Number 2 - toJSON SaveFocusOut = A.Number 3 - -instance A.FromJSON TextDocumentSaveReason where - parseJSON (A.Number 1) = pure SaveManual - parseJSON (A.Number 2) = pure SaveAfterDelay - parseJSON (A.Number 3) = pure SaveFocusOut - parseJSON _ = mempty - -data WillSaveTextDocumentParams = - WillSaveTextDocumentParams - { _textDocument :: TextDocumentIdentifier - , _reason :: TextDocumentSaveReason - } deriving (Show, Read, Eq) - -deriveJSON lspOptions ''WillSaveTextDocumentParams - -type WillSaveTextDocumentNotification = NotificationMessage ClientMethod WillSaveTextDocumentParams - --- --------------------------------------------------------------------- -{- -New in 3.0 ----------- - -WillSaveWaitUntilTextDocument Request - -The document will save request is sent from the client to the server before the -document is actually saved. The request can return an array of TextEdits which -will be applied to the text document before it is saved. Please note that -clients might drop results if computing the text edits took too long or if a -server constantly fails on this request. This is done to keep the save fast and -reliable. - -Request: - - method: 'textDocument/willSaveWaitUntil' - params: WillSaveTextDocumentParams - -Response: - - result: TextEdit[] - error: code and message set in case an exception happens during the willSaveWaitUntil request. - -Registration Options: TextDocumentRegistrationOptions --} - -type WillSaveWaitUntilTextDocumentRequest = RequestMessage ClientMethod WillSaveTextDocumentParams (List TextEdit) -type WillSaveWaitUntilTextDocumentResponse = ResponseMessage (List TextEdit) - --- --------------------------------------------------------------------- -{- -DidSaveTextDocument Notification - -https://github.com/Microsoft/language-server-protocol/blob/master/protocol.md#didsavetextdocument-notification - - New: The document save notification is sent from the client to the server - when the document was saved in the client. - - method: 'textDocument/didSave' - params: DidSaveTextDocumentParams defined as follows: - -interface DidSaveTextDocumentParams { - /** - * The document that was saved. - */ - textDocument: TextDocumentIdentifier; -} --} -data DidSaveTextDocumentParams = - DidSaveTextDocumentParams - { _textDocument :: TextDocumentIdentifier - } deriving (Read,Show,Eq) - -deriveJSON lspOptions ''DidSaveTextDocumentParams - -type DidSaveTextDocumentNotification = NotificationMessage ClientMethod DidSaveTextDocumentParams - - - --- --------------------------------------------------------------------- -{- -DidCloseTextDocument Notification - -https://github.com/Microsoft/language-server-protocol/blob/master/protocol.md#didclosetextdocument-notification - -The document close notification is sent from the client to the server when the -document got closed in the client. The document's truth now exists where the -document's uri points to (e.g. if the document's uri is a file uri the truth now -exists on disk). - - Changed: In 2.0 the params are of type DidCloseTextDocumentParams which - contains a reference to a text document. - -Notification: - - method: 'textDocument/didClose' - params: DidCloseTextDocumentParams defined as follows: - -interface DidCloseTextDocumentParams { - /** - * The document that was closed. - */ - textDocument: TextDocumentIdentifier; -} --} -data DidCloseTextDocumentParams = - DidCloseTextDocumentParams - { _textDocument :: TextDocumentIdentifier - } deriving (Read,Show,Eq) - -deriveJSON lspOptions ''DidCloseTextDocumentParams - - -type DidCloseTextDocumentNotification = NotificationMessage ClientMethod DidCloseTextDocumentParams - --- --------------------------------------------------------------------- -{- -DidChangeWatchedFiles Notification - -https://github.com/Microsoft/language-server-protocol/blob/master/protocol.md#didchangewatchedfiles-notification - -The watched files notification is sent from the client to the server when the -client detects changes to files watched by the language client. - -Notification: - - method: 'workspace/didChangeWatchedFiles' - params: DidChangeWatchedFilesParams defined as follows: - -interface DidChangeWatchedFilesParams { - /** - * The actual file events. - */ - changes: FileEvent[]; -} - -Where FileEvents are described as follows: - -/** - * The file event type. - */ -enum FileChangeType { - /** - * The file got created. - */ - Created = 1, - /** - * The file got changed. - */ - Changed = 2, - /** - * The file got deleted. - */ - Deleted = 3 -} - -/** - * An event describing a file change. - */ -interface FileEvent { - /** - * The file's URI. - */ - uri: string; - /** - * The change type. - */ - type: number; --} -data FileChangeType = FcCreated - | FcChanged - | FcDeleted - deriving (Read,Show,Eq) - -instance A.ToJSON FileChangeType where - toJSON FcCreated = A.Number 1 - toJSON FcChanged = A.Number 2 - toJSON FcDeleted = A.Number 3 - -instance A.FromJSON FileChangeType where - parseJSON (A.Number 1) = pure FcCreated - parseJSON (A.Number 2) = pure FcChanged - parseJSON (A.Number 3) = pure FcDeleted - parseJSON _ = mempty - - --- ------------------------------------- - -data FileEvent = - FileEvent - { _uri :: Uri - , _xtype :: FileChangeType - } deriving (Read,Show,Eq) - -deriveJSON lspOptions{ fieldLabelModifier = customModifier } ''FileEvent - -data DidChangeWatchedFilesParams = - DidChangeWatchedFilesParams - { _changes :: List FileEvent - } deriving (Read,Show,Eq) - -deriveJSON lspOptions ''DidChangeWatchedFilesParams - - -type DidChangeWatchedFilesNotification = NotificationMessage ClientMethod DidChangeWatchedFilesParams - --- --------------------------------------------------------------------- -{- -PublishDiagnostics Notification - -https://github.com/Microsoft/language-server-protocol/blob/master/protocol.md#publishdiagnostics-notification - -Diagnostics notification are sent from the server to the client to signal -results of validation runs. - -Notification - - method: 'textDocument/publishDiagnostics' - params: PublishDiagnosticsParams defined as follows: - -interface PublishDiagnosticsParams { - /** - * The URI for which diagnostic information is reported. - */ - uri: string; - - /** - * An array of diagnostic information items. - */ - diagnostics: Diagnostic[]; -} --} - -data PublishDiagnosticsParams = - PublishDiagnosticsParams - { _uri :: Uri - , _diagnostics :: List Diagnostic - } deriving (Read,Show,Eq) - -deriveJSON lspOptions ''PublishDiagnosticsParams - - -type PublishDiagnosticsNotification = NotificationMessage ServerMethod PublishDiagnosticsParams - --- --------------------------------------------------------------------- -{- -Signature Help Request - -https://github.com/Microsoft/language-server-protocol/blob/master/protocol.md#signature-help-request - -The signature help request is sent from the client to the server to request -signature information at a given cursor position. - - Changed: In 2.0 the request uses TextDocumentPositionParams with proper - textDocument and position properties. In 1.0 the uri of the referenced text - document was inlined into the params object. - -Request - - method: 'textDocument/signatureHelp' - params: TextDocumentPositionParams - -Response - - result: SignatureHelp defined as follows: - -/** - * Signature help represents the signature of something - * callable. There can be multiple signature but only one - * active and only one active parameter. - */ -interface SignatureHelp { - /** - * One or more signatures. - */ - signatures: SignatureInformation[]; - - /** - * The active signature. - */ - activeSignature?: number; - - /** - * The active parameter of the active signature. - */ - activeParameter?: number; -} - -/** - * Represents the signature of something callable. A signature - * can have a label, like a function-name, a doc-comment, and - * a set of parameters. - */ -interface SignatureInformation { - /** - * The label of this signature. Will be shown in - * the UI. - */ - label: string; - - /** - * The human-readable doc-comment of this signature. Will be shown - * in the UI but can be omitted. - */ - documentation?: string; - - /** - * The parameters of this signature. - */ - parameters?: ParameterInformation[]; -} - -/** - * Represents a parameter of a callable-signature. A parameter can - * have a label and a doc-comment. - */ -interface ParameterInformation { - /** - * The label of this signature. Will be shown in - * the UI. - */ - label: string; - - /** - * The human-readable doc-comment of this signature. Will be shown - * in the UI but can be omitted. - */ - documentation?: string; -} - - error: code and message set in case an exception happens during the - signature help request. --} - - -data ParameterInformation = - ParameterInformation - { _label :: Text - , _documentation :: Maybe Text - } deriving (Read,Show,Eq) -deriveJSON lspOptions ''ParameterInformation - - --- ------------------------------------- - -data SignatureInformation = - SignatureInformation - { _label :: Text - , _documentation :: Maybe Text - , _parameters :: Maybe [ParameterInformation] - } deriving (Read,Show,Eq) - -deriveJSON lspOptions ''SignatureInformation - -data SignatureHelp = - SignatureHelp - { _signatures :: List SignatureInformation - , _activeSignature :: Maybe Int -- ^ The active signature - , _activeParameter :: Maybe Int -- ^ The active parameter of the active signature - } deriving (Read,Show,Eq) - -deriveJSON lspOptions ''SignatureHelp - -type SignatureHelpRequest = RequestMessage ClientMethod TextDocumentPositionParams SignatureHelp -type SignatureHelpResponse = ResponseMessage SignatureHelp - --- ------------------------------------- -{- -New in 3.0 ----------- -Registration Options: SignatureHelpRegistrationOptions defined as follows: - -export interface SignatureHelpRegistrationOptions extends TextDocumentRegistrationOptions { - /** - * The characters that trigger signature help - * automatically. - */ - triggerCharacters?: string[]; -} --} - -data SignatureHelpRegistrationOptions = - SignatureHelpRegistrationOptions - { _documentSelector :: Maybe DocumentSelector - , _triggerCharacters :: Maybe (List String) - } deriving (Show, Read, Eq) - -deriveJSON lspOptions ''SignatureHelpRegistrationOptions - --- --------------------------------------------------------------------- -{- -Goto Definition Request - -https://github.com/Microsoft/language-server-protocol/blob/master/protocol.md#goto-definition-request - -The goto definition request is sent from the client to the server to resolve the -definition location of a symbol at a given text document position. - - Changed: In 2.0 the request uses TextDocumentPositionParams with proper - textDocument and position properties. In 1.0 the uri of the referenced text - document was inlined into the params object. - -Request - - method: 'textDocument/definition' - params: TextDocumentPositionParams - -Response: - - result: Location | Location[] - error: code and message set in case an exception happens during the definition request. - - --} - --- {"jsonrpc":"2.0","id":1,"method":"textDocument/definition","params":{"textDocument":{"uri":"file:///tmp/Foo.hs"},"position":{"line":1,"character":8}}} - -data LocationResponseParams = SingleLoc Location | MultiLoc [Location] - deriving (Eq,Read,Show) - -instance A.ToJSON LocationResponseParams where - toJSON (SingleLoc x) = toJSON x - toJSON (MultiLoc xs) = toJSON xs - -instance A.FromJSON LocationResponseParams where - parseJSON xs@(A.Array _) = MultiLoc <$> parseJSON xs - parseJSON x = SingleLoc <$> parseJSON x - -type DefinitionRequest = RequestMessage ClientMethod TextDocumentPositionParams LocationResponseParams -type DefinitionResponse = ResponseMessage LocationResponseParams - --- --------------------------------------------------------------------- - -{- -Goto Type Definition Request (:leftwards_arrow_with_hook:) -Since version 3.6.0 - -The goto type definition request is sent from the client to the server to resolve the type definition location of a symbol at a given text document position. - -Request: - -method: ‘textDocument/typeDefinition’ -params: TextDocumentPositionParams -Response: - -result: Location | Location[] | null -error: code and message set in case an exception happens during the definition request. -Registration Options: TextDocumentRegistrationOptions --} - -type TypeDefinitionRequest = RequestMessage ClientMethod TextDocumentPositionParams LocationResponseParams -type TypeDefinitionResponse = ResponseMessage LocationResponseParams - --- --------------------------------------------------------------------- - -{- -Goto Implementation Request (:leftwards_arrow_with_hook:) -Since version 3.6.0 - -The goto implementation request is sent from the client to the server to resolve the implementation location of a symbol at a given text document position. - -Request: - -method: ‘textDocument/implementation’ -params: TextDocumentPositionParams -Response: - -result: Location | Location[] | null -error: code and message set in case an exception happens during the definition request. -Registration Options: TextDocumentRegistrationOptions --} - - -type ImplementationRequest = RequestMessage ClientMethod TextDocumentPositionParams LocationResponseParams -type ImplementationResponse = ResponseMessage LocationResponseParams - --- --------------------------------------------------------------------- - -{- -Find References Request - -https://github.com/Microsoft/language-server-protocol/blob/master/protocol.md#find-references-request - -The references request is sent from the client to the server to resolve -project-wide references for the symbol denoted by the given text document -position. - - Changed: In 2.0 the request uses TextDocumentPositionParams with proper - textDocument and position properties. In 1.0 the uri of the referenced text - document was inlined into the params object. - -Request - - method: 'textDocument/references' - params: ReferenceParams defined as follows: - -interface ReferenceParams extends TextDocumentPositionParams { - context: ReferenceContext -} - -interface ReferenceContext { - /** - * Include the declaration of the current symbol. - */ - includeDeclaration: boolean; -} - -Response: - - result: Location[] - error: code and message set in case an exception happens during the - reference request. --} - -data ReferenceContext = - ReferenceContext - { _includeDeclaration :: Bool - } deriving (Read,Show,Eq) - -deriveJSON lspOptions ''ReferenceContext - - -data ReferenceParams = - ReferenceParams - { _textDocument :: TextDocumentIdentifier - , _position :: Position - , _context :: ReferenceContext - , _workDoneToken :: Maybe ProgressToken -- ^ An optional token that a server can use to report work done progress. - } deriving (Read,Show,Eq) - -deriveJSON lspOptions ''ReferenceParams - - -type ReferencesRequest = RequestMessage ClientMethod ReferenceParams (List Location) -type ReferencesResponse = ResponseMessage (List Location) - --- --------------------------------------------------------------------- -{- -Document Highlights Request - -https://github.com/Microsoft/language-server-protocol/blob/master/protocol.md#document-highlights-request - -The document highlight request is sent from the client to the server to resolve -a document highlights for a given text document position. For programming -languages this usually highlights all references to the symbol scoped to this -file. However we kept 'textDocument/documentHighlight' and -'textDocument/references' separate requests since the first one is allowed to be -more fuzzy. Symbol matches usually have a DocumentHighlightKind of Read or Write -whereas fuzzy or textual matches use Textas the kind. - - Changed: In 2.0 the request uses TextDocumentPositionParams with proper - textDocument and position properties. In 1.0 the uri of the referenced text - document was inlined into the params object. - -Request - - method: 'textDocument/documentHighlight' - params: TextDocumentPositionParams - -Response - - result: DocumentHighlight[] defined as follows: - -/** - * A document highlight is a range inside a text document which deserves - * special attention. Usually a document highlight is visualized by changing - * the background color of its range. - * - */ -interface DocumentHighlight { - /** - * The range this highlight applies to. - */ - range: Range; - - /** - * The highlight kind, default is DocumentHighlightKind.Text. - */ - kind?: number; -} - -/** - * A document highlight kind. - */ -enum DocumentHighlightKind { - /** - * A textual occurrance. - */ - Text = 1, - - /** - * Read-access of a symbol, like reading a variable. - */ - Read = 2, - - /** - * Write-access of a symbol, like writing to a variable. - */ - Write = 3 -} - - error: code and message set in case an exception happens during the document - highlight request. - -Registration Options: TextDocumentRegistrationOptions - --} - -data DocumentHighlightKind = HkText | HkRead | HkWrite - deriving (Read,Show,Eq) - -instance A.ToJSON DocumentHighlightKind where - toJSON HkText = A.Number 1 - toJSON HkRead = A.Number 2 - toJSON HkWrite = A.Number 3 - -instance A.FromJSON DocumentHighlightKind where - parseJSON (A.Number 1) = pure HkText - parseJSON (A.Number 2) = pure HkRead - parseJSON (A.Number 3) = pure HkWrite - parseJSON _ = mempty - --- ------------------------------------- - -data DocumentHighlight = - DocumentHighlight - { _range :: Range - , _kind :: Maybe DocumentHighlightKind - } deriving (Read,Show,Eq) - -deriveJSON lspOptions ''DocumentHighlight - -type DocumentHighlightRequest = RequestMessage ClientMethod TextDocumentPositionParams (List DocumentHighlight) -type DocumentHighlightsResponse = ResponseMessage (List DocumentHighlight) - --- --------------------------------------------------------------------- -{- -Workspace Symbols Request - -https://github.com/Microsoft/language-server-protocol/blob/master/protocol.md#workspace-symbols-request - -The workspace symbol request is sent from the client to the server to list -project-wide symbols matching the query string. - -Request - - method: 'workspace/symbol' - params: WorkspaceSymbolParams defined as follows: - -/** - * The parameters of a Workspace Symbol Request. - */ -interface WorkspaceSymbolParams { - /** - * A non-empty query string - */ - query: string; -} - -Response - - result: SymbolInformation[] as defined above. - error: code and message set in case an exception happens during the - workspace symbol request. --} - -data WorkspaceSymbolParams = - WorkspaceSymbolParams - { _query :: Text -- ^ A query string to filter symbols by. Clients may send an empty string here to request all symbols. - , _workDoneToken :: Maybe ProgressToken -- ^ An optional token that a server can use to report work done progress. - } deriving (Read,Show,Eq) - -deriveJSON lspOptions ''WorkspaceSymbolParams - -type WorkspaceSymbolRequest = RequestMessage ClientMethod WorkspaceSymbolParams (List SymbolInformation) -type WorkspaceSymbolsResponse = ResponseMessage (List SymbolInformation) - --- --------------------------------------------------------------------- -{- -Code Lens Request - -The code lens request is sent from the client to the server to compute code -lenses for a given text document. - - Changed: In 2.0 the request uses CodeLensParams instead of a single uri. - -Request - - method: 'textDocument/codeLens' - params: CodeLensParams defined as follows: - -interface CodeLensParams { - /** - * The document to request code lens for. - */ - textDocument: TextDocumentIdentifier; -} - -Response - - result: CodeLens[] defined as follows: - -/** - * A code lens represents a command that should be shown along with - * source text, like the number of references, a way to run tests, etc. - * - * A code lens is _unresolved_ when no command is associated to it. For performance - * reasons the creation of a code lens and resolving should be done in two stages. - */ -interface CodeLens { - /** - * The range in which this code lens is valid. Should only span a single line. - */ - range: Range; - - /** - * The command this code lens represents. - */ - command?: Command; - - /** - * A data entry field that is preserved on a code lens item between - * a code lens and a code lens resolve request. - */ - data?: any -} - - error: code and message set in case an exception happens during the code - lens request. --} - -data CodeLensParams = - CodeLensParams - { _textDocument :: TextDocumentIdentifier - , _workDoneToken :: Maybe ProgressToken -- ^ An optional token that a server can use to report work done progress. - } deriving (Read,Show,Eq) - -deriveJSON lspOptions ''CodeLensParams - - --- ------------------------------------- - -data CodeLens = - CodeLens - { _range :: Range - , _command :: Maybe Command - , _xdata :: Maybe A.Value - } deriving (Read,Show,Eq) - -deriveJSON lspOptions{ fieldLabelModifier = customModifier } ''CodeLens - - -type CodeLensRequest = RequestMessage ClientMethod CodeLensParams (List CodeLens) -type CodeLensResponse = ResponseMessage (List CodeLens) - --- ------------------------------------- -{- -Registration Options: CodeLensRegistrationOptions defined as follows: - -export interface CodeLensRegistrationOptions extends TextDocumentRegistrationOptions { - /** - * Code lens has a resolve provider as well. - */ - resolveProvider?: boolean; -} --} - -data CodeLensRegistrationOptions = - CodeLensRegistrationOptions - { _documentSelector :: Maybe DocumentSelector - , _resolveProvider :: Maybe Bool - } deriving (Show, Read, Eq) - -deriveJSON lspOptions ''CodeLensRegistrationOptions - --- --------------------------------------------------------------------- -{- -Code Lens Resolve Request - -https://github.com/Microsoft/language-server-protocol/blob/master/protocol.md#code-lens-resolve-request - -The code lens resolve request is sent from the client to the server to resolve -the command for a given code lens item. - -Request - - method: 'codeLens/resolve' - params: CodeLens - -Response - - result: CodeLens - error: code and message set in case an exception happens during the code - lens resolve request. - - --} - -type CodeLensResolveRequest = RequestMessage ClientMethod CodeLens CodeLens -type CodeLensResolveResponse = ResponseMessage CodeLens - --- --------------------------------------------------------------------- -{- -New in 3.0 ----------- - -Document Link Request - -The document links request is sent from the client to the server to request the -location of links in a document. - -Request: - - method: 'textDocument/documentLink' - params: DocumentLinkParams, defined as follows - -interface DocumentLinkParams { - /** - * The document to provide document links for. - */ - textDocument: TextDocumentIdentifier; -} - -Response: - - result: An array of DocumentLink, or null. - -/** - * A document link is a range in a text document that links to an internal or external resource, like another - * text document or a web site. - */ -interface DocumentLink { - /** - * The range this link applies to. - */ - range: Range; - /** - * The uri this link points to. If missing a resolve request is sent later. - */ - target?: DocumentUri; -} - - error: code and message set in case an exception happens during the document link request. - -Registration Options: DocumentLinkRegistrationOptions defined as follows: - -export interface DocumentLinkRegistrationOptions extends TextDocumentRegistrationOptions { - /** - * Document links have a resolve provider as well. - */ - resolveProvider?: boolean; -} --} - -data DocumentLinkParams = - DocumentLinkParams - { _textDocument :: TextDocumentIdentifier - , _workDoneToken :: Maybe ProgressToken -- ^ An optional token that a server can use to report work done progress. - } deriving (Read,Show,Eq) - -deriveJSON lspOptions ''DocumentLinkParams - -data DocumentLink = - DocumentLink - { _range :: Range - , _target :: Maybe Text - } deriving (Show, Read, Eq) - -deriveJSON lspOptions ''DocumentLink - -type DocumentLinkRequest = RequestMessage ClientMethod DocumentLinkParams (List DocumentLink) -type DocumentLinkResponse = ResponseMessage (List DocumentLink) - --- --------------------------------------------------------------------- -{- -New in 3.0 ----------- - -Document Link Resolve Request - -The document link resolve request is sent from the client to the server to resolve the target of a given document link. - -Request: - - method: 'documentLink/resolve' - params: DocumentLink - -Response: - - result: DocumentLink - error: code and message set in case an exception happens during the document link resolve request. - --} - -type DocumentLinkResolveRequest = RequestMessage ClientMethod DocumentLink DocumentLink -type DocumentLinkResolveResponse = ResponseMessage DocumentLink - --- --------------------------------------------------------------------- -{- -Document Formatting Request - -https://github.com/Microsoft/language-server-protocol/blob/master/protocol.md#document-formatting-request - -The document formatting request is sent from the server to the client to format -a whole document. - -Request - - method: 'textDocument/formatting' - params: DocumentFormattingParams defined as follows - -interface DocumentFormattingParams { - /** - * The document to format. - */ - textDocument: TextDocumentIdentifier; - - /** - * The format options. - */ - options: FormattingOptions; -} - -/** - * Value-object describing what options formatting should use. - */ -interface FormattingOptions { - /** - * Size of a tab in spaces. - */ - tabSize: number; - - /** - * Prefer spaces over tabs. - */ - insertSpaces: boolean; - - /** - * Signature for further properties. - */ - [key: string]: boolean | number | string; -} - -Response - - result: TextEdit[] describing the modification to the document to be - formatted. - error: code and message set in case an exception happens during the - formatting request. - -Registration Options: TextDocumentRegistrationOptions --} - -data FormattingOptions = - FormattingOptions - { _tabSize :: Int - , _insertSpaces :: Bool -- ^ Prefer spaces over tabs - -- Note: May be more properties - } deriving (Read,Show,Eq) - -deriveJSON lspOptions ''FormattingOptions - -data DocumentFormattingParams = - DocumentFormattingParams - { _textDocument :: TextDocumentIdentifier - , _options :: FormattingOptions - , _workDoneToken :: Maybe ProgressToken -- ^ An optional token that a server can use to report work done progress. - } deriving (Show,Read,Eq) - -deriveJSON lspOptions ''DocumentFormattingParams - -type DocumentFormattingRequest = RequestMessage ClientMethod DocumentFormattingParams (List TextEdit) -type DocumentFormattingResponse = ResponseMessage (List TextEdit) - --- --------------------------------------------------------------------- -{- -Document Range Formatting Request - -https://github.com/Microsoft/language-server-protocol/blob/master/protocol.md#document-range-formatting-request - -The document range formatting request is sent from the client to the server to -format a given range in a document. - -Request - - method: 'textDocument/rangeFormatting', - params: DocumentRangeFormattingParams defined as follows - -interface DocumentRangeFormattingParams { - /** - * The document to format. - */ - textDocument: TextDocumentIdentifier; - - /** - * The range to format - */ - range: Range; - - /** - * The format options - */ - options: FormattingOptions; -} - -Response - - result: TextEdit[] describing the modification to the document to be - formatted. - error: code and message set in case an exception happens during the range - formatting request. --} - -data DocumentRangeFormattingParams = - DocumentRangeFormattingParams - { _textDocument :: TextDocumentIdentifier - , _range :: Range - , _options :: FormattingOptions - , _workDoneToken :: Maybe ProgressToken -- ^ An optional token that a server can use to report work done progress. - } deriving (Read,Show,Eq) - -deriveJSON lspOptions ''DocumentRangeFormattingParams - -type DocumentRangeFormattingRequest = RequestMessage ClientMethod DocumentRangeFormattingParams (List TextEdit) -type DocumentRangeFormattingResponse = ResponseMessage (List TextEdit) - --- --------------------------------------------------------------------- -{- -Document on Type Formatting Request - -https://github.com/Microsoft/language-server-protocol/blob/master/protocol.md#document-on-type-formatting-request - -The document on type formatting request is sent from the client to the server to -format parts of the document during typing. - -Request - - method: 'textDocument/onTypeFormatting' - params: DocumentOnTypeFormattingParams defined as follows - -interface DocumentOnTypeFormattingParams { - /** - * The document to format. - */ - textDocument: TextDocumentIdentifier; - - /** - * The position at which this request was sent. - */ - position: Position; - - /** - * The character that has been typed. - */ - ch: string; - - /** - * The format options. - */ - options: FormattingOptions; -} - -Response - - result: TextEdit[] describing the modification to the document. - error: code and message set in case an exception happens during the range - formatting request. - -Registration Options: DocumentOnTypeFormattingRegistrationOptions defined as follows: - -export interface DocumentOnTypeFormattingRegistrationOptions extends TextDocumentRegistrationOptions { - /** - * A character on which formatting should be triggered, like `}`. - */ - firstTriggerCharacter: string; - /** - * More trigger characters. - */ - moreTriggerCharacter?: string[] -} --} - -data DocumentOnTypeFormattingParams = - DocumentOnTypeFormattingParams - { _textDocument :: TextDocumentIdentifier - , _position :: Position - , _ch :: Text - , _options :: FormattingOptions - } deriving (Read,Show,Eq) - -deriveJSON lspOptions ''DocumentOnTypeFormattingParams - -type DocumentOnTypeFormattingRequest = RequestMessage ClientMethod DocumentOnTypeFormattingParams (List TextEdit) -type DocumentOnTypeFormattingResponse = ResponseMessage (List TextEdit) - -data DocumentOnTypeFormattingRegistrationOptions = - DocumentOnTypeFormattingRegistrationOptions - { _firstTriggerCharacter :: Text - , _moreTriggerCharacter :: Maybe (List String) - } deriving (Show, Read, Eq) - -deriveJSON lspOptions ''DocumentOnTypeFormattingRegistrationOptions - --- --------------------------------------------------------------------- -{- -Rename Request - -https://github.com/Microsoft/language-server-protocol/blob/master/protocol.md#rename-request - -The rename request is sent from the client to the server to perform a -workspace-wide rename of a symbol. - -Request - - method: 'textDocument/rename' - params: RenameParams defined as follows - -interface RenameParams { - /** - * The document to format. - */ - textDocument: TextDocumentIdentifier; - - /** - * The position at which this request was sent. - */ - position: Position; - - /** - * The new name of the symbol. If the given name is not valid the - * request must return a [ResponseError](#ResponseError) with an - * appropriate message set. - */ - newName: string; -} - -Response - - result: WorkspaceEdit describing the modification to the workspace. - error: code and message set in case an exception happens during the rename - request. - -Registration Options: TextDocumentRegistrationOptions - --} -data RenameParams = - RenameParams - { _textDocument :: TextDocumentIdentifier - , _position :: Position - , _newName :: Text - , _workDoneToken :: Maybe ProgressToken -- ^ An optional token that a server can use to report work done progress. - } deriving (Show, Read, Eq) - -deriveJSON lspOptions ''RenameParams - - --- {\"jsonrpc\":\"2.0\",\"id\":1,\"method\":\"textDocument/rename\",\"params\":{\"textDocument\":{\"uri\":\"file:///home/alanz/mysrc/github/alanz/haskell-lsp/src/HieVscode.hs\"},\"position\":{\"line\":37,\"character\":17},\"newName\":\"getArgs'\"}} - -type RenameRequest = RequestMessage ClientMethod RenameParams WorkspaceEdit -type RenameResponse = ResponseMessage WorkspaceEdit - --- --------------------------------------------------------------------- -{- -Prepare Rename Request - -Since version 3.12.0 - -The prepare rename request is sent from the client to the server to setup -and test the validity of a rename operation at a given location. - -Request: - - method: ‘textDocument/prepareRename’ - params: TextDocumentPositionParams - -Response: - - result: Range | { range: Range, placeholder: string } | null describing - the range of the string to rename and optionally a placeholder - text of the string content to be renamed. If null is returned - then it is deemed that a ‘textDocument/rename’ request is not - valid at the given position. - error: code and message set in case an exception happens during the - prepare rename request. - --} - --- {\"jsonrpc\":\"2.0\",\"id\":1,\"method\":\"textDocument/rename\",\"params\":{\"textDocument\":{\"uri\":\"file:///home/alanz/mysrc/github/alanz/haskell-lsp/src/HieVscode.hs\"},\"position\":{\"line\":37,\"character\":17},\"newName\":\"getArgs'\"}} - -data RangeWithPlaceholder = - RangeWithPlaceholder - { - _range :: Range - , _placeholder :: Text - } - -deriveJSON lspOptions { sumEncoding = A.UntaggedValue } ''RangeWithPlaceholder - -data RangeOrRangeWithPlaceholder = RangeWithPlaceholderValue RangeWithPlaceholder - | RangeValue Range - -deriveJSON lspOptions { sumEncoding = A.UntaggedValue } ''RangeOrRangeWithPlaceholder - -type PrepareRenameRequest = RequestMessage ClientMethod TextDocumentPositionParams Range -type PrepareRenameResponse = ResponseMessage (Maybe RangeOrRangeWithPlaceholder) - --- --------------------------------------------------------------------- -{- -New in 3.0 ----------- - -Execute a command - -The workspace/executeCommand request is sent from the client to the server to -trigger command execution on the server. In most cases the server creates a -WorkspaceEdit structure and applies the changes to the workspace using the -request workspace/applyEdit which is sent from the server to the client. - -Request: - - method: 'workspace/executeCommand' - params: ExecuteCommandParams defined as follows: - -export interface ExecuteCommandParams { - - /** - * The identifier of the actual command handler. - */ - command: string; - /** - * Arguments that the command should be invoked with. - */ - arguments?: any[]; -} - -The arguments are typically specified when a command is returned from the server -to the client. Example requests that return a command are -textDocument/codeAction or textDocument/codeLens. - -Response: - - result: any - error: code and message set in case an exception happens during the request. - -Registration Options: ExecuteCommandRegistrationOptions defined as follows: - -/** - * Execute command registration options. - */ -export interface ExecuteCommandRegistrationOptions { - /** - * The commands to be executed on the server - */ - commands: string[] -} --} - -data ExecuteCommandParams = - ExecuteCommandParams - { _command :: Text -- ^ The identifier of the actual command handler. - , _arguments :: Maybe (List A.Value) -- ^ Arguments that the command should be invoked with. - , _workDoneToken :: Maybe ProgressToken -- ^ An optional token that a server can use to report work done progress. - } deriving (Show, Read, Eq) - -deriveJSON lspOptions ''ExecuteCommandParams - -type ExecuteCommandRequest = RequestMessage ClientMethod ExecuteCommandParams A.Value -type ExecuteCommandResponse = ResponseMessage A.Value - -data ExecuteCommandRegistrationOptions = - ExecuteCommandRegistrationOptions - { _commands :: List Text - } deriving (Show, Read, Eq) - -deriveJSON lspOptions ''ExecuteCommandRegistrationOptions - --- --------------------------------------------------------------------- -{- -New in 3.0 ----------- - -Applies a WorkspaceEdit - -The workspace/applyEdit request is sent from the server to the client to modify -resource on the client side. - -Request: - - method: 'workspace/applyEdit' - params: ApplyWorkspaceEditParams defined as follows: - -export interface ApplyWorkspaceEditParams { - /** - * The edits to apply. - */ - edit: WorkspaceEdit; -} - -Response: - - result: ApplyWorkspaceEditResponse defined as follows: - -export interface ApplyWorkspaceEditResponse { - /** - * Indicates whether the edit was applied or not. - */ - applied: boolean; -} - - error: code and message set in case an exception happens during the request. - --} -data ApplyWorkspaceEditParams = - ApplyWorkspaceEditParams - { _edit :: WorkspaceEdit - } deriving (Show, Read, Eq) - -deriveJSON lspOptions ''ApplyWorkspaceEditParams - -data ApplyWorkspaceEditResponseBody = - ApplyWorkspaceEditResponseBody - { _applied :: Bool - } deriving (Show, Read, Eq) - -deriveJSON lspOptions ''ApplyWorkspaceEditResponseBody - --- | Sent from the server to the client -type ApplyWorkspaceEditRequest = RequestMessage ServerMethod ApplyWorkspaceEditParams ApplyWorkspaceEditResponseBody -type ApplyWorkspaceEditResponse = ResponseMessage ApplyWorkspaceEditResponseBody - --- %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% - --- --------------------------------------------------------------------- - -data TraceParams = - TraceParams { - _value :: Text - } deriving (Show, Read, Eq) - -deriveJSON lspOptions ''TraceParams - - -data TraceNotification = - TraceNotification { - _params :: TraceParams - } deriving (Show, Read, Eq) - -deriveJSON lspOptions ''TraceNotification diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/Declaration.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Declaration.hs new file mode 100644 index 000000000..7fcd88953 --- /dev/null +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Declaration.hs @@ -0,0 +1,39 @@ +{-# LANGUAGE DuplicateRecordFields #-} +{-# LANGUAGE TemplateHaskell #-} + +module Language.Haskell.LSP.Types.Declaration where + +import Data.Aeson.TH +import Language.Haskell.LSP.Types.Progress +import Language.Haskell.LSP.Types.StaticRegistrationOptions +import Language.Haskell.LSP.Types.TextDocument +import Language.Haskell.LSP.Types.Utils + +data DeclarationClientCapabilities = + DeclarationClientCapabilities + { -- | Whether declaration supports dynamic registration. If this is set to 'true' + -- the client supports the new 'DeclarationRegistrationOptions' return value + -- for the corresponding server capability as well. + _dynamicRegistration :: Maybe Bool + -- | The client supports additional metadata in the form of declaration links. + , _linkSupport :: Maybe Bool + } + deriving (Read, Show, Eq) +deriveJSON lspOptions ''DeclarationClientCapabilities + +makeExtendingDatatype "DeclarationOptions" [''WorkDoneProgressOptions] [] +deriveJSON lspOptions ''DeclarationOptions + +makeExtendingDatatype "DeclarationRegistrationOptions" + [ ''DeclarationOptions + , ''TextDocumentRegistrationOptions + , ''StaticRegistrationOptions + ] [] +deriveJSON lspOptions ''DeclarationRegistrationOptions + +makeExtendingDatatype "DeclarationParams" + [ ''TextDocumentPositionParams + , ''WorkDoneProgressParams + , ''PartialResultParams + ] [] +deriveJSON lspOptions ''DeclarationParams diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/Definition.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Definition.hs new file mode 100644 index 000000000..7ae9b2cec --- /dev/null +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Definition.hs @@ -0,0 +1,36 @@ +{-# LANGUAGE DuplicateRecordFields #-} +{-# LANGUAGE TemplateHaskell #-} + +module Language.Haskell.LSP.Types.Definition where + +import Data.Aeson.TH +import Language.Haskell.LSP.Types.Progress +import Language.Haskell.LSP.Types.TextDocument +import Language.Haskell.LSP.Types.Utils + +data DefinitionClientCapabilities = + DefinitionClientCapabilities + { -- | Whether definition supports dynamic registration. + _dynamicRegistration :: Maybe Bool + -- | The client supports additional metadata in the form of definition + -- links. + -- Since LSP 3.14.0 + , _linkSupport :: Maybe Bool + } deriving (Show, Read, Eq) +deriveJSON lspOptions ''DefinitionClientCapabilities + +makeExtendingDatatype "DefinitionOptions" [''WorkDoneProgressOptions] [] +deriveJSON lspOptions ''DefinitionOptions + +makeExtendingDatatype "DefinitionRegistrationOptions" + [ ''TextDocumentRegistrationOptions + , ''DefinitionOptions + ] [] +deriveJSON lspOptions ''DefinitionRegistrationOptions + +makeExtendingDatatype "DefinitionParams" + [ ''TextDocumentPositionParams + , ''WorkDoneProgressParams + , ''PartialResultParams + ] [] +deriveJSON lspOptions ''DefinitionParams diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/Diagnostic.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Diagnostic.hs index 3af203ed9..6cbc13000 100644 --- a/haskell-lsp-types/src/Language/Haskell/LSP/Types/Diagnostic.hs +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Diagnostic.hs @@ -1,42 +1,22 @@ {-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE TypeOperators #-} module Language.Haskell.LSP.Types.Diagnostic where import Control.DeepSeq import qualified Data.Aeson as A import Data.Aeson.TH -import Data.Scientific import Data.Text import GHC.Generics -import Language.Haskell.LSP.Types.Constants -import Language.Haskell.LSP.Types.List +import Language.Haskell.LSP.Types.Common import Language.Haskell.LSP.Types.Location +import Language.Haskell.LSP.Types.Uri +import Language.Haskell.LSP.Types.Utils -- --------------------------------------------------------------------- -{- -The protocol currently supports the following diagnostic severities: - -enum DiagnosticSeverity { - /** - * Reports an error. - */ - Error = 1, - /** - * Reports a warning. - */ - Warning = 2, - /** - * Reports an information. - */ - Information = 3, - /** - * Reports a hint. - */ - Hint = 4 -} --} + data DiagnosticSeverity = DsError -- ^ Error = 1, | DsWarning -- ^ Warning = 2, @@ -59,25 +39,6 @@ instance A.FromJSON DiagnosticSeverity where parseJSON (A.Number 4) = pure DsHint parseJSON _ = mempty -{- -The diagnostic tags. - -export namespace DiagnosticTag { - /** - * Unused or unnecessary code. - * - * Clients are allowed to render diagnostics with this tag faded out instead of having - * an error squiggle. - */ - export const Unnecessary: 1; - /** - * Deprecated or obsolete code. - * - * Clients are allowed to rendered diagnostics with this tag strike through. - */ - export const Deprecated: 2; -} --} data DiagnosticTag -- | Unused or unnecessary code. -- @@ -103,23 +64,6 @@ instance A.FromJSON DiagnosticTag where parseJSON _ = mempty -- --------------------------------------------------------------------- -{- -Represents a related message and source code location for a diagnostic. This should be -used to point to code locations that cause or related to a diagnostics, e.g when duplicating -a symbol in a scope. - -export interface DiagnosticRelatedInformation { - /** - * The location of this related diagnostic information. - */ - location: Location; - - /** - * The message of this related diagnostic information. - */ - message: string; -} --} data DiagnosticRelatedInformation = DiagnosticRelatedInformation @@ -132,72 +76,13 @@ instance NFData DiagnosticRelatedInformation deriveJSON lspOptions ''DiagnosticRelatedInformation -- --------------------------------------------------------------------- -{- -Diagnostic - -https://github.com/Microsoft/language-server-protocol/blob/master/protocol.md#diagnostic - -Represents a diagnostic, such as a compiler error or warning. Diagnostic objects -are only valid in the scope of a resource. - -interface Diagnostic { - /** - * The range at which the message applies. - */ - range: Range; - - /** - * The diagnostic's severity. Can be omitted. If omitted it is up to the - * client to interpret diagnostics as error, warning, info or hint. - */ - severity?: number; - - /** - * The diagnostic's code. Can be omitted. - */ - code?: number | string; - - /** - * A human-readable string describing the source of this - * diagnostic, e.g. 'typescript' or 'super lint'. - */ - source?: string; - - /** - * The diagnostic's message. - */ - message: string; - - /** - * Additional metadata about the diagnostic. - * - * @since 3.15.0 - */ - tags?: DiagnosticTag[]; - - /** - * An array of related diagnostic information, e.g. when symbol-names within - * a scope collide all definitions can be marked via this property. - */ - relatedInformation?: DiagnosticRelatedInformation[]; -} --} - -data NumberOrString = - NumberValue Scientific - | StringValue Text - deriving (Show, Read, Eq, Ord, Generic) - -instance NFData NumberOrString - -deriveJSON lspOptions { sumEncoding = A.UntaggedValue } ''NumberOrString type DiagnosticSource = Text data Diagnostic = Diagnostic { _range :: Range , _severity :: Maybe DiagnosticSeverity - , _code :: Maybe NumberOrString + , _code :: Maybe (Int |? String) , _source :: Maybe DiagnosticSource , _message :: Text , _tags :: Maybe (List DiagnosticTag) @@ -207,3 +92,48 @@ data Diagnostic = instance NFData Diagnostic deriveJSON lspOptions ''Diagnostic + +-- ------------------------------------- + +data PublishDiagnosticsTagsClientCapabilities = + PublishDiagnosticsTagsClientCapabilities + { -- | The tags supported by the client. + _valueSet :: List DiagnosticTag + } deriving (Show, Read, Eq) + +deriveJSON lspOptions ''PublishDiagnosticsTagsClientCapabilities + +data PublishDiagnosticsClientCapabilities = + PublishDiagnosticsClientCapabilities + { -- | Whether the clients accepts diagnostics with related information. + _relatedInformation :: Maybe Bool + -- | Client supports the tag property to provide metadata about a + -- diagnostic. + -- + -- Clients supporting tags have to handle unknown tags gracefully. + -- + -- Since LSP 3.15.0 + , _tagSupport :: Maybe PublishDiagnosticsTagsClientCapabilities + -- | Whether the client interprets the version property of the + -- @textDocument/publishDiagnostics@ notification's parameter. + -- + -- Since LSP 3.15.0 + , _versionSupport :: Maybe Bool + } deriving (Show, Read, Eq) + +deriveJSON lspOptions ''PublishDiagnosticsClientCapabilities + +data PublishDiagnosticsParams = + PublishDiagnosticsParams + { -- | The URI for which diagnostic information is reported. + _uri :: Uri + -- | Optional the version number of the document the diagnostics are + -- published for. + -- + -- Since LSP 3.15.0 + , _version :: Maybe Int + -- | An array of diagnostic information items. + , _diagnostics :: List Diagnostic + } deriving (Read,Show,Eq) + +deriveJSON lspOptions ''PublishDiagnosticsParams diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/DocumentColor.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/DocumentColor.hs new file mode 100644 index 000000000..827367076 --- /dev/null +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/DocumentColor.hs @@ -0,0 +1,91 @@ +{-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE DuplicateRecordFields #-} +module Language.Haskell.LSP.Types.DocumentColor where + +import Data.Aeson.TH +import Data.Text (Text) +import Language.Haskell.LSP.Types.Common +import Language.Haskell.LSP.Types.Location +import Language.Haskell.LSP.Types.Progress +import Language.Haskell.LSP.Types.StaticRegistrationOptions +import Language.Haskell.LSP.Types.TextDocument +import Language.Haskell.LSP.Types.Utils +import Language.Haskell.LSP.Types.WorkspaceEdit + +data DocumentColorClientCapabilities = + DocumentColorClientCapabilities + { -- | Whether document color supports dynamic registration. + _dynamicRegistration :: Maybe Bool + } deriving (Read, Show, Eq) +deriveJSON lspOptions ''DocumentColorClientCapabilities + +-- ------------------------------------- + +makeExtendingDatatype "DocumentColorOptions" [''WorkDoneProgressOptions] [] +deriveJSON lspOptions ''DocumentColorOptions + +makeExtendingDatatype "DocumentColorRegistrationOptions" + [ ''TextDocumentRegistrationOptions + , ''StaticRegistrationOptions + , ''DocumentColorOptions + ] [] +deriveJSON lspOptions ''DocumentColorRegistrationOptions + +-- ------------------------------------- + +makeExtendingDatatype "DocumentColorParams" + [ ''WorkDoneProgressParams + , ''PartialResultParams + ] + [("_textDocument", [t| TextDocumentIdentifier |])] +deriveJSON lspOptions ''DocumentColorParams + +-- ------------------------------------- + +-- | Represents a color in RGBA space. +data Color = + Color + { _red :: Int -- ^ The red component of this color in the range [0-1]. + , _green :: Int -- ^ The green component of this color in the range [0-1]. + , _blue :: Int -- ^ The blue component of this color in the range [0-1]. + , _alpha :: Int -- ^ The alpha component of this color in the range [0-1]. + } deriving (Read, Show, Eq) +deriveJSON lspOptions ''Color + +data ColorInformation = + ColorInformation + { _range :: Range -- ^ The range in the document where this color appears. + , _color :: Color -- ^ The actual color value for this color range. + } deriving (Read, Show, Eq) +deriveJSON lspOptions ''ColorInformation + +-- ------------------------------------- + +makeExtendingDatatype "ColorPresentationParams" + [ ''WorkDoneProgressParams + , ''PartialResultParams + ] + [ ("_textDocument", [t| TextDocumentIdentifier |]) + , ("_color", [t| Color |]) + , ("_range", [t| Range |]) + ] +deriveJSON lspOptions ''ColorPresentationParams + +-- ------------------------------------- + +data ColorPresentation = + ColorPresentation + { -- | The label of this color presentation. It will be shown on the color + -- picker header. By default this is also the text that is inserted when selecting + -- this color presentation. + _label :: Text + -- | A 'TextEdit' which is applied to a document when selecting + -- this presentation for the color. When `falsy` the '_label' + -- is used. + , _textEdit :: Maybe TextEdit + -- | An optional array of additional 'TextEdit's that are applied when + -- selecting this color presentation. Edits must not overlap with the main + -- '_textEdit' nor with themselves. + , _additionalTextEdits :: Maybe (List TextEdit) + } deriving (Read, Show, Eq) +deriveJSON lspOptions ''ColorPresentation diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/DocumentFilter.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/DocumentFilter.hs index 96331b475..ce5de929c 100644 --- a/haskell-lsp-types/src/Language/Haskell/LSP/Types/DocumentFilter.hs +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/DocumentFilter.hs @@ -3,46 +3,27 @@ module Language.Haskell.LSP.Types.DocumentFilter where import Data.Aeson.TH import Data.Text ( Text ) -import Language.Haskell.LSP.Types.Constants -import Language.Haskell.LSP.Types.List +import Language.Haskell.LSP.Types.Common +import Language.Haskell.LSP.Types.Utils -- --------------------------------------------------------------------- -{- -New in 3.0 ----------- - -DocumentFilter -https://github.com/Microsoft/language-server-protocol/blob/master/protocol.md#new-documentfilter - -A document filter denotes a document through properties like language, schema or -pattern. Examples are a filter that applies to TypeScript files on disk or a -filter the applies to JSON files with name package.json: - - { language: 'typescript', scheme: 'file' } - { language: 'json', pattern: '**/package.json' } -export interface DocumentFilter { - /** - * A language id, like `typescript`. - */ - language?: string; - - /** - * A Uri [scheme](#Uri.scheme), like `file` or `untitled`. - */ - scheme?: string; - - /** - * A glob pattern, like `*.{ts,js}`. - */ - pattern?: string; -} --} data DocumentFilter = DocumentFilter - { _language :: Maybe Text + { -- | A language id, like `typescript`. + _language :: Maybe Text + -- | A Uri scheme, like @file@ or @untitled@. , _scheme :: Maybe Text - , _pattern :: Maybe Text + , -- | A glob pattern, like `*.{ts,js}`. + -- + -- Glob patterns can have the following syntax: + -- - @*@ to match one or more characters in a path segment + -- - @?@ to match on one character in a path segment + -- - @**@ to match any number of path segments, including none + -- - @{}@ to group conditions (e.g. @**​/*.{ts,js}@ matches all TypeScript and JavaScript files) + -- - @[]@ to declare a range of characters to match in a path segment (e.g., @example.[0-9]@ to match on @example.0@, @example.1@, …) + -- - @[!...]@ to negate a range of characters to match in a path segment (e.g., @example.[!0-9]@ to match on @example.a@, @example.b@, but not @example.0@) + _pattern :: Maybe Text } deriving (Show, Read, Eq) deriveJSON lspOptions ''DocumentFilter diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/DocumentHighlight.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/DocumentHighlight.hs new file mode 100644 index 000000000..9ebc11e07 --- /dev/null +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/DocumentHighlight.hs @@ -0,0 +1,71 @@ +{-# LANGUAGE DuplicateRecordFields #-} +{-# LANGUAGE TemplateHaskell #-} +module Language.Haskell.LSP.Types.DocumentHighlight where + +import Data.Aeson +import Data.Aeson.TH +import Language.Haskell.LSP.Types.Location +import Language.Haskell.LSP.Types.Progress +import Language.Haskell.LSP.Types.TextDocument +import Language.Haskell.LSP.Types.Utils + +-- ------------------------------------- + +data DocumentHighlightClientCapabilities = + DocumentHighlightClientCapabilities + { -- | Whether document highlight supports dynamic registration. + _dynamicRegistration :: Maybe Bool + } deriving (Show, Read, Eq) + +deriveJSON lspOptions ''DocumentHighlightClientCapabilities + +makeExtendingDatatype "DocumentHighlightOptions" [''WorkDoneProgressOptions] [] +deriveJSON lspOptions ''DocumentHighlightOptions + +makeExtendingDatatype "DocumentHighlightRegistrationOptions" + [ ''TextDocumentRegistrationOptions + , ''DocumentHighlightOptions + ] [] +deriveJSON lspOptions ''DocumentHighlightRegistrationOptions + +makeExtendingDatatype "DocumentHighlightParams" + [ ''TextDocumentPositionParams + , ''WorkDoneProgressParams + , ''PartialResultParams + ] [] +deriveJSON lspOptions ''DocumentHighlightParams + +data DocumentHighlightKind + = -- | A textual occurrence. + HkText + | -- | Read-access of a symbol, like reading a variable. + HkRead + | -- | Write-access of a symbol, like writing to a variable. + HkWrite + deriving (Read, Show, Eq) + +instance ToJSON DocumentHighlightKind where + toJSON HkText = Number 1 + toJSON HkRead = Number 2 + toJSON HkWrite = Number 3 + +instance FromJSON DocumentHighlightKind where + parseJSON (Number 1) = pure HkText + parseJSON (Number 2) = pure HkRead + parseJSON (Number 3) = pure HkWrite + parseJSON _ = mempty + +-- ------------------------------------- + +-- | A document highlight is a range inside a text document which deserves +-- special attention. Usually a document highlight is visualized by changing the +-- background color of its range. +data DocumentHighlight = + DocumentHighlight + { -- | The range this highlight applies to. + _range :: Range + -- | The highlight kind, default is 'HkText'. + , _kind :: Maybe DocumentHighlightKind + } deriving (Read,Show,Eq) + +deriveJSON lspOptions ''DocumentHighlight diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/DocumentLink.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/DocumentLink.hs new file mode 100644 index 000000000..8a8532a27 --- /dev/null +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/DocumentLink.hs @@ -0,0 +1,70 @@ +{-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE DuplicateRecordFields #-} + +module Language.Haskell.LSP.Types.DocumentLink where + +import Data.Aeson +import Data.Aeson.TH +import Language.Haskell.LSP.Types.Location +import Language.Haskell.LSP.Types.Progress +import Language.Haskell.LSP.Types.TextDocument +import Language.Haskell.LSP.Types.Uri +import Language.Haskell.LSP.Types.Utils + +data DocumentLinkClientCapabilities = + DocumentLinkClientCapabilities + { -- | Whether document link supports dynamic registration. + _dynamicRegistration :: Maybe Bool + -- | Whether the client supports the `tooltip` property on `DocumentLink`. + -- + -- Since LSP 3.15.0 + , _tooltipSupport :: Maybe Bool + } deriving (Read, Show, Eq) +deriveJSON lspOptions ''DocumentLinkClientCapabilities + +-- ------------------------------------- + +makeExtendingDatatype "DocumentLinkOptions" [''WorkDoneProgressOptions] + [("_resolveProvider", [t| Maybe Bool |])] +deriveJSON lspOptions ''DocumentLinkOptions + +makeExtendingDatatype "DocumentLinkRegistrationOptions" + [ ''TextDocumentRegistrationOptions + , ''DocumentLinkOptions + ] [] +deriveJSON lspOptions ''DocumentLinkRegistrationOptions + +-- ------------------------------------- + +makeExtendingDatatype "DocumentLinkParams" + [ ''WorkDoneProgressParams + , ''PartialResultParams + ] + [("_textDocument", [t| TextDocumentIdentifier |])] +deriveJSON lspOptions ''DocumentLinkParams + +-- ------------------------------------- + +-- | A document link is a range in a text document that links to an internal or +-- external resource, like another text document or a web site. +data DocumentLink = + DocumentLink + { -- | The range this link applies to. + _range :: Range + -- | The uri this link points to. If missing a resolve request is sent + -- later. + , _target :: Maybe Uri + -- | The tooltip text when you hover over this link. + -- + -- If a tooltip is provided, is will be displayed in a string that includes + -- instructions on how to trigger the link, such as @{0} (ctrl + click)@. + -- The specific instructions vary depending on OS, user settings, and + -- localization. + -- + -- Since LSP 3.15.0 + , _tooltip :: Maybe String + -- | A data entry field that is preserved on a document link between a + -- DocumentLinkRequest and a DocumentLinkResolveRequest. + , _xdata :: Maybe Value + } deriving (Read, Show, Eq) +deriveJSON lspOptions ''DocumentLink diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/Symbol.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/DocumentSymbol.hs similarity index 69% rename from haskell-lsp-types/src/Language/Haskell/LSP/Types/Symbol.hs rename to haskell-lsp-types/src/Language/Haskell/LSP/Types/DocumentSymbol.hs index feb74bd84..7138af5d9 100644 --- a/haskell-lsp-types/src/Language/Haskell/LSP/Types/Symbol.hs +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/DocumentSymbol.hs @@ -1,111 +1,36 @@ {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE DuplicateRecordFields #-} -module Language.Haskell.LSP.Types.Symbol where +module Language.Haskell.LSP.Types.DocumentSymbol where -import Control.Applicative import Data.Aeson import Data.Aeson.TH import Data.Scientific import Data.Text (Text) -import Language.Haskell.LSP.Types.Constants + import Language.Haskell.LSP.Types.TextDocument -import Language.Haskell.LSP.Types.List +import Language.Haskell.LSP.Types.Common import Language.Haskell.LSP.Types.Location -import Language.Haskell.LSP.Types.Message import Language.Haskell.LSP.Types.Progress +import Language.Haskell.LSP.Types.Utils -- --------------------------------------------------------------------- -{- -Document Symbols Request - -https://github.com/Microsoft/language-server-protocol/blob/master/protocol.md#document-symbols-request - -The document symbol request is sent from the client to the server to list all -symbols found in a given text document. - - Changed: In 2.0 the request uses DocumentSymbolParams instead of a single - uri. - -Request - - method: 'textDocument/documentSymbol' - params: DocumentSymbolParams defined as follows: - -interface DocumentSymbolParams { - /** - * The text document. - */ - textDocument: TextDocumentIdentifier; -} - -Response - - result: SymbolInformation[] defined as follows: - -/** - * Represents information about programming constructs like variables, classes, - * interfaces etc. - */ -interface SymbolInformation { - /** - * The name of this symbol. - */ - name: string; - - /** - * The kind of this symbol. - */ - kind: number; - - /** - * The location of this symbol. - */ - location: Location; - - /** - * The name of the symbol containing this symbol. - */ - containerName?: string; -} - -Where the kind is defined like this: -/** - * A symbol kind. - */ -export enum SymbolKind { - File = 1, - Module = 2, - Namespace = 3, - Package = 4, - Class = 5, - Method = 6, - Property = 7, - Field = 8, - Constructor = 9, - Enum = 10, - Interface = 11, - Function = 12, - Variable = 13, - Constant = 14, - Text = 15, - Number = 16, - Boolean = 17, - Array = 18, -} +makeExtendingDatatype "DocumentSymbolOptions" [''WorkDoneProgressOptions] [] +deriveJSON lspOptions ''DocumentSymbolOptions - error: code and message set in case an exception happens during the document - symbol request. +makeExtendingDatatype "DocumentSymbolRegistrationOptions" + [ ''TextDocumentRegistrationOptions + , ''DocumentSymbolOptions + ] [] +deriveJSON lspOptions ''DocumentSymbolRegistrationOptions -Registration Options: TextDocumentRegistrationOptions --} - -data DocumentSymbolParams = - DocumentSymbolParams - { _textDocument :: TextDocumentIdentifier - , _workDoneToken :: Maybe ProgressToken -- ^ An optional token that a server can use to report work done progress. - } deriving (Read,Show,Eq) +-- --------------------------------------------------------------------- +makeExtendingDatatype "DocumentSymbolParams" + [ ''WorkDoneProgressParams + , ''PartialResultParams + ] + [ ("_textDocument", [t| TextDocumentIdentifier |])] deriveJSON lspOptions ''DocumentSymbolParams -- ------------------------------------- @@ -198,6 +123,36 @@ instance FromJSON SymbolKind where parseJSON (Number 26) = pure SkTypeParameter parseJSON (Number x) = pure (SkUnknown x) parseJSON _ = mempty + +-- ------------------------------------- + +data DocumentSymbolKindClientCapabilities = + DocumentSymbolKindClientCapabilities + { -- | The symbol kind values the client supports. When this + -- property exists the client also guarantees that it will + -- handle values outside its set gracefully and falls back + -- to a default value when unknown. + -- + -- If this property is not present the client only supports + -- the symbol kinds from `File` to `Array` as defined in + -- the initial version of the protocol. + _valueSet :: Maybe (List SymbolKind) + } + deriving (Show, Read, Eq) + +deriveJSON lspOptions ''DocumentSymbolKindClientCapabilities + +data DocumentSymbolClientCapabilities = + DocumentSymbolClientCapabilities + { -- | Whether document symbol supports dynamic registration. + _dynamicRegistration :: Maybe Bool + -- | Specific capabilities for the `SymbolKind`. + , _symbolKind :: Maybe DocumentSymbolKindClientCapabilities + , _hierarchicalDocumentSymbolSupport :: Maybe Bool + } deriving (Show, Read, Eq) + +deriveJSON lspOptions ''DocumentSymbolClientCapabilities + -- --------------------------------------------------------------------- @@ -254,20 +209,3 @@ data SymbolInformation = } deriving (Read,Show,Eq) deriveJSON lspOptions ''SymbolInformation - --- ------------------------------------- - -data DSResult = DSDocumentSymbols (List DocumentSymbol) - | DSSymbolInformation (List SymbolInformation) - deriving (Read,Show,Eq) - -instance FromJSON DSResult where - parseJSON x = DSDocumentSymbols <$> parseJSON x <|> DSSymbolInformation <$> parseJSON x - -instance ToJSON DSResult where - toJSON (DSDocumentSymbols x) = toJSON x - toJSON (DSSymbolInformation x) = toJSON x - - -type DocumentSymbolRequest = RequestMessage ClientMethod DocumentSymbolParams DSResult -type DocumentSymbolsResponse = ResponseMessage DSResult diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/FoldingRange.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/FoldingRange.hs index 6ca93076c..0019dae61 100644 --- a/haskell-lsp-types/src/Language/Haskell/LSP/Types/FoldingRange.hs +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/FoldingRange.hs @@ -1,23 +1,53 @@ {-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE TemplateHaskell #-} module Language.Haskell.LSP.Types.FoldingRange where import qualified Data.Aeson as A import Data.Aeson.TH import Data.Text (Text) -import Language.Haskell.LSP.Types.Constants -import Language.Haskell.LSP.Types.List import Language.Haskell.LSP.Types.Progress +import Language.Haskell.LSP.Types.StaticRegistrationOptions import Language.Haskell.LSP.Types.TextDocument -import Language.Haskell.LSP.Types.Message +import Language.Haskell.LSP.Types.Utils -data FoldingRangeParams = - FoldingRangeParams - { _textDocument :: TextDocumentIdentifier -- ^ The text document. - , _workDoneToken :: Maybe ProgressToken -- ^ An optional token that a server can use to report work done progress. - } - deriving (Read, Show, Eq) +-- ------------------------------------- + +data FoldingRangeClientCapabilities = + FoldingRangeClientCapabilities + { -- | Whether implementation supports dynamic registration for folding range + -- providers. If this is set to `true` the client supports the new + -- `(FoldingRangeProviderOptions & TextDocumentRegistrationOptions & StaticRegistrationOptions)` + -- return value for the corresponding server capability as well. + _dynamicRegistration :: Maybe Bool + -- | The maximum number of folding ranges that the client prefers to receive + -- per document. The value serves as a hint, servers are free to follow the limit. + , _rangeLimit :: Maybe Int + -- | If set, the client signals that it only supports folding complete lines. If set, + -- client will ignore specified `startCharacter` and `endCharacter` properties in a + -- FoldingRange. + , _lineFoldingOnly :: Maybe Bool + } deriving (Show, Read, Eq) + +deriveJSON lspOptions ''FoldingRangeClientCapabilities + +makeExtendingDatatype "FoldingRangeOptions" [''WorkDoneProgressOptions] [] +deriveJSON lspOptions ''FoldingRangeOptions + +makeExtendingDatatype "FoldingRangeRegistrationOptions" + [ ''TextDocumentRegistrationOptions + , ''FoldingRangeOptions + , ''StaticRegistrationOptions + ] [] +deriveJSON lspOptions ''FoldingRangeRegistrationOptions + + +makeExtendingDatatype "FoldingRangeParams" + [ ''WorkDoneProgressParams + , ''PartialResultParams + ] + [("_textDocument", [t| TextDocumentIdentifier |])] deriveJSON lspOptions ''FoldingRangeParams -- | Enum of known range kinds @@ -67,6 +97,3 @@ data FoldingRange = deriving (Read, Show, Eq) deriveJSON lspOptions ''FoldingRange - -type FoldingRangeRequest = RequestMessage ClientMethod FoldingRangeParams (List FoldingRange) -type FoldingRangeResponse = ResponseMessage (List FoldingRange) diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/Formatting.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Formatting.hs new file mode 100644 index 000000000..284de0c0d --- /dev/null +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Formatting.hs @@ -0,0 +1,113 @@ +{-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE DuplicateRecordFields #-} +module Language.Haskell.LSP.Types.Formatting where + +import Data.Aeson.TH +import Data.Text (Text) +import Language.Haskell.LSP.Types.Location +import Language.Haskell.LSP.Types.Progress +import Language.Haskell.LSP.Types.TextDocument +import Language.Haskell.LSP.Types.Utils + +data DocumentFormattingClientCapabilities = + DocumentFormattingClientCapabilities + { -- | Whether formatting supports dynamic registration. + _dynamicRegistration :: Maybe Bool + } deriving (Show, Read, Eq) +deriveJSON lspOptions ''DocumentFormattingClientCapabilities + +makeExtendingDatatype "DocumentFormattingOptions" [''WorkDoneProgressOptions] [] +deriveJSON lspOptions ''DocumentFormattingOptions + +makeExtendingDatatype "DocumentFormattingRegistrationOptions" + [ ''TextDocumentRegistrationOptions, + ''DocumentFormattingOptions + ] + [] +deriveJSON lspOptions ''DocumentFormattingRegistrationOptions + +-- | Value-object describing what options formatting should use. +data FormattingOptions = FormattingOptions + { -- | Size of a tab in spaces. + _tabSize :: Int, + -- | Prefer spaces over tabs + _insertSpaces :: Bool, + -- | Trim trailing whitespace on a line. + -- + -- Since LSP 3.15.0 + _trimTrailingWhitespace :: Maybe Bool, + -- | Insert a newline character at the end of the file if one does not exist. + -- + -- Since LSP 3.15.0 + _insertFinalNewline :: Maybe Bool, + -- | Trim all newlines after the final newline at the end of the file. + -- + -- Since LSP 3.15.0 + _trimFinalNewlines :: Maybe Bool + -- Note: May be more properties + } + deriving (Read, Show, Eq) + +deriveJSON lspOptions ''FormattingOptions +makeExtendingDatatype "DocumentFormattingParams" [''WorkDoneProgressParams] + [ ("_textDocument", [t| TextDocumentIdentifier |]) + , ("_options", [t| FormattingOptions |]) + ] +deriveJSON lspOptions ''DocumentFormattingParams + +-- ------------------------------------- + +data DocumentRangeFormattingClientCapabilities = + DocumentRangeFormattingClientCapabilities + { -- | Whether formatting supports dynamic registration. + _dynamicRegistration :: Maybe Bool + } deriving (Show, Read, Eq) +deriveJSON lspOptions ''DocumentRangeFormattingClientCapabilities + +makeExtendingDatatype "DocumentRangeFormattingOptions" [''WorkDoneProgressOptions] [] +deriveJSON lspOptions ''DocumentRangeFormattingOptions + +makeExtendingDatatype "DocumentRangeFormattingRegistrationOptions" + [ ''TextDocumentRegistrationOptions + , ''DocumentRangeFormattingOptions + ] + [] +deriveJSON lspOptions ''DocumentRangeFormattingRegistrationOptions + +makeExtendingDatatype "DocumentRangeFormattingParams" [''WorkDoneProgressParams] + [ ("_textDocument", [t| TextDocumentIdentifier |]) + , ("_range", [t| Range |]) + , ("_options", [t| FormattingOptions |]) + ] +deriveJSON lspOptions ''DocumentRangeFormattingParams + +-- ------------------------------------- + +data DocumentOnTypeFormattingClientCapabilities = + DocumentOnTypeFormattingClientCapabilities + { -- | Whether formatting supports dynamic registration. + _dynamicRegistration :: Maybe Bool + } deriving (Show, Read, Eq) +deriveJSON lspOptions ''DocumentOnTypeFormattingClientCapabilities + +data DocumentOnTypeFormattingOptions = + DocumentOnTypeFormattingOptions + { -- | A character on which formatting should be triggered, like @}@. + _firstTriggerCharacter :: Text + , -- | More trigger characters. + _moreTriggerCharacter :: Maybe [Text] + } deriving (Read,Show,Eq) +deriveJSON lspOptions ''DocumentOnTypeFormattingOptions + +makeExtendingDatatype "DocumentOnTypeFormattingRegistrationOptions" + [ ''TextDocumentRegistrationOptions + , ''DocumentOnTypeFormattingOptions + ] + [] +deriveJSON lspOptions ''DocumentOnTypeFormattingRegistrationOptions + +makeExtendingDatatype "DocumentOnTypeFormattingParams" [''TextDocumentPositionParams] + [ ("_ch", [t| String |]) + , ("_options", [t| FormattingOptions |]) + ] +deriveJSON lspOptions ''DocumentOnTypeFormattingParams diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/Hover.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Hover.hs index c46a85251..2ea5d3f6b 100644 --- a/haskell-lsp-types/src/Language/Haskell/LSP/Types/Hover.hs +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Hover.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE CPP #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE DuplicateRecordFields #-} module Language.Haskell.LSP.Types.Hover where @@ -7,38 +6,34 @@ import Control.Applicative import Data.Aeson import Data.Aeson.TH import Data.Text ( Text ) -import Language.Haskell.LSP.Types.Constants -import Language.Haskell.LSP.Types.List + +import Language.Haskell.LSP.Types.Common import Language.Haskell.LSP.Types.Location import Language.Haskell.LSP.Types.MarkupContent -import Language.Haskell.LSP.Types.Message +import Language.Haskell.LSP.Types.Progress import Language.Haskell.LSP.Types.TextDocument +import Language.Haskell.LSP.Types.Utils + --- --------------------------------------------------------------------- +-- ------------------------------------- -{- -/** - * MarkedString can be used to render human readable text. It is either a markdown string - * or a code-block that provides a language and a code snippet. The language identifier - * is semantically equal to the optional language identifier in fenced code blocks in GitHub - * issues. See https://help.github.com/articles/creating-and-highlighting-code-blocks/#syntax-highlighting - * - * The pair of a language and a value is an equivalent to markdown: - * ```${language} - * ${value} - * ``` - * - * Note that markdown strings will be sanitized - that means html will be escaped. -* @deprecated use MarkupContent instead. -*/ -type MarkedString = string | { language: string; value: string }; +data HoverClientCapabilities = + HoverClientCapabilities + { _dynamicRegistration :: Maybe Bool + , _contentFormat :: Maybe (List MarkupKind) + } deriving (Show, Read, Eq) +deriveJSON lspOptions ''HoverClientCapabilities - error: code and message set in case an exception happens during the hover - request. +makeExtendingDatatype "HoverOptions" [''WorkDoneProgressOptions] [] +deriveJSON lspOptions ''HoverOptions -Registration Options: TextDocumentRegistrationOptions +makeExtendingDatatype "HoverRegistrationOptions" [''TextDocumentRegistrationOptions, ''HoverOptions] [] +deriveJSON lspOptions ''HoverRegistrationOptions --} +makeExtendingDatatype "HoverParams" [''TextDocumentPositionParams, ''WorkDoneProgressParams] [] +deriveJSON lspOptions ''HoverParams + +-- ------------------------------------- data LanguageString = LanguageString @@ -61,46 +56,6 @@ instance FromJSON MarkedString where parseJSON (String t) = pure $ PlainString t parseJSON o = CodeString <$> parseJSON o --- --------------------------------------------------------------------- -{- -Hover Request - -The hover request is sent from the client to the server to request hover -information at a given text document position. - - Changed: In 2.0 the request uses TextDocumentPositionParams with a proper - textDocument and position property. In 1.0 the uri of the referenced text - document was inlined into the params object. - -Request - - method: 'textDocument/hover' - params: TextDocumentPositionParams - -Response - - result: Hover | null defined as follows: - - -/** - * The result of a hover request. - */ -interface Hover { - /** - * The hover's content - */ - contents: MarkedString | MarkedString[] | MarkupContent; - - /** - * An optional range is a range inside a text document - * that is used to visualize a hover, e.g. by changing the background color. - */ - range?: Range; -} - --} - - -- ------------------------------------- data HoverContents = @@ -120,19 +75,15 @@ instance FromJSON HoverContents where -- ------------------------------------- -#if __GLASGOW_HASKELL__ >= 804 instance Semigroup HoverContents where - (<>) = mappend -#endif + HoverContents h1 <> HoverContents h2 = HoverContents (h1 `mappend` h2) + HoverContents h1 <> HoverContentsMS (List h2s) = HoverContents (mconcat (h1: (map toMarkupContent h2s))) + HoverContentsMS (List h1s) <> HoverContents h2 = HoverContents (mconcat ((map toMarkupContent h1s) ++ [h2])) + HoverContentsMS (List h1s) <> HoverContentsMS (List h2s) = HoverContentsMS (List (h1s `mappend` h2s)) instance Monoid HoverContents where mempty = HoverContentsMS (List []) - HoverContents h1 `mappend` HoverContents h2 = HoverContents (h1 `mappend` h2) - HoverContents h1 `mappend` HoverContentsMS (List h2s) = HoverContents (mconcat (h1: (map toMarkupContent h2s))) - HoverContentsMS (List h1s) `mappend` HoverContents h2 = HoverContents (mconcat ((map toMarkupContent h1s) ++ [h2])) - HoverContentsMS (List h1s) `mappend` HoverContentsMS (List h2s) = HoverContentsMS (List (h1s `mappend` h2s)) - toMarkupContent :: MarkedString -> MarkupContent toMarkupContent (PlainString s) = unmarkedUpContent s toMarkupContent (CodeString (LanguageString lang s)) = markedUpContent lang s @@ -146,6 +97,3 @@ data Hover = } deriving (Read,Show,Eq) deriveJSON lspOptions ''Hover - -type HoverRequest = RequestMessage ClientMethod TextDocumentPositionParams (Maybe Hover) -type HoverResponse = ResponseMessage (Maybe Hover) diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/Implementation.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Implementation.hs new file mode 100644 index 000000000..4974f88a6 --- /dev/null +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Implementation.hs @@ -0,0 +1,42 @@ +{-# LANGUAGE DuplicateRecordFields #-} +{-# LANGUAGE TemplateHaskell #-} + +module Language.Haskell.LSP.Types.Implementation where + +import Data.Aeson.TH +import Language.Haskell.LSP.Types.Progress +import Language.Haskell.LSP.Types.StaticRegistrationOptions +import Language.Haskell.LSP.Types.TextDocument +import Language.Haskell.LSP.Types.Utils + +data ImplementationClientCapabilities = ImplementationClientCapabilities + { -- | Whether implementation supports dynamic registration. If this is set + -- to 'True' + -- the client supports the new 'ImplementationRegistrationOptions' return + -- value for the corresponding server capability as well. + _dynamicRegistration :: Maybe Bool, + -- | The client supports additional metadata in the form of definition links. + -- + -- Since LSP 3.14.0 + _linkSupport :: Maybe Bool + } + deriving (Read, Show, Eq) + +deriveJSON lspOptions ''ImplementationClientCapabilities + +makeExtendingDatatype "ImplementationOptions" [''WorkDoneProgressOptions] [] +deriveJSON lspOptions ''ImplementationOptions + +makeExtendingDatatype "ImplementationRegistrationOptions" + [ ''TextDocumentRegistrationOptions + , ''ImplementationOptions + , ''StaticRegistrationOptions + ] [] +deriveJSON lspOptions ''ImplementationRegistrationOptions + +makeExtendingDatatype "ImplementationParams" + [ ''TextDocumentPositionParams + , ''WorkDoneProgressParams + , ''PartialResultParams + ] [] +deriveJSON lspOptions ''ImplementationParams diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/Initialize.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Initialize.hs new file mode 100644 index 000000000..87213216d --- /dev/null +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Initialize.hs @@ -0,0 +1,98 @@ +{-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE DuplicateRecordFields #-} + +module Language.Haskell.LSP.Types.Initialize where + +import Data.Aeson +import Data.Aeson.TH +import Data.Text (Text) +import qualified Data.Text as T +import Language.Haskell.LSP.Types.ClientCapabilities +import Language.Haskell.LSP.Types.Common +import Language.Haskell.LSP.Types.Progress +import Language.Haskell.LSP.Types.ServerCapabilities +import Language.Haskell.LSP.Types.Uri +import Language.Haskell.LSP.Types.Utils +import Language.Haskell.LSP.Types.WorkspaceFolders + +data Trace = TraceOff | TraceMessages | TraceVerbose + deriving (Show, Read, Eq) + +instance ToJSON Trace where + toJSON TraceOff = String (T.pack "off") + toJSON TraceMessages = String (T.pack "messages") + toJSON TraceVerbose = String (T.pack "verbose") + +instance FromJSON Trace where + parseJSON (String s) = case T.unpack s of + "off" -> return TraceOff + "messages" -> return TraceMessages + "verbose" -> return TraceVerbose + _ -> mempty + parseJSON _ = mempty + +data ClientInfo = + ClientInfo + { -- | The name of the client as defined by the client. + _name :: Text + -- | The client's version as defined by the client. + , _version :: Maybe Text + } deriving (Show, Read, Eq) +deriveJSON lspOptions ''ClientInfo + +makeExtendingDatatype "InitializeParams" [''WorkDoneProgressParams] + [ ("_processId", [t| Maybe Int|]) + , ("_clientInfo", [t| Maybe ClientInfo |]) + , ("_rootPath", [t| Maybe Text |]) + , ("_rootUri", [t| Maybe Uri |]) + , ("_initializationOptions", [t| Maybe Value |]) + , ("_capabilities", [t| ClientCapabilities |]) + , ("_trace", [t| Maybe Trace |]) + , ("_workspaceFolders", [t| Maybe (List WorkspaceFolder) |]) + ] + +{-# DEPRECATED _rootPath "Use _rootUri" #-} + +deriveJSON lspOptions ''InitializeParams + +data InitializeError = + InitializeError + { _retry :: Bool + } deriving (Read, Show, Eq) + +deriveJSON lspOptions ''InitializeError + +data ServerInfo = + ServerInfo + { -- | The name of the server as defined by the server. + _name :: Text + -- | The server's version as defined by the server. + , _version :: Maybe Text + } deriving (Show, Read, Eq) +deriveJSON lspOptions ''ServerInfo + +data InitializeResult = + InitializeResult + { -- | The capabilities the language server provides. + _capabilities :: ServerCapabilities + -- | Information about the server. + -- Since LSP 3.15.0 + , _serverInfo :: Maybe ServerInfo + } deriving (Show, Read, Eq) + +deriveJSON lspOptions ''InitializeResult + +-- --------------------------------------------------------------------- + +data InitializedParams = + InitializedParams + { + } deriving (Show, Read, Eq) + +instance FromJSON InitializedParams where + parseJSON (Object _) = pure InitializedParams + parseJSON _ = mempty + +instance ToJSON InitializedParams where + toJSON InitializedParams = Object mempty + diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/Lens.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Lens.hs index c91b1c577..673024f5c 100644 --- a/haskell-lsp-types/src/Language/Haskell/LSP/Types/Lens.hs +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Lens.hs @@ -2,61 +2,72 @@ {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FunctionalDependencies #-} +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE GADTs #-} +{-# LANGUAGE UndecidableInstances #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE FlexibleContexts #-} module Language.Haskell.LSP.Types.Lens where +import Language.Haskell.LSP.Types.Cancellation import Language.Haskell.LSP.Types.ClientCapabilities import Language.Haskell.LSP.Types.CodeAction -import Language.Haskell.LSP.Types.Color +import Language.Haskell.LSP.Types.CodeLens +import Language.Haskell.LSP.Types.DocumentColor import Language.Haskell.LSP.Types.Command import Language.Haskell.LSP.Types.Completion -import Language.Haskell.LSP.Types.DataTypesJSON +import Language.Haskell.LSP.Types.Configuration +import Language.Haskell.LSP.Types.Declaration +import Language.Haskell.LSP.Types.Definition import Language.Haskell.LSP.Types.Diagnostic import Language.Haskell.LSP.Types.DocumentFilter +import Language.Haskell.LSP.Types.DocumentHighlight +import Language.Haskell.LSP.Types.DocumentLink import Language.Haskell.LSP.Types.FoldingRange +import Language.Haskell.LSP.Types.Formatting import Language.Haskell.LSP.Types.Hover -import Language.Haskell.LSP.Types.Message +import Language.Haskell.LSP.Types.Implementation +import Language.Haskell.LSP.Types.Initialize import Language.Haskell.LSP.Types.Location -import Language.Haskell.LSP.Types.Symbol +import Language.Haskell.LSP.Types.Progress +import Language.Haskell.LSP.Types.Registration +import Language.Haskell.LSP.Types.References +import Language.Haskell.LSP.Types.Rename +import Language.Haskell.LSP.Types.SignatureHelp +import Language.Haskell.LSP.Types.SelectionRange +import Language.Haskell.LSP.Types.ServerCapabilities +import Language.Haskell.LSP.Types.DocumentSymbol import Language.Haskell.LSP.Types.TextDocument +import Language.Haskell.LSP.Types.TypeDefinition import Language.Haskell.LSP.Types.Window +import Language.Haskell.LSP.Types.WatchedFiles import Language.Haskell.LSP.Types.WorkspaceEdit import Language.Haskell.LSP.Types.WorkspaceFolders +import Language.Haskell.LSP.Types.WorkspaceSymbol +import Language.Haskell.LSP.Types.Message import Control.Lens.TH +-- TODO: This is out of date and very unmantainable, use TH to call all these!! + -- client capabilities makeFieldsNoPrefix ''WorkspaceEditClientCapabilities makeFieldsNoPrefix ''DidChangeConfigurationClientCapabilities -makeFieldsNoPrefix ''DidChangeWatchedFilesClientCapabilities -makeFieldsNoPrefix ''SymbolKindClientCapabilities -makeFieldsNoPrefix ''SymbolClientCapabilities -makeFieldsNoPrefix ''ExecuteClientCapabilities +makeFieldsNoPrefix ''ExecuteCommandClientCapabilities makeFieldsNoPrefix ''WorkspaceClientCapabilities -makeFieldsNoPrefix ''SynchronizationTextDocumentClientCapabilities +makeFieldsNoPrefix ''TextDocumentSyncClientCapabilities makeFieldsNoPrefix ''CompletionItemTagsClientCapabilities makeFieldsNoPrefix ''CompletionItemClientCapabilities makeFieldsNoPrefix ''CompletionItemKindClientCapabilities makeFieldsNoPrefix ''CompletionClientCapabilities makeFieldsNoPrefix ''HoverClientCapabilities -makeFieldsNoPrefix ''SignatureInformationClientCapabilities +makeFieldsNoPrefix ''SignatureHelpSignatureInformation +makeFieldsNoPrefix ''SignatureHelpParameterInformation makeFieldsNoPrefix ''SignatureHelpClientCapabilities makeFieldsNoPrefix ''ReferencesClientCapabilities -makeFieldsNoPrefix ''DocumentHighlightClientCapabilities -makeFieldsNoPrefix ''DocumentSymbolKindClientCapabilities -makeFieldsNoPrefix ''DocumentSymbolClientCapabilities -makeFieldsNoPrefix ''FormattingClientCapabilities -makeFieldsNoPrefix ''RangeFormattingClientCapabilities -makeFieldsNoPrefix ''OnTypeFormattingClientCapabilities makeFieldsNoPrefix ''DefinitionClientCapabilities makeFieldsNoPrefix ''TypeDefinitionClientCapabilities makeFieldsNoPrefix ''ImplementationClientCapabilities -makeFieldsNoPrefix ''CodeActionKindClientCapabilities -makeFieldsNoPrefix ''CodeActionLiteralSupport -makeFieldsNoPrefix ''CodeActionClientCapabilities -makeFieldsNoPrefix ''CodeLensClientCapabilities -makeFieldsNoPrefix ''DocumentLinkClientCapabilities -makeFieldsNoPrefix ''ColorProviderClientCapabilities -makeFieldsNoPrefix ''RenameClientCapabilities makeFieldsNoPrefix ''PublishDiagnosticsClientCapabilities makeFieldsNoPrefix ''PublishDiagnosticsTagsClientCapabilities makeFieldsNoPrefix ''TextDocumentClientCapabilities @@ -64,25 +75,16 @@ makeFieldsNoPrefix ''ClientCapabilities -- --------------------------------------------------------------------- -makeFieldsNoPrefix ''InitializeParams -makeFieldsNoPrefix ''InitializeError makeFieldsNoPrefix ''CompletionOptions makeFieldsNoPrefix ''SignatureHelpOptions -makeFieldsNoPrefix ''CodeLensOptions -makeFieldsNoPrefix ''DocumentOnTypeFormattingOptions -makeFieldsNoPrefix ''DocumentLinkOptions makeFieldsNoPrefix ''ExecuteCommandOptions makeFieldsNoPrefix ''SaveOptions makeFieldsNoPrefix ''TextDocumentSyncOptions -makeFieldsNoPrefix ''WorkspaceFolderOptions -makeFieldsNoPrefix ''WorkspaceOptions -makeFieldsNoPrefix ''InitializeResponseCapabilitiesInner -makeFieldsNoPrefix ''InitializeResponseCapabilities +makeFieldsNoPrefix ''WorkspaceServerCapabilities +makeFieldsNoPrefix ''WorkspaceFoldersServerCapabilities +makeFieldsNoPrefix ''ServerCapabilities makeFieldsNoPrefix ''Registration makeFieldsNoPrefix ''RegistrationParams -makeFieldsNoPrefix ''DidChangeWatchedFilesRegistrationOptions -makeFieldsNoPrefix ''FileSystemWatcher -makeFieldsNoPrefix ''WatchKind makeFieldsNoPrefix ''TextDocumentRegistrationOptions makeFieldsNoPrefix ''Unregistration makeFieldsNoPrefix ''UnregistrationParams @@ -95,39 +97,46 @@ makeFieldsNoPrefix ''DidChangeTextDocumentParams makeFieldsNoPrefix ''TextDocumentChangeRegistrationOptions makeFieldsNoPrefix ''WillSaveTextDocumentParams makeFieldsNoPrefix ''DidSaveTextDocumentParams +makeFieldsNoPrefix ''TextDocumentSaveRegistrationOptions makeFieldsNoPrefix ''DidCloseTextDocumentParams -makeFieldsNoPrefix ''FileEvent -makeFieldsNoPrefix ''DidChangeWatchedFilesParams makeFieldsNoPrefix ''PublishDiagnosticsParams makeFieldsNoPrefix ''LanguageString -makeFieldsNoPrefix ''Hover makeFieldsNoPrefix ''ParameterInformation makeFieldsNoPrefix ''SignatureInformation makeFieldsNoPrefix ''SignatureHelp makeFieldsNoPrefix ''SignatureHelpRegistrationOptions makeFieldsNoPrefix ''ReferenceContext makeFieldsNoPrefix ''ReferenceParams -makeFieldsNoPrefix ''DocumentHighlight -makeFieldsNoPrefix ''WorkspaceSymbolParams -makeFieldsNoPrefix ''CodeLensParams -makeFieldsNoPrefix ''CodeLens -makeFieldsNoPrefix ''CodeLensRegistrationOptions -makeFieldsNoPrefix ''DocumentLinkParams -makeFieldsNoPrefix ''DocumentLink -makeFieldsNoPrefix ''FormattingOptions -makeFieldsNoPrefix ''DocumentFormattingParams -makeFieldsNoPrefix ''DocumentRangeFormattingParams -makeFieldsNoPrefix ''DocumentOnTypeFormattingParams -makeFieldsNoPrefix ''RenameParams makeFieldsNoPrefix ''ExecuteCommandParams makeFieldsNoPrefix ''ExecuteCommandRegistrationOptions makeFieldsNoPrefix ''ApplyWorkspaceEditParams makeFieldsNoPrefix ''ApplyWorkspaceEditResponseBody -makeFieldsNoPrefix ''TraceParams -makeFieldsNoPrefix ''TraceNotification -- --------------------------------------------------------------------- +-- Initialize +makeFieldsNoPrefix ''InitializeParams +makeFieldsNoPrefix ''InitializeError +makeFieldsNoPrefix ''InitializeResult +makeFieldsNoPrefix ''ClientInfo +makeFieldsNoPrefix ''ServerInfo +makeFieldsNoPrefix ''InitializedParams + +-- Watched files +makeFieldsNoPrefix ''DidChangeWatchedFilesClientCapabilities +makeFieldsNoPrefix ''DidChangeWatchedFilesRegistrationOptions +makeFieldsNoPrefix ''FileSystemWatcher +makeFieldsNoPrefix ''WatchKind +makeFieldsNoPrefix ''FileEvent +makeFieldsNoPrefix ''DidChangeWatchedFilesParams + +-- Workspace symbols +makeFieldsNoPrefix ''WorkspaceSymbolKindClientCapabilities +makeFieldsNoPrefix ''WorkspaceSymbolClientCapabilities +makeFieldsNoPrefix ''WorkspaceSymbolOptions +makeFieldsNoPrefix ''WorkspaceSymbolRegistrationOptions +makeFieldsNoPrefix ''WorkspaceSymbolParams + -- Location makeFieldsNoPrefix ''Position makeFieldsNoPrefix ''Range @@ -136,15 +145,111 @@ makeFieldsNoPrefix ''Location -- Completion makeFieldsNoPrefix ''CompletionItem makeFieldsNoPrefix ''CompletionContext -makeFieldsNoPrefix ''CompletionListType +makeFieldsNoPrefix ''CompletionList makeFieldsNoPrefix ''CompletionParams makeFieldsNoPrefix ''CompletionRegistrationOptions +-- Declaration +makeFieldsNoPrefix ''DeclarationClientCapabilities +makeFieldsNoPrefix ''DeclarationOptions +makeFieldsNoPrefix ''DeclarationRegistrationOptions +makeFieldsNoPrefix ''DeclarationParams + -- CodeActions +makeFieldsNoPrefix ''CodeActionKindClientCapabilities +makeFieldsNoPrefix ''CodeActionLiteralSupport +makeFieldsNoPrefix ''CodeActionClientCapabilities +makeFieldsNoPrefix ''CodeActionOptions +makeFieldsNoPrefix ''CodeActionRegistrationOptions makeFieldsNoPrefix ''CodeActionContext makeFieldsNoPrefix ''CodeActionParams makeFieldsNoPrefix ''CodeAction +-- CodeLens +makeFieldsNoPrefix ''CodeLensClientCapabilities +makeFieldsNoPrefix ''CodeLensOptions +makeFieldsNoPrefix ''CodeLensRegistrationOptions +makeFieldsNoPrefix ''CodeLensParams +makeFieldsNoPrefix ''CodeLens + +-- DocumentLink +makeFieldsNoPrefix ''DocumentLinkClientCapabilities +makeFieldsNoPrefix ''DocumentLinkOptions +makeFieldsNoPrefix ''DocumentLinkRegistrationOptions +makeFieldsNoPrefix ''DocumentLinkParams +makeFieldsNoPrefix ''DocumentLink + +-- DocumentColor +makeFieldsNoPrefix ''DocumentColorClientCapabilities +makeFieldsNoPrefix ''DocumentColorOptions +makeFieldsNoPrefix ''DocumentColorRegistrationOptions +makeFieldsNoPrefix ''DocumentColorParams +makeFieldsNoPrefix ''Color +makeFieldsNoPrefix ''ColorInformation + +-- ColorPresentation +makeFieldsNoPrefix ''ColorPresentationParams +makeFieldsNoPrefix ''ColorPresentation + +-- Formatting +makeFieldsNoPrefix ''DocumentFormattingClientCapabilities +makeFieldsNoPrefix ''DocumentFormattingOptions +makeFieldsNoPrefix ''DocumentFormattingRegistrationOptions +makeFieldsNoPrefix ''FormattingOptions +makeFieldsNoPrefix ''DocumentFormattingParams + +-- RangeFormatting +makeFieldsNoPrefix ''DocumentRangeFormattingClientCapabilities +makeFieldsNoPrefix ''DocumentRangeFormattingOptions +makeFieldsNoPrefix ''DocumentRangeFormattingRegistrationOptions +makeFieldsNoPrefix ''DocumentRangeFormattingParams + +-- OnTypeFormatting +makeFieldsNoPrefix ''DocumentOnTypeFormattingClientCapabilities +makeFieldsNoPrefix ''DocumentOnTypeFormattingOptions +makeFieldsNoPrefix ''DocumentOnTypeFormattingRegistrationOptions +makeFieldsNoPrefix ''DocumentOnTypeFormattingParams + +-- Rename +makeFieldsNoPrefix ''RenameClientCapabilities +makeFieldsNoPrefix ''RenameOptions +makeFieldsNoPrefix ''RenameRegistrationOptions +makeFieldsNoPrefix ''RenameParams + +-- PrepareRename +makeFieldsNoPrefix ''PrepareRenameParams +makeFieldsNoPrefix ''RangeWithPlaceholder + +-- FoldingRange +makeFieldsNoPrefix ''FoldingRangeClientCapabilities +makeFieldsNoPrefix ''FoldingRangeOptions +makeFieldsNoPrefix ''FoldingRangeRegistrationOptions +makeFieldsNoPrefix ''FoldingRangeParams +makeFieldsNoPrefix ''FoldingRange + +-- SelectionRange +makeFieldsNoPrefix ''SelectionRangeClientCapabilities +makeFieldsNoPrefix ''SelectionRangeOptions +makeFieldsNoPrefix ''SelectionRangeRegistrationOptions +makeFieldsNoPrefix ''SelectionRangeParams +makeFieldsNoPrefix ''SelectionRange + +-- DocumentHighlight +makeFieldsNoPrefix ''DocumentHighlightClientCapabilities +makeFieldsNoPrefix ''DocumentHighlightOptions +makeFieldsNoPrefix ''DocumentHighlightRegistrationOptions +makeFieldsNoPrefix ''DocumentHighlightParams +makeFieldsNoPrefix ''DocumentHighlight + +-- DocumentSymbol +makeFieldsNoPrefix ''DocumentSymbolKindClientCapabilities +makeFieldsNoPrefix ''DocumentSymbolClientCapabilities +makeFieldsNoPrefix ''DocumentSymbolOptions +makeFieldsNoPrefix ''DocumentSymbolRegistrationOptions +makeFieldsNoPrefix ''DocumentSymbolParams +makeFieldsNoPrefix ''DocumentSymbol +makeFieldsNoPrefix ''SymbolInformation + -- DocumentFilter makeFieldsNoPrefix ''DocumentFilter @@ -178,21 +283,10 @@ makeFieldsNoPrefix ''Command makeFieldsNoPrefix ''Diagnostic makeFieldsNoPrefix ''DiagnosticRelatedInformation --- Symbol -makeFieldsNoPrefix ''DocumentSymbolParams -makeFieldsNoPrefix ''DocumentSymbol -makeFieldsNoPrefix ''SymbolInformation - --- Color -makeFieldsNoPrefix ''Color -makeFieldsNoPrefix ''ColorInformation -makeFieldsNoPrefix ''DocumentColorParams -makeFieldsNoPrefix ''ColorPresentationParams -makeFieldsNoPrefix ''ColorPresentation +-- Hover +makeFieldsNoPrefix ''Hover +makeFieldsNoPrefix ''HoverRegistrationOptions --- Folding Range -makeFieldsNoPrefix ''FoldingRange -makeFieldsNoPrefix ''FoldingRangeParams -- Window makeFieldsNoPrefix ''ShowMessageParams diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/List.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/List.hs deleted file mode 100644 index 1217da210..000000000 --- a/haskell-lsp-types/src/Language/Haskell/LSP/Types/List.hs +++ /dev/null @@ -1,31 +0,0 @@ --- Need to split these types out into a separate module since --- ClientCapabilities also depends on them -{-# LANGUAGE CPP #-} -{-# LANGUAGE GeneralizedNewtypeDeriving #-} -{-# LANGUAGE DeriveTraversable #-} -{-# LANGUAGE DeriveGeneric #-} -module Language.Haskell.LSP.Types.List where - -import Control.DeepSeq -import qualified Data.Aeson as A -import Data.Aeson.Types -import GHC.Generics - --- | This data type is used to host a FromJSON instance for the encoding used by --- elisp, where an empty list shows up as "null" -newtype List a = List [a] - deriving (Show,Read,Eq,Ord,Monoid,Functor,Foldable,Traversable,Generic) - -instance NFData a => NFData (List a) - -instance (A.ToJSON a) => A.ToJSON (List a) where - toJSON (List ls) = toJSON ls - -instance (A.FromJSON a) => A.FromJSON (List a) where - parseJSON A.Null = return (List []) - parseJSON v = List <$> parseJSON v - -#if __GLASGOW_HASKELL__ >= 804 -instance Semigroup (List a) where - (<>) = mappend -#endif diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/Location.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Location.hs index 97487ed97..880d3d5e2 100644 --- a/haskell-lsp-types/src/Language/Haskell/LSP/Types/Location.hs +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Location.hs @@ -5,42 +5,18 @@ module Language.Haskell.LSP.Types.Location where import Control.DeepSeq import Data.Aeson.TH import GHC.Generics -import Language.Haskell.LSP.Types.Constants import Language.Haskell.LSP.Types.Uri +import Language.Haskell.LSP.Types.Utils -- --------------------------------------------------------------------- -{- -The current protocol is talored for textual documents which content can be -represented as a string. There is currently no support for binary documents. -Positions inside a document (see Position definition below) are expressed as a -zero-based line and character offset. To ensure that both client and server -split the string into the same line representation the protocol specs the -following end of line sequences: '\n', '\r\n' and '\r'. - -export const EOL: string[] = ['\n', '\r\n', '\r']; --} -{- -https://github.com/Microsoft/language-server-protocol/blob/master/protocol.md#position - -Position in a text document expressed as zero-based line and character offset. A -position is between two characters like an 'insert' cursor in a editor. - -interface Position { - /** - * Line position in a document (zero-based). - */ - line: number; - - /** - * Character offset on a line in a document (zero-based). - */ - character: number; -} --} data Position = Position - { _line :: Int + { -- | Line position in a document (zero-based). + _line :: Int + -- | Character offset on a line in a document (zero-based). Assuming that + -- the line is represented as a string, the @character@ value represents the + -- gap between the @character@ and @character + 1@. , _character :: Int } deriving (Show, Read, Eq, Ord, Generic) @@ -48,46 +24,17 @@ instance NFData Position deriveJSON lspOptions ''Position -- --------------------------------------------------------------------- -{- -https://github.com/Microsoft/language-server-protocol/blob/master/protocol.md#range - -A range in a text document expressed as (zero-based) start and end positions. A -range is comparable to a selection in an editor. Therefore the end position is -exclusive. - -interface Range { - /** - * The range's start position. - */ - start: Position; - - /** - * The range's end position. - */ - end: Position; -} --} data Range = Range - { _start :: Position - , _end :: Position + { _start :: Position -- ^ The range's start position. + , _end :: Position -- ^ The range's end position. } deriving (Show, Read, Eq, Ord, Generic) instance NFData Range deriveJSON lspOptions ''Range -- --------------------------------------------------------------------- -{- -https://github.com/Microsoft/language-server-protocol/blob/master/protocol.md#location - -Represents a location inside a resource, such as a line inside a text file. - -interface Location { - uri: string; - range: Range; -} --} data Location = Location @@ -97,3 +44,33 @@ data Location = instance NFData Location deriveJSON lspOptions ''Location + +-- --------------------------------------------------------------------- + +-- | Represents a link between a source and a target location. +data LocationLink = + LocationLink + { -- | Span of the origin of this link. + -- Used as the underlined span for mouse interaction. Defaults to the word + -- range at the mouse position. + _originSelectionRange :: Maybe Range + -- | The target resource identifier of this link. + , _targetUri :: Uri + -- | The full target range of this link. If the target for example is a + -- symbol then target range is the range enclosing this symbol not including + -- leading/trailing whitespace but everything else like comments. This + -- information is typically used to highlight the range in the editor. + , _targetRange :: Range + -- | The range that should be selected and revealed when this link is being + -- followed, e.g the name of a function. Must be contained by the the + -- 'targetRange'. See also @DocumentSymbol._range@ + , _targetSelectionRange :: Range + } deriving (Read, Show, Eq) +deriveJSON lspOptions ''LocationLink + +-- --------------------------------------------------------------------- + +-- | A helper function for creating ranges. +-- prop> mkRange l c l' c' = Range (Position l c) (Position l' c') +mkRange :: Int -> Int -> Int -> Int -> Range +mkRange l c l' c' = Range (Position l c) (Position l' c') diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/LspId.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/LspId.hs new file mode 100644 index 000000000..9417ab9ce --- /dev/null +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/LspId.hs @@ -0,0 +1,39 @@ +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE StandaloneDeriving #-} +{-# LANGUAGE GADTs #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE TypeInType #-} +{-# OPTIONS_GHC -Wno-unticked-promoted-constructors #-} +module Language.Haskell.LSP.Types.LspId where + +import qualified Data.Aeson as A +import Data.Text (Text) +import Data.IxMap +import Language.Haskell.LSP.Types.Method + +-- | Id used for a request, Can be either a String or an Int +data LspId (m :: Method f Request) = IdInt Int | IdString Text + deriving (Show,Read,Eq,Ord) + +instance A.ToJSON (LspId m) where + toJSON (IdInt i) = A.toJSON i + toJSON (IdString s) = A.toJSON s + +instance A.FromJSON (LspId m) where + parseJSON v@(A.Number _) = IdInt <$> A.parseJSON v + parseJSON (A.String s) = return (IdString s) + parseJSON _ = mempty + +instance IxOrd LspId where + type Base LspId = Either Int Text + toBase (IdInt i) = Left i + toBase (IdString s) = Right s + +data SomeLspId where + SomeLspId :: LspId m -> SomeLspId + +deriving instance Show SomeLspId +instance Eq SomeLspId where + SomeLspId a == SomeLspId b = toBase a == toBase b +instance Ord SomeLspId where + SomeLspId a `compare` SomeLspId b = toBase a `compare` toBase b diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/MarkupContent.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/MarkupContent.hs index 7a6e1c51a..50ec0be9f 100644 --- a/haskell-lsp-types/src/Language/Haskell/LSP/Types/MarkupContent.hs +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/MarkupContent.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE CPP #-} {-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TemplateHaskell #-} @@ -12,31 +11,8 @@ module Language.Haskell.LSP.Types.MarkupContent where import Data.Aeson import Data.Aeson.TH -import Data.Monoid ((<>)) import Data.Text (Text) -import Language.Haskell.LSP.Types.Constants - -{- -/** - * Describes the content type that a client supports in various - * result literals like `Hover`, `ParameterInfo` or `CompletionItem`. - * - * Please note that `MarkupKinds` must not start with a `$`. This kinds - * are reserved for internal usage. - */ -export namespace MarkupKind { - /** - * Plain text is supported as a content format - */ - export const PlainText: 'plaintext' = 'plaintext'; - - /** - * Markdown is supported as a content format - */ - export const Markdown: 'markdown' = 'markdown'; -} -export type MarkupKind = 'plaintext' | 'markdown'; --} +import Language.Haskell.LSP.Types.Utils -- | Describes the content type that a client supports in various -- result literals like `Hover`, `ParameterInfo` or `CompletionItem`. @@ -53,45 +29,6 @@ instance FromJSON MarkupKind where parseJSON (String "markdown") = pure MkMarkdown parseJSON _ = mempty - -{- -/** - * A `MarkupContent` literal represents a string value which content is interpreted base on its - * kind flag. Currently the protocol supports `plaintext` and `markdown` as markup kinds. - * - * If the kind is `markdown` then the value can contain fenced code blocks like in GitHub issues. - * See https://help.github.com/articles/creating-and-highlighting-code-blocks/#syntax-highlighting - * - * Here is an example how such a string can be constructed using JavaScript / TypeScript: - * ```ts - * let markdown: MarkdownContent = { - * kind: MarkupKind.Markdown, - * value: [ - * '# Header', - * 'Some text', - * '```typescript', - * 'someCode();', - * '```' - * ].join('\n') - * }; - * ``` - * - * *Please Note* that clients might sanitize the return markdown. A client could decide to - * remove HTML from the markdown to avoid script execution. - */ -export interface MarkupContent { - /** - * The type of the Markup - */ - kind: MarkupKind; - - /** - * The content itself - */ - value: string; -} --} - -- | A `MarkupContent` literal represents a string value which content is interpreted base on its -- | kind flag. Currently the protocol supports `plaintext` and `markdown` as markup kinds. -- | @@ -144,16 +81,13 @@ sectionSeparator = "* * *\n" -- --------------------------------------------------------------------- -#if __GLASGOW_HASKELL__ >= 804 instance Semigroup MarkupContent where - (<>) = mappend -#endif + MarkupContent MkPlainText s1 <> MarkupContent MkPlainText s2 = MarkupContent MkPlainText (s1 `mappend` s2) + MarkupContent MkMarkdown s1 <> MarkupContent _ s2 = MarkupContent MkMarkdown (s1 `mappend` s2) + MarkupContent _ s1 <> MarkupContent MkMarkdown s2 = MarkupContent MkMarkdown (s1 `mappend` s2) instance Monoid MarkupContent where mempty = MarkupContent MkPlainText "" - MarkupContent MkPlainText s1 `mappend` MarkupContent MkPlainText s2 = MarkupContent MkPlainText (s1 `mappend` s2) - MarkupContent MkMarkdown s1 `mappend` MarkupContent _ s2 = MarkupContent MkMarkdown (s1 `mappend` s2) - MarkupContent _ s1 `mappend` MarkupContent MkMarkdown s2 = MarkupContent MkMarkdown (s1 `mappend` s2) -- --------------------------------------------------------------------- diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/Message.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Message.hs index 9c94614cb..f70bd31c4 100644 --- a/haskell-lsp-types/src/Language/Haskell/LSP/Types/Message.hs +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Message.hs @@ -1,329 +1,284 @@ +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE GADTs #-} +{-# LANGUAGE TypeOperators #-} +{-# LANGUAGE UndecidableInstances #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE DuplicateRecordFields #-} -{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE TemplateHaskell #-} -module Language.Haskell.LSP.Types.Message where - -import qualified Data.Aeson as A -import Data.Aeson.TH -import Data.Aeson.Types -import Data.Hashable --- For <= 8.2.2 -import Data.Text (Text) -import Language.Haskell.LSP.Types.Constants - - --- | Id used for a request, Can be either a String or an Int -data LspId = IdInt Int | IdString Text - deriving (Show,Read,Eq,Ord) - -instance A.ToJSON LspId where - toJSON (IdInt i) = toJSON i - toJSON (IdString s) = toJSON s +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE StandaloneDeriving #-} +{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE TupleSections #-} +{-# OPTIONS_GHC -Wno-unticked-promoted-constructors #-} -instance A.FromJSON LspId where - parseJSON v@(A.Number _) = IdInt <$> parseJSON v - parseJSON (A.String s) = return (IdString s) - parseJSON _ = mempty +module Language.Haskell.LSP.Types.Message where -instance Hashable LspId where - hashWithSalt salt (IdInt i) = hashWithSalt salt i - hashWithSalt salt (IdString s) = hashWithSalt salt s +import Language.Haskell.LSP.Types.Cancellation +import Language.Haskell.LSP.Types.CodeAction +import Language.Haskell.LSP.Types.CodeLens +import Language.Haskell.LSP.Types.Command +import Language.Haskell.LSP.Types.Common +import Language.Haskell.LSP.Types.Configuration +import Language.Haskell.LSP.Types.Completion +import Language.Haskell.LSP.Types.Declaration +import Language.Haskell.LSP.Types.Definition +import Language.Haskell.LSP.Types.Diagnostic +import Language.Haskell.LSP.Types.DocumentColor +import Language.Haskell.LSP.Types.DocumentHighlight +import Language.Haskell.LSP.Types.DocumentLink +import Language.Haskell.LSP.Types.DocumentSymbol +import Language.Haskell.LSP.Types.FoldingRange +import Language.Haskell.LSP.Types.Formatting +import Language.Haskell.LSP.Types.Hover +import Language.Haskell.LSP.Types.Implementation +import Language.Haskell.LSP.Types.Initialize +import Language.Haskell.LSP.Types.Location +import Language.Haskell.LSP.Types.LspId +import Language.Haskell.LSP.Types.Method +import Language.Haskell.LSP.Types.Progress +import Language.Haskell.LSP.Types.Registration +import Language.Haskell.LSP.Types.Rename +import Language.Haskell.LSP.Types.References +import Language.Haskell.LSP.Types.SelectionRange +import Language.Haskell.LSP.Types.SignatureHelp +import Language.Haskell.LSP.Types.TextDocument +import Language.Haskell.LSP.Types.TypeDefinition +import Language.Haskell.LSP.Types.Utils +import Language.Haskell.LSP.Types.Window +import Language.Haskell.LSP.Types.WatchedFiles +import Language.Haskell.LSP.Types.WorkspaceEdit +import Language.Haskell.LSP.Types.WorkspaceFolders +import Language.Haskell.LSP.Types.WorkspaceSymbol +import qualified Data.HashMap.Strict as HM + +import Data.Kind +import Data.Aeson +import Data.Aeson.Types +import Data.Aeson.TH +import Data.Text (Text) +import Data.Function (on) +import GHC.Generics -- --------------------------------------------------------------------- - --- | Id used for a response, Can be either a String or an Int, or Null. If a --- request doesn't provide a result value the receiver of a request still needs --- to return a response message to conform to the JSON RPC specification. The --- result property of the ResponseMessage should be set to null in this case to --- signal a successful request. -data LspIdRsp = IdRspInt Int | IdRspString Text | IdRspNull - deriving (Show,Read,Eq) - -instance A.ToJSON LspIdRsp where - toJSON (IdRspInt i) = toJSON i - toJSON (IdRspString s) = toJSON s - toJSON IdRspNull = A.Null - -instance A.FromJSON LspIdRsp where - parseJSON v@(A.Number _) = IdRspInt <$> parseJSON v - parseJSON (A.String s) = return $ IdRspString s - parseJSON A.Null = return IdRspNull - parseJSON _ = mempty - -instance Hashable LspIdRsp where - hashWithSalt salt (IdRspInt i) = hashWithSalt salt i - hashWithSalt salt (IdRspString s) = hashWithSalt salt s - hashWithSalt _ IdRspNull = 0 - --- | Converts an LspId to its LspIdRsp counterpart. -responseId :: LspId -> LspIdRsp -responseId (IdInt i) = IdRspInt i -responseId (IdString s) = IdRspString s - --- | Converts an LspIdRsp to its LspId counterpart. -requestId :: LspIdRsp -> LspId -requestId (IdRspInt i) = IdInt i -requestId (IdRspString s) = IdString s -requestId IdRspNull = error "Null response id" - +-- PARAMS definition +-- Map Methods to params/responses -- --------------------------------------------------------------------- --- Client Methods -data ClientMethod = - -- General - Initialize - | Initialized - | Shutdown - | Exit - | CancelRequest - -- Workspace - | WorkspaceDidChangeWorkspaceFolders - | WorkspaceDidChangeConfiguration - | WorkspaceDidChangeWatchedFiles - | WorkspaceSymbol - | WorkspaceExecuteCommand - -- Progress - | WorkDoneProgressCancel - -- Document - | TextDocumentDidOpen - | TextDocumentDidChange - | TextDocumentWillSave - | TextDocumentWillSaveWaitUntil - | TextDocumentDidSave - | TextDocumentDidClose - | TextDocumentCompletion - | CompletionItemResolve - | TextDocumentHover - | TextDocumentSignatureHelp - | TextDocumentDefinition - | TextDocumentTypeDefinition - | TextDocumentImplementation - | TextDocumentReferences - | TextDocumentDocumentHighlight - | TextDocumentDocumentSymbol - | TextDocumentCodeAction - | TextDocumentCodeLens - | CodeLensResolve - | TextDocumentDocumentLink - | DocumentLinkResolve - | TextDocumentDocumentColor - | TextDocumentColorPresentation - | TextDocumentFormatting - | TextDocumentRangeFormatting - | TextDocumentOnTypeFormatting - | TextDocumentRename - | TextDocumentPrepareRename - | TextDocumentFoldingRange - -- A custom message type. It is not enforced that this starts with $/. - | CustomClientMethod Text - deriving (Eq,Ord,Read,Show) - -instance A.FromJSON ClientMethod where - -- General - parseJSON (A.String "initialize") = return Initialize - parseJSON (A.String "initialized") = return Initialized - parseJSON (A.String "shutdown") = return Shutdown - parseJSON (A.String "exit") = return Exit - parseJSON (A.String "$/cancelRequest") = return CancelRequest - -- Workspace - parseJSON (A.String "workspace/didChangeWorkspaceFolders") = return WorkspaceDidChangeWorkspaceFolders - parseJSON (A.String "workspace/didChangeConfiguration") = return WorkspaceDidChangeConfiguration - parseJSON (A.String "workspace/didChangeWatchedFiles") = return WorkspaceDidChangeWatchedFiles - parseJSON (A.String "workspace/symbol") = return WorkspaceSymbol - parseJSON (A.String "workspace/executeCommand") = return WorkspaceExecuteCommand - -- Document - parseJSON (A.String "textDocument/didOpen") = return TextDocumentDidOpen - parseJSON (A.String "textDocument/didChange") = return TextDocumentDidChange - parseJSON (A.String "textDocument/willSave") = return TextDocumentWillSave - parseJSON (A.String "textDocument/willSaveWaitUntil") = return TextDocumentWillSaveWaitUntil - parseJSON (A.String "textDocument/didSave") = return TextDocumentDidSave - parseJSON (A.String "textDocument/didClose") = return TextDocumentDidClose - parseJSON (A.String "textDocument/completion") = return TextDocumentCompletion - parseJSON (A.String "completionItem/resolve") = return CompletionItemResolve - parseJSON (A.String "textDocument/hover") = return TextDocumentHover - parseJSON (A.String "textDocument/signatureHelp") = return TextDocumentSignatureHelp - parseJSON (A.String "textDocument/definition") = return TextDocumentDefinition - parseJSON (A.String "textDocument/typeDefinition") = return TextDocumentTypeDefinition - parseJSON (A.String "textDocument/implementation") = return TextDocumentImplementation - parseJSON (A.String "textDocument/references") = return TextDocumentReferences - parseJSON (A.String "textDocument/documentHighlight") = return TextDocumentDocumentHighlight - parseJSON (A.String "textDocument/documentSymbol") = return TextDocumentDocumentSymbol - parseJSON (A.String "textDocument/codeAction") = return TextDocumentCodeAction - parseJSON (A.String "textDocument/codeLens") = return TextDocumentCodeLens - parseJSON (A.String "codeLens/resolve") = return CodeLensResolve - parseJSON (A.String "textDocument/documentLink") = return TextDocumentDocumentLink - parseJSON (A.String "documentLink/resolve") = return DocumentLinkResolve - parseJSON (A.String "textDocument/documentColor") = return TextDocumentDocumentColor - parseJSON (A.String "textDocument/colorPresentation") = return TextDocumentColorPresentation - parseJSON (A.String "textDocument/formatting") = return TextDocumentFormatting - parseJSON (A.String "textDocument/rangeFormatting") = return TextDocumentRangeFormatting - parseJSON (A.String "textDocument/onTypeFormatting") = return TextDocumentOnTypeFormatting - parseJSON (A.String "textDocument/rename") = return TextDocumentRename - parseJSON (A.String "textDocument/prepareRename") = return TextDocumentPrepareRename - parseJSON (A.String "textDocument/foldingRange") = return TextDocumentFoldingRange - parseJSON (A.String "window/workDoneProgress/cancel") = return WorkDoneProgressCancel - parseJSON (A.String x) = return (CustomClientMethod x) - parseJSON _ = mempty - -instance A.ToJSON ClientMethod where +-- | Map a method to the message payload type +type family MessageParams (m :: Method f t) :: Type where +-- Client -- General - toJSON Initialize = A.String "initialize" - toJSON Initialized = A.String "initialized" - toJSON Shutdown = A.String "shutdown" - toJSON Exit = A.String "exit" - toJSON CancelRequest = A.String "$/cancelRequest" + MessageParams Initialize = InitializeParams + MessageParams Initialized = Maybe InitializedParams + MessageParams Shutdown = Empty + MessageParams Exit = Empty -- Workspace - toJSON WorkspaceDidChangeWorkspaceFolders = A.String "workspace/didChangeWorkspaceFolders" - toJSON WorkspaceDidChangeConfiguration = A.String "workspace/didChangeConfiguration" - toJSON WorkspaceDidChangeWatchedFiles = A.String "workspace/didChangeWatchedFiles" - toJSON WorkspaceSymbol = A.String "workspace/symbol" - toJSON WorkspaceExecuteCommand = A.String "workspace/executeCommand" - -- Document - toJSON TextDocumentDidOpen = A.String "textDocument/didOpen" - toJSON TextDocumentDidChange = A.String "textDocument/didChange" - toJSON TextDocumentWillSave = A.String "textDocument/willSave" - toJSON TextDocumentWillSaveWaitUntil = A.String "textDocument/willSaveWaitUntil" - toJSON TextDocumentDidSave = A.String "textDocument/didSave" - toJSON TextDocumentDidClose = A.String "textDocument/didClose" - toJSON TextDocumentCompletion = A.String "textDocument/completion" - toJSON CompletionItemResolve = A.String "completionItem/resolve" - toJSON TextDocumentHover = A.String "textDocument/hover" - toJSON TextDocumentSignatureHelp = A.String "textDocument/signatureHelp" - toJSON TextDocumentReferences = A.String "textDocument/references" - toJSON TextDocumentDocumentHighlight = A.String "textDocument/documentHighlight" - toJSON TextDocumentDocumentSymbol = A.String "textDocument/documentSymbol" - toJSON TextDocumentDefinition = A.String "textDocument/definition" - toJSON TextDocumentTypeDefinition = A.String "textDocument/typeDefinition" - toJSON TextDocumentImplementation = A.String "textDocument/implementation" - toJSON TextDocumentCodeAction = A.String "textDocument/codeAction" - toJSON TextDocumentCodeLens = A.String "textDocument/codeLens" - toJSON CodeLensResolve = A.String "codeLens/resolve" - toJSON TextDocumentDocumentColor = A.String "textDocument/documentColor" - toJSON TextDocumentColorPresentation = A.String "textDocument/colorPresentation" - toJSON TextDocumentFormatting = A.String "textDocument/formatting" - toJSON TextDocumentRangeFormatting = A.String "textDocument/rangeFormatting" - toJSON TextDocumentOnTypeFormatting = A.String "textDocument/onTypeFormatting" - toJSON TextDocumentRename = A.String "textDocument/rename" - toJSON TextDocumentPrepareRename = A.String "textDocument/prepareRename" - toJSON TextDocumentFoldingRange = A.String "textDocument/foldingRange" - toJSON TextDocumentDocumentLink = A.String "textDocument/documentLink" - toJSON DocumentLinkResolve = A.String "documentLink/resolve" - toJSON WorkDoneProgressCancel = A.String "window/workDoneProgress/cancel" - toJSON (CustomClientMethod xs) = A.String xs - -data ServerMethod = - -- Window - WindowShowMessage - | WindowShowMessageRequest - | WindowLogMessage - | WindowWorkDoneProgressCreate - | Progress - | TelemetryEvent + MessageParams WorkspaceDidChangeWorkspaceFolders = DidChangeWorkspaceFoldersParams + MessageParams WorkspaceDidChangeConfiguration = DidChangeConfigurationParams + MessageParams WorkspaceDidChangeWatchedFiles = DidChangeWatchedFilesParams + MessageParams WorkspaceSymbol = WorkspaceSymbolParams + MessageParams WorkspaceExecuteCommand = ExecuteCommandParams + -- Sync/Document state + MessageParams TextDocumentDidOpen = DidOpenTextDocumentParams + MessageParams TextDocumentDidChange = DidChangeTextDocumentParams + MessageParams TextDocumentWillSave = WillSaveTextDocumentParams + MessageParams TextDocumentWillSaveWaitUntil = WillSaveTextDocumentParams + MessageParams TextDocumentDidSave = DidSaveTextDocumentParams + MessageParams TextDocumentDidClose = DidCloseTextDocumentParams + -- Completion + MessageParams TextDocumentCompletion = CompletionParams + MessageParams CompletionItemResolve = CompletionItem + -- Language Queries + MessageParams TextDocumentHover = HoverParams + MessageParams TextDocumentSignatureHelp = SignatureHelpParams + MessageParams TextDocumentDeclaration = DeclarationParams + MessageParams TextDocumentDefinition = DefinitionParams + MessageParams TextDocumentTypeDefinition = TypeDefinitionParams + MessageParams TextDocumentImplementation = ImplementationParams + MessageParams TextDocumentReferences = ReferenceParams + MessageParams TextDocumentDocumentHighlight = DocumentHighlightParams + MessageParams TextDocumentDocumentSymbol = DocumentSymbolParams + -- Code Action/Lens/Link + MessageParams TextDocumentCodeAction = CodeActionParams + MessageParams TextDocumentCodeLens = CodeLensParams + MessageParams CodeLensResolve = CodeLens + MessageParams TextDocumentDocumentLink = DocumentLinkParams + MessageParams DocumentLinkResolve = DocumentLink + -- Syntax highlighting/coloring + MessageParams TextDocumentDocumentColor = DocumentColorParams + MessageParams TextDocumentColorPresentation = ColorPresentationParams + -- Formatting + MessageParams TextDocumentFormatting = DocumentFormattingParams + MessageParams TextDocumentRangeFormatting = DocumentRangeFormattingParams + MessageParams TextDocumentOnTypeFormatting = DocumentOnTypeFormattingParams + -- Rename + MessageParams TextDocumentRename = RenameParams + MessageParams TextDocumentPrepareRename = PrepareRenameParams + -- Folding Range + MessageParams TextDocumentFoldingRange = FoldingRangeParams + -- Selection Range + MessageParams TextDocumentSelectionRange = SelectionRangeParams +-- Server + -- Window + MessageParams WindowShowMessage = ShowMessageParams + MessageParams WindowShowMessageRequest = ShowMessageRequestParams + MessageParams WindowLogMessage = LogMessageParams + -- Progress + MessageParams WindowWorkDoneProgressCreate = WorkDoneProgressCreateParams + MessageParams WindowWorkDoneProgressCancel = WorkDoneProgressCancelParams + MessageParams Progress = ProgressParams SomeProgressParams + -- Telemetry + MessageParams TelemetryEvent = Value -- Client - | ClientRegisterCapability - | ClientUnregisterCapability + MessageParams ClientRegisterCapability = RegistrationParams + MessageParams ClientUnregisterCapability = UnregistrationParams -- Workspace - | WorkspaceWorkspaceFolders - | WorkspaceConfiguration - | WorkspaceApplyEdit - -- Document - | TextDocumentPublishDiagnostics - -- Cancelling - | CancelRequestServer - | CustomServerMethod Text - deriving (Eq,Ord,Read,Show) - -instance A.FromJSON ServerMethod where - -- Window - parseJSON (A.String "window/showMessage") = return WindowShowMessage - parseJSON (A.String "window/showMessageRequest") = return WindowShowMessageRequest - parseJSON (A.String "window/logMessage") = return WindowLogMessage - parseJSON (A.String "window/workDoneProgress/create") = return WindowWorkDoneProgressCreate - parseJSON (A.String "$/progress") = return Progress - parseJSON (A.String "telemetry/event") = return TelemetryEvent - -- Client - parseJSON (A.String "client/registerCapability") = return ClientRegisterCapability - parseJSON (A.String "client/unregisterCapability") = return ClientUnregisterCapability + MessageParams WorkspaceWorkspaceFolders = Empty + MessageParams WorkspaceConfiguration = ConfigurationParams + MessageParams WorkspaceApplyEdit = ApplyWorkspaceEditParams + -- Document/Diagnostic + MessageParams TextDocumentPublishDiagnostics = PublishDiagnosticsParams + -- Cancel + MessageParams CancelRequest = CancelParams + -- Custom + MessageParams CustomMethod = Value + +-- | Map a request method to the response payload type +type family ResponseParams (m :: Method f Request) :: Type where +-- Even though the specification mentions that the result types are +-- @x | y | ... | null@, they don't actually need to be wrapped in a Maybe since +-- (we think) this is just to account for how the response field is always +-- nullable. I.e. if it is null, then the error field is set + +-- Client + -- General + ResponseParams Initialize = InitializeResult + ResponseParams Shutdown = Empty -- Workspace - parseJSON (A.String "workspace/workspaceFolders") = return WorkspaceWorkspaceFolders - parseJSON (A.String "workspace/configuration") = return WorkspaceConfiguration - parseJSON (A.String "workspace/applyEdit") = return WorkspaceApplyEdit - -- Document - parseJSON (A.String "textDocument/publishDiagnostics") = return TextDocumentPublishDiagnostics - -- Cancelling - parseJSON (A.String "$/cancelRequest") = return CancelRequestServer - parseJSON (A.String m) = return (CustomServerMethod m) - parseJSON _ = mempty - -instance A.ToJSON ServerMethod where + ResponseParams WorkspaceSymbol = List SymbolInformation + ResponseParams WorkspaceExecuteCommand = Value + -- Sync/Document state + ResponseParams TextDocumentWillSaveWaitUntil = List TextEdit + -- Completion + ResponseParams TextDocumentCompletion = List CompletionItem |? CompletionList + ResponseParams CompletionItemResolve = CompletionItem + -- Language Queries + ResponseParams TextDocumentHover = Maybe Hover + ResponseParams TextDocumentSignatureHelp = SignatureHelp + ResponseParams TextDocumentDeclaration = Location |? List Location |? List LocationLink + ResponseParams TextDocumentDefinition = Location |? List Location |? List LocationLink + ResponseParams TextDocumentTypeDefinition = Location |? List Location |? List LocationLink + ResponseParams TextDocumentImplementation = Location |? List Location |? List LocationLink + ResponseParams TextDocumentReferences = List Location + ResponseParams TextDocumentDocumentHighlight = List DocumentHighlight + ResponseParams TextDocumentDocumentSymbol = List DocumentSymbol |? List SymbolInformation + -- Code Action/Lens/Link + ResponseParams TextDocumentCodeAction = List (Command |? CodeAction) + ResponseParams TextDocumentCodeLens = List CodeLens + ResponseParams CodeLensResolve = CodeLens + ResponseParams TextDocumentDocumentLink = List DocumentLink + ResponseParams DocumentLinkResolve = DocumentLink + -- Syntax highlighting/coloring + ResponseParams TextDocumentDocumentColor = List ColorInformation + ResponseParams TextDocumentColorPresentation = List ColorPresentation + -- Formatting + ResponseParams TextDocumentFormatting = List TextEdit + ResponseParams TextDocumentRangeFormatting = List TextEdit + ResponseParams TextDocumentOnTypeFormatting = List TextEdit + -- Rename + ResponseParams TextDocumentRename = WorkspaceEdit + ResponseParams TextDocumentPrepareRename = Range |? RangeWithPlaceholder + -- FoldingRange + ResponseParams TextDocumentFoldingRange = List FoldingRange + ResponseParams TextDocumentSelectionRange = List SelectionRange + -- Custom can be either a notification or a message +-- Server -- Window - toJSON WindowShowMessage = A.String "window/showMessage" - toJSON WindowShowMessageRequest = A.String "window/showMessageRequest" - toJSON WindowLogMessage = A.String "window/logMessage" - toJSON WindowWorkDoneProgressCreate = A.String "window/workDoneProgress/create" - toJSON Progress = A.String "$/progress" - toJSON TelemetryEvent = A.String "telemetry/event" - -- Client - toJSON ClientRegisterCapability = A.String "client/registerCapability" - toJSON ClientUnregisterCapability = A.String "client/unregisterCapability" + ResponseParams WindowShowMessageRequest = Maybe MessageActionItem + ResponseParams WindowWorkDoneProgressCreate = () + -- Capability + ResponseParams ClientRegisterCapability = Empty + ResponseParams ClientUnregisterCapability = Empty -- Workspace - toJSON WorkspaceWorkspaceFolders = A.String "workspace/workspaceFolders" - toJSON WorkspaceConfiguration = A.String "workspace/configuration" - toJSON WorkspaceApplyEdit = A.String "workspace/applyEdit" - -- Document - toJSON TextDocumentPublishDiagnostics = A.String "textDocument/publishDiagnostics" - -- Cancelling - toJSON CancelRequestServer = A.String "$/cancelRequest" - toJSON (CustomServerMethod m) = A.String m - -data RequestMessage m req resp = - RequestMessage - { _jsonrpc :: Text - , _id :: LspId - , _method :: m - , _params :: req - } deriving (Read,Show,Eq) + ResponseParams WorkspaceWorkspaceFolders = Maybe (List WorkspaceFolder) + ResponseParams WorkspaceConfiguration = List Value + ResponseParams WorkspaceApplyEdit = ApplyWorkspaceEditResponseBody +-- Custom + ResponseParams CustomMethod = Value -deriveJSON lspOptions ''RequestMessage -- --------------------------------------------------------------------- {- -interface ResponseError { - /** - * A number indicating the error type that occurred. - */ - code: number; - - /** - * A string providing a short description of the error. - */ - message: string; - - /** - * A Primitive or Structured value that contains additional - * information about the error. Can be omitted. - */ - data?: D; -} - -export namespace ErrorCodes { - // Defined by JSON RPC - export const ParseError: number = -32700; - export const InvalidRequest: number = -32600; - export const MethodNotFound: number = -32601; - export const InvalidParams: number = -32602; - export const InternalError: number = -32603; - export const serverErrorStart: number = -32099; - export const serverErrorEnd: number = -32000; - export const ServerNotInitialized: number = -32002; - export const UnknownErrorCode: number = -32001; - - // Defined by the protocol. - export const RequestCancelled: number = -32800; - export const ContentModified: number = -32801; -} +$ Notifications and Requests + +Notification and requests ids starting with '$/' are messages which are protocol +implementation dependent and might not be implementable in all clients or +servers. For example if the server implementation uses a single threaded +synchronous programming language then there is little a server can do to react +to a '$/cancelRequest'. If a server or client receives notifications or requests +starting with '$/' it is free to ignore them if they are unknown. + -} +data NotificationMessage (m :: Method f Notification) = + NotificationMessage + { _jsonrpc :: Text + , _method :: SMethod m + , _params :: MessageParams m + } deriving Generic + +deriving instance Eq (MessageParams m) => Eq (NotificationMessage m) +deriving instance Show (MessageParams m) => Show (NotificationMessage m) + +instance (FromJSON (MessageParams m), FromJSON (SMethod m)) => FromJSON (NotificationMessage m) where + parseJSON = genericParseJSON lspOptions +instance (ToJSON (MessageParams m)) => ToJSON (NotificationMessage m) where + toJSON = genericToJSON lspOptions + toEncoding = genericToEncoding lspOptions + +data RequestMessage (m :: Method f Request) = RequestMessage + { _jsonrpc :: Text + , _id :: LspId m + , _method :: SMethod m + , _params :: MessageParams m + } deriving Generic + +deriving instance Eq (MessageParams m) => Eq (RequestMessage m) +deriving instance (Read (SMethod m), Read (MessageParams m)) => Read (RequestMessage m) +deriving instance Show (MessageParams m) => Show (RequestMessage m) + +instance (FromJSON (MessageParams m), FromJSON (SMethod m)) => FromJSON (RequestMessage m) where + parseJSON = genericParseJSON lspOptions +instance (ToJSON (MessageParams m), FromJSON (SMethod m)) => ToJSON (RequestMessage m) where + toJSON = genericToJSON lspOptions + toEncoding = genericToEncoding lspOptions + +-- | A custom message data type is needed to distinguish between +-- notifications and requests, since a CustomMethod can be both! +data CustomMessage f t where + ReqMess :: RequestMessage (CustomMethod :: Method f Request) -> CustomMessage f Request + NotMess :: NotificationMessage (CustomMethod :: Method f Notification) -> CustomMessage f Notification + +deriving instance Show (CustomMessage p t) + +instance ToJSON (CustomMessage p t) where + toJSON (ReqMess a) = toJSON a + toJSON (NotMess a) = toJSON a + +instance FromJSON (CustomMessage p Request) where + parseJSON v = ReqMess <$> parseJSON v +instance FromJSON (CustomMessage p Notification) where + parseJSON v = NotMess <$> parseJSON v + +-- --------------------------------------------------------------------- +-- Response Message +-- --------------------------------------------------------------------- + data ErrorCode = ParseError | InvalidRequest | MethodNotFound @@ -338,98 +293,57 @@ data ErrorCode = ParseError -- ^ Note: server error codes are reserved from -32099 to -32000 deriving (Read,Show,Eq) -instance A.ToJSON ErrorCode where - toJSON ParseError = A.Number (-32700) - toJSON InvalidRequest = A.Number (-32600) - toJSON MethodNotFound = A.Number (-32601) - toJSON InvalidParams = A.Number (-32602) - toJSON InternalError = A.Number (-32603) - toJSON ServerErrorStart = A.Number (-32099) - toJSON ServerErrorEnd = A.Number (-32000) - toJSON ServerNotInitialized = A.Number (-32002) - toJSON UnknownErrorCode = A.Number (-32001) - toJSON RequestCancelled = A.Number (-32800) - toJSON ContentModified = A.Number (-32801) - -instance A.FromJSON ErrorCode where - parseJSON (A.Number (-32700)) = pure ParseError - parseJSON (A.Number (-32600)) = pure InvalidRequest - parseJSON (A.Number (-32601)) = pure MethodNotFound - parseJSON (A.Number (-32602)) = pure InvalidParams - parseJSON (A.Number (-32603)) = pure InternalError - parseJSON (A.Number (-32099)) = pure ServerErrorStart - parseJSON (A.Number (-32000)) = pure ServerErrorEnd - parseJSON (A.Number (-32002)) = pure ServerNotInitialized - parseJSON (A.Number (-32001)) = pure UnknownErrorCode - parseJSON (A.Number (-32800)) = pure RequestCancelled - parseJSON (A.Number (-32801)) = pure ContentModified +instance ToJSON ErrorCode where + toJSON ParseError = Number (-32700) + toJSON InvalidRequest = Number (-32600) + toJSON MethodNotFound = Number (-32601) + toJSON InvalidParams = Number (-32602) + toJSON InternalError = Number (-32603) + toJSON ServerErrorStart = Number (-32099) + toJSON ServerErrorEnd = Number (-32000) + toJSON ServerNotInitialized = Number (-32002) + toJSON UnknownErrorCode = Number (-32001) + toJSON RequestCancelled = Number (-32800) + toJSON ContentModified = Number (-32801) + +instance FromJSON ErrorCode where + parseJSON (Number (-32700)) = pure ParseError + parseJSON (Number (-32600)) = pure InvalidRequest + parseJSON (Number (-32601)) = pure MethodNotFound + parseJSON (Number (-32602)) = pure InvalidParams + parseJSON (Number (-32603)) = pure InternalError + parseJSON (Number (-32099)) = pure ServerErrorStart + parseJSON (Number (-32000)) = pure ServerErrorEnd + parseJSON (Number (-32002)) = pure ServerNotInitialized + parseJSON (Number (-32001)) = pure UnknownErrorCode + parseJSON (Number (-32800)) = pure RequestCancelled + parseJSON (Number (-32801)) = pure ContentModified parseJSON _ = mempty -- ------------------------------------- -{- - https://microsoft.github.io/language-server-protocol/specification#responseMessage - - interface ResponseError { - /** - * A number indicating the error type that occurred. - */ - code: number; - - /** - * A string providing a short description of the error. - */ - message: string; - - /** - * A primitive or structured value that contains additional - * information about the error. Can be omitted. - */ - data?: string | number | boolean | array | object | null; - } --} - data ResponseError = ResponseError { _code :: ErrorCode , _message :: Text - , _xdata :: Maybe A.Value + , _xdata :: Maybe Value } deriving (Read,Show,Eq) -deriveJSON lspOptions{ fieldLabelModifier = customModifier } ''ResponseError - --- --------------------------------------------------------------------- - -{- - https://microsoft.github.io/language-server-protocol/specification#responseMessage - - interface ResponseMessage extends Message { - /** - * The request id. - */ - id: number | string | null; - - /** - * The result of a request. This member is REQUIRED on success. - * This member MUST NOT exist if there was an error invoking the method. - */ - result?: string | number | boolean | object | null; - - /** - * The error object in case a request fails. - */ - error?: ResponseError; - } --} +deriveJSON lspOptions ''ResponseError -data ResponseMessage a = +-- | Either result or error must be Just. +data ResponseMessage (m :: Method f Request) = ResponseMessage { _jsonrpc :: Text - , _id :: LspIdRsp - , _result :: Either ResponseError a - } deriving (Read,Show,Eq) + , _id :: Maybe (LspId m) + , _result :: Either ResponseError (ResponseParams m) + } deriving Generic + +deriving instance Eq (ResponseParams m) => Eq (ResponseMessage m) +deriving instance Read (ResponseParams m) => Read (ResponseMessage m) +deriving instance Show (ResponseParams m) => Show (ResponseMessage m) -instance ToJSON a => ToJSON (ResponseMessage a) where +instance (ToJSON (ResponseParams m)) => ToJSON (ResponseMessage m) where toJSON (ResponseMessage { _jsonrpc = jsonrpc, _id = lspid, _result = result }) = object [ "jsonrpc" .= jsonrpc @@ -439,7 +353,7 @@ instance ToJSON a => ToJSON (ResponseMessage a) where Right a -> "result" .= a ] -instance FromJSON a => FromJSON (ResponseMessage a) where +instance FromJSON (ResponseParams a) => FromJSON (ResponseMessage a) where parseJSON = withObject "Response" $ \o -> do _jsonrpc <- o .: "jsonrpc" _id <- o .: "id" @@ -449,73 +363,251 @@ instance FromJSON a => FromJSON (ResponseMessage a) where result <- case (_error, _result) of ((Just err), Nothing ) -> pure $ Left err (Nothing , (Just res)) -> pure $ Right res - ((Just _), (Just _)) -> fail $ "Both error and result cannot be present" - (Nothing, Nothing) -> fail "Both error and result cannot be Nothing" + ((Just _err), (Just _res)) -> fail $ "both error and result cannot be present: " ++ show o + (Nothing, Nothing) -> fail "both error and result cannot be Nothing" return $ ResponseMessage _jsonrpc _id $ result -type ErrorResponse = ResponseMessage () - -- --------------------------------------------------------------------- +-- Helper Type Families +-- --------------------------------------------------------------------- + +-- | Map a method to the Request/Notification type with the correct +-- payload +type family Message (m :: Method f t) :: Type where + Message (CustomMethod :: Method f t) = CustomMessage f t + Message (m :: Method f Request) = RequestMessage m + Message (m :: Method f Notification) = NotificationMessage m -type BareResponseMessage = ResponseMessage A.Value +-- Some helpful type synonyms +type ClientMessage (m :: Method FromClient t) = Message m +type ServerMessage (m :: Method FromServer t) = Message m -- --------------------------------------------------------------------- -{- -$ Notifications and Requests +-- Working with arbritary messages +-- --------------------------------------------------------------------- -Notification and requests ids starting with '$/' are messages which are protocol -implementation dependent and might not be implementable in all clients or -servers. For example if the server implementation uses a single threaded -synchronous programming language then there is little a server can do to react -to a '$/cancelRequest'. If a server or client receives notifications or requests -starting with '$/' it is free to ignore them if they are unknown. --} +data FromServerMessage' a where + FromServerMess :: forall t (m :: Method FromServer t) a. SMethod m -> Message m -> FromServerMessage' a + FromServerRsp :: forall (m :: Method FromClient Request) a. a m -> ResponseMessage m -> FromServerMessage' a -data NotificationMessage m a = - NotificationMessage - { _jsonrpc :: Text - , _method :: m - , _params :: a - } deriving (Read,Show,Eq) +type FromServerMessage = FromServerMessage' SMethod -deriveJSON lspOptions ''NotificationMessage +instance Eq FromServerMessage where + (==) = (==) `on` toJSON +instance Show FromServerMessage where + show = show . toJSON --- --------------------------------------------------------------------- -{- -Cancellation Support +instance ToJSON FromServerMessage where + toJSON (FromServerMess m p) = serverMethodJSON m (toJSON p) + toJSON (FromServerRsp m p) = clientResponseJSON m (toJSON p) -https://github.com/Microsoft/language-server-protocol/blob/master/protocol.md#cancellation-support +fromServerNot :: forall (m :: Method FromServer Notification). + Message m ~ NotificationMessage m => NotificationMessage m -> FromServerMessage +fromServerNot m@NotificationMessage{_method=meth} = FromServerMess meth m - New: The base protocol now offers support for request cancellation. To - cancel a request, a notification message with the following properties is - sent: +fromServerReq :: forall (m :: Method FromServer Request). + Message m ~ RequestMessage m => RequestMessage m -> FromServerMessage +fromServerReq m@RequestMessage{_method=meth} = FromServerMess meth m -Notification: +data FromClientMessage' a where + FromClientMess :: forall t (m :: Method FromClient t) a. SMethod m -> Message m -> FromClientMessage' a + FromClientRsp :: forall (m :: Method FromServer Request) a. a m -> ResponseMessage m -> FromClientMessage' a - method: '$/cancelRequest' - params: CancelParams defined as follows: +type FromClientMessage = FromClientMessage' SMethod -interface CancelParams { - /** - * The request id to cancel. - */ - id: number | string; -} +instance ToJSON FromClientMessage where + toJSON (FromClientMess m p) = clientMethodJSON m (toJSON p) + toJSON (FromClientRsp m p) = serverResponseJSON m (toJSON p) -A request that got canceled still needs to return from the server and send a -response back. It can not be left open / hanging. This is in line with the JSON -RPC protocol that requires that every request sends a response back. In addition -it allows for returning partial results on cancel. --} +fromClientNot :: forall (m :: Method FromClient Notification). + Message m ~ NotificationMessage m => NotificationMessage m -> FromClientMessage +fromClientNot m@NotificationMessage{_method=meth} = FromClientMess meth m -data CancelParams = - CancelParams - { _id :: LspId - } deriving (Read,Show,Eq) +fromClientReq :: forall (m :: Method FromClient Request). + Message m ~ RequestMessage m => RequestMessage m -> FromClientMessage +fromClientReq m@RequestMessage{_method=meth} = FromClientMess meth m -deriveJSON lspOptions ''CancelParams +type LookupFunc f a = forall (m :: Method f Request). LspId m -> Maybe (SMethod m, a m) -type CancelNotification = NotificationMessage ClientMethod CancelParams -type CancelNotificationServer = NotificationMessage ServerMethod CancelParams +{- +Message Types we must handle are the following + +Request | jsonrpc | id | method | params? +Response | jsonrpc | id | | | response? | error? +Notification | jsonrpc | | method | params? +-} + +parseServerMessage :: LookupFunc FromClient a -> Value -> Parser (FromServerMessage' a) +parseServerMessage lookupId v@(Object o) = do + case HM.lookup "method" o of + Just cmd -> do + -- Request or Notification + SomeServerMethod m <- parseJSON cmd + case splitServerMethod m of + IsServerNot -> FromServerMess m <$> parseJSON v + IsServerReq -> FromServerMess m <$> parseJSON v + IsServerEither + | HM.member "id" o -- Request + , SCustomMethod cm <- m -> + let m' = (SCustomMethod cm :: SMethod (CustomMethod :: Method FromServer Request)) + in FromServerMess m' <$> parseJSON v + | SCustomMethod cm <- m -> + let m' = (SCustomMethod cm :: SMethod (CustomMethod :: Method FromServer Notification)) + in FromServerMess m' <$> parseJSON v + Nothing -> do + case HM.lookup "id" o of + Just i' -> do + i <- parseJSON i' + case lookupId i of + Just (m,res) -> clientResponseJSON m $ FromServerRsp res <$> parseJSON v + Nothing -> fail $ unwords ["Failed in looking up response type of", show v] + Nothing -> fail $ unwords ["Got unexpected message without method or id"] +parseServerMessage _ v = fail $ unwords ["parseServerMessage expected object, got:",show v] + +parseClientMessage :: LookupFunc FromServer a -> Value -> Parser (FromClientMessage' a) +parseClientMessage lookupId v@(Object o) = do + case HM.lookup "method" o of + Just cmd -> do + -- Request or Notification + SomeClientMethod m <- parseJSON cmd + case splitClientMethod m of + IsClientNot -> FromClientMess m <$> parseJSON v + IsClientReq -> FromClientMess m <$> parseJSON v + IsClientEither + | HM.member "id" o -- Request + , SCustomMethod cm <- m -> + let m' = (SCustomMethod cm :: SMethod (CustomMethod :: Method FromClient Request)) + in FromClientMess m' <$> parseJSON v + | SCustomMethod cm <- m -> + let m' = (SCustomMethod cm :: SMethod (CustomMethod :: Method FromClient Notification)) + in FromClientMess m' <$> parseJSON v + Nothing -> do + case HM.lookup "id" o of + Just i' -> do + i <- parseJSON i' + case lookupId i of + Just (m,res) -> serverResponseJSON m $ FromClientRsp res <$> parseJSON v + Nothing -> fail $ unwords ["Failed in looking up response type of", show v] + Nothing -> fail $ unwords ["Got unexpected message without method or id"] +parseClientMessage _ v = fail $ unwords ["parseClientMessage expected object, got:",show v] -- --------------------------------------------------------------------- +-- Helper Utilities +-- --------------------------------------------------------------------- + +clientResponseJSON :: SClientMethod m -> (HasJSON (ResponseMessage m) => x) -> x +clientResponseJSON m x = case splitClientMethod m of + IsClientReq -> x + IsClientEither -> x + +serverResponseJSON :: SServerMethod m -> (HasJSON (ResponseMessage m) => x) -> x +serverResponseJSON m x = case splitServerMethod m of + IsServerReq -> x + IsServerEither -> x + +clientMethodJSON :: SClientMethod m -> (ToJSON (ClientMessage m) => x) -> x +clientMethodJSON m x = + case splitClientMethod m of + IsClientNot -> x + IsClientReq -> x + IsClientEither -> x + +serverMethodJSON :: SServerMethod m -> (ToJSON (ServerMessage m) => x) -> x +serverMethodJSON m x = + case splitServerMethod m of + IsServerNot -> x + IsServerReq -> x + IsServerEither -> x + +type HasJSON a = (ToJSON a,FromJSON a,Eq a) + +-- Reify universal properties about Client/Server Messages + +data ClientNotOrReq (m :: Method FromClient t) where + IsClientNot + :: ( HasJSON (ClientMessage m) + , Message m ~ NotificationMessage m) + => ClientNotOrReq (m :: Method FromClient Notification) + IsClientReq + :: forall (m :: Method FromClient Request). + ( HasJSON (ClientMessage m) + , HasJSON (ResponseMessage m) + , Message m ~ RequestMessage m) + => ClientNotOrReq m + IsClientEither + :: ClientNotOrReq CustomMethod + +data ServerNotOrReq (m :: Method FromServer t) where + IsServerNot + :: ( HasJSON (ServerMessage m) + , Message m ~ NotificationMessage m) + => ServerNotOrReq (m :: Method FromServer Notification) + IsServerReq + :: forall (m :: Method FromServer Request). + ( HasJSON (ServerMessage m) + , HasJSON (ResponseMessage m) + , Message m ~ RequestMessage m) + => ServerNotOrReq m + IsServerEither + :: ServerNotOrReq CustomMethod + +splitClientMethod :: SClientMethod m -> ClientNotOrReq m +splitClientMethod SInitialize = IsClientReq +splitClientMethod SInitialized = IsClientNot +splitClientMethod SShutdown = IsClientReq +splitClientMethod SExit = IsClientNot +splitClientMethod SWorkspaceDidChangeWorkspaceFolders = IsClientNot +splitClientMethod SWorkspaceDidChangeConfiguration = IsClientNot +splitClientMethod SWorkspaceDidChangeWatchedFiles = IsClientNot +splitClientMethod SWorkspaceSymbol = IsClientReq +splitClientMethod SWorkspaceExecuteCommand = IsClientReq +splitClientMethod SWindowWorkDoneProgressCancel = IsClientNot +splitClientMethod STextDocumentDidOpen = IsClientNot +splitClientMethod STextDocumentDidChange = IsClientNot +splitClientMethod STextDocumentWillSave = IsClientNot +splitClientMethod STextDocumentWillSaveWaitUntil = IsClientReq +splitClientMethod STextDocumentDidSave = IsClientNot +splitClientMethod STextDocumentDidClose = IsClientNot +splitClientMethod STextDocumentCompletion = IsClientReq +splitClientMethod SCompletionItemResolve = IsClientReq +splitClientMethod STextDocumentHover = IsClientReq +splitClientMethod STextDocumentSignatureHelp = IsClientReq +splitClientMethod STextDocumentDeclaration = IsClientReq +splitClientMethod STextDocumentDefinition = IsClientReq +splitClientMethod STextDocumentTypeDefinition = IsClientReq +splitClientMethod STextDocumentImplementation = IsClientReq +splitClientMethod STextDocumentReferences = IsClientReq +splitClientMethod STextDocumentDocumentHighlight = IsClientReq +splitClientMethod STextDocumentDocumentSymbol = IsClientReq +splitClientMethod STextDocumentCodeAction = IsClientReq +splitClientMethod STextDocumentCodeLens = IsClientReq +splitClientMethod SCodeLensResolve = IsClientReq +splitClientMethod STextDocumentDocumentLink = IsClientReq +splitClientMethod SDocumentLinkResolve = IsClientReq +splitClientMethod STextDocumentDocumentColor = IsClientReq +splitClientMethod STextDocumentColorPresentation = IsClientReq +splitClientMethod STextDocumentFormatting = IsClientReq +splitClientMethod STextDocumentRangeFormatting = IsClientReq +splitClientMethod STextDocumentOnTypeFormatting = IsClientReq +splitClientMethod STextDocumentRename = IsClientReq +splitClientMethod STextDocumentPrepareRename = IsClientReq +splitClientMethod STextDocumentFoldingRange = IsClientReq +splitClientMethod STextDocumentSelectionRange = IsClientReq +splitClientMethod SCancelRequest = IsClientNot +splitClientMethod SCustomMethod{} = IsClientEither + +splitServerMethod :: SServerMethod m -> ServerNotOrReq m +splitServerMethod SWindowShowMessage = IsServerNot +splitServerMethod SWindowShowMessageRequest = IsServerReq +splitServerMethod SWindowLogMessage = IsServerNot +splitServerMethod SWindowWorkDoneProgressCreate = IsServerReq +splitServerMethod SProgress = IsServerNot +splitServerMethod STelemetryEvent = IsServerNot +splitServerMethod SClientRegisterCapability = IsServerReq +splitServerMethod SClientUnregisterCapability = IsServerReq +splitServerMethod SWorkspaceWorkspaceFolders = IsServerReq +splitServerMethod SWorkspaceConfiguration = IsServerReq +splitServerMethod SWorkspaceApplyEdit = IsServerReq +splitServerMethod STextDocumentPublishDiagnostics = IsServerNot +splitServerMethod SCancelRequest = IsServerNot +splitServerMethod SCustomMethod{} = IsServerEither diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/MessageFuncs.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/MessageFuncs.hs deleted file mode 100644 index c223e31e1..000000000 --- a/haskell-lsp-types/src/Language/Haskell/LSP/Types/MessageFuncs.hs +++ /dev/null @@ -1,341 +0,0 @@ -{-# LANGUAGE GADTs #-} -{-# LANGUAGE MultiWayIf #-} -{-# LANGUAGE BinaryLiterals #-} -{-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE RankNTypes #-} -{-# LANGUAGE ScopedTypeVariables #-} - -module Language.Haskell.LSP.Types.MessageFuncs ( - -- * General - fmClientInitializeRequest - , fmClientInitializedNotification - , fmClientShutdownRequest - , fmClientExitNotification - , fmClientCancelNotification - - -- * Window - , fmServerShowMessageNotification - , fmServerShowMessageRequest - , fmServerLogMessageNotification - , fmServerWorkDoneProgressBeginNotification - , fmServerWorkDoneProgressReportNotification - , fmServerWorkDoneProgressEndNotification - , fmServerWorkDoneProgressCreateRequest - , fmServerTelemetryNotification - - -- * Client - , fmServerRegisterCapabilityRequest - , fmServerUnregisterCapabilityRequest - - -- * Workspace - , fmClientDidChangeConfigurationNotification - , fmClientDidChangeWatchedFilesNotification - , fmClientWorkspaceSymbolRequest - , fmClientExecuteCommandRequest - , fmServerApplyWorkspaceEditRequest - - -- * Document - , fmServerPublishDiagnosticsNotification - , fmClientDidOpenTextDocumentNotification - , fmClientDidChangeTextDocumentNotification - , fmClientWillSaveTextDocumentNotification - , fmClientWillSaveWaitUntilRequest - , fmClientDidSaveTextDocumentNotification - , fmClientDidCloseTextDocumentNotification - , fmClientCompletionRequest - , fmClientCompletionItemResolveRequest - , fmClientHoverRequest - , fmClientSignatureHelpRequest - , fmClientReferencesRequest - , fmClientDocumentHighlightRequest - , fmClientDocumentSymbolRequest - , fmClientDocumentFormattingRequest - , fmClientDocumentRangeFormattingRequest - , fmClientDocumentOnTypeFormattingRequest - , fmClientDefinitionRequest - , fmClientCodeActionRequest - , fmClientCodeLensRequest - , fmClientCodeLensResolveRequest - , fmClientDocumentLinkRequest - , fmClientDocumentLinkResolveRequest - , fmClientRenameRequest - , fmClientPrepareRenameRequest - ) where - -import qualified Data.Aeson as J -import Data.Text ( Text ) -import qualified Language.Haskell.LSP.Types as J - --- --------------------------------------------------------------------- -{-# ANN module ("HLint: ignore Eta reduce" :: String) #-} -{-# ANN module ("HLint: ignore Redundant do" :: String) #-} -{-# ANN module ("HLint: ignore Reduce duplication" :: String) #-} --- --------------------------------------------------------------------- - --- ---------------------------------------------------------------------- --- General --- ---------------------------------------------------------------------- - --- * :leftwards_arrow_with_hook: [initialize](#initialize) - -fmClientInitializeRequest :: J.LspId -> J.InitializeParams -> J.InitializeRequest -fmClientInitializeRequest rid params - = J.RequestMessage "2.0" rid J.Initialize params - --- ---------------------------------------------------------------------- --- * **New** :arrow_right: [initialized](#initialized) - --- | From 3.0 -fmClientInitializedNotification :: J.InitializedNotification -fmClientInitializedNotification = J.NotificationMessage "2.0" J.Initialized Nothing - --- ---------------------------------------------------------------------- --- * :leftwards_arrow_with_hook: [shutdown](#shutdown) - -fmClientShutdownRequest :: J.LspId -> Maybe J.Value -> J.ShutdownRequest -fmClientShutdownRequest rid params - = J.RequestMessage "2.0" rid J.Shutdown params - --- ---------------------------------------------------------------------- --- * :arrow_right: [exit](#exit) - -fmClientExitNotification :: J.ExitNotification -fmClientExitNotification = J.NotificationMessage "2.0" J.Exit Nothing - --- ---------------------------------------------------------------------- --- * :arrow_right: [$/cancelRequest](#cancelRequest) - -fmClientCancelNotification :: J.LspId -> J.CancelNotification -fmClientCancelNotification idToCancel - = J.NotificationMessage "2.0" J.CancelRequest (J.CancelParams idToCancel) - --- ---------------------------------------------------------------------- --- Window --- ---------------------------------------------------------------------- - --- * :arrow_left: [window/showMessage](#window_showMessage) - -fmServerShowMessageNotification :: J.MessageType -> Text -> J.ShowMessageNotification -fmServerShowMessageNotification mt msg - = J.NotificationMessage "2.0" J.WindowShowMessage (J.ShowMessageParams mt msg) - --- ---------------------------------------------------------------------- --- * :arrow_right_hook: [window/showMessageRequest](#window_showMessageRequest) - -fmServerShowMessageRequest :: J.LspId -> J.ShowMessageRequestParams -> J.ShowMessageRequest -fmServerShowMessageRequest rid params - = J.RequestMessage "2.0" rid J.WindowShowMessageRequest params - --- ---------------------------------------------------------------------- --- * :arrow_left: [window/logMessage](#window_logMessage) - -fmServerLogMessageNotification :: J.MessageType -> Text -> J.LogMessageNotification -fmServerLogMessageNotification mt msg - = J.NotificationMessage "2.0" J.WindowLogMessage (J.LogMessageParams mt msg) - --- ---------------------------------------------------------------------- - -fmServerWorkDoneProgressBeginNotification :: J.ProgressParams J.WorkDoneProgressBeginParams -> J.WorkDoneProgressBeginNotification -fmServerWorkDoneProgressBeginNotification params - = J.NotificationMessage "2.0" J.Progress params - --- ---------------------------------------------------------------------- - -fmServerWorkDoneProgressReportNotification :: J.ProgressParams J.WorkDoneProgressReportParams -> J.WorkDoneProgressReportNotification -fmServerWorkDoneProgressReportNotification params - = J.NotificationMessage "2.0" J.Progress params - --- ---------------------------------------------------------------------- - -fmServerWorkDoneProgressEndNotification :: J.ProgressParams J.WorkDoneProgressEndParams -> J.WorkDoneProgressEndNotification -fmServerWorkDoneProgressEndNotification params - = J.NotificationMessage "2.0" J.Progress params - -fmServerWorkDoneProgressCreateRequest :: J.LspId -> J.WorkDoneProgressCreateParams -> J.WorkDoneProgressCreateRequest -fmServerWorkDoneProgressCreateRequest rid params - = J.RequestMessage "2.0" rid J.WindowWorkDoneProgressCreate params - --- ---------------------------------------------------------------------- --- * :arrow_left: [telemetry/event](#telemetry_event) - -fmServerTelemetryNotification :: J.Value -> J.TelemetryNotification -fmServerTelemetryNotification params - = J.NotificationMessage "2.0" J.TelemetryEvent params - --- ---------------------------------------------------------------------- --- Client --- ---------------------------------------------------------------------- - --- * :arrow_right_hook: [client/registerCapability](#client_registerCapability) --- | from 3.0 -fmServerRegisterCapabilityRequest :: J.LspId -> J.RegistrationParams -> J.RegisterCapabilityRequest -fmServerRegisterCapabilityRequest rid params - = J.RequestMessage "2.0" rid J.ClientRegisterCapability params - --- * :arrow_right_hook: [client/unregisterCapability](#client_unregisterCapability) --- | from 3.0 -fmServerUnregisterCapabilityRequest :: J.LspId -> J.UnregistrationParams -> J.UnregisterCapabilityRequest -fmServerUnregisterCapabilityRequest rid params - = J.RequestMessage "2.0" rid J.ClientUnregisterCapability params - --- ---------------------------------------------------------------------- --- Workspace --- ---------------------------------------------------------------------- - --- * :arrow_right: [workspace/didChangeConfiguration](#workspace_didChangeConfiguration) -fmClientDidChangeConfigurationNotification :: J.DidChangeConfigurationParams -> J.DidChangeConfigurationNotification -fmClientDidChangeConfigurationNotification params - = J.NotificationMessage "2.0" J.WorkspaceDidChangeConfiguration params - --- * :arrow_right: [workspace/didChangeWatchedFiles](#workspace_didChangeWatchedFiles) -fmClientDidChangeWatchedFilesNotification :: J.DidChangeWatchedFilesParams -> J.DidChangeWatchedFilesNotification -fmClientDidChangeWatchedFilesNotification params - = J.NotificationMessage "2.0" J.WorkspaceDidChangeWatchedFiles params - --- * :leftwards_arrow_with_hook: [workspace/symbol](#workspace_symbol) -fmClientWorkspaceSymbolRequest :: J.LspId -> J.WorkspaceSymbolParams -> J.WorkspaceSymbolRequest -fmClientWorkspaceSymbolRequest rid params - = J.RequestMessage "2.0" rid J.WorkspaceSymbol params - --- * **New** :leftwards_arrow_with_hook: [workspace/executeCommand](#workspace_executeCommand) --- | From 3.0 -fmClientExecuteCommandRequest :: J.LspId -> J.ExecuteCommandParams -> J.ExecuteCommandRequest -fmClientExecuteCommandRequest rid params - = J.RequestMessage "2.0" rid J.WorkspaceExecuteCommand params - --- * **New** :arrow_right_hook: [workspace/applyEdit](#workspace_applyEdit) --- | From 3.0 -fmServerApplyWorkspaceEditRequest :: J.LspId -> J.ApplyWorkspaceEditParams -> J.ApplyWorkspaceEditRequest -fmServerApplyWorkspaceEditRequest rid params - = J.RequestMessage "2.0" rid J.WorkspaceApplyEdit params - --- ---------------------------------------------------------------------- - -- Document --- ---------------------------------------------------------------------- - --- * :arrow_left: [textDocument/publishDiagnostics](#textDocument_publishDiagnostics) -fmServerPublishDiagnosticsNotification :: J.PublishDiagnosticsParams -> J.PublishDiagnosticsNotification -fmServerPublishDiagnosticsNotification params - = J.NotificationMessage "2.0" J.TextDocumentPublishDiagnostics params - --- * :arrow_right: [textDocument/didOpen](#textDocument_didOpen) -fmClientDidOpenTextDocumentNotification :: J.DidOpenTextDocumentParams -> J.DidOpenTextDocumentNotification -fmClientDidOpenTextDocumentNotification params - = J.NotificationMessage "2.0" J.TextDocumentDidOpen params - --- * :arrow_right: [textDocument/didChange](#textDocument_didChange) -fmClientDidChangeTextDocumentNotification :: J.DidChangeTextDocumentParams -> J.DidChangeTextDocumentNotification -fmClientDidChangeTextDocumentNotification params - = J.NotificationMessage "2.0" J.TextDocumentDidChange params - --- * :arrow_right: [textDocument/willSave](#textDocument_willSave) -fmClientWillSaveTextDocumentNotification :: J.WillSaveTextDocumentParams -> J.WillSaveTextDocumentNotification -fmClientWillSaveTextDocumentNotification params - = J.NotificationMessage "2.0" J.TextDocumentWillSave params - --- * **New** :leftwards_arrow_with_hook: [textDocument/willSaveWaitUntil](#textDocument_willSaveWaitUntil) --- | From 3.0 -fmClientWillSaveWaitUntilRequest :: J.LspId -> J.WillSaveTextDocumentParams -> J.WillSaveWaitUntilTextDocumentRequest -fmClientWillSaveWaitUntilRequest rid params - = J.RequestMessage "2.0" rid J.TextDocumentWillSaveWaitUntil params - --- * **New** :arrow_right: [textDocument/didSave](#textDocument_didSave) --- | 3.0 -fmClientDidSaveTextDocumentNotification :: J.DidSaveTextDocumentParams -> J.DidSaveTextDocumentNotification -fmClientDidSaveTextDocumentNotification params - = J.NotificationMessage "2.0" J.TextDocumentDidSave params - --- * :arrow_right: [textDocument/didClose](#textDocument_didClose) -fmClientDidCloseTextDocumentNotification :: J.DidCloseTextDocumentParams -> J.DidCloseTextDocumentNotification -fmClientDidCloseTextDocumentNotification params - = J.NotificationMessage "2.0" J.TextDocumentDidClose params - --- * :leftwards_arrow_with_hook: [textDocument/completion](#textDocument_completion) -fmClientCompletionRequest :: J.LspId -> J.CompletionParams -> J.CompletionRequest -fmClientCompletionRequest rid params - = J.RequestMessage "2.0" rid J.TextDocumentCompletion params - --- * :leftwards_arrow_with_hook: [completionItem/resolve](#completionItem_resolve) -fmClientCompletionItemResolveRequest :: J.LspId -> J.CompletionItem -> J.CompletionItemResolveRequest -fmClientCompletionItemResolveRequest rid params - = J.RequestMessage "2.0" rid J.CompletionItemResolve params - --- * :leftwards_arrow_with_hook: [textDocument/hover](#textDocument_hover) -fmClientHoverRequest :: J.LspId -> J.TextDocumentPositionParams -> J.HoverRequest -fmClientHoverRequest rid params - = J.RequestMessage "2.0" rid J.TextDocumentHover params - --- * :leftwards_arrow_with_hook: [textDocument/signatureHelp](#textDocument_signatureHelp) -fmClientSignatureHelpRequest :: J.LspId -> J.TextDocumentPositionParams -> J.SignatureHelpRequest -fmClientSignatureHelpRequest rid params - = J.RequestMessage "2.0" rid J.TextDocumentSignatureHelp params - --- * :leftwards_arrow_with_hook: [textDocument/references](#textDocument_references) -fmClientReferencesRequest :: J.LspId -> J.ReferenceParams -> J.ReferencesRequest -fmClientReferencesRequest rid params - = J.RequestMessage "2.0" rid J.TextDocumentReferences params - --- * :leftwards_arrow_with_hook: [textDocument/documentHighlight](#textDocument_documentHighlight) -fmClientDocumentHighlightRequest :: J.LspId -> J.TextDocumentPositionParams -> J.DocumentHighlightRequest -fmClientDocumentHighlightRequest rid params - = J.RequestMessage "2.0" rid J.TextDocumentDocumentHighlight params - --- * :leftwards_arrow_with_hook: [textDocument/documentSymbol](#textDocument_documentSymbol) -fmClientDocumentSymbolRequest :: J.LspId -> J.DocumentSymbolParams -> J.DocumentSymbolRequest -fmClientDocumentSymbolRequest rid params - = J.RequestMessage "2.0" rid J.TextDocumentDocumentSymbol params - --- * :leftwards_arrow_with_hook: [textDocument/formatting](#textDocument_formatting) -fmClientDocumentFormattingRequest :: J.LspId -> J.DocumentFormattingParams -> J.DocumentFormattingRequest -fmClientDocumentFormattingRequest rid params - = J.RequestMessage "2.0" rid J.TextDocumentFormatting params - --- * :leftwards_arrow_with_hook: [textDocument/rangeFormatting](#textDocument_rangeFormatting) -fmClientDocumentRangeFormattingRequest :: J.LspId -> J.DocumentRangeFormattingParams -> J.DocumentRangeFormattingRequest -fmClientDocumentRangeFormattingRequest rid params - = J.RequestMessage "2.0" rid J.TextDocumentRangeFormatting params - --- * :leftwards_arrow_with_hook: [textDocument/onTypeFormatting](#textDocument_onTypeFormatting) -fmClientDocumentOnTypeFormattingRequest :: J.LspId -> J.DocumentOnTypeFormattingParams -> J.DocumentOnTypeFormattingRequest -fmClientDocumentOnTypeFormattingRequest rid params - = J.RequestMessage "2.0" rid J.TextDocumentOnTypeFormatting params - --- * :leftwards_arrow_with_hook: [textDocument/definition](#textDocument_definition) -fmClientDefinitionRequest :: J.LspId -> J.TextDocumentPositionParams -> J.DefinitionRequest -fmClientDefinitionRequest rid params - = J.RequestMessage "2.0" rid J.TextDocumentDefinition params - --- * :leftwards_arrow_with_hook: [textDocument/codeAction](#textDocument_codeAction) -fmClientCodeActionRequest :: J.LspId -> J.CodeActionParams -> J.CodeActionRequest -fmClientCodeActionRequest rid params - = J.RequestMessage "2.0" rid J.TextDocumentCodeAction params - --- * :leftwards_arrow_with_hook: [textDocument/codeLens](#textDocument_codeLens) -fmClientCodeLensRequest :: J.LspId -> J.CodeLensParams -> J.CodeLensRequest -fmClientCodeLensRequest rid params - = J.RequestMessage "2.0" rid J.TextDocumentCodeLens params - --- * :leftwards_arrow_with_hook: [codeLens/resolve](#codeLens_resolve) -fmClientCodeLensResolveRequest :: J.LspId -> J.CodeLens -> J.CodeLensResolveRequest -fmClientCodeLensResolveRequest rid params - = J.RequestMessage "2.0" rid J.CodeLensResolve params - --- * :leftwards_arrow_with_hook: [textDocument/documentLink](#textDocument_documentLink) -fmClientDocumentLinkRequest :: J.LspId -> J.DocumentLinkParams -> J.DocumentLinkRequest -fmClientDocumentLinkRequest rid params - = J.RequestMessage "2.0" rid J.TextDocumentDocumentLink params - --- * :leftwards_arrow_with_hook: [documentLink/resolve](#documentLink_resolve) -fmClientDocumentLinkResolveRequest :: J.LspId -> J.DocumentLink -> J.DocumentLinkResolveRequest -fmClientDocumentLinkResolveRequest rid params - = J.RequestMessage "2.0" rid J.DocumentLinkResolve params - --- * :leftwards_arrow_with_hook: [textDocument/rename](#textDocument_rename) -fmClientRenameRequest :: J.LspId -> J.RenameParams -> J.RenameRequest -fmClientRenameRequest rid params - = J.RequestMessage "2.0" rid J.TextDocumentRename params - --- * :leftwards_arrow_with_hook: [textDocument/prepareRename](#textDocument_prepareRename) -fmClientPrepareRenameRequest :: J.LspId -> J.TextDocumentPositionParams -> J.PrepareRenameRequest -fmClientPrepareRenameRequest rid params - = J.RequestMessage "2.0" rid J.TextDocumentPrepareRename params diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/Method.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Method.hs new file mode 100644 index 000000000..6d11c567a --- /dev/null +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Method.hs @@ -0,0 +1,385 @@ +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE GADTs #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE TypeInType #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE StandaloneDeriving #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# OPTIONS_GHC -Wno-unticked-promoted-constructors #-} +module Language.Haskell.LSP.Types.Method where + +import qualified Data.Aeson as A +import Data.Aeson.Types +import Data.Text (Text) +import Language.Haskell.LSP.Types.Utils +import Data.Function (on) +import Control.Applicative +import Data.GADT.Compare.TH + +-- --------------------------------------------------------------------- + +data From = FromServer | FromClient +data MethodType = Notification | Request + +data Method (f :: From) (t :: MethodType) where +-- Client Methods + -- General + Initialize :: Method FromClient Request + Initialized :: Method FromClient Notification + Shutdown :: Method FromClient Request + Exit :: Method FromClient Notification + -- Workspace + WorkspaceDidChangeWorkspaceFolders :: Method FromClient Notification + WorkspaceDidChangeConfiguration :: Method FromClient Notification + WorkspaceDidChangeWatchedFiles :: Method FromClient Notification + WorkspaceSymbol :: Method FromClient Request + WorkspaceExecuteCommand :: Method FromClient Request + -- Document + TextDocumentDidOpen :: Method FromClient Notification + TextDocumentDidChange :: Method FromClient Notification + TextDocumentWillSave :: Method FromClient Notification + TextDocumentWillSaveWaitUntil :: Method FromClient Request + TextDocumentDidSave :: Method FromClient Notification + TextDocumentDidClose :: Method FromClient Notification + -- Completion + TextDocumentCompletion :: Method FromClient Request + CompletionItemResolve :: Method FromClient Request + -- LanguageQueries + TextDocumentHover :: Method FromClient Request + TextDocumentSignatureHelp :: Method FromClient Request + TextDocumentDeclaration :: Method FromClient Request + TextDocumentDefinition :: Method FromClient Request + TextDocumentTypeDefinition :: Method FromClient Request + TextDocumentImplementation :: Method FromClient Request + TextDocumentReferences :: Method FromClient Request + TextDocumentDocumentHighlight :: Method FromClient Request + TextDocumentDocumentSymbol :: Method FromClient Request + -- Code Action/Lens/Link + TextDocumentCodeAction :: Method FromClient Request + TextDocumentCodeLens :: Method FromClient Request + CodeLensResolve :: Method FromClient Request + TextDocumentDocumentLink :: Method FromClient Request + DocumentLinkResolve :: Method FromClient Request + -- Syntax highlighting/Coloring + TextDocumentDocumentColor :: Method FromClient Request + TextDocumentColorPresentation :: Method FromClient Request + -- Formatting + TextDocumentFormatting :: Method FromClient Request + TextDocumentRangeFormatting :: Method FromClient Request + TextDocumentOnTypeFormatting :: Method FromClient Request + -- Rename + TextDocumentRename :: Method FromClient Request + TextDocumentPrepareRename :: Method FromClient Request + -- FoldingRange + TextDocumentFoldingRange :: Method FromClient Request + TextDocumentSelectionRange :: Method FromClient Request + +-- ServerMethods + -- Window + WindowShowMessage :: Method FromServer Notification + WindowShowMessageRequest :: Method FromServer Request + WindowLogMessage :: Method FromServer Notification + WindowWorkDoneProgressCancel :: Method FromClient Notification + WindowWorkDoneProgressCreate :: Method FromServer Request + -- Progress + Progress :: Method FromServer Notification + -- Telemetry + TelemetryEvent :: Method FromServer Notification + -- Client + ClientRegisterCapability :: Method FromServer Request + ClientUnregisterCapability :: Method FromServer Request + -- Workspace + WorkspaceWorkspaceFolders :: Method FromServer Request + WorkspaceConfiguration :: Method FromServer Request + WorkspaceApplyEdit :: Method FromServer Request + -- Document + TextDocumentPublishDiagnostics :: Method FromServer Notification + +-- Cancelling + CancelRequest :: Method f Notification + +-- Custom + -- A custom message type. It is not enforced that this starts with $/. + CustomMethod :: Method f t + +data SMethod (m :: Method f t) where + SInitialize :: SMethod Initialize + SInitialized :: SMethod Initialized + SShutdown :: SMethod Shutdown + SExit :: SMethod Exit + SWorkspaceDidChangeWorkspaceFolders :: SMethod WorkspaceDidChangeWorkspaceFolders + SWorkspaceDidChangeConfiguration :: SMethod WorkspaceDidChangeConfiguration + SWorkspaceDidChangeWatchedFiles :: SMethod WorkspaceDidChangeWatchedFiles + SWorkspaceSymbol :: SMethod WorkspaceSymbol + SWorkspaceExecuteCommand :: SMethod WorkspaceExecuteCommand + STextDocumentDidOpen :: SMethod TextDocumentDidOpen + STextDocumentDidChange :: SMethod TextDocumentDidChange + STextDocumentWillSave :: SMethod TextDocumentWillSave + STextDocumentWillSaveWaitUntil :: SMethod TextDocumentWillSaveWaitUntil + STextDocumentDidSave :: SMethod TextDocumentDidSave + STextDocumentDidClose :: SMethod TextDocumentDidClose + STextDocumentCompletion :: SMethod TextDocumentCompletion + SCompletionItemResolve :: SMethod CompletionItemResolve + STextDocumentHover :: SMethod TextDocumentHover + STextDocumentSignatureHelp :: SMethod TextDocumentSignatureHelp + STextDocumentDeclaration :: SMethod TextDocumentDeclaration + STextDocumentDefinition :: SMethod TextDocumentDefinition + STextDocumentTypeDefinition :: SMethod TextDocumentTypeDefinition + STextDocumentImplementation :: SMethod TextDocumentImplementation + STextDocumentReferences :: SMethod TextDocumentReferences + STextDocumentDocumentHighlight :: SMethod TextDocumentDocumentHighlight + STextDocumentDocumentSymbol :: SMethod TextDocumentDocumentSymbol + STextDocumentCodeAction :: SMethod TextDocumentCodeAction + STextDocumentCodeLens :: SMethod TextDocumentCodeLens + SCodeLensResolve :: SMethod CodeLensResolve + STextDocumentDocumentLink :: SMethod TextDocumentDocumentLink + SDocumentLinkResolve :: SMethod DocumentLinkResolve + STextDocumentDocumentColor :: SMethod TextDocumentDocumentColor + STextDocumentColorPresentation :: SMethod TextDocumentColorPresentation + STextDocumentFormatting :: SMethod TextDocumentFormatting + STextDocumentRangeFormatting :: SMethod TextDocumentRangeFormatting + STextDocumentOnTypeFormatting :: SMethod TextDocumentOnTypeFormatting + STextDocumentRename :: SMethod TextDocumentRename + STextDocumentPrepareRename :: SMethod TextDocumentPrepareRename + STextDocumentFoldingRange :: SMethod TextDocumentFoldingRange + STextDocumentSelectionRange :: SMethod TextDocumentSelectionRange + + SWindowShowMessage :: SMethod WindowShowMessage + SWindowShowMessageRequest :: SMethod WindowShowMessageRequest + SWindowLogMessage :: SMethod WindowLogMessage + SWindowWorkDoneProgressCreate :: SMethod WindowWorkDoneProgressCreate + SWindowWorkDoneProgressCancel :: SMethod WindowWorkDoneProgressCancel + SProgress :: SMethod Progress + STelemetryEvent :: SMethod TelemetryEvent + SClientRegisterCapability :: SMethod ClientRegisterCapability + SClientUnregisterCapability :: SMethod ClientUnregisterCapability + SWorkspaceWorkspaceFolders :: SMethod WorkspaceWorkspaceFolders + SWorkspaceConfiguration :: SMethod WorkspaceConfiguration + SWorkspaceApplyEdit :: SMethod WorkspaceApplyEdit + STextDocumentPublishDiagnostics :: SMethod TextDocumentPublishDiagnostics + + SCancelRequest :: SMethod CancelRequest + SCustomMethod :: Text -> SMethod CustomMethod + +deriveGEq ''SMethod +deriveGCompare ''SMethod + +deriving instance Eq (SMethod m) +deriving instance Ord (SMethod m) +deriving instance Show (SMethod m) + +-- Some useful type synonyms +type SClientMethod (m :: Method FromClient t) = SMethod m +type SServerMethod (m :: Method FromServer t) = SMethod m + +data SomeClientMethod = forall t (m :: Method FromClient t). SomeClientMethod (SMethod m) +data SomeServerMethod = forall t (m :: Method FromServer t). SomeServerMethod (SMethod m) + +data SomeMethod where + SomeMethod :: forall m. SMethod m -> SomeMethod + +deriving instance Show SomeMethod +instance Eq SomeMethod where + (==) = (==) `on` toJSON +instance Ord SomeMethod where + compare = compare `on` (getString . toJSON) + where + getString (A.String t) = t + getString _ = error "ToJSON instance for some method isn't string" +deriving instance Show SomeClientMethod +instance Eq SomeClientMethod where + (==) = (==) `on` toJSON +instance Ord SomeClientMethod where + compare = compare `on` (getString . toJSON) + where + getString (A.String t) = t + getString _ = error "ToJSON instance for some method isn't string" +deriving instance Show SomeServerMethod +instance Eq SomeServerMethod where + (==) = (==) `on` toJSON +instance Ord SomeServerMethod where + compare = compare `on` (getString . toJSON) + where + getString (A.String t) = t + getString _ = error "ToJSON instance for some method isn't string" + +-- --------------------------------------------------------------------- +-- From JSON +-- --------------------------------------------------------------------- + +instance FromJSON SomeMethod where + parseJSON v = client <|> server + where + client = do + c <- parseJSON v + case c of + -- Don't parse the client custom method so that we can still + -- parse the server methods + SomeClientMethod (SCustomMethod _) -> mempty + SomeClientMethod m -> pure $ SomeMethod m + server = do + c <- parseJSON v + case c of + SomeServerMethod m -> pure $ SomeMethod m + +instance FromJSON SomeClientMethod where + -- General + parseJSON (A.String "initialize") = pure $ SomeClientMethod SInitialize + parseJSON (A.String "initialized") = pure $ SomeClientMethod SInitialized + parseJSON (A.String "shutdown") = pure $ SomeClientMethod SShutdown + parseJSON (A.String "exit") = pure $ SomeClientMethod SExit + -- Workspace + parseJSON (A.String "workspace/didChangeWorkspaceFolders") = pure $ SomeClientMethod SWorkspaceDidChangeWorkspaceFolders + parseJSON (A.String "workspace/didChangeConfiguration") = pure $ SomeClientMethod SWorkspaceDidChangeConfiguration + parseJSON (A.String "workspace/didChangeWatchedFiles") = pure $ SomeClientMethod SWorkspaceDidChangeWatchedFiles + parseJSON (A.String "workspace/symbol") = pure $ SomeClientMethod SWorkspaceSymbol + parseJSON (A.String "workspace/executeCommand") = pure $ SomeClientMethod SWorkspaceExecuteCommand + -- Document + parseJSON (A.String "textDocument/didOpen") = pure $ SomeClientMethod STextDocumentDidOpen + parseJSON (A.String "textDocument/didChange") = pure $ SomeClientMethod STextDocumentDidChange + parseJSON (A.String "textDocument/willSave") = pure $ SomeClientMethod STextDocumentWillSave + parseJSON (A.String "textDocument/willSaveWaitUntil") = pure $ SomeClientMethod STextDocumentWillSaveWaitUntil + parseJSON (A.String "textDocument/didSave") = pure $ SomeClientMethod STextDocumentDidSave + parseJSON (A.String "textDocument/didClose") = pure $ SomeClientMethod STextDocumentDidClose + parseJSON (A.String "textDocument/completion") = pure $ SomeClientMethod STextDocumentCompletion + parseJSON (A.String "completionItem/resolve") = pure $ SomeClientMethod SCompletionItemResolve + parseJSON (A.String "textDocument/hover") = pure $ SomeClientMethod STextDocumentHover + parseJSON (A.String "textDocument/signatureHelp") = pure $ SomeClientMethod STextDocumentSignatureHelp + parseJSON (A.String "textDocument/declaration") = pure $ SomeClientMethod STextDocumentDeclaration + parseJSON (A.String "textDocument/definition") = pure $ SomeClientMethod STextDocumentDefinition + parseJSON (A.String "textDocument/typeDefinition") = pure $ SomeClientMethod STextDocumentTypeDefinition + parseJSON (A.String "textDocument/implementation") = pure $ SomeClientMethod STextDocumentImplementation + parseJSON (A.String "textDocument/references") = pure $ SomeClientMethod STextDocumentReferences + parseJSON (A.String "textDocument/documentHighlight") = pure $ SomeClientMethod STextDocumentDocumentHighlight + parseJSON (A.String "textDocument/documentSymbol") = pure $ SomeClientMethod STextDocumentDocumentSymbol + parseJSON (A.String "textDocument/codeAction") = pure $ SomeClientMethod STextDocumentCodeAction + parseJSON (A.String "textDocument/codeLens") = pure $ SomeClientMethod STextDocumentCodeLens + parseJSON (A.String "codeLens/resolve") = pure $ SomeClientMethod SCodeLensResolve + parseJSON (A.String "textDocument/documentLink") = pure $ SomeClientMethod STextDocumentDocumentLink + parseJSON (A.String "documentLink/resolve") = pure $ SomeClientMethod SDocumentLinkResolve + parseJSON (A.String "textDocument/documentColor") = pure $ SomeClientMethod STextDocumentDocumentColor + parseJSON (A.String "textDocument/colorPresentation") = pure $ SomeClientMethod STextDocumentColorPresentation + parseJSON (A.String "textDocument/formatting") = pure $ SomeClientMethod STextDocumentFormatting + parseJSON (A.String "textDocument/rangeFormatting") = pure $ SomeClientMethod STextDocumentRangeFormatting + parseJSON (A.String "textDocument/onTypeFormatting") = pure $ SomeClientMethod STextDocumentOnTypeFormatting + parseJSON (A.String "textDocument/rename") = pure $ SomeClientMethod STextDocumentRename + parseJSON (A.String "textDocument/prepareRename") = pure $ SomeClientMethod STextDocumentPrepareRename + parseJSON (A.String "textDocument/foldingRange") = pure $ SomeClientMethod STextDocumentFoldingRange + parseJSON (A.String "textDocument/selectionRange") = pure $ SomeClientMethod STextDocumentFoldingRange + parseJSON (A.String "window/workDoneProgress/cancel") = pure $ SomeClientMethod SWindowWorkDoneProgressCancel +-- Cancelling + parseJSON (A.String "$/cancelRequest") = pure $ SomeClientMethod SCancelRequest +-- Custom + parseJSON (A.String m) = pure $ SomeClientMethod (SCustomMethod m) + parseJSON _ = mempty + +instance A.FromJSON SomeServerMethod where +-- Server + -- Window + parseJSON (A.String "window/showMessage") = pure $ SomeServerMethod SWindowShowMessage + parseJSON (A.String "window/showMessageRequest") = pure $ SomeServerMethod SWindowShowMessageRequest + parseJSON (A.String "window/logMessage") = pure $ SomeServerMethod SWindowLogMessage + parseJSON (A.String "window/workDoneProgress/create") = pure $ SomeServerMethod SWindowWorkDoneProgressCreate + parseJSON (A.String "$/progress") = pure $ SomeServerMethod SProgress + parseJSON (A.String "telemetry/event") = pure $ SomeServerMethod STelemetryEvent + -- Client + parseJSON (A.String "client/registerCapability") = pure $ SomeServerMethod SClientRegisterCapability + parseJSON (A.String "client/unregisterCapability") = pure $ SomeServerMethod SClientUnregisterCapability + -- Workspace + parseJSON (A.String "workspace/workspaceFolders") = pure $ SomeServerMethod SWorkspaceWorkspaceFolders + parseJSON (A.String "workspace/configuration") = pure $ SomeServerMethod SWorkspaceConfiguration + parseJSON (A.String "workspace/applyEdit") = pure $ SomeServerMethod SWorkspaceApplyEdit + -- Document + parseJSON (A.String "textDocument/publishDiagnostics") = pure $ SomeServerMethod STextDocumentPublishDiagnostics + +-- Cancelling + parseJSON (A.String "$/cancelRequest") = pure $ SomeServerMethod SCancelRequest + +-- Custom + parseJSON (A.String m) = pure $ SomeServerMethod (SCustomMethod m) + parseJSON _ = mempty + +-- instance FromJSON (SMethod m) +makeSingletonFromJSON 'SomeMethod ''SMethod + +-- --------------------------------------------------------------------- +-- TO JSON +-- --------------------------------------------------------------------- + +instance ToJSON SomeMethod where + toJSON (SomeMethod m) = toJSON m + +instance ToJSON SomeClientMethod where + toJSON (SomeClientMethod m) = toJSON m +instance ToJSON SomeServerMethod where + toJSON (SomeServerMethod m) = toJSON m + +instance A.ToJSON (SMethod m) where +-- Client + -- General + toJSON SInitialize = A.String "initialize" + toJSON SInitialized = A.String "initialized" + toJSON SShutdown = A.String "shutdown" + toJSON SExit = A.String "exit" + -- Workspace + toJSON SWorkspaceDidChangeWorkspaceFolders = A.String "workspace/didChangeWorkspaceFolders" + toJSON SWorkspaceDidChangeConfiguration = A.String "workspace/didChangeConfiguration" + toJSON SWorkspaceDidChangeWatchedFiles = A.String "workspace/didChangeWatchedFiles" + toJSON SWorkspaceSymbol = A.String "workspace/symbol" + toJSON SWorkspaceExecuteCommand = A.String "workspace/executeCommand" + -- Document + toJSON STextDocumentDidOpen = A.String "textDocument/didOpen" + toJSON STextDocumentDidChange = A.String "textDocument/didChange" + toJSON STextDocumentWillSave = A.String "textDocument/willSave" + toJSON STextDocumentWillSaveWaitUntil = A.String "textDocument/willSaveWaitUntil" + toJSON STextDocumentDidSave = A.String "textDocument/didSave" + toJSON STextDocumentDidClose = A.String "textDocument/didClose" + toJSON STextDocumentCompletion = A.String "textDocument/completion" + toJSON SCompletionItemResolve = A.String "completionItem/resolve" + toJSON STextDocumentHover = A.String "textDocument/hover" + toJSON STextDocumentSignatureHelp = A.String "textDocument/signatureHelp" + toJSON STextDocumentReferences = A.String "textDocument/references" + toJSON STextDocumentDocumentHighlight = A.String "textDocument/documentHighlight" + toJSON STextDocumentDocumentSymbol = A.String "textDocument/documentSymbol" + toJSON STextDocumentDeclaration = A.String "textDocument/declaration" + toJSON STextDocumentDefinition = A.String "textDocument/definition" + toJSON STextDocumentTypeDefinition = A.String "textDocument/typeDefinition" + toJSON STextDocumentImplementation = A.String "textDocument/implementation" + toJSON STextDocumentCodeAction = A.String "textDocument/codeAction" + toJSON STextDocumentCodeLens = A.String "textDocument/codeLens" + toJSON SCodeLensResolve = A.String "codeLens/resolve" + toJSON STextDocumentDocumentColor = A.String "textDocument/documentColor" + toJSON STextDocumentColorPresentation = A.String "textDocument/colorPresentation" + toJSON STextDocumentFormatting = A.String "textDocument/formatting" + toJSON STextDocumentRangeFormatting = A.String "textDocument/rangeFormatting" + toJSON STextDocumentOnTypeFormatting = A.String "textDocument/onTypeFormatting" + toJSON STextDocumentRename = A.String "textDocument/rename" + toJSON STextDocumentPrepareRename = A.String "textDocument/prepareRename" + toJSON STextDocumentFoldingRange = A.String "textDocument/foldingRange" + toJSON STextDocumentSelectionRange = A.String "textDocument/selectionRange" + toJSON STextDocumentDocumentLink = A.String "textDocument/documentLink" + toJSON SDocumentLinkResolve = A.String "documentLink/resolve" + toJSON SWindowWorkDoneProgressCancel = A.String "window/workDoneProgress/cancel" +-- Server + -- Window + toJSON SWindowShowMessage = A.String "window/showMessage" + toJSON SWindowShowMessageRequest = A.String "window/showMessageRequest" + toJSON SWindowLogMessage = A.String "window/logMessage" + toJSON SWindowWorkDoneProgressCreate = A.String "window/workDoneProgress/create" + toJSON SProgress = A.String "$/progress" + toJSON STelemetryEvent = A.String "telemetry/event" + -- Client + toJSON SClientRegisterCapability = A.String "client/registerCapability" + toJSON SClientUnregisterCapability = A.String "client/unregisterCapability" + -- Workspace + toJSON SWorkspaceWorkspaceFolders = A.String "workspace/workspaceFolders" + toJSON SWorkspaceConfiguration = A.String "workspace/configuration" + toJSON SWorkspaceApplyEdit = A.String "workspace/applyEdit" + -- Document + toJSON STextDocumentPublishDiagnostics = A.String "textDocument/publishDiagnostics" + -- Cancelling + toJSON SCancelRequest = A.String "$/cancelRequest" +-- Custom + toJSON (SCustomMethod m) = A.String m diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/Progress.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Progress.hs index 433b114a9..f7411aa13 100644 --- a/haskell-lsp-types/src/Language/Haskell/LSP/Types/Progress.hs +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Progress.hs @@ -1,7 +1,18 @@ +{-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE DuplicateRecordFields #-} +{-# LANGUAGE DeriveFunctor #-} +{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE OverloadedStrings #-} + module Language.Haskell.LSP.Types.Progress where +import Control.Applicative +import Control.Monad (unless) import qualified Data.Aeson as A -import Data.Text (Text) +import Data.Aeson.TH +import Data.Maybe (catMaybes) +import Data.Text (Text) +import Language.Haskell.LSP.Types.Utils -- | A token used to report progress back or return partial results for a -- specific request. @@ -19,3 +30,201 @@ instance A.FromJSON ProgressToken where parseJSON (A.String t) = pure $ ProgressTextToken t parseJSON (A.Number i) = ProgressNumericToken <$> A.parseJSON (A.Number i) parseJSON v = fail $ "Invalid progress token: " ++ show v + +-- | Parameters for a $/progress notification. +data ProgressParams t = + ProgressParams { + _token :: ProgressToken + , _value :: t + } deriving (Show, Read, Eq, Functor) + +deriveJSON lspOptions ''ProgressParams + +data SomeProgressParams + = Begin WorkDoneProgressBeginParams + | Report WorkDoneProgressReportParams + | End WorkDoneProgressEndParams + deriving Eq + +instance A.FromJSON SomeProgressParams where + parseJSON x = + (Begin <$> A.parseJSON x) + <|> (Report <$> A.parseJSON x) + <|> (End <$> A.parseJSON x) + +instance A.ToJSON SomeProgressParams where + toJSON (Begin x) = A.toJSON x + toJSON (Report x) = A.toJSON x + toJSON (End x) = A.toJSON x + +-- | Parameters for 'WorkDoneProgressBeginNotification'. +-- +-- @since 0.10.0.0 +data WorkDoneProgressBeginParams = + WorkDoneProgressBeginParams { + -- | Mandatory title of the progress operation. + -- Used to briefly inform about the kind of operation being + -- performed. Examples: "Indexing" or "Linking dependencies". + _title :: Text + -- | Controls if a cancel button should show to allow the user to cancel the + -- long running operation. Clients that don't support cancellation are allowed + -- to ignore the setting. + , _cancellable :: Maybe Bool + -- | Optional, more detailed associated progress + -- message. Contains complementary information to the + -- '_title'. Examples: "3/25 files", + -- "project/src/module2", "node_modules/some_dep". If + -- unset, the previous progress message (if any) is + -- still valid. + , _message :: Maybe Text + -- | Optional progress percentage to display (value 100 is considered 100%). + -- If not provided infinite progress is assumed and clients are allowed + -- to ignore the '_percentage' value in subsequent in report notifications. + -- + -- The value should be steadily rising. Clients are free to ignore values + -- that are not following this rule. + , _percentage :: Maybe Double + } deriving (Show, Read, Eq) + +instance A.ToJSON WorkDoneProgressBeginParams where + toJSON WorkDoneProgressBeginParams{..} = + A.object $ catMaybes + [ Just $ "kind" A..= ("begin" :: Text) + , Just $ "title" A..= _title + , ("cancellable" A..=) <$> _cancellable + , ("message" A..=) <$> _message + , ("percentage" A..=) <$> _percentage + ] + +instance A.FromJSON WorkDoneProgressBeginParams where + parseJSON = A.withObject "WorkDoneProgressBegin" $ \o -> do + kind <- o A..: "kind" + unless (kind == ("begin" :: Text)) $ fail $ "Expected kind \"begin\" but got " ++ show kind + _title <- o A..: "title" + _cancellable <- o A..:? "cancellable" + _message <- o A..:? "message" + _percentage <- o A..:? "percentage" + pure WorkDoneProgressBeginParams{..} + +-- The $/progress begin notification is sent from the server to the +-- client to ask the client to start progress. +-- +-- @since 0.10.0.0 + +-- | Parameters for 'WorkDoneProgressReportNotification' +-- +-- @since 0.10.0.0 +data WorkDoneProgressReportParams = + WorkDoneProgressReportParams { + _cancellable :: Maybe Bool + -- | Optional, more detailed associated progress + -- message. Contains complementary information to the + -- '_title'. Examples: "3/25 files", + -- "project/src/module2", "node_modules/some_dep". If + -- unset, the previous progress message (if any) is + -- still valid. + , _message :: Maybe Text + -- | Optional progress percentage to display (value 100 is considered 100%). + -- If infinite progress was indicated in the start notification client + -- are allowed to ignore the value. In addition the value should be steadily + -- rising. Clients are free to ignore values that are not following this rule. + , _percentage :: Maybe Double + } deriving (Show, Read, Eq) + +instance A.ToJSON WorkDoneProgressReportParams where + toJSON WorkDoneProgressReportParams{..} = + A.object $ catMaybes + [ Just $ "kind" A..= ("report" :: Text) + , ("cancellable" A..=) <$> _cancellable + , ("message" A..=) <$> _message + , ("percentage" A..=) <$> _percentage + ] + +instance A.FromJSON WorkDoneProgressReportParams where + parseJSON = A.withObject "WorkDoneProgressReport" $ \o -> do + kind <- o A..: "kind" + unless (kind == ("report" :: Text)) $ fail $ "Expected kind \"report\" but got " ++ show kind + _cancellable <- o A..:? "cancellable" + _message <- o A..:? "message" + _percentage <- o A..:? "percentage" + pure WorkDoneProgressReportParams{..} + +-- The workdone $/progress report notification is sent from the server to the +-- client to report progress for a previously started progress. +-- +-- @since 0.10.0.0 + +-- | Parameters for 'WorkDoneProgressEndNotification'. +-- +-- @since 0.10.0.0 +data WorkDoneProgressEndParams = + WorkDoneProgressEndParams { + _message :: Maybe Text + } deriving (Show, Read, Eq) + +instance A.ToJSON WorkDoneProgressEndParams where + toJSON WorkDoneProgressEndParams{..} = + A.object $ catMaybes + [ Just $ "kind" A..= ("end" :: Text) + , ("message" A..=) <$> _message + ] + +instance A.FromJSON WorkDoneProgressEndParams where + parseJSON = A.withObject "WorkDoneProgressEnd" $ \o -> do + kind <- o A..: "kind" + unless (kind == ("end" :: Text)) $ fail $ "Expected kind \"end\" but got " ++ show kind + _message <- o A..:? "message" + pure WorkDoneProgressEndParams{..} + +-- The $/progress end notification is sent from the server to the +-- client to stop a previously started progress. +-- +-- @since 0.10.0.0 + +-- | Parameters for 'WorkDoneProgressCancelNotification'. +-- +-- @since 0.10.0.0 +data WorkDoneProgressCancelParams = + WorkDoneProgressCancelParams { + -- | A unique identifier to associate multiple progress + -- notifications with the same progress. + _token :: ProgressToken + } deriving (Show, Read, Eq) + +deriveJSON lspOptions ''WorkDoneProgressCancelParams + +-- The window/workDoneProgress/cancel notification is sent from the client to the server +-- to inform the server that the user has pressed the cancel button on the progress UX. +-- A server receiving a cancel request must still close a progress using the done notification. +-- +-- @since 0.10.0.0 + +data WorkDoneProgressCreateParams = + WorkDoneProgressCreateParams { + _token :: ProgressToken + } deriving (Show, Read, Eq) + +deriveJSON lspOptions ''WorkDoneProgressCreateParams + +data WorkDoneProgressOptions = + WorkDoneProgressOptions + { _workDoneProgress :: Maybe Bool + } + deriving (Read, Show, Eq) + +deriveJSON lspOptions ''WorkDoneProgressOptions + +data WorkDoneProgressParams = + WorkDoneProgressParams + { -- | An optional token that a server can use to report work done progress + _workDoneToken :: Maybe ProgressToken + } deriving (Read,Show,Eq) +deriveJSON lspOptions ''WorkDoneProgressParams + +data PartialResultParams = + PartialResultParams + { -- | An optional token that a server can use to report partial results + -- (e.g. streaming) to the client. + _partialResultToken :: Maybe ProgressToken + } deriving (Read,Show,Eq) +deriveJSON lspOptions ''PartialResultParams diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/References.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/References.hs new file mode 100644 index 000000000..43499573f --- /dev/null +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/References.hs @@ -0,0 +1,43 @@ +{-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE DuplicateRecordFields #-} +-- | Find References Request +-- https://microsoft.github.io/language-server-protocol/specifications/specification-3-15/#textDocument_references +module Language.Haskell.LSP.Types.References where + +import Data.Aeson.TH + +import Language.Haskell.LSP.Types.TextDocument +import Language.Haskell.LSP.Types.Progress +import Language.Haskell.LSP.Types.Utils + +data ReferencesClientCapabilities = + ReferencesClientCapabilities + { -- | Whether references supports dynamic registration. + _dynamicRegistration :: Maybe Bool + } deriving (Show, Read, Eq) +deriveJSON lspOptions ''ReferencesClientCapabilities + +makeExtendingDatatype "ReferenceOptions" [''WorkDoneProgressOptions] [] +deriveJSON lspOptions ''ReferenceOptions + +makeExtendingDatatype "ReferenceRegistrationOptions" + [ ''TextDocumentRegistrationOptions + , ''ReferenceOptions + ] + [] +deriveJSON lspOptions ''ReferenceRegistrationOptions + +data ReferenceContext = + ReferenceContext + { -- | Include the declaration of the current symbol. + _includeDeclaration :: Bool + } deriving (Read,Show,Eq) +deriveJSON lspOptions ''ReferenceContext + +makeExtendingDatatype "ReferenceParams" + [ ''TextDocumentPositionParams + , ''WorkDoneProgressParams + , ''PartialResultParams + ] + [("_context", [t| ReferenceContext |])] +deriveJSON lspOptions ''ReferenceParams diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/Registration.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Registration.hs new file mode 100644 index 000000000..dbbb01523 --- /dev/null +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Registration.hs @@ -0,0 +1,176 @@ +{-# LANGUAGE GADTs #-} +{-# LANGUAGE TypeApplications #-} +{-# LANGUAGE TypeFamilyDependencies #-} +{-# LANGUAGE ExistentialQuantification #-} +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE UndecidableInstances #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE TypeOperators #-} +{-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE StandaloneDeriving #-} +{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE DeriveAnyClass #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE DuplicateRecordFields #-} + +{-# OPTIONS_GHC -Wno-unticked-promoted-constructors #-} +{-# OPTIONS_GHC -Werror=incomplete-patterns #-} + +module Language.Haskell.LSP.Types.Registration where + +import Data.Aeson +import Data.Aeson.TH +import Data.Text (Text) +import Data.Function (on) +import Data.Kind +import Data.Void (Void) +import GHC.Generics +import Language.Haskell.LSP.Types.CodeAction +import Language.Haskell.LSP.Types.CodeLens +import Language.Haskell.LSP.Types.Command +import Language.Haskell.LSP.Types.Common +import Language.Haskell.LSP.Types.Completion +import Language.Haskell.LSP.Types.Declaration +import Language.Haskell.LSP.Types.Definition +import Language.Haskell.LSP.Types.DocumentColor +import Language.Haskell.LSP.Types.DocumentHighlight +import Language.Haskell.LSP.Types.DocumentLink +import Language.Haskell.LSP.Types.DocumentSymbol +import Language.Haskell.LSP.Types.FoldingRange +import Language.Haskell.LSP.Types.Formatting +import Language.Haskell.LSP.Types.Hover +import Language.Haskell.LSP.Types.Implementation +import Language.Haskell.LSP.Types.Method +import Language.Haskell.LSP.Types.References +import Language.Haskell.LSP.Types.Rename +import Language.Haskell.LSP.Types.SignatureHelp +import Language.Haskell.LSP.Types.SelectionRange +import Language.Haskell.LSP.Types.TextDocument +import Language.Haskell.LSP.Types.TypeDefinition +import Language.Haskell.LSP.Types.Utils +import Language.Haskell.LSP.Types.WatchedFiles +import Language.Haskell.LSP.Types.WorkspaceSymbol + + +-- --------------------------------------------------------------------- + +-- | Matches up the registration options for a specific method +type family RegistrationOptions (m :: Method FromClient t) :: Type where + -- Workspace + RegistrationOptions WorkspaceDidChangeWorkspaceFolders = Empty + RegistrationOptions WorkspaceDidChangeConfiguration = Empty + RegistrationOptions WorkspaceDidChangeWatchedFiles = DidChangeWatchedFilesRegistrationOptions + RegistrationOptions WorkspaceSymbol = WorkspaceSymbolRegistrationOptions + RegistrationOptions WorkspaceExecuteCommand = ExecuteCommandRegistrationOptions + + -- Text synchronisation + RegistrationOptions TextDocumentDidOpen = TextDocumentRegistrationOptions + RegistrationOptions TextDocumentDidChange = TextDocumentChangeRegistrationOptions + RegistrationOptions TextDocumentWillSave = TextDocumentRegistrationOptions + RegistrationOptions TextDocumentWillSaveWaitUntil = TextDocumentRegistrationOptions + RegistrationOptions TextDocumentDidSave = TextDocumentSaveRegistrationOptions + RegistrationOptions TextDocumentDidClose = TextDocumentRegistrationOptions + + -- Language features + RegistrationOptions TextDocumentCompletion = CompletionRegistrationOptions + RegistrationOptions TextDocumentHover = HoverRegistrationOptions + RegistrationOptions TextDocumentSignatureHelp = SignatureHelpRegistrationOptions + RegistrationOptions TextDocumentDeclaration = DeclarationRegistrationOptions + RegistrationOptions TextDocumentDefinition = DefinitionRegistrationOptions + RegistrationOptions TextDocumentTypeDefinition = TypeDefinitionRegistrationOptions + RegistrationOptions TextDocumentImplementation = ImplementationRegistrationOptions + RegistrationOptions TextDocumentReferences = ReferenceRegistrationOptions + RegistrationOptions TextDocumentDocumentHighlight = DocumentHighlightRegistrationOptions + RegistrationOptions TextDocumentDocumentSymbol = DocumentSymbolRegistrationOptions + RegistrationOptions TextDocumentCodeAction = CodeActionRegistrationOptions + RegistrationOptions TextDocumentCodeLens = CodeLensRegistrationOptions + RegistrationOptions TextDocumentDocumentLink = DocumentLinkRegistrationOptions + RegistrationOptions TextDocumentDocumentColor = DocumentColorRegistrationOptions + RegistrationOptions TextDocumentFormatting = DocumentFormattingRegistrationOptions + RegistrationOptions TextDocumentRangeFormatting = DocumentRangeFormattingRegistrationOptions + RegistrationOptions TextDocumentOnTypeFormatting = DocumentOnTypeFormattingRegistrationOptions + RegistrationOptions TextDocumentRename = RenameRegistrationOptions + RegistrationOptions TextDocumentFoldingRange = FoldingRangeRegistrationOptions + RegistrationOptions TextDocumentSelectionRange = SelectionRangeRegistrationOptions + RegistrationOptions m = Void + +data Registration (m :: Method FromClient t) = + Registration + { -- | The id used to register the request. The id can be used to deregister + -- the request again. + _id :: Text + -- | The method / capability to register for. + , _method :: SClientMethod m + -- | Options necessary for the registration. + -- Make this strict to aid the pattern matching exhaustiveness checker + , _registerOptions :: !(RegistrationOptions m) + } + deriving Generic + +deriving instance Eq (RegistrationOptions m) => Eq (Registration m) +deriving instance Show (RegistrationOptions m) => Show (Registration m) + +-- This generates the function +-- regHelper :: SMethod m +-- -> (( Show (RegistrationOptions m) +-- , ToJSON (RegistrationOptions m) +-- , FromJSON ($regOptTcon m) +-- => x) +-- -> x +makeRegHelper ''RegistrationOptions + +instance ToJSON (Registration m) where + toJSON x@(Registration _ m _) = regHelper m (genericToJSON lspOptions x) + +data SomeRegistration = forall t (m :: Method FromClient t). SomeRegistration (Registration m) + +instance ToJSON SomeRegistration where + toJSON (SomeRegistration r) = toJSON r + +instance FromJSON SomeRegistration where + parseJSON = withObject "Registration" $ \o -> do + SomeClientMethod m <- o .: "method" + r <- Registration <$> o .: "id" <*> pure m <*> regHelper m (o .: "registerOptions") + pure (SomeRegistration r) + +instance Eq SomeRegistration where + (==) = (==) `on` toJSON + +instance Show SomeRegistration where + show (SomeRegistration r@(Registration _ m _)) = regHelper m (show r) + +data RegistrationParams = + RegistrationParams { _registrations :: List SomeRegistration } + deriving (Show, Eq) + +deriveJSON lspOptions ''RegistrationParams + + +-- --------------------------------------------------------------------- + +-- | General parameters to unregister a capability. +data Unregistration = + Unregistration + { -- | The id used to unregister the request or notification. Usually an id + -- provided during the register request. + _id :: Text + -- | The method / capability to unregister for. + , _method :: SomeClientMethod + } deriving (Show, Eq) + +deriveJSON lspOptions ''Unregistration + +data UnregistrationParams = + UnregistrationParams + { -- | This should correctly be named @unregistrations@. However changing this + -- is a breaking change and needs to wait until we deliver a 4.x version + -- of the specification. + _unregisterations :: List Unregistration + } deriving (Show, Eq) + +deriveJSON lspOptions ''UnregistrationParams diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/Rename.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Rename.hs new file mode 100644 index 000000000..f39e32b83 --- /dev/null +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Rename.hs @@ -0,0 +1,55 @@ +{-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE DuplicateRecordFields #-} + +module Language.Haskell.LSP.Types.Rename where + +import Data.Aeson.TH +import Data.Text (Text) + +import Language.Haskell.LSP.Types.Location +import Language.Haskell.LSP.Types.TextDocument +import Language.Haskell.LSP.Types.Progress +import Language.Haskell.LSP.Types.Utils + +data RenameClientCapabilities = + RenameClientCapabilities + { -- | Whether rename supports dynamic registration. + _dynamicRegistration :: Maybe Bool + -- | Client supports testing for validity of rename operations + -- before execution. + -- + -- Since LSP 3.12.0 + , _prepareSupport :: Maybe Bool + } deriving (Show, Read, Eq) + +deriveJSON lspOptions ''RenameClientCapabilities + +makeExtendingDatatype "RenameOptions" [''WorkDoneProgressOptions] + [("_prepareProvider", [t| Maybe Bool |])] +deriveJSON lspOptions ''RenameOptions + +makeExtendingDatatype "RenameRegistrationOptions" + [ ''TextDocumentRegistrationOptions + , ''RenameOptions + ] [] +deriveJSON lspOptions ''RenameRegistrationOptions + +makeExtendingDatatype "RenameParams" + [ ''TextDocumentPositionParams + , ''WorkDoneProgressParams + ] + [("_newName", [t| Text |])] +deriveJSON lspOptions ''RenameParams + +-- ----------------------------------------- + +makeExtendingDatatype "PrepareRenameParams" [''TextDocumentPositionParams] [] +deriveJSON lspOptions ''PrepareRenameParams + +data RangeWithPlaceholder = + RangeWithPlaceholder + { + _range :: Range + , _placeholder :: Text + } deriving Eq +deriveJSON lspOptions ''RangeWithPlaceholder diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/SelectionRange.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/SelectionRange.hs new file mode 100644 index 000000000..07ab78e6b --- /dev/null +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/SelectionRange.hs @@ -0,0 +1,54 @@ +{-# LANGUAGE DuplicateRecordFields #-} +{-# LANGUAGE TemplateHaskell #-} + +module Language.Haskell.LSP.Types.SelectionRange where + +import Data.Aeson.TH +import Language.Haskell.LSP.Types.Common +import Language.Haskell.LSP.Types.Location +import Language.Haskell.LSP.Types.Progress +import Language.Haskell.LSP.Types.StaticRegistrationOptions +import Language.Haskell.LSP.Types.TextDocument +import Language.Haskell.LSP.Types.Utils + +data SelectionRangeClientCapabilities = SelectionRangeClientCapabilities + { -- | Whether implementation supports dynamic registration for selection range providers. If this is set to 'True' + -- the client supports the new 'SelectionRangeRegistrationOptions' return value for the corresponding server + -- capability as well. + _dynamicRegistration :: Maybe Bool + } + deriving (Read, Show, Eq) + +deriveJSON lspOptions ''SelectionRangeClientCapabilities + +makeExtendingDatatype "SelectionRangeOptions" [''WorkDoneProgressOptions] [] +deriveJSON lspOptions ''SelectionRangeOptions + +makeExtendingDatatype + "SelectionRangeRegistrationOptions" + [ ''SelectionRangeOptions, + ''TextDocumentRegistrationOptions, + ''StaticRegistrationOptions + ] + [] +deriveJSON lspOptions ''SelectionRangeRegistrationOptions + +makeExtendingDatatype + "SelectionRangeParams" + [ ''WorkDoneProgressParams, + ''PartialResultParams + ] + [ ("_textDocument", [t|TextDocumentIdentifier|]), + ("_positions", [t|List Position|]) + ] +deriveJSON lspOptions ''SelectionRangeParams + +data SelectionRange = SelectionRange + { -- | The 'range' of this selection range. + _range :: Range, + -- | The parent selection range containing this range. Therefore @parent.range@ must contain @this.range@. + _parent :: Maybe SelectionRange + } + deriving (Read, Show, Eq) + +deriveJSON lspOptions ''SelectionRange diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/ServerCapabilities.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/ServerCapabilities.hs new file mode 100644 index 000000000..07f9adce1 --- /dev/null +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/ServerCapabilities.hs @@ -0,0 +1,128 @@ +{-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE TypeOperators #-} +{-# LANGUAGE DuplicateRecordFields #-} + +module Language.Haskell.LSP.Types.ServerCapabilities where + +import Data.Aeson +import Data.Aeson.TH +import Data.Text (Text) +import Language.Haskell.LSP.Types.CodeAction +import Language.Haskell.LSP.Types.CodeLens +import Language.Haskell.LSP.Types.Command +import Language.Haskell.LSP.Types.Common +import Language.Haskell.LSP.Types.Completion +import Language.Haskell.LSP.Types.Declaration +import Language.Haskell.LSP.Types.Definition +import Language.Haskell.LSP.Types.DocumentColor +import Language.Haskell.LSP.Types.DocumentHighlight +import Language.Haskell.LSP.Types.DocumentLink +import Language.Haskell.LSP.Types.DocumentSymbol +import Language.Haskell.LSP.Types.FoldingRange +import Language.Haskell.LSP.Types.Formatting +import Language.Haskell.LSP.Types.Hover +import Language.Haskell.LSP.Types.Implementation +import Language.Haskell.LSP.Types.References +import Language.Haskell.LSP.Types.Rename +import Language.Haskell.LSP.Types.SelectionRange +import Language.Haskell.LSP.Types.SignatureHelp +import Language.Haskell.LSP.Types.TextDocument +import Language.Haskell.LSP.Types.TypeDefinition +import Language.Haskell.LSP.Types.Utils + +-- --------------------------------------------------------------------- + +data WorkspaceFoldersServerCapabilities = + WorkspaceFoldersServerCapabilities + { -- | The server has support for workspace folders + _supported :: Maybe Bool + -- | Whether the server wants to receive workspace folder + -- change notifications. + -- If a strings is provided the string is treated as a ID + -- under which the notification is registered on the client + -- side. The ID can be used to unregister for these events + -- using the `client/unregisterCapability` request. + , _changeNotifications :: Maybe (Text |? Bool) + } + deriving (Show, Read, Eq) + +deriveJSON lspOptions ''WorkspaceFoldersServerCapabilities + +data WorkspaceServerCapabilities = + WorkspaceServerCapabilities + { -- | The server supports workspace folder. Since LSP 3.6 + -- + -- @since 0.7.0.0 + _workspaceFolders :: Maybe WorkspaceFoldersServerCapabilities + } + deriving (Show, Read, Eq) +deriveJSON lspOptions ''WorkspaceServerCapabilities + +data ServerCapabilities = + ServerCapabilities + { -- | Defines how text documents are synced. Is either a detailed structure + -- defining each notification or for backwards compatibility the + -- 'TextDocumentSyncKind' number. + -- If omitted it defaults to 'TdSyncNone'. + _textDocumentSync :: Maybe (TextDocumentSyncOptions |? TextDocumentSyncKind) + -- | The server provides hover support. + , _hoverProvider :: Maybe (Bool |? HoverOptions) + -- | The server provides completion support. + , _completionProvider :: Maybe CompletionOptions + -- | The server provides signature help support. + , _signatureHelpProvider :: Maybe SignatureHelpOptions + -- | The server provides go to declaration support. + -- + -- Since LSP 3.14.0 + , _declarationProvider :: Maybe (Bool |? DeclarationOptions |? DeclarationRegistrationOptions) + -- | The server provides goto definition support. + , _definitionProvider :: Maybe (Bool |? DefinitionOptions) + -- | The server provides Goto Type Definition support. Since LSP 3.6 + -- + -- @since 0.7.0.0 + , _typeDefinitionProvider :: Maybe (Bool |? TypeDefinitionOptions |? TypeDefinitionRegistrationOptions) + -- | The server provides Goto Implementation support. Since LSP 3.6 + -- + -- @since 0.7.0.0 + , _implementationProvider :: Maybe (Bool |? ImplementationOptions |? ImplementationRegistrationOptions) + -- | The server provides find references support. + , _referencesProvider :: Maybe (Bool |? ReferenceOptions) + -- | The server provides document highlight support. + , _documentHighlightProvider :: Maybe (Bool |? DocumentHighlightOptions) + -- | The server provides document symbol support. + , _documentSymbolProvider :: Maybe (Bool |? DocumentSymbolOptions) + -- | The server provides code actions. + , _codeActionProvider :: Maybe (Bool |? CodeActionOptions) + -- | The server provides code lens. + , _codeLensProvider :: Maybe CodeLensOptions + -- | The server provides document link support. + , _documentLinkProvider :: Maybe DocumentLinkOptions + -- | The server provides color provider support. Since LSP 3.6 + -- + -- @since 0.7.0.0 + , _colorProvider :: Maybe (Bool |? DocumentColorOptions |? DocumentColorRegistrationOptions) + -- | The server provides document formatting. + , _documentFormattingProvider :: Maybe (Bool |? DocumentFormattingOptions) + -- | The server provides document range formatting. + , _documentRangeFormattingProvider :: Maybe (Bool |? DocumentRangeFormattingOptions) + -- | The server provides document formatting on typing. + , _documentOnTypeFormattingProvider :: Maybe DocumentOnTypeFormattingOptions + -- | The server provides rename support. + , _renameProvider :: Maybe (Bool |? RenameOptions) + -- | The server provides folding provider support. Since LSP 3.10 + -- + -- @since 0.7.0.0 + , _foldingRangeProvider :: Maybe (Bool |? FoldingRangeOptions |? FoldingRangeRegistrationOptions) + -- | The server provides execute command support. + , _executeCommandProvider :: Maybe ExecuteCommandOptions + -- | The server provides selection range support. Since LSP 3.15 + , _selectionRangeProvider :: Maybe (Bool |? SelectionRangeOptions |? SelectionRangeRegistrationOptions) + -- | The server provides workspace symbol support. + , _workspaceSymbolProvider :: Maybe Bool + -- | Workspace specific server capabilities + , _workspace :: Maybe WorkspaceServerCapabilities + -- | Experimental server capabilities. + , _experimental :: Maybe Value + } deriving (Show, Read, Eq) + +deriveJSON lspOptions ''ServerCapabilities diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/SignatureHelp.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/SignatureHelp.hs new file mode 100644 index 000000000..fdcd4d350 --- /dev/null +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/SignatureHelp.hs @@ -0,0 +1,154 @@ +{-# LANGUAGE DuplicateRecordFields #-} +{-# LANGUAGE TemplateHaskell #-} +-- | Signature Help Request +-- https://github.com/Microsoft/language-server-protocol/blob/master/protocol.md#signature-help-request +module Language.Haskell.LSP.Types.SignatureHelp where + +import Data.Aeson +import Data.Aeson.TH +import Data.Text (Text) +import Language.Haskell.LSP.Types.Common +import Language.Haskell.LSP.Types.MarkupContent +import Language.Haskell.LSP.Types.Progress +import Language.Haskell.LSP.Types.TextDocument +import Language.Haskell.LSP.Types.Utils + +-- ------------------------------------- + +data SignatureHelpParameterInformation = + SignatureHelpParameterInformation + { -- | The client supports processing label offsets instead of a simple + -- label string. + -- + -- @since 3.14.0 + _labelOffsetSupport :: Maybe Bool + } + deriving (Read, Show, Eq) +deriveJSON lspOptions ''SignatureHelpParameterInformation + +data SignatureHelpSignatureInformation = + SignatureHelpSignatureInformation + { -- | Client supports the follow content formats for the documentation + -- property. The order describes the preferred format of the client. + _documentationFormat :: Maybe (List MarkupKind) + -- | Client capabilities specific to parameter information. + , _parameterInformation :: Maybe SignatureHelpParameterInformation + } + deriving (Show, Read, Eq) + +deriveJSON lspOptions ''SignatureHelpSignatureInformation + +data SignatureHelpClientCapabilities = + SignatureHelpClientCapabilities + { -- | Whether signature help supports dynamic registration. + _dynamicRegistration :: Maybe Bool + -- | The client supports the following 'SignatureInformation' + -- specific properties. + , _signatureInformation :: Maybe SignatureHelpSignatureInformation + -- | The client supports to send additional context information for a + -- @textDocument/signatureHelp@ request. A client that opts into + -- contextSupport will also support the '_retriggerCharacters' on + -- 'SignatureHelpOptions'. + -- + -- @since 3.15.0 + , _contextSupport :: Maybe Bool + } deriving (Show, Read, Eq) + +deriveJSON lspOptions ''SignatureHelpClientCapabilities + +-- ------------------------------------- + +makeExtendingDatatype "SignatureHelpOptions" [''WorkDoneProgressOptions] + [ ("_triggerCharacters", [t| Maybe (List String) |]) + , ("_retriggerCharacters", [t| Maybe (List String) |]) + ] +deriveJSON lspOptions ''SignatureHelpOptions + +makeExtendingDatatype "SignatureHelpRegistrationOptions" + [ ''TextDocumentRegistrationOptions + , ''SignatureHelpOptions + ] [] +deriveJSON lspOptions ''SignatureHelpRegistrationOptions + +-- ------------------------------------- + +data ParameterInformation = + ParameterInformation + { _label :: Text + , _documentation :: Maybe Text + } deriving (Read,Show,Eq) +deriveJSON lspOptions ''ParameterInformation + +-- ------------------------------------- + +data SignatureInformation = + SignatureInformation + { _label :: Text + , _documentation :: Maybe Text + , _parameters :: Maybe (List ParameterInformation) + } deriving (Read,Show,Eq) + +deriveJSON lspOptions ''SignatureInformation + +data SignatureHelp = + SignatureHelp + { _signatures :: List SignatureInformation + , _activeSignature :: Maybe Int -- ^ The active signature + , _activeParameter :: Maybe Int -- ^ The active parameter of the active signature + } deriving (Read,Show,Eq) + +deriveJSON lspOptions ''SignatureHelp + +-- ------------------------------------- + +data SignatureHelpTriggerKind = SHTKInvoked + | SHTKTriggerCharacter + | SHTKContentChange + deriving (Read,Show,Eq) + +instance ToJSON SignatureHelpTriggerKind where + toJSON SHTKInvoked = Number 1 + toJSON SHTKTriggerCharacter = Number 2 + toJSON SHTKContentChange = Number 3 + +instance FromJSON SignatureHelpTriggerKind where + parseJSON (Number 1) = pure SHTKInvoked + parseJSON (Number 2) = pure SHTKTriggerCharacter + parseJSON (Number 3) = pure SHTKContentChange + parseJSON _ = mempty + +-- | Additional information about the context in which a signature help request +-- was triggered. +data SignatureHelpContext = + SignatureHelpContext + { -- | Action that caused signature help to be triggered. + _triggerKind :: SignatureHelpTriggerKind + -- | Character that caused signature help to be triggered. This is + -- undefined when @triggerKind !== + -- SignatureHelpTriggerKind.TriggerCharacter@ + , _triggerCharacter :: Maybe String + -- | 'True' if signature help was already showing when it was triggered. + -- + -- Retriggers occur when the signature help is already active and can be + -- caused by actions such as typing a trigger character, a cursor move, or + -- document content changes. + , _isRetrigger :: Bool + -- | The currently active 'SignatureHelp'. + -- + -- The '_activeSignatureHelp' has its @SignatureHelp.activeSignature@ + -- field updated based on the user navigating through available + -- signatures. + , _activeSignatureHelp :: Maybe SignatureHelp + } + deriving (Read,Show,Eq) +deriveJSON lspOptions ''SignatureHelpContext + +makeExtendingDatatype "SignatureHelpParams" + [ ''TextDocumentPositionParams + , ''WorkDoneProgressParams + ] + [ ("_context", [t| Maybe SignatureHelpContext |]) + ] +deriveJSON lspOptions ''SignatureHelpParams + + diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/StaticRegistrationOptions.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/StaticRegistrationOptions.hs new file mode 100644 index 000000000..978d7a947 --- /dev/null +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/StaticRegistrationOptions.hs @@ -0,0 +1,13 @@ +{-# LANGUAGE TemplateHaskell #-} +-- Cyclic dependencies mean we have to put poor StaticRegistrationOptions on its own +module Language.Haskell.LSP.Types.StaticRegistrationOptions where + +import Data.Aeson.TH +import Data.Text (Text) +import Language.Haskell.LSP.Types.Utils + +data StaticRegistrationOptions = + StaticRegistrationOptions + { _id :: Maybe Text + } deriving (Read,Show,Eq) +deriveJSON lspOptions ''StaticRegistrationOptions diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/Synonyms.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Synonyms.hs new file mode 100644 index 000000000..ba9d28eb6 --- /dev/null +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Synonyms.hs @@ -0,0 +1,177 @@ +{-# LANGUAGE DataKinds #-} +{-# OPTIONS_GHC -Wno-unticked-promoted-constructors #-} + +module Language.Haskell.LSP.Types.Synonyms where + +import Language.Haskell.LSP.Types.Method +import Language.Haskell.LSP.Types.Message + +-- Server Messages + +-- Window +type ShowMessageNotification = Message WindowShowMessage + +type ShowMessageRequest = Message WindowShowMessageRequest +type ShowMessageResponse = ResponseMessage WindowShowMessageRequest + +type LogMessageNotification = Message WindowLogMessage + +type WindowWorkDoneProgressCreateRequest = Message WindowWorkDoneProgressCreate +type WindowWorkDoneProgressCreateResponse = ResponseMessage WindowWorkDoneProgressCreate + +type ProgressNotification = Message Progress + +type TelemetryNotification = Message TelemetryEvent + +-- Capability +type RegisterCapabilityRequest = Message ClientRegisterCapability +type RegisterCapabilityResponse = ResponseMessage ClientRegisterCapability + +type UnregisterCapabilityRequest = Message ClientUnregisterCapability +type UnregisterCapabilityResponse = ResponseMessage ClientUnregisterCapability + +-- Workspace +type WorkspaceFoldersRequest = Message WorkspaceWorkspaceFolders +type WorkspaceFoldersResponse = ResponseMessage WorkspaceWorkspaceFolders + +type ConfigurationRequest = Message WorkspaceConfiguration +type ConfigurationResponse = ResponseMessage WorkspaceConfiguration + +type ApplyWorkspaceEditRequest = Message WorkspaceApplyEdit +type ApplyWorkspaceEditResponse = ResponseMessage WorkspaceApplyEdit + +-- Document/Diagnostic +type PublishDiagnosticsNotification = Message TextDocumentPublishDiagnostics + +-- Cancel +type CancelNotificationServer = Message CancelRequest + +-- Custom +type CustomServerNotification = Message CustomMethod +type CustomServerRequest = Message CustomMethod + +-- Client Messages + +-- General +type InitializeRequest = Message Initialize +type InitializeResponse = ResponseMessage Initialize + +type InitializedNotification = Message Initialized + +type ShutdownRequest = Message Shutdown +type ShutdownResponse = ResponseMessage Shutdown + +type ExitNotification = Message Exit +type CancelNotification = Message CancelRequest + +-- Workspace +type DidChangeWorkspaceFoldersNotification = Message WorkspaceDidChangeWorkspaceFolders +type DidChangeConfigurationNotification = Message WorkspaceDidChangeConfiguration +type DidChangeWatchedFilesNotification = Message WorkspaceDidChangeWatchedFiles + +type WorkspaceSymbolRequest = Message WorkspaceSymbol +type WorkspaceSymbolsResponse = ResponseMessage WorkspaceSymbol + +type ExecuteCommandRequest = Message WorkspaceExecuteCommand +type ExecuteCommandResponse = ResponseMessage WorkspaceExecuteCommand + +type WorkDoneProgressCancelNotification = Message WindowWorkDoneProgressCancel + +-- Document/Sync +type DidOpenTextDocumentNotification = Message TextDocumentDidOpen +type DidChangeTextDocumentNotification = Message TextDocumentDidChange +type WillSaveTextDocumentNotification = Message TextDocumentWillSave + +type WillSaveWaitUntilTextDocumentRequest = Message TextDocumentWillSaveWaitUntil +type WillSaveWaitUntilTextDocumentResponse = ResponseMessage TextDocumentWillSaveWaitUntil + +type DidSaveTextDocumentNotification = Message TextDocumentDidSave +type DidCloseTextDocumentNotification = Message TextDocumentDidClose + +-- Completion + +type CompletionRequest = Message TextDocumentCompletion +type CompletionResponse = ResponseMessage TextDocumentCompletion + +type CompletionItemResolveRequest = Message CompletionItemResolve +type CompletionItemResolveResponse = ResponseMessage CompletionItemResolve + +-- Queries +type HoverRequest = Message TextDocumentHover +type HoverResponse = ResponseMessage TextDocumentHover + +type SignatureHelpRequest = Message TextDocumentSignatureHelp +type SignatureHelpResponse = ResponseMessage TextDocumentSignatureHelp + +type DeclarationRequest = Message TextDocumentDeclaration +type DeclarationResponse = ResponseMessage TextDocumentDeclaration + +type DefinitionRequest = Message TextDocumentDefinition +type DefinitionResponse = ResponseMessage TextDocumentDefinition + +type TypeDefinitionRequest = Message TextDocumentTypeDefinition +type TypeDefinitionResponse = ResponseMessage TextDocumentTypeDefinition + +type ImplementationRequest = Message TextDocumentImplementation +type ImplementationResponse = ResponseMessage TextDocumentImplementation + +type ReferencesRequest = Message TextDocumentReferences +type ReferencesResponse = ResponseMessage TextDocumentReferences + +type DocumentHighlightRequest = Message TextDocumentDocumentHighlight +type DocumentHighlightsResponse = ResponseMessage TextDocumentDocumentHighlight + +type DocumentSymbolRequest = Message TextDocumentDocumentSymbol +type DocumentSymbolsResponse = ResponseMessage TextDocumentDocumentSymbol + +-- Code Lens/Action/Link + +type CodeActionRequest = Message TextDocumentCodeAction +type CodeActionResponse = ResponseMessage TextDocumentCodeAction + +type CodeLensRequest = Message TextDocumentCodeLens +type CodeLensResponse = ResponseMessage TextDocumentCodeLens + +type CodeLensResolveRequest = Message CodeLensResolve +type CodeLensResolveResponse = ResponseMessage CodeLensResolve + +type DocumentLinkRequest = Message TextDocumentDocumentLink +type DocumentLinkResponse = ResponseMessage TextDocumentDocumentLink + +type DocumentLinkResolveRequest = Message DocumentLinkResolve +type DocumentLinkResolveResponse = ResponseMessage DocumentLinkResolve + +-- Color/Syntax + +type DocumentColorRequest = Message TextDocumentDocumentColor +type DocumentColorResponse = ResponseMessage TextDocumentDocumentColor + +type ColorPresentationRequest = Message TextDocumentColorPresentation +type ColorPresentationResponse = ResponseMessage TextDocumentColorPresentation + + +-- Formatting +type DocumentFormattingRequest = Message TextDocumentFormatting +type DocumentFormattingResponse = ResponseMessage TextDocumentFormatting + +type DocumentRangeFormattingRequest = Message TextDocumentRangeFormatting +type DocumentRangeFormattingResponse = ResponseMessage TextDocumentRangeFormatting + +type DocumentOnTypeFormattingRequest = Message TextDocumentOnTypeFormatting +type DocumentOnTypeFormattingResponse = ResponseMessage TextDocumentOnTypeFormatting + +-- Rename +type RenameRequest = Message TextDocumentRename +type RenameResponse = ResponseMessage TextDocumentRename + +type PrepareRenameRequest = Message TextDocumentPrepareRename +type PrepareRenameResponse = ResponseMessage TextDocumentPrepareRename + +-- Folding +type FoldingRangeRequest = Message TextDocumentFoldingRange +type FoldingRangeResponse = ResponseMessage TextDocumentFoldingRange + +-- Custom +type CustomClientNotification = Message CustomMethod +type CustomClientRequest = Message CustomMethod +type CustomResponse = ResponseMessage CustomMethod diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/TextDocument.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/TextDocument.hs index 53ba138fb..c7f9e8e30 100644 --- a/haskell-lsp-types/src/Language/Haskell/LSP/Types/TextDocument.hs +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/TextDocument.hs @@ -1,67 +1,32 @@ {-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE TypeOperators #-} module Language.Haskell.LSP.Types.TextDocument where +import Data.Aeson import Data.Aeson.TH +import Data.Default import Data.Text ( Text ) -import Language.Haskell.LSP.Types.Constants + +import Language.Haskell.LSP.Types.Common +import Language.Haskell.LSP.Types.DocumentFilter import Language.Haskell.LSP.Types.Location -import Language.Haskell.LSP.Types.Progress import Language.Haskell.LSP.Types.Uri +import Language.Haskell.LSP.Types.Utils -- --------------------------------------------------------------------- -{- -TextDocumentIdentifier - -https://github.com/Microsoft/language-server-protocol/blob/master/protocol.md#textdocumentidentifier - -Text documents are identified using a URI. On the protocol level, URIs are -passed as strings. The corresponding JSON structure looks like this: -interface TextDocumentIdentifier { - /** - * The text document's URI. - */ - uri: string; -} --} data TextDocumentIdentifier = TextDocumentIdentifier { _uri :: Uri } deriving (Show, Read, Eq) - deriveJSON lspOptions ''TextDocumentIdentifier -{- -TextDocumentItem - -https://github.com/Microsoft/language-server-protocol/blob/master/protocol.md#textdocumentitem - - New: An item to transfer a text document from the client to the server. - -interface TextDocumentItem { - /** - * The text document's URI. - */ - uri: string; - - /** - * The text document's language identifier. - */ - languageId: string; - - /** - * The version number of this document (it will strictly increase after each - * change, including undo/redo). - */ - version: number; - - /** - * The content of the opened text document. - */ - text: string; -} --} +type TextDocumentVersion = Maybe Int + +makeExtendingDatatype "VersionedTextDocumentIdentifier" [''TextDocumentIdentifier] + [ ("_version", [t| TextDocumentVersion |])] +deriveJSON lspOptions ''VersionedTextDocumentIdentifier data TextDocumentItem = TextDocumentItem { @@ -74,32 +39,226 @@ data TextDocumentItem = deriveJSON lspOptions ''TextDocumentItem -- --------------------------------------------------------------------- -{- -TextDocumentPositionParams -https://github.com/Microsoft/language-server-protocol/blob/master/protocol.md#textdocumentpositionparams +data TextDocumentPositionParams = + TextDocumentPositionParams + { -- | The text document. + _textDocument :: TextDocumentIdentifier + , -- | The position inside the text document. + _position :: Position + } deriving (Show, Read, Eq) + +deriveJSON lspOptions ''TextDocumentPositionParams + +-- ------------------------------------- - Changed: Was TextDocumentPosition in 1.0 with inlined parameters +-- Text document synchronisation -interface TextDocumentPositionParams { - /** - * The text document. - */ - textDocument: TextDocumentIdentifier; +data TextDocumentSyncClientCapabilities = + TextDocumentSyncClientCapabilities + { -- | Whether text document synchronization supports dynamic registration. + _dynamicRegistration :: Maybe Bool - /** - * The position inside the text document. - */ - position: Position; -} + -- | The client supports sending will save notifications. + , _willSave :: Maybe Bool + -- | The client supports sending a will save request and waits for a + -- response providing text edits which will be applied to the document + -- before it is saved. + , _willSaveWaitUntil :: Maybe Bool + + -- | The client supports did save notifications. + , _didSave :: Maybe Bool + } deriving (Show, Read, Eq) + +deriveJSON lspOptions ''TextDocumentSyncClientCapabilities + +instance Default TextDocumentSyncClientCapabilities where + def = TextDocumentSyncClientCapabilities def def def def + +-- ------------------------------------- + +data SaveOptions = + SaveOptions + { -- | The client is supposed to include the content on save. + _includeText :: Maybe Bool + } deriving (Show, Read, Eq) + +-- ------------------------------------- + +-- | Defines how the host (editor) should sync document changes to the language server. +data TextDocumentSyncKind + = -- | Documents should not be synced at all. + TdSyncNone + | -- | Documents are synced by always sending the full content of the document. + TdSyncFull + | -- | Documents are synced by sending the full content on open. After that only incremental updates to the document are send. + TdSyncIncremental + deriving (Read, Eq, Show) + +instance ToJSON TextDocumentSyncKind where + toJSON TdSyncNone = Number 0 + toJSON TdSyncFull = Number 1 + toJSON TdSyncIncremental = Number 2 + +instance FromJSON TextDocumentSyncKind where + parseJSON (Number 0) = pure TdSyncNone + parseJSON (Number 1) = pure TdSyncFull + parseJSON (Number 2) = pure TdSyncIncremental + parseJSON _ = mempty + +data TextDocumentSyncOptions = + TextDocumentSyncOptions + { -- | Open and close notifications are sent to the server. If omitted open + -- close notification should not be sent. + _openClose :: Maybe Bool + , -- | Change notifications are sent to the server. See + -- TextDocumentSyncKind.None, TextDocumentSyncKind.Full + -- and TextDocumentSyncKind.Incremental. If omitted it defaults to + -- TextDocumentSyncKind.None. + _change :: Maybe TextDocumentSyncKind + -- | If present will save notifications are sent to the server. If omitted the notification should not be + -- sent. + , _willSave :: Maybe Bool + -- | If present will save wait until requests are sent to the server. If omitted the request should not be + -- sent. + , _willSaveWaitUntil :: Maybe Bool + -- | If present save notifications are sent to the server. If omitted the + -- notification should not be sent. + , _save :: Maybe (Bool |? SaveOptions) + } deriving (Show, Read, Eq) +deriveJSON lspOptions ''TextDocumentSyncOptions + +-- ------------------------------------- + +{- +Since most of the registration options require to specify a document selector +there is a base interface that can be used. -} -data TextDocumentPositionParams = - TextDocumentPositionParams - { _textDocument :: TextDocumentIdentifier - , _position :: Position - , _workDoneToken :: Maybe ProgressToken -- ^ An optional token that a server can use to report work done progress. + +data TextDocumentRegistrationOptions = + TextDocumentRegistrationOptions + { _documentSelector :: Maybe DocumentSelector } deriving (Show, Read, Eq) -deriveJSON lspOptions ''TextDocumentPositionParams +deriveJSON lspOptions ''TextDocumentRegistrationOptions + +-- ------------------------------------- + +data DidOpenTextDocumentParams = + DidOpenTextDocumentParams + { -- | The document that was opened. + _textDocument :: TextDocumentItem + } deriving (Show, Read, Eq) + +deriveJSON lspOptions ''DidOpenTextDocumentParams + +-- ------------------------------------- + +makeExtendingDatatype "TextDocumentChangeRegistrationOptions" + [''TextDocumentRegistrationOptions] + [("_syncKind", [t| TextDocumentSyncKind |])] + +deriveJSON lspOptions ''TextDocumentChangeRegistrationOptions + +{-# DEPRECATED _rangeLength "Use _range instead" #-} +data TextDocumentContentChangeEvent = + TextDocumentContentChangeEvent + { -- | The range of the document that changed. + _range :: Maybe Range + -- | The optional length of the range that got replaced. + , _rangeLength :: Maybe Int + -- | The new text for the provided range, if provided. + -- Otherwise the new text of the whole document. + , _text :: Text + } + deriving (Read,Show,Eq) + +deriveJSON lspOptions ''TextDocumentContentChangeEvent + +-- ------------------------------------- + +data DidChangeTextDocumentParams = + DidChangeTextDocumentParams + { -- | The document that did change. The version number points + -- to the version after all provided content changes have + -- been applied. + _textDocument :: VersionedTextDocumentIdentifier + -- | The actual content changes. The content changes describe single state changes + -- to the document. So if there are two content changes c1 (at array index 0) and + -- c2 (at array index 1) for a document in state S then c1 moves the document from + -- S to S' and c2 from S' to S''. So c1 is computed on the state S and c2 is computed + -- on the state S'. + -- + -- To mirror the content of a document using change events use the following approach: + -- - start with the same initial content + -- - apply the 'textDocument/didChange' notifications in the order you recevie them. + -- - apply the `TextDocumentContentChangeEvent`s in a single notification in the order + -- you receive them. + , _contentChanges :: List TextDocumentContentChangeEvent + } deriving (Show,Read,Eq) + +deriveJSON lspOptions ''DidChangeTextDocumentParams + +-- ------------------------------------- + +data TextDocumentSaveReason + = SaveManual + -- ^ Manually triggered, e.g. by the user pressing save, by starting + -- debugging, or by an API call. + | SaveAfterDelay -- ^ Automatic after a delay + | SaveFocusOut -- ^ When the editor lost focus + deriving (Show, Read, Eq) + +instance ToJSON TextDocumentSaveReason where + toJSON SaveManual = Number 1 + toJSON SaveAfterDelay = Number 2 + toJSON SaveFocusOut = Number 3 + +instance FromJSON TextDocumentSaveReason where + parseJSON (Number 1) = pure SaveManual + parseJSON (Number 2) = pure SaveAfterDelay + parseJSON (Number 3) = pure SaveFocusOut + parseJSON _ = mempty + +data WillSaveTextDocumentParams = + WillSaveTextDocumentParams + { -- | The document that will be saved. + _textDocument :: TextDocumentIdentifier + -- | The 'TextDocumentSaveReason'. + , _reason :: TextDocumentSaveReason + } deriving (Show, Read, Eq) + +deriveJSON lspOptions ''WillSaveTextDocumentParams + +-- ------------------------------------- + +deriveJSON lspOptions ''SaveOptions + +makeExtendingDatatype "TextDocumentSaveRegistrationOptions" + [''TextDocumentRegistrationOptions] + [("_includeText", [t| Maybe Bool |])] + +deriveJSON lspOptions ''TextDocumentSaveRegistrationOptions + +data DidSaveTextDocumentParams = + DidSaveTextDocumentParams + { -- | The document that was saved. + _textDocument :: TextDocumentIdentifier + -- | Optional the content when saved. Depends on the includeText value + -- when the save notification was requested. + , _text :: Maybe Text + } deriving (Read,Show,Eq) + +deriveJSON lspOptions ''DidSaveTextDocumentParams + +-- ------------------------------------- + +data DidCloseTextDocumentParams = + DidCloseTextDocumentParams + { -- | The document that was closed. + _textDocument :: TextDocumentIdentifier + } deriving (Read,Show,Eq) + +deriveJSON lspOptions ''DidCloseTextDocumentParams diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/TypeDefinition.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/TypeDefinition.hs new file mode 100644 index 000000000..edd618d67 --- /dev/null +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/TypeDefinition.hs @@ -0,0 +1,42 @@ +{-# LANGUAGE DuplicateRecordFields #-} +{-# LANGUAGE TemplateHaskell #-} + +module Language.Haskell.LSP.Types.TypeDefinition where + +import Data.Aeson.TH +import Language.Haskell.LSP.Types.Progress +import Language.Haskell.LSP.Types.StaticRegistrationOptions +import Language.Haskell.LSP.Types.TextDocument +import Language.Haskell.LSP.Types.Utils + +data TypeDefinitionClientCapabilities = TypeDefinitionClientCapabilities + { -- | Whether implementation supports dynamic registration. If this is set + -- to 'True' + -- the client supports the new 'TypeDefinitionRegistrationOptions' return + -- value for the corresponding server capability as well. + _dynamicRegistration :: Maybe Bool, + -- | The client supports additional metadata in the form of definition links. + -- + -- Since LSP 3.14.0 + _linkSupport :: Maybe Bool + } + deriving (Read, Show, Eq) + +deriveJSON lspOptions ''TypeDefinitionClientCapabilities + +makeExtendingDatatype "TypeDefinitionOptions" [''WorkDoneProgressOptions] [] +deriveJSON lspOptions ''TypeDefinitionOptions + +makeExtendingDatatype "TypeDefinitionRegistrationOptions" + [ ''TextDocumentRegistrationOptions + , ''TypeDefinitionOptions + , ''StaticRegistrationOptions + ] [] +deriveJSON lspOptions ''TypeDefinitionRegistrationOptions + +makeExtendingDatatype "TypeDefinitionParams" + [ ''TextDocumentPositionParams + , ''WorkDoneProgressParams + , ''PartialResultParams + ] [] +deriveJSON lspOptions ''TypeDefinitionParams diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/Uri.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Uri.hs index d2d55b3a4..bf7b449bb 100644 --- a/haskell-lsp-types/src/Language/Haskell/LSP/Types/Uri.hs +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Uri.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE CPP #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE RecordWildCards #-} @@ -25,9 +24,6 @@ import qualified Data.Aeson as A import Data.Binary (Binary, Get, put, get) import Data.Hashable import Data.List (stripPrefix) -#if __GLASGOW_HASKELL__ < 804 -import Data.Monoid ((<>)) -#endif import Data.String (IsString, fromString) import Data.Text (Text) import qualified Data.Text as T @@ -113,8 +109,8 @@ platformAdjustFromUriPath systemOS authority srcPath = if systemOS /= windowsOS || null srcPath then srcPath else let firstSegment:rest = (FPP.splitDirectories . tail) srcPath -- Drop leading '/' for absolute Windows paths - drive = if FPW.isDrive firstSegment - then FPW.addTrailingPathSeparator firstSegment + drive = if FPW.isDrive firstSegment + then FPW.addTrailingPathSeparator firstSegment else firstSegment in FPW.joinDrive drive $ FPW.joinPath rest diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/Utils.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Utils.hs index 8b7b23110..07e2eb64c 100644 --- a/haskell-lsp-types/src/Language/Haskell/LSP/Types/Utils.hs +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Utils.hs @@ -1,6 +1,118 @@ -module Language.Haskell.LSP.Types.Utils where +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE LambdaCase #-} +-- | Internal helpers for generating definitions +module Language.Haskell.LSP.Types.Utils + ( rdrop + , makeSingletonFromJSON + , makeRegHelper + , makeExtendingDatatype + , lspOptions + ) where + +import Control.Monad +import Data.Aeson +import Data.List +import Language.Haskell.TH -- --------------------------------------------------------------------- rdrop :: Int -> [a] -> [a] rdrop cnt = reverse . drop cnt . reverse + +-- | Given a wrapper and a singleton GADT, construct FromJSON +-- instances for each constructor return type by invoking the +-- FromJSON instance for the wrapper and unwrapping +makeSingletonFromJSON :: Name -> Name -> Q [Dec] +makeSingletonFromJSON wrap gadt = do + TyConI (DataD _ _ _ _ cons _) <- reify gadt + concat <$> mapM (makeInst wrap) cons + +{- +instance FromJSON (SMethod $method) where + parseJSON = parseJSON >=> \case + SomeMethod $singleton-method -> pure $singleton-method + _ -> mempty +-} +makeInst :: Name -> Con -> Q [Dec] +makeInst wrap (GadtC [sConstructor] args t) = do + ns <- replicateM (length args) (newName "x") + let wrappedPat = pure $ ConP wrap [ConP sConstructor (map VarP ns)] + unwrappedE = pure $ foldl' AppE (ConE sConstructor) (map VarE ns) + [d| instance FromJSON $(pure t) where + parseJSON = parseJSON >=> \case + $wrappedPat -> pure $unwrappedE + _ -> mempty + |] +makeInst wrap (ForallC _ _ con) = makeInst wrap con -- Cancel and Custom requests +makeInst _ _ = fail "makeInst only defined for GADT constructors" + +makeRegHelper :: Name -> DecsQ +makeRegHelper regOptTypeName = do + Just sMethodTypeName <- lookupTypeName "SMethod" + Just fromClientName <- lookupValueName "FromClient" + TyConI (DataD _ _ _ _ allCons _) <- reify sMethodTypeName + + let isConsFromClient (GadtC _ _ (AppT _ method)) = isMethodFromClient method + isConsFromClient _ = return False + isMethodFromClient :: Type -> Q Bool + isMethodFromClient (PromotedT method) = do + DataConI _ typ _ <- reify method + case typ of + AppT (AppT _ (PromotedT n)) _ -> return $ n == fromClientName + _ -> return False + isMethodFromClient _ = fail "Didn't expect this type of Method!" + + cons <- filterM isConsFromClient allCons + + let conNames = map (\(GadtC [name] _ _) -> name) cons + helperName = mkName "regHelper" + mkClause name = do + x <- newName "x" + clause [ conP name [], varP x ] + (normalB (varE x)) + [] + regOptTcon = conT regOptTypeName + fun <- funD helperName (map mkClause conNames) + + typSig <- sigD helperName $ + [t| forall m x. $(conT sMethodTypeName) m + -> (Show ($regOptTcon m) => ToJSON ($regOptTcon m) => FromJSON ($regOptTcon m) => x) + -> x |] + return [typSig, fun] + +-- | @makeExtendingDatatype name extends fields@ generates a record datatype +-- that contains all the fields of @extends@, plus the additional fields in +-- @fields@. +-- e.g. +-- data Foo = { a :: Int } +-- makeExtendingDatatype "bar" [''Foo] [("b", [t| String |])] +-- Will generate +-- data Bar = { a :: Int, b :: String } +makeExtendingDatatype :: String -> [Name] -> [(String, TypeQ)] -> DecsQ +makeExtendingDatatype datatypeNameStr extends fields = do + extendFields <- fmap concat $ forM extends $ \e -> do + TyConI (DataD _ _ _ _ [RecC _ eFields] _) <- reify e + return eFields + let datatypeName = mkName datatypeNameStr + insts = [[t| Read |], [t| Show |], [t| Eq |]] + constructor = recC datatypeName combinedFields + userFields = flip map fields $ \(s, typ) -> do + varBangType (mkName s) (bangType (bang noSourceUnpackedness noSourceStrictness) typ) + combinedFields = (map pure extendFields) <> userFields + derivs = [derivClause Nothing insts] + (\a -> [a]) <$> dataD (cxt []) datatypeName [] Nothing [constructor] derivs + +-- | Standard options for use when generating JSON instances +-- NOTE: This needs to be in a separate file because of the TH stage restriction +lspOptions :: Options +lspOptions = defaultOptions { omitNothingFields = True, fieldLabelModifier = modifier } + where + modifier :: String -> String + -- For fields called data and type in the spec, we call them xdata and xtype + -- in haskell-lsp-types to avoid it clashing with the Haskell keywords. This + -- fixes up the json derivation + modifier "_xdata" = "data" + modifier "_xtype" = "type" + modifier xs = drop 1 xs + diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/WatchedFiles.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/WatchedFiles.hs new file mode 100644 index 000000000..5b2eabbf2 --- /dev/null +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/WatchedFiles.hs @@ -0,0 +1,113 @@ +{-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE DuplicateRecordFields #-} + +module Language.Haskell.LSP.Types.WatchedFiles where + +import Data.Aeson +import Data.Aeson.TH +import Data.Bits +import Data.Scientific +import Language.Haskell.LSP.Types.Common +import Language.Haskell.LSP.Types.Uri +import Language.Haskell.LSP.Types.Utils + +-- ------------------------------------- + +data DidChangeWatchedFilesClientCapabilities = DidChangeWatchedFilesClientCapabilities + { -- | Did change watched files notification supports dynamic + -- registration. + _dynamicRegistration :: Maybe Bool + } + deriving (Show, Read, Eq) +deriveJSON lspOptions ''DidChangeWatchedFilesClientCapabilities + +-- | Describe options to be used when registering for file system change events. +data DidChangeWatchedFilesRegistrationOptions = + DidChangeWatchedFilesRegistrationOptions + { -- | The watchers to register. + _watchers :: List FileSystemWatcher + } deriving (Show, Read, Eq) + +data FileSystemWatcher = + FileSystemWatcher + { -- | The glob pattern to watch. + -- Glob patterns can have the following syntax: + -- - @*@ to match one or more characters in a path segment + -- - @?@ to match on one character in a path segment + -- - @**@ to match any number of path segments, including none + -- - @{}@ to group conditions (e.g. @**​/*.{ts,js}@ matches all TypeScript and JavaScript files) + -- - @[]@ to declare a range of characters to match in a path segment (e.g., @example.[0-9]@ to match on @example.0@, @example.1@, …) + -- - @[!...]@ to negate a range of characters to match in a path segment (e.g., @example.[!0-9]@ to match on @example.a@, @example.b@, but not @example.0@) + _globPattern :: String, + -- | The kind of events of interest. If omitted it defaults + -- to WatchKind.Create | WatchKind.Change | WatchKind.Delete + -- which is 7. + _kind :: Maybe WatchKind + } deriving (Show, Read, Eq) + +data WatchKind = + WatchKind { + -- | Watch for create events + _watchCreate :: Bool, + -- | Watch for change events + _watchChange :: Bool, + -- | Watch for delete events + _watchDelete :: Bool + } deriving (Show, Read, Eq) + +instance ToJSON WatchKind where + toJSON wk = Number (createNum + changeNum + deleteNum) + where + createNum = if _watchCreate wk then 0x1 else 0x0 + changeNum = if _watchChange wk then 0x2 else 0x0 + deleteNum = if _watchDelete wk then 0x4 else 0x0 + +instance FromJSON WatchKind where + parseJSON (Number n) + | Right i <- floatingOrInteger n :: Either Double Int + , 0 <= i && i <= 7 = + pure $ WatchKind (testBit i 0x0) (testBit i 0x1) (testBit i 0x2) + | otherwise = mempty + parseJSON _ = mempty + +deriveJSON lspOptions ''DidChangeWatchedFilesRegistrationOptions +deriveJSON lspOptions ''FileSystemWatcher + +-- | The file event type. +data FileChangeType = FcCreated -- ^ The file got created. + | FcChanged -- ^ The file got changed. + | FcDeleted -- ^ The file got deleted. + deriving (Read,Show,Eq) + +instance ToJSON FileChangeType where + toJSON FcCreated = Number 1 + toJSON FcChanged = Number 2 + toJSON FcDeleted = Number 3 + +instance FromJSON FileChangeType where + parseJSON (Number 1) = pure FcCreated + parseJSON (Number 2) = pure FcChanged + parseJSON (Number 3) = pure FcDeleted + parseJSON _ = mempty + + +-- ------------------------------------- + +-- | An event describing a file change. +data FileEvent = + FileEvent + { -- | The file's URI. + _uri :: Uri + -- | The change type. + , _xtype :: FileChangeType + } deriving (Read,Show,Eq) + +deriveJSON lspOptions ''FileEvent + +data DidChangeWatchedFilesParams = + DidChangeWatchedFilesParams + { -- | The actual file events. + _changes :: List FileEvent + } deriving (Read,Show,Eq) + +deriveJSON lspOptions ''DidChangeWatchedFilesParams diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/Window.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Window.hs index a99ad145a..983f162ad 100644 --- a/haskell-lsp-types/src/Language/Haskell/LSP/Types/Window.hs +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/Window.hs @@ -4,62 +4,13 @@ {-# LANGUAGE TemplateHaskell #-} module Language.Haskell.LSP.Types.Window where -import Control.Monad (unless) import qualified Data.Aeson as A import Data.Aeson.TH -import Data.Maybe (catMaybes) import Data.Text (Text) -import Language.Haskell.LSP.Types.Constants -import Language.Haskell.LSP.Types.Message -import Language.Haskell.LSP.Types.Progress +import Language.Haskell.LSP.Types.Utils -- --------------------------------------------------------------------- -{- -ShowMessage Notification -https://github.com/Microsoft/language-server-protocol/blob/master/protocol.md#showmessage-notification - -The show message notification is sent from a server to a client to ask the -client to display a particular message in the user interface. - -Notification: - - method: 'window/showMessage' - params: ShowMessageParams defined as follows: - -interface ShowMessageParams { - /** - * The message type. See {@link MessageType}. - */ - type: number; - - /** - * The actual message. - */ - message: string; -} - -Where the type is defined as follows: - -enum MessageType { - /** - * An error message. - */ - Error = 1, - /** - * A warning message. - */ - Warning = 2, - /** - * An information message. - */ - Info = 3, - /** - * A log message. - */ - Log = 4 -} --} data MessageType = MtError -- ^ Error = 1, | MtWarning -- ^ Warning = 2, | MtInfo -- ^ Info = 3, @@ -88,57 +39,9 @@ data ShowMessageParams = , _message :: Text } deriving (Show, Read, Eq) -deriveJSON lspOptions{ fieldLabelModifier = customModifier } ''ShowMessageParams - -type ShowMessageNotification = NotificationMessage ServerMethod ShowMessageParams +deriveJSON lspOptions ''ShowMessageParams -- --------------------------------------------------------------------- -{- -ShowMessage Request - -https://github.com/Microsoft/language-server-protocol/blob/master/protocol.md#showmessage-request - - New: The show message request is sent from a server to a client to ask the - client to display a particular message in the user interface. In addition to - the show message notification the request allows to pass actions and to wait - for an answer from the client. - -Request: - - method: 'window/showMessageRequest' - params: ShowMessageRequestParams defined as follows: - -Response: - - result: the selected MessageActionItem - error: code and message set in case an exception happens during showing a message. - -interface ShowMessageRequestParams { - /** - * The message type. See {@link MessageType} - */ - type: number; - - /** - * The actual message - */ - message: string; - - /** - * The message action items to present. - */ - actions?: MessageActionItem[]; -} - -Where the MessageActionItem is defined as follows: - -interface MessageActionItem { - /** - * A short title like 'Retry', 'Open Log' etc. - */ - title: string; -} --} data MessageActionItem = MessageActionItem @@ -155,39 +58,9 @@ data ShowMessageRequestParams = , _actions :: Maybe [MessageActionItem] } deriving (Show,Read,Eq) -deriveJSON lspOptions{ fieldLabelModifier = customModifier } ''ShowMessageRequestParams - -type ShowMessageRequest = RequestMessage ServerMethod ShowMessageRequestParams Text -type ShowMessageResponse = ResponseMessage Text +deriveJSON lspOptions ''ShowMessageRequestParams -- --------------------------------------------------------------------- -{- -LogMessage Notification - -https://github.com/Microsoft/language-server-protocol/blob/master/protocol.md#logmessage-notification - -The log message notification is sent from the server to the client to ask the -client to log a particular message. - -Notification: - - method: 'window/logMessage' - params: LogMessageParams defined as follows: - -interface LogMessageParams { - /** - * The message type. See {@link MessageType} - */ - type: number; - - /** - * The actual message - */ - message: string; -} - -Where type is defined as above. --} data LogMessageParams = LogMessageParams { @@ -195,288 +68,4 @@ data LogMessageParams = , _message :: Text } deriving (Show, Read, Eq) -deriveJSON lspOptions{ fieldLabelModifier = customModifier } ''LogMessageParams - - -type LogMessageNotification = NotificationMessage ServerMethod LogMessageParams - -{- -Progress Begin Notification - -To start progress reporting a $/progress notification with the following payload must be sent: - -export interface WorkDoneProgressBegin { - - kind: 'begin'; - - /** - * Mandatory title of the progress operation. Used to briefly inform about - * the kind of operation being performed. - * - * Examples: "Indexing" or "Linking dependencies". - */ - title: string; - - /** - * Controls if a cancel button should show to allow the user to cancel the - * long running operation. Clients that don't support cancellation are allowed - * to ignore the setting. - */ - cancellable?: boolean; - - /** - * Optional, more detailed associated progress message. Contains - * complementary information to the `title`. - * - * Examples: "3/25 files", "project/src/module2", "node_modules/some_dep". - * If unset, the previous progress message (if any) is still valid. - */ - message?: string; - - /** - * Optional progress percentage to display (value 100 is considered 100%). - * If not provided infinite progress is assumed and clients are allowed - * to ignore the `percentage` value in subsequent in report notifications. - * - * The value should be steadily rising. Clients are free to ignore values - * that are not following this rule. - */ - percentage?: number; --} - --- | Parameters for a $/progress notification. -data ProgressParams t = - ProgressParams { - _token :: ProgressToken - , _value :: t - } deriving (Show, Read, Eq) - -deriveJSON lspOptions{ fieldLabelModifier = customModifier } ''ProgressParams - --- | Parameters for 'WorkDoneProgressBeginNotification'. --- --- @since 0.10.0.0 -data WorkDoneProgressBeginParams = - WorkDoneProgressBeginParams { - -- | Mandatory title of the progress operation. - -- Used to briefly inform about the kind of operation being - -- performed. Examples: "Indexing" or "Linking dependencies". - _title :: Text - -- | Controls if a cancel button should show to allow the user to cancel the - -- long running operation. Clients that don't support cancellation are allowed - -- to ignore the setting. - , _cancellable :: Maybe Bool - -- | Optional, more detailed associated progress - -- message. Contains complementary information to the - -- '_title'. Examples: "3/25 files", - -- "project/src/module2", "node_modules/some_dep". If - -- unset, the previous progress message (if any) is - -- still valid. - , _message :: Maybe Text - -- | Optional progress percentage to display (value 100 is considered 100%). - -- If not provided infinite progress is assumed and clients are allowed - -- to ignore the '_percentage' value in subsequent in report notifications. - -- - -- The value should be steadily rising. Clients are free to ignore values - -- that are not following this rule. - , _percentage :: Maybe Double - } deriving (Show, Read, Eq) - -instance A.ToJSON WorkDoneProgressBeginParams where - toJSON WorkDoneProgressBeginParams{..} = - A.object $ catMaybes - [ Just $ "kind" A..= ("begin" :: Text) - , Just $ "title" A..= _title - , ("cancellable" A..=) <$> _cancellable - , ("message" A..=) <$> _message - , ("percentage" A..=) <$> _percentage - ] - -instance A.FromJSON WorkDoneProgressBeginParams where - parseJSON = A.withObject "WorkDoneProgressBegin" $ \o -> do - kind <- o A..: "kind" - unless (kind == ("begin" :: Text)) $ fail $ "Expected kind \"begin\" but got " ++ show kind - _title <- o A..: "title" - _cancellable <- o A..:? "cancellable" - _message <- o A..:? "message" - _percentage <- o A..:? "percentage" - pure WorkDoneProgressBeginParams{..} - --- | The $/progress begin notification is sent from the server to the --- client to ask the client to start progress. --- --- @since 0.10.0.0 -type WorkDoneProgressBeginNotification = NotificationMessage ServerMethod (ProgressParams WorkDoneProgressBeginParams) - -{- -Progress Report Notification - -Reporting progress is done using the following payload: - -export interface WorkDoneProgressReport { - - kind: 'report'; - - /** - * Controls enablement state of a cancel button. This property is only valid if a cancel - * button got requested in the `WorkDoneProgressStart` payload. - * - * Clients that don't support cancellation or don't support control the button's - * enablement state are allowed to ignore the setting. - */ - cancellable?: boolean; - - /** - * Optional, more detailed associated progress message. Contains - * complementary information to the `title`. - * - * Examples: "3/25 files", "project/src/module2", "node_modules/some_dep". - * If unset, the previous progress message (if any) is still valid. - */ - message?: string; - - /** - * Optional progress percentage to display (value 100 is considered 100%). - * If not provided infinite progress is assumed and clients are allowed - * to ignore the `percentage` value in subsequent in report notifications. - * - * The value should be steadily rising. Clients are free to ignore values - * that are not following this rule. - */ - percentage?: number; -} --} - --- | Parameters for 'WorkDoneProgressReportNotification' --- --- @since 0.10.0.0 -data WorkDoneProgressReportParams = - WorkDoneProgressReportParams { - _cancellable :: Maybe Bool - -- | Optional, more detailed associated progress - -- message. Contains complementary information to the - -- '_title'. Examples: "3/25 files", - -- "project/src/module2", "node_modules/some_dep". If - -- unset, the previous progress message (if any) is - -- still valid. - , _message :: Maybe Text - -- | Optional progress percentage to display (value 100 is considered 100%). - -- If infinite progress was indicated in the start notification client - -- are allowed to ignore the value. In addition the value should be steadily - -- rising. Clients are free to ignore values that are not following this rule. - , _percentage :: Maybe Double - } deriving (Show, Read, Eq) - -instance A.ToJSON WorkDoneProgressReportParams where - toJSON WorkDoneProgressReportParams{..} = - A.object $ catMaybes - [ Just $ "kind" A..= ("report" :: Text) - , ("cancellable" A..=) <$> _cancellable - , ("message" A..=) <$> _message - , ("percentage" A..=) <$> _percentage - ] - -instance A.FromJSON WorkDoneProgressReportParams where - parseJSON = A.withObject "WorkDoneProgressReport" $ \o -> do - kind <- o A..: "kind" - unless (kind == ("report" :: Text)) $ fail $ "Expected kind \"report\" but got " ++ show kind - _cancellable <- o A..:? "cancellable" - _message <- o A..:? "message" - _percentage <- o A..:? "percentage" - pure WorkDoneProgressReportParams{..} - --- | The workdone $/progress report notification is sent from the server to the --- client to report progress for a previously started progress. --- --- @since 0.10.0.0 -type WorkDoneProgressReportNotification = NotificationMessage ServerMethod (ProgressParams WorkDoneProgressReportParams) - -{- -Progress End Notification - -Signaling the end of a progress reporting is done using the following payload: - -export interface WorkDoneProgressEnd { - - kind: 'end'; - - /** - * Optional, a final message indicating to for example indicate the outcome - * of the operation. - */ - message?: string; -} --} - --- | Parameters for 'WorkDoneProgressEndNotification'. --- --- @since 0.10.0.0 -data WorkDoneProgressEndParams = - WorkDoneProgressEndParams { - _message :: Maybe Text - } deriving (Show, Read, Eq) - -instance A.ToJSON WorkDoneProgressEndParams where - toJSON WorkDoneProgressEndParams{..} = - A.object $ catMaybes - [ Just $ "kind" A..= ("end" :: Text) - , ("message" A..=) <$> _message - ] - -instance A.FromJSON WorkDoneProgressEndParams where - parseJSON = A.withObject "WorkDoneProgressEnd" $ \o -> do - kind <- o A..: "kind" - unless (kind == ("end" :: Text)) $ fail $ "Expected kind \"end\" but got " ++ show kind - _message <- o A..:? "message" - pure WorkDoneProgressEndParams{..} - --- | The $/progress end notification is sent from the server to the --- client to stop a previously started progress. --- --- @since 0.10.0.0 -type WorkDoneProgressEndNotification = NotificationMessage ServerMethod (ProgressParams WorkDoneProgressEndParams) - -{- -Progress Cancel Notification - -The window/workDoneProgress/cancel notification is sent from the client to the server to inform the server that the user has pressed the cancel button on the progress UX. A server receiving a cancel request must still close a progress using the done notification. - -Notification: - -method: 'window/workDoneProgress/cancel' -params: WorkDoneProgressCancelParams defined as follows: -export interface WorkDoneProgressCancelParams { - /** - * The token to be used to report progress. - */ - token: ProgressToken; -} --} - --- | Parameters for 'WorkDoneProgressCancelNotification'. --- --- @since 0.10.0.0 -data WorkDoneProgressCancelParams = - WorkDoneProgressCancelParams { - -- | A unique identifier to associate multiple progress - -- notifications with the same progress. - _token :: ProgressToken - } deriving (Show, Read, Eq) - -deriveJSON lspOptions{ fieldLabelModifier = customModifier } ''WorkDoneProgressCancelParams - --- | The window/workDoneProgress/cancel notification is sent from the client to the server --- to inform the server that the user has pressed the cancel button on the progress UX. --- A server receiving a cancel request must still close a progress using the done notification. --- --- @since 0.10.0.0 -type WorkDoneProgressCancelNotification = NotificationMessage ClientMethod WorkDoneProgressCancelParams - -data WorkDoneProgressCreateParams = - WorkDoneProgressCreateParams { - _token :: ProgressToken - } deriving (Show, Read, Eq) - -deriveJSON lspOptions{ fieldLabelModifier = customModifier } ''WorkDoneProgressCreateParams - -type WorkDoneProgressCreateRequest = RequestMessage ServerMethod WorkDoneProgressCreateParams () +deriveJSON lspOptions ''LogMessageParams diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/WorkspaceEdit.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/WorkspaceEdit.hs index 5c21bc286..a37746064 100644 --- a/haskell-lsp-types/src/Language/Haskell/LSP/Types/WorkspaceEdit.hs +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/WorkspaceEdit.hs @@ -1,43 +1,21 @@ -{-# LANGUAGE CPP #-} {-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE OverloadedStrings #-} module Language.Haskell.LSP.Types.WorkspaceEdit where +import Data.Aeson import Data.Aeson.TH import qualified Data.HashMap.Strict as H --- For <= 8.2.2 -import Data.Monoid ((<>)) import Data.Text (Text) import qualified Data.Text as T -import Language.Haskell.LSP.Types.Constants -import Language.Haskell.LSP.Types.List + +import Language.Haskell.LSP.Types.Common import Language.Haskell.LSP.Types.Location +import Language.Haskell.LSP.Types.TextDocument import Language.Haskell.LSP.Types.Uri +import Language.Haskell.LSP.Types.Utils -- --------------------------------------------------------------------- -{- -TextEdit - -https://github.com/Microsoft/language-server-protocol/blob/master/protocol.md#textedit - -A textual edit applicable to a text document. - -interface TextEdit { - /** - * The range of the text document to be manipulated. To insert - * text into a document create a range where start === end. - */ - range: Range; - - /** - * The string to be inserted. For delete operations use an - * empty string. - */ - newText: string; -} - - --} data TextEdit = TextEdit @@ -47,61 +25,8 @@ data TextEdit = deriveJSON lspOptions ''TextEdit --- --------------------------------------------------------------------- -{- -VersionedTextDocumentIdentifier - -https://github.com/Microsoft/language-server-protocol/blob/master/protocol.md#versionedtextdocumentidentifier - - New: An identifier to denote a specific version of a text document. - -interface VersionedTextDocumentIdentifier extends TextDocumentIdentifier { - /** - * The version number of this document. If a versioned text document identifier - * is sent from the server to the client and the file is not open in the editor - * (the server has not received an open notification before) the server can send - * `null` to indicate that the version is known and the content on disk is the - * truth (as speced with document content ownership) - */ - version: number | null; --} - -type TextDocumentVersion = Maybe Int - -data VersionedTextDocumentIdentifier = - VersionedTextDocumentIdentifier - { _uri :: Uri - , _version :: TextDocumentVersion - } deriving (Show, Read, Eq) - -deriveJSON lspOptions ''VersionedTextDocumentIdentifier -- --------------------------------------------------------------------- -{- -New in 3.0 ----------- - -TextDocumentEdit -https://github.com/Microsoft/language-server-protocol/blob/master/protocol.md#new-textdocumentedit - -If multiple TextEdits are applied to a text document, all text edits describe -changes made to the initial document version. Execution wise text edits should -applied from the bottom to the top of the text document. Overlapping text edits -are not supported. - -export interface TextDocumentEdit { - /** - * The text document to change. - */ - textDocument: VersionedTextDocumentIdentifier; - - /** - * The edits to be applied. - */ - edits: TextEdit[]; -} - --} data TextDocumentEdit = TextDocumentEdit @@ -112,34 +37,6 @@ data TextDocumentEdit = deriveJSON lspOptions ''TextDocumentEdit -- --------------------------------------------------------------------- -{- -Changed in 3.0 --------------- - -WorkspaceEdit - -https://github.com/Microsoft/language-server-protocol/blob/master/protocol.md#workspaceedit - - -Changed A workspace edit represents changes to many resources managed in the -workspace. The edit should either provide changes or documentChanges. If -documentChanges are present they are preferred over changes if the client can -handle versioned document edits. - -export interface WorkspaceEdit { - /** - * Holds changes to existing resources. - */ - changes?: { [uri: string]: TextEdit[]; }; - - /** - * An array of `TextDocumentEdit`s to express changes to specific a specific - * version of a text document. Whether a client supports versioned document - * edits is expressed via `WorkspaceClientCapabilities.versionedWorkspaceEdit`. - */ - documentChanges?: TextDocumentEdit[]; -} --} type WorkspaceEditMap = H.HashMap Uri (List TextEdit) @@ -149,17 +46,93 @@ data WorkspaceEdit = , _documentChanges :: Maybe (List TextDocumentEdit) } deriving (Show, Read, Eq) +instance Semigroup WorkspaceEdit where + (WorkspaceEdit a b) <> (WorkspaceEdit c d) = WorkspaceEdit (a <> c) (b <> d) instance Monoid WorkspaceEdit where mempty = WorkspaceEdit Nothing Nothing - mappend (WorkspaceEdit a b) (WorkspaceEdit c d) = WorkspaceEdit (a <> c) (b <> d) - -#if __GLASGOW_HASKELL__ >= 804 -instance Semigroup WorkspaceEdit where - (<>) = mappend -#endif deriveJSON lspOptions ''WorkspaceEdit +-- ------------------------------------- + +data ResourceOperationKind + = ResourceOperationCreate -- ^ Supports creating new files and folders. + | ResourceOperationRename -- ^ Supports renaming existing files and folders. + | ResourceOperationDelete -- ^ Supports deleting existing files and folders. + deriving (Read, Show, Eq) + +instance ToJSON ResourceOperationKind where + toJSON ResourceOperationCreate = String "create" + toJSON ResourceOperationRename = String "rename" + toJSON ResourceOperationDelete = String "delete" + +instance FromJSON ResourceOperationKind where + parseJSON (String "create") = pure ResourceOperationCreate + parseJSON (String "rename") = pure ResourceOperationRename + parseJSON (String "delete") = pure ResourceOperationDelete + parseJSON _ = mempty + +data FailureHandlingKind + = FailureHandlingAbort -- ^ Applying the workspace change is simply aborted if one of the changes provided fails. All operations executed before the failing operation stay executed. + | FailureHandlingTransactional -- ^ All operations are executed transactional. That means they either all succeed or no changes at all are applied to the workspace. + | FailureHandlingTextOnlyTransactional -- ^ If the workspace edit contains only textual file changes they are executed transactional. If resource changes (create, rename or delete file) are part of the change the failure handling strategy is abort. + | FailureHandlingUndo -- ^ The client tries to undo the operations already executed. But there is no guarantee that this is succeeding. + deriving (Read, Show, Eq) + +instance ToJSON FailureHandlingKind where + toJSON FailureHandlingAbort = String "abort" + toJSON FailureHandlingTransactional = String "transactional" + toJSON FailureHandlingTextOnlyTransactional = String "textOnlyTransactional" + toJSON FailureHandlingUndo = String "undo" + +instance FromJSON FailureHandlingKind where + parseJSON (String "abort") = pure FailureHandlingAbort + parseJSON (String "transactional") = pure FailureHandlingTransactional + parseJSON (String "textOnlyTransactional") = pure FailureHandlingTextOnlyTransactional + parseJSON (String "undo") = pure FailureHandlingUndo + parseJSON _ = mempty + +data WorkspaceEditClientCapabilities = + WorkspaceEditClientCapabilities + { _documentChanges :: Maybe Bool -- ^The client supports versioned document + -- changes in 'WorkspaceEdit's + -- | The resource operations the client supports. Clients should at least + -- support @create@, @rename@ and @delete@ files and folders. + , _resourceOperations :: Maybe (List ResourceOperationKind) + -- | The failure handling strategy of a client if applying the workspace edit + -- fails. + , _failureHandling :: Maybe FailureHandlingKind + } deriving (Show, Read, Eq) + +deriveJSON lspOptions ''WorkspaceEditClientCapabilities + +-- --------------------------------------------------------------------- + +data ApplyWorkspaceEditParams = + ApplyWorkspaceEditParams + { -- | An optional label of the workspace edit. This label is + -- presented in the user interface for example on an undo + -- stack to undo the workspace edit. + _label :: Maybe Text + -- | The edits to apply + , _edit :: WorkspaceEdit + } deriving (Show, Read, Eq) + +deriveJSON lspOptions ''ApplyWorkspaceEditParams + +data ApplyWorkspaceEditResponseBody = + ApplyWorkspaceEditResponseBody + { -- | Indicates whether the edit was applied or not. + _applied :: Bool + -- | An optional textual description for why the edit was not applied. + -- This may be used may be used by the server for diagnostic + -- logging or to provide a suitable error for a request that + -- triggered the edit. + , _failureReason :: Maybe Text + } deriving (Show, Read, Eq) + +deriveJSON lspOptions ''ApplyWorkspaceEditResponseBody + -- --------------------------------------------------------------------- -- | Applies a 'TextEdit' to some 'Text'. diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/WorkspaceFolders.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/WorkspaceFolders.hs index 41bbd9188..4898ef993 100644 --- a/haskell-lsp-types/src/Language/Haskell/LSP/Types/WorkspaceFolders.hs +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/WorkspaceFolders.hs @@ -4,50 +4,9 @@ module Language.Haskell.LSP.Types.WorkspaceFolders where import Data.Aeson.TH import Data.Text ( Text ) -import Language.Haskell.LSP.Types.Constants -import Language.Haskell.LSP.Types.List -import Language.Haskell.LSP.Types.Message -{- -Workspace folders request (:arrow_right_hook:) -Since version 3.6.0 - -Many tools support more than one root folder per workspace. Examples for this -are VS Code’s multi-root support, Atom’s project folder support or Sublime’s -project support. If a client workspace consists of multiple roots then a server -typically needs to know about this. The protocol up to now assumes one root -folder which is announce to the server by the rootUri property of the -InitializeParams. If the client supports workspace folders and announces them -via the corrsponding workspaceFolders client capability the InitializeParams -contain an additional property workspaceFolders with the configured workspace -folders when the server starts. - -The workspace/workspaceFolders request is sent from the server to the client to -fetch the current open list of workspace folders. Returns null in the response -if only a single file is open in the tool. Returns an empty array if a workspace -is open but no folders are configured. - -Request: - -method: ‘workspace/workspaceFolders’ -params: none -Response: - -result: WorkspaceFolder[] | null defines as follows: -export interface WorkspaceFolder { - /** - * The associated URI for this workspace folder. - */ - uri: string; - - /** - * The name of the workspace folder. Defaults to the - * uri's basename. - */ - name: string; -} -error: code and message set in case an exception happens during the ‘workspace/workspaceFolders’ request --} +import Language.Haskell.LSP.Types.Common +import Language.Haskell.LSP.Types.Utils data WorkspaceFolder = WorkspaceFolder @@ -59,55 +18,6 @@ data WorkspaceFolder = deriveJSON lspOptions ''WorkspaceFolder -type WorkspaceFoldersRequest = RequestMessage ServerMethod () (Maybe (List WorkspaceFolder)) -type WorkspaceFoldersResponse = ResponseMessage (Maybe (List WorkspaceFolder)) - -{- -DidChangeWorkspaceFolders Notification (:arrow_right:) -Since version 3.6.0 - -The workspace/didChangeWorkspaceFolders notification is sent from the client to -the server to inform the server about workspace folder configuration changes. -The notification is sent by default if both -ServerCapabilities/workspace/workspaceFolders and -ClientCapabilities/workspace/workspaceFolders are true; or if the server has -registered to receive this notification it first. To register for the -workspace/didChangeWorkspaceFolders send a client/registerCapability request -from the client to the server. The registration parameter must have a -registrations item of the following form, where id is a unique id used to -unregister the capability (the example uses a UUID): - -{ - id: "28c6150c-bd7b-11e7-abc4-cec278b6b50a", - method: "workspace/didChangeWorkspaceFolders" -} -Notification: - -method: ‘workspace/didChangeWorkspaceFolders’ -params: DidChangeWorkspaceFoldersParams defined as follows: -export interface DidChangeWorkspaceFoldersParams { - /** - * The actual workspace folder change event. - */ - event: WorkspaceFoldersChangeEvent; -} - -/** - * The workspace folder change event. - */ -export interface WorkspaceFoldersChangeEvent { - /** - * The array of added workspace folders - */ - added: WorkspaceFolder[]; - - /** - * The array of the removed workspace folders - */ - removed: WorkspaceFolder[]; -} --} - -- | The workspace folder change event. data WorkspaceFoldersChangeEvent = WorkspaceFoldersChangeEvent @@ -125,5 +35,3 @@ data DidChangeWorkspaceFoldersParams = deriveJSON lspOptions ''DidChangeWorkspaceFoldersParams -type DidChangeWorkspaceFoldersNotification = - NotificationMessage ClientMethod DidChangeWorkspaceFoldersParams diff --git a/haskell-lsp-types/src/Language/Haskell/LSP/Types/WorkspaceSymbol.hs b/haskell-lsp-types/src/Language/Haskell/LSP/Types/WorkspaceSymbol.hs new file mode 100644 index 000000000..eae512d37 --- /dev/null +++ b/haskell-lsp-types/src/Language/Haskell/LSP/Types/WorkspaceSymbol.hs @@ -0,0 +1,76 @@ +{-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE DuplicateRecordFields #-} + +module Language.Haskell.LSP.Types.WorkspaceSymbol where + +import Data.Aeson.TH +import Data.Default +import Language.Haskell.LSP.Types.Common +import Language.Haskell.LSP.Types.DocumentSymbol +import Language.Haskell.LSP.Types.Progress +import Language.Haskell.LSP.Types.Utils + +data WorkspaceSymbolKindClientCapabilities = + WorkspaceSymbolKindClientCapabilities + { -- | The symbol kind values the client supports. When this + -- property exists the client also guarantees that it will + -- handle values outside its set gracefully and falls back + -- to a default value when unknown. + -- + -- If this property is not present the client only supports + -- the symbol kinds from `File` to `Array` as defined in + -- the initial version of the protocol. + _valueSet :: Maybe (List SymbolKind) + } deriving (Show, Read, Eq) + +deriveJSON lspOptions ''WorkspaceSymbolKindClientCapabilities + +instance Default WorkspaceSymbolKindClientCapabilities where + def = WorkspaceSymbolKindClientCapabilities (Just $ List allKinds) + where allKinds = [ SkFile + , SkModule + , SkNamespace + , SkPackage + , SkClass + , SkMethod + , SkProperty + , SkField + , SkConstructor + , SkEnum + , SkInterface + , SkFunction + , SkVariable + , SkConstant + , SkString + , SkNumber + , SkBoolean + , SkArray + ] + +data WorkspaceSymbolClientCapabilities = + WorkspaceSymbolClientCapabilities + { _dynamicRegistration :: Maybe Bool -- ^Symbol request supports dynamic + -- registration. + , _symbolKind :: Maybe WorkspaceSymbolKindClientCapabilities -- ^ Specific capabilities for the `SymbolKind`. + } deriving (Show, Read, Eq) + +deriveJSON lspOptions ''WorkspaceSymbolClientCapabilities + +-- ------------------------------------- + +makeExtendingDatatype "WorkspaceSymbolOptions" [''WorkDoneProgressOptions] [] +deriveJSON lspOptions ''WorkspaceSymbolOptions + +makeExtendingDatatype "WorkspaceSymbolRegistrationOptions" + [''WorkspaceSymbolOptions] [] +deriveJSON lspOptions ''WorkspaceSymbolRegistrationOptions + +-- ------------------------------------- + +makeExtendingDatatype "WorkspaceSymbolParams" + [ ''WorkDoneProgressParams + , ''PartialResultParams + ] + [("_query", [t| String |])] + +deriveJSON lspOptions ''WorkspaceSymbolParams diff --git a/haskell-lsp.cabal b/haskell-lsp.cabal index cacb1672c..620bd3e63 100644 --- a/haskell-lsp.cabal +++ b/haskell-lsp.cabal @@ -24,13 +24,9 @@ library reexported-modules: Language.Haskell.LSP.Types , Language.Haskell.LSP.Types.Capabilities , Language.Haskell.LSP.Types.Lens - exposed-modules: Language.Haskell.LSP.Capture - , Language.Haskell.LSP.Constant - , Language.Haskell.LSP.Core + exposed-modules: Language.Haskell.LSP.Core , Language.Haskell.LSP.Control , Language.Haskell.LSP.Diagnostics - , Language.Haskell.LSP.Messages - , Language.Haskell.LSP.Utility , Language.Haskell.LSP.VFS -- other-modules: -- other-extensions: @@ -47,25 +43,32 @@ library , hslogger , hashable , haskell-lsp-types == 0.23.* + , dependent-map , lens >= 4.15.2 , mtl , network-uri , rope-utf16-splay >= 0.3.1.0 , sorted-list == 0.2.1.* , stm + , scientific , temporary , text + , transformers , time , unordered-containers + , unliftio-core + -- used for generating random uuids for dynamic registration + , random + , uuid >= 1.3 hs-source-dirs: src default-language: Haskell2010 + ghc-options: -Wall -fprint-explicit-kinds -executable lsp-hello - main-is: Main.hs +executable lsp-demo-reactor-server + main-is: Reactor.hs hs-source-dirs: example - -- src default-language: Haskell2010 - ghc-options: -Wall + ghc-options: -Wall -Wno-unticked-promoted-constructors build-depends: base >= 4.9 && < 4.15 , aeson @@ -73,25 +76,38 @@ executable lsp-hello , containers , directory , data-default + , dependent-map , filepath , hslogger , lens >= 4.15.2 , mtl , network-uri - , rope-utf16-splay >= 0.2 , stm , text , time , transformers , unordered-containers - , vector + , unliftio -- the package library. Comment this out if you want repl changes to propagate , haskell-lsp if !flag(demo) buildable: False +executable lsp-demo-simple-server + main-is: Simple.hs + hs-source-dirs: example + default-language: Haskell2010 + ghc-options: -Wall -Wno-unticked-promoted-constructors + build-depends: base >= 4.9 && < 5 + , data-default + -- the package library. Comment this out if you want repl changes to propagate + , haskell-lsp + , text + if !flag(demo) + buildable: False + flag demo { - description: Build the lsp-hello demo executable + description: Build the demo executables default: False } @@ -110,8 +126,6 @@ test-suite haskell-lsp-test URIFilePathSpec VspSpec WorkspaceEditSpec - WorkspaceFoldersSpec - InitialConfigurationSpec build-depends: base , QuickCheck , aeson diff --git a/hie.yaml b/hie.yaml new file mode 100644 index 000000000..e695c10fd --- /dev/null +++ b/hie.yaml @@ -0,0 +1,21 @@ +# This is a sample hie.yaml file for opening haskell-language-server +# in hie, using cabal as the build system. To use is, copy it to a +# file called 'hie.yaml' +# WARNING: This configuration works for hie but does not for +# haskell-language-server or ghcide. +# They need support for multi-cradle: +# https://github.com/digital-asset/ghcide/issues/113 +cradle: + cabal: + - path: "./haskell-lsp-types" + component: "haskell-lsp-types" + - path: "./src" + component: "haskell-lsp" + - path: "./test" + component: "haskell-lsp-test" + - path: "./func-test" + component: "func-test" + - path: "./example/Reactor.hs" + component: "lsp-demo-reactor-server" + - path: "./example/Simple.hs" + component: "lsp-demo-simple-server" diff --git a/src/Language/Haskell/LSP/Capture.hs b/src/Language/Haskell/LSP/Capture.hs deleted file mode 100644 index a782cd725..000000000 --- a/src/Language/Haskell/LSP/Capture.hs +++ /dev/null @@ -1,55 +0,0 @@ -{-# LANGUAGE DeriveAnyClass #-} -{-# LANGUAGE DeriveGeneric #-} -{-# LANGUAGE OverloadedStrings #-} -module Language.Haskell.LSP.Capture - ( Event(..) - , CaptureContext - , noCapture - , captureToFile - , captureFromClient - , captureFromServer - ) where - -import Data.Aeson -import Data.ByteString.Lazy.Char8 as BSL -import Data.Time.Clock -import GHC.Generics -import Language.Haskell.LSP.Messages -import System.IO -import Language.Haskell.LSP.Utility -import Control.Concurrent -import Control.Monad -import Control.Concurrent.STM - -data Event = FromClient !UTCTime !FromClientMessage - | FromServer !UTCTime !FromServerMessage - deriving (Show, Eq, Generic, ToJSON, FromJSON) - -data CaptureContext = NoCapture | Capture (TChan Event) - -noCapture :: CaptureContext -noCapture = NoCapture - -captureToFile :: FilePath -> IO CaptureContext -captureToFile fname = do - logs $ "haskell-lsp:Logging to " ++ fname - chan <- newTChanIO - _tid <- forkIO $ withFile fname WriteMode $ writeToHandle chan - return $ Capture chan - -captureFromServer :: FromServerMessage -> CaptureContext -> IO () -captureFromServer _ NoCapture = return () -captureFromServer msg (Capture chan) = do - time <- getCurrentTime - atomically $ writeTChan chan $ FromServer time msg - -captureFromClient :: FromClientMessage -> CaptureContext -> IO () -captureFromClient _ NoCapture = return () -captureFromClient msg (Capture chan) = do - time <- getCurrentTime - atomically $ writeTChan chan $ FromClient time msg - -writeToHandle :: TChan Event -> Handle -> IO () -writeToHandle chan hdl = forever $ do - ev <- atomically $ readTChan chan - BSL.hPutStrLn hdl $ encode ev diff --git a/src/Language/Haskell/LSP/Constant.hs b/src/Language/Haskell/LSP/Constant.hs deleted file mode 100644 index 0cd9cdf10..000000000 --- a/src/Language/Haskell/LSP/Constant.hs +++ /dev/null @@ -1,13 +0,0 @@ -module Language.Haskell.LSP.Constant where - -_LOG_NAME :: String -_LOG_NAME = "haskell-lsp" - -_LOG_FORMAT :: String --- _LOG_FORMAT = "$time [$tid] $prio $loggername - $msg" -_LOG_FORMAT = "$time [$tid] - $msg" - -_LOG_FORMAT_DATE :: String --- _LOG_FORMAT_DATE = "%Y-%m-%d %H:%M:%S" -_LOG_FORMAT_DATE = "%Y-%m-%d %H:%M:%S%Q" - diff --git a/src/Language/Haskell/LSP/Control.hs b/src/Language/Haskell/LSP/Control.hs index 94a953ec8..de7a9258b 100644 --- a/src/Language/Haskell/LSP/Control.hs +++ b/src/Language/Haskell/LSP/Control.hs @@ -1,9 +1,7 @@ -{-# LANGUAGE CPP #-} -{-# LANGUAGE GADTs #-} -{-# LANGUAGE MultiWayIf #-} -{-# LANGUAGE BinaryLiterals #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE TypeOperators #-} module Language.Haskell.LSP.Control ( @@ -14,7 +12,6 @@ module Language.Haskell.LSP.Control import Control.Concurrent import Control.Concurrent.STM.TChan -import Control.Concurrent.STM.TVar import Control.Monad import Control.Monad.STM import qualified Data.Aeson as J @@ -23,46 +20,39 @@ import Data.Attoparsec.ByteString.Char8 import qualified Data.ByteString as BS import Data.ByteString.Builder.Extra (defaultChunkSize) import qualified Data.ByteString.Lazy as BSL -import qualified Data.ByteString.Lazy.Char8 as B -import Data.Time.Clock -import Data.Time.Format -#if __GLASGOW_HASKELL__ < 804 -import Data.Monoid -#endif -import Language.Haskell.LSP.Capture +import qualified Data.Text.Lazy as TL +import qualified Data.Text.Lazy.Encoding as TL +import qualified Data.Text as T +import qualified Data.Text.Encoding as T +import Data.List import qualified Language.Haskell.LSP.Core as Core -import Language.Haskell.LSP.Messages import Language.Haskell.LSP.VFS -import Language.Haskell.LSP.Utility import System.IO -import System.FilePath +import System.Log.Logger -- --------------------------------------------------------------------- -- | Convenience function for 'runWithHandles stdin stdout'. -run :: (Show configs) => Core.InitializeCallbacks configs +run :: Core.InitializeCallbacks config -- ^ function to be called once initialize has -- been received from the client. Further message -- processing will start only after this returns. - -> Core.Handlers -> Core.Options - -> Maybe FilePath -- ^ File to capture the session to. -> IO Int run = runWithHandles stdin stdout -- | Convenience function for 'runWith' using the specified handles. -runWithHandles :: (Show config) => +runWithHandles :: Handle -- ^ Handle to read client input from. -> Handle -- ^ Handle to write output to. -> Core.InitializeCallbacks config - -> Core.Handlers -> Core.Options - -> Maybe FilePath -> IO Int -- exit code -runWithHandles hin hout initializeCallbacks h o captureFp = do +runWithHandles hin hout initializeCallbacks o = do + hSetBuffering hin NoBuffering hSetEncoding hin utf8 @@ -76,68 +66,84 @@ runWithHandles hin hout initializeCallbacks h o captureFp = do BSL.hPut hout out hFlush hout - runWith clientIn clientOut initializeCallbacks h o captureFp + runWith clientIn clientOut initializeCallbacks o -- | Starts listening and sending requests and responses -- using the specified I/O. -runWith :: (Show config) => +runWith :: IO BS.ByteString -- ^ Client input. -> (BSL.ByteString -> IO ()) -- ^ Function to provide output to. -> Core.InitializeCallbacks config - -> Core.Handlers -> Core.Options - -> Maybe FilePath -> IO Int -- exit code -runWith clientIn clientOut initializeCallbacks h o captureFp = do - - logm $ B.pack "\n\n\n\n\nhaskell-lsp:Starting up server ..." +runWith clientIn clientOut initializeCallbacks o = do - timestamp <- formatTime defaultTimeLocale (iso8601DateFormat (Just "%H-%M-%S")) <$> getCurrentTime - let timestampCaptureFp = fmap (\f -> dropExtension f ++ timestamp ++ takeExtension f) - captureFp - captureCtx <- maybe (return noCapture) captureToFile timestampCaptureFp + infoM "haskell-lsp.runWith" "\n\n\n\n\nhaskell-lsp:Starting up server ..." - cout <- atomically newTChan :: IO (TChan FromServerMessage) - _rhpid <- forkIO $ sendServer cout clientOut captureCtx + cout <- atomically newTChan :: IO (TChan J.Value) + _rhpid <- forkIO $ sendServer cout clientOut + let sendMsg msg = atomically $ writeTChan cout $ J.toJSON msg - let sendFunc :: Core.SendFunc - sendFunc msg = atomically $ writeTChan cout msg - let lf = error "LifeCycle error, ClientCapabilities not set yet via initialize maessage" - - tvarId <- atomically $ newTVar 0 initVFS $ \vfs -> do - tvarDat <- atomically $ newTVar $ Core.defaultLanguageContextData h o lf tvarId sendFunc captureCtx vfs - - ioLoop clientIn initializeCallbacks tvarDat + ioLoop clientIn initializeCallbacks vfs o sendMsg return 1 - -- --------------------------------------------------------------------- -ioLoop :: (Show config) => IO BS.ByteString - -> Core.InitializeCallbacks config - -> TVar (Core.LanguageContextData config) - -> IO () -ioLoop clientIn dispatcherProc tvarDat = - go (parse parser "") +ioLoop :: + IO BS.ByteString + -> Core.InitializeCallbacks config + -> VFS + -> Core.Options + -> (Core.FromServerMessage -> IO ()) + -> IO () +ioLoop clientIn initializeCallbacks vfs o sendMsg = do + minitialize <- parseOne (parse parser "") + case minitialize of + Nothing -> pure () + Just (msg,remainder) -> do + case J.eitherDecode $ BSL.fromStrict msg of + Left err -> + errorM "haskell-lsp.ioLoop" $ + "Got error while decoding initialize:\n" <> err <> "\n exiting 1 ...\n" + Right initialize -> do + mInitResp <- Core.initializeRequestHandler initializeCallbacks vfs o sendMsg initialize + case mInitResp of + Nothing -> pure () + Just env -> loop env (parse parser remainder) where - go :: Result BS.ByteString -> IO () - go (Fail _ ctxs err) = logm $ B.pack - "\nhaskell-lsp: Failed to parse message header:\n" <> B.intercalate " > " (map str2lbs ctxs) <> ": " <> - str2lbs err <> "\n exiting 1 ...\n" - go (Partial c) = do + + parseOne :: Result BS.ByteString -> IO (Maybe (BS.ByteString,BS.ByteString)) + parseOne (Fail _ ctxs err) = do + errorM "haskell-lsp.parseOne" $ + "Failed to parse message header:\n" <> intercalate " > " ctxs <> ": " <> + err <> "\n exiting 1 ...\n" + pure Nothing + parseOne (Partial c) = do bs <- clientIn if BS.null bs - then logm $ B.pack "\nhaskell-lsp:Got EOF, exiting 1 ...\n" - else go (c bs) - go (Done remainder msg) = do - logm $ B.pack "---> " <> BSL.fromStrict msg - Core.handleMessage dispatcherProc tvarDat (BSL.fromStrict msg) - go (parse parser remainder) + then do + errorM "haskell-lsp.parseON" "haskell-lsp:Got EOF, exiting 1 ...\n" + pure Nothing + else parseOne (c bs) + parseOne (Done remainder msg) = do + debugM "haskell-lsp.parseOne" $ "---> " <> T.unpack (T.decodeUtf8 msg) + pure $ Just (msg,remainder) + + loop env = go + where + go r = do + res <- parseOne r + case res of + Nothing -> pure () + Just (msg,remainder) -> do + Core.runLspT env $ Core.processMessage $ BSL.fromStrict msg + go (parse parser remainder) + parser = do _ <- string "Content-Length: " len <- decimal @@ -147,25 +153,22 @@ ioLoop clientIn dispatcherProc tvarDat = -- --------------------------------------------------------------------- -- | Simple server to make sure all output is serialised -sendServer :: TChan FromServerMessage -> (BSL.ByteString -> IO ()) -> CaptureContext -> IO () -sendServer msgChan clientOut captureCtxt = +sendServer :: TChan J.Value -> (BSL.ByteString -> IO ()) -> IO () +sendServer msgChan clientOut = do forever $ do msg <- atomically $ readTChan msgChan -- We need to make sure we only send over the content of the message, -- and no other tags/wrapper stuff - let str = J.encode $ - J.genericToJSON (J.defaultOptions { J.sumEncoding = J.UntaggedValue }) msg + let str = J.encode msg let out = BSL.concat - [ str2lbs $ "Content-Length: " ++ show (BSL.length str) - , BSL.fromStrict _TWO_CRLF - , str ] + [ TL.encodeUtf8 $ TL.pack $ "Content-Length: " ++ show (BSL.length str) + , BSL.fromStrict _TWO_CRLF + , str ] clientOut out - logm $ B.pack "<--2--" <> str - - captureFromServer msg captureCtxt + debugM "haskell-lsp.sendServer" $ "<--2--" <> TL.unpack (TL.decodeUtf8 str) -- | -- diff --git a/src/Language/Haskell/LSP/Core.hs b/src/Language/Haskell/LSP/Core.hs index a24cb7d98..c4af9f4cc 100644 --- a/src/Language/Haskell/LSP/Core.hs +++ b/src/Language/Haskell/LSP/Core.hs @@ -1,60 +1,126 @@ -{-# LANGUAGE NamedFieldPuns #-} -{-# LANGUAGE GADTs #-} -{-# LANGUAGE MultiWayIf #-} -{-# LANGUAGE BinaryLiterals #-} -{-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE RankNTypes #-} -{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE TypeFamilyDependencies #-} +{-# LANGUAGE UndecidableInstances #-} +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE GADTs #-} +{-# LANGUAGE MultiWayIf #-} +{-# LANGUAGE BinaryLiterals #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE ViewPatterns #-} +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE TypeApplications #-} +{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE FunctionalDependencies #-} +{-# LANGUAGE TypeOperators #-} +{-# LANGUAGE RecursiveDo #-} +{-# OPTIONS_GHC -Wno-unticked-promoted-constructors #-} +{-# OPTIONS_GHC -fprint-explicit-kinds #-} + module Language.Haskell.LSP.Core ( - handleMessage - , LanguageContextData(..) + processMessage , VFSData(..) - , Handler , InitializeCallbacks(..) - , LspFuncs(..) - , Progress(..) - , ProgressCancellable(..) - , ProgressCancelledException - , SendFunc + + -- * Handlers , Handlers(..) + , Handler + , transmuteHandlers + , mapHandlers + , notificationHandler + , requestHandler + , ClientMessageHandler(..) + , Options(..) - , defaultLanguageContextData - , makeResponseMessage - , makeResponseError + + -- * LspT and LspM + , LspT(..) + , LspM + , MonadLsp(..) + , runLspT + , LanguageContextEnv(..) + , type (<~>)(..) + + , getClientCapabilities + , getConfig + , getRootPath + , getWorkspaceFolders + + , sendRequest + , sendNotification + + -- * VFS + , getVirtualFile + , getVirtualFiles + , persistVirtualFile + , getVersionedTextDoc + , reverseFileMap + + -- * Diagnostics + , publishDiagnostics + , flushDiagnosticsBySource + + -- * Progress + , withProgress + , withIndefiniteProgress + , ProgressAmount(..) + , ProgressCancellable(..) + , ProgressCancelledException + + -- * Dynamic registration + , registerCapability + , unregisterCapability + , RegistrationToken + , setupLogger - , sendErrorResponseS - , sendErrorLogS - , sendErrorShowS , reverseSortEdit - , Priority(..) + , initializeRequestHandler + , FromServerMessage ) where import Control.Concurrent.Async import Control.Concurrent.STM import qualified Control.Exception as E import Control.Monad +import Control.Applicative +import Control.Monad.Fix import Control.Monad.IO.Class +import Control.Monad.Trans.Except +import Control.Monad.Trans.Reader +import Control.Monad.Trans.Class +import Control.Monad.IO.Unlift import Control.Lens ( (<&>), (^.), (^?), _Just ) import qualified Data.Aeson as J +import qualified Data.Aeson.Types as J import qualified Data.ByteString.Lazy as BSL -import qualified Data.ByteString.Lazy.Char8 as B import Data.Default +import Data.Functor.Product +import Data.IxMap +import qualified Data.Dependent.Map as DMap +import Data.Dependent.Map (DMap) import qualified Data.HashMap.Strict as HM +import Data.Kind import qualified Data.List as L import Data.List.NonEmpty (NonEmpty(..)) import qualified Data.Map as Map import Data.Maybe -import Data.Monoid +import Data.Monoid hiding (Product) import qualified Data.Text as T import Data.Text ( Text ) -import Language.Haskell.LSP.Capture -import Language.Haskell.LSP.Constant -import Language.Haskell.LSP.Messages -import qualified Language.Haskell.LSP.Types.Capabilities as C -import qualified Language.Haskell.LSP.Types as J -import qualified Language.Haskell.LSP.Types.Lens as J -import Language.Haskell.LSP.Utility +import qualified Data.Text.Lazy as TL +import qualified Data.Text.Lazy.Encoding as TL +import qualified Data.UUID as UUID +import qualified Language.Haskell.LSP.Types.Capabilities as J +import Language.Haskell.LSP.Types as J +import qualified Language.Haskell.LSP.Types.Lens as J import Language.Haskell.LSP.VFS import Language.Haskell.LSP.Diagnostics import System.Directory @@ -65,6 +131,8 @@ import qualified System.Log.Handler as LH import qualified System.Log.Handler.Simple as LHS import System.Log.Logger import qualified System.Log.Logger as L +import System.Random +import Control.Monad.Trans.Identity -- --------------------------------------------------------------------- {-# ANN module ("HLint: ignore Eta reduce" :: String) #-} @@ -72,28 +140,107 @@ import qualified System.Log.Logger as L {-# ANN module ("HLint: ignore Reduce duplication" :: String) #-} -- --------------------------------------------------------------------- --- | A function to send a message to the client -type SendFunc = FromServerMessage -> IO () +newtype LspT config m a = LspT { unLspT :: ReaderT (LanguageContextEnv config) m a } + deriving (Functor, Applicative, Monad, MonadIO, MonadTrans, MonadUnliftIO, MonadFix) + +runLspT :: LanguageContextEnv config -> LspT config m a -> m a +runLspT env = flip runReaderT env . unLspT + +type LspM config = LspT config IO + +class MonadUnliftIO m => MonadLsp config m | m -> config where + getLspEnv :: m (LanguageContextEnv config) + +instance MonadUnliftIO m => MonadLsp config (LspT config m) where + getLspEnv = LspT ask + +instance MonadLsp c m => MonadLsp c (ReaderT r m) where + getLspEnv = lift getLspEnv +instance MonadLsp c m => MonadLsp c (IdentityT m) where + getLspEnv = lift getLspEnv + +data LanguageContextEnv config = + LanguageContextEnv + { resHandlers :: !(Handlers IO) + , resParseConfig :: !(J.Value -> IO (Either T.Text config)) + , resSendMessage :: !(FromServerMessage -> IO ()) + , resState :: !(TVar (LanguageContextState config)) + , resClientCapabilities :: !J.ClientCapabilities + , resRootPath :: !(Maybe FilePath) + } + +-- --------------------------------------------------------------------- +-- Handlers +-- --------------------------------------------------------------------- + +-- | A mapping from methods to the static 'Handler's that should be used to +-- handle responses when they come in from the client. +data Handlers m + = Handlers + { reqHandlers :: DMap SMethod (ClientMessageHandler m Request) + , notHandlers :: DMap SMethod (ClientMessageHandler m Notification) + } +instance Semigroup (Handlers config) where + Handlers r1 n1 <> Handlers r2 n2 = Handlers (r1 <> r2) (n1 <> n2) +instance Monoid (Handlers config) where + mempty = Handlers mempty mempty + +notificationHandler :: forall (m :: Method FromClient Notification) f. SMethod m -> Handler f m -> Handlers f +notificationHandler m h = Handlers mempty (DMap.singleton m (ClientMessageHandler h)) + +requestHandler :: forall (m :: Method FromClient Request) f. SMethod m -> Handler f m -> Handlers f +requestHandler m h = Handlers (DMap.singleton m (ClientMessageHandler h)) mempty + +-- | The type of a handler that handles requests and notifications coming in +-- from the server or client +type family Handler (f :: Type -> Type) (m :: Method from t) = (result :: Type) | result -> f t m where + Handler f (m :: Method from Request) = RequestMessage m -> (Either ResponseError (ResponseParams m) -> f ()) -> f () + Handler f (m :: Method from Notification) = NotificationMessage m -> f () + +data m <~> n + = Iso + { forward :: forall a. m a -> n a + , backward :: forall a. n a -> m a + } + +transmuteHandlers :: (m <~> n) -> Handlers m -> Handlers n +transmuteHandlers nat = mapHandlers (\i m k -> forward nat (i m (backward nat . k))) (\i m -> forward nat (i m)) + +mapHandlers + :: (forall (a :: Method FromClient Request). Handler m a -> Handler n a) + -> (forall (a :: Method FromClient Notification). Handler m a -> Handler n a) + -> Handlers m -> Handlers n +mapHandlers mapReq mapNot (Handlers reqs nots) = Handlers reqs' nots' + where + reqs' = DMap.map (\(ClientMessageHandler i) -> ClientMessageHandler $ mapReq i) reqs + nots' = DMap.map (\(ClientMessageHandler i) -> ClientMessageHandler $ mapNot i) nots -- | state used by the LSP dispatcher to manage the message loop -data LanguageContextData config = - LanguageContextData { - resSeqDebugContextData :: !Int - , resHandlers :: !Handlers - , resOptions :: !Options - , resSendResponse :: !SendFunc - , resVFS :: !VFSData +data LanguageContextState config = + LanguageContextState + { resVFS :: !VFSData , resDiagnostics :: !DiagnosticStore , resConfig :: !(Maybe config) - , resLspId :: !(TVar Int) - , resLspFuncs :: LspFuncs config -- NOTE: Cannot be strict, lazy initialization - , resCaptureContext :: !CaptureContext - , resWorkspaceFolders :: ![J.WorkspaceFolder] + , resWorkspaceFolders :: ![WorkspaceFolder] , resProgressData :: !ProgressData + , resPendingResponses :: !ResponseMap + , resRegistrationsNot :: !(RegistrationMap Notification) + , resRegistrationsReq :: !(RegistrationMap Request) + , resLspId :: !Int } +type ResponseMap = IxMap LspId (Product SMethod ServerResponseCallback) + +type RegistrationMap (t :: MethodType) = DMap SMethod (Product RegistrationId (ClientMessageHandler IO t)) + +data RegistrationToken (m :: Method FromClient t) = RegistrationToken (SMethod m) (RegistrationId m) +newtype RegistrationId (m :: Method FromClient t) = RegistrationId Text + deriving Eq + +newtype ClientMessageHandler f (t :: MethodType) (m :: Method FromClient t) = ClientMessageHandler (Handler f m) + data ProgressData = ProgressData { progressNextId :: !Int - , progressCancel :: !(Map.Map J.ProgressToken (IO ())) } + , progressCancel :: !(Map.Map ProgressToken (IO ())) } data VFSData = VFSData @@ -101,6 +248,21 @@ data VFSData = , reverseMap :: !(Map.Map FilePath FilePath) } +modifyState :: MonadLsp config m => (LanguageContextState config -> LanguageContextState config) -> m () +modifyState f = do + tvarDat <- resState <$> getLspEnv + liftIO $ atomically $ modifyTVar' tvarDat f + +stateState :: MonadLsp config m => (LanguageContextState config -> (a,LanguageContextState config)) -> m a +stateState f = do + tvarDat <- resState <$> getLspEnv + liftIO $ atomically $ stateTVar tvarDat f + +getsState :: MonadLsp config m => (LanguageContextState config -> a) -> m a +getsState f = do + tvarDat <- resState <$> getLspEnv + liftIO $ f <$> readTVarIO tvarDat + -- --------------------------------------------------------------------- -- | Language Server Protocol options that the server may configure. @@ -123,7 +285,7 @@ data Options = -- | CodeActionKinds that this server may return. -- The list of kinds may be generic, such as `CodeActionKind.Refactor`, or the server -- may list out every specific kind they provide. - , codeActionKinds :: Maybe [J.CodeActionKind] + , codeActionKinds :: Maybe [CodeActionKind] -- | The list of characters that triggers on type formatting. -- If you set `documentOnTypeFormattingHandler`, you **must** set this. -- The first character is mandatory, so a 'NonEmpty' should be passed. @@ -131,28 +293,19 @@ data Options = -- | The commands to be executed on the server. -- If you set `executeCommandHandler`, you **must** set this. , executeCommandCommands :: Maybe [Text] + -- | Information about the server that can be advertised to the client. + , serverInfo :: Maybe J.ServerInfo } instance Default Options where def = Options Nothing Nothing Nothing Nothing Nothing - Nothing Nothing Nothing - --- | A function to publish diagnostics. It aggregates all diagnostics pertaining --- to a particular version of a document, by source, and sends a --- 'textDocument/publishDiagnostics' notification with the total (limited by the --- first parameter) whenever it is updated. -type PublishDiagnosticsFunc = Int -- Max number of diagnostics to send - -> J.NormalizedUri -> J.TextDocumentVersion -> DiagnosticsBySource -> IO () - --- | A function to remove all diagnostics from a particular source, and send the updates to the client. -type FlushDiagnosticsBySourceFunc = Int -- Max number of diagnostics to send - -> Maybe J.DiagnosticSource -> IO () + Nothing Nothing Nothing Nothing -- | A package indicating the perecentage of progress complete and a -- an optional message to go with it during a 'withProgress' -- -- @since 0.10.0.0 -data Progress = Progress (Maybe Double) (Maybe Text) +data ProgressAmount = ProgressAmount (Maybe Double) (Maybe Text) -- | Thrown if the user cancels a 'Cancellable' 'withProgress'/'withIndefiniteProgress'/ session -- @@ -167,773 +320,652 @@ instance E.Exception ProgressCancelledException -- @since 0.11.0.0 data ProgressCancellable = Cancellable | NotCancellable --- | Returned to the server on startup, providing ways to interact with the client. -data LspFuncs c = - LspFuncs - { clientCapabilities :: !C.ClientCapabilities - , config :: !(IO (Maybe c)) - -- ^ Derived from the DidChangeConfigurationNotification message via a - -- server-provided function. - , sendFunc :: !SendFunc - , getVirtualFileFunc :: !(J.NormalizedUri -> IO (Maybe VirtualFile)) - -- ^ Function to return the 'VirtualFile' associated with a - -- given 'NormalizedUri', if there is one. - , persistVirtualFileFunc :: !(J.NormalizedUri -> IO (Maybe FilePath)) - , reverseFileMapFunc :: !(IO (FilePath -> FilePath)) - , publishDiagnosticsFunc :: !PublishDiagnosticsFunc - , flushDiagnosticsBySourceFunc :: !FlushDiagnosticsBySourceFunc - , getNextReqId :: !(IO J.LspId) - , rootPath :: !(Maybe FilePath) - , getWorkspaceFolders :: !(IO (Maybe [J.WorkspaceFolder])) - , withProgress :: !(forall a . Text -> ProgressCancellable - -> ((Progress -> IO ()) -> IO a) -> IO a) - -- ^ Wrapper for reporting progress to the client during a long running - -- task. - -- 'withProgress' @title cancellable f@ starts a new progress reporting - -- session, and finishes it once f is completed. - -- f is provided with an update function that allows it to report on - -- the progress during the session. - -- If @cancellable@ is 'Cancellable', @f@ will be thrown a - -- 'ProgressCancelledException' if the user cancels the action in - -- progress. - -- - -- @since 0.10.0.0 - , withIndefiniteProgress :: !(forall a . Text -> ProgressCancellable - -> IO a -> IO a) - -- ^ Same as 'withProgress', but for processes that do not report the - -- precentage complete. - -- - -- @since 0.10.0.0 - } - -- | Contains all the callbacks to use for initialized the language server. -- it is parameterized over a config type variable representing the type for the -- specific configuration data the language server needs to use. -data InitializeCallbacks config = +data InitializeCallbacks config = forall m a. InitializeCallbacks - { onInitialConfiguration :: J.InitializeRequest -> Either T.Text config - -- ^ Invoked on the first message from the language client, containg the client configuration - -- This callback should return either the parsed configuration data or an error indicating - -- what went wrong. The parsed configuration object will be stored internally and passed to - -- hanlder functions as context. - , onConfigurationChange :: J.DidChangeConfigurationNotification-> Either T.Text config - -- ^ Invoked whenever the clients sends a message with a changed client configuration. - -- This callback should return either the parsed configuration data or an error indicating - -- what went wrong. The parsed configuration object will be stored internally and passed to - -- hanlder functions as context. - , onStartup :: LspFuncs config -> IO (Maybe J.ResponseError) - -- ^ Once the initial configuration has been received, this callback will be invoked to offer - -- the language server implementation the chance to create any processes or start new threads + { onConfigurationChange :: J.Value -> m (Either T.Text config) + -- ^ @onConfigurationChange newConfig@ is called whenever the + -- clients sends a message with a changed client configuration. This + -- 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) + -- ^ 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 start new threads -- that may be necesary for the server lifecycle. + -- It can also return an error in the initialization if necessary. + , staticHandlers :: Handlers m + -- ^ The actual handlers + , interpretHandler :: a -> (m <~> IO) + -- ^ How to run the handlers + -- Passed the result of 'doInitialize' as well as the LanguageContextEnv } --- | The Handler type captures a function that receives local read-only state --- 'a', a function to send a reply message once encoded as a ByteString, and a --- received message of type 'b' -type Handler b = b -> IO () - --- | Callbacks from the language server to the language handler -data Handlers = - Handlers - { - -- Capability-advertised handlers - hoverHandler :: !(Maybe (Handler J.HoverRequest)) - , completionHandler :: !(Maybe (Handler J.CompletionRequest)) - , completionResolveHandler :: !(Maybe (Handler J.CompletionItemResolveRequest)) - , signatureHelpHandler :: !(Maybe (Handler J.SignatureHelpRequest)) - , definitionHandler :: !(Maybe (Handler J.DefinitionRequest)) - , typeDefinitionHandler :: !(Maybe (Handler J.TypeDefinitionRequest)) - , implementationHandler :: !(Maybe (Handler J.ImplementationRequest)) - , referencesHandler :: !(Maybe (Handler J.ReferencesRequest)) - , documentHighlightHandler :: !(Maybe (Handler J.DocumentHighlightRequest)) - , documentSymbolHandler :: !(Maybe (Handler J.DocumentSymbolRequest)) - , workspaceSymbolHandler :: !(Maybe (Handler J.WorkspaceSymbolRequest)) - , codeActionHandler :: !(Maybe (Handler J.CodeActionRequest)) - , codeLensHandler :: !(Maybe (Handler J.CodeLensRequest)) - , codeLensResolveHandler :: !(Maybe (Handler J.CodeLensResolveRequest)) - , documentColorHandler :: !(Maybe (Handler J.DocumentColorRequest)) - , colorPresentationHandler :: !(Maybe (Handler J.ColorPresentationRequest)) - , documentFormattingHandler :: !(Maybe (Handler J.DocumentFormattingRequest)) - , documentRangeFormattingHandler :: !(Maybe (Handler J.DocumentRangeFormattingRequest)) - , documentOnTypeFormattingHandler :: !(Maybe (Handler J.DocumentOnTypeFormattingRequest)) - , renameHandler :: !(Maybe (Handler J.RenameRequest)) - , prepareRenameHandler :: !(Maybe (Handler J.PrepareRenameRequest)) - , foldingRangeHandler :: !(Maybe (Handler J.FoldingRangeRequest)) - -- new in 3.0 - , documentLinkHandler :: !(Maybe (Handler J.DocumentLinkRequest)) - , documentLinkResolveHandler :: !(Maybe (Handler J.DocumentLinkResolveRequest)) - , executeCommandHandler :: !(Maybe (Handler J.ExecuteCommandRequest)) - -- Next 2 go from server -> client - -- , registerCapabilityHandler :: !(Maybe (Handler J.RegisterCapabilityRequest)) - -- , unregisterCapabilityHandler :: !(Maybe (Handler J.UnregisterCapabilityRequest)) - , willSaveWaitUntilTextDocHandler:: !(Maybe (Handler J.WillSaveWaitUntilTextDocumentRequest)) - - -- Notifications from the client - , didChangeConfigurationParamsHandler :: !(Maybe (Handler J.DidChangeConfigurationNotification)) - , didOpenTextDocumentNotificationHandler :: !(Maybe (Handler J.DidOpenTextDocumentNotification)) - , didChangeTextDocumentNotificationHandler :: !(Maybe (Handler J.DidChangeTextDocumentNotification)) - -- ^ Note: If you need to keep track of document changes, - -- "Language.Haskell.LSP.VFS" will take care of these messages for you! - , didCloseTextDocumentNotificationHandler :: !(Maybe (Handler J.DidCloseTextDocumentNotification)) - , didSaveTextDocumentNotificationHandler :: !(Maybe (Handler J.DidSaveTextDocumentNotification)) - , didChangeWatchedFilesNotificationHandler :: !(Maybe (Handler J.DidChangeWatchedFilesNotification)) - , didChangeWorkspaceFoldersNotificationHandler :: !(Maybe (Handler J.DidChangeWorkspaceFoldersNotification)) - -- new in 3.0 - , initializedHandler :: !(Maybe (Handler J.InitializedNotification)) - , willSaveTextDocumentNotificationHandler :: !(Maybe (Handler J.WillSaveTextDocumentNotification)) - , cancelNotificationHandler :: !(Maybe (Handler J.CancelNotification)) - - -- Responses to Request messages originated from the server - -- TODO: Properly decode response types and replace them with actual handlers - , responseHandler :: !(Maybe (Handler J.BareResponseMessage)) - -- , registerCapabilityHandler :: !(Maybe (Handler J.RegisterCapabilityResponse)) - -- , unregisterCapabilityHandler :: !(Maybe (Handler J.RegisterCapabilityResponse)) - -- , showMessageHandler :: !(Maybe (Handler J.ShowMessageResponse)) - - -- Initialization request on startup - , initializeRequestHandler :: !(Maybe (Handler J.InitializeRequest)) - -- Will default to terminating `exitMessage` if Nothing - , exitNotificationHandler :: !(Maybe (Handler J.ExitNotification)) - - , customRequestHandler :: !(Maybe (Handler J.CustomClientRequest)) - , customNotificationHandler :: !(Maybe (Handler J.CustomClientNotification)) - - } - -instance Default Handlers where - -- These already implicitly do stuff to the VFS, so silence warnings about no handler - def = nothings { didChangeTextDocumentNotificationHandler = Just ignore - , didOpenTextDocumentNotificationHandler = Just ignore - , didCloseTextDocumentNotificationHandler = Just ignore - } - where ignore = const (pure ()) - nothings = Handlers Nothing Nothing Nothing Nothing Nothing Nothing - Nothing Nothing Nothing Nothing Nothing Nothing - Nothing Nothing Nothing Nothing Nothing Nothing - Nothing Nothing Nothing Nothing Nothing Nothing - Nothing Nothing Nothing Nothing Nothing Nothing - Nothing Nothing Nothing Nothing Nothing Nothing - Nothing Nothing Nothing Nothing Nothing - --- --------------------------------------------------------------------- -nop :: Maybe (a -> b -> (a,[String])) -nop = Nothing - - -helper :: J.FromJSON a => (TVar (LanguageContextData config) -> a -> IO ()) -> (TVar (LanguageContextData config) -> J.Value -> IO ()) -helper requestHandler tvarDat json = - case J.fromJSON json of - J.Success req -> requestHandler tvarDat req - J.Error err -> do - let msg = T.pack . unwords $ ["haskell-lsp:parse error.", show json, show err] ++ _ERR_MSG_URL - failLog = sendErrorLog tvarDat msg - case json of - (J.Object o) -> case HM.lookup "id" o of - Just olid -> case J.fromJSON olid of - J.Success lid -> sendErrorResponse tvarDat lid msg - _ -> failLog - _ -> failLog - _ -> failLog - -handlerMap :: (Show config) - => InitializeCallbacks config -> Handlers -> J.ClientMethod - -> (TVar (LanguageContextData config) -> J.Value -> IO ()) --- General -handlerMap i h J.Initialize = handleInitialConfig i (initializeRequestHandler h) -handlerMap _ h J.Initialized = hh nop NotInitialized $ initializedHandler h -handlerMap _ _ J.Shutdown = helper shutdownRequestHandler -handlerMap _ h J.Exit = - case exitNotificationHandler h of - Just _ -> hh nop NotExit $ exitNotificationHandler h - Nothing -> \ctxVar v -> do - ctx <- readTVarIO ctxVar - -- Capture exit notification - case J.fromJSON v :: J.Result J.ExitNotification of - J.Success n -> captureFromClient (NotExit n) (resCaptureContext ctx) - J.Error _ -> return () - logm $ B.pack "haskell-lsp:Got exit, exiting" - exitSuccess -handlerMap _ h J.CancelRequest = hh nop NotCancelRequestFromClient $ cancelNotificationHandler h --- Workspace -handlerMap _ h J.WorkspaceDidChangeWorkspaceFolders = hwf $ didChangeWorkspaceFoldersNotificationHandler h -handlerMap i h J.WorkspaceDidChangeConfiguration = hc i $ didChangeConfigurationParamsHandler h -handlerMap _ h J.WorkspaceDidChangeWatchedFiles = hh nop NotDidChangeWatchedFiles $ didChangeWatchedFilesNotificationHandler h -handlerMap _ h J.WorkspaceSymbol = hh nop ReqWorkspaceSymbols $ workspaceSymbolHandler h -handlerMap _ h J.WorkspaceExecuteCommand = hh nop ReqExecuteCommand $ executeCommandHandler h --- Document -handlerMap _ h J.TextDocumentDidOpen = hh (Just openVFS) NotDidOpenTextDocument $ didOpenTextDocumentNotificationHandler h -handlerMap _ h J.TextDocumentDidChange = hh (Just changeFromClientVFS) NotDidChangeTextDocument $ didChangeTextDocumentNotificationHandler h -handlerMap _ h J.TextDocumentWillSave = hh nop NotWillSaveTextDocument $ willSaveTextDocumentNotificationHandler h -handlerMap _ h J.TextDocumentWillSaveWaitUntil = hh nop ReqWillSaveWaitUntil $ willSaveWaitUntilTextDocHandler h -handlerMap _ h J.TextDocumentDidSave = hh nop NotDidSaveTextDocument $ didSaveTextDocumentNotificationHandler h -handlerMap _ h J.TextDocumentDidClose = hh (Just closeVFS) NotDidCloseTextDocument $ didCloseTextDocumentNotificationHandler h -handlerMap _ h J.TextDocumentCompletion = hh nop ReqCompletion $ completionHandler h -handlerMap _ h J.CompletionItemResolve = hh nop ReqCompletionItemResolve $ completionResolveHandler h -handlerMap _ h J.TextDocumentHover = hh nop ReqHover $ hoverHandler h -handlerMap _ h J.TextDocumentSignatureHelp = hh nop ReqSignatureHelp $ signatureHelpHandler h -handlerMap _ h J.TextDocumentDefinition = hh nop ReqDefinition $ definitionHandler h -handlerMap _ h J.TextDocumentTypeDefinition = hh nop ReqTypeDefinition $ typeDefinitionHandler h -handlerMap _ h J.TextDocumentImplementation = hh nop ReqImplementation $ implementationHandler h -handlerMap _ h J.TextDocumentReferences = hh nop ReqFindReferences $ referencesHandler h -handlerMap _ h J.TextDocumentDocumentHighlight = hh nop ReqDocumentHighlights $ documentHighlightHandler h -handlerMap _ h J.TextDocumentDocumentSymbol = hh nop ReqDocumentSymbols $ documentSymbolHandler h -handlerMap _ h J.TextDocumentFormatting = hh nop ReqDocumentFormatting $ documentFormattingHandler h -handlerMap _ h J.TextDocumentRangeFormatting = hh nop ReqDocumentRangeFormatting $ documentRangeFormattingHandler h -handlerMap _ h J.TextDocumentOnTypeFormatting = hh nop ReqDocumentOnTypeFormatting $ documentOnTypeFormattingHandler h -handlerMap _ h J.TextDocumentCodeAction = hh nop ReqCodeAction $ codeActionHandler h -handlerMap _ h J.TextDocumentCodeLens = hh nop ReqCodeLens $ codeLensHandler h -handlerMap _ h J.CodeLensResolve = hh nop ReqCodeLensResolve $ codeLensResolveHandler h -handlerMap _ h J.TextDocumentDocumentColor = hh nop ReqDocumentColor $ documentColorHandler h -handlerMap _ h J.TextDocumentColorPresentation = hh nop ReqColorPresentation $ colorPresentationHandler h -handlerMap _ h J.TextDocumentDocumentLink = hh nop ReqDocumentLink $ documentLinkHandler h -handlerMap _ h J.DocumentLinkResolve = hh nop ReqDocumentLinkResolve $ documentLinkResolveHandler h -handlerMap _ h J.TextDocumentRename = hh nop ReqRename $ renameHandler h -handlerMap _ h J.TextDocumentPrepareRename = hh nop ReqPrepareRename $ prepareRenameHandler h -handlerMap _ h J.TextDocumentFoldingRange = hh nop ReqFoldingRange $ foldingRangeHandler h -handlerMap _ _ J.WorkDoneProgressCancel = helper progressCancelHandler -handlerMap _ h (J.CustomClientMethod _) = \ctxData val -> - case val of - J.Object o | "id" `HM.member` o -> - -- Custom request - hh nop ReqCustomClient (customRequestHandler h) ctxData val - _ -> -- Custom notification - hh nop NotCustomClient (customNotificationHandler h) ctxData val +-- | A function that a 'Handler' is passed that can be used to respond to a +-- request with either an error, or the response params. +newtype ServerResponseCallback (m :: Method FromServer Request) + = ServerResponseCallback (Either ResponseError (ResponseParams m) -> IO ()) + +-- | Return value signals if response handler was inserted succesfully +-- Might fail if the id was already in the map +addResponseHandler :: MonadLsp config f => LspId m -> (Product SMethod ServerResponseCallback) m -> f Bool +addResponseHandler lid h = do + stateState $ \ctx@LanguageContextState{resPendingResponses} -> + case insertIxMap lid h resPendingResponses of + Just m -> (True, ctx { resPendingResponses = m}) + Nothing -> (False, ctx) + +sendNotification + :: forall (m :: Method FromServer Notification) f config. MonadLsp config f + => SServerMethod m + -> MessageParams m + -> f () +sendNotification m params = + let msg = NotificationMessage "2.0" m params + in case splitServerMethod m of + IsServerNot -> sendToClient $ fromServerNot msg + IsServerEither -> sendToClient $ FromServerMess m $ NotMess msg + +sendRequest :: forall (m :: Method FromServer Request) f config. MonadLsp config f + => SServerMethod m + -> MessageParams m + -> (Either ResponseError (ResponseParams m) -> f ()) + -> f (LspId m) +sendRequest m params resHandler = do + reqId <- IdInt <$> freshLspId + rio <- askRunInIO + success <- addResponseHandler reqId (Pair m (ServerResponseCallback (rio . resHandler))) + unless success $ error "haskell-lsp: could not send FromServer request as id is reused" + + let msg = RequestMessage "2.0" reqId m params + ~() <- case splitServerMethod m of + IsServerReq -> sendToClient $ fromServerReq msg + IsServerEither -> sendToClient $ FromServerMess m $ ReqMess msg + return reqId -- --------------------------------------------------------------------- --- | Adapter from the normal handlers exposed to the library users and the --- internal message loop -hh :: forall b config. (J.FromJSON b) - => Maybe (VFS -> b -> (VFS, [String])) -> (b -> FromClientMessage) -> Maybe (Handler b) - -> TVar (LanguageContextData config) -> J.Value -> IO () -hh mVfs wrapper mh tvarDat json = do - case J.fromJSON json of - J.Success req -> do - case mVfs of - Just modifyVfs -> do - join $ atomically $ modifyVFSData tvarDat $ \(VFSData vfs rm) -> - let (vfs', ls) = modifyVfs vfs req - in (VFSData vfs' rm, mapM_ logs ls) - Nothing -> return () - - ctx <- readTVarIO tvarDat - let req' = wrapper req - captureFromClient req' (resCaptureContext ctx) - - case mh of - Just h -> h req - Nothing - -- '$/' notifications should/could be ignored by server. - -- Don't log errors in that case. - -- See https://microsoft.github.io/language-server-protocol/specifications/specification-current/#-notifications-and-requests. - | isOptionalNotification req' -> return () - | otherwise -> do - let msg = T.pack $ unwords ["haskell-lsp:no handler for.", show json] - sendErrorLog tvarDat msg - J.Error err -> do - let msg = T.pack $ unwords $ ["haskell-lsp:parse error.", show json, show err] ++ _ERR_MSG_URL - sendErrorLog tvarDat msg +-- | Invokes the registered dynamic or static handlers for the given message and +-- method, as well as doing some bookkeeping. +handle :: SClientMethod m -> ClientMessage m -> LspM config () +handle m msg = + case m of + SWorkspaceDidChangeWorkspaceFolders -> handle' (Just updateWorkspaceFolders) m msg + SWorkspaceDidChangeConfiguration -> handle' (Just handleConfigChange) m msg + STextDocumentDidOpen -> handle' (Just $ vfsFunc openVFS) m msg + STextDocumentDidChange -> handle' (Just $ vfsFunc changeFromClientVFS) m msg + STextDocumentDidClose -> handle' (Just $ vfsFunc closeVFS) m msg + SWindowWorkDoneProgressCancel -> handle' (Just progressCancelHandler) m msg + _ -> handle' Nothing m msg + + +handle' :: forall t (m :: Method FromClient t) (config :: Type). + Maybe (ClientMessage m -> LspM config ()) + -- ^ An action to be run before invoking the handler, used for + -- bookkeeping stuff like the vfs etc. + -> SClientMethod m + -> ClientMessage m + -> LspM config () +handle' mAction m msg = do + maybe (return ()) (\f -> f msg) mAction + + dynReqHandlers <- getsState resRegistrationsReq + dynNotHandlers <- getsState resRegistrationsNot + + env <- getLspEnv + let Handlers{reqHandlers, notHandlers} = resHandlers env + + let mkRspCb :: RequestMessage (m1 :: Method FromClient Request) -> Either ResponseError (ResponseParams m1) -> IO () + mkRspCb req (Left err) = runLspT env $ sendToClient $ + FromServerRsp (req ^. J.method) $ ResponseMessage "2.0" (Just (req ^. J.id)) (Left err) + mkRspCb req (Right rsp) = runLspT env $ sendToClient $ + FromServerRsp (req ^. J.method) $ ResponseMessage "2.0" (Just (req ^. J.id)) (Right rsp) + + case splitClientMethod m of + IsClientNot -> case pickHandler dynNotHandlers notHandlers of + Just h -> liftIO $ h msg + Nothing + | SExit <- m -> liftIO $ exitNotificationHandler msg + | otherwise -> reportMissingHandler + + IsClientReq -> case pickHandler dynReqHandlers reqHandlers of + Just h -> liftIO $ h msg (mkRspCb msg) + Nothing + | SShutdown <- m -> liftIO $ shutdownRequestHandler msg (mkRspCb msg) + | otherwise -> reportMissingHandler + + IsClientEither -> case msg of + NotMess noti -> case pickHandler dynNotHandlers notHandlers of + Just h -> liftIO $ h noti + Nothing -> reportMissingHandler + ReqMess req -> case pickHandler dynReqHandlers reqHandlers of + Just h -> liftIO $ h req (mkRspCb req) + Nothing -> reportMissingHandler where - isOptionalNotification req - | NotCustomClient _ <- req - , J.Object object <- json - , Just (J.String method) <- HM.lookup "method" object - , "$/" `T.isPrefixOf` method - = True - | otherwise = False - -handleInitialConfig - :: (Show config) - => InitializeCallbacks config - -> Maybe (Handler J.InitializeRequest) - -> TVar (LanguageContextData config) - -> J.Value - -> IO () -handleInitialConfig (InitializeCallbacks { onInitialConfiguration, onStartup }) mh tvarDat json - = handleMessageWithConfigChange ReqInitialize - onInitialConfiguration - (Just $ initializeRequestHandler' onStartup mh tvarDat) - tvarDat - json - - -hc - :: (Show config) - => InitializeCallbacks config - -> Maybe (Handler J.DidChangeConfigurationNotification) - -> TVar (LanguageContextData config) - -> J.Value - -> IO () -hc (InitializeCallbacks { onConfigurationChange }) mh tvarDat json = - handleMessageWithConfigChange NotDidChangeConfiguration - onConfigurationChange - mh - tvarDat - json - -handleMessageWithConfigChange - :: (J.FromJSON reqParams, Show reqParams, Show err) - => (reqParams -> FromClientMessage) -- ^ The notification message from the client to expect - -> (reqParams -> Either err config) -- ^ A function to parse the config out of the request - -> Maybe (reqParams -> IO ()) -- ^ The upstream handler for the client request - -> TVar (LanguageContextData config) -- ^ The context data containing the current configuration - -> J.Value -- ^ The raw reqeust data - -> IO () -handleMessageWithConfigChange notification parseConfig mh tvarDat json = - -- logs $ "haskell-lsp:hc DidChangeConfigurationNotification entered" - case J.fromJSON json of - J.Success req -> do - ctx <- readTVarIO tvarDat - - captureFromClient (notification req) (resCaptureContext ctx) - - case parseConfig req of - Left err -> do - let - msg = - T.pack $ unwords - ["haskell-lsp:configuration parse error.", show req, show err] - sendErrorLog tvarDat msg - Right newConfig -> - atomically $ modifyTVar' tvarDat (\ctx' -> ctx' { resConfig = Just newConfig }) - case mh of - Just h -> h req - Nothing -> return () - J.Error err -> do - let msg = - T.pack - $ unwords - $ ["haskell-lsp:parse error.", show json, show err] - ++ _ERR_MSG_URL - sendErrorLog tvarDat msg - --- | Updates the list of workspace folders and then delegates back to 'hh' -hwf :: Maybe (Handler J.DidChangeWorkspaceFoldersNotification) -> TVar (LanguageContextData config) -> J.Value -> IO () -hwf h tvarDat json = do - case J.fromJSON json :: J.Result J.DidChangeWorkspaceFoldersNotification of - J.Success (J.NotificationMessage _ _ params) -> atomically $ do - - oldWfs <- resWorkspaceFolders <$> readTVar tvarDat - let J.List toRemove = params ^. J.event . J.removed - wfs0 = foldr L.delete oldWfs toRemove - J.List toAdd = params ^. J.event . J.added - wfs1 = wfs0 <> toAdd - - modifyTVar' tvarDat (\c -> c {resWorkspaceFolders = wfs1}) - _ -> return () - hh nop NotDidChangeWorkspaceFolders h tvarDat json - --- --------------------------------------------------------------------- - -modifyVFSData :: TVar (LanguageContextData config) -> (VFSData -> (VFSData, a)) -> STM a -modifyVFSData tvarDat f = do - (vfs', a) <- f . resVFS <$> readTVar tvarDat - modifyTVar tvarDat $ \vd -> vd { resVFS = vfs' } - return a + -- | Checks to see if there's a dynamic handler, and uses it in favour of the + -- static handler, if it exists. + pickHandler :: RegistrationMap t -> DMap SMethod (ClientMessageHandler IO t) -> Maybe (Handler IO m) + pickHandler dynHandlerMap staticHandler = case (DMap.lookup m dynHandlerMap, DMap.lookup m staticHandler) of + (Just (Pair _ (ClientMessageHandler h)), _) -> Just h + (Nothing, Just (ClientMessageHandler h)) -> Just h + (Nothing, Nothing) -> Nothing + + -- '$/' notifications should/could be ignored by server. + -- Don't log errors in that case. + -- See https://microsoft.github.io/language-server-protocol/specifications/specification-current/#-notifications-and-requests. + reportMissingHandler :: LspM config () + reportMissingHandler + | isOptionalNotification m = return () + | otherwise = do + let errorMsg = T.pack $ unwords ["haskell-lsp:no handler for: ", show m] + sendErrorLog errorMsg + isOptionalNotification (SCustomMethod method) + | "$/" `T.isPrefixOf` method = True + isOptionalNotification _ = False + + +handleConfigChange :: DidChangeConfigurationNotification -> LspM config () +handleConfigChange req = do + parseConfig <- LspT $ asks resParseConfig + res <- liftIO $ parseConfig (req ^. J.params . J.settings) + case res of + Left err -> do + let msg = T.pack $ unwords + ["haskell-lsp:configuration parse error.", show req, show err] + sendErrorLog msg + Right newConfig -> + modifyState $ \ctx -> ctx { resConfig = Just newConfig } + +vfsFunc :: (VFS -> b -> (VFS, [String])) -> b -> LspM config () +vfsFunc modifyVfs req = do + join $ stateState $ \ctx@LanguageContextState{resVFS = VFSData vfs rm} -> + let (vfs', ls) = modifyVfs vfs req + in (liftIO $ mapM_ (debugM "haskell-lsp.vfsFunc") ls,ctx{ resVFS = VFSData vfs' rm}) + +-- | Updates the list of workspace folders +updateWorkspaceFolders :: Message WorkspaceDidChangeWorkspaceFolders -> LspM config () +updateWorkspaceFolders (NotificationMessage _ _ params) = do + let List toRemove = params ^. J.event . J.removed + List toAdd = params ^. J.event . J.added + newWfs oldWfs = foldr L.delete oldWfs toRemove <> toAdd + modifyState $ \c -> c {resWorkspaceFolders = newWfs $ resWorkspaceFolders c} -- --------------------------------------------------------------------- -- | Return the 'VirtualFile' associated with a given 'NormalizedUri', if there is one. -getVirtualFile :: TVar (LanguageContextData config) -> J.NormalizedUri -> IO (Maybe VirtualFile) -getVirtualFile tvarDat uri = Map.lookup uri . vfsMap . vfsData . resVFS <$> readTVarIO tvarDat +getVirtualFile :: MonadLsp config m => NormalizedUri -> m (Maybe VirtualFile) +getVirtualFile uri = getsState $ Map.lookup uri . vfsMap . vfsData . resVFS + +getVirtualFiles :: MonadLsp config m => m VFS +getVirtualFiles = getsState $ vfsData . resVFS -- | Dump the current text for a given VFS file to a temporary file, -- and return the path to the file. -persistVirtualFile :: TVar (LanguageContextData config) -> J.NormalizedUri -> IO (Maybe FilePath) -persistVirtualFile tvarDat uri = join $ atomically $ do - st <- readTVar tvarDat - let vfs_data = resVFS st - cur_vfs = vfsData vfs_data - revMap = reverseMap vfs_data - - case persistFileVFS cur_vfs uri of - Nothing -> return (return Nothing) - Just (fn, write) -> do - let revMap' = - -- TODO: Does the VFS make sense for URIs which are not files? - -- The reverse map should perhaps be (FilePath -> URI) - case J.uriToFilePath (J.fromNormalizedUri uri) of - Just uri_fp -> Map.insert fn uri_fp revMap - Nothing -> revMap - - modifyVFSData tvarDat (\d -> (d { reverseMap = revMap' }, ())) - return ((Just fn) <$ write) +persistVirtualFile :: MonadLsp config m => NormalizedUri -> m (Maybe FilePath) +persistVirtualFile uri = do + join $ stateState $ \ctx@LanguageContextState{resVFS = vfs} -> + case persistFileVFS (vfsData vfs) uri of + Nothing -> (return Nothing, ctx) + Just (fn, write) -> + let revMap = case uriToFilePath (fromNormalizedUri uri) of + Just uri_fp -> Map.insert fn uri_fp $ reverseMap vfs + -- TODO: Does the VFS make sense for URIs which are not files? + -- The reverse map should perhaps be (FilePath -> URI) + Nothing -> reverseMap vfs + act = do + liftIO write + pure (Just fn) + in (act, ctx{resVFS = vfs {reverseMap = revMap} }) + +-- | Given a text document identifier, annotate it with the latest version. +getVersionedTextDoc :: MonadLsp config m => TextDocumentIdentifier -> m VersionedTextDocumentIdentifier +getVersionedTextDoc doc = do + let uri = doc ^. J.uri + mvf <- getVirtualFile (toNormalizedUri uri) + let ver = case mvf of + Just (VirtualFile lspver _ _) -> Just lspver + Nothing -> Nothing + return (VersionedTextDocumentIdentifier uri ver) -- TODO: should this function return a URI? -- | If the contents of a VFS has been dumped to a temporary file, map -- the temporary file name back to the original one. -reverseFileMap :: TVar (LanguageContextData config) - -> IO (FilePath -> FilePath) -reverseFileMap tvarDat = do - vfs <- resVFS <$> readTVarIO tvarDat - let f fp = fromMaybe fp . Map.lookup fp . reverseMap $ vfs - return f +reverseFileMap :: MonadLsp config m => m (FilePath -> FilePath) +reverseFileMap = do + vfs <- getsState resVFS + let f fp = fromMaybe fp . Map.lookup fp . reverseMap $ vfs + return f -- --------------------------------------------------------------------- -getConfig :: TVar (LanguageContextData config) -> IO (Maybe config) -getConfig tvar = resConfig <$> readTVarIO tvar - --- --------------------------------------------------------------------- --- | --- --- -_INITIAL_RESPONSE_SEQUENCE :: Int -_INITIAL_RESPONSE_SEQUENCE = 0 - - --- | --- --- -_SEP_WIN :: Char -_SEP_WIN = '\\' - --- | --- --- -_SEP_UNIX :: Char -_SEP_UNIX = '/' - --- | --- --- -_ERR_MSG_URL :: [String] -_ERR_MSG_URL = [ "`stack update` and install new haskell-lsp." - , "Or check information on https://marketplace.visualstudio.com/items?itemName=xxxxxxxxxxxxxxx" - ] - - --- | --- --- -defaultLanguageContextData :: Handlers -> Options -> LspFuncs config -> TVar Int -> SendFunc -> CaptureContext -> VFS -> LanguageContextData config -defaultLanguageContextData h o lf tv sf cc vfs = - LanguageContextData _INITIAL_RESPONSE_SEQUENCE h o sf (VFSData vfs mempty) mempty - Nothing tv lf cc mempty defaultProgressData - defaultProgressData :: ProgressData defaultProgressData = ProgressData 0 Map.empty -- --------------------------------------------------------------------- -handleMessage :: (Show config) => InitializeCallbacks config - -> TVar (LanguageContextData config) -> BSL.ByteString -> IO () -handleMessage dispatcherProc tvarDat jsonStr = do - {- - Message Types we must handle are the following - - Request | jsonrpc | id | method | params? - Response | jsonrpc | id | | | response? | error? - Notification | jsonrpc | | method | params? - - -} - - case J.eitherDecode jsonStr :: Either String J.Object of - Left err -> do - let msg = T.pack $ unwords [ "haskell-lsp:incoming message parse error.", lbs2str jsonStr, show err] - ++ L.intercalate "\n" ("" : "" : _ERR_MSG_URL) - ++ "\n" - sendErrorLog tvarDat msg - - Right o -> do - - case HM.lookup "method" o of - Just cmd@(J.String s) -> case J.fromJSON cmd of - J.Success m -> handle (J.Object o) m - J.Error _ -> do - let msg = T.pack $ unwords ["haskell-lsp:unknown message received:method='" - ++ T.unpack s ++ "',", lbs2str jsonStr] - sendErrorLog tvarDat msg - Just oops -> logs $ "haskell-lsp:got strange method param, ignoring:" ++ show oops - Nothing -> do - logs $ "haskell-lsp:Got reply message:" ++ show jsonStr - handleResponse (J.Object o) - +processMessage :: BSL.ByteString -> LspM config () +processMessage jsonStr = do + tvarDat <- LspT $ asks resState + join $ liftIO $ atomically $ fmap handleErrors $ runExceptT $ do + val <- except $ J.eitherDecode jsonStr + ctx <- lift $ readTVar tvarDat + msg <- except $ J.parseEither (parser $ resPendingResponses ctx) val + lift $ case msg of + FromClientMess m mess -> + pure $ handle m mess + FromClientRsp (Pair (ServerResponseCallback f) (Const newMap)) res -> do + modifyTVar' tvarDat (\c -> c { resPendingResponses = newMap }) + pure $ liftIO $ f (res ^. J.result) where - handleResponse json = do - ctx <- readTVarIO tvarDat - case responseHandler $ resHandlers ctx of - Nothing -> sendErrorLog tvarDat $ T.pack $ "haskell-lsp: responseHandler is not defined, ignoring response " ++ lbs2str jsonStr - Just h -> case J.fromJSON json of - J.Success res -> h res - J.Error err -> let msg = T.pack $ unwords $ ["haskell-lsp:response parse error.", lbs2str jsonStr, show err] ++ _ERR_MSG_URL - in sendErrorLog tvarDat msg - -- capability based handlers - handle json cmd = do - ctx <- readTVarIO tvarDat - let h = resHandlers ctx - handlerMap dispatcherProc h cmd tvarDat json + parser :: ResponseMap -> J.Value -> J.Parser (FromClientMessage' (Product ServerResponseCallback (Const ResponseMap))) + parser rm = parseClientMessage $ \i -> + let (mhandler, newMap) = pickFromIxMap i rm + in (\(Pair m handler) -> (m,Pair handler (Const newMap))) <$> mhandler --- --------------------------------------------------------------------- + handleErrors = either (sendErrorLog . errMsg) id -makeResponseMessage :: J.RequestMessage J.ClientMethod req resp -> resp -> J.ResponseMessage resp -makeResponseMessage req result = J.ResponseMessage "2.0" (J.responseId $ req ^. J.id) (Right result) + errMsg err = TL.toStrict $ TL.unwords + [ "haskell-lsp:incoming message parse error." + , TL.decodeUtf8 jsonStr + , TL.pack err + ] <> "\n" -makeResponseError :: J.LspIdRsp -> J.ResponseError -> J.ResponseMessage () -makeResponseError origId err = J.ResponseMessage "2.0" origId (Left err) -- --------------------------------------------------------------------- --- | --- -sendEvent :: TVar (LanguageContextData config) -> FromServerMessage -> IO () -sendEvent tvarCtx msg = sendResponse tvarCtx msg - --- | --- -sendResponse :: TVar (LanguageContextData config) -> FromServerMessage -> IO () -sendResponse tvarCtx msg = do - ctx <- readTVarIO tvarCtx - resSendResponse ctx msg +sendToClient :: MonadLsp config m => FromServerMessage -> m () +sendToClient msg = do + f <- resSendMessage <$> getLspEnv + liftIO $ f msg -- --------------------------------------------------------------------- --- | --- --- -sendErrorResponse :: TVar (LanguageContextData config) -> J.LspIdRsp -> Text -> IO () -sendErrorResponse tv origId msg = sendErrorResponseS (sendEvent tv) origId J.InternalError msg - -sendErrorResponseS :: SendFunc -> J.LspIdRsp -> J.ErrorCode -> Text -> IO () -sendErrorResponseS sf origId err msg = do - sf $ RspError (J.ResponseMessage "2.0" origId - (Left $ J.ResponseError err msg Nothing) :: J.ErrorResponse) - -sendErrorLog :: TVar (LanguageContextData config) -> Text -> IO () -sendErrorLog tv msg = sendErrorLogS (sendEvent tv) msg -sendErrorLogS :: SendFunc -> Text -> IO () -sendErrorLogS sf msg = - sf $ NotLogMessage $ fmServerLogMessageNotification J.MtError msg - --- sendErrorShow :: String -> IO () --- sendErrorShow msg = sendErrorShowS sendEvent msg - -sendErrorShowS :: SendFunc -> Text -> IO () -sendErrorShowS sf msg = - sf $ NotShowMessage $ fmServerShowMessageNotification J.MtError msg +sendErrorLog :: MonadLsp config m => Text -> m () +sendErrorLog msg = + sendToClient $ fromServerNot $ + NotificationMessage "2.0" SWindowLogMessage (LogMessageParams MtError msg) -- --------------------------------------------------------------------- -defaultErrorHandlers :: (Show a) => TVar (LanguageContextData config) -> J.LspIdRsp -> a -> [E.Handler ()] -defaultErrorHandlers tvarDat origId req = [ E.Handler someExcept ] +initializeErrorHandler :: (ResponseError -> IO ()) -> E.SomeException -> IO (Maybe a) +initializeErrorHandler sendResp e = do + sendResp $ ResponseError InternalError msg Nothing + pure Nothing where - someExcept (e :: E.SomeException) = do - let msg = T.pack $ unwords ["request error.", show req, show e] - sendErrorResponse tvarDat origId msg - sendErrorLog tvarDat msg - + msg = T.pack $ unwords ["Error on initialize:", show e] -- |===================================================================== -- -- Handlers --- | --- -initializeRequestHandler' - :: (Show config) - => (LspFuncs config -> IO (Maybe J.ResponseError)) - -> Maybe (Handler J.InitializeRequest) - -> TVar (LanguageContextData config) - -> J.InitializeRequest - -> IO () -initializeRequestHandler' onStartup mHandler tvarCtx req@(J.RequestMessage _ origId _ params) = - flip E.catches (defaultErrorHandlers tvarCtx (J.responseId origId) req) $ do - - case mHandler of - Just handler -> handler req - Nothing -> return () - - let wfs = case params ^. J.workspaceFolders of - Just (J.List xs) -> xs - Nothing -> [] - - atomically $ modifyTVar' tvarCtx (\c -> c { resWorkspaceFolders = wfs }) - - ctx0 <- readTVarIO tvarCtx - let rootDir = getFirst $ foldMap First [ params ^. J.rootUri >>= J.uriToFilePath +freshLspId :: MonadLsp config m => m Int +freshLspId = do + stateState $ \c -> + (resLspId c, c{resLspId = resLspId c+1}) + +-- | Call this to initialize the session +initializeRequestHandler + :: InitializeCallbacks config + -> VFS + -> Options + -> (FromServerMessage -> IO ()) + -> Message Initialize + -> IO (Maybe (LanguageContextEnv config)) +initializeRequestHandler InitializeCallbacks{..} vfs options sendFunc req = do + let sendResp = sendFunc . FromServerRsp SInitialize + handleErr (Left err) = do + sendResp $ makeResponseError (req ^. J.id) err + pure Nothing + handleErr (Right a) = pure $ Just a + flip E.catch (initializeErrorHandler $ sendResp . makeResponseError (req ^. J.id)) $ handleErr <=< runExceptT $ mdo + + let params = req ^. J.params + + let rootDir = getFirst $ foldMap First [ params ^. J.rootUri >>= uriToFilePath , params ^. J.rootPath <&> T.unpack ] - case rootDir of + liftIO $ case rootDir of Nothing -> return () Just dir -> do - logs $ "haskell-lsp:initializeRequestHandler: setting current dir to project root:" ++ dir + debugM "haskell-lsp.initializeRequestHandler" $ "Setting current dir to project root:" ++ dir unless (null dir) $ setCurrentDirectory dir - let - getCapabilities :: J.InitializeParams -> C.ClientCapabilities - getCapabilities (J.InitializeParams _ _ _ _ c _ _) = c - getLspId tvId = atomically $ do - cid <- readTVar tvId - modifyTVar' tvId (+1) - return $ J.IdInt cid - - clientSupportsWfs = fromMaybe False $ do - let (C.ClientCapabilities mw _ _ _) = params ^. J.capabilities - (C.WorkspaceClientCapabilities _ _ _ _ _ _ mwf _) <- mw + let initialWfs = case params ^. J.workspaceFolders of + Just (List xs) -> xs + Nothing -> [] + + tvarCtx <- liftIO $ newTVarIO $ + LanguageContextState + (VFSData vfs mempty) + mempty + Nothing + initialWfs + defaultProgressData + emptyIxMap + mempty + mempty + 0 + + -- Call the 'duringInitialization' callback to let the server kick stuff up + let env = LanguageContextEnv handlers (forward interpreter . onConfigurationChange) sendFunc tvarCtx (params ^. J.capabilities) rootDir + handlers = transmuteHandlers interpreter staticHandlers + interpreter = interpretHandler initializationResult + initializationResult <- ExceptT $ doInitialize env req + + let serverCaps = inferServerCapabilities (params ^. J.capabilities) options handlers + liftIO $ sendResp $ makeResponseMessage (req ^. J.id) (InitializeResult serverCaps (serverInfo options)) + pure env + where + makeResponseMessage rid result = ResponseMessage "2.0" (Just rid) (Right result) + makeResponseError origId err = ResponseMessage "2.0" (Just origId) (Left err) + +-- --------------------------------------------------------------------- + +-- | The current configuration from the client as set via the @initialize@ and +-- @workspace/didChangeConfiguration@ requests. +getConfig :: MonadLsp config m => m (Maybe config) +getConfig = getsState resConfig + +getClientCapabilities :: MonadLsp config m => m J.ClientCapabilities +getClientCapabilities = resClientCapabilities <$> getLspEnv + +getRootPath :: MonadLsp config m => m (Maybe FilePath) +getRootPath = resRootPath <$> getLspEnv + +-- | The current workspace folders, if the client supports workspace folders. +getWorkspaceFolders :: MonadLsp config m => m (Maybe [WorkspaceFolder]) +getWorkspaceFolders = do + clientCaps <- getClientCapabilities + let clientSupportsWfs = fromMaybe False $ do + let (J.ClientCapabilities mw _ _ _) = clientCaps + (J.WorkspaceClientCapabilities _ _ _ _ _ _ mwf _) <- mw mwf - getWfs tvc - | clientSupportsWfs = atomically $ Just . resWorkspaceFolders <$> readTVar tvc - | otherwise = return Nothing - - clientSupportsProgress = fromMaybe False $ do - let (C.ClientCapabilities _ _ wc _) = params ^. J.capabilities - (C.WindowClientCapabilities mProgress) <- wc - mProgress - - storeProgress :: J.ProgressToken -> Async a -> IO () - storeProgress n a = atomically $ do - pd <- resProgressData <$> readTVar tvarCtx - let pc = progressCancel pd - pc' = Map.insert n (cancelWith a ProgressCancelledException) pc - modifyTVar tvarCtx (\ctx -> ctx { resProgressData = pd { progressCancel = pc' }}) - - deleteProgress :: J.ProgressToken -> IO () - deleteProgress n = atomically $ do - pd <- resProgressData <$> readTVar tvarCtx - let x = progressCancel pd - x' = Map.delete n x - modifyTVar tvarCtx (\ctx -> ctx { resProgressData = pd { progressCancel = x' }}) - - -- Get a new id for the progress session and make a new one - getNewProgressId :: IO J.ProgressToken - getNewProgressId = liftIO $ atomically $ do - pd <- resProgressData <$> readTVar tvarCtx - let x = progressNextId pd - modifyTVar tvarCtx (\ctx -> ctx { resProgressData = pd { progressNextId = x + 1 }}) - return $ J.ProgressNumericToken x - - withProgressBase :: Bool -> (Text -> ProgressCancellable - -> ((Progress -> IO ()) -> IO a) -> IO a) - withProgressBase indefinite title cancellable f - | clientSupportsProgress = do - let sf = sendResponse tvarCtx - - progId <- getNewProgressId - - let initialPercentage - | indefinite = Nothing - | otherwise = Just 0 - cancellable' = case cancellable of - Cancellable -> True - NotCancellable -> False - - rId <- getLspId $ resLspId ctx0 - - -- Create progress token - liftIO $ sf $ ReqWorkDoneProgressCreate $ - fmServerWorkDoneProgressCreateRequest rId $ J.WorkDoneProgressCreateParams progId - - -- Send initial notification - liftIO $ sf $ NotWorkDoneProgressBegin $ fmServerWorkDoneProgressBeginNotification $ - J.ProgressParams progId $ - J.WorkDoneProgressBeginParams title (Just cancellable') Nothing initialPercentage - - aid <- async $ f (updater progId sf) - storeProgress progId aid - res <- wait aid - - -- Send done notification - liftIO $ sf $ NotWorkDoneProgressEnd $ fmServerWorkDoneProgressEndNotification $ - J.ProgressParams progId $ - J.WorkDoneProgressEndParams Nothing - -- Delete the progress cancellation from the map - -- If we don't do this then it's easy to leak things as the map contains any IO action. - deleteProgress progId - - - return res - | otherwise = f (const $ return ()) - where updater progId sf (Progress percentage msg) = - sf $ NotWorkDoneProgressReport $ fmServerWorkDoneProgressReportNotification $ - J.ProgressParams progId $ - J.WorkDoneProgressReportParams Nothing msg percentage - - withProgress' :: Text -> ProgressCancellable -> ((Progress -> IO ()) -> IO a) -> IO a - withProgress' = withProgressBase False - - withIndefiniteProgress' :: Text -> ProgressCancellable -> IO a -> IO a - withIndefiniteProgress' title cancellable f = - withProgressBase True title cancellable (const f) - - -- Launch the given process once the project root directory has been set - let lspFuncs = LspFuncs (getCapabilities params) - (getConfig tvarCtx) - (resSendResponse ctx0) - (getVirtualFile tvarCtx) - (persistVirtualFile tvarCtx) - (reverseFileMap tvarCtx) - (publishDiagnostics tvarCtx) - (flushDiagnosticsBySource tvarCtx) - (getLspId $ resLspId ctx0) - rootDir - (getWfs tvarCtx) - withProgress' - withIndefiniteProgress' - atomically $ modifyTVar tvarCtx (\cur_ctx -> cur_ctx { resLspFuncs = lspFuncs }) - - ctx <- readTVarIO tvarCtx - - initializationResult <- onStartup lspFuncs - - case initializationResult of - Just errResp -> do - sendResponse tvarCtx $ RspError $ makeResponseError (J.responseId origId) errResp - - Nothing -> do - let capa = serverCapabilities (getCapabilities params) (resOptions ctx) (resHandlers ctx) - -- TODO: wrap this up into a fn to create a response message - res = J.ResponseMessage "2.0" (J.responseId origId) (Right $ J.InitializeResponseCapabilities capa) - - sendResponse tvarCtx $ RspInitialize res + if clientSupportsWfs + then Just <$> getsState resWorkspaceFolders + else pure Nothing + +-- | Sends a @client/registerCapability@ request and dynamically registers +-- a 'Method' with a 'Handler'. Returns 'Nothing' if the client does not +-- support dynamic registration for the specified method, otherwise a +-- 'RegistrationToken' which can be used to unregister it later. +registerCapability :: forall f t (m :: Method FromClient t) config. + MonadLsp config f + => SClientMethod m + -> RegistrationOptions m + -> Handler f m + -> f (Maybe (RegistrationToken m)) +registerCapability method regOpts f = do + clientCaps <- resClientCapabilities <$> getLspEnv + handlers <- resHandlers <$> getLspEnv + let alreadyStaticallyRegistered = case splitClientMethod method of + IsClientNot -> DMap.member method $ notHandlers handlers + IsClientReq -> DMap.member method $ reqHandlers handlers + IsClientEither -> error "Cannot register capability for custom methods" + go clientCaps alreadyStaticallyRegistered + where + -- If the server has already registered statically, don't dynamically register + -- as per the spec + go _clientCaps True = pure Nothing + go clientCaps False + -- First, check to see if the client supports dynamic registration on this method + | dynamicSupported clientCaps = do + uuid <- liftIO $ UUID.toText <$> getStdRandom random + let registration = J.Registration uuid method regOpts + params = J.RegistrationParams (J.List [J.SomeRegistration registration]) + regId = RegistrationId uuid + rio <- askUnliftIO + ~() <- case splitClientMethod method of + IsClientNot -> modifyState $ \ctx -> + let newRegs = DMap.insert method pair (resRegistrationsNot ctx) + pair = Pair regId (ClientMessageHandler (unliftIO rio . f)) + in ctx { resRegistrationsNot = newRegs } + IsClientReq -> modifyState $ \ctx -> + let newRegs = DMap.insert method pair (resRegistrationsReq ctx) + pair = Pair regId (ClientMessageHandler (\msg k -> unliftIO rio $ f msg (liftIO . k))) + in ctx { resRegistrationsReq = newRegs } + IsClientEither -> error "Cannot register capability for custom methods" + + -- TODO: handle the scenario where this returns an error + _ <- sendRequest SClientRegisterCapability params $ \_res -> pure () + + pure (Just (RegistrationToken method regId)) + | otherwise = pure Nothing + + -- Also I'm thinking we should move this function to somewhere in messages.hs so + -- we don't forget to update it when adding new methods... + capDyn :: J.HasDynamicRegistration a (Maybe Bool) => Maybe a -> Bool + capDyn (Just x) = fromMaybe False $ x ^. J.dynamicRegistration + capDyn Nothing = False + + -- | Checks if client capabilities declares that the method supports dynamic registration + dynamicSupported clientCaps = case method of + SWorkspaceDidChangeConfiguration -> capDyn $ clientCaps ^? J.workspace . _Just . J.didChangeConfiguration . _Just + SWorkspaceDidChangeWatchedFiles -> capDyn $ clientCaps ^? J.workspace . _Just . J.didChangeWatchedFiles . _Just + SWorkspaceSymbol -> capDyn $ clientCaps ^? J.workspace . _Just . J.symbol . _Just + SWorkspaceExecuteCommand -> capDyn $ clientCaps ^? J.workspace . _Just . J.executeCommand . _Just + STextDocumentDidOpen -> capDyn $ clientCaps ^? J.textDocument . _Just . J.synchronization . _Just + STextDocumentDidChange -> capDyn $ clientCaps ^? J.textDocument . _Just . J.synchronization . _Just + STextDocumentDidClose -> capDyn $ clientCaps ^? J.textDocument . _Just . J.synchronization . _Just + STextDocumentCompletion -> capDyn $ clientCaps ^? J.textDocument . _Just . J.completion . _Just + STextDocumentHover -> capDyn $ clientCaps ^? J.textDocument . _Just . J.hover . _Just + STextDocumentSignatureHelp -> capDyn $ clientCaps ^? J.textDocument . _Just . J.signatureHelp . _Just + STextDocumentDeclaration -> capDyn $ clientCaps ^? J.textDocument . _Just . J.declaration . _Just + STextDocumentDefinition -> capDyn $ clientCaps ^? J.textDocument . _Just . J.definition . _Just + STextDocumentTypeDefinition -> capDyn $ clientCaps ^? J.textDocument . _Just . J.typeDefinition . _Just + STextDocumentImplementation -> capDyn $ clientCaps ^? J.textDocument . _Just . J.implementation . _Just + STextDocumentReferences -> capDyn $ clientCaps ^? J.textDocument . _Just . J.references . _Just + STextDocumentDocumentHighlight -> capDyn $ clientCaps ^? J.textDocument . _Just . J.documentHighlight . _Just + STextDocumentDocumentSymbol -> capDyn $ clientCaps ^? J.textDocument . _Just . J.documentSymbol . _Just + STextDocumentCodeAction -> capDyn $ clientCaps ^? J.textDocument . _Just . J.codeAction . _Just + STextDocumentCodeLens -> capDyn $ clientCaps ^? J.textDocument . _Just . J.codeLens . _Just + STextDocumentDocumentLink -> capDyn $ clientCaps ^? J.textDocument . _Just . J.documentLink . _Just + STextDocumentDocumentColor -> capDyn $ clientCaps ^? J.textDocument . _Just . J.colorProvider . _Just + STextDocumentColorPresentation -> capDyn $ clientCaps ^? J.textDocument . _Just . J.colorProvider . _Just + STextDocumentFormatting -> capDyn $ clientCaps ^? J.textDocument . _Just . J.formatting . _Just + STextDocumentRangeFormatting -> capDyn $ clientCaps ^? J.textDocument . _Just . J.rangeFormatting . _Just + STextDocumentOnTypeFormatting -> capDyn $ clientCaps ^? J.textDocument . _Just . J.onTypeFormatting . _Just + STextDocumentRename -> capDyn $ clientCaps ^? J.textDocument . _Just . J.rename . _Just + STextDocumentFoldingRange -> capDyn $ clientCaps ^? J.textDocument . _Just . J.foldingRange . _Just + STextDocumentSelectionRange -> capDyn $ clientCaps ^? J.textDocument . _Just . J.selectionRange . _Just + _ -> False + +-- | Sends a @client/unregisterCapability@ request and removes the handler +-- for that associated registration. +unregisterCapability :: MonadLsp config f => RegistrationToken m -> f () +unregisterCapability (RegistrationToken m (RegistrationId uuid)) = do + ~() <- case splitClientMethod m of + IsClientReq -> do + reqRegs <- getsState resRegistrationsReq + let newMap = DMap.delete m reqRegs + modifyState (\ctx -> ctx { resRegistrationsReq = newMap }) + IsClientNot -> do + notRegs <- getsState resRegistrationsNot + let newMap = DMap.delete m notRegs + modifyState (\ctx -> ctx { resRegistrationsNot = newMap }) + IsClientEither -> error "Cannot unregister capability for custom methods" + + let unregistration = J.Unregistration uuid (J.SomeClientMethod m) + params = J.UnregistrationParams (J.List [unregistration]) + void $ sendRequest SClientUnregisterCapability params $ \_res -> pure () + +-------------------------------------------------------------------------------- +-- PROGRESS +-------------------------------------------------------------------------------- + +storeProgress :: MonadLsp config m => ProgressToken -> Async a -> m () +storeProgress n a = do + let f = Map.insert n (cancelWith a ProgressCancelledException) . progressCancel + modifyState $ \ctx -> ctx { resProgressData = (resProgressData ctx) { progressCancel = f (resProgressData ctx)}} + +deleteProgress :: MonadLsp config m => ProgressToken -> m () +deleteProgress n = do + let f = Map.delete n . progressCancel + modifyState $ \ctx -> ctx { resProgressData = (resProgressData ctx) { progressCancel = f (resProgressData ctx)}} + +-- Get a new id for the progress session and make a new one +getNewProgressId :: MonadLsp config m => m ProgressToken +getNewProgressId = do + stateState $ \ctx@LanguageContextState{resProgressData} -> + let x = progressNextId resProgressData + ctx' = ctx { resProgressData = resProgressData { progressNextId = x + 1 }} + in (ProgressNumericToken x, ctx') + +withProgressBase :: MonadLsp c m => Bool -> Text -> ProgressCancellable -> ((ProgressAmount -> m ()) -> m a) -> m a +withProgressBase indefinite title cancellable f = do + + progId <- getNewProgressId + + let initialPercentage + | indefinite = Nothing + | otherwise = Just 0 + cancellable' = case cancellable of + Cancellable -> True + NotCancellable -> False + + -- Create progress token + -- FIXME : This needs to wait until the request returns before + -- continuing!!! + _ <- sendRequest SWindowWorkDoneProgressCreate + (WorkDoneProgressCreateParams progId) $ \res -> do + case res of + -- An error ocurred when the client was setting it up + -- No need to do anything then, as per the spec + Left _err -> pure () + Right () -> pure () + + -- Send initial notification + sendNotification SProgress $ + fmap Begin $ ProgressParams progId $ + WorkDoneProgressBeginParams title (Just cancellable') Nothing initialPercentage + + -- Send the begin and done notifications via 'bracket_' so that they are always fired + res <- withRunInIO $ \runInBase -> + E.bracket_ + -- Send begin notification + (runInBase $ sendNotification SProgress $ + fmap Begin $ ProgressParams progId $ + WorkDoneProgressBeginParams title (Just cancellable') Nothing initialPercentage) + + -- Send end notification + (runInBase $ sendNotification SProgress $ + End <$> ProgressParams progId (WorkDoneProgressEndParams Nothing)) $ do + + -- Run f asynchronously + aid <- async $ runInBase $ f (updater progId) + runInBase $ storeProgress progId aid + wait aid + + -- Delete the progress cancellation from the map + -- If we don't do this then it's easy to leak things as the map contains any IO action. + deleteProgress progId + + return res + where updater progId (ProgressAmount percentage msg) = do + liftIO $ putStrLn "asdf" + sendNotification SProgress $ fmap Report $ ProgressParams progId $ + WorkDoneProgressReportParams Nothing msg percentage + +clientSupportsProgress :: J.ClientCapabilities -> Bool +clientSupportsProgress (J.ClientCapabilities _ _ wc _) = fromMaybe False $ do + (J.WindowClientCapabilities mProgress) <- wc + mProgress + +-- | Wrapper for reporting progress to the client during a long running +-- task. +-- 'withProgress' @title cancellable f@ starts a new progress reporting +-- session, and finishes it once f is completed. +-- f is provided with an update function that allows it to report on +-- the progress during the session. +-- If @cancellable@ is 'Cancellable', @f@ will be thrown a +-- 'ProgressCancelledException' if the user cancels the action in +-- progress. +withProgress :: MonadLsp c m => Text -> ProgressCancellable -> ((ProgressAmount -> m ()) -> m a) -> m a +withProgress title cancellable f = do + clientCaps <- getClientCapabilities + if clientSupportsProgress clientCaps + then withProgressBase False title cancellable f + else f (const $ return ()) + +-- | Same as 'withProgress', but for processes that do not report the +-- precentage complete. +-- +-- @since 0.10.0.0 +withIndefiniteProgress :: MonadLsp c m => Text -> ProgressCancellable -> m a -> m a +withIndefiniteProgress title cancellable f = do + clientCaps <- getClientCapabilities + if clientSupportsProgress clientCaps + then withProgressBase True title cancellable (const f) + else f -- | Infers the capabilities based on registered handlers, and sets the appropriate options. -- A provider should be set to Nothing if the server does not support it, unless it is a -- static option. -serverCapabilities :: C.ClientCapabilities -> Options -> Handlers -> J.InitializeResponseCapabilitiesInner -serverCapabilities clientCaps o h = - J.InitializeResponseCapabilitiesInner +inferServerCapabilities :: J.ClientCapabilities -> Options -> Handlers m -> J.ServerCapabilities +inferServerCapabilities clientCaps o h = + J.ServerCapabilities { J._textDocumentSync = sync - , J._hoverProvider = supported (hoverHandler h) + , J._hoverProvider = supportedBool J.STextDocumentHover , J._completionProvider = completionProvider + , J._declarationProvider = supportedBool J.STextDocumentDeclaration , J._signatureHelpProvider = signatureHelpProvider - , J._definitionProvider = supported (definitionHandler h) - , J._typeDefinitionProvider = Just $ J.GotoOptionsStatic $ isJust $ typeDefinitionHandler h - , J._implementationProvider = Just $ J.GotoOptionsStatic $ isJust $ typeDefinitionHandler h - , J._referencesProvider = supported (referencesHandler h) - , J._documentHighlightProvider = supported (documentHighlightHandler h) - , J._documentSymbolProvider = supported (documentSymbolHandler h) - , J._workspaceSymbolProvider = supported (workspaceSymbolHandler h) + , J._definitionProvider = supportedBool J.STextDocumentDefinition + , J._typeDefinitionProvider = supportedBool J.STextDocumentTypeDefinition + , J._implementationProvider = supportedBool J.STextDocumentImplementation + , J._referencesProvider = supportedBool J.STextDocumentReferences + , J._documentHighlightProvider = supportedBool J.STextDocumentDocumentHighlight + , J._documentSymbolProvider = supportedBool J.STextDocumentDocumentSymbol , J._codeActionProvider = codeActionProvider - , J._codeLensProvider = supported' (codeLensHandler h) $ J.CodeLensOptions $ - supported (codeLensResolveHandler h) - , J._documentFormattingProvider = supported (documentFormattingHandler h) - , J._documentRangeFormattingProvider = supported (documentRangeFormattingHandler h) + , J._codeLensProvider = supported' J.STextDocumentCodeLens $ J.CodeLensOptions + (Just False) + (supported J.SCodeLensResolve) + , J._documentFormattingProvider = supportedBool J.STextDocumentFormatting + , J._documentRangeFormattingProvider = supportedBool J.STextDocumentRangeFormatting , J._documentOnTypeFormattingProvider = documentOnTypeFormattingProvider - , J._renameProvider = Just $ J.RenameOptionsStatic $ isJust $ renameHandler h - , J._documentLinkProvider = supported' (documentLinkHandler h) $ J.DocumentLinkOptions $ - Just $ isJust $ documentLinkResolveHandler h - , J._colorProvider = Just $ J.ColorOptionsStatic $ isJust $ documentColorHandler h - , J._foldingRangeProvider = Just $ J.FoldingRangeOptionsStatic $ isJust $ foldingRangeHandler h + , J._renameProvider = supportedBool J.STextDocumentRename + , J._documentLinkProvider = supported' J.STextDocumentDocumentLink $ J.DocumentLinkOptions + (Just False) + (supported J.SDocumentLinkResolve) + , J._colorProvider = supportedBool J.STextDocumentDocumentColor + , J._foldingRangeProvider = supportedBool J.STextDocumentFoldingRange , J._executeCommandProvider = executeCommandProvider + , J._selectionRangeProvider = supportedBool J.STextDocumentSelectionRange + , J._workspaceSymbolProvider = supported J.SWorkspaceSymbol , J._workspace = Just workspace -- TODO: Add something for experimental , J._experimental = Nothing :: Maybe J.Value } where - supported x = supported' x True - supported' (Just _) = Just - supported' Nothing = const Nothing + -- | For when we just return a simple @true@/@false@ to indicate if we + -- support the capability + supportedBool = Just . J.InL . supported_b + + supported' m b + | supported_b m = Just b + | otherwise = Nothing + + supported :: forall m. J.SClientMethod m -> Maybe Bool + supported = Just . supported_b + + supported_b :: forall m. J.SClientMethod m -> Bool + supported_b m = case splitClientMethod m of + IsClientNot -> DMap.member m $ notHandlers h + IsClientReq -> DMap.member m $ reqHandlers h + IsClientEither -> error "capabilities depend on custom method" singleton :: a -> [a] singleton x = [x] completionProvider - | isJust $ completionHandler h = Just $ + | supported_b J.STextDocumentCompletion = Just $ J.CompletionOptions - (Just $ isJust $ completionResolveHandler h) + Nothing (map singleton <$> completionTriggerCharacters o) (map singleton <$> completionAllCommitCharacters o) + (supported J.SCompletionItemResolve) | otherwise = Nothing clientSupportsCodeActionKinds = isJust $ @@ -941,98 +973,96 @@ serverCapabilities clientCaps o h = codeActionProvider | clientSupportsCodeActionKinds - , isJust $ codeActionHandler h = Just $ maybe (J.CodeActionOptionsStatic True) (J.CodeActionOptions . Just) (codeActionKinds o) - | isJust $ codeActionHandler h = Just (J.CodeActionOptionsStatic True) - | otherwise = Just (J.CodeActionOptionsStatic False) + , supported_b J.STextDocumentCodeAction = Just $ + maybe (J.InL True) (J.InR . J.CodeActionOptions Nothing . Just . J.List) + (codeActionKinds o) + | supported_b J.STextDocumentCodeAction = Just (J.InL True) + | otherwise = Just (J.InL False) signatureHelpProvider - | isJust $ signatureHelpHandler h = Just $ + | supported_b J.STextDocumentSignatureHelp = Just $ J.SignatureHelpOptions - (map singleton <$> signatureHelpTriggerCharacters o) - (map singleton <$> signatureHelpRetriggerCharacters o) + Nothing + (J.List . map singleton <$> signatureHelpTriggerCharacters o) + (J.List . map singleton <$> signatureHelpRetriggerCharacters o) | otherwise = Nothing documentOnTypeFormattingProvider - | isJust $ documentOnTypeFormattingHandler h + | supported_b J.STextDocumentOnTypeFormatting , Just (first :| rest) <- documentOnTypeFormattingTriggerCharacters o = Just $ J.DocumentOnTypeFormattingOptions (T.pack [first]) (Just (map (T.pack . singleton) rest)) - | isJust $ documentOnTypeFormattingHandler h + | supported_b J.STextDocumentOnTypeFormatting , Nothing <- documentOnTypeFormattingTriggerCharacters o = error "documentOnTypeFormattingTriggerCharacters needs to be set if a documentOnTypeFormattingHandler is set" | otherwise = Nothing executeCommandProvider - | isJust $ executeCommandHandler h - , Just cmds <- executeCommandCommands o = Just (J.ExecuteCommandOptions (J.List cmds)) - | isJust $ executeCommandHandler h + | supported_b J.SWorkspaceExecuteCommand + , Just cmds <- executeCommandCommands o = Just (J.ExecuteCommandOptions Nothing (J.List cmds)) + | supported_b J.SWorkspaceExecuteCommand , Nothing <- executeCommandCommands o = error "executeCommandCommands needs to be set if a executeCommandHandler is set" | otherwise = Nothing sync = case textDocumentSync o of - Just x -> Just (J.TDSOptions x) + Just x -> Just (J.InL x) Nothing -> Nothing - workspace = J.WorkspaceOptions workspaceFolder - workspaceFolder = case didChangeWorkspaceFoldersNotificationHandler h of - Just _ -> Just $ + workspace = J.WorkspaceServerCapabilities workspaceFolder + workspaceFolder = supported' J.SWorkspaceDidChangeWorkspaceFolders $ -- sign up to receive notifications - J.WorkspaceFolderOptions (Just True) (Just (J.WorkspaceFolderChangeNotificationsBool True)) - Nothing -> Nothing + J.WorkspaceFoldersServerCapabilities (Just True) (Just (J.InR True)) -progressCancelHandler :: TVar (LanguageContextData config) -> J.WorkDoneProgressCancelNotification -> IO () -progressCancelHandler tvarCtx (J.NotificationMessage _ _ (J.WorkDoneProgressCancelParams tid)) = do - mact <- Map.lookup tid . progressCancel . resProgressData <$> readTVarIO tvarCtx +progressCancelHandler :: J.WorkDoneProgressCancelNotification -> LspM config () +progressCancelHandler (J.NotificationMessage _ _ (J.WorkDoneProgressCancelParams tid)) = do + mact <- getsState $ Map.lookup tid . progressCancel . resProgressData case mact of Nothing -> return () - Just cancelAction -> cancelAction + Just cancelAction -> liftIO $ cancelAction +exitNotificationHandler :: Handler IO J.Exit +exitNotificationHandler = \_ -> do + noticeM "haskell-lsp.exitNotificationHandler" "Got exit, exiting" + exitSuccess --- | --- -shutdownRequestHandler :: TVar (LanguageContextData config) -> J.ShutdownRequest -> IO () -shutdownRequestHandler tvarCtx req@(J.RequestMessage _ origId _ _) = - flip E.catches (defaultErrorHandlers tvarCtx (J.responseId origId) req) $ do - let res = makeResponseMessage req Nothing - - sendResponse tvarCtx $ RspShutdown res +-- | Default Shutdown handler +shutdownRequestHandler :: Handler IO J.Shutdown +shutdownRequestHandler = \_req k -> do + k $ Right J.Empty -- --------------------------------------------------------------------- --- | Take the new diagnostics, update the stored diagnostics for the given file --- and version, and publish the total to the client. -publishDiagnostics :: TVar (LanguageContextData config) -> PublishDiagnosticsFunc -publishDiagnostics tvarDat maxDiagnosticCount uri version diags = do - join $ atomically $ do - ctx <- readTVar tvarDat - let ds = updateDiagnostics (resDiagnostics ctx) uri version diags - writeTVar tvarDat $ ctx{resDiagnostics = ds} - let mdp = getDiagnosticParamsFor maxDiagnosticCount ds uri - return $ case mdp of - Nothing -> return () - Just params -> - resSendResponse ctx $ NotPublishDiagnostics - $ J.NotificationMessage "2.0" J.TextDocumentPublishDiagnostics params +-- | Aggregate all diagnostics pertaining to a particular version of a document, +-- by source, and sends a @textDocument/publishDiagnostics@ notification with +-- the total (limited by the first parameter) whenever it is updated. +publishDiagnostics :: MonadLsp config m => Int -> NormalizedUri -> TextDocumentVersion -> DiagnosticsBySource -> m () +publishDiagnostics maxDiagnosticCount uri version diags = join $ stateState $ \ctx -> + let ds = updateDiagnostics (resDiagnostics ctx) uri version diags + ctx' = ctx{resDiagnostics = ds} + mdp = getDiagnosticParamsFor maxDiagnosticCount ds uri + act = case mdp of + Nothing -> return () + Just params -> + sendToClient $ J.fromServerNot $ J.NotificationMessage "2.0" J.STextDocumentPublishDiagnostics params + in (act,ctx') -- --------------------------------------------------------------------- --- | Take the new diagnostics, update the stored diagnostics for the given file --- and version, and publish the total to the client. -flushDiagnosticsBySource :: TVar (LanguageContextData config) -> FlushDiagnosticsBySourceFunc -flushDiagnosticsBySource tvarDat maxDiagnosticCount msource = join $ atomically $ do - -- logs $ "haskell-lsp:flushDiagnosticsBySource:source=" ++ show source - ctx <- readTVar tvarDat +-- | Remove all diagnostics from a particular source, and send the updates to +-- the client. +flushDiagnosticsBySource :: MonadLsp config m => Int -- ^ Max number of diagnostics to send + -> Maybe DiagnosticSource -> m () +flushDiagnosticsBySource maxDiagnosticCount msource = join $ stateState $ \ctx -> let ds = flushBySource (resDiagnostics ctx) msource - writeTVar tvarDat $ ctx {resDiagnostics = ds} - -- Send the updated diagnostics to the client - return $ forM_ (HM.keys ds) $ \uri -> do - -- logs $ "haskell-lsp:flushDiagnosticsBySource:uri=" ++ show uri - let mdp = getDiagnosticParamsFor maxDiagnosticCount ds uri - case mdp of - Nothing -> return () - Just params -> do - resSendResponse ctx $ NotPublishDiagnostics - $ J.NotificationMessage "2.0" J.TextDocumentPublishDiagnostics params + ctx' = ctx {resDiagnostics = ds} + -- Send the updated diagnostics to the client + act = forM_ (HM.keys ds) $ \uri -> do + let mdp = getDiagnosticParamsFor maxDiagnosticCount ds uri + case mdp of + Nothing -> return () + Just params -> do + sendToClient $ J.fromServerNot $ J.NotificationMessage "2.0" J.STextDocumentPublishDiagnostics params + in (act,ctx') -- ===================================================================== -- @@ -1046,25 +1076,32 @@ setupLogger :: Maybe FilePath -> [String] -> Priority -> IO () setupLogger mLogFile extraLogNames level = do logStream <- case mLogFile of - Just logFile -> openFile logFile AppendMode + Just logFile -> openFile logFile AppendMode `E.catch` handleIOException logFile Nothing -> return stderr hSetEncoding logStream utf8 logH <- LHS.streamHandler logStream level let logHandle = logH {LHS.closeFunc = hClose} - logFormat = L.tfLogFormatter _LOG_FORMAT_DATE _LOG_FORMAT - logHandler = LH.setFormatter logHandle logFormat + logFormatter = L.tfLogFormatter logDateFormat logFormat + logHandler = LH.setFormatter logHandle logFormatter L.updateGlobalLogger L.rootLoggerName $ L.setHandlers ([] :: [LHS.GenericHandler Handle]) - L.updateGlobalLogger _LOG_NAME $ L.setHandlers [logHandler] - L.updateGlobalLogger _LOG_NAME $ L.setLevel level + L.updateGlobalLogger "haskell-lsp" $ L.setHandlers [logHandler] + L.updateGlobalLogger "haskell-lsp" $ L.setLevel level -- Also route the additional log names to the same log forM_ extraLogNames $ \logName -> do L.updateGlobalLogger logName $ L.setHandlers [logHandler] L.updateGlobalLogger logName $ L.setLevel level + where + logFormat = "$time [$tid] $prio $loggername:\t$msg" + logDateFormat = "%Y-%m-%d %H:%M:%S%Q" +handleIOException :: FilePath -> E.IOException -> IO Handle +handleIOException logFile _ = do + hPutStr stderr $ "Couldn't open log file " ++ logFile ++ "; falling back to stderr logging" + return stderr -- --------------------------------------------------------------------- diff --git a/src/Language/Haskell/LSP/Diagnostics.hs b/src/Language/Haskell/LSP/Diagnostics.hs index d40eceae4..5851717a8 100644 --- a/src/Language/Haskell/LSP/Diagnostics.hs +++ b/src/Language/Haskell/LSP/Diagnostics.hs @@ -91,7 +91,7 @@ getDiagnosticParamsFor :: Int -> DiagnosticStore -> J.NormalizedUri -> Maybe J.P getDiagnosticParamsFor maxDiagnostics ds uri = case HM.lookup uri ds of Nothing -> Nothing - Just (StoreItem _ diags) -> - Just $ J.PublishDiagnosticsParams (J.fromNormalizedUri uri) (J.List (take maxDiagnostics $ SL.fromSortedList $ mconcat $ Map.elems diags)) + Just (StoreItem mv diags) -> + Just $ J.PublishDiagnosticsParams (J.fromNormalizedUri uri) mv (J.List (take maxDiagnostics $ SL.fromSortedList $ mconcat $ Map.elems diags)) -- --------------------------------------------------------------------- diff --git a/src/Language/Haskell/LSP/Messages.hs b/src/Language/Haskell/LSP/Messages.hs deleted file mode 100644 index c15119036..000000000 --- a/src/Language/Haskell/LSP/Messages.hs +++ /dev/null @@ -1,126 +0,0 @@ -{-# LANGUAGE DeriveAnyClass #-} -{-# LANGUAGE DeriveGeneric #-} - -module Language.Haskell.LSP.Messages - ( module Language.Haskell.LSP.Types.MessageFuncs - , FromClientMessage(..) - , FromServerMessage(..) - ) -where - -import Language.Haskell.LSP.Types.MessageFuncs -import Language.Haskell.LSP.Types -import GHC.Generics -import Data.Aeson - --- | A wrapper around a message that originates from the client --- and is sent to the server. -data FromClientMessage = ReqInitialize InitializeRequest - | ReqShutdown ShutdownRequest - | ReqHover HoverRequest - | ReqCompletion CompletionRequest - | ReqCompletionItemResolve CompletionItemResolveRequest - | ReqSignatureHelp SignatureHelpRequest - | ReqDefinition DefinitionRequest - | ReqTypeDefinition TypeDefinitionRequest - | ReqImplementation ImplementationRequest - | ReqFindReferences ReferencesRequest - | ReqDocumentHighlights DocumentHighlightRequest - | ReqDocumentSymbols DocumentSymbolRequest - | ReqWorkspaceSymbols WorkspaceSymbolRequest - | ReqCodeAction CodeActionRequest - | ReqCodeLens CodeLensRequest - | ReqCodeLensResolve CodeLensResolveRequest - | ReqDocumentLink DocumentLinkRequest - | ReqDocumentLinkResolve DocumentLinkResolveRequest - | ReqDocumentColor DocumentColorRequest - | ReqColorPresentation ColorPresentationRequest - | ReqDocumentFormatting DocumentFormattingRequest - | ReqDocumentRangeFormatting DocumentRangeFormattingRequest - | ReqDocumentOnTypeFormatting DocumentOnTypeFormattingRequest - | ReqRename RenameRequest - | ReqPrepareRename PrepareRenameRequest - | ReqFoldingRange FoldingRangeRequest - | ReqExecuteCommand ExecuteCommandRequest - | ReqWillSaveWaitUntil WillSaveWaitUntilTextDocumentRequest - -- Responses - | RspApplyWorkspaceEdit ApplyWorkspaceEditResponse - -- TODO: Remove this and properly decode the type of responses - -- based on the id - | RspFromClient BareResponseMessage - -- Notifications - | NotInitialized InitializedNotification - | NotExit ExitNotification - -- A cancel request notification is duplex! - | NotCancelRequestFromClient CancelNotification - | NotDidChangeConfiguration DidChangeConfigurationNotification - | NotDidOpenTextDocument DidOpenTextDocumentNotification - | NotDidChangeTextDocument DidChangeTextDocumentNotification - | NotDidCloseTextDocument DidCloseTextDocumentNotification - | NotWillSaveTextDocument WillSaveTextDocumentNotification - | NotDidSaveTextDocument DidSaveTextDocumentNotification - | NotDidChangeWatchedFiles DidChangeWatchedFilesNotification - | NotDidChangeWorkspaceFolders DidChangeWorkspaceFoldersNotification - | NotWorkDoneProgressCancel WorkDoneProgressCancelNotification - - -- It is common for language servers to add custom message types so these - -- three constructors can be used to handle custom request, response or notification - -- types. - | ReqCustomClient CustomClientRequest - | NotCustomClient CustomClientNotification - deriving (Eq,Read,Show,Generic,ToJSON,FromJSON) - --- | A wrapper around a message that originates from the server --- and is sent to the client. -data FromServerMessage = ReqRegisterCapability RegisterCapabilityRequest - | ReqUnregisterCapability UnregisterCapabilityRequest - | ReqApplyWorkspaceEdit ApplyWorkspaceEditRequest - | ReqShowMessage ShowMessageRequest - | ReqWorkDoneProgressCreate WorkDoneProgressCreateRequest - -- Responses - | RspInitialize InitializeResponse - | RspShutdown ShutdownResponse - | RspHover HoverResponse - | RspCompletion CompletionResponse - | RspCompletionItemResolve CompletionItemResolveResponse - | RspSignatureHelp SignatureHelpResponse - | RspDefinition DefinitionResponse - | RspTypeDefinition TypeDefinitionResponse - | RspImplementation ImplementationResponse - | RspFindReferences ReferencesResponse - | RspDocumentHighlights DocumentHighlightsResponse - | RspDocumentSymbols DocumentSymbolsResponse - | RspWorkspaceSymbols WorkspaceSymbolsResponse - | RspCodeAction CodeActionResponse - | RspCodeLens CodeLensResponse - | RspCodeLensResolve CodeLensResolveResponse - | RspDocumentLink DocumentLinkResponse - | RspDocumentLinkResolve DocumentLinkResolveResponse - | RspDocumentColor DocumentColorResponse - | RspColorPresentation ColorPresentationResponse - | RspDocumentFormatting DocumentFormattingResponse - | RspDocumentRangeFormatting DocumentRangeFormattingResponse - | RspDocumentOnTypeFormatting DocumentOnTypeFormattingResponse - | RspRename RenameResponse - | RspFoldingRange FoldingRangeResponse - | RspExecuteCommand ExecuteCommandResponse - | RspError ErrorResponse - | RspWillSaveWaitUntil WillSaveWaitUntilTextDocumentResponse - -- Notifications - | NotPublishDiagnostics PublishDiagnosticsNotification - | NotLogMessage LogMessageNotification - | NotShowMessage ShowMessageNotification - | NotWorkDoneProgressBegin WorkDoneProgressBeginNotification - | NotWorkDoneProgressReport WorkDoneProgressReportNotification - | NotWorkDoneProgressEnd WorkDoneProgressEndNotification - | NotTelemetry TelemetryNotification - -- A cancel request notification is duplex! - | NotCancelRequestFromServer CancelNotificationServer - - -- It is common for language servers to add custom message types so these - -- three constructors can be used to handle custom request, response or notification - -- types. - | ReqCustomServer CustomServerRequest - | RspCustomServer CustomResponse - | NotCustomServer CustomServerNotification - deriving (Eq,Read,Show,Generic,ToJSON,FromJSON) diff --git a/src/Language/Haskell/LSP/Utility.hs b/src/Language/Haskell/LSP/Utility.hs deleted file mode 100644 index e0bdefbbb..000000000 --- a/src/Language/Haskell/LSP/Utility.hs +++ /dev/null @@ -1,52 +0,0 @@ -module Language.Haskell.LSP.Utility where - - --- Based on Phoityne.VSCode.Utility - -import qualified Data.ByteString as BS -import qualified Data.ByteString.Lazy as LBS -import qualified Data.ByteString.Lazy.Char8 as B -import qualified Data.Text as T -import qualified Data.Text.Encoding as TE -import qualified Data.Text.Lazy as TL -import qualified Data.Text.Lazy.Encoding as TLE -import Language.Haskell.LSP.Constant -import System.Log.Logger - --- --------------------------------------------------------------------- -{-# ANN module ("HLint: ignore Eta reduce" :: String) #-} -{-# ANN module ("HLint: ignore Redundant do" :: String) #-} -{-# ANN module ("HLint: ignore Reduce duplication" :: String) #-} --- --------------------------------------------------------------------- - --- | --- UTF8文字列をByteStringへの変換 --- -str2bs :: String -> BS.ByteString -str2bs = TE.encodeUtf8 . T.pack - --- | --- ByteStringをUTF8文字列への変換 --- -bs2str :: BS.ByteString -> String -bs2str = T.unpack. TE.decodeUtf8 - --- | --- UTF8文字列をLazyByteStringへの変換 --- -str2lbs :: String -> LBS.ByteString -str2lbs = TLE.encodeUtf8 . TL.pack - --- | --- LazyByteStringをUTF8文字列への変換 --- -lbs2str :: LBS.ByteString -> String -lbs2str = TL.unpack. TLE.decodeUtf8 - --- --------------------------------------------------------------------- - -logs :: String -> IO () -logs s = debugM _LOG_NAME s - -logm :: B.ByteString -> IO () -logm str = logs (lbs2str str) diff --git a/src/Language/Haskell/LSP/VFS.hs b/src/Language/Haskell/LSP/VFS.hs index 994827c04..ab6ddcd90 100644 --- a/src/Language/Haskell/LSP/VFS.hs +++ b/src/Language/Haskell/LSP/VFS.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE CPP #-} {-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE MultiWayIf #-} {-# LANGUAGE OverloadedStrings #-} @@ -54,12 +53,12 @@ import Data.Rope.UTF16 ( Rope ) import qualified Data.Rope.UTF16 as Rope import qualified Language.Haskell.LSP.Types as J import qualified Language.Haskell.LSP.Types.Lens as J -import Language.Haskell.LSP.Utility import System.FilePath import Data.Hashable import System.Directory import System.IO import System.IO.Temp +import System.Log.Logger -- --------------------------------------------------------------------- {-# ANN module ("hlint: ignore Eta reduce" :: String) #-} @@ -132,14 +131,14 @@ 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 initVfs (J.RequestMessage _ _ _ params) = do - let J.ApplyWorkspaceEditParams edit = params + let J.ApplyWorkspaceEditParams _label edit = params J.WorkspaceEdit mChanges mDocChanges = edit case mDocChanges of Just (J.List textDocEdits) -> applyEdits textDocEdits Nothing -> case mChanges of Just cs -> applyEdits $ HashMap.foldlWithKey' changeToTextDocumentEdit [] cs Nothing -> do - logs "haskell-lsp:changeVfs:no changes" + debugM "haskell-lsp.changeVfs" "No changes" return initVfs where @@ -158,9 +157,9 @@ changeFromServerVFS initVfs (J.RequestMessage _ _ _ params) = do let sortedEdits = sortOn (Down . (^. J.range)) edits changeEvents = map editToChangeEvent sortedEdits ps = J.DidChangeTextDocumentParams vid (J.List changeEvents) - notif = J.NotificationMessage "" J.TextDocumentDidChange ps + notif = J.NotificationMessage "" J.STextDocumentDidChange ps let (vfs',ls) = changeFromClientVFS vfs notif - mapM_ logs ls + mapM_ (debugM "haskell-lsp.changeFromServerVFS") ls return vfs' editToChangeEvent (J.TextEdit range text) = J.TextDocumentContentChangeEvent (Just range) Nothing text @@ -195,7 +194,7 @@ persistFileVFS vfs uri = hSetNewlineMode h noNewlineTranslation hSetEncoding h utf8 hPutStr h contents - logs $ "haskell-lsp:persistFileVFS: Writing virtual file: " + debugM "haskell-lsp.persistFileVFS" $ "Writing virtual file: " ++ "uri = " ++ show uri ++ ", virtual file = " ++ show tfn withFile tfn WriteMode writeRaw in Just (tfn, action) diff --git a/stack-8.2.2.yaml b/stack-8.2.2.yaml deleted file mode 100644 index 990a002a7..000000000 --- a/stack-8.2.2.yaml +++ /dev/null @@ -1,12 +0,0 @@ -resolver: lts-11.20 # GHC 8.2.2 version - -packages: -- '.' -- ./haskell-lsp-types -extra-deps: -- sorted-list-0.2.1.0 -- rope-utf16-splay-0.3.1.0 -flags: {} -extra-package-dbs: [] -nix: - packages: [icu] diff --git a/stack-8.4.2.yaml b/stack-8.4.2.yaml index 8ce35b2f4..66746665f 100644 --- a/stack-8.4.2.yaml +++ b/stack-8.4.2.yaml @@ -3,6 +3,7 @@ resolver: nightly-2018-05-30 # last nightly for GHC 8.4.2 packages: - '.' - ./haskell-lsp-types +- ./func-test extra-deps: - rope-utf16-splay-0.3.1.0 diff --git a/stack-8.4.3.yaml b/stack-8.4.3.yaml index 982082203..f10f7ddd0 100644 --- a/stack-8.4.3.yaml +++ b/stack-8.4.3.yaml @@ -3,6 +3,7 @@ resolver: lts-12.5 # GHC 8.4.3 packages: - '.' - ./haskell-lsp-types +- ./func-test extra-deps: - rope-utf16-splay-0.3.1.0 diff --git a/stack-8.4.4.yaml b/stack-8.4.4.yaml index c2433c7e7..f2c049e42 100644 --- a/stack-8.4.4.yaml +++ b/stack-8.4.4.yaml @@ -3,9 +3,14 @@ resolver: lts-12.26 # GHC 8.4.4 packages: - '.' - ./haskell-lsp-types +- ./func-test extra-deps: - rope-utf16-splay-0.3.1.0 +- some-1.0.1@sha256:26e5bab7276f48b25ea8660d3fd1166c0f20fd497dac879a40f408e23211f93e,2055 +- parser-combinators-1.2.1@sha256:16c3490e007ec10b1255a2b36fb483d000156d555269107131241d9e0fa96412,1788 +- github: bubba/lsp-test + commit: e251176a4b2ff4dead7846fe5d0a4e1dbea69fd4 flags: {} extra-package-dbs: [] diff --git a/stack-8.6.4.yaml b/stack-8.6.4.yaml index 2cd138514..d4be31616 100644 --- a/stack-8.6.4.yaml +++ b/stack-8.6.4.yaml @@ -3,6 +3,7 @@ resolver: lts-13.16 # GHC 8.6.4 packages: - '.' - ./haskell-lsp-types +- ./func-test extra-deps: - rope-utf16-splay-0.3.1.0 diff --git a/stack-8.6.5.yaml b/stack-8.6.5.yaml index c04ae023a..4c2b7895d 100644 --- a/stack-8.6.5.yaml +++ b/stack-8.6.5.yaml @@ -3,8 +3,13 @@ resolver: lts-14.11 # GHC 8.6.5 packages: - '.' - ./haskell-lsp-types +- ./func-test extra-deps: +- some-1.0.1@sha256:26e5bab7276f48b25ea8660d3fd1166c0f20fd497dac879a40f408e23211f93e,2055 +- parser-combinators-1.2.1@sha256:16c3490e007ec10b1255a2b36fb483d000156d555269107131241d9e0fa96412,1788 +- github: bubba/lsp-test + commit: e251176a4b2ff4dead7846fe5d0a4e1dbea69fd4 flags: {} extra-package-dbs: [] diff --git a/stack-8.8.1.yaml b/stack-8.8.1.yaml index f23e7a35e..fd3bc60ce 100644 --- a/stack-8.8.1.yaml +++ b/stack-8.8.1.yaml @@ -3,8 +3,15 @@ resolver: nightly-2020-01-21 # last GHC 8.8.1 packages: - '.' - ./haskell-lsp-types +- ./func-test extra-deps: +- dependent-map-0.4.0.0@sha256:ca2b131046f4340a1c35d138c5a003fe4a5be96b14efc26291ed35fd08c62221,1657 +- dependent-sum-template-0.1.0.3@sha256:0bbbacdfbd3abf2a15aaf0cf2c27e5bdd159b519441fec39e1e6f2f54424adde,1682 +- constraints-extras-0.3.0.2@sha256:013b8d0392582c6ca068e226718a4fe8be8e22321cc0634f6115505bf377ad26,1853 +- dependent-sum-0.7.1.0@sha256:5599aa89637db434431b1dd3fa7c34bc3d565ee44f0519bfbc877be1927c2531,2068 +- github: bubba/lsp-test + commit: e251176a4b2ff4dead7846fe5d0a4e1dbea69fd4 flags: {} extra-package-dbs: [] diff --git a/stack-8.8.2.yaml b/stack-8.8.2.yaml index e985c892d..6ee882d7e 100644 --- a/stack-8.8.2.yaml +++ b/stack-8.8.2.yaml @@ -3,8 +3,15 @@ resolver: nightly-2020-01-31 packages: - '.' - ./haskell-lsp-types +- ./func-test extra-deps: +- dependent-map-0.4.0.0@sha256:ca2b131046f4340a1c35d138c5a003fe4a5be96b14efc26291ed35fd08c62221,1657 +- dependent-sum-template-0.1.0.3@sha256:0bbbacdfbd3abf2a15aaf0cf2c27e5bdd159b519441fec39e1e6f2f54424adde,1682 +- constraints-extras-0.3.0.2@sha256:013b8d0392582c6ca068e226718a4fe8be8e22321cc0634f6115505bf377ad26,1853 +- dependent-sum-0.7.1.0@sha256:5599aa89637db434431b1dd3fa7c34bc3d565ee44f0519bfbc877be1927c2531,2068 +- github: bubba/lsp-test + commit: e251176a4b2ff4dead7846fe5d0a4e1dbea69fd4 flags: {} extra-package-dbs: [] diff --git a/test/CapabilitiesSpec.hs b/test/CapabilitiesSpec.hs index 10d130ce2..59bac99a9 100644 --- a/test/CapabilitiesSpec.hs +++ b/test/CapabilitiesSpec.hs @@ -1,5 +1,6 @@ module CapabilitiesSpec where +import Language.Haskell.LSP.Types import Language.Haskell.LSP.Types.Capabilities import Test.Hspec diff --git a/test/DiagnosticsSpec.hs b/test/DiagnosticsSpec.hs index 3e5d7bcca..43921934e 100644 --- a/test/DiagnosticsSpec.hs +++ b/test/DiagnosticsSpec.hs @@ -205,8 +205,8 @@ diagnosticsSpec = do ] uri = J.toNormalizedUri $ J.Uri "uri" let ds = updateDiagnostics HM.empty uri (Just 1) (partitionBySource diags) - (getDiagnosticParamsFor 10 ds uri) `shouldBe` - Just (J.PublishDiagnosticsParams (J.fromNormalizedUri uri) (J.List $ reverse diags)) + getDiagnosticParamsFor 10 ds uri `shouldBe` + Just (J.PublishDiagnosticsParams (J.fromNormalizedUri uri) (Just 1) (J.List $ reverse diags)) -- --------------------------------- @@ -222,15 +222,15 @@ diagnosticsSpec = do ] uri = J.toNormalizedUri $ J.Uri "uri" let ds = updateDiagnostics HM.empty uri (Just 1) (partitionBySource diags) - (getDiagnosticParamsFor 2 ds uri) `shouldBe` - Just (J.PublishDiagnosticsParams (J.fromNormalizedUri uri) + getDiagnosticParamsFor 2 ds uri `shouldBe` + Just (J.PublishDiagnosticsParams (J.fromNormalizedUri uri) (Just 1) (J.List [ mkDiagnostic (Just "ghcmod") "d" , mkDiagnostic (Just "hlint") "c" ])) - (getDiagnosticParamsFor 1 ds uri) `shouldBe` - Just (J.PublishDiagnosticsParams (J.fromNormalizedUri uri) + getDiagnosticParamsFor 1 ds uri `shouldBe` + Just (J.PublishDiagnosticsParams (J.fromNormalizedUri uri) (Just 1) (J.List [ mkDiagnostic (Just "ghcmod") "d" ])) @@ -249,8 +249,8 @@ diagnosticsSpec = do ] uri = J.toNormalizedUri $ J.Uri "uri" let ds = updateDiagnostics HM.empty uri (Just 1) (partitionBySource diags) - (getDiagnosticParamsFor 100 ds uri) `shouldBe` - Just (J.PublishDiagnosticsParams (J.fromNormalizedUri uri) + getDiagnosticParamsFor 100 ds uri `shouldBe` + Just (J.PublishDiagnosticsParams (J.fromNormalizedUri uri) (Just 1) (J.List [ mkDiagnostic (Just "ghcmod") "d" , mkDiagnostic (Just "hlint") "c" @@ -259,8 +259,8 @@ diagnosticsSpec = do ])) let ds' = flushBySource ds (Just "hlint") - (getDiagnosticParamsFor 100 ds' uri) `shouldBe` - Just (J.PublishDiagnosticsParams (J.fromNormalizedUri uri) + getDiagnosticParamsFor 100 ds' uri `shouldBe` + Just (J.PublishDiagnosticsParams (J.fromNormalizedUri uri) (Just 1) (J.List [ mkDiagnostic (Just "ghcmod") "d" , mkDiagnostic2 (Just "ghcmod") "b" diff --git a/test/InitialConfigurationSpec.hs b/test/InitialConfigurationSpec.hs deleted file mode 100644 index 712254307..000000000 --- a/test/InitialConfigurationSpec.hs +++ /dev/null @@ -1,66 +0,0 @@ -{-# LANGUAGE OverloadedStrings #-} - -module InitialConfigurationSpec where - -import Control.Concurrent.MVar -import Control.Concurrent.STM -import Data.Aeson -import Data.Default -import Language.Haskell.LSP.Capture -import Language.Haskell.LSP.Core -import Language.Haskell.LSP.Types -import Language.Haskell.LSP.VFS -import Language.Haskell.LSP.Types.Capabilities -import Test.Hspec - -spec :: Spec -spec = - describe "initial configuration" $ it "stores initial configuration data" $ initVFS $ \vfs -> do - - lfVar <- newEmptyMVar - - let - initialConfigHandler (RequestMessage _ _ Initialize InitializeParams{_initializationOptions = Just opts}) = - case (fromJSON opts :: Result String) of - Success s -> Right s - _ -> Left "Could not decode configuration" - initialConfigHandler _ = - error "Got the wrong request for the onInitialConfiguration callback" - - initCb :: InitializeCallbacks String - initCb = InitializeCallbacks - initialConfigHandler - (const $ Left "") - (\lf -> putMVar lfVar lf >> return Nothing) - - handlers = def - - tvarLspId <- newTVarIO 0 - tvarCtx <- newTVarIO $ defaultLanguageContextData handlers - def - undefined - tvarLspId - (const $ return ()) - noCapture - vfs - - let putMsg msg = - let jsonStr = encode msg in handleMessage initCb tvarCtx jsonStr - - let - initParams = InitializeParams - Nothing - Nothing - (Just (Uri "/foo")) - (Just (Data.Aeson.String "configuration")) - fullCaps - Nothing - Nothing - - initMsg :: InitializeRequest - initMsg = RequestMessage "2.0" (IdInt 0) Initialize initParams - - putMsg initMsg - contents <- readTVarIO tvarCtx - resConfig contents `shouldBe` Just "configuration" - diff --git a/test/JsonSpec.hs b/test/JsonSpec.hs index 43bdd7392..ec2addee6 100644 --- a/test/JsonSpec.hs +++ b/test/JsonSpec.hs @@ -1,3 +1,6 @@ +{-# LANGUAGE UndecidableInstances #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE PolyKinds #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE OverloadedStrings #-} @@ -42,10 +45,10 @@ jsonSpec = do prop "HoverContents" (propertyJsonRoundtrip :: HoverContents -> Property) prop "ResponseError" (propertyJsonRoundtrip :: ResponseError -> Property) prop "WatchedFiles" (propertyJsonRoundtrip :: DidChangeWatchedFilesRegistrationOptions -> Property) - prop "ResponseMessage ()" - (propertyJsonRoundtrip :: ResponseMessage () -> Property) - prop "ResponseMessage JSON value" - (propertyJsonRoundtrip :: ResponseMessage J.Value -> Property) + prop "ResponseMessage Initialize" + (propertyJsonRoundtrip :: ResponseMessage 'TextDocumentHover -> Property) + -- prop "ResponseMessage JSON value" + -- (propertyJsonRoundtrip :: ResponseMessage J.Value -> Property) describe "JSON decoding regressions" $ it "CompletionItem" $ (J.decode "{\"jsonrpc\":\"2.0\",\"result\":[{\"label\":\"raisebox\"}],\"id\":1}" :: Maybe CompletionResponse) @@ -58,17 +61,17 @@ responseMessageSpec = do it "decodes result = null" $ do let input = "{\"jsonrpc\": \"2.0\", \"id\": 123, \"result\": null}" in J.decode input `shouldBe` Just - (ResponseMessage "2.0" (IdRspInt 123) (Right J.Null)) + ((ResponseMessage "2.0" (Just (IdInt 123)) (Right J.Null)) :: ResponseMessage 'WorkspaceExecuteCommand) describe "invalid JSON" $ do it "throws if neither result nor error is present" $ do - (J.eitherDecode "{\"jsonrpc\":\"2.0\",\"id\":1}" :: Either String (ResponseMessage ())) - `shouldBe` Left ("Error in $: Both error and result cannot be Nothing") + (J.eitherDecode "{\"jsonrpc\":\"2.0\",\"id\":1}" :: Either String (ResponseMessage 'Initialize)) + `shouldBe` Left ("Error in $: both error and result cannot be Nothing") it "throws if both result and error are present" $ do (J.eitherDecode - "{\"jsonrpc\":\"2.0\",\"id\": 1,\"result\":1,\"error\":{\"code\":-32700,\"message\":\"\",\"data\":null}}" - :: Either String (ResponseMessage Int)) + "{\"jsonrpc\":\"2.0\",\"id\": 1,\"result\":{\"capabilities\": {}},\"error\":{\"code\":-32700,\"message\":\"\",\"data\":null}}" + :: Either String (ResponseMessage 'Initialize)) `shouldSatisfy` - (either (\err -> isPrefixOf "Error in $: Both error and result cannot be present" err) (\_ -> False)) + (either (\err -> "Error in $: both error and result cannot be present" `isPrefixOf` err) (\_ -> False)) -- --------------------------------------------------------------------- @@ -94,7 +97,22 @@ instance Arbitrary HoverContents where , HoverContents <$> arbitrary ] -instance Arbitrary a => Arbitrary (ResponseMessage a) where +instance Arbitrary Uri where + arbitrary = Uri <$> arbitrary + +instance Arbitrary Position where + arbitrary = Position <$> arbitrary <*> arbitrary + +instance Arbitrary Location where + arbitrary = Location <$> arbitrary <*> arbitrary + +instance Arbitrary Range where + arbitrary = Range <$> arbitrary <*> arbitrary + +instance Arbitrary Hover where + arbitrary = Hover <$> arbitrary <*> arbitrary + +instance Arbitrary (ResponseParams m) => Arbitrary (ResponseMessage m) where arbitrary = oneof [ ResponseMessage @@ -107,8 +125,8 @@ instance Arbitrary a => Arbitrary (ResponseMessage a) where <*> (Left <$> arbitrary) ] -instance Arbitrary LspIdRsp where - arbitrary = oneof [IdRspInt <$> arbitrary, IdRspString <$> arbitrary, pure IdRspNull] +instance Arbitrary (LspId m) where + arbitrary = oneof [IdInt <$> arbitrary, IdString <$> arbitrary] instance Arbitrary ResponseError where arbitrary = ResponseError <$> arbitrary <*> arbitrary <*> pure Nothing diff --git a/test/MethodSpec.hs b/test/MethodSpec.hs index 284869f50..2d5b5854a 100644 --- a/test/MethodSpec.hs +++ b/test/MethodSpec.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE OverloadedStrings, DataKinds #-} module MethodSpec where @@ -79,12 +79,12 @@ diagnosticsSpec = do describe "Client Methods" $ do it "maintains roundtrip consistency" $ do forM_ clientMethods $ \m -> do - (J.toJSON <$> (J.fromJSON (J.String m) :: J.Result J.ClientMethod)) + (J.toJSON <$> (J.fromJSON (J.String m) :: J.Result (J.SomeClientMethod))) `shouldBe` (J.Success $ J.String m) describe "Server Methods" $ do it "maintains roundtrip consistency" $ do forM_ serverMethods $ \m -> do - (J.toJSON <$> (J.fromJSON (J.String m) :: J.Result J.ServerMethod)) + (J.toJSON <$> (J.fromJSON (J.String m) :: J.Result (J.SomeServerMethod))) `shouldBe` (J.Success $ J.String m) -- --------------------------------- diff --git a/test/ServerCapabilitiesSpec.hs b/test/ServerCapabilitiesSpec.hs index c3e3c0550..a31a9a383 100644 --- a/test/ServerCapabilitiesSpec.hs +++ b/test/ServerCapabilitiesSpec.hs @@ -1,13 +1,10 @@ -{-# LANGUAGE CPP #-} {-# LANGUAGE OverloadedStrings #-} module ServerCapabilitiesSpec where import Control.Lens.Operators import Data.Aeson -#if __GLASGOW_HASKELL__ < 808 -import Data.Monoid ((<>)) -#endif import Language.Haskell.LSP.Types +import Language.Haskell.LSP.Types.Capabilities import Language.Haskell.LSP.Types.Lens import Test.Hspec @@ -17,20 +14,20 @@ spec = describe "server capabilities" $ do describe "decodes" $ do it "just id" $ let input = "{\"id\": \"abc123\"}" - in decode input `shouldBe` Just (FoldingRangeOptionsDynamicDocument Nothing (Just "abc123")) + in decode input `shouldBe` Just (FoldingRangeRegistrationOptions Nothing Nothing (Just "abc123")) it "id and document selector" $ let input = "{\"id\": \"foo\", \"documentSelector\": " <> documentFiltersJson <> "}" - in decode input `shouldBe` Just (FoldingRangeOptionsDynamicDocument (Just documentFilters) (Just "foo")) + in decode input `shouldBe` Just (FoldingRangeRegistrationOptions (Just documentFilters) Nothing (Just "foo")) it "static boolean" $ let input = "true" - in decode input `shouldBe` Just (FoldingRangeOptionsStatic True) + in decode input `shouldBe` Just True describe "encodes" $ it "just id" $ - encode (FoldingRangeOptionsDynamicDocument Nothing (Just "foo")) `shouldBe` "{\"id\":\"foo\"}" + encode (FoldingRangeRegistrationOptions Nothing Nothing (Just "foo")) `shouldBe` "{\"id\":\"foo\"}" it "decodes" $ let input = "{\"hoverProvider\": true, \"colorProvider\": {\"id\": \"abc123\", \"documentSelector\": " <> documentFiltersJson <> "}}" - Just caps = decode input :: Maybe InitializeResponseCapabilitiesInner - in caps ^. colorProvider `shouldBe` Just (ColorOptionsDynamicDocument (Just documentFilters) (Just "abc123")) + Just caps = decode input :: Maybe ServerCapabilities + in caps ^. colorProvider `shouldBe` Just (InR $ InR $ DocumentColorRegistrationOptions (Just documentFilters) (Just "abc123") Nothing) where documentFilters = List [DocumentFilter (Just "haskell") Nothing Nothing] documentFiltersJson = "[{\"language\": \"haskell\"}]" diff --git a/test/TypesSpec.hs b/test/TypesSpec.hs index 67501bea4..3574e5269 100644 --- a/test/TypesSpec.hs +++ b/test/TypesSpec.hs @@ -1,10 +1,6 @@ -{-# LANGUAGE CPP #-} {-# LANGUAGE OverloadedStrings #-} module TypesSpec where -#if __GLASGOW_HASKELL__ < 808 -import Data.Monoid ((<>)) -#endif import qualified Language.Haskell.LSP.Types as J import Test.Hspec diff --git a/test/URIFilePathSpec.hs b/test/URIFilePathSpec.hs index 8726ca51d..9c2a1068b 100644 --- a/test/URIFilePathSpec.hs +++ b/test/URIFilePathSpec.hs @@ -1,21 +1,14 @@ -{-# LANGUAGE CPP #-} {-# LANGUAGE OverloadedStrings #-} module URIFilePathSpec where import Control.Monad (when) import Data.List -#if __GLASGOW_HASKELL__ < 808 -import Data.Monoid ((<>)) -#endif import Data.Text (Text, pack) import Language.Haskell.LSP.Types import Network.URI import Test.Hspec import Test.QuickCheck -#if !MIN_VERSION_QuickCheck(2,10,0) -import Data.Char (GeneralCategory(..), generalCategory) -#endif import qualified System.FilePath.Windows as FPW import System.FilePath (normalise) import qualified System.Info @@ -255,14 +248,6 @@ genValidUnicodeChar :: Gen Char genValidUnicodeChar = arbitraryUnicodeChar `suchThat` isCharacter where isCharacter x = x /= '\65534' && x /= '\65535' -#if !MIN_VERSION_QuickCheck(2,10,0) -arbitraryUnicodeChar :: Gen Char -arbitraryUnicodeChar = - arbitraryBoundedEnum `suchThat` (not . isSurrogate) - where - isSurrogate c = generalCategory c == Surrogate -#endif - normalizedFilePathSpec :: Spec normalizedFilePathSpec = do it "makes file path normalized" $ property $ forAll genFilePath $ \fp -> do diff --git a/test/WorkspaceFoldersSpec.hs b/test/WorkspaceFoldersSpec.hs deleted file mode 100644 index f57a79025..000000000 --- a/test/WorkspaceFoldersSpec.hs +++ /dev/null @@ -1,77 +0,0 @@ -{-# LANGUAGE OverloadedStrings #-} - -module WorkspaceFoldersSpec where - -import Control.Concurrent.MVar -import Control.Concurrent.STM -import Data.Aeson -import Data.Default -import Language.Haskell.LSP.Capture -import Language.Haskell.LSP.Core -import Language.Haskell.LSP.Types -import Language.Haskell.LSP.VFS -import Language.Haskell.LSP.Types.Capabilities -import Test.Hspec - -spec :: Spec -spec = - describe "workspace folders" $ it "keeps track of open workspace folders" $ initVFS $ \vfs -> do - - lfVar <- newEmptyMVar - - let initCb :: InitializeCallbacks () - initCb = InitializeCallbacks - (const $ Left "") - (const $ Left "") - (\lf -> putMVar lfVar lf >> return Nothing) - handlers = def - - tvarLspId <- newTVarIO 0 - tvarCtx <- newTVarIO $ defaultLanguageContextData handlers - def - undefined - tvarLspId - (const $ return ()) - noCapture - vfs - - let putMsg msg = - let jsonStr = encode msg - in handleMessage initCb tvarCtx jsonStr - - let starterWorkspaces = List [wf0] - initParams = InitializeParams - Nothing Nothing (Just (Uri "/foo")) Nothing fullCaps Nothing (Just starterWorkspaces) - initMsg :: InitializeRequest - initMsg = RequestMessage "2.0" (IdInt 0) Initialize initParams - - putMsg initMsg - - firstWorkspaces <- readMVar lfVar >>= getWorkspaceFolders - firstWorkspaces `shouldBe` Just [wf0] - - - putMsg (makeNotif [wf1] []) - readMVar lfVar >>= \lf -> do - Just wfs <- getWorkspaceFolders lf - wfs `shouldContain` [wf1] - wfs `shouldContain` [wf0] - - putMsg (makeNotif [wf2] [wf1]) - readMVar lfVar >>= \lf -> do - Just wfs <- getWorkspaceFolders lf - wfs `shouldNotContain` [wf1] - wfs `shouldContain` [wf0] - wfs `shouldContain` [wf2] - - where - wf0 = WorkspaceFolder "one" "Starter workspace" - wf1 = WorkspaceFolder "/foo/bar" "My workspace" - wf2 = WorkspaceFolder "/foo/baz" "My other workspace" - - makeNotif add rmv = - let addedFolders = List add - removedFolders = List rmv - ev = WorkspaceFoldersChangeEvent addedFolders removedFolders - ps = DidChangeWorkspaceFoldersParams ev - in NotificationMessage "2.0" WorkspaceDidChangeWorkspaceFolders ps