@@ -36,6 +36,7 @@ import Development.IDE.Core.PositionMapping (PositionResult (..),
3636 positionResultToMaybe ,
3737 toCurrent )
3838import Development.IDE.Core.Shake (Q (.. ))
39+ import Development.IDE.Main as IDE
3940import Development.IDE.GHC.Util
4041import Development.IDE.Plugin.Completions.Types (extendImportCommandId )
4142import Development.IDE.Plugin.TypeLenses (typeLensCommandId )
@@ -75,7 +76,7 @@ import qualified System.IO.Extra
7576import System.Info.Extra (isWindows )
7677import System.Process.Extra (CreateProcess (cwd ),
7778 proc ,
78- readCreateProcessWithExitCode )
79+ readCreateProcessWithExitCode , createPipe )
7980import Test.QuickCheck
8081-- import Test.QuickCheck.Instances ()
8182import Control.Lens ((^.) )
@@ -92,6 +93,14 @@ import Test.Tasty.ExpectedFailure
9293import Test.Tasty.HUnit
9394import Test.Tasty.Ingredients.Rerun
9495import Test.Tasty.QuickCheck
96+ import Data.IORef
97+ import Ide.PluginUtils (pluginDescToIdePlugins )
98+ import Control.Concurrent.Async
99+ import Ide.Types
100+ import Data.String (IsString (fromString ))
101+ import qualified Language.LSP.Types as LSP
102+ import Data.IORef.Extra (atomicModifyIORef_ )
103+ import qualified Development.IDE.Plugin.HLS.GhcIde as Ghcide
95104
96105waitForProgressBegin :: Session ()
97106waitForProgressBegin = skipManyTill anyMessage $ satisfyMaybe $ \ case
@@ -179,7 +188,7 @@ initializeResponseTests = withResource acquire release tests where
179188 , chk " NO doc link" _documentLinkProvider Nothing
180189 , chk " NO color" _colorProvider (Just $ InL False )
181190 , chk " NO folding range" _foldingRangeProvider (Just $ InL False )
182- , che " execute command" _executeCommandProvider [blockCommandId, extendImportCommandId, typeLensCommandId]
191+ , che " execute command" _executeCommandProvider [extendImportCommandId, typeLensCommandId, blockCommandId ]
183192 , chk " workspace" _workspace (Just $ WorkspaceServerCapabilities (Just WorkspaceFoldersServerCapabilities {_supported = Just True , _changeNotifications = Just ( InR True )}))
184193 , chk " NO experimental" _experimental Nothing
185194 ] where
@@ -5145,21 +5154,26 @@ runInDir' dir startExeIn startSessionIn extraOptions s = do
51455154 -- HIE calls getXgdDirectory which assumes that HOME is set.
51465155 -- Only sets HOME if it wasn't already set.
51475156 setEnv " HOME" " /homeless-shelter" False
5148- let lspTestCaps = fullCaps { _window = Just $ WindowClientCapabilities $ Just True }
5157+ conf <- getConfigFromEnv
5158+ runSessionWithConfig conf cmd lspTestCaps projDir s
5159+
5160+ getConfigFromEnv :: IO SessionConfig
5161+ getConfigFromEnv = do
51495162 logColor <- fromMaybe True <$> checkEnv " LSP_TEST_LOG_COLOR"
51505163 timeoutOverride <- fmap read <$> getEnv " LSP_TIMEOUT"
5151- let conf = defaultConfig{messageTimeout = fromMaybe (messageTimeout defaultConfig) timeoutOverride}
5152- -- uncomment this or set LSP_TEST_LOG_STDERR=1 to see all logging
5153- -- { logStdErr = True }
5154- -- uncomment this or set LSP_TEST_LOG_MESSAGES=1 to see all messages
5155- -- { logMessages = True }
5156- runSessionWithConfig conf{logColor} cmd lspTestCaps projDir s
5164+ return defaultConfig
5165+ { messageTimeout = fromMaybe (messageTimeout defaultConfig) timeoutOverride
5166+ , logColor
5167+ }
51575168 where
51585169 checkEnv :: String -> IO (Maybe Bool )
51595170 checkEnv s = fmap convertVal <$> getEnv s
51605171 convertVal " 0" = False
51615172 convertVal _ = True
51625173
5174+ lspTestCaps :: ClientCapabilities
5175+ lspTestCaps = fullCaps { _window = Just $ WindowClientCapabilities $ Just True }
5176+
51635177openTestDataDoc :: FilePath -> Session TextDocumentIdentifier
51645178openTestDataDoc path = do
51655179 source <- liftIO $ readFileUtf8 $ " test/data" </> path
@@ -5227,8 +5241,39 @@ unitTests = do
52275241 let expected = " 1:2-3:4"
52285242 assertBool (unwords [" expected to find range" , expected, " in diagnostic" , shown]) $
52295243 expected `isInfixOf` shown
5244+ , testCase " notification handlers run sequentially" $ do
5245+ orderRef <- newIORef []
5246+ let plugins = pluginDescToIdePlugins $
5247+ [ (defaultPluginDescriptor $ fromString $ show i)
5248+ { pluginNotificationHandlers = mconcat
5249+ [ mkPluginNotificationHandler LSP. STextDocumentDidOpen $ \ _ _ _ ->
5250+ liftIO $ atomicModifyIORef_ orderRef (i: )
5251+ ]
5252+ }
5253+ | i <- [(1 :: Int ).. 20 ]
5254+ ] ++ Ghcide. descriptors
5255+
5256+ testIde def{argsHlsPlugins = plugins} $ do
5257+ _ <- createDoc " haskell" " A.hs" " module A where"
5258+ waitForProgressDone
5259+ actualOrder <- liftIO $ readIORef orderRef
5260+
5261+ liftIO $ actualOrder @?= reverse [(1 :: Int ).. 20 ]
52305262 ]
52315263
5264+ testIde :: Arguments -> Session () -> IO ()
5265+ testIde arguments session = do
5266+ config <- getConfigFromEnv
5267+ (hInRead, hInWrite) <- createPipe
5268+ (hOutRead, hOutWrite) <- createPipe
5269+ let server = IDE. defaultMain arguments
5270+ { argsHandleIn = pure hInRead
5271+ , argsHandleOut = pure hOutWrite
5272+ }
5273+
5274+ withAsync server $ \ _ ->
5275+ runSessionWithHandles hInWrite hOutRead config lspTestCaps " ." session
5276+
52325277positionMappingTests :: TestTree
52335278positionMappingTests =
52345279 testGroup " position mapping"
0 commit comments