| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Ide.Types
Synopsis
- newtype IdePlugins ideState = IdePlugins {- ipMap :: [(PluginId, PluginDescriptor ideState)]
 
- data DynFlagsModifications = DynFlagsModifications {}
- newtype IdeCommand state = IdeCommand (state -> IO ())
- data PluginDescriptor ideState = PluginDescriptor {- pluginId :: !PluginId
- pluginRules :: !(Rules ())
- pluginCommands :: ![PluginCommand ideState]
- pluginHandlers :: PluginHandlers ideState
- pluginConfigDescriptor :: ConfigDescriptor
- pluginNotificationHandlers :: PluginNotificationHandlers ideState
- pluginModifyDynflags :: DynFlagsModifications
- pluginCli :: Maybe (ParserInfo (IdeCommand ideState))
 
- data CustomConfig = forall r. CustomConfig (Properties r)
- data ConfigDescriptor = ConfigDescriptor {}
- mkCustomConfig :: Properties r -> CustomConfig
- defaultConfigDescriptor :: ConfigDescriptor
- class HasTracing (MessageParams m) => PluginMethod m where- pluginEnabled :: SMethod m -> PluginId -> Config -> Bool
- combineResponses :: SMethod m -> Config -> ClientCapabilities -> MessageParams m -> NonEmpty (ResponseResult m) -> ResponseResult m
 
- data IdeMethod (m :: Method FromClient Request) = PluginMethod m => IdeMethod (SMethod m)
- data IdeNotification (m :: Method FromClient Notification) = HasTracing (MessageParams m) => IdeNotification (SMethod m)
- newtype PluginHandler a (m :: Method FromClient Request) = PluginHandler (PluginId -> a -> MessageParams m -> LspM Config (NonEmpty (Either ResponseError (ResponseResult m))))
- newtype PluginNotificationHandler a (m :: Method FromClient Notification) = PluginNotificationHandler (PluginId -> a -> VFS -> MessageParams m -> LspM Config ())
- newtype PluginHandlers a = PluginHandlers (DMap IdeMethod (PluginHandler a))
- newtype PluginNotificationHandlers a = PluginNotificationHandlers (DMap IdeNotification (PluginNotificationHandler a))
- type PluginMethodHandler a m = a -> PluginId -> MessageParams m -> LspM Config (Either ResponseError (ResponseResult m))
- type PluginNotificationMethodHandler a m = a -> VFS -> PluginId -> MessageParams m -> LspM Config ()
- mkPluginHandler :: PluginMethod m => SClientMethod m -> PluginMethodHandler ideState m -> PluginHandlers ideState
- mkPluginNotificationHandler :: HasTracing (MessageParams m) => SClientMethod (m :: Method FromClient Notification) -> PluginNotificationMethodHandler ideState m -> PluginNotificationHandlers ideState
- defaultPluginDescriptor :: PluginId -> PluginDescriptor ideState
- newtype CommandId = CommandId Text
- data PluginCommand ideState = forall a.FromJSON a =>  PluginCommand {- commandId :: CommandId
- commandDesc :: Text
- commandFunc :: CommandFunction ideState a
 
- type CommandFunction ideState a = ideState -> a -> LspM Config (Either ResponseError Value)
- newtype PluginId = PluginId Text
- configForPlugin :: Config -> PluginId -> PluginConfig
- pluginEnabledConfig :: (PluginConfig -> Bool) -> PluginId -> Config -> Bool
- data FormattingType
- type FormattingMethod m = (HasOptions (MessageParams m) FormattingOptions, HasTextDocument (MessageParams m) TextDocumentIdentifier, ResponseResult m ~ List TextEdit)
- type FormattingHandler a = a -> FormattingType -> Text -> NormalizedFilePath -> FormattingOptions -> LspM Config (Either ResponseError (List TextEdit))
- mkFormattingHandlers :: forall a. FormattingHandler a -> PluginHandlers a
- responseError :: Text -> ResponseError
- data FallbackCodeActionParams = FallbackCodeActionParams {}
- otSetUri :: SpanInFlight -> Uri -> IO ()
- class HasTracing a where- traceWithSpan :: SpanInFlight -> a -> IO ()
 
- pROCESS_ID :: Text
- mkLspCommand :: PluginId -> CommandId -> Text -> Maybe [Value] -> Command
- mkLspCmdId :: Text -> PluginId -> CommandId -> Text
- getPid :: IO Text
- getProcessID :: IO Int
- installSigUsr1Handler :: IO () -> IO ()
Documentation
newtype IdePlugins ideState Source #
Constructors
| IdePlugins | |
| Fields 
 | |
Instances
| Semigroup (IdePlugins ideState) Source # | |
| Defined in Ide.Types Methods (<>) :: IdePlugins ideState -> IdePlugins ideState -> IdePlugins ideState # sconcat :: NonEmpty (IdePlugins ideState) -> IdePlugins ideState # stimes :: Integral b => b -> IdePlugins ideState -> IdePlugins ideState # | |
| Monoid (IdePlugins ideState) Source # | |
| Defined in Ide.Types Methods mempty :: IdePlugins ideState # mappend :: IdePlugins ideState -> IdePlugins ideState -> IdePlugins ideState # mconcat :: [IdePlugins ideState] -> IdePlugins ideState # | |
data DynFlagsModifications Source #
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
| Semigroup DynFlagsModifications Source # | |
| Defined in Ide.Types Methods (<>) :: DynFlagsModifications -> DynFlagsModifications -> DynFlagsModifications # sconcat :: NonEmpty DynFlagsModifications -> DynFlagsModifications # stimes :: Integral b => b -> DynFlagsModifications -> DynFlagsModifications # | |
| Monoid DynFlagsModifications Source # | |
| Defined in Ide.Types | |
newtype IdeCommand state Source #
Constructors
| IdeCommand (state -> IO ()) | 
Instances
| Show (IdeCommand st) Source # | |
| Defined in Ide.Types Methods showsPrec :: Int -> IdeCommand st -> ShowS # show :: IdeCommand st -> String # showList :: [IdeCommand st] -> ShowS # | |
data PluginDescriptor ideState Source #
Constructors
| PluginDescriptor | |
| Fields 
 | |
data CustomConfig Source #
An existential wrapper of Properties
Constructors
| forall r. CustomConfig (Properties r) | 
data ConfigDescriptor Source #
Describes the configuration a plugin.
 A plugin may be configurable in such form:
 
 {
  "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 
 | |
mkCustomConfig :: Properties r -> CustomConfig Source #
class HasTracing (MessageParams m) => PluginMethod m where Source #
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
Methods
pluginEnabled :: SMethod m -> PluginId -> Config -> Bool Source #
Parse the configuration to check if this plugin is enabled
Arguments
| :: SMethod m | |
| -> Config | IDE Configuration | 
| -> ClientCapabilities | |
| -> MessageParams m | |
| -> NonEmpty (ResponseResult m) | |
| -> ResponseResult m | 
How to combine responses from different plugins
default combineResponses :: Semigroup (ResponseResult m) => SMethod m -> Config -> ClientCapabilities -> MessageParams m -> NonEmpty (ResponseResult m) -> ResponseResult m Source #
Instances
data IdeMethod (m :: Method FromClient Request) Source #
Methods which have a PluginMethod instance
Constructors
| PluginMethod m => IdeMethod (SMethod m) | 
data IdeNotification (m :: Method FromClient Notification) Source #
Methods which have a PluginMethod instance
Constructors
| HasTracing (MessageParams m) => IdeNotification (SMethod m) | 
Instances
| GEq IdeNotification Source # | |
| Defined in Ide.Types Methods geq :: forall (a :: k) (b :: k). IdeNotification a -> IdeNotification b -> Maybe (a :~: b) # | |
| GCompare IdeNotification Source # | |
| Defined in Ide.Types Methods gcompare :: forall (a :: k) (b :: k). IdeNotification a -> IdeNotification b -> GOrdering a b # | |
newtype PluginHandler a (m :: Method FromClient Request) Source #
Combine handlers for the
Constructors
| PluginHandler (PluginId -> a -> MessageParams m -> LspM Config (NonEmpty (Either ResponseError (ResponseResult m)))) | 
newtype PluginNotificationHandler a (m :: Method FromClient Notification) Source #
Constructors
| PluginNotificationHandler (PluginId -> a -> VFS -> MessageParams m -> LspM Config ()) | 
newtype PluginHandlers a Source #
Constructors
| PluginHandlers (DMap IdeMethod (PluginHandler a)) | 
Instances
| Semigroup (PluginHandlers a) Source # | |
| 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 # | |
| Monoid (PluginHandlers a) Source # | |
| Defined in Ide.Types Methods mempty :: PluginHandlers a # mappend :: PluginHandlers a -> PluginHandlers a -> PluginHandlers a # mconcat :: [PluginHandlers a] -> PluginHandlers a # | |
newtype PluginNotificationHandlers a Source #
Constructors
| PluginNotificationHandlers (DMap IdeNotification (PluginNotificationHandler a)) | 
Instances
| Semigroup (PluginNotificationHandlers a) Source # | |
| 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 # | |
| Monoid (PluginNotificationHandlers a) Source # | |
| Defined in Ide.Types Methods mempty :: PluginNotificationHandlers a # mappend :: PluginNotificationHandlers a -> PluginNotificationHandlers a -> PluginNotificationHandlers a # mconcat :: [PluginNotificationHandlers a] -> PluginNotificationHandlers a # | |
type PluginMethodHandler a m = a -> PluginId -> MessageParams m -> LspM Config (Either ResponseError (ResponseResult m)) Source #
type PluginNotificationMethodHandler a m = a -> VFS -> PluginId -> MessageParams m -> LspM Config () Source #
mkPluginHandler :: PluginMethod m => SClientMethod m -> PluginMethodHandler ideState m -> PluginHandlers ideState Source #
Make a handler for plugins with no extra data
mkPluginNotificationHandler :: HasTracing (MessageParams m) => SClientMethod (m :: Method FromClient Notification) -> PluginNotificationMethodHandler ideState m -> PluginNotificationHandlers ideState Source #
Make a handler for plugins with no extra data
defaultPluginDescriptor :: PluginId -> PluginDescriptor ideState Source #
Instances
| Eq CommandId Source # | |
| Ord CommandId Source # | |
| Read CommandId Source # | |
| Show CommandId Source # | |
| IsString CommandId Source # | |
| Defined in Ide.Types Methods fromString :: String -> CommandId # | |
data PluginCommand ideState Source #
Constructors
| forall a.FromJSON a => PluginCommand | |
| Fields 
 | |
type CommandFunction ideState a = ideState -> a -> LspM Config (Either ResponseError Value) Source #
configForPlugin :: Config -> PluginId -> PluginConfig Source #
pluginEnabledConfig :: (PluginConfig -> Bool) -> PluginId -> Config -> Bool Source #
Checks that a given plugin is both enabled and the specific feature is enabled
data FormattingType Source #
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, ResponseResult m ~ List TextEdit) Source #
type FormattingHandler a = a -> FormattingType -> Text -> NormalizedFilePath -> FormattingOptions -> LspM Config (Either ResponseError (List TextEdit)) Source #
mkFormattingHandlers :: forall a. FormattingHandler a -> PluginHandlers a Source #
responseError :: Text -> ResponseError Source #
data FallbackCodeActionParams Source #
Constructors
| FallbackCodeActionParams | |
| Fields | |
Instances
class HasTracing a where Source #
Minimal complete definition
Nothing
Methods
traceWithSpan :: SpanInFlight -> a -> IO () Source #
Instances
pROCESS_ID :: Text Source #
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.
getProcessID :: IO Int Source #
installSigUsr1Handler :: IO () -> IO () Source #