Skip to content

Commit 8f68882

Browse files
authored
Add throwPluginError to Plugin Utilities (#2924)
* Add new PluginUtility function. Add the function `throwPluginError`. This function is intended to provide a common `ResponseError` message for use in logging. Renamed `response` to `pluginResponse` for more clarity. * Call hierarchy clean up * Make Descriptor usable as String/Text or PluginID * Update reference to ChangeTypeSignature descriptor * Use unpack rather than show * Import cleanup * Merge cleanup * Fix test suites for effected plugins * forgot to change the CodeAction kind in the test suite... * Update new plugin
1 parent 2cb8c23 commit 8f68882

File tree

14 files changed

+84
-69
lines changed

14 files changed

+84
-69
lines changed

exe/Plugins.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -157,7 +157,7 @@ idePlugins recorder includeExamples = pluginDescToIdePlugins allPlugins
157157
Brittany.descriptor "brittany" :
158158
#endif
159159
#if callHierarchy
160-
CallHierarchy.descriptor "callHierarchy":
160+
CallHierarchy.descriptor :
161161
#endif
162162
#if class
163163
Class.descriptor "class" :
@@ -187,13 +187,13 @@ idePlugins recorder includeExamples = pluginDescToIdePlugins allPlugins
187187
Splice.descriptor "splice" :
188188
#endif
189189
#if alternateNumberFormat
190-
AlternateNumberFormat.descriptor pluginRecorder "alternateNumberFormat" :
190+
AlternateNumberFormat.descriptor pluginRecorder :
191191
#endif
192192
#if selectionRange
193193
SelectionRange.descriptor "selectionRange" :
194194
#endif
195195
#if changeTypeSignature
196-
ChangeTypeSignature.descriptor "changeTypeSignature" :
196+
ChangeTypeSignature.descriptor :
197197
#endif
198198
#if gadt
199199
GADT.descriptor "gadt" :

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

Lines changed: 9 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -28,14 +28,14 @@ module Ide.PluginUtils
2828
positionInRange,
2929
usePropertyLsp,
3030
getNormalizedFilePath,
31-
response,
31+
pluginResponse,
3232
handleMaybe,
3333
handleMaybeM,
34+
throwPluginError
3435
)
3536
where
3637

3738

38-
import Control.Lens ((^.))
3939
import Control.Monad.Extra (maybeM)
4040
import Control.Monad.Trans.Class (lift)
4141
import Control.Monad.Trans.Except (ExceptT, runExceptT, throwE)
@@ -253,13 +253,18 @@ getNormalizedFilePath (PluginId plId) uri = handleMaybe errMsg
253253
errMsg = T.unpack $ "Error(" <> plId <> "): converting " <> getUri uri <> " to NormalizedFilePath"
254254

255255
-- ---------------------------------------------------------------------
256+
throwPluginError :: Monad m => PluginId -> String -> String -> ExceptT String m b
257+
throwPluginError (PluginId who) what where' = throwE msg
258+
where
259+
msg = (T.unpack who) <> " failed with " <> what <> " at " <> where'
260+
256261
handleMaybe :: Monad m => e -> Maybe b -> ExceptT e m b
257262
handleMaybe msg = maybe (throwE msg) return
258263

259264
handleMaybeM :: Monad m => e -> m (Maybe b) -> ExceptT e m b
260265
handleMaybeM msg act = maybeM (throwE msg) return $ lift act
261266

262-
response :: Monad m => ExceptT String m a -> m (Either ResponseError a)
263-
response =
267+
pluginResponse :: Monad m => ExceptT String m a -> m (Either ResponseError a)
268+
pluginResponse =
264269
fmap (first (\msg -> ResponseError InternalError (fromString msg) Nothing))
265270
. runExceptT

plugins/hls-alternate-number-format-plugin/src/Ide/Plugin/AlternateNumberFormat.hs

