module Ide.Plugin.Class (descriptor, Log(..)) where import Development.IDE (IdeState, Recorder, WithPriority) import Ide.Plugin.Class.CodeAction import Ide.Plugin.Class.CodeLens import Ide.Plugin.Class.Types import Ide.Types import Language.LSP.Protocol.Message descriptor :: Recorder (WithPriority Log) -> PluginId -> PluginDescriptor IdeState descriptor :: Recorder (WithPriority Log) -> PluginId -> PluginDescriptor IdeState descriptor Recorder (WithPriority Log) recorder PluginId plId = (forall ideState. PluginId -> PluginDescriptor ideState defaultPluginDescriptor PluginId plId) { $sel:pluginCommands:PluginDescriptor :: [PluginCommand IdeState] pluginCommands = PluginId -> [PluginCommand IdeState] commands PluginId plId , $sel:pluginRules:PluginDescriptor :: Rules () pluginRules = Recorder (WithPriority Log) -> Rules () getInstanceBindTypeSigsRule Recorder (WithPriority Log) recorder forall (m :: * -> *) a b. Monad m => m a -> m b -> m b >> Recorder (WithPriority Log) -> Rules () getInstanceBindLensRule Recorder (WithPriority Log) recorder , $sel:pluginHandlers:PluginDescriptor :: PluginHandlers IdeState pluginHandlers = forall ideState (m :: Method 'ClientToServer 'Request). PluginRequestMethod m => SClientMethod m -> PluginMethodHandler ideState m -> PluginHandlers ideState mkPluginHandler SMethod 'Method_TextDocumentCodeAction SMethod_TextDocumentCodeAction (Recorder (WithPriority Log) -> PluginMethodHandler IdeState 'Method_TextDocumentCodeAction codeAction Recorder (WithPriority Log) recorder) forall a. Semigroup a => a -> a -> a <> forall ideState (m :: Method 'ClientToServer 'Request). PluginRequestMethod m => SClientMethod m -> PluginMethodHandler ideState m -> PluginHandlers ideState mkPluginHandler SMethod 'Method_TextDocumentCodeLens SMethod_TextDocumentCodeLens PluginMethodHandler IdeState 'Method_TextDocumentCodeLens codeLens forall a. Semigroup a => a -> a -> a <> forall ideState a (m :: Method 'ClientToServer 'Request). (FromJSON a, PluginRequestMethod m, HasData_ (MessageParams m) (Maybe Value)) => SClientMethod m -> ResolveFunction ideState a m -> PluginHandlers ideState mkResolveHandler SMethod 'Method_CodeLensResolve SMethod_CodeLensResolve ResolveFunction IdeState Int 'Method_CodeLensResolve codeLensResolve } commands :: PluginId -> [PluginCommand IdeState] commands :: PluginId -> [PluginCommand IdeState] commands PluginId plId = [ forall ideState a. FromJSON a => CommandId -> Text -> CommandFunction ideState a -> PluginCommand ideState PluginCommand CommandId codeActionCommandId Text "add placeholders for minimal methods" (PluginId -> CommandFunction IdeState AddMinimalMethodsParams addMethodPlaceholders PluginId plId) , forall ideState a. FromJSON a => CommandId -> Text -> CommandFunction ideState a -> PluginCommand ideState PluginCommand CommandId typeLensCommandId Text "add type signatures for instance methods" (PluginId -> CommandFunction IdeState InstanceBindLensCommand codeLensCommandHandler PluginId plId) ]