@@ -21,38 +21,51 @@ module Development.IDE.Types.Logger
2121 , priorityToHsLoggerPriority
2222 , LoggingColumn (.. )
2323 , cmapWithPrio
24+ , withBacklog
25+ , lspClientMessageRecorder
26+ , lspClientLogRecorder
2427 , module PrettyPrinterModule
2528 , renderStrict
2629 ) where
2730
28- import Control.Concurrent (myThreadId )
29- import Control.Concurrent.Extra (Lock , newLock , withLock )
30- import Control.Exception (IOException )
31- import Control.Monad (forM_ , when , (>=>) )
32- import Control.Monad.IO.Class (MonadIO (liftIO ))
33- import Data.Functor.Contravariant (Contravariant (contramap ))
34- import Data.Maybe (fromMaybe )
35- import Data.Text (Text )
36- import qualified Data.Text as T
37- import qualified Data.Text as Text
38- import qualified Data.Text.IO as Text
39- import Data.Time (defaultTimeLocale , formatTime ,
40- getCurrentTime )
41- import GHC.Stack (CallStack , HasCallStack ,
42- SrcLoc (SrcLoc , srcLocModule , srcLocStartCol , srcLocStartLine ),
43- callStack , getCallStack ,
44- withFrozenCallStack )
45- import Prettyprinter as PrettyPrinterModule
46- import Prettyprinter.Render.Text (renderStrict )
47- import System.IO (Handle , IOMode (AppendMode ),
48- hClose , hFlush , hSetEncoding ,
49- openFile , stderr , utf8 )
50- import qualified System.Log.Formatter as HSL
51- import qualified System.Log.Handler as HSL
52- import qualified System.Log.Handler.Simple as HSL
53- import qualified System.Log.Logger as HsLogger
54- import UnliftIO (MonadUnliftIO , displayException ,
55- finally , try )
31+ import Control.Concurrent (MVar , myThreadId , tryReadMVar )
32+ import Control.Concurrent.Extra (Lock , newLock , withLock )
33+ import Control.Concurrent.STM (atomically , newTQueueIO ,
34+ writeTQueue )
35+ import Control.Concurrent.STM.TQueue (flushTQueue )
36+ import Control.Exception (IOException )
37+ import Control.Monad (forM_ , when , (>=>) )
38+ import Control.Monad.IO.Class (MonadIO (liftIO ))
39+ import Data.Foldable (for_ )
40+ import Data.Functor.Contravariant (Contravariant (contramap ))
41+ import Data.Maybe (fromMaybe )
42+ import Data.Text (Text )
43+ import qualified Data.Text as T
44+ import qualified Data.Text as Text
45+ import qualified Data.Text.IO as Text
46+ import Data.Time (defaultTimeLocale , formatTime ,
47+ getCurrentTime )
48+ import GHC.Stack (CallStack , HasCallStack ,
49+ SrcLoc (SrcLoc , srcLocModule , srcLocStartCol , srcLocStartLine ),
50+ callStack , getCallStack ,
51+ withFrozenCallStack )
52+ import Language.LSP.Server
53+ import qualified Language.LSP.Server as LSP
54+ import Language.LSP.Types (LogMessageParams (.. ),
55+ MessageType (.. ),
56+ SMethod (SWindowLogMessage , SWindowShowMessage ),
57+ ShowMessageParams (.. ))
58+ import Prettyprinter as PrettyPrinterModule
59+ import Prettyprinter.Render.Text (renderStrict )
60+ import System.IO (Handle , IOMode (AppendMode ),
61+ hClose , hFlush , hSetEncoding ,
62+ openFile , stderr , utf8 )
63+ import qualified System.Log.Formatter as HSL
64+ import qualified System.Log.Handler as HSL
65+ import qualified System.Log.Handler.Simple as HSL
66+ import qualified System.Log.Logger as HsLogger
67+ import UnliftIO (MonadUnliftIO , displayException ,
68+ finally , try )
5669
5770data Priority
5871-- Don't change the ordering of this type or you will mess up the Ord
@@ -204,10 +217,10 @@ makeDefaultHandleRecorder columns minPriority lock handle = do
204217
205218priorityToHsLoggerPriority :: Priority -> HsLogger. Priority
206219priorityToHsLoggerPriority = \ case
207- Debug -> HsLogger. DEBUG
208- Info -> HsLogger. INFO
209- Warning -> HsLogger. WARNING
210- Error -> HsLogger. ERROR
220+ Debug -> HsLogger. DEBUG
221+ Info -> HsLogger. INFO
222+ Warning -> HsLogger. WARNING
223+ Error -> HsLogger. ERROR
211224
212225-- | The purpose of setting up `hslogger` at all is that `hie-bios` uses
213226-- `hslogger` to output compilation logs. The easiest way to merge these logs
@@ -290,3 +303,50 @@ textWithPriorityToText columns WithPriority{ priority, callStack_, payload } = d
290303 pure (threadIdToText threadId)
291304 PriorityColumn -> pure (priorityToText priority)
292305 DataColumn -> pure payload
306+
307+ -- | Given a 'Recorder' that requires an argument, and an 'MVar' that
308+ -- will eventually be filled with that argument, produces a 'Recorder'
309+ -- that queues up messages until the argument is available, at which
310+ -- point it sends the backlog.
311+ withBacklog :: MVar v -> (v -> Recorder a ) -> IO (Recorder a )
312+ withBacklog argVar recFun = do
313+ backlog <- newTQueueIO
314+ pure $ Recorder $ \ it -> do
315+ marg <- liftIO $ tryReadMVar argVar
316+ case marg of
317+ Nothing -> liftIO $ atomically $ writeTQueue backlog it
318+ Just arg -> do
319+ let recorder = recFun arg
320+ toRecord <- liftIO $ atomically $ flushTQueue backlog
321+ for_ toRecord (logger_ recorder)
322+ logger_ recorder it
323+
324+ -- | Creates a recorder that sends logs to the LSP client via @window/showMessage@ notifications.
325+ lspClientMessageRecorder :: LanguageContextEnv config -> Recorder (WithPriority Text )
326+ lspClientMessageRecorder env = Recorder $ \ WithPriority {.. } ->
327+ LSP. runLspT env $
328+ LSP. sendNotification
329+ SWindowShowMessage
330+ ShowMessageParams
331+ { _xtype = priorityToLsp priority,
332+ _message = payload
333+ }
334+
335+ -- | Creates a recorder that sends logs to the LSP client via @window/logMessage@ notifications.
336+ lspClientLogRecorder :: LanguageContextEnv config -> Recorder (WithPriority Text )
337+ lspClientLogRecorder env = Recorder $ \ WithPriority {.. } ->
338+ LSP. runLspT env $
339+ LSP. sendNotification
340+ SWindowLogMessage
341+ LogMessageParams
342+ { _xtype = priorityToLsp priority,
343+ _message = payload
344+ }
345+
346+ priorityToLsp :: Priority -> MessageType
347+ priorityToLsp =
348+ \ case
349+ Debug -> MtLog
350+ Info -> MtInfo
351+ Warning -> MtWarning
352+ Error -> MtError
0 commit comments