Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- normalize :: Range -> Range
- extendNextLine :: Range -> Range
- extendLineStart :: Range -> Range
- extendToFullLines :: Range -> Range
- data WithDeletions
- getProcessID :: IO Int
- makeDiffTextEdit :: Text -> Text -> [TextEdit]
- makeDiffTextEditAdditive :: Text -> Text -> [TextEdit]
- diffText :: ClientCapabilities -> (VersionedTextDocumentIdentifier, Text) -> Text -> WithDeletions -> WorkspaceEdit
- diffText' :: Bool -> (VersionedTextDocumentIdentifier, Text) -> Text -> WithDeletions -> WorkspaceEdit
- pluginDescToIdePlugins :: [PluginDescriptor ideState] -> IdePlugins ideState
- idePluginsToPluginDesc :: IdePlugins ideState -> [PluginDescriptor ideState]
- getClientConfig :: MonadLsp Config m => m Config
- getPluginConfig :: MonadLsp Config m => PluginDescriptor c -> m PluginConfig
- configForPlugin :: Config -> PluginDescriptor c -> PluginConfig
- pluginEnabled :: PluginMethod k m => SMethod m -> MessageParams m -> PluginDescriptor c -> Config -> Bool
- extractTextInRange :: Range -> Text -> Text
- fullRange :: Text -> Range
- mkLspCommand :: PluginId -> CommandId -> Text -> Maybe [Value] -> Command
- mkLspCmdId :: Text -> PluginId -> CommandId -> Text
- getPid :: IO Text
- allLspCmdIds :: Text -> [(PluginId, [PluginCommand ideState])] -> [Text]
- allLspCmdIds' :: Text -> IdePlugins ideState -> [Text]
- installSigUsr1Handler :: IO () -> IO ()
- subRange :: Range -> Range -> Bool
- positionInRange :: Position -> Range -> Bool
- usePropertyLsp :: (HasProperty s k t r, MonadLsp Config m) => KeyNameProxy s -> PluginDescriptor c -> Properties r -> m (ToHsType t)
- unescape :: Text -> Text
LSP Range manipulation functions
normalize :: Range -> Range Source #
Extend to the line below and above to replace newline character.
>>>
normalize (Range (Position 5 5) (Position 5 10))
Range (Position 5 0) (Position 6 0)
extendNextLine :: Range -> Range Source #
Extend Range
to the start of the next line.
>>>
extendNextLine (Range (Position 5 5) (Position 5 10))
Range (Position 5 5) (Position 6 0)
extendLineStart :: Range -> Range Source #
Extend Range
to the start of the current line.
>>>
extendLineStart (Range (Position 5 5) (Position 5 10))
Range (Position 5 0) (Position 5 10)
extendToFullLines :: Range -> Range Source #
Extend Range
to include the start of the first line and start of the next line of the last line.
Caveat: It always extend the last line to the beginning of next line, even when the last position is at column 0.
This is to keep the compatibility with the implementation of old function extractRange
.
>>>
extendToFullLines (Range (Position 5 5) (Position 5 10))
Range (Position 5 0) (Position 6 0)
>>>
extendToFullLines (Range (Position 5 5) (Position 7 2))
Range (Position 5 0) (Position 8 0)
>>>
extendToFullLines (Range (Position 5 5) (Position 7 0))
Range (Position 5 0) (Position 8 0)
data WithDeletions Source #
Instances
Eq WithDeletions Source # | |
Defined in Ide.PluginUtils (==) :: WithDeletions -> WithDeletions -> Bool # (/=) :: WithDeletions -> WithDeletions -> Bool # |
getProcessID :: IO Int Source #
diffText :: ClientCapabilities -> (VersionedTextDocumentIdentifier, Text) -> Text -> WithDeletions -> WorkspaceEdit Source #
Generate a WorkspaceEdit
value from a pair of source Text
diffText' :: Bool -> (VersionedTextDocumentIdentifier, Text) -> Text -> WithDeletions -> WorkspaceEdit Source #
A pure version of diffText
for testing
pluginDescToIdePlugins :: [PluginDescriptor ideState] -> IdePlugins ideState Source #
idePluginsToPluginDesc :: IdePlugins ideState -> [PluginDescriptor ideState] Source #
getClientConfig :: MonadLsp Config m => m Config Source #
Returns the current client configuration. It is not wise to permanently cache the returned value of this function, as clients can at runtime change their configuration.
getPluginConfig :: MonadLsp Config m => PluginDescriptor c -> m PluginConfig Source #
Returns the current plugin configuration. It is not wise to permanently cache the returned value of this function, as clients can change their configuration at runtime.
configForPlugin :: Config -> PluginDescriptor c -> PluginConfig Source #
Lookup the current config for a plugin
:: PluginMethod k m | |
=> SMethod m | Method type. |
-> MessageParams m | Whether a plugin is enabled might depend on the message parameters
e.g. |
-> PluginDescriptor c | Contains meta information such as PluginId and which file types this plugin is able to handle. |
-> Config | Generic config description, expected to contain |
-> Bool | Is this plugin enabled and allowed to respond to the given request with the given parameters? |
Parse the configuration to check if this plugin is enabled. Perform sanity checks on the message to see whether the plugin is enabled for this message in particular. If a plugin is not enabled, its handlers, commands, etc. will not be run for the given message.
Semantically, this method describes whether a plugin is enabled configuration wise and is allowed to respond to the message. This might depend on the URI that is associated to the Message Parameters. There are requests with no associated URI that, consequentially, cannot inspect the URI.
A common reason why a plugin might not be allowed to respond although it is enabled: * The plugin cannot handle requests associated with the specific URI * Since the implementation of cabal plugins HLS knows plugins specific to Haskell and specific to Cabal file descriptions
Strictly speaking, we are conflating two concepts here: * Dynamically enabled (e.g. on a per-message basis) * Statically enabled (e.g. by configuration in the lsp-client) * Strictly speaking, this might also change dynamically
But there is no use to split it up into two different methods for now.
Get the operating system process id for the running server instance. This should be the same for the lifetime of the instance, and different from that of any other currently running instance.
allLspCmdIds :: Text -> [(PluginId, [PluginCommand ideState])] -> [Text] Source #
allLspCmdIds' :: Text -> IdePlugins ideState -> [Text] Source #
installSigUsr1Handler :: IO () -> IO () Source #
positionInRange :: Position -> Range -> Bool #
positionInRange
returns true if the given Position
is in the Range
.
usePropertyLsp :: (HasProperty s k t r, MonadLsp Config m) => KeyNameProxy s -> PluginDescriptor c -> Properties r -> m (ToHsType t) Source #
Returns the value of a property defined by the current plugin.