@@ -31,6 +31,7 @@ module Ide.Types
3131, PluginCommand (.. ), CommandId (.. ), CommandFunction , mkLspCommand, mkLspCmdId
3232, PluginId (.. )
3333, PluginHandler (.. ), mkPluginHandler
34+ , PluginM , runPluginM, pluginGetClientCapabilities, pluginGetVirtualFile, pluginGetVersionedTextDoc, pluginSendNotification, pluginSendRequest, pluginWithIndefiniteProgress
3435, PluginHandlers (.. )
3536, PluginMethod (.. )
3637, PluginMethodHandler
@@ -62,6 +63,7 @@ import Control.Lens (_Just, view, (.~), (?~), (^.),
6263 (^?) )
6364import Control.Monad (void )
6465import Control.Monad.Error.Class (MonadError (throwError ))
66+ import Control.Monad.IO.Class (MonadIO )
6567import Control.Monad.Trans.Class (MonadTrans (lift ))
6668import Control.Monad.Trans.Except (ExceptT , runExceptT )
6769import Data.Aeson hiding (Null , defaultOptions )
@@ -94,7 +96,7 @@ import Ide.Plugin.Properties
9496import qualified Language.LSP.Protocol.Lens as L
9597import Language.LSP.Protocol.Message
9698import Language.LSP.Protocol.Types
97- import Language.LSP.Server ( LspM , LspT , getVirtualFile )
99+ import Language.LSP.Server
98100import Language.LSP.VFS
99101import Numeric.Natural
100102import OpenTelemetry.Eventlog
@@ -103,6 +105,7 @@ import Prettyprinter as PP
103105import System.FilePath
104106import System.IO.Unsafe
105107import Text.Regex.TDFA.Text ()
108+ import UnliftIO (MonadUnliftIO )
106109-- ---------------------------------------------------------------------
107110
108111data IdePlugins ideState = IdePlugins_
@@ -890,9 +893,52 @@ instance GEq IdeNotification where
890893instance GCompare IdeNotification where
891894 gcompare (IdeNotification a) (IdeNotification b) = gcompare a b
892895
896+ -- | Restricted version of 'LspM' specific to plugins
897+ newtype PluginM config a = PluginM { _runPluginM :: LspM config a }
898+ deriving newtype (Applicative , Functor , Monad , MonadIO , MonadUnliftIO )
899+
900+ runPluginM :: PluginM config a -> LspM config a
901+ runPluginM = _runPluginM
902+
903+ -- | Wrapper of 'getVirtualFile' for PluginM
904+ --
905+ -- TODO: To be replaced by a lookup of the Shake build graph
906+ pluginGetVirtualFile :: NormalizedUri -> PluginM config (Maybe VirtualFile )
907+ pluginGetVirtualFile uri = PluginM $ getVirtualFile uri
908+
909+ -- | Version of 'getVersionedTextDoc' for PluginM
910+ --
911+ -- TODO: Should use 'pluginGetVirtualFile' instead of wrapping 'getVersionedTextDoc'.
912+ -- At the time of writing, 'pluginGetVirtualFile' of the "lsp" package is implemented with 'getVirtualFile'.
913+ pluginGetVersionedTextDoc :: TextDocumentIdentifier -> PluginM config VersionedTextDocumentIdentifier
914+ pluginGetVersionedTextDoc = PluginM . getVersionedTextDoc
915+
916+ -- | Wrapper of 'getClientCapabilities' for PluginM
917+ pluginGetClientCapabilities :: PluginM config ClientCapabilities
918+ pluginGetClientCapabilities = PluginM getClientCapabilities
919+
920+ -- | Wrapper of 'sendNotification for PluginM
921+ --
922+ -- TODO: Return notification in result instead of calling `sendNotification` directly
923+ pluginSendNotification :: forall (m :: Method ServerToClient Notification ) config . SServerMethod m -> MessageParams m -> PluginM config ()
924+ pluginSendNotification smethod params = PluginM $ sendNotification smethod params
925+
926+ -- | Wrapper of 'sendRequest' for PluginM
927+ --
928+ -- TODO: Return request in result instead of calling `sendRequest` directly
929+ pluginSendRequest :: forall (m :: Method ServerToClient Request ) config . SServerMethod m -> MessageParams m -> (Either (TResponseError m ) (MessageResult m ) -> PluginM config () ) -> PluginM config (LspId m )
930+ pluginSendRequest smethod params action = PluginM $ sendRequest smethod params (runPluginM . action)
931+
932+ -- | Wrapper of 'withIndefiniteProgress' for PluginM
933+ pluginWithIndefiniteProgress :: T. Text -> Maybe ProgressToken -> ProgressCancellable -> ((T. Text -> PluginM config () ) -> PluginM config a ) -> PluginM config a
934+ pluginWithIndefiniteProgress title progressToken cancellable updateAction =
935+ PluginM $
936+ withIndefiniteProgress title progressToken cancellable $ \ putUpdate ->
937+ runPluginM $ updateAction (PluginM . putUpdate)
938+
893939-- | Combine handlers for the
894940newtype PluginHandler a (m :: Method ClientToServer Request )
895- = PluginHandler (PluginId -> a -> MessageParams m -> LspM Config (NonEmpty (Either PluginError (MessageResult m ))))
941+ = PluginHandler (PluginId -> a -> MessageParams m -> PluginM Config (NonEmpty (Either PluginError (MessageResult m ))))
896942
897943newtype PluginNotificationHandler a (m :: Method ClientToServer Notification )
898944 = PluginNotificationHandler (PluginId -> a -> VFS -> MessageParams m -> LspM Config () )
@@ -917,7 +963,7 @@ instance Semigroup (PluginNotificationHandlers a) where
917963instance Monoid (PluginNotificationHandlers a ) where
918964 mempty = PluginNotificationHandlers mempty
919965
920- type PluginMethodHandler a m = a -> PluginId -> MessageParams m -> ExceptT PluginError (LspM Config ) (MessageResult m )
966+ type PluginMethodHandler a m = a -> PluginId -> MessageParams m -> ExceptT PluginError (PluginM Config ) (MessageResult m )
921967
922968type PluginNotificationMethodHandler a m = a -> VFS -> PluginId -> MessageParams m -> LspM Config ()
923969
@@ -930,7 +976,7 @@ mkPluginHandler
930976 -> PluginHandlers ideState
931977mkPluginHandler m f = PluginHandlers $ DMap. singleton (IdeMethod m) (PluginHandler (f' m))
932978 where
933- f' :: SMethod m -> PluginId -> ideState -> MessageParams m -> LspT Config IO (NonEmpty (Either PluginError (MessageResult m )))
979+ f' :: SMethod m -> PluginId -> ideState -> MessageParams m -> PluginM Config (NonEmpty (Either PluginError (MessageResult m )))
934980 -- We need to have separate functions for each method that supports resolve, so far we only support CodeActions
935981 -- CodeLens, and Completion methods.
936982 f' SMethod_TextDocumentCodeAction pid ide params@ CodeActionParams {_textDocument= TextDocumentIdentifier {_uri}} =
@@ -1034,7 +1080,7 @@ type CommandFunction ideState a
10341080 = ideState
10351081 -> Maybe ProgressToken
10361082 -> a
1037- -> ExceptT PluginError (LspM Config ) (Value |? Null )
1083+ -> ExceptT PluginError (PluginM Config ) (Value |? Null )
10381084
10391085-- ---------------------------------------------------------------------
10401086
@@ -1044,7 +1090,7 @@ type ResolveFunction ideState a (m :: Method ClientToServer Request) =
10441090 -> MessageParams m
10451091 -> Uri
10461092 -> a
1047- -> ExceptT PluginError (LspM Config ) (MessageResult m )
1093+ -> ExceptT PluginError (PluginM Config ) (MessageResult m )
10481094
10491095-- | Make a handler for resolve methods. In here we take your provided ResolveFunction
10501096-- and turn it into a PluginHandlers. See Note [Resolve in PluginHandlers]
@@ -1126,7 +1172,7 @@ type FormattingHandler a
11261172 -> T. Text
11271173 -> NormalizedFilePath
11281174 -> FormattingOptions
1129- -> ExceptT PluginError (LspM Config ) ([TextEdit ] |? Null )
1175+ -> ExceptT PluginError (PluginM Config ) ([TextEdit ] |? Null )
11301176
11311177mkFormattingHandlers :: forall a . FormattingHandler a -> PluginHandlers a
11321178mkFormattingHandlers f = mkPluginHandler SMethod_TextDocumentFormatting ( provider SMethod_TextDocumentFormatting )
@@ -1135,7 +1181,7 @@ mkFormattingHandlers f = mkPluginHandler SMethod_TextDocumentFormatting ( provid
11351181 provider :: forall m . FormattingMethod m => SMethod m -> PluginMethodHandler a m
11361182 provider m ide _pid params
11371183 | Just nfp <- uriToNormalizedFilePath $ toNormalizedUri uri = do
1138- mf <- lift $ getVirtualFile $ toNormalizedUri uri
1184+ mf <- lift $ pluginGetVirtualFile $ toNormalizedUri uri -- TODO(awjchen): we don't want to get this from the VFS. we want to get this from the "shake graph"
11391185 case mf of
11401186 Just vf -> do
11411187 let (typ, mtoken) = case m of
0 commit comments