Skip to content

Commit ecec539

Browse files
committed
2 parents 395faf3 + 5afb077 commit ecec539

File tree

11 files changed

+110
-38
lines changed

11 files changed

+110
-38
lines changed

exe/Main.hs

+26-8
Original file line numberDiff line numberDiff line change
@@ -5,18 +5,21 @@
55
module Main(main) where
66

77
import Data.Function ((&))
8-
import Development.IDE.Types.Logger (Priority (Debug, Info),
8+
import Development.IDE.Types.Logger (Priority (Debug, Info, Error),
99
WithPriority (WithPriority, priority),
1010
cfilter, cmapWithPrio,
1111
makeDefaultStderrRecorder,
12-
withDefaultRecorder)
12+
withDefaultRecorder, renderStrict, layoutPretty, defaultLayoutOptions, Doc)
1313
import Ide.Arguments (Arguments (..),
1414
GhcideArguments (..),
1515
getArguments)
1616
import Ide.Main (defaultMain)
1717
import qualified Ide.Main as IdeMain
1818
import qualified Plugins
19-
import Prettyprinter (Pretty (pretty))
19+
import Prettyprinter (Pretty (pretty), vcat)
20+
import Development.IDE.Plugin.LSPWindowShowMessageRecorder (makeLspShowMessageRecorder)
21+
import Data.Text (Text)
22+
import Ide.PluginUtils (pluginDescToIdePlugins)
2023

2124
data Log
2225
= LogIdeMain IdeMain.Log
@@ -33,6 +36,7 @@ main = do
3336
-- parser to get logging arguments first or do more complicated things
3437
pluginCliRecorder <- cmapWithPrio pretty <$> makeDefaultStderrRecorder Nothing Info
3538
args <- getArguments "haskell-language-server" (Plugins.idePlugins (cmapWithPrio LogPlugins pluginCliRecorder) False)
39+
(lspRecorder, lspRecorderPlugin) <- makeLspShowMessageRecorder
3640

3741
let (minPriority, logFilePath, includeExamplePlugins) =
3842
case args of
@@ -42,9 +46,23 @@ main = do
4246
_ -> (Info, Nothing, False)
4347

4448
withDefaultRecorder logFilePath Nothing minPriority $ \textWithPriorityRecorder -> do
45-
let recorder =
46-
textWithPriorityRecorder
47-
& cfilter (\WithPriority{ priority } -> priority >= minPriority)
48-
& cmapWithPrio pretty
49+
let
50+
recorder = cmapWithPrio pretty $ mconcat
51+
[textWithPriorityRecorder
52+
& cfilter (\WithPriority{ priority } -> priority >= minPriority)
53+
, lspRecorder
54+
& cfilter (\WithPriority{ priority } -> priority >= Error)
55+
& cmapWithPrio renderDoc
56+
]
57+
plugins = Plugins.idePlugins (cmapWithPrio LogPlugins recorder) includeExamplePlugins
4958

50-
defaultMain (cmapWithPrio LogIdeMain recorder) args (Plugins.idePlugins (cmapWithPrio LogPlugins recorder) includeExamplePlugins)
59+
defaultMain (cmapWithPrio LogIdeMain recorder) args (pluginDescToIdePlugins [lspRecorderPlugin] <> plugins)
60+
61+
renderDoc :: Doc a -> Text
62+
renderDoc d = renderStrict $ layoutPretty defaultLayoutOptions $ vcat
63+
["Unhandled exception, please check your setup and/or the [issue tracker](" <> issueTrackerUrl <> "): "
64+
,d
65+
]
66+
67+
issueTrackerUrl :: Doc a
68+
issueTrackerUrl = "https://github.com/haskell/haskell-language-server/issues"

ghcide/exe/Main.hs

+11-4
Original file line numberDiff line numberDiff line change
@@ -23,11 +23,11 @@ import qualified Development.IDE.Plugin.HLS.GhcIde as GhcIde
2323
import Development.IDE.Types.Logger (Logger (Logger),
2424
LoggingColumn (DataColumn, PriorityColumn),
2525
Pretty (pretty),
26-
Priority (Debug, Info),
26+
Priority (Debug, Info, Error),
2727
Recorder (Recorder),
2828
WithPriority (WithPriority, priority),
2929
cfilter, cmapWithPrio,
30-
makeDefaultStderrRecorder)
30+
makeDefaultStderrRecorder, layoutPretty, renderStrict, payload, defaultLayoutOptions)
3131
import qualified Development.IDE.Types.Logger as Logger
3232
import Development.IDE.Types.Options
3333
import GHC.Stack (emptyCallStack)
@@ -39,6 +39,8 @@ import System.Environment (getExecutablePath)
3939
import System.Exit (exitSuccess)
4040
import System.IO (hPutStrLn, stderr)
4141
import System.Info (compilerVersion)
42+
import Development.IDE.Plugin.LSPWindowShowMessageRecorder (makeLspShowMessageRecorder)
43+
import Control.Lens (Contravariant(contramap))
4244

4345
data Log
4446
= LogIDEMain IDEMain.Log
@@ -86,9 +88,13 @@ main = withTelemetryLogger $ \telemetryLogger -> do
8688

8789
docWithPriorityRecorder <- makeDefaultStderrRecorder (Just [PriorityColumn, DataColumn]) minPriority
8890

91+
(lspRecorder, lspRecorderPlugin) <- makeLspShowMessageRecorder
92+
8993
let docWithFilteredPriorityRecorder@Recorder{ logger_ } =
90-
docWithPriorityRecorder
91-
& cfilter (\WithPriority{ priority } -> priority >= minPriority)
94+
(docWithPriorityRecorder & cfilter (\WithPriority{ priority } -> priority >= minPriority)) <>
95+
(lspRecorder & cmapWithPrio (renderStrict . layoutPretty defaultLayoutOptions)
96+
& cfilter (\WithPriority{ priority } -> priority >= Error)
97+
)
9298

9399
-- exists so old-style logging works. intended to be phased out
94100
let logger = Logger $ \p m -> logger_ (WithPriority p emptyCallStack (pretty m))
@@ -105,6 +111,7 @@ main = withTelemetryLogger $ \telemetryLogger -> do
105111
{ IDEMain.argsProjectRoot = Just argsCwd
106112
, IDEMain.argCommand = argsCommand
107113
, IDEMain.argsLogger = IDEMain.argsLogger arguments <> pure telemetryLogger
114+
, IDEMain.argsHlsPlugins = pluginDescToIdePlugins [lspRecorderPlugin] <> IDEMain.argsHlsPlugins arguments
108115

109116
, IDEMain.argsRules = do
110117
-- install the main and ghcide-plugin rules

ghcide/ghcide.cabal

+1
Original file line numberDiff line numberDiff line change
@@ -202,6 +202,7 @@ library
202202
Development.IDE.Plugin.Completions.Types
203203
Development.IDE.Plugin.CodeAction
204204
Development.IDE.Plugin.CodeAction.ExactPrint
205+
Development.IDE.Plugin.LSPWindowShowMessageRecorder
205206
Development.IDE.Plugin.HLS
206207
Development.IDE.Plugin.HLS.GhcIde
207208
Development.IDE.Plugin.Test

ghcide/session-loader/Development/IDE/Session.hs

+3-2
Original file line numberDiff line numberDiff line change
@@ -99,6 +99,7 @@ import HieDb.Types
9999
import HieDb.Utils
100100
import System.Random (RandomGen)
101101
import qualified System.Random as Random
102+
import Control.Monad.IO.Unlift (MonadUnliftIO)
102103

103104
data Log
104105
= LogSettingInitialDynFlags
@@ -253,7 +254,7 @@ getInitialGhcLibDirDefault recorder rootDir = do
253254
case libDirRes of
254255
CradleSuccess libdir -> pure $ Just $ LibDir libdir
255256
CradleFail err -> do
256-
log Warning $ LogGetInitialGhcLibDirDefaultCradleFail err rootDir hieYaml cradle
257+
log Error $ LogGetInitialGhcLibDirDefaultCradleFail err rootDir hieYaml cradle
257258
pure Nothing
258259
CradleNone -> do
259260
log Warning LogGetInitialGhcLibDirDefaultCradleNone
@@ -845,7 +846,7 @@ should be filtered out, such that we dont have to re-compile everything.
845846
-- | Set the cache-directory based on the ComponentOptions and a list of
846847
-- internal packages.
847848
-- For the exact reason, see Note [Avoiding bad interface files].
848-
setCacheDirs :: MonadIO m => Recorder (WithPriority Log) -> CacheDirs -> DynFlags -> m DynFlags
849+
setCacheDirs :: MonadUnliftIO m => Recorder (WithPriority Log) -> CacheDirs -> DynFlags -> m DynFlags
849850
setCacheDirs recorder CacheDirs{..} dflags = do
850851
logWith recorder Info $ LogInterfaceFilesCacheDir (fromMaybe cacheDir hiCacheDir)
851852
pure $ dflags

ghcide/src/Development/IDE/Core/Rules.hs

+2-2
Original file line numberDiff line numberDiff line change
@@ -628,14 +628,14 @@ readHieFileForSrcFromDisk recorder file = do
628628
ShakeExtras{withHieDb} <- ask
629629
row <- MaybeT $ liftIO $ withHieDb (\hieDb -> HieDb.lookupHieFileFromSource hieDb $ fromNormalizedFilePath file)
630630
let hie_loc = HieDb.hieModuleHieFile row
631-
logWith recorder Logger.Debug $ LogLoadingHieFile file
631+
liftIO $ logWith recorder Logger.Debug $ LogLoadingHieFile file
632632
exceptToMaybeT $ readHieFileFromDisk recorder hie_loc
633633

634634
readHieFileFromDisk :: Recorder (WithPriority Log) -> FilePath -> ExceptT SomeException IdeAction Compat.HieFile
635635
readHieFileFromDisk recorder hie_loc = do
636636
nc <- asks ideNc
637637
res <- liftIO $ tryAny $ loadHieFile (mkUpdater nc) hie_loc
638-
let log = logWith recorder
638+
let log = (liftIO .) . logWith recorder
639639
case res of
640640
Left e -> log Logger.Debug $ LogLoadingHieFileFail hie_loc e
641641
Right _ -> log Logger.Debug $ LogLoadingHieFileSuccess hie_loc

ghcide/src/Development/IDE/LSP/LanguageServer.hs

-12
Original file line numberDiff line numberDiff line change
@@ -71,9 +71,6 @@ instance Pretty Log where
7171
"Cancelled request" <+> viaShow requestId
7272
LogSession log -> pretty log
7373

74-
issueTrackerUrl :: T.Text
75-
issueTrackerUrl = "https://github.com/haskell/haskell-language-server/issues"
76-
7774
-- used to smuggle RankNType WithHieDb through dbMVar
7875
newtype WithHieDbShield = WithHieDbShield WithHieDb
7976

@@ -184,20 +181,11 @@ runLanguageServer recorder options inH outH getHieDbLoc defaultConfig onConfigur
184181

185182
let handleServerException (Left e) = do
186183
log Error $ LogReactorThreadException e
187-
sendErrorMessage e
188184
exitClientMsg
189185
handleServerException (Right _) = pure ()
190186

191-
sendErrorMessage (e :: SomeException) = do
192-
LSP.runLspT env $ LSP.sendNotification SWindowShowMessage $
193-
ShowMessageParams MtError $ T.unlines
194-
[ "Unhandled exception, please [report](" <> issueTrackerUrl <> "): "
195-
, T.pack(show e)
196-
]
197-
198187
exceptionInHandler e = do
199188
log Error $ LogReactorMessageActionException e
200-
sendErrorMessage e
201189

202190
checkCancelled _id act k =
203191
flip finally (clearReqId _id) $

ghcide/src/Development/IDE/Main.hs

+2-2
Original file line numberDiff line numberDiff line change
@@ -31,7 +31,7 @@ import Data.Text.Lazy.Encoding (decodeUtf8)
3131
import qualified Data.Text.Lazy.IO as LT
3232
import Data.Typeable (typeOf)
3333
import Development.IDE (Action, GhcVersion (..),
34-
Priority (Debug), Rules,
34+
Priority (Debug, Error), Rules,
3535
ghcVersion,
3636
hDuplicateTo')
3737
import Development.IDE.Core.Debouncer (Debouncer,
@@ -336,7 +336,7 @@ defaultMain recorder Arguments{..} = withHeapStats (cmapWithPrio LogHeapStats re
336336
_mlibdir <-
337337
setInitialDynFlags (cmapWithPrio LogSession recorder) dir argsSessionLoadingOptions
338338
-- TODO: should probably catch/log/rethrow at top level instead
339-
`catchAny` (\e -> log Debug (LogSetInitialDynFlagsException e) >> pure Nothing)
339+
`catchAny` (\e -> log Error (LogSetInitialDynFlagsException e) >> pure Nothing)
340340

341341
sessionLoader <- loadSessionWithOptions (cmapWithPrio LogSession recorder) argsSessionLoadingOptions dir
342342
config <- LSP.runLspT env LSP.getConfig
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,58 @@
1+
{-# LANGUAGE GADTs #-}
2+
3+
module Development.IDE.Plugin.LSPWindowShowMessageRecorder (makeLspShowMessageRecorder) where
4+
5+
import Control.Monad.IO.Class
6+
import Control.Monad.IO.Unlift (MonadUnliftIO)
7+
import Data.Foldable (for_)
8+
import Data.IORef
9+
import Data.IORef.Extra (atomicModifyIORef'_)
10+
import Data.Text (Text)
11+
import Development.IDE.Types.Logger
12+
import Ide.Types (PluginDescriptor (pluginNotificationHandlers), defaultPluginDescriptor, mkPluginNotificationHandler)
13+
import Language.LSP.Server (LanguageContextEnv, getLspEnv)
14+
import qualified Language.LSP.Server as LSP
15+
import Language.LSP.Types (MessageType (..), SMethod (SInitialized, SWindowShowMessage), ShowMessageParams (..))
16+
17+
-- | Creates a recorder that logs to the LSP stream via WindowShowMessage notifications.
18+
-- The recorder won't attempt to send messages until the LSP stream is initialized.
19+
makeLspShowMessageRecorder ::
20+
IO (Recorder (WithPriority Text), PluginDescriptor c)
21+
makeLspShowMessageRecorder = do
22+
envRef <- newIORef Nothing
23+
-- messages logged before the LSP stream is initialized will be sent when it is
24+
backLogRef <- newIORef []
25+
let recorder = Recorder $ \it -> do
26+
mbenv <- liftIO $ readIORef envRef
27+
case mbenv of
28+
Nothing -> liftIO $ atomicModifyIORef'_ backLogRef (it :)
29+
Just env -> sendMsg env it
30+
-- the plugin captures the language context, so it can be used to send messages
31+
plugin =
32+
(defaultPluginDescriptor "LSPWindowShowMessageRecorder")
33+
{ pluginNotificationHandlers = mkPluginNotificationHandler SInitialized $ \_ _ _ -> do
34+
env <- getLspEnv
35+
liftIO $ writeIORef envRef $ Just env
36+
-- flush the backlog
37+
backLog <- liftIO $ atomicModifyIORef' backLogRef ([],)
38+
for_ (reverse backLog) $ sendMsg env
39+
}
40+
return (recorder, plugin)
41+
42+
sendMsg :: MonadUnliftIO m => LanguageContextEnv config -> WithPriority Text -> m ()
43+
sendMsg env WithPriority {..} =
44+
LSP.runLspT env $
45+
LSP.sendNotification
46+
SWindowShowMessage
47+
ShowMessageParams
48+
{ _xtype = priorityToLsp priority,
49+
_message = payload
50+
}
51+
52+
priorityToLsp :: Priority -> MessageType
53+
priorityToLsp =
54+
\case
55+
Debug -> MtLog
56+
Info -> MtInfo
57+
Warning -> MtWarning
58+
Error -> MtError

ghcide/src/Development/IDE/Types/Logger.hs

+4-7
Original file line numberDiff line numberDiff line change
@@ -22,6 +22,7 @@ module Development.IDE.Types.Logger
2222
, LoggingColumn(..)
2323
, cmapWithPrio
2424
, module PrettyPrinterModule
25+
, renderStrict
2526
) where
2627

2728
import Control.Concurrent (myThreadId)
@@ -95,10 +96,10 @@ data WithPriority a = WithPriority { priority :: Priority, callStack_ :: CallSta
9596
-- | Note that this is logging actions _of the program_, not of the user.
9697
-- You shouldn't call warning/error if the user has caused an error, only
9798
-- if our code has gone wrong and is itself erroneous (e.g. we threw an exception).
98-
data Recorder msg = Recorder
99-
{ logger_ :: forall m. (MonadIO m) => msg -> m () }
99+
newtype Recorder msg = Recorder
100+
{ logger_ :: forall m. (MonadUnliftIO m) => msg -> m () }
100101

101-
logWith :: (HasCallStack, MonadIO m) => Recorder (WithPriority msg) -> Priority -> msg -> m ()
102+
logWith :: (HasCallStack, MonadUnliftIO m) => Recorder (WithPriority msg) -> Priority -> msg -> m ()
102103
logWith recorder priority msg = withFrozenCallStack $ logger_ recorder (WithPriority priority callStack msg)
103104

104105
instance Semigroup (Recorder msg) where
@@ -289,7 +290,3 @@ textWithPriorityToText columns WithPriority{ priority, callStack_, payload } = d
289290
pure (threadIdToText threadId)
290291
PriorityColumn -> pure (priorityToText priority)
291292
DataColumn -> pure payload
292-
293-
294-
295-

hls-graph/hls-graph.cabal

+1
Original file line numberDiff line numberDiff line change
@@ -81,6 +81,7 @@ library
8181
, stm-containers
8282
, time
8383
, transformers
84+
, unliftio
8485
, unordered-containers
8586

8687
if flag(embed-files)

hls-graph/src/Development/IDE/Graph/Internal/Types.hs

+2-1
Original file line numberDiff line numberDiff line change
@@ -36,6 +36,7 @@ import qualified ListT
3636
import StmContainers.Map (Map)
3737
import qualified StmContainers.Map as SMap
3838
import System.Time.Extra (Seconds)
39+
import UnliftIO (MonadUnliftIO)
3940

4041

4142
unwrapDynamic :: forall a . Typeable a => Dynamic -> a
@@ -62,7 +63,7 @@ data SRules = SRules {
6263
-- ACTIONS
6364

6465
newtype Action a = Action {fromAction :: ReaderT SAction IO a}
65-
deriving newtype (Monad, Applicative, Functor, MonadIO, MonadFail, MonadThrow, MonadCatch, MonadMask)
66+
deriving newtype (Monad, Applicative, Functor, MonadIO, MonadFail, MonadThrow, MonadCatch, MonadMask, MonadUnliftIO)
6667

6768
data SAction = SAction {
6869
actionDatabase :: !Database,

0 commit comments

Comments
 (0)