forked from haskell/haskell-language-server
-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy pathDependentFileTest.hs
58 lines (53 loc) · 2.57 KB
/
DependentFileTest.hs
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
{-# LANGUAGE GADTs #-}
{-# LANGUAGE OverloadedLabels #-}
module DependentFileTest (tests) where
import Control.Monad.IO.Class (liftIO)
import Data.Row
import qualified Data.Text as T
import Development.IDE.Test (expectDiagnostics)
import Development.IDE.Types.Location
import Language.LSP.Protocol.Message
import Language.LSP.Protocol.Types hiding
(SemanticTokenAbsolute (..),
SemanticTokenRelative (..),
SemanticTokensEdit (..),
mkRange)
import Language.LSP.Test
import System.FilePath
import Test.Tasty
import TestUtils
tests :: TestTree
tests = testGroup "addDependentFile"
[testGroup "file-changed" [testSession' "test" test]
]
where
test dir = do
-- If the file contains B then no type error
-- otherwise type error
let depFilePath = dir </> "dep-file.txt"
liftIO $ writeFile depFilePath "A"
let fooContent = T.unlines
[ "{-# LANGUAGE TemplateHaskell #-}"
, "module Foo where"
, "import Language.Haskell.TH.Syntax"
, "foo :: Int"
, "foo = 1 + $(do"
, " qAddDependentFile \"dep-file.txt\""
, " f <- qRunIO (readFile \"dep-file.txt\")"
, " if f == \"B\" then [| 1 |] else lift f)"
]
let bazContent = T.unlines ["module Baz where", "import Foo ()"]
_ <- createDoc "Foo.hs" "haskell" fooContent
doc <- createDoc "Baz.hs" "haskell" bazContent
expectDiagnostics
[("Foo.hs", [(DiagnosticSeverity_Error, (4,11), "Couldn't match type")])]
-- Now modify the dependent file
liftIO $ writeFile depFilePath "B"
sendNotification SMethod_WorkspaceDidChangeWatchedFiles $ DidChangeWatchedFilesParams
[FileEvent (filePathToUri "dep-file.txt") FileChangeType_Changed ]
-- Modifying Baz will now trigger Foo to be rebuilt as well
let change = TextDocumentContentChangeEvent $ InL $ #range .== Range (Position 2 0) (Position 2 6)
.+ #rangeLength .== Nothing
.+ #text .== "f = ()"
changeDoc doc [change]
expectDiagnostics [("Foo.hs", [])]