Skip to content

Add throwPluginError to Plugin Utilities #2924

New issue

Have a question about this project? Sign up for a free GitHub account to open an issue and contact its maintainers and the community.

By clicking “Sign up for GitHub”, you agree to our terms of service and privacy statement. We’ll occasionally send you account related emails.

Already on GitHub? Sign in to your account

Merged
merged 13 commits into from
May 27, 2022
Merged
6 changes: 3 additions & 3 deletions exe/Plugins.hs
Original file line number Diff line number Diff line change
Expand Up @@ -157,7 +157,7 @@ idePlugins recorder includeExamples = pluginDescToIdePlugins allPlugins
Brittany.descriptor "brittany" :
#endif
#if callHierarchy
CallHierarchy.descriptor "callHierarchy":
CallHierarchy.descriptor :
#endif
#if class
Class.descriptor "class" :
Expand Down Expand Up @@ -187,13 +187,13 @@ idePlugins recorder includeExamples = pluginDescToIdePlugins allPlugins
Splice.descriptor "splice" :
#endif
#if alternateNumberFormat
AlternateNumberFormat.descriptor pluginRecorder "alternateNumberFormat" :
AlternateNumberFormat.descriptor pluginRecorder :
#endif
#if selectionRange
SelectionRange.descriptor "selectionRange" :
#endif
#if changeTypeSignature
ChangeTypeSignature.descriptor "changeTypeSignature" :
ChangeTypeSignature.descriptor :
#endif
#if gadt
GADT.descriptor "gadt" :
Expand Down
13 changes: 9 additions & 4 deletions hls-plugin-api/src/Ide/PluginUtils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,14 +28,14 @@ module Ide.PluginUtils
positionInRange,
usePropertyLsp,
getNormalizedFilePath,
response,
pluginResponse,
handleMaybe,
handleMaybeM,
throwPluginError
)
where


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

-- ---------------------------------------------------------------------
throwPluginError :: Monad m => PluginId -> String -> String -> ExceptT String m b
throwPluginError (PluginId who) what where' = throwE msg
where
msg = (T.unpack who) <> " failed with " <> what <> " at " <> where'

handleMaybe :: Monad m => e -> Maybe b -> ExceptT e m b
handleMaybe msg = maybe (throwE msg) return

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

response :: Monad m => ExceptT String m a -> m (Either ResponseError a)
response =
pluginResponse :: Monad m => ExceptT String m a -> m (Either ResponseError a)
pluginResponse =
fmap (first (\msg -> ResponseError InternalError (fromString msg) Nothing))
. runExceptT
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,7 @@ module Ide.Plugin.AlternateNumberFormat (descriptor, Log(..)) where
import Control.Lens ((^.))
import Control.Monad.Except (ExceptT, MonadIO, liftIO)
import qualified Data.HashMap.Strict as HashMap
import Data.String (IsString)
import Data.Text (Text)
import qualified Data.Text as T
import Development.IDE (GetParsedModule (GetParsedModule),
Expand All @@ -31,19 +32,22 @@ import Ide.Plugin.Conversion (AlternateFormat,
alternateFormat)
import Ide.Plugin.Literals
import Ide.PluginUtils (getNormalizedFilePath,
handleMaybeM, response)
handleMaybeM, pluginResponse)
import Ide.Types
import Language.LSP.Types
import Language.LSP.Types.Lens (uri)
import qualified Language.LSP.Types.Lens as L

newtype Log = LogShake Shake.Log deriving Show

instance Pretty Log where
pretty = \case
LogShake log -> pretty log

descriptor :: Recorder (WithPriority Log) -> PluginId -> PluginDescriptor IdeState
descriptor recorder plId = (defaultPluginDescriptor plId)
alternateNumberFormatId :: IsString a => a
alternateNumberFormatId = "alternateNumberFormat"

descriptor :: Recorder (WithPriority Log) -> PluginDescriptor IdeState
descriptor recorder = (defaultPluginDescriptor alternateNumberFormatId)
{ pluginHandlers = mkPluginHandler STextDocumentCodeAction codeActionHandler
, pluginRules = collectLiteralsRule recorder
}
Expand Down Expand Up @@ -83,8 +87,8 @@ collectLiteralsRule recorder = define (cmapWithPrio LogShake recorder) $ \Collec
getExtensions = map GhcExtension . toList . extensionFlags . ms_hspp_opts . pm_mod_summary

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

getFirstPragma :: MonadIO m => IdeState -> NormalizedFilePath -> ExceptT String m NextPragmaInfo
getFirstPragma state nfp = handleMaybeM "Error: Could not get NextPragmaInfo" $ do
ghcSession <- liftIO $ runAction "AlternateNumberFormat.GhcSession" state $ useWithStale GhcSession nfp
(_, fileContents) <- liftIO $ runAction "AlternateNumberFormat.GetFileContents" state $ getFileContents nfp
ghcSession <- liftIO $ runAction (alternateNumberFormatId <> ".GhcSession") state $ useWithStale GhcSession nfp
Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

This does make me feel like we need some kind of "component context" for our logs and errors.... seems to be one of those things that everyone invents eventually.

Copy link
Collaborator Author

@drsooch drsooch May 24, 2022

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Yeah #2919 I'm going to look to enhance the pluginRecorder to hopefully be able to decorate it with the plugin id. The other question is how to integrate that with runAction logging.

This is one of the big things I want to look at considering all plugins have this same model of id.Action.

Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Yeah, I guess what I'm wondering is whether we want some more generic "log context" stack in our recorders or something. It comes up a lot.

Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I strongly want something that can wrap runAction and return ExceptT String m ActionResult, then we can clean much boilerplate code.

(_, fileContents) <- liftIO $ runAction (alternateNumberFormatId <> ".GetFileContents") state $ getFileContents nfp
case ghcSession of
Just (hscEnv -> hsc_dflags -> sessionDynFlags, _) -> pure $ Just $ getNextPragmaInfo sessionDynFlags fileContents
Nothing -> pure Nothing
Nothing -> pure Nothing

requestLiterals :: MonadIO m => IdeState -> NormalizedFilePath -> ExceptT String m CollectLiteralsResult
requestLiterals state = handleMaybeM "Error: Could not Collect Literals"
. liftIO
. runAction "AlternateNumberFormat.CollectLiterals" state
. runAction (alternateNumberFormatId <> ".CollectLiterals") state
. use CollectLiterals
2 changes: 1 addition & 1 deletion plugins/hls-alternate-number-format-plugin/test/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,7 @@ main :: IO ()
main = defaultTestRunner test

alternateNumberFormatPlugin :: PluginDescriptor IdeState
alternateNumberFormatPlugin = AlternateNumberFormat.descriptor mempty "alternateNumberFormat"
alternateNumberFormatPlugin = AlternateNumberFormat.descriptor mempty

-- NOTE: For whatever reason, this plugin does not play nice with creating Code Actions on time.
-- As a result tests will mostly pass if `import Prelude` is added at the top. We (mostly fendor) surmise this has something
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -5,8 +5,8 @@ import qualified Ide.Plugin.CallHierarchy.Internal as X
import Ide.Types
import Language.LSP.Types

descriptor :: PluginId -> PluginDescriptor IdeState
descriptor plId = (defaultPluginDescriptor plId)
descriptor :: PluginDescriptor IdeState
descriptor = (defaultPluginDescriptor X.callHierarchyId)
{ Ide.Types.pluginHandlers = mkPluginHandler STextDocumentPrepareCallHierarchy X.prepareCallHierarchy
<> mkPluginHandler SCallHierarchyIncomingCalls X.incomingCalls
<> mkPluginHandler SCallHierarchyOutgoingCalls X.outgoingCalls
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,7 @@ module Ide.Plugin.CallHierarchy.Internal (
prepareCallHierarchy
, incomingCalls
, outgoingCalls
, callHierarchyId
) where

import Control.Lens ((^.))
Expand All @@ -35,23 +36,23 @@ import GHC.Conc.Sync
import HieDb (Symbol (Symbol))
import qualified Ide.Plugin.CallHierarchy.Query as Q
import Ide.Plugin.CallHierarchy.Types
import Ide.PluginUtils (getNormalizedFilePath,
handleMaybe, pluginResponse,
throwPluginError)
import Ide.Types
import Language.LSP.Types
import qualified Language.LSP.Types.Lens as L
import Text.Read (readMaybe)

callHierarchyId :: PluginId
callHierarchyId = PluginId "callHierarchy"

-- | Render prepare call hierarchy request.
prepareCallHierarchy :: PluginMethodHandler IdeState TextDocumentPrepareCallHierarchy
prepareCallHierarchy state pluginId param
| Just nfp <- uriToNormalizedFilePath $ toNormalizedUri uri =
liftIO (runAction "CallHierarchy.prepareHierarchy" state (prepareCallHierarchyItem nfp pos)) >>=
\case
Just items -> pure $ Right $ Just $ List items
Nothing -> pure $ Right Nothing
| otherwise = pure $ Left $ responseError $ T.pack $ "Call Hierarchy: uriToNormalizedFilePath failed for: " <> show uri
where
uri = param ^. (L.textDocument . L.uri)
pos = param ^. L.position
prepareCallHierarchy state pluginId param = pluginResponse $ do
nfp <- getNormalizedFilePath pluginId (param ^. L.textDocument ^. L.uri)
items <- liftIO (runAction "CallHierarchy.prepareHierarchy" state (prepareCallHierarchyItem nfp (param ^. L.position)))
pure (List <$> items)

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

-- | Render incoming calls request.
incomingCalls :: PluginMethodHandler IdeState CallHierarchyIncomingCalls
incomingCalls state pluginId param = do
liftIO $ runAction "CallHierarchy.incomingCalls" state $
incomingCalls state pluginId param = pluginResponse $ do
calls <- liftIO $ runAction "CallHierarchy.incomingCalls" state $
queryCalls (param ^. L.item) Q.incomingCalls mkCallHierarchyIncomingCall
mergeIncomingCalls >>=
\case
Just x -> pure $ Right $ Just $ List x
Nothing -> pure $ Left $ responseError "CallHierarchy: IncomingCalls internal error"
mergeIncomingCalls
case calls of
Just x -> pure $ Just $ List x
Nothing -> throwPluginError callHierarchyId "Internal Error" "incomingCalls"
where
mkCallHierarchyIncomingCall :: Vertex -> Action (Maybe CallHierarchyIncomingCall)
mkCallHierarchyIncomingCall = mkCallHierarchyCall CallHierarchyIncomingCall
Expand All @@ -217,13 +218,13 @@ incomingCalls state pluginId param = do

-- Render outgoing calls request.
outgoingCalls :: PluginMethodHandler IdeState CallHierarchyOutgoingCalls
outgoingCalls state pluginId param = do
liftIO $ runAction "CallHierarchy.outgoingCalls" state $
outgoingCalls state pluginId param = pluginResponse $ do
calls <- liftIO $ runAction "CallHierarchy.outgoingCalls" state $
queryCalls (param ^. L.item) Q.outgoingCalls mkCallHierarchyOutgoingCall
mergeOutgoingCalls >>=
\case
Just x -> pure $ Right $ Just $ List x
Nothing -> pure $ Left $ responseError "CallHierarchy: OutgoingCalls internal error"
mergeOutgoingCalls
case calls of
Just x -> pure $ Just $ List x
Nothing -> throwPluginError callHierarchyId "Internal Error" "outgoingCalls"
where
mkCallHierarchyOutgoingCall :: Vertex -> Action (Maybe CallHierarchyOutgoingCall)
mkCallHierarchyOutgoingCall = mkCallHierarchyCall CallHierarchyOutgoingCall
Expand Down
2 changes: 1 addition & 1 deletion plugins/hls-call-hierarchy-plugin/test/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@ import Test.Hls
import Test.Hls.Util (withCanonicalTempDir)

plugin :: PluginDescriptor IdeState
plugin = descriptor "callHierarchy"
plugin = descriptor

main :: IO ()
main = defaultTestRunner $
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,7 @@ import Control.Monad.Trans.Except (ExceptT)
import Data.Foldable (asum)
import qualified Data.HashMap.Strict as Map
import Data.Maybe (mapMaybe)
import Data.String (IsString)
import Data.Text (Text)
import qualified Data.Text as T
import Development.IDE (realSrcSpanToRange)
Expand All @@ -22,19 +23,22 @@ import Development.IDE.GHC.Compat
import Development.IDE.GHC.Util (printOutputable)
import Generics.SYB (extQ, something)
import Ide.PluginUtils (getNormalizedFilePath,
handleMaybeM, response)
handleMaybeM, pluginResponse)
import Ide.Types (PluginDescriptor (..),
PluginId, PluginMethodHandler,
PluginMethodHandler,
defaultPluginDescriptor,
mkPluginHandler)
import Language.LSP.Types
import Text.Regex.TDFA ((=~))

descriptor :: PluginId -> PluginDescriptor IdeState
descriptor plId = (defaultPluginDescriptor plId) { pluginHandlers = mkPluginHandler STextDocumentCodeAction codeActionHandler }
changeTypeSignatureId :: IsString a => a
changeTypeSignatureId = "changeTypeSignature"

descriptor :: PluginDescriptor IdeState
descriptor = (defaultPluginDescriptor changeTypeSignatureId) { pluginHandlers = mkPluginHandler STextDocumentCodeAction codeActionHandler }

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

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

changeSigToCodeAction :: Uri -> ChangeSignature -> Command |? CodeAction
changeSigToCodeAction uri ChangeSignature{..} = InR CodeAction { _title = mkChangeSigTitle declName actualType
, _kind = Just (CodeActionUnknown "quickfix.changeSignature")
, _kind = Just (CodeActionUnknown ("quickfix." <> changeTypeSignatureId))
, _diagnostics = Just $ List [diagnostic]
, _isPreferred = Nothing
, _disabled = Nothing
Expand Down
6 changes: 3 additions & 3 deletions plugins/hls-change-type-signature-plugin/test/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,7 @@ main :: IO ()
main = defaultTestRunner test

changeTypeSignaturePlugin :: PluginDescriptor IdeState
changeTypeSignaturePlugin = ChangeTypeSignature.descriptor "changeTypeSignature"
changeTypeSignaturePlugin = ChangeTypeSignature.descriptor

test :: TestTree
test = testGroup "changeTypeSignature" [
Expand Down Expand Up @@ -112,8 +112,8 @@ findChangeTypeActions = pure . filter isChangeTypeAction . rights . map toEither
isChangeTypeAction CodeAction{_kind} = case _kind of
Nothing -> False
Just kind -> case kind of
"quickfix.changeSignature" -> True
_ -> False
"quickfix.changeTypeSignature" -> True
_ -> False


regexTest :: FilePath -> Text -> Bool -> TestTree
Expand Down
12 changes: 6 additions & 6 deletions plugins/hls-eval-plugin/src/Ide/Plugin/Eval/CodeLens.hs
Original file line number Diff line number Diff line change
Expand Up @@ -48,14 +48,13 @@ import Development.IDE (GetModSummary (..),
GhcSessionIO (..), IdeState,
ModSummaryResult (..),
NeedsCompilation (NeedsCompilation),
evalGhcEnv,
VFSModified (..), evalGhcEnv,
hscEnvWithImportPaths,
printOutputable, runAction,
textToStringBuffer,
toNormalizedFilePath',
uriToFilePath', useNoFile_,
useWithStale_, use_,
VFSModified(..))
useWithStale_, use_)
import Development.IDE.Core.Rules (GhcSessionDepsConfig (..),
ghcSessionDepsDefinition)
import Development.IDE.GHC.Compat hiding (typeKind, unitState)
Expand Down Expand Up @@ -91,7 +90,8 @@ import Ide.Plugin.Eval.Code (Statement, asStatements,
evalSetup, myExecStmt,
propSetup, resultRange,
testCheck, testRanges)
import Ide.Plugin.Eval.Config (getEvalConfig, EvalConfig(..))
import Ide.Plugin.Eval.Config (EvalConfig (..),
getEvalConfig)
import Ide.Plugin.Eval.GHC (addImport, addPackages,
hasPackage, showDynFlags)
import Ide.Plugin.Eval.Parse.Comments (commentsToSections)
Expand All @@ -101,7 +101,7 @@ import Ide.Plugin.Eval.Types
import Ide.Plugin.Eval.Util (gStrictTry, isLiterate,
logWith, response', timed)
import Ide.PluginUtils (handleMaybe, handleMaybeM,
response)
pluginResponse)
import Ide.Types
import Language.LSP.Server
import Language.LSP.Types hiding
Expand All @@ -127,7 +127,7 @@ codeLens st plId CodeLensParams{_textDocument} =
let dbg = logWith st
perf = timed dbg
in perf "codeLens" $
response $ do
pluginResponse $ do
let TextDocumentIdentifier uri = _textDocument
fp <- handleMaybe "uri" $ uriToFilePath' uri
let nfp = toNormalizedFilePath' fp
Expand Down
4 changes: 2 additions & 2 deletions plugins/hls-gadt-plugin/src/Ide/Plugin/GADT.hs
Original file line number Diff line number Diff line change
Expand Up @@ -52,7 +52,7 @@ toGADTSyntaxCommandId = "GADT.toGADT"

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

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