Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Ide.Types
Synopsis
- data PluginDescriptor (ideState :: Type) = PluginDescriptor {
- pluginId :: !PluginId
- pluginPriority :: Natural
- pluginRules :: !(Rules ())
- pluginCommands :: ![PluginCommand ideState]
- pluginHandlers :: PluginHandlers ideState
- pluginConfigDescriptor :: ConfigDescriptor
- pluginNotificationHandlers :: PluginNotificationHandlers ideState
- pluginModifyDynflags :: DynFlagsModifications
- pluginCli :: Maybe (ParserInfo (IdeCommand ideState))
- pluginFileType :: [Text]
- defaultPluginDescriptor :: PluginId -> PluginDescriptor ideState
- defaultCabalPluginDescriptor :: PluginId -> PluginDescriptor ideState
- defaultPluginPriority :: Natural
- newtype IdeCommand state = IdeCommand (state -> IO ())
- data IdeMethod (m :: Method ClientToServer Request) = PluginRequestMethod m => IdeMethod (SMethod m)
- data IdeNotification (m :: Method ClientToServer Notification) = PluginNotificationMethod m => IdeNotification (SMethod m)
- data IdePlugins ideState where
- pattern IdePlugins :: [PluginDescriptor ideState] -> IdePlugins ideState
- data DynFlagsModifications = DynFlagsModifications {
- dynFlagsModifyGlobal :: DynFlags -> DynFlags
- dynFlagsModifyParser :: DynFlags -> DynFlags
- data Config = Config {
- checkParents :: CheckParents
- checkProject :: !Bool
- formattingProvider :: !Text
- cabalFormattingProvider :: !Text
- maxCompletions :: !Int
- plugins :: !(Map PluginId PluginConfig)
- data PluginConfig = PluginConfig {
- plcGlobalOn :: !Bool
- plcCallHierarchyOn :: !Bool
- plcCodeActionsOn :: !Bool
- plcCodeLensOn :: !Bool
- plcDiagnosticsOn :: !Bool
- plcHoverOn :: !Bool
- plcSymbolsOn :: !Bool
- plcCompletionOn :: !Bool
- plcRenameOn :: !Bool
- plcSelectionRangeOn :: !Bool
- plcFoldingRangeOn :: !Bool
- plcConfig :: !Object
- data CheckParents
- data ConfigDescriptor = ConfigDescriptor {}
- defaultConfigDescriptor :: ConfigDescriptor
- configForPlugin :: Config -> PluginDescriptor c -> PluginConfig
- pluginEnabledConfig :: (PluginConfig -> Bool) -> PluginConfig -> Bool
- data CustomConfig = forall r. CustomConfig (Properties r)
- mkCustomConfig :: Properties r -> CustomConfig
- data FallbackCodeActionParams = FallbackCodeActionParams {
- fallbackWorkspaceEdit :: Maybe WorkspaceEdit
- fallbackCommand :: Maybe Command
- data FormattingType
- type FormattingMethod m = (HasOptions (MessageParams m) FormattingOptions, HasTextDocument (MessageParams m) TextDocumentIdentifier, MessageResult m ~ ([TextEdit] |? Null))
- type FormattingHandler a = a -> FormattingType -> Text -> NormalizedFilePath -> FormattingOptions -> ExceptT PluginError (LspM Config) ([TextEdit] |? Null)
- mkFormattingHandlers :: forall a. FormattingHandler a -> PluginHandlers a
- class HasTracing a where
- traceWithSpan :: SpanInFlight -> a -> IO ()
- data PluginCommand ideState = forall a.FromJSON a => PluginCommand {
- commandId :: CommandId
- commandDesc :: Text
- commandFunc :: CommandFunction ideState a
- newtype CommandId = CommandId Text
- type CommandFunction ideState a = ideState -> a -> ExceptT PluginError (LspM Config) (Value |? Null)
- mkLspCommand :: PluginId -> CommandId -> Text -> Maybe [Value] -> Command
- mkLspCmdId :: Text -> PluginId -> CommandId -> Text
- newtype PluginId = PluginId Text
- newtype PluginHandler a (m :: Method ClientToServer Request) = PluginHandler (PluginId -> a -> MessageParams m -> LspM Config (NonEmpty (Either PluginError (MessageResult m))))
- mkPluginHandler :: forall ideState m. PluginRequestMethod m => SClientMethod m -> PluginMethodHandler ideState m -> PluginHandlers ideState
- newtype PluginHandlers a = PluginHandlers (DMap IdeMethod (PluginHandler a))
- class HasTracing (MessageParams m) => PluginMethod (k :: MessageKind) (m :: Method ClientToServer k) where
- pluginEnabled :: SMethod m -> MessageParams m -> PluginDescriptor c -> Config -> Bool
- type PluginMethodHandler a m = a -> PluginId -> MessageParams m -> ExceptT PluginError (LspM Config) (MessageResult m)
- newtype PluginNotificationHandler a (m :: Method ClientToServer Notification) = PluginNotificationHandler (PluginId -> a -> VFS -> MessageParams m -> LspM Config ())
- mkPluginNotificationHandler :: PluginNotificationMethod m => SClientMethod (m :: Method ClientToServer Notification) -> PluginNotificationMethodHandler ideState m -> PluginNotificationHandlers ideState
- newtype PluginNotificationHandlers a = PluginNotificationHandlers (DMap IdeNotification (PluginNotificationHandler a))
- class PluginMethod Request m => PluginRequestMethod (m :: Method ClientToServer Request) where
- combineResponses :: SMethod m -> Config -> ClientCapabilities -> MessageParams m -> NonEmpty (MessageResult m) -> MessageResult m
- getProcessID :: IO Int
- getPid :: IO Text
- installSigUsr1Handler :: IO () -> IO ()
- lookupCommandProvider :: IdePlugins ideState -> CommandId -> Maybe PluginId
- type ResolveFunction ideState a (m :: Method ClientToServer Request) = ideState -> PluginId -> MessageParams m -> Uri -> a -> ExceptT PluginError (LspM Config) (MessageResult m)
- mkResolveHandler :: forall ideState a m. (FromJSON a, PluginRequestMethod m, HasData_ (MessageParams m) (Maybe Value)) => SClientMethod m -> ResolveFunction ideState a m -> PluginHandlers ideState
Documentation
data PluginDescriptor (ideState :: Type) #
Constructors
PluginDescriptor | |
Fields
|
defaultPluginDescriptor :: PluginId -> PluginDescriptor ideState #
Set up a plugin descriptor, initialized with default values.
This plugin descriptor is prepared for haskell
files, such as
.hs
.lhs
.hs-boot
and handlers will be enabled for files with the appropriate file extensions.
defaultCabalPluginDescriptor :: PluginId -> PluginDescriptor ideState #
Set up a plugin descriptor, initialized with default values.
This plugin descriptor is prepared for .cabal
files and as such,
will only respond / run when .cabal
files are currently in scope.
Handles files with the following extensions:
* .cabal
defaultPluginPriority :: Natural #
newtype IdeCommand state #
Constructors
IdeCommand (state -> IO ()) |
Instances
Show (IdeCommand st) # | |
Defined in Ide.Types Methods showsPrec :: Int -> IdeCommand st -> ShowS # show :: IdeCommand st -> String # showList :: [IdeCommand st] -> ShowS # |
data IdeMethod (m :: Method ClientToServer Request) #
Methods which have a PluginMethod instance
Constructors
PluginRequestMethod m => IdeMethod (SMethod m) |
data IdeNotification (m :: Method ClientToServer Notification) #
Methods which have a PluginMethod instance
Constructors
PluginNotificationMethod m => IdeNotification (SMethod m) |
Instances
GCompare IdeNotification # | |
Defined in Ide.Types Methods gcompare :: forall (a :: k) (b :: k). IdeNotification a -> IdeNotification b -> GOrdering a b # | |
GEq IdeNotification # | |
Defined in Ide.Types Methods geq :: forall (a :: k) (b :: k). IdeNotification a -> IdeNotification b -> Maybe (a :~: b) # |
data IdePlugins ideState where #
Bundled Patterns
pattern IdePlugins :: [PluginDescriptor ideState] -> IdePlugins ideState | Smart constructor that deduplicates plugins |
Instances
Monoid (IdePlugins a) # | |
Defined in Ide.Types Methods mempty :: IdePlugins a # mappend :: IdePlugins a -> IdePlugins a -> IdePlugins a # mconcat :: [IdePlugins a] -> IdePlugins a # | |
Semigroup (IdePlugins a) # | |
Defined in Ide.Types Methods (<>) :: IdePlugins a -> IdePlugins a -> IdePlugins a # sconcat :: NonEmpty (IdePlugins a) -> IdePlugins a # stimes :: Integral b => b -> IdePlugins a -> IdePlugins a # |
data DynFlagsModifications #
Hooks for modifying the DynFlags
at different times of the compilation
process. Plugins can install a DynFlagsModifications
via
pluginModifyDynflags
in their PluginDescriptor
.
Constructors
DynFlagsModifications | |
Fields
|
Instances
Monoid DynFlagsModifications # | |
Defined in Ide.Types | |
Semigroup DynFlagsModifications # | |
Defined in Ide.Types Methods (<>) :: DynFlagsModifications -> DynFlagsModifications -> DynFlagsModifications # sconcat :: NonEmpty DynFlagsModifications -> DynFlagsModifications # stimes :: Integral b => b -> DynFlagsModifications -> DynFlagsModifications # |
We (initially anyway) mirror the hie configuration, so that existing clients can simply switch executable and not have any nasty surprises. There will initially be surprises relating to config options being ignored though.
Constructors
Config | |
Fields
|
data PluginConfig #
A PluginConfig is a generic configuration for a given HLS plugin. It provides a "big switch" to turn it on or off as a whole, as well as small switches per feature, and a slot for custom config. This provides a regular naming scheme for all plugin config.
Constructors
PluginConfig | |
Fields
|
Instances
ToJSON PluginConfig # | |
Defined in Ide.Types Methods toJSON :: PluginConfig -> Value # toEncoding :: PluginConfig -> Encoding # toJSONList :: [PluginConfig] -> Value # toEncodingList :: [PluginConfig] -> Encoding # omitField :: PluginConfig -> Bool # | |
Show PluginConfig # | |
Defined in Ide.Types Methods showsPrec :: Int -> PluginConfig -> ShowS # show :: PluginConfig -> String # showList :: [PluginConfig] -> ShowS # | |
Default PluginConfig # | |
Defined in Ide.Types Methods def :: PluginConfig # | |
Eq PluginConfig # | |
Defined in Ide.Types |
data CheckParents #
Constructors
NeverCheck | |
CheckOnSave | |
AlwaysCheck |
Instances
FromJSON CheckParents # | |
Defined in Ide.Types Methods parseJSON :: Value -> Parser CheckParents # parseJSONList :: Value -> Parser [CheckParents] # omittedField :: Maybe CheckParents # | |
ToJSON CheckParents # | |
Defined in Ide.Types Methods toJSON :: CheckParents -> Value # toEncoding :: CheckParents -> Encoding # toJSONList :: [CheckParents] -> Value # toEncodingList :: [CheckParents] -> Encoding # omitField :: CheckParents -> Bool # | |
Generic CheckParents # | |
Defined in Ide.Types Associated Types type Rep CheckParents :: Type -> Type | |
Show CheckParents # | |
Defined in Ide.Types Methods showsPrec :: Int -> CheckParents -> ShowS # show :: CheckParents -> String # showList :: [CheckParents] -> ShowS # | |
Eq CheckParents # | |
Defined in Ide.Types | |
Ord CheckParents # | |
Defined in Ide.Types Methods compare :: CheckParents -> CheckParents -> Ordering (<) :: CheckParents -> CheckParents -> Bool (<=) :: CheckParents -> CheckParents -> Bool (>) :: CheckParents -> CheckParents -> Bool (>=) :: CheckParents -> CheckParents -> Bool max :: CheckParents -> CheckParents -> CheckParents min :: CheckParents -> CheckParents -> CheckParents | |
type Rep CheckParents # | |
Defined in Ide.Types type Rep CheckParents = D1 ('MetaData "CheckParents" "Ide.Types" "hls-plugin-api-2.4.0.0-KJfNpTBJq8lII4el4H2UW6" 'False) (C1 ('MetaCons "NeverCheck" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CheckOnSave" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AlwaysCheck" 'PrefixI 'False) (U1 :: Type -> Type))) |
data ConfigDescriptor #
Describes the configuration of a plugin. A plugin may be configurable as can be seen below:
{ "plugin-id": { "globalOn": true, "codeActionsOn": true, "codeLensOn": true, "config": { "property1": "foo" } } }
globalOn
, codeActionsOn
, and codeLensOn
etc. are called generic configs
which can be inferred from handlers registered by the plugin.
config
is called custom config, which is defined using Properties
.
Constructors
ConfigDescriptor | |
Fields
|
configForPlugin :: Config -> PluginDescriptor c -> PluginConfig #
Lookup the current config for a plugin
pluginEnabledConfig :: (PluginConfig -> Bool) -> PluginConfig -> Bool #
Checks that a given plugin is both enabled and the specific feature is enabled
data CustomConfig #
An existential wrapper of Properties
Constructors
forall r. CustomConfig (Properties r) |
mkCustomConfig :: Properties r -> CustomConfig #
data FallbackCodeActionParams #
Constructors
FallbackCodeActionParams | |
Fields
|
Instances
FromJSON FallbackCodeActionParams # | |
Defined in Ide.Types Methods parseJSON :: Value -> Parser FallbackCodeActionParams # parseJSONList :: Value -> Parser [FallbackCodeActionParams] # omittedField :: Maybe FallbackCodeActionParams # | |
ToJSON FallbackCodeActionParams # | |
Defined in Ide.Types Methods toJSON :: FallbackCodeActionParams -> Value # toEncoding :: FallbackCodeActionParams -> Encoding # toJSONList :: [FallbackCodeActionParams] -> Value # toEncodingList :: [FallbackCodeActionParams] -> Encoding # omitField :: FallbackCodeActionParams -> Bool # | |
Generic FallbackCodeActionParams # | |
Defined in Ide.Types Associated Types type Rep FallbackCodeActionParams :: Type -> Type Methods from :: FallbackCodeActionParams -> Rep FallbackCodeActionParams x to :: Rep FallbackCodeActionParams x -> FallbackCodeActionParams | |
type Rep FallbackCodeActionParams # | |
Defined in Ide.Types type Rep FallbackCodeActionParams = D1 ('MetaData "FallbackCodeActionParams" "Ide.Types" "hls-plugin-api-2.4.0.0-KJfNpTBJq8lII4el4H2UW6" 'False) (C1 ('MetaCons "FallbackCodeActionParams" 'PrefixI 'True) (S1 ('MetaSel ('Just "fallbackWorkspaceEdit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe WorkspaceEdit)) :*: S1 ('MetaSel ('Just "fallbackCommand") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Command)))) |
data FormattingType #
Format the given Text as a whole or only a Range
of it.
Range must be relative to the text to format.
To format the whole document, read the Text from the file and use FormatText
as the FormattingType.
Constructors
FormatText | |
FormatRange Range |
type FormattingMethod m = (HasOptions (MessageParams m) FormattingOptions, HasTextDocument (MessageParams m) TextDocumentIdentifier, MessageResult m ~ ([TextEdit] |? Null)) #
type FormattingHandler a = a -> FormattingType -> Text -> NormalizedFilePath -> FormattingOptions -> ExceptT PluginError (LspM Config) ([TextEdit] |? Null) #
mkFormattingHandlers :: forall a. FormattingHandler a -> PluginHandlers a #
class HasTracing a where #
Minimal complete definition
Nothing
Methods
traceWithSpan :: SpanInFlight -> a -> IO () #
Instances
data PluginCommand ideState #
Constructors
forall a.FromJSON a => PluginCommand | |
Fields
|
type CommandFunction ideState a = ideState -> a -> ExceptT PluginError (LspM Config) (Value |? Null) #
newtype PluginHandler a (m :: Method ClientToServer Request) #
Combine handlers for the
Constructors
PluginHandler (PluginId -> a -> MessageParams m -> LspM Config (NonEmpty (Either PluginError (MessageResult m)))) |
mkPluginHandler :: forall ideState m. PluginRequestMethod m => SClientMethod m -> PluginMethodHandler ideState m -> PluginHandlers ideState #
Make a handler for plugins. For how resolve works with this see Note [Resolve in PluginHandlers]
newtype PluginHandlers a #
Constructors
PluginHandlers (DMap IdeMethod (PluginHandler a)) |
Instances
Monoid (PluginHandlers a) # | |
Defined in Ide.Types Methods mempty :: PluginHandlers a # mappend :: PluginHandlers a -> PluginHandlers a -> PluginHandlers a # mconcat :: [PluginHandlers a] -> PluginHandlers a # | |
Semigroup (PluginHandlers a) # | |
Defined in Ide.Types Methods (<>) :: PluginHandlers a -> PluginHandlers a -> PluginHandlers a # sconcat :: NonEmpty (PluginHandlers a) -> PluginHandlers a # stimes :: Integral b => b -> PluginHandlers a -> PluginHandlers a # |
class HasTracing (MessageParams m) => PluginMethod (k :: MessageKind) (m :: Method ClientToServer k) where #
Methods that can be handled by plugins.
ExtraParams
captures any extra data the IDE passes to the handlers for this method
Only methods for which we know how to combine responses can be instances of PluginMethod
Minimal complete definition
Nothing
Methods
Arguments
:: 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.
default pluginEnabled :: (HasTextDocument (MessageParams m) doc, HasUri doc Uri) => SMethod m -> MessageParams m -> PluginDescriptor c -> Config -> Bool #
Instances
type PluginMethodHandler a m = a -> PluginId -> MessageParams m -> ExceptT PluginError (LspM Config) (MessageResult m) #
newtype PluginNotificationHandler a (m :: Method ClientToServer Notification) #
Constructors
PluginNotificationHandler (PluginId -> a -> VFS -> MessageParams m -> LspM Config ()) |
mkPluginNotificationHandler :: PluginNotificationMethod m => SClientMethod (m :: Method ClientToServer Notification) -> PluginNotificationMethodHandler ideState m -> PluginNotificationHandlers ideState #
Make a handler for plugins with no extra data
newtype PluginNotificationHandlers a #
Constructors
PluginNotificationHandlers (DMap IdeNotification (PluginNotificationHandler a)) |
Instances
Monoid (PluginNotificationHandlers a) # | |
Defined in Ide.Types Methods mempty :: PluginNotificationHandlers a # mappend :: PluginNotificationHandlers a -> PluginNotificationHandlers a -> PluginNotificationHandlers a # mconcat :: [PluginNotificationHandlers a] -> PluginNotificationHandlers a # | |
Semigroup (PluginNotificationHandlers a) # | |
Defined in Ide.Types Methods (<>) :: PluginNotificationHandlers a -> PluginNotificationHandlers a -> PluginNotificationHandlers a # sconcat :: NonEmpty (PluginNotificationHandlers a) -> PluginNotificationHandlers a # stimes :: Integral b => b -> PluginNotificationHandlers a -> PluginNotificationHandlers a # |
class PluginMethod Request m => PluginRequestMethod (m :: Method ClientToServer Request) where #
Minimal complete definition
Nothing
Methods
Arguments
:: SMethod m | |
-> Config | IDE Configuration |
-> ClientCapabilities | |
-> MessageParams m | |
-> NonEmpty (MessageResult m) | |
-> MessageResult m |
How to combine responses from different plugins.
For example, for Hover requests, we might have multiple producers of Hover information. We do not want to decide which one to display to the user but instead allow to define how to merge two hover request responses into one glorious hover box.
However, as sometimes only one handler of a request can realistically exist (such as TextDocumentFormatting), it is safe to just unconditionally report back one arbitrary result (arbitrary since it should only be one anyway).
default combineResponses :: Semigroup (MessageResult m) => SMethod m -> Config -> ClientCapabilities -> MessageParams m -> NonEmpty (MessageResult m) -> MessageResult m #
Instances
getProcessID :: IO Int #
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.
installSigUsr1Handler :: IO () -> IO () #
lookupCommandProvider :: IdePlugins ideState -> CommandId -> Maybe PluginId #
type ResolveFunction ideState a (m :: Method ClientToServer Request) = ideState -> PluginId -> MessageParams m -> Uri -> a -> ExceptT PluginError (LspM Config) (MessageResult m) #
mkResolveHandler :: forall ideState a m. (FromJSON a, PluginRequestMethod m, HasData_ (MessageParams m) (Maybe Value)) => SClientMethod m -> ResolveFunction ideState a m -> PluginHandlers ideState #
Make a handler for resolve methods. In here we take your provided ResolveFunction and turn it into a PluginHandlers. See Note [Resolve in PluginHandlers]