Remove Bios plugin

No longer need to supply checkCmd (only JSON transport could previously
use it)
This commit is contained in:
Luke Lau 2019-12-22 00:31:06 +00:00
parent 44c6fb35cf
commit 25e1f76671
4 changed files with 1 additions and 35 deletions

View File

@ -26,7 +26,6 @@ import System.IO
import Haskell.Ide.Engine.Plugin.ApplyRefact
import Haskell.Ide.Engine.Plugin.Brittany
import Haskell.Ide.Engine.Plugin.Example2
import Haskell.Ide.Engine.Plugin.Bios
-- import Haskell.Ide.Engine.Plugin.HaRe
import Haskell.Ide.Engine.Plugin.Haddock
import Haskell.Ide.Engine.Plugin.HfaAlign
@ -56,7 +55,6 @@ plugins includeExamples = pluginDescToIdePlugins allPlugins
, packageDescriptor "package"
, pragmasDescriptor "pragmas"
, floskellDescriptor "floskell"
, biosDescriptor "bios"
, genericDescriptor "generic"
]
examplePlugins =

View File

@ -28,7 +28,6 @@ library
Haskell.Ide.Engine.Plugin.Brittany
Haskell.Ide.Engine.Plugin.Example2
Haskell.Ide.Engine.Plugin.Floskell
Haskell.Ide.Engine.Plugin.Bios
-- Haskell.Ide.Engine.Plugin.HaRe
Haskell.Ide.Engine.Plugin.Haddock
Haskell.Ide.Engine.Plugin.HfaAlign

View File

@ -1,30 +0,0 @@
{-# LANGUAGE OverloadedStrings #-}
module Haskell.Ide.Engine.Plugin.Bios
( setTypecheckedModule
, biosDescriptor
)
where
import Haskell.Ide.Engine.MonadTypes
import Haskell.Ide.Engine.Ghc
-- ---------------------------------------------------------------------
biosDescriptor :: PluginId -> PluginDescriptor
biosDescriptor plId = PluginDescriptor
{ pluginId = plId
, pluginCommands =
[PluginCommand "check" "check a file for GHC warnings and errors" checkCmd]
, pluginCodeActionProvider = Nothing
, pluginDiagnosticProvider = Nothing
, pluginHoverProvider = Nothing
, pluginSymbolProvider = Nothing
, pluginFormattingProvider = Nothing
}
checkCmd :: Uri -> IdeGhcM (IdeResult (Diagnostics, AdditionalErrs))
checkCmd = setTypecheckedModule
-- ---------------------------------------------------------------------

View File

@ -53,7 +53,6 @@ import Haskell.Ide.Engine.PluginUtils
import qualified Haskell.Ide.Engine.Scheduler as Scheduler
import qualified Haskell.Ide.Engine.Support.HieExtras as Hie
import Haskell.Ide.Engine.Types
import qualified Haskell.Ide.Engine.Plugin.Bios as BIOS
import Haskell.Ide.Engine.Version
import qualified Language.Haskell.LSP.Control as CTRL
import qualified Language.Haskell.LSP.Core as Core
@ -927,7 +926,7 @@ requestDiagnosticsNormal tn file mVer = do
-- get GHC diagnostics and loads the typechecked module into the cache
let reqg = GReq tn "typecheck" (Just file) (Just (file,ver)) Nothing callbackg mempty
$ BIOS.setTypecheckedModule file
$ HIE.setTypecheckedModule file
callbackg (HIE.Diagnostics pd, errs) = do
forM_ errs $ \e -> do
reactorSend $ NotShowMessage $