Skip to content

Commit 405bbc0

Browse files
committed
Fix Brittany tests
Need to read in those test results as a file, since the CPP preprocessor trips on those multiline strings Also use @?= instead of `shouldBe`, since the exception thrown by it gets caught by tasty and is pretty printed
1 parent 9d3d0e6 commit 405bbc0

10 files changed

+77
-64
lines changed

haskell-language-server.cabal

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -245,7 +245,7 @@ test-suite func-test
245245
, haskell-lsp-types
246246
, hspec-expectations
247247
, lens
248-
, lsp-test >= 0.10.0.3
248+
, lsp-test >= 0.11.0.3
249249
, tasty
250250
, tasty-ant-xml >= 1.1.6
251251
, tasty-expected-failure

test/functional/Deferred.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -92,7 +92,7 @@ tests = testGroup "deferred responses" [
9292
-- }
9393
-- ]
9494

95-
testCase "instantly respond to failed modules with no cache" $ runSession hieCommand fullCaps "test/testdata" $ do
95+
testCase "instantly respond to failed modules with no cache" $ runSessionWithConfig (defaultConfig { logStdErr = True, logMessages = True }) hieCommand fullCaps "test/testdata" $ do
9696
doc <- openDoc "FuncTestFail.hs" "haskell"
9797
defs <- getDefinitions doc (Position 1 11)
9898
liftIO $ defs `shouldBe` []

test/functional/Format.hs

Lines changed: 28 additions & 52 deletions
Original file line numberDiff line numberDiff line change
@@ -1,18 +1,21 @@
1-
{-# LANGUAGE OverloadedStrings #-}
1+
{-# LANGUAGE OverloadedStrings, CPP #-}
22
module Format (tests) where
33

44
import Control.Monad.IO.Class
55
import Data.Aeson
66
import qualified Data.ByteString.Lazy as BS
7-
import qualified Data.Text as T
87
import qualified Data.Text.Encoding as T
98
import Language.Haskell.LSP.Test
109
import Language.Haskell.LSP.Types
1110
import Test.Hls.Util
1211
import Test.Tasty
1312
import Test.Tasty.Golden
1413
import Test.Tasty.HUnit
15-
import Test.Hspec.Expectations
14+
15+
#if MIN_VERSION_GLASGOW_HASKELL(8,10,0,0) || !defined(AGPL)
16+
#else
17+
import qualified Data.Text.IO as T
18+
#endif
1619

1720
tests :: TestTree
1821
tests = testGroup "format document" [
@@ -27,7 +30,11 @@ tests = testGroup "format document" [
2730
, rangeTests
2831
, providerTests
2932
, stylishHaskellTests
33+
-- There's no Brittany formatter on the 8.10.1 builds (yet)
34+
#if MIN_VERSION_GLASGOW_HASKELL(8,10,0,0) || !defined(AGPL)
35+
#else
3036
, brittanyTests
37+
#endif
3138
, ormoluTests
3239
]
3340

@@ -50,36 +57,46 @@ providerTests = testGroup "formatting provider" [
5057
orig <- documentContents doc
5158

5259
formatDoc doc (FormattingOptions 2 True)
53-
documentContents doc >>= liftIO . (`shouldBe` orig)
60+
documentContents doc >>= liftIO . (@?= orig)
5461

5562
formatRange doc (FormattingOptions 2 True) (Range (Position 1 0) (Position 3 10))
56-
documentContents doc >>= liftIO . (`shouldBe` orig)
63+
documentContents doc >>= liftIO . (@?= orig)
5764

65+
-- There's no Brittany formatter on the 8.10.1 builds (yet)
66+
#if MIN_VERSION_GLASGOW_HASKELL(8,10,0,0) || !defined(AGPL)
67+
#else
5868
, testCase "can change on the fly" $ runSession hieCommand fullCaps "test/testdata" $ do
69+
formattedBrittany <- liftIO $ T.readFile "test/testdata/Format.brittany.formatted.hs"
70+
formattedFloskell <- liftIO $ T.readFile "test/testdata/Format.floskell.formatted.hs"
71+
formattedBrittanyPostFloskell <- liftIO $ T.readFile "test/testdata/Format.brittany_post_floskell.formatted.hs"
72+
5973
doc <- openDoc "Format.hs" "haskell"
6074

6175
sendNotification WorkspaceDidChangeConfiguration (DidChangeConfigurationParams (formatLspConfig "brittany"))
6276
formatDoc doc (FormattingOptions 2 True)
63-
documentContents doc >>= liftIO . (`shouldBe` formattedBrittany)
77+
documentContents doc >>= liftIO . (@?= formattedBrittany)
6478

6579
sendNotification WorkspaceDidChangeConfiguration (DidChangeConfigurationParams (formatLspConfig "floskell"))
6680
formatDoc doc (FormattingOptions 2 True)
67-
documentContents doc >>= liftIO . (`shouldBe` formattedFloskell)
81+
documentContents doc >>= liftIO . (@?= formattedFloskell)
6882

6983
sendNotification WorkspaceDidChangeConfiguration (DidChangeConfigurationParams (formatLspConfig "brittany"))
7084
formatDoc doc (FormattingOptions 2 True)
71-
documentContents doc >>= liftIO . (`shouldBe` formattedBrittanyPostFloskell)
85+
documentContents doc >>= liftIO . (@?= formattedBrittanyPostFloskell)
7286
, testCase "supports both new and old configuration sections" $ runSession hieCommand fullCaps "test/testdata" $ do
87+
formattedBrittany <- liftIO $ T.readFile "test/testdata/Format.brittany.formatted.hs"
88+
formattedFloskell <- liftIO $ T.readFile "test/testdata/Format.floskell.formatted.hs"
89+
7390
doc <- openDoc "Format.hs" "haskell"
7491

7592
sendNotification WorkspaceDidChangeConfiguration (DidChangeConfigurationParams (formatLspConfigOld "brittany"))
7693
formatDoc doc (FormattingOptions 2 True)
77-
documentContents doc >>= liftIO . (`shouldBe` formattedBrittany)
94+
documentContents doc >>= liftIO . (@?= formattedBrittany)
7895

7996
sendNotification WorkspaceDidChangeConfiguration (DidChangeConfigurationParams (formatLspConfigOld "floskell"))
8097
formatDoc doc (FormattingOptions 2 True)
81-
documentContents doc >>= liftIO . (`shouldBe` formattedFloskell)
82-
98+
documentContents doc >>= liftIO . (@?= formattedFloskell)
99+
#endif
83100
]
84101

85102
stylishHaskellTests :: TestTree
@@ -152,44 +169,3 @@ formatConfig provider = defaultConfig { lspConfig = Just (formatLspConfig provid
152169

153170
goldenGitDiff :: FilePath -> FilePath -> [String]
154171
goldenGitDiff fRef fNew = ["git", "diff", "--no-index", "--text", "--exit-code", fRef, fNew]
155-
156-
157-
formattedBrittany :: T.Text
158-
formattedBrittany =
159-
"module Format where\n\
160-
\foo :: Int -> Int\n\
161-
\foo 3 = 2\n\
162-
\foo x = x\n\
163-
\bar :: String -> IO String\n\
164-
\bar s = do\n\
165-
\ x <- return \"hello\"\n\
166-
\ return \"asdf\"\n\n\
167-
\data Baz = Baz { a :: Int, b :: String }\n\n"
168-
169-
formattedFloskell :: T.Text
170-
formattedFloskell =
171-
"module Format where\n\
172-
\\n\
173-
\foo :: Int -> Int\n\
174-
\foo 3 = 2\n\
175-
\foo x = x\n\
176-
\\n\
177-
\bar :: String -> IO String\n\
178-
\bar s = do\n\
179-
\ x <- return \"hello\"\n\
180-
\ return \"asdf\"\n\n\
181-
\data Baz = Baz { a :: Int, b :: String }\n\n"
182-
183-
formattedBrittanyPostFloskell :: T.Text
184-
formattedBrittanyPostFloskell =
185-
"module Format where\n\
186-
\\n\
187-
\foo :: Int -> Int\n\
188-
\foo 3 = 2\n\
189-
\foo x = x\n\
190-
\\n\
191-
\bar :: String -> IO String\n\
192-
\bar s = do\n\
193-
\ x <- return \"hello\"\n\
194-
\ return \"asdf\"\n\n\
195-
\data Baz = Baz { a :: Int, b :: String }\n\n"
Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
11
foo :: Int -> String -> IO ()
22
foo x y = do
3-
print x
4-
return 42
3+
print x
4+
return 42
Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
1-
foo :: Int -> String -> IO ()
1+
foo :: Int -> String-> IO ()
22
foo x y = do
3-
print x
4-
return 42
3+
print x
4+
return 42
Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
11
foo :: Int -> String -> IO ()
22
foo x y = do
3-
print x
4-
return 42
3+
print x
4+
return 42
Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
1-
foo :: Int -> String -> IO ()
1+
foo :: Int -> String-> IO ()
22
foo x y = do
3-
print x
4-
return 42
3+
print x
4+
return 42
Lines changed: 11 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,11 @@
1+
module Format where
2+
foo :: Int -> Int
3+
foo 3 = 2
4+
foo x = x
5+
bar :: String -> IO String
6+
bar s = do
7+
x <- return "hello"
8+
return "asdf"
9+
10+
data Baz = Baz { a :: Int, b :: String }
11+
Lines changed: 13 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,13 @@
1+
module Format where
2+
3+
foo :: Int -> Int
4+
foo 3 = 2
5+
foo x = x
6+
7+
bar :: String -> IO String
8+
bar s = do
9+
x <- return "hello"
10+
return "asdf"
11+
12+
data Baz = Baz { a :: Int, b :: String }
13+
Lines changed: 13 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,13 @@
1+
module Format where
2+
3+
foo :: Int -> Int
4+
foo 3 = 2
5+
foo x = x
6+
7+
bar :: String -> IO String
8+
bar s = do
9+
x <- return "hello"
10+
return "asdf"
11+
12+
data Baz = Baz { a :: Int, b :: String }
13+

0 commit comments

Comments
 (0)