module Wingman.Plugin where
import Control.Monad
import Development.IDE.Core.Shake (IdeState (..))
import Ide.Types
import Language.LSP.Types
import Prelude hiding (span)
import Wingman.AbstractLSP
import Wingman.AbstractLSP.TacticActions (makeTacticInteraction)
import Wingman.EmptyCase
import Wingman.LanguageServer hiding (Log)
import qualified Wingman.LanguageServer as WingmanLanguageServer
import Wingman.LanguageServer.Metaprogram (hoverProvider)
import Wingman.StaticPlugin
import Development.IDE.Types.Logger (Recorder, cmapWithPrio, WithPriority, Pretty (pretty))
newtype Log
= LogWingmanLanguageServer WingmanLanguageServer.Log
deriving Int -> Log -> ShowS
[Log] -> ShowS
Log -> String
(Int -> Log -> ShowS)
-> (Log -> String) -> ([Log] -> ShowS) -> Show Log
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Log] -> ShowS
$cshowList :: [Log] -> ShowS
show :: Log -> String
$cshow :: Log -> String
showsPrec :: Int -> Log -> ShowS
$cshowsPrec :: Int -> Log -> ShowS
Show
instance Pretty Log where
pretty :: Log -> Doc ann
pretty = \case
LogWingmanLanguageServer Log
log -> Log -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Log
log
descriptor :: Recorder (WithPriority Log) -> PluginId -> PluginDescriptor IdeState
descriptor :: Recorder (WithPriority Log)
-> PluginId -> PluginDescriptor IdeState
descriptor Recorder (WithPriority Log)
recorder PluginId
plId
= [Interaction]
-> PluginDescriptor IdeState -> PluginDescriptor IdeState
installInteractions
( Interaction
emptyCaseInteraction
Interaction -> [Interaction] -> [Interaction]
forall a. a -> [a] -> [a]
: (TacticCommand -> Interaction) -> [TacticCommand] -> [Interaction]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap TacticCommand -> Interaction
makeTacticInteraction [TacticCommand
forall a. Bounded a => a
minBound .. TacticCommand
forall a. Bounded a => a
maxBound]
)
(PluginDescriptor IdeState -> PluginDescriptor IdeState)
-> PluginDescriptor IdeState -> PluginDescriptor IdeState
forall a b. (a -> b) -> a -> b
$ (PluginId -> PluginDescriptor IdeState
forall ideState. PluginId -> PluginDescriptor ideState
defaultPluginDescriptor PluginId
plId)
{ pluginHandlers :: PluginHandlers IdeState
pluginHandlers = SClientMethod 'TextDocumentHover
-> PluginMethodHandler IdeState 'TextDocumentHover
-> PluginHandlers IdeState
forall (m :: Method 'FromClient 'Request) ideState.
PluginMethod m =>
SClientMethod m
-> PluginMethodHandler ideState m -> PluginHandlers ideState
mkPluginHandler SClientMethod 'TextDocumentHover
STextDocumentHover PluginMethodHandler IdeState 'TextDocumentHover
hoverProvider
, pluginRules :: Rules ()
pluginRules = Recorder (WithPriority Log) -> PluginId -> Rules ()
wingmanRules ((Log -> Log)
-> Recorder (WithPriority Log) -> Recorder (WithPriority Log)
forall a b.
(a -> b) -> Recorder (WithPriority b) -> Recorder (WithPriority a)
cmapWithPrio Log -> Log
LogWingmanLanguageServer Recorder (WithPriority Log)
recorder) PluginId
plId
, pluginConfigDescriptor :: ConfigDescriptor
pluginConfigDescriptor =
ConfigDescriptor
defaultConfigDescriptor
{ configCustomConfig :: CustomConfig
configCustomConfig = Properties
'[ 'PropertyKey
"hole_severity" ('TEnum (Maybe DiagnosticSeverity)),
'PropertyKey "max_use_ctor_actions" 'TInteger,
'PropertyKey "timeout_duration" 'TInteger,
'PropertyKey "auto_gas" 'TInteger,
'PropertyKey "proofstate_styling" 'TBoolean]
-> CustomConfig
forall (r :: [PropertyKey]). Properties r -> CustomConfig
mkCustomConfig Properties
'[ 'PropertyKey
"hole_severity" ('TEnum (Maybe DiagnosticSeverity)),
'PropertyKey "max_use_ctor_actions" 'TInteger,
'PropertyKey "timeout_duration" 'TInteger,
'PropertyKey "auto_gas" 'TInteger,
'PropertyKey "proofstate_styling" 'TBoolean]
properties
}
, pluginModifyDynflags :: DynFlagsModifications
pluginModifyDynflags = DynFlagsModifications
staticPlugin
}