Lines changed: 14 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,7 @@ module Ide.Plugin.AlternateNumberFormat (descriptor, Log(..)) where
88
import Control.Lens ((^.))
99
import Control.Monad.Except (ExceptT, MonadIO, liftIO)
1010
import qualified Data.HashMap.Strict as HashMap
11+
import Data.String (IsString)
1112
import Data.Text (Text)
1213
import qualified Data.Text as T
1314
import Development.IDE (GetParsedModule (GetParsedModule),
@@ -31,19 +32,22 @@ import Ide.Plugin.Conversion (AlternateFormat,
3132
alternateFormat)
3233
import Ide.Plugin.Literals
3334
import Ide.PluginUtils (getNormalizedFilePath,
34-
handleMaybeM, response)
35+
handleMaybeM, pluginResponse)
3536
import Ide.Types
3637
import Language.LSP.Types
37-
import Language.LSP.Types.Lens (uri)
38+
import qualified Language.LSP.Types.Lens as L
3839

3940
newtype Log = LogShake Shake.Log deriving Show
4041

4142
instance Pretty Log where
4243
pretty = \case
4344
LogShake log -> pretty log
4445

45-
descriptor :: Recorder (WithPriority Log) -> PluginId -> PluginDescriptor IdeState
46-
descriptor recorder plId = (defaultPluginDescriptor plId)
46+
alternateNumberFormatId :: IsString a => a
47+
alternateNumberFormatId = "alternateNumberFormat"
48+
49+
descriptor :: Recorder (WithPriority Log) -> PluginDescriptor IdeState
50+
descriptor recorder = (defaultPluginDescriptor alternateNumberFormatId)
4751
{ pluginHandlers = mkPluginHandler STextDocumentCodeAction codeActionHandler
4852
, pluginRules = collectLiteralsRule recorder
4953
}
@@ -83,8 +87,8 @@ collectLiteralsRule recorder = define (cmapWithPrio LogShake recorder) $ \Collec
8387
getExtensions = map GhcExtension . toList . extensionFlags . ms_hspp_opts . pm_mod_summary
8488

8589
codeActionHandler :: PluginMethodHandler IdeState 'TextDocumentCodeAction
86-
codeActionHandler state plId (CodeActionParams _ _ docId currRange _) = response $ do
87-
nfp <- getNormalizedFilePath plId (docId ^. uri)
90+
codeActionHandler state plId (CodeActionParams _ _ docId currRange _) = pluginResponse $ do
91+
nfp <- getNormalizedFilePath plId (docId ^. L.uri)
8892
CLR{..} <- requestLiterals state nfp
8993
pragma <- getFirstPragma state nfp
9094
-- remove any invalid literals (see validTarget comment)
@@ -144,14 +148,14 @@ p `isInsideRealSrcSpan` r = let (Range sp ep) = realSrcSpanToRange r in sp <= p
144148

145149
getFirstPragma :: MonadIO m => IdeState -> NormalizedFilePath -> ExceptT String m NextPragmaInfo
146150
getFirstPragma state nfp = handleMaybeM "Error: Could not get NextPragmaInfo" $ do
147-
ghcSession <- liftIO $ runAction "AlternateNumberFormat.GhcSession" state $ useWithStale GhcSession nfp
148-
(_, fileContents) <- liftIO $ runAction "AlternateNumberFormat.GetFileContents" state $ getFileContents nfp
151+
ghcSession <- liftIO $ runAction (alternateNumberFormatId <> ".GhcSession") state $ useWithStale GhcSession nfp
152+
(_, fileContents) <- liftIO $ runAction (alternateNumberFormatId <> ".GetFileContents") state $ getFileContents nfp
149153
case ghcSession of
150154
Just (hscEnv -> hsc_dflags -> sessionDynFlags, _) -> pure $ Just $ getNextPragmaInfo sessionDynFlags fileContents
151-
Nothing -> pure Nothing
155+
Nothing -> pure Nothing
152156

153157
requestLiterals :: MonadIO m => IdeState -> NormalizedFilePath -> ExceptT String m CollectLiteralsResult
154158
requestLiterals state = handleMaybeM "Error: Could not Collect Literals"
155159
. liftIO
156-
. runAction "AlternateNumberFormat.CollectLiterals" state
160+
. runAction (alternateNumberFormatId <> ".CollectLiterals") state
157161
. use CollectLiterals

plugins/hls-alternate-number-format-plugin/test/Main.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -21,7 +21,7 @@ main :: IO ()
2121
main = defaultTestRunner test
2222

2323
alternateNumberFormatPlugin :: PluginDescriptor IdeState
24-
alternateNumberFormatPlugin = AlternateNumberFormat.descriptor mempty "alternateNumberFormat"
24+
alternateNumberFormatPlugin = AlternateNumberFormat.descriptor mempty
2525

2626
-- NOTE: For whatever reason, this plugin does not play nice with creating Code Actions on time.
2727
-- As a result tests will mostly pass if `import Prelude` is added at the top. We (mostly fendor) surmise this has something

plugins/hls-call-hierarchy-plugin/src/Ide/Plugin/CallHierarchy.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -5,8 +5,8 @@ import qualified Ide.Plugin.CallHierarchy.Internal as X
55
import Ide.Types
66
import Language.LSP.Types
77

8-
descriptor :: PluginId -> PluginDescriptor IdeState
9-
descriptor plId = (defaultPluginDescriptor plId)
8+
descriptor :: PluginDescriptor IdeState
9+
descriptor = (defaultPluginDescriptor X.callHierarchyId)
1010
{ Ide.Types.pluginHandlers = mkPluginHandler STextDocumentPrepareCallHierarchy X.prepareCallHierarchy
1111
<> mkPluginHandler SCallHierarchyIncomingCalls X.incomingCalls
1212
<> mkPluginHandler SCallHierarchyOutgoingCalls X.outgoingCalls

plugins/hls-call-hierarchy-plugin/src/Ide/Plugin/CallHierarchy/Internal.hs

Lines changed: 23 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -11,6 +11,7 @@ module Ide.Plugin.CallHierarchy.Internal (
1111
prepareCallHierarchy
1212
, incomingCalls
1313
, outgoingCalls
14+
, callHierarchyId
1415
) where
1516

1617
import Control.Lens ((^.))
@@ -35,23 +36,23 @@ import GHC.Conc.Sync
3536
import HieDb (Symbol (Symbol))
3637
import qualified Ide.Plugin.CallHierarchy.Query as Q
3738
import Ide.Plugin.CallHierarchy.Types
39+
import Ide.PluginUtils (getNormalizedFilePath,
40+
handleMaybe, pluginResponse,
41+
throwPluginError)
3842
import Ide.Types
3943
import Language.LSP.Types
4044
import qualified Language.LSP.Types.Lens as L
4145
import Text.Read (readMaybe)
4246

47+
callHierarchyId :: PluginId
48+
callHierarchyId = PluginId "callHierarchy"
49+
4350
-- | Render prepare call hierarchy request.
4451
prepareCallHierarchy :: PluginMethodHandler IdeState TextDocumentPrepareCallHierarchy
45-
prepareCallHierarchy state pluginId param
46-
| Just nfp <- uriToNormalizedFilePath $ toNormalizedUri uri =
47-
liftIO (runAction "CallHierarchy.prepareHierarchy" state (prepareCallHierarchyItem nfp pos)) >>=
48-
\case
49-
Just items -> pure $ Right $ Just $ List items
50-
Nothing -> pure $ Right Nothing
51-
| otherwise = pure $ Left $ responseError $ T.pack $ "Call Hierarchy: uriToNormalizedFilePath failed for: " <> show uri
52-
where
53-
uri = param ^. (L.textDocument . L.uri)
54-
pos = param ^. L.position
52+
prepareCallHierarchy state pluginId param = pluginResponse $ do
53+
nfp <- getNormalizedFilePath pluginId (param ^. L.textDocument ^. L.uri)
54+
items <- liftIO (runAction "CallHierarchy.prepareHierarchy" state (prepareCallHierarchyItem nfp (param ^. L.position)))
55+
pure (List <$> items)
5556

5657
prepareCallHierarchyItem :: NormalizedFilePath -> Position -> Action (Maybe [CallHierarchyItem])
5758
prepareCallHierarchyItem = constructFromAst
@@ -196,13 +197,13 @@ deriving instance Ord Value
196197

197198
-- | Render incoming calls request.
198199
incomingCalls :: PluginMethodHandler IdeState CallHierarchyIncomingCalls
199-
incomingCalls state pluginId param = do
200-
liftIO $ runAction "CallHierarchy.incomingCalls" state $
200+
incomingCalls state pluginId param = pluginResponse $ do
201+
calls <- liftIO $ runAction "CallHierarchy.incomingCalls" state $
201202
queryCalls (param ^. L.item) Q.incomingCalls mkCallHierarchyIncomingCall
202-
mergeIncomingCalls >>=
203-
\case
204-
Just x -> pure $ Right $ Just $ List x
205-
Nothing -> pure $ Left $ responseError "CallHierarchy: IncomingCalls internal error"
203+
mergeIncomingCalls
204+
case calls of
205+
Just x -> pure $ Just $ List x
206+
Nothing -> throwPluginError callHierarchyId "Internal Error" "incomingCalls"
206207
where
207208
mkCallHierarchyIncomingCall :: Vertex -> Action (Maybe CallHierarchyIncomingCall)
208209
mkCallHierarchyIncomingCall = mkCallHierarchyCall CallHierarchyIncomingCall
@@ -217,13 +218,13 @@ incomingCalls state pluginId param = do
217218

218219
-- Render outgoing calls request.
219220
outgoingCalls :: PluginMethodHandler IdeState CallHierarchyOutgoingCalls
220-
outgoingCalls state pluginId param = do
221-
liftIO $ runAction "CallHierarchy.outgoingCalls" state $
221+
outgoingCalls state pluginId param = pluginResponse $ do
222+
calls <- liftIO $ runAction "CallHierarchy.outgoingCalls" state $
222223
queryCalls (param ^. L.item) Q.outgoingCalls mkCallHierarchyOutgoingCall
223-
mergeOutgoingCalls >>=
224-
\case
225-
Just x -> pure $ Right $ Just $ List x
226-
Nothing -> pure $ Left $ responseError "CallHierarchy: OutgoingCalls internal error"
224+
mergeOutgoingCalls
225+
case calls of
226+
Just x -> pure $ Just $ List x
227+
Nothing -> throwPluginError callHierarchyId "Internal Error" "outgoingCalls"
227228
where
228229
mkCallHierarchyOutgoingCall :: Vertex -> Action (Maybe CallHierarchyOutgoingCall)
229230
mkCallHierarchyOutgoingCall = mkCallHierarchyCall CallHierarchyOutgoingCall

plugins/hls-call-hierarchy-plugin/test/Main.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -22,7 +22,7 @@ import Test.Hls
2222
import Test.Hls.Util (withCanonicalTempDir)
2323

2424
plugin :: PluginDescriptor IdeState
25-
plugin = descriptor "callHierarchy"
25+
plugin = descriptor
2626

2727
main :: IO ()
2828
main = defaultTestRunner $

plugins/hls-change-type-signature-plugin/src/Ide/Plugin/ChangeTypeSignature.hs

Lines changed: 11 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -12,6 +12,7 @@ import Control.Monad.Trans.Except (ExceptT)
1212
import Data.Foldable (asum)
1313
import qualified Data.HashMap.Strict as Map
1414
import Data.Maybe (mapMaybe)
15+
import Data.String (IsString)
1516
import Data.Text (Text)
1617
import qualified Data.Text as T
1718
import Development.IDE (realSrcSpanToRange)
@@ -22,19 +23,22 @@ import Development.IDE.GHC.Compat
2223
import Development.IDE.GHC.Util (printOutputable)
2324
import Generics.SYB (extQ, something)
2425
import Ide.PluginUtils (getNormalizedFilePath,
25-
handleMaybeM, response)
26+
handleMaybeM, pluginResponse)
2627
import Ide.Types (PluginDescriptor (..),
27-
PluginId, PluginMethodHandler,
28+
PluginMethodHandler,
2829
defaultPluginDescriptor,
2930
mkPluginHandler)
3031
import Language.LSP.Types
3132
import Text.Regex.TDFA ((=~))
3233

33-
descriptor :: PluginId -> PluginDescriptor IdeState
34-
descriptor plId = (defaultPluginDescriptor plId) { pluginHandlers = mkPluginHandler STextDocumentCodeAction codeActionHandler }
34+
changeTypeSignatureId :: IsString a => a
35+
changeTypeSignatureId = "changeTypeSignature"
36+
37+
descriptor :: PluginDescriptor IdeState
38+
descriptor = (defaultPluginDescriptor changeTypeSignatureId) { pluginHandlers = mkPluginHandler STextDocumentCodeAction codeActionHandler }
3539

3640
codeActionHandler :: PluginMethodHandler IdeState 'TextDocumentCodeAction
37-
codeActionHandler ideState plId CodeActionParams {_textDocument = TextDocumentIdentifier uri, _context = CodeActionContext (List diags) _} = response $ do
41+
codeActionHandler ideState plId CodeActionParams {_textDocument = TextDocumentIdentifier uri, _context = CodeActionContext (List diags) _} = pluginResponse $ do
3842
nfp <- getNormalizedFilePath plId uri
3943
decls <- getDecls ideState nfp
4044
let actions = mapMaybe (generateAction uri decls) diags
@@ -44,7 +48,7 @@ getDecls :: MonadIO m => IdeState -> NormalizedFilePath -> ExceptT String m [LHs
4448
getDecls state = handleMaybeM "Error: Could not get Parsed Module"
4549
. liftIO
4650
. fmap (fmap (hsmodDecls . unLoc . pm_parsed_source))
47-
. runAction "changeSignature.GetParsedModule" state
51+
. runAction (changeTypeSignatureId <> ".GetParsedModule") state
4852
. use GetParsedModule
4953

5054
-- | Text representing a Declaration's Name
@@ -146,7 +150,7 @@ stripSignature (T.filter (/= '\n') -> sig) = if T.isInfixOf " => " sig
146150

147151
changeSigToCodeAction :: Uri -> ChangeSignature -> Command |? CodeAction
148152
changeSigToCodeAction uri ChangeSignature{..} = InR CodeAction { _title = mkChangeSigTitle declName actualType
149-
, _kind = Just (CodeActionUnknown "quickfix.changeSignature")
153+
, _kind = Just (CodeActionUnknown ("quickfix." <> changeTypeSignatureId))
150154
, _diagnostics = Just $ List [diagnostic]
151155
, _isPreferred = Nothing
152156
, _disabled = Nothing

plugins/hls-change-type-signature-plugin/test/Main.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -32,7 +32,7 @@ main :: IO ()
3232
main = defaultTestRunner test
3333

3434
changeTypeSignaturePlugin :: PluginDescriptor IdeState
35-
changeTypeSignaturePlugin = ChangeTypeSignature.descriptor "changeTypeSignature"
35+
changeTypeSignaturePlugin = ChangeTypeSignature.descriptor
3636

3737
test :: TestTree
3838
test = testGroup "changeTypeSignature" [
@@ -112,8 +112,8 @@ findChangeTypeActions = pure . filter isChangeTypeAction . rights . map toEither
112112
isChangeTypeAction CodeAction{_kind} = case _kind of
113113
Nothing -> False
114114
Just kind -> case kind of
115-
"quickfix.changeSignature" -> True
116-
_ -> False
115+
"quickfix.changeTypeSignature" -> True
116+
_ -> False
117117

118118

119119
regexTest :: FilePath -> Text -> Bool -> TestTree

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

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -48,14 +48,13 @@ import Development.IDE (GetModSummary (..),
4848
GhcSessionIO (..), IdeState,
4949
ModSummaryResult (..),
5050
NeedsCompilation (NeedsCompilation),
51-
evalGhcEnv,
51+
VFSModified (..), evalGhcEnv,
5252
hscEnvWithImportPaths,
5353
printOutputable, runAction,
5454
textToStringBuffer,
5555
toNormalizedFilePath',
5656
uriToFilePath', useNoFile_,
57-
useWithStale_, use_,
58-
VFSModified(..))
57+
useWithStale_, use_)
5958
import Development.IDE.Core.Rules (GhcSessionDepsConfig (..),
6059
ghcSessionDepsDefinition)
6160
import Development.IDE.GHC.Compat hiding (typeKind, unitState)
@@ -91,7 +90,8 @@ import Ide.Plugin.Eval.Code (Statement, asStatements,
9190
evalSetup, myExecStmt,
9291
propSetup, resultRange,
9392
testCheck, testRanges)
94-
import Ide.Plugin.Eval.Config (getEvalConfig, EvalConfig(..))
93+
import Ide.Plugin.Eval.Config (EvalConfig (..),
94+
getEvalConfig)
9595
import Ide.Plugin.Eval.GHC (addImport, addPackages,
9696
hasPackage, showDynFlags)
9797
import Ide.Plugin.Eval.Parse.Comments (commentsToSections)
@@ -101,7 +101,7 @@ import Ide.Plugin.Eval.Types
101101
import Ide.Plugin.Eval.Util (gStrictTry, isLiterate,
102102
logWith, response', timed)
103103
import Ide.PluginUtils (handleMaybe, handleMaybeM,
104-
response)
104+
pluginResponse)
105105
import Ide.Types
106106
import Language.LSP.Server
107107
import Language.LSP.Types hiding
@@ -127,7 +127,7 @@ codeLens st plId CodeLensParams{_textDocument} =
127127
let dbg = logWith st
128128
perf = timed dbg
129129
in perf "codeLens" $
130-
response $ do
130+
pluginResponse $ do
131131
let TextDocumentIdentifier uri = _textDocument
132132
fp <- handleMaybe "uri" $ uriToFilePath' uri
133133
let nfp = toNormalizedFilePath' fp

plugins/hls-gadt-plugin/src/Ide/Plugin/GADT.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -52,7 +52,7 @@ toGADTSyntaxCommandId = "GADT.toGADT"
5252

5353
-- | A command replaces H98 data decl with GADT decl in place
5454
toGADTCommand :: PluginId -> CommandFunction IdeState ToGADTParams
55-
toGADTCommand plId state ToGADTParams{..} = response $ do
55+
toGADTCommand plId state ToGADTParams{..} = pluginResponse $ do
5656
nfp <- getNormalizedFilePath plId uri
5757
(decls, exts) <- getInRangeH98DeclsAndExts state range nfp
5858
(L ann decl) <- case decls of
@@ -82,7 +82,7 @@ toGADTCommand plId state ToGADTParams{..} = response $ do
8282
Nothing Nothing
8383

8484
codeActionHandler :: PluginMethodHandler IdeState TextDocumentCodeAction
85-
codeActionHandler state plId (CodeActionParams _ _ doc range _) = response $ do
85+
codeActionHandler state plId (CodeActionParams _ _ doc range _) = pluginResponse $ do
8686
nfp <- getNormalizedFilePath plId (doc ^. L.uri)
8787
(inRangeH98Decls, _) <- getInRangeH98DeclsAndExts state range nfp
8888
let actions = map (mkAction . printOutputable . tcdLName . unLoc) inRangeH98Decls

0 commit comments

Comments
 (0)