1
+ {-# LANGUAGE GADTs #-}
2
+ {-# LANGUAGE OverloadedStrings #-}
1
3
{-# LANGUAGE RankNTypes #-}
2
- {-# LANGUAGE GADTs, OverloadedStrings #-}
4
+
3
5
module Main where
4
6
5
- import Language.LSP.Server
6
- import qualified Language.LSP.Test as Test
7
- import Language.LSP.Protocol.Types
8
- import qualified Language.LSP.Protocol. Lens as L
9
- import Language.LSP.Protocol.Message
7
+ import Colog.Core qualified as L
8
+ import Control.Applicative.Combinators
9
+ import Control.Exception
10
+ import Control. Lens hiding ( Iso , List )
11
+ import Control.Monad
10
12
import Control.Monad.IO.Class
13
+ import Data.Maybe
14
+ import Language.LSP.Protocol.Lens qualified as L
15
+ import Language.LSP.Protocol.Message
16
+ import Language.LSP.Protocol.Types
17
+ import Language.LSP.Server
18
+ import Language.LSP.Test qualified as Test
19
+ import System.Exit
11
20
import System.IO
12
- import Control.Monad
13
21
import System.Process
14
- import Control.Applicative.Combinators
15
- import Control.Lens hiding (List , Iso )
16
22
import Test.Hspec
17
- import Data.Maybe
18
23
import UnliftIO
19
24
import UnliftIO.Concurrent
20
- import Control.Exception
21
- import System.Exit
22
- import qualified Colog.Core as L
23
25
24
26
main :: IO ()
25
27
main = hspec $ do
@@ -28,42 +30,44 @@ main = hspec $ do
28
30
it " sends end notification if thread is killed" $ do
29
31
(hinRead, hinWrite) <- createPipe
30
32
(houtRead, houtWrite) <- createPipe
31
-
33
+
32
34
killVar <- newEmptyMVar
33
35
34
- let definition = ServerDefinition
35
- { parseConfig = const $ const $ Right ()
36
- , onConfigChange = const $ pure ()
37
- , defaultConfig = ()
38
- , configSection = " demo"
39
- , doInitialize = \ env _req -> pure $ Right env
40
- , staticHandlers = \ _caps -> handlers killVar
41
- , interpretHandler = \ env -> Iso (runLspT env) liftIO
42
- , options = defaultOptions
43
- }
36
+ let definition =
37
+ ServerDefinition
38
+ { parseConfig = const $ const $ Right ()
39
+ , onConfigChange = const $ pure ()
40
+ , defaultConfig = ()
41
+ , configSection = " demo"
42
+ , doInitialize = \ env _req -> pure $ Right env
43
+ , staticHandlers = \ _caps -> handlers killVar
44
+ , interpretHandler = \ env -> Iso (runLspT env) liftIO
45
+ , options = defaultOptions
46
+ }
44
47
45
48
handlers :: MVar () -> Handlers (LspM () )
46
49
handlers killVar =
47
50
notificationHandler SMethod_Initialized $ \ noti -> do
48
51
tid <- withRunInIO $ \ runInIO ->
49
- forkIO $ runInIO $
50
- withProgress " Doing something" NotCancellable $ \ updater ->
51
- liftIO $ threadDelay (1 * 1000000 )
52
+ forkIO $
53
+ runInIO $
54
+ withProgress " Doing something" NotCancellable $ \ updater ->
55
+ liftIO $ threadDelay (1 * 1000000 )
52
56
liftIO $ void $ forkIO $ do
53
57
takeMVar killVar
54
58
killThread tid
55
-
59
+
56
60
forkIO $ void $ runServerWithHandles logger (L. hoistLogAction liftIO logger) hinRead houtWrite definition
57
-
61
+
58
62
Test. runSessionWithHandles hinWrite houtRead Test. defaultConfig Test. fullCaps " ." $ do
59
63
-- First make sure that we get a $/progress begin notification
60
64
skipManyTill Test. anyMessage $ do
61
65
x <- Test. message SMethod_Progress
62
66
guard $ has (L. params . L. value . _workDoneProgressBegin) x
63
-
67
+
64
68
-- Then kill the thread
65
69
liftIO $ putMVar killVar ()
66
-
70
+
67
71
-- Then make sure we still get a $/progress end notification
68
72
skipManyTill Test. anyMessage $ do
69
73
x <- Test. message SMethod_Progress
@@ -73,58 +77,60 @@ main = hspec $ do
73
77
it " keeps track of open workspace folders" $ do
74
78
(hinRead, hinWrite) <- createPipe
75
79
(houtRead, houtWrite) <- createPipe
76
-
80
+
77
81
countVar <- newMVar 0
78
82
79
83
let wf0 = WorkspaceFolder (filePathToUri " one" ) " Starter workspace"
80
84
wf1 = WorkspaceFolder (filePathToUri " /foo/bar" ) " My workspace"
81
85
wf2 = WorkspaceFolder (filePathToUri " /foo/baz" ) " My other workspace"
82
-
83
- definition = ServerDefinition
84
- { parseConfig = const $ const $ Right ()
85
- , onConfigChange = const $ pure ()
86
- , defaultConfig = ()
87
- , configSection = " demo"
88
- , doInitialize = \ env _req -> pure $ Right env
89
- , staticHandlers = \ _caps -> handlers
90
- , interpretHandler = \ env -> Iso (runLspT env) liftIO
91
- , options = defaultOptions
92
- }
86
+
87
+ definition =
88
+ ServerDefinition
89
+ { parseConfig = const $ const $ Right ()
90
+ , onConfigChange = const $ pure ()
91
+ , defaultConfig = ()
92
+ , configSection = " demo"
93
+ , doInitialize = \ env _req -> pure $ Right env
94
+ , staticHandlers = \ _caps -> handlers
95
+ , interpretHandler = \ env -> Iso (runLspT env) liftIO
96
+ , options = defaultOptions
97
+ }
93
98
94
99
handlers :: Handlers (LspM () )
95
- handlers = mconcat
96
- [ notificationHandler SMethod_Initialized $ \ noti -> do
97
- wfs <- fromJust <$> getWorkspaceFolders
98
- liftIO $ wfs `shouldContain` [wf0]
99
- , notificationHandler SMethod_WorkspaceDidChangeWorkspaceFolders $ \ noti -> do
100
- i <- liftIO $ modifyMVar countVar (\ i -> pure (i + 1 , i))
101
- wfs <- fromJust <$> getWorkspaceFolders
102
- liftIO $ case i of
103
- 0 -> do
104
- wfs `shouldContain` [wf1]
105
- wfs `shouldContain` [wf0]
106
- 1 -> do
107
- wfs `shouldNotContain` [wf1]
108
- wfs `shouldContain` [wf0]
109
- wfs `shouldContain` [wf2]
110
- _ -> error " Shouldn't be here"
111
- ]
112
-
100
+ handlers =
101
+ mconcat
102
+ [ notificationHandler SMethod_Initialized $ \ noti -> do
103
+ wfs <- fromJust <$> getWorkspaceFolders
104
+ liftIO $ wfs `shouldContain` [wf0]
105
+ , notificationHandler SMethod_WorkspaceDidChangeWorkspaceFolders $ \ noti -> do
106
+ i <- liftIO $ modifyMVar countVar (\ i -> pure (i + 1 , i))
107
+ wfs <- fromJust <$> getWorkspaceFolders
108
+ liftIO $ case i of
109
+ 0 -> do
110
+ wfs `shouldContain` [wf1]
111
+ wfs `shouldContain` [wf0]
112
+ 1 -> do
113
+ wfs `shouldNotContain` [wf1]
114
+ wfs `shouldContain` [wf0]
115
+ wfs `shouldContain` [wf2]
116
+ _ -> error " Shouldn't be here"
117
+ ]
118
+
113
119
server <- async $ void $ runServerWithHandles logger (L. hoistLogAction liftIO logger) hinRead houtWrite definition
114
-
115
- let config = Test. defaultConfig
116
- { Test. initialWorkspaceFolders = Just [wf0]
117
- }
118
-
120
+
121
+ let config =
122
+ Test. defaultConfig
123
+ { Test. initialWorkspaceFolders = Just [wf0]
124
+ }
125
+
119
126
changeFolders add rmv =
120
127
let ev = WorkspaceFoldersChangeEvent add rmv
121
128
ps = DidChangeWorkspaceFoldersParams ev
122
- in Test. sendNotification SMethod_WorkspaceDidChangeWorkspaceFolders ps
129
+ in Test. sendNotification SMethod_WorkspaceDidChangeWorkspaceFolders ps
123
130
124
131
Test. runSessionWithHandles hinWrite houtRead config Test. fullCaps " ." $ do
125
132
changeFolders [wf1] []
126
133
changeFolders [wf2] [wf1]
127
134
128
135
Left e <- waitCatch server
129
136
fromException e `shouldBe` Just ExitSuccess
130
-
0 commit comments