{-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Ide.Plugin.Eval.Util (
timed,
isLiterate,
response',
gStrictTry,
logWith,
) where
import Control.Exception (SomeException, evaluate)
import Control.Monad.IO.Class (MonadIO (liftIO))
import Control.Monad.Trans.Except (ExceptT (..), runExceptT)
import Data.Aeson (Value (Null))
import Data.String (IsString (fromString))
import qualified Data.Text as T
import Development.IDE (IdeState, Priority (..),
ideLogger, logPriority)
import Development.IDE.GHC.Compat.Util (MonadCatch, catch)
import GHC.Exts (toList)
import GHC.Stack (HasCallStack, callStack,
srcLocFile, srcLocStartCol,
srcLocStartLine)
import Language.LSP.Server
import Language.LSP.Types
import System.FilePath (takeExtension)
import System.Time.Extra (duration, showDuration)
import UnliftIO.Exception (catchAny)
timed :: MonadIO m => (t -> String -> m a) -> t -> m b -> m b
timed :: forall (m :: * -> *) t a b.
MonadIO m =>
(t -> String -> m a) -> t -> m b -> m b
timed t -> String -> m a
out t
name m b
op = do
(Seconds
secs, b
r) <- forall (m :: * -> *) a. MonadIO m => m a -> m (Seconds, a)
duration m b
op
a
_ <- t -> String -> m a
out t
name (Seconds -> String
showDuration Seconds
secs)
forall (m :: * -> *) a. Monad m => a -> m a
return b
r
logWith :: (HasCallStack, MonadIO m, Show a1, Show a2) => IdeState -> a1 -> a2 -> m ()
logWith :: forall (m :: * -> *) a1 a2.
(HasCallStack, MonadIO m, Show a1, Show a2) =>
IdeState -> a1 -> a2 -> m ()
logWith IdeState
state a1
key a2
val =
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. Logger -> Priority -> Text -> IO ()
logPriority (IdeState -> Logger
ideLogger IdeState
state) Priority
logLevel forall a b. (a -> b) -> a -> b
$
[Text] -> Text
T.unwords
[String -> Text
T.pack String
logWithPos, forall a. Show a => a -> Text
asT a1
key, forall a. Show a => a -> Text
asT a2
val]
where
logWithPos :: String
logWithPos =
let stk :: [Item CallStack]
stk = forall l. IsList l => l -> [Item l]
toList HasCallStack => CallStack
callStack
pr :: SrcLoc -> String
pr SrcLoc
pos = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [SrcLoc -> String
srcLocFile SrcLoc
pos, String
":", forall a. Show a => a -> String
show forall b c a. (b -> c) -> (a -> b) -> a -> c
. SrcLoc -> Int
srcLocStartLine forall a b. (a -> b) -> a -> b
$ SrcLoc
pos, String
":", forall a. Show a => a -> String
show forall b c a. (b -> c) -> (a -> b) -> a -> c
. SrcLoc -> Int
srcLocStartCol forall a b. (a -> b) -> a -> b
$ SrcLoc
pos]
in if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(String, SrcLoc)]
stk then String
"" else SrcLoc -> String
pr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> a
head forall a b. (a -> b) -> a -> b
$ [(String, SrcLoc)]
stk
asT :: Show a => a -> T.Text
asT :: forall a. Show a => a -> Text
asT = String -> Text
T.pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show
logLevel :: Priority
logLevel :: Priority
logLevel = Priority
Debug
isLiterate :: FilePath -> Bool
isLiterate :: String -> Bool
isLiterate String
x = String -> String
takeExtension String
x forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String
".lhs", String
".lhs-boot"]
response' :: ExceptT String (LspM c) WorkspaceEdit -> LspM c (Either ResponseError Value)
response' :: forall c.
ExceptT String (LspM c) WorkspaceEdit
-> LspM c (Either ResponseError Value)
response' ExceptT String (LspT c IO) WorkspaceEdit
act = do
Either String WorkspaceEdit
res <- forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT ExceptT String (LspT c IO) WorkspaceEdit
act
forall (m :: * -> *) a.
MonadUnliftIO m =>
m a -> (SomeException -> m a) -> m a
`catchAny` forall (m :: * -> *) b.
Monad m =>
SomeException -> m (Either String b)
showErr
case Either String WorkspaceEdit
res of
Left String
e ->
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. a -> Either a b
Left (ErrorCode -> Text -> Maybe Value -> ResponseError
ResponseError ErrorCode
InternalError (forall a. IsString a => String -> a
fromString String
e) forall a. Maybe a
Nothing)
Right WorkspaceEdit
a -> do
LspId 'WorkspaceApplyEdit
_ <- forall (m :: Method 'FromServer 'Request) (f :: * -> *) config.
MonadLsp config f =>
SServerMethod m
-> MessageParams m
-> (Either ResponseError (ResponseResult m) -> f ())
-> f (LspId m)
sendRequest SMethod 'WorkspaceApplyEdit
SWorkspaceApplyEdit (Maybe Text -> WorkspaceEdit -> ApplyWorkspaceEditParams
ApplyWorkspaceEditParams forall a. Maybe a
Nothing WorkspaceEdit
a) (\Either ResponseError (ResponseResult 'WorkspaceApplyEdit)
_ -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. b -> Either a b
Right Value
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 =
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> (e -> m a) -> m a
catch
(m b
op forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. b -> Either a b
Right forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. MonadIO m => a -> m a
gevaluate)
forall (m :: * -> *) b.
Monad m =>
SomeException -> m (Either String b)
showErr
gevaluate :: MonadIO m => a -> m a
gevaluate :: forall (m :: * -> *) a. MonadIO m => a -> m a
gevaluate = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> IO a
evaluate
showErr :: Monad m => SomeException -> m (Either String b)
showErr :: forall (m :: * -> *) b.
Monad m =>
SomeException -> m (Either String b)
showErr = forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. a -> Either a b
Left forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show