1
- {-# LANGUAGE OverloadedStrings #-}
1
+ {-# LANGUAGE OverloadedStrings, CPP #-}
2
2
module Format (tests ) where
3
3
4
4
import Control.Monad.IO.Class
5
5
import Data.Aeson
6
6
import qualified Data.ByteString.Lazy as BS
7
- import qualified Data.Text as T
8
7
import qualified Data.Text.Encoding as T
9
8
import Language.Haskell.LSP.Test
10
9
import Language.Haskell.LSP.Types
11
10
import Test.Hls.Util
12
11
import Test.Tasty
13
12
import Test.Tasty.Golden
14
13
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
16
19
17
20
tests :: TestTree
18
21
tests = testGroup " format document" [
@@ -27,7 +30,11 @@ tests = testGroup "format document" [
27
30
, rangeTests
28
31
, providerTests
29
32
, 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
30
36
, brittanyTests
37
+ #endif
31
38
, ormoluTests
32
39
]
33
40
@@ -50,36 +57,46 @@ providerTests = testGroup "formatting provider" [
50
57
orig <- documentContents doc
51
58
52
59
formatDoc doc (FormattingOptions 2 True )
53
- documentContents doc >>= liftIO . (`shouldBe` orig)
60
+ documentContents doc >>= liftIO . (@?= orig)
54
61
55
62
formatRange doc (FormattingOptions 2 True ) (Range (Position 1 0 ) (Position 3 10 ))
56
- documentContents doc >>= liftIO . (`shouldBe` orig)
63
+ documentContents doc >>= liftIO . (@?= orig)
57
64
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
58
68
, 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
+
59
73
doc <- openDoc " Format.hs" " haskell"
60
74
61
75
sendNotification WorkspaceDidChangeConfiguration (DidChangeConfigurationParams (formatLspConfig " brittany" ))
62
76
formatDoc doc (FormattingOptions 2 True )
63
- documentContents doc >>= liftIO . (`shouldBe` formattedBrittany)
77
+ documentContents doc >>= liftIO . (@?= formattedBrittany)
64
78
65
79
sendNotification WorkspaceDidChangeConfiguration (DidChangeConfigurationParams (formatLspConfig " floskell" ))
66
80
formatDoc doc (FormattingOptions 2 True )
67
- documentContents doc >>= liftIO . (`shouldBe` formattedFloskell)
81
+ documentContents doc >>= liftIO . (@?= formattedFloskell)
68
82
69
83
sendNotification WorkspaceDidChangeConfiguration (DidChangeConfigurationParams (formatLspConfig " brittany" ))
70
84
formatDoc doc (FormattingOptions 2 True )
71
- documentContents doc >>= liftIO . (`shouldBe` formattedBrittanyPostFloskell)
85
+ documentContents doc >>= liftIO . (@?= formattedBrittanyPostFloskell)
72
86
, 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
+
73
90
doc <- openDoc " Format.hs" " haskell"
74
91
75
92
sendNotification WorkspaceDidChangeConfiguration (DidChangeConfigurationParams (formatLspConfigOld " brittany" ))
76
93
formatDoc doc (FormattingOptions 2 True )
77
- documentContents doc >>= liftIO . (`shouldBe` formattedBrittany)
94
+ documentContents doc >>= liftIO . (@?= formattedBrittany)
78
95
79
96
sendNotification WorkspaceDidChangeConfiguration (DidChangeConfigurationParams (formatLspConfigOld " floskell" ))
80
97
formatDoc doc (FormattingOptions 2 True )
81
- documentContents doc >>= liftIO . (`shouldBe` formattedFloskell)
82
-
98
+ documentContents doc >>= liftIO . (@?= formattedFloskell)
99
+ #endif
83
100
]
84
101
85
102
stylishHaskellTests :: TestTree
@@ -152,44 +169,3 @@ formatConfig provider = defaultConfig { lspConfig = Just (formatLspConfig provid
152
169
153
170
goldenGitDiff :: FilePath -> FilePath -> [String ]
154
171
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 "
0 commit comments