Skip to content

Commit 5f84f05

Browse files
committed
non-formatting plugins
1 parent af7d249 commit 5f84f05

File tree

35 files changed

+300
-297
lines changed

35 files changed

+300
-297
lines changed

ghcide/src/Development/IDE/GHC/Warnings.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -37,7 +37,7 @@ withWarnings diagSource action = do
3737
return (reverse $ concat warns, res)
3838

3939
attachReason :: WarnReason -> Diagnostic -> Diagnostic
40-
attachReason wr d = d{_code = InR . T.unpack <$> showReason wr}
40+
attachReason wr d = d{_code = InR <$> showReason wr}
4141
where
4242
showReason = \case
4343
NoReason -> Nothing

ghcide/src/Development/IDE/Plugin/CodeAction.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -174,7 +174,7 @@ findDeclContainingLoc loc = find (\(L l _) -> loc `isInsideSrcSpan` l)
174174

175175
suggestDisableWarning :: ParsedModule -> Maybe T.Text -> Diagnostic -> [(T.Text, [TextEdit])]
176176
suggestDisableWarning pm contents Diagnostic{..}
177-
| Just (InR (T.stripPrefix "-W" . T.pack -> Just w)) <- _code =
177+
| Just (InR (T.stripPrefix "-W" -> Just w)) <- _code =
178178
pure
179179
( "Disable \"" <> w <> "\" warnings"
180180
, [TextEdit (endOfModuleHeader pm contents) $ "{-# OPTIONS_GHC -Wno-" <> w <> " #-}\n"]

haskell-language-server.cabal

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -66,7 +66,7 @@ library
6666
, ghc
6767
, ghcide >=0.7
6868
, gitrev
69-
, haskell-lsp ^>=0.23
69+
, lsp
7070
, hls-plugin-api >=0.7
7171
, hie-bios
7272
, hiedb
@@ -323,7 +323,7 @@ executable haskell-language-server
323323
, ghcide
324324
, hashable
325325
, haskell-language-server
326-
, haskell-lsp ^>=0.23
326+
, lsp
327327
, hie-bios
328328
, hiedb
329329
, lens
@@ -386,7 +386,7 @@ common hls-test-utils
386386
, blaze-markup
387387
, containers
388388
, data-default
389-
, haskell-lsp
389+
, lsp
390390
, hie-bios
391391
, hls-plugin-api >=0.6
392392
, hslogger

hls-plugin-api/src/Ide/Plugin/Config.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -26,8 +26,8 @@ import GHC.Generics (Generic)
2626

2727
-- | Given a DidChangeConfigurationNotification message, this function returns the parsed
2828
-- Config object if possible.
29-
getConfigFromNotification :: NotificationMessage WorkspaceDidChangeConfiguration -> Either T.Text Config
30-
getConfigFromNotification (NotificationMessage _ _ (DidChangeConfigurationParams p)) =
29+
getConfigFromNotification :: Applicative m => a -> A.Value -> m (Either T.Text Config)
30+
getConfigFromNotification _ p = pure $
3131
case fromJSON p of
3232
A.Success c -> Right c
3333
A.Error err -> Left $ T.pack err

hls-plugin-api/src/Ide/Types.hs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -218,11 +218,13 @@ instance Semigroup (PluginHandlers a) where
218218
instance Monoid (PluginHandlers a) where
219219
mempty = PluginHandlers mempty
220220

221+
type SimpleHandler a m = a -> PluginId -> MessageParams m -> LspM Config (Either ResponseError (ResponseResult m))
222+
221223
-- | Make a handler for plugins with no extra data
222224
mkPluginHandler
223225
:: PluginMethod m
224226
=> SClientMethod m
225-
-> (ideState -> PluginId -> MessageParams m -> LspM Config (Either ResponseError (ResponseResult m)))
227+
-> SimpleHandler ideState m
226228
-> PluginHandlers ideState
227229
mkPluginHandler m f = PluginHandlers $ DMap.singleton (IdeMethod m) (PluginHandler f')
228230
where

plugins/default/src/Ide/Plugin/Brittany.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -12,8 +12,8 @@ import qualified Data.Text as T
1212
import Development.IDE
1313
import Development.IDE.GHC.Compat (topDir, ModSummary(ms_hspp_opts))
1414
import Language.Haskell.Brittany
15-
import Language.Haskell.LSP.Types as J
16-
import qualified Language.Haskell.LSP.Types.Lens as J
15+
import Language.LSP.Types as J
16+
import qualified Language.LSP.Types.Lens as J
1717
import Ide.PluginUtils
1818
import Ide.Types
1919

plugins/default/src/Ide/Plugin/Example.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -29,7 +29,7 @@ import Development.IDE.Core.Shake (getDiagnostics, getHiddenDiagnostics)
2929
import GHC.Generics
3030
import Ide.PluginUtils
3131
import Ide.Types
32-
import Language.Haskell.LSP.Types
32+
import Language.LSP.Types
3333
import Text.Regex.TDFA.Text()
3434

3535
-- ---------------------------------------------------------------------

plugins/default/src/Ide/Plugin/Example2.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -28,7 +28,7 @@ import Development.IDE.Core.Shake
2828
import GHC.Generics
2929
import Ide.PluginUtils
3030
import Ide.Types
31-
import Language.Haskell.LSP.Types
31+
import Language.LSP.Types
3232
import Text.Regex.TDFA.Text()
3333

3434
-- ---------------------------------------------------------------------

plugins/default/src/Ide/Plugin/Floskell.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -15,7 +15,7 @@ import Development.IDE as D
1515
import Floskell
1616
import Ide.PluginUtils
1717
import Ide.Types
18-
import Language.Haskell.LSP.Types
18+
import Language.LSP.Types
1919
import Text.Regex.TDFA.Text()
2020

2121
-- ---------------------------------------------------------------------

plugins/default/src/Ide/Plugin/Fourmolu.hs

Lines changed: 3 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -22,12 +22,11 @@ import GHC (DynFlags, moduleNameString)
2222
import GHC.LanguageExtensions.Type (Extension (Cpp))
2323
import GhcPlugins (HscEnv (hsc_dflags))
2424
import Ide.PluginUtils (responseError, makeDiffTextEdit)
25-
import Language.Haskell.LSP.Messages (FromServerMessage (ReqShowMessage))
2625

2726
import Ide.Types
28-
import Language.Haskell.LSP.Core
29-
import Language.Haskell.LSP.Types
30-
import Language.Haskell.LSP.Types.Lens
27+
import Language.LSP.Server
28+
import Language.LSP.Types
29+
import Language.LSP.Types.Lens
3130
import "fourmolu" Ormolu
3231

3332
-- ---------------------------------------------------------------------

plugins/default/src/Ide/Plugin/ModuleName.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -64,11 +64,11 @@ import Ide.Types (
6464
PluginId (..),
6565
defaultPluginDescriptor,
6666
)
67-
import Language.Haskell.LSP.Core (
67+
import Language.LSP.Server (
6868
LspFuncs,
6969
getVirtualFileFunc,
7070
)
71-
import Language.Haskell.LSP.Types (
71+
import Language.LSP.Types (
7272
ApplyWorkspaceEditParams (..),
7373
CodeLens (CodeLens),
7474
CodeLensParams (CodeLensParams),
@@ -82,7 +82,7 @@ import Language.Haskell.LSP.Types (
8282
WorkspaceEdit (..),
8383
uriToNormalizedFilePath,
8484
)
85-
import Language.Haskell.LSP.VFS (virtualFileText)
85+
import Language.LSP.VFS (virtualFileText)
8686
import System.Directory (canonicalizePath)
8787
import System.FilePath (
8888
dropExtension,

plugins/default/src/Ide/Plugin/Ormolu.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -20,9 +20,9 @@ import GHC.LanguageExtensions.Type
2020
import GhcPlugins (HscEnv (hsc_dflags))
2121
import Ide.PluginUtils
2222
import Ide.Types
23-
import Language.Haskell.LSP.Core (LspFuncs (withIndefiniteProgress),
23+
import Language.LSP.Server (LspFuncs (withIndefiniteProgress),
2424
ProgressCancellable (Cancellable))
25-
import Language.Haskell.LSP.Types
25+
import Language.LSP.Types
2626
import "ormolu" Ormolu
2727
import System.FilePath (takeFileName)
2828
import Text.Regex.TDFA.Text ()

plugins/default/src/Ide/Plugin/Pragmas.hs

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -17,14 +17,14 @@ import qualified Data.Text as T
1717
import Development.IDE as D
1818
import qualified GHC.Generics as Generics
1919
import Ide.Types
20-
import Language.Haskell.LSP.Types
21-
import qualified Language.Haskell.LSP.Types as J
22-
import qualified Language.Haskell.LSP.Types.Lens as J
20+
import Language.LSP.Types
21+
import qualified Language.LSP.Types as J
22+
import qualified Language.LSP.Types.Lens as J
2323

2424
import Control.Monad (join)
2525
import Development.IDE.GHC.Compat
26-
import qualified Language.Haskell.LSP.Core as LSP
27-
import qualified Language.Haskell.LSP.VFS as VFS
26+
import qualified Language.LSP.Server as LSP
27+
import qualified Language.LSP.VFS as VFS
2828
import qualified Text.Fuzzy as Fuzzy
2929

3030
-- ---------------------------------------------------------------------

plugins/default/src/Ide/Plugin/StylishHaskell.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -12,7 +12,7 @@ import Development.IDE (IdeState)
1212
import Ide.PluginUtils
1313
import Ide.Types
1414
import Language.Haskell.Stylish
15-
import Language.Haskell.LSP.Types as J
15+
import Language.LSP.Types as J
1616

1717
import System.Directory
1818
import System.FilePath

plugins/hls-class-plugin/hls-class-plugin.cabal

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -20,7 +20,7 @@ library
2020
build-depends: aeson
2121
, base >=4.12 && <5
2222
, containers
23-
, haskell-lsp
23+
, lsp
2424
, hls-plugin-api
2525
, ghc
2626
, ghc-exactprint

plugins/hls-class-plugin/src/Ide/Plugin/Class.hs

Lines changed: 31 additions & 27 deletions
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,7 @@
44
{-# LANGUAGE RecordWildCards #-}
55
{-# LANGUAGE TypeFamilies #-}
66
{-# LANGUAGE ViewPatterns #-}
7+
{-# LANGUAGE DataKinds #-}
78
module Ide.Plugin.Class
89
( descriptor
910
) where
@@ -22,8 +23,8 @@ import Data.List
2223
import qualified Data.Map.Strict as Map
2324
import Data.Maybe
2425
import qualified Data.Text as T
25-
import Development.IDE
26-
import Development.IDE.Core.PositionMapping (fromCurrentRange)
26+
import Development.IDE hiding (pluginHandlers)
27+
import Development.IDE.Core.PositionMapping (fromCurrentRange, toCurrentRange)
2728
import Development.IDE.GHC.Compat hiding (getLoc)
2829
import Development.IDE.Spans.AtPoint
2930
import qualified GHC.Generics as Generics
@@ -33,17 +34,17 @@ import Ide.Types
3334
import Language.Haskell.GHC.ExactPrint
3435
import Language.Haskell.GHC.ExactPrint.Parsers (parseDecl)
3536
import Language.Haskell.GHC.ExactPrint.Types hiding (GhcPs, Parens)
36-
import Language.Haskell.LSP.Core
37-
import Language.Haskell.LSP.Types
38-
import qualified Language.Haskell.LSP.Types.Lens as J
37+
import Language.LSP.Server
38+
import Language.LSP.Types
39+
import qualified Language.LSP.Types.Lens as J
3940
import SrcLoc
4041
import TcEnv
4142
import TcRnMonad
4243

4344
descriptor :: PluginId -> PluginDescriptor IdeState
4445
descriptor plId = (defaultPluginDescriptor plId)
4546
{ pluginCommands = commands
46-
, pluginCodeActionProvider = Just codeAction
47+
, pluginHandlers = mkPluginHandler STextDocumentCodeAction codeAction
4748
}
4849

4950
commands :: [PluginCommand IdeState]
@@ -60,25 +61,28 @@ data AddMinimalMethodsParams = AddMinimalMethodsParams
6061
deriving (Show, Eq, Generics.Generic, ToJSON, FromJSON)
6162

6263
addMethodPlaceholders :: CommandFunction IdeState AddMinimalMethodsParams
63-
addMethodPlaceholders lf state AddMinimalMethodsParams{..} = fmap (fromMaybe errorResult) . runMaybeT $ do
64-
docPath <- MaybeT . pure . uriToNormalizedFilePath $ toNormalizedUri uri
65-
pm <- MaybeT . runAction "classplugin" state $ use GetParsedModule docPath
66-
let
67-
ps = pm_parsed_source pm
68-
anns = relativiseApiAnns ps (pm_annotations pm)
69-
old = T.pack $ exactPrint ps anns
70-
71-
(hsc_dflags . hscEnv -> df) <- MaybeT . runAction "classplugin" state $ use GhcSessionDeps docPath
72-
List (unzip -> (mAnns, mDecls)) <- MaybeT . pure $ traverse (makeMethodDecl df) methodGroup
73-
let
74-
(ps', (anns', _), _) = runTransform (mergeAnns (mergeAnnList mAnns) anns) (addMethodDecls ps mDecls)
75-
new = T.pack $ exactPrint ps' anns'
76-
77-
pure (Right Null, Just (WorkspaceApplyEdit, ApplyWorkspaceEditParams (workspaceEdit caps old new)))
64+
addMethodPlaceholders state AddMinimalMethodsParams{..} = do
65+
caps <- getClientCapabilities
66+
medit <- liftIO $ runMaybeT $ do
67+
docPath <- MaybeT . pure . uriToNormalizedFilePath $ toNormalizedUri uri
68+
pm <- MaybeT . runAction "classplugin" state $ use GetParsedModule docPath
69+
let
70+
ps = pm_parsed_source pm
71+
anns = relativiseApiAnns ps (pm_annotations pm)
72+
old = T.pack $ exactPrint ps anns
73+
74+
(hsc_dflags . hscEnv -> df) <- MaybeT . runAction "classplugin" state $ use GhcSessionDeps docPath
75+
List (unzip -> (mAnns, mDecls)) <- MaybeT . pure $ traverse (makeMethodDecl df) methodGroup
76+
let
77+
(ps', (anns', _), _) = runTransform (mergeAnns (mergeAnnList mAnns) anns) (addMethodDecls ps mDecls)
78+
new = T.pack $ exactPrint ps' anns'
79+
80+
pure (workspaceEdit caps old new)
81+
forM_ medit $ \edit ->
82+
sendRequest SWorkspaceApplyEdit (ApplyWorkspaceEditParams Nothing edit) (\_ -> pure ())
83+
pure (Right Null)
7884
where
79-
errorResult = (Right Null, Nothing)
8085

81-
caps = clientCapabilities lf
8286
indent = 2
8387

8488
makeMethodDecl df mName =
@@ -126,8 +130,8 @@ addMethodPlaceholders lf state AddMinimalMethodsParams{..} = fmap (fromMaybe err
126130
-- |
127131
-- This implementation is ad-hoc in a sense that the diagnostic detection mechanism is
128132
-- sensitive to the format of diagnostic messages from GHC.
129-
codeAction :: CodeActionProvider IdeState
130-
codeAction _ state plId docId _ context = fmap (fromMaybe errorResult) . runMaybeT $ do
133+
codeAction :: SimpleHandler IdeState TextDocumentCodeAction
134+
codeAction state plId (CodeActionParams _ _ docId _ context) = liftIO $ fmap (fromMaybe errorResult) . runMaybeT $ do
131135
docPath <- MaybeT . pure . uriToNormalizedFilePath $ toNormalizedUri uri
132136
actions <- join <$> mapM (mkActions docPath) methodDiags
133137
pure . Right . List $ actions
@@ -160,8 +164,8 @@ codeAction _ state plId docId _ context = fmap (fromMaybe errorResult) . runMayb
160164
mkCmdParams methodGroup = [toJSON (AddMinimalMethodsParams uri range (List methodGroup))]
161165

162166
mkCodeAction title
163-
= CACodeAction
164-
. CodeAction title (Just CodeActionQuickFix) (Just (List [])) Nothing
167+
= InR
168+
. CodeAction title (Just CodeActionQuickFix) (Just (List [])) Nothing Nothing Nothing
165169
. Just
166170

167171
findClassIdentifier docPath range = do

plugins/hls-eval-plugin/hls-eval-plugin.cabal

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -51,8 +51,8 @@ library
5151
, ghc-paths
5252
, ghcide >=0.7.3.0
5353
, hashable
54-
, haskell-lsp
55-
, haskell-lsp-types
54+
, lsp
55+
, lsp-types
5656
, hls-plugin-api >=0.7
5757
, lens
5858
, megaparsec >=0.9
@@ -67,6 +67,7 @@ library
6767
, time
6868
, transformers
6969
, unordered-containers
70+
, unliftio
7071

7172
ghc-options: -Wall -Wno-name-shadowing
7273

plugins/hls-eval-plugin/src/Ide/Plugin/Eval.hs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -15,12 +15,14 @@ import Ide.Types (
1515
PluginDescriptor (..),
1616
PluginId,
1717
defaultPluginDescriptor,
18+
mkPluginHandler
1819
)
20+
import Language.LSP.Types
1921

2022
-- |Plugin descriptor
2123
descriptor :: PluginId -> PluginDescriptor IdeState
2224
descriptor plId =
2325
(defaultPluginDescriptor plId)
24-
{ pluginCodeLensProvider = Just CL.codeLens
26+
{ pluginHandlers = mkPluginHandler STextDocumentCodeLens CL.codeLens
2527
, pluginCommands = [CL.evalCommand]
2628
}

plugins/hls-eval-plugin/src/Ide/Plugin/Eval/Code.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -24,7 +24,7 @@ import Ide.Plugin.Eval.Types (
2424
import InteractiveEval (runDecls)
2525
import Unsafe.Coerce (unsafeCoerce)
2626
import Control.Lens ((^.))
27-
import Language.Haskell.LSP.Types.Lens (start, line)
27+
import Language.LSP.Types.Lens (start, line)
2828

2929
-- | Return the ranges of the expression and result parts of the given test
3030
testRanges :: Test -> (Range, Range)

0 commit comments

Comments
 (0)