{-# LANGUAGE CPP #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# OPTIONS_GHC -Wno-orphans -Wno-unused-imports #-}
{-# LANGUAGE RecordWildCards #-}
module Ide.Plugin.Eval.Util (
timed,
isLiterate,
response',
gStrictTry,
DynFlagsParsingWarnings,
prettyWarnings,
) where
import Control.Exception (SomeException, evaluate,
fromException)
import Control.Monad.Error.Class (MonadError (throwError))
import Control.Monad.IO.Class (MonadIO (liftIO))
import Control.Monad.Trans.Class (MonadTrans (lift))
import Control.Monad.Trans.Except (ExceptT (..),
runExceptT)
import Data.Aeson (Value)
import Data.Bifunctor (second)
import Data.String (IsString (fromString))
import qualified Data.Text as T
import Development.IDE (IdeState,
printOutputable)
import qualified Development.IDE.Core.PluginUtils as PluginUtils
import qualified Development.IDE.GHC.Compat.Core as Core
import qualified Development.IDE.GHC.Compat.Core as SrcLoc
import Development.IDE.GHC.Compat.Outputable
import Development.IDE.GHC.Compat.Util (MonadCatch, bagToList,
catch)
import GHC.Exts (toList)
import GHC.Stack (HasCallStack, callStack,
srcLocFile,
srcLocStartCol,
srcLocStartLine)
import Ide.Plugin.Error
import Ide.Types (HandlerM,
pluginSendRequest)
import Language.LSP.Protocol.Message
import Language.LSP.Protocol.Types
import Language.LSP.Server
import System.FilePath (takeExtension)
import qualified System.Time.Extra as Extra
import System.Time.Extra (duration, showDuration)
import UnliftIO.Exception (catchAny)
timed :: MonadIO m => (t -> Extra.Seconds -> m a) -> t -> m b -> m b
timed :: forall (m :: * -> *) t a b.
MonadIO m =>
(t -> Seconds -> m a) -> t -> m b -> m b
timed t -> Seconds -> m a
out t
name m b
op = do
(Seconds
secs, b
r) <- m b -> m (Seconds, b)
forall (m :: * -> *) a. MonadIO m => m a -> m (Seconds, a)
duration m b
op
a
_ <- t -> Seconds -> m a
out t
name Seconds
secs
b -> m b
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return b
r
isLiterate :: FilePath -> Bool
isLiterate :: String -> Bool
isLiterate String
x = String -> String
takeExtension String
x String -> [String] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String
".lhs", String
".lhs-boot"]
response' :: ExceptT PluginError (HandlerM c) WorkspaceEdit -> ExceptT PluginError (HandlerM c) (Value |? Null)
response' :: forall c.
ExceptT PluginError (HandlerM c) WorkspaceEdit
-> ExceptT PluginError (HandlerM c) (Value |? Null)
response' ExceptT PluginError (HandlerM c) WorkspaceEdit
act = do
WorkspaceEdit
res <- HandlerM c (Either PluginError WorkspaceEdit)
-> ExceptT PluginError (HandlerM c) WorkspaceEdit
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (ExceptT PluginError (HandlerM c) WorkspaceEdit
-> HandlerM c (Either PluginError WorkspaceEdit)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT ExceptT PluginError (HandlerM c) WorkspaceEdit
act
HandlerM c (Either PluginError WorkspaceEdit)
-> (SomeException -> HandlerM c (Either PluginError WorkspaceEdit))
-> HandlerM c (Either PluginError WorkspaceEdit)
forall (m :: * -> *) a.
MonadUnliftIO m =>
m a -> (SomeException -> m a) -> m a
`catchAny` \SomeException
e -> do
String
res <- SomeException -> HandlerM c String
forall (m :: * -> *). Monad m => SomeException -> m String
showErr SomeException
e
Either PluginError WorkspaceEdit
-> HandlerM c (Either PluginError WorkspaceEdit)
forall a. a -> HandlerM c a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either PluginError WorkspaceEdit
-> HandlerM c (Either PluginError WorkspaceEdit))
-> (Text -> Either PluginError WorkspaceEdit)
-> Text
-> HandlerM c (Either PluginError WorkspaceEdit)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PluginError -> Either PluginError WorkspaceEdit
forall a b. a -> Either a b
Left (PluginError -> Either PluginError WorkspaceEdit)
-> (Text -> PluginError)
-> Text
-> Either PluginError WorkspaceEdit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> PluginError
PluginInternalError (Text -> HandlerM c (Either PluginError WorkspaceEdit))
-> Text -> HandlerM c (Either PluginError WorkspaceEdit)
forall a b. (a -> b) -> a -> b
$ String -> Text
forall a. IsString a => String -> a
fromString String
res)
LspId 'Method_WorkspaceApplyEdit
_ <- HandlerM c (LspId 'Method_WorkspaceApplyEdit)
-> ExceptT
PluginError (HandlerM c) (LspId 'Method_WorkspaceApplyEdit)
forall (m :: * -> *) a. Monad m => m a -> ExceptT PluginError m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (HandlerM c (LspId 'Method_WorkspaceApplyEdit)
-> ExceptT
PluginError (HandlerM c) (LspId 'Method_WorkspaceApplyEdit))
-> HandlerM c (LspId 'Method_WorkspaceApplyEdit)
-> ExceptT
PluginError (HandlerM c) (LspId 'Method_WorkspaceApplyEdit)
forall a b. (a -> b) -> a -> b
$ SServerMethod 'Method_WorkspaceApplyEdit
-> MessageParams 'Method_WorkspaceApplyEdit
-> (Either
(TResponseError 'Method_WorkspaceApplyEdit)
(MessageResult 'Method_WorkspaceApplyEdit)
-> HandlerM c ())
-> HandlerM c (LspId 'Method_WorkspaceApplyEdit)
forall (m :: Method 'ServerToClient 'Request) config.
SServerMethod m
-> MessageParams m
-> (Either (TResponseError m) (MessageResult m)
-> HandlerM config ())
-> HandlerM config (LspId m)
pluginSendRequest SServerMethod 'Method_WorkspaceApplyEdit
SMethod_WorkspaceApplyEdit (Maybe Text -> WorkspaceEdit -> ApplyWorkspaceEditParams
ApplyWorkspaceEditParams Maybe Text
forall a. Maybe a
Nothing WorkspaceEdit
res) (\Either
(TResponseError 'Method_WorkspaceApplyEdit)
(MessageResult 'Method_WorkspaceApplyEdit)
_ -> () -> HandlerM c ()
forall a. a -> HandlerM c a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
(Value |? Null) -> ExceptT PluginError (HandlerM c) (Value |? Null)
forall a. a -> ExceptT PluginError (HandlerM c) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Value |? Null)
-> ExceptT PluginError (HandlerM c) (Value |? Null))
-> (Value |? Null)
-> ExceptT PluginError (HandlerM c) (Value |? Null)
forall a b. (a -> b) -> a -> b
$ Null -> Value |? Null
forall a b. b -> a |? b
InR Null
Null
gStrictTry :: (MonadIO m, MonadCatch m) => m b -> m (Either String b)
gStrictTry :: forall (m :: * -> *) b.
(MonadIO m, MonadCatch m) =>
m b -> m (Either String b)
gStrictTry m b
op =
m (Either String b)
-> (SomeException -> m (Either String b)) -> m (Either String b)
forall (m :: * -> *) e a.
(HasCallStack, MonadCatch m, Exception e) =>
m a -> (e -> m a) -> m a
catch
(m b
op m b -> (b -> m (Either String b)) -> m (Either String b)
forall a b. m a -> (a -> m b) -> m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (b -> Either String b) -> m b -> m (Either String b)
forall a b. (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap b -> Either String b
forall a b. b -> Either a b
Right (m b -> m (Either String b))
-> (b -> m b) -> b -> m (Either String b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> m b
forall (m :: * -> *) a. MonadIO m => a -> m a
gevaluate)
((String -> Either String b) -> m String -> m (Either String b)
forall a b. (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Either String b
forall a b. a -> Either a b
Left (m String -> m (Either String b))
-> (SomeException -> m String)
-> SomeException
-> m (Either String b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SomeException -> m String
forall (m :: * -> *). Monad m => SomeException -> m String
showErr)
gevaluate :: MonadIO m => a -> m a
gevaluate :: forall (m :: * -> *) a. MonadIO m => a -> m a
gevaluate = IO a -> m a
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO a -> m a) -> (a -> IO a) -> a -> m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> IO a
forall a. a -> IO a
evaluate
showErr :: Monad m => SomeException -> m String
showErr :: forall (m :: * -> *). Monad m => SomeException -> m String
showErr SomeException
e =
#if MIN_VERSION_ghc(9,3,0)
case SomeException -> Maybe SourceError
forall e. Exception e => SomeException -> Maybe e
fromException SomeException
e of
Just (SourceError Messages GhcMessage
msgs) -> String -> m String
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> m String) -> String -> m String
forall a b. (a -> b) -> a -> b
$ SDocContext -> SDoc -> String
renderWithContext SDocContext
defaultSDocContext
(SDoc -> String) -> SDoc -> String
forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat
([SDoc] -> SDoc) -> [SDoc] -> SDoc
forall a b. (a -> b) -> a -> b
$ Bag SDoc -> [SDoc]
forall a. Bag a -> [a]
bagToList
(Bag SDoc -> [SDoc]) -> Bag SDoc -> [SDoc]
forall a b. (a -> b) -> a -> b
$ (MsgEnvelope GhcMessage -> SDoc)
-> Bag (MsgEnvelope GhcMessage) -> Bag SDoc
forall a b. (a -> b) -> Bag a -> Bag b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat ([SDoc] -> SDoc)
-> (MsgEnvelope GhcMessage -> [SDoc])
-> MsgEnvelope GhcMessage
-> SDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DecoratedSDoc -> [SDoc]
unDecorated
(DecoratedSDoc -> [SDoc])
-> (MsgEnvelope GhcMessage -> DecoratedSDoc)
-> MsgEnvelope GhcMessage
-> [SDoc]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DiagnosticOpts GhcMessage -> GhcMessage -> DecoratedSDoc
forall a. Diagnostic a => DiagnosticOpts a -> a -> DecoratedSDoc
diagnosticMessage
#if MIN_VERSION_ghc(9,5,0)
(forall a. Diagnostic a => DiagnosticOpts a
defaultDiagnosticOpts @GhcMessage)
#endif
(GhcMessage -> DecoratedSDoc)
-> (MsgEnvelope GhcMessage -> GhcMessage)
-> MsgEnvelope GhcMessage
-> DecoratedSDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MsgEnvelope GhcMessage -> GhcMessage
forall e. MsgEnvelope e -> e
errMsgDiagnostic)
(Bag (MsgEnvelope GhcMessage) -> Bag SDoc)
-> Bag (MsgEnvelope GhcMessage) -> Bag SDoc
forall a b. (a -> b) -> a -> b
$ Messages GhcMessage -> Bag (MsgEnvelope GhcMessage)
forall e. Messages e -> Bag (MsgEnvelope e)
getMessages Messages GhcMessage
msgs
Maybe SourceError
_ ->
#endif
String -> m String
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> m String)
-> (SomeException -> String) -> SomeException -> m String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SomeException -> String
forall a. Show a => a -> String
show (SomeException -> m String) -> SomeException -> m String
forall a b. (a -> b) -> a -> b
$ SomeException
e
#if MIN_VERSION_ghc(9,8,0)
type DynFlagsParsingWarnings = Messages DriverMessage
prettyWarnings :: DynFlagsParsingWarnings -> String
prettyWarnings = printWithoutUniques . pprMessages (defaultDiagnosticOpts @DriverMessage)
#else
type DynFlagsParsingWarnings = [Core.Warn]
prettyWarnings :: DynFlagsParsingWarnings -> String
prettyWarnings :: DynFlagsParsingWarnings -> String
prettyWarnings = [String] -> String
unlines ([String] -> String)
-> (DynFlagsParsingWarnings -> [String])
-> DynFlagsParsingWarnings
-> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Warn -> String) -> DynFlagsParsingWarnings -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Warn -> String
prettyWarn
prettyWarn :: Core.Warn -> String
prettyWarn :: Warn -> String
prettyWarn Core.Warn{Located String
DiagnosticReason
warnReason :: DiagnosticReason
warnMsg :: Located String
warnReason :: Warn -> DiagnosticReason
warnMsg :: Warn -> Located String
..} =
Text -> String
T.unpack (SrcSpan -> Text
forall a. Outputable a => a -> Text
printOutputable (SrcSpan -> Text) -> SrcSpan -> Text
forall a b. (a -> b) -> a -> b
$ Located String -> SrcSpan
forall a. HasSrcSpan a => a -> SrcSpan
SrcLoc.getLoc Located String
warnMsg) String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
": warning:\n"
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Located String -> String
forall l e. GenLocated l e -> e
SrcLoc.unLoc Located String
warnMsg
#endif