Skip to content

Commit dd00cb8

Browse files
committed
Change logging to use co-log-core instead of hslogger
This started as an attempt to bubble up errors from the VFS as actual errors and return them to the user via the LSP response. However, in fact VFS operations occur in response to notifications, which don't have responses. So all we can do is log the error and drop the change, which is okay. However, that made me look at how the logging works. At the moment we use `hslogger`, which is fine, but isn't so great when it's plugging into part of a larger system. For example, we might want to have a global log handler that sends error-level logs to the client as messages, or uses the `logMessage` method of the LSP spec. But there's no way to intercept the messages sent by the VFS currently. So I switched over to using `co-log-core`, which is also the direction that [HLS is going](haskell/haskell-language-server#2558). `co-log-core` is also a lightweight dependency. It's suboptimal for `lsp-types` to depend on a logging library, however, but that should be fixed when we do haskell#394.
1 parent 28232e6 commit dd00cb8

File tree

17 files changed

+419
-363
lines changed

17 files changed

+419
-363
lines changed

lsp-test/bench/SimpleBench.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -44,7 +44,7 @@ main = do
4444

4545
n <- read . head <$> getArgs
4646

47-
forkIO $ void $ runServerWithHandles hinRead houtWrite server
47+
forkIO $ void $ runServerWithHandles mempty hinRead houtWrite server
4848
liftIO $ putStrLn $ "Starting " <> show n <> " rounds"
4949

5050
i <- newIORef 0

lsp-test/func-test/FuncTest.hs

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -18,9 +18,11 @@ import UnliftIO
1818
import UnliftIO.Concurrent
1919
import Control.Exception
2020
import System.Exit
21+
import qualified Colog.Core as L
2122

2223
main :: IO ()
2324
main = hspec $ do
25+
let logger = (L.cmap show L.logStringStderr)
2426
describe "progress reporting" $
2527
it "sends end notification if thread is killed" $ do
2628
(hinRead, hinWrite) <- createPipe
@@ -48,7 +50,7 @@ main = hspec $ do
4850
takeMVar killVar
4951
killThread tid
5052

51-
forkIO $ void $ runServerWithHandles hinRead houtWrite definition
53+
forkIO $ void $ runServerWithHandles logger hinRead houtWrite definition
5254

5355
Test.runSessionWithHandles hinWrite houtRead Test.defaultConfig Test.fullCaps "." $ do
5456
-- First make sure that we get a $/progress begin notification
@@ -108,7 +110,7 @@ main = hspec $ do
108110
]
109111

110112

111-
server <- async $ void $ runServerWithHandles hinRead houtWrite definition
113+
server <- async $ void $ runServerWithHandles logger hinRead houtWrite definition
112114

113115
let config = Test.defaultConfig
114116
{ Test.initialWorkspaceFolders = Just [wf0]

lsp-test/lsp-test.cabal

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -43,6 +43,7 @@ library
4343
, ansi-terminal
4444
, async
4545
, bytestring
46+
, co-log-core
4647
, conduit
4748
, conduit-parse == 0.2.*
4849
, containers >= 0.5.9
@@ -103,6 +104,7 @@ test-suite func-test
103104
, lsp-test
104105
, lsp
105106
, process
107+
, co-log-core
106108
, lens
107109
, unliftio
108110
, hspec

lsp-test/src/Language/LSP/Test.hs

Lines changed: 12 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,6 @@
11
{-# LANGUAGE OverloadedStrings #-}
22
{-# LANGUAGE TypeOperators #-}
33
{-# LANGUAGE FlexibleContexts #-}
4-
{-# LANGUAGE KindSignatures #-}
54
{-# LANGUAGE GADTs #-}
65
{-# LANGUAGE RankNTypes #-}
76
{-# LANGUAGE TypeInType #-}
@@ -119,7 +118,7 @@ import Data.List
119118
import Data.Maybe
120119
import Language.LSP.Types
121120
import Language.LSP.Types.Lens hiding
122-
(id, capabilities, message, executeCommand, applyEdit, rename)
121+
(id, capabilities, message, executeCommand, applyEdit, rename, to)
123122
import qualified Language.LSP.Types.Lens as LSP
124123
import qualified Language.LSP.Types.Capabilities as C
125124
import Language.LSP.VFS
@@ -135,6 +134,7 @@ import System.Directory
135134
import System.FilePath
136135
import System.Process (ProcessHandle)
137136
import qualified System.FilePath.Glob as Glob
137+
import Control.Monad.State (execState)
138138

139139
-- | Starts a new session.
140140
--
@@ -280,7 +280,7 @@ envOverrideConfig cfg = do
280280
documentContents :: TextDocumentIdentifier -> Session T.Text
281281
documentContents doc = do
282282
vfs <- vfs <$> get
283-
let file = vfsMap vfs Map.! toNormalizedUri (doc ^. uri)
283+
let Just file = vfs ^. vfsMap . at (toNormalizedUri (doc ^. uri))
284284
return (virtualFileText file)
285285

286286
-- | Parses an ApplyEditRequest, checks that it is for the passed document
@@ -348,24 +348,24 @@ sendNotification :: SClientMethod (m :: Method FromClient Notification) -- ^ The
348348
sendNotification STextDocumentDidOpen params = do
349349
let n = NotificationMessage "2.0" STextDocumentDidOpen params
350350
oldVFS <- vfs <$> get
351-
let (newVFS,_) = openVFS oldVFS n
351+
let newVFS = flip execState oldVFS $ openVFS mempty n
352352
modify (\s -> s { vfs = newVFS })
353353
sendMessage n
354354

355355
-- Close a virtual file if we send a close text document notification
356356
sendNotification STextDocumentDidClose params = do
357357
let n = NotificationMessage "2.0" STextDocumentDidClose params
358358
oldVFS <- vfs <$> get
359-
let (newVFS,_) = closeVFS oldVFS n
359+
let newVFS = flip execState oldVFS $ closeVFS mempty n
360360
modify (\s -> s { vfs = newVFS })
361361
sendMessage n
362362

363363
sendNotification STextDocumentDidChange params = do
364-
let n = NotificationMessage "2.0" STextDocumentDidChange params
365-
oldVFS <- vfs <$> get
366-
let (newVFS,_) = changeFromClientVFS oldVFS n
367-
modify (\s -> s { vfs = newVFS })
368-
sendMessage n
364+
let n = NotificationMessage "2.0" STextDocumentDidChange params
365+
oldVFS <- vfs <$> get
366+
let newVFS = flip execState oldVFS $ changeFromClientVFS mempty n
367+
modify (\s -> s { vfs = newVFS })
368+
sendMessage n
369369

370370
sendNotification method params =
371371
case splitClientMethod method of
@@ -594,11 +594,8 @@ executeCodeAction action = do
594594
-- | Adds the current version to the document, as tracked by the session.
595595
getVersionedDoc :: TextDocumentIdentifier -> Session VersionedTextDocumentIdentifier
596596
getVersionedDoc (TextDocumentIdentifier uri) = do
597-
fs <- vfsMap . vfs <$> get
598-
let ver =
599-
case fs Map.!? toNormalizedUri uri of
600-
Just vf -> Just (virtualFileVersion vf)
601-
_ -> Nothing
597+
vfs <- vfs <$> get
598+
let ver = vfs ^? vfsMap . ix (toNormalizedUri uri) . to virtualFileVersion
602599
return (VersionedTextDocumentIdentifier uri ver)
603600

604601
-- | Applys an edit to the document and returns the updated document version.

lsp-test/src/Language/LSP/Test/Session.hs

Lines changed: 12 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,4 @@
11
{-# LANGUAGE CPP #-}
2-
{-# LANGUAGE BangPatterns #-}
32
{-# LANGUAGE GADTs #-}
43
{-# LANGUAGE OverloadedStrings #-}
54
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
@@ -48,7 +47,7 @@ import Control.Monad.Fail
4847
#endif
4948
import Control.Monad.Trans.Reader (ReaderT, runReaderT)
5049
import qualified Control.Monad.Trans.Reader as Reader (ask)
51-
import Control.Monad.Trans.State (StateT, runStateT)
50+
import Control.Monad.Trans.State (StateT, runStateT, execState)
5251
import qualified Control.Monad.Trans.State as State
5352
import qualified Data.ByteString.Lazy.Char8 as B
5453
import Data.Aeson
@@ -80,8 +79,9 @@ import System.Process (ProcessHandle())
8079
#ifndef mingw32_HOST_OS
8180
import System.Process (waitForProcess)
8281
#endif
83-
import System.Timeout
82+
import System.Timeout ( timeout )
8483
import Data.IORef
84+
import Colog.Core as L
8585

8686
-- | A session representing one instance of launching and connecting to a server.
8787
--
@@ -367,7 +367,7 @@ updateState (FromServerMess SWorkspaceApplyEdit r) = do
367367
error "WorkspaceEdit contains neither documentChanges nor changes!"
368368

369369
modifyM $ \s -> do
370-
newVFS <- liftIO $ changeFromServerVFS (vfs s) r
370+
let newVFS = flip execState (vfs s) $ changeFromServerVFS logger r
371371
return $ s { vfs = newVFS }
372372

373373
let groupedParams = groupBy (\a b -> a ^. textDocument == b ^. textDocument) allChangeParams
@@ -384,22 +384,24 @@ updateState (FromServerMess SWorkspaceApplyEdit r) = do
384384
modify $ \s ->
385385
let oldVFS = vfs s
386386
update (VirtualFile oldV file_ver t) = VirtualFile (fromMaybe oldV v) (file_ver +1) t
387-
newVFS = updateVFS (Map.adjust update (toNormalizedUri uri)) oldVFS
387+
newVFS = oldVFS & vfsMap . ix (toNormalizedUri uri) %~ update
388388
in s { vfs = newVFS }
389389

390-
where checkIfNeedsOpened uri = do
390+
where
391+
logger = L.LogAction $ \m -> case logSeverity m of { L.Error -> error $ show m; _ -> pure () }
392+
checkIfNeedsOpened uri = do
391393
oldVFS <- vfs <$> get
392394

393395
-- if its not open, open it
394-
unless (toNormalizedUri uri `Map.member` vfsMap oldVFS) $ do
396+
unless (has (vfsMap . ix (toNormalizedUri uri)) oldVFS) $ do
395397
let fp = fromJust $ uriToFilePath uri
396398
contents <- liftIO $ T.readFile fp
397399
let item = TextDocumentItem (filePathToUri fp) "" 0 contents
398400
msg = NotificationMessage "2.0" STextDocumentDidOpen (DidOpenTextDocumentParams item)
399401
sendMessage msg
400402

401403
modifyM $ \s -> do
402-
let (newVFS,_) = openVFS (vfs s) msg
404+
let newVFS = flip execState (vfs s) $ openVFS logger msg
403405
return $ s { vfs = newVFS }
404406

405407
getParamsFromTextDocumentEdit :: TextDocumentEdit -> DidChangeTextDocumentParams
@@ -420,9 +422,8 @@ updateState (FromServerMess SWorkspaceApplyEdit r) = do
420422
-- For a uri returns an infinite list of versions [n,n+1,n+2,...]
421423
-- where n is the current version
422424
textDocumentVersions uri = do
423-
m <- vfsMap . vfs <$> get
424-
let curVer = fromMaybe 0 $
425-
_lsp_version <$> m Map.!? (toNormalizedUri uri)
425+
vfs <- vfs <$> get
426+
let curVer = fromMaybe 0 $ vfs ^? vfsMap . ix (toNormalizedUri uri) . lsp_version
426427
pure $ map (VersionedTextDocumentIdentifier uri . Just) [curVer + 1..]
427428

428429
textDocumentEdits uri edits = do

lsp-test/test/DummyServer.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -35,7 +35,7 @@ withDummyServer f = do
3535
}
3636

3737
bracket
38-
(forkIO $ void $ runServerWithHandles hinRead houtWrite definition)
38+
(forkIO $ void $ runServerWithHandles mempty hinRead houtWrite definition)
3939
killThread
4040
(const $ f (hinWrite, houtRead))
4141

lsp-types/lsp-types.cabal

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -76,14 +76,14 @@ library
7676
, binary
7777
, bytestring
7878
, containers
79+
, co-log-core
7980
, data-default
8081
, deepseq
8182
, Diff
8283
, directory
8384
, dlist
8485
, filepath
8586
, hashable
86-
, hslogger
8787
, lens >= 4.15.2
8888
, mtl
8989
, network-uri

lsp-types/src/Language/LSP/Types/Message.hs

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -372,7 +372,7 @@ deriving instance Read (ResponseResult m) => Read (ResponseMessage m)
372372
deriving instance Show (ResponseResult m) => Show (ResponseMessage m)
373373

374374
instance (ToJSON (ResponseResult m)) => ToJSON (ResponseMessage m) where
375-
toJSON (ResponseMessage { _jsonrpc = jsonrpc, _id = lspid, _result = result })
375+
toJSON ResponseMessage { _jsonrpc = jsonrpc, _id = lspid, _result = result }
376376
= object
377377
[ "jsonrpc" .= jsonrpc
378378
, "id" .= lspid
@@ -389,11 +389,11 @@ instance FromJSON (ResponseResult a) => FromJSON (ResponseMessage a) where
389389
_result <- o .:! "result"
390390
_error <- o .:? "error"
391391
result <- case (_error, _result) of
392-
((Just err), Nothing ) -> pure $ Left err
393-
(Nothing , (Just res)) -> pure $ Right res
394-
((Just _err), (Just _res)) -> fail $ "both error and result cannot be present: " ++ show o
392+
(Just err, Nothing) -> pure $ Left err
393+
(Nothing, Just res) -> pure $ Right res
394+
(Just _err, Just _res) -> fail $ "both error and result cannot be present: " ++ show o
395395
(Nothing, Nothing) -> fail "both error and result cannot be Nothing"
396-
return $ ResponseMessage _jsonrpc _id $ result
396+
return $ ResponseMessage _jsonrpc _id result
397397

398398
-- ---------------------------------------------------------------------
399399
-- Helper Type Families

lsp-types/src/Language/LSP/Types/Method.hs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,5 @@
11
{-# LANGUAGE OverloadedStrings #-}
22
{-# LANGUAGE TemplateHaskell #-}
3-
{-# LANGUAGE DataKinds #-}
43
{-# LANGUAGE GADTs #-}
54
{-# LANGUAGE MagicHash #-}
65
{-# LANGUAGE TypeFamilies #-}

0 commit comments

Comments
 (0)