@@ -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
@@ -5143,21 +5152,26 @@ runInDir' dir startExeIn startSessionIn extraOptions s = do
51435152 -- HIE calls getXgdDirectory which assumes that HOME is set.
51445153 -- Only sets HOME if it wasn't already set.
51455154 setEnv " HOME" " /homeless-shelter" False
5146- let lspTestCaps = fullCaps { _window = Just $ WindowClientCapabilities $ Just True }
5155+ conf <- getConfigFromEnv
5156+ runSessionWithConfig conf cmd lspTestCaps projDir s
5157+
5158+ getConfigFromEnv :: IO SessionConfig
5159+ getConfigFromEnv = do
51475160 logColor <- fromMaybe True <$> checkEnv " LSP_TEST_LOG_COLOR"
51485161 timeoutOverride <- fmap read <$> getEnv " LSP_TIMEOUT"
5149- let conf = defaultConfig{messageTimeout = fromMaybe (messageTimeout defaultConfig) timeoutOverride}
5150- -- uncomment this or set LSP_TEST_LOG_STDERR=1 to see all logging
5151- -- { logStdErr = True }
5152- -- uncomment this or set LSP_TEST_LOG_MESSAGES=1 to see all messages
5153- -- { logMessages = True }
5154- runSessionWithConfig conf{logColor} cmd lspTestCaps projDir s
5162+ return defaultConfig
5163+ { messageTimeout = fromMaybe (messageTimeout defaultConfig) timeoutOverride
5164+ , logColor
5165+ }
51555166 where
51565167 checkEnv :: String -> IO (Maybe Bool )
51575168 checkEnv s = fmap convertVal <$> getEnv s
51585169 convertVal " 0" = False
51595170 convertVal _ = True
51605171
5172+ lspTestCaps :: ClientCapabilities
5173+ lspTestCaps = fullCaps { _window = Just $ WindowClientCapabilities $ Just True }
5174+
51615175openTestDataDoc :: FilePath -> Session TextDocumentIdentifier
51625176openTestDataDoc path = do
51635177 source <- liftIO $ readFileUtf8 $ " test/data" </> path
@@ -5225,8 +5239,39 @@ unitTests = do
52255239 let expected = " 1:2-3:4"
52265240 assertBool (unwords [" expected to find range" , expected, " in diagnostic" , shown]) $
52275241 expected `isInfixOf` shown
5242+ , testCase " notification handlers run sequentially" $ do
5243+ orderRef <- newIORef []
5244+ let plugins = pluginDescToIdePlugins $
5245+ [ (defaultPluginDescriptor $ fromString $ show i)
5246+ { pluginNotificationHandlers = mconcat
5247+ [ mkPluginNotificationHandler LSP. STextDocumentDidOpen $ \ _ _ _ ->
5248+ liftIO $ atomicModifyIORef_ orderRef (i: )
5249+ ]
5250+ }
5251+ | i <- [(1 :: Int ).. 20 ]
5252+ ] ++ Ghcide. descriptors
5253+
5254+ testIde def{argsHlsPlugins = plugins} $ do
5255+ _ <- createDoc " haskell" " A.hs" " module A where"
5256+ waitForProgressDone
5257+ actualOrder <- liftIO $ readIORef orderRef
5258+
5259+ liftIO $ actualOrder @?= reverse [(1 :: Int ).. 20 ]
52285260 ]
52295261
5262+ testIde :: Arguments -> Session () -> IO ()
5263+ testIde arguments session = do
5264+ config <- getConfigFromEnv
5265+ (hInRead, hInWrite) <- createPipe
5266+ (hOutRead, hOutWrite) <- createPipe
5267+ let server = IDE. defaultMain arguments
5268+ { argsHandleIn = pure hInRead
5269+ , argsHandleOut = pure hOutWrite
5270+ }
5271+
5272+ withAsync server $ \ _ ->
5273+ runSessionWithHandles hInWrite hOutRead config lspTestCaps " ." session
5274+
52305275positionMappingTests :: TestTree
52315276positionMappingTests =
52325277 testGroup " position mapping"
0 commit comments