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
- import Test.Tasty.ExpectedFailure (ignoreTestBecause )
14
12
import Test.Tasty.Golden
15
13
import Test.Tasty.HUnit
16
- 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
17
19
18
20
tests :: TestTree
19
21
tests = testGroup " format document" [
@@ -28,7 +30,11 @@ tests = testGroup "format document" [
28
30
, rangeTests
29
31
, providerTests
30
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
31
36
, brittanyTests
37
+ #endif
32
38
, ormoluTests
33
39
]
34
40
@@ -51,25 +57,46 @@ providerTests = testGroup "formatting provider" [
51
57
orig <- documentContents doc
52
58
53
59
formatDoc doc (FormattingOptions 2 True )
54
- documentContents doc >>= liftIO . (`shouldBe` orig)
60
+ documentContents doc >>= liftIO . (@?= orig)
55
61
56
62
formatRange doc (FormattingOptions 2 True ) (Range (Position 1 0 ) (Position 3 10 ))
57
- documentContents doc >>= liftIO . (`shouldBe` orig)
63
+ documentContents doc >>= liftIO . (@?= orig)
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
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"
58
72
59
- , ignoreTestBecause " Broken" $ testCase " can change on the fly" $ runSession hieCommand fullCaps " test/testdata" $ do
60
73
doc <- openDoc " Format.hs" " haskell"
61
74
62
75
sendNotification WorkspaceDidChangeConfiguration (DidChangeConfigurationParams (formatLspConfig " brittany" ))
63
76
formatDoc doc (FormattingOptions 2 True )
64
- documentContents doc >>= liftIO . (`shouldBe` formattedBrittany)
77
+ documentContents doc >>= liftIO . (@?= formattedBrittany)
65
78
66
79
sendNotification WorkspaceDidChangeConfiguration (DidChangeConfigurationParams (formatLspConfig " floskell" ))
67
80
formatDoc doc (FormattingOptions 2 True )
68
- documentContents doc >>= liftIO . (`shouldBe` formattedFloskell)
81
+ documentContents doc >>= liftIO . (@?= formattedFloskell)
69
82
70
83
sendNotification WorkspaceDidChangeConfiguration (DidChangeConfigurationParams (formatLspConfig " brittany" ))
71
84
formatDoc doc (FormattingOptions 2 True )
72
- documentContents doc >>= liftIO . (`shouldBe` formattedBrittanyPostFloskell)
85
+ documentContents doc >>= liftIO . (@?= formattedBrittanyPostFloskell)
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
+
90
+ doc <- openDoc " Format.hs" " haskell"
91
+
92
+ sendNotification WorkspaceDidChangeConfiguration (DidChangeConfigurationParams (formatLspConfigOld " brittany" ))
93
+ formatDoc doc (FormattingOptions 2 True )
94
+ documentContents doc >>= liftIO . (@?= formattedBrittany)
95
+
96
+ sendNotification WorkspaceDidChangeConfiguration (DidChangeConfigurationParams (formatLspConfigOld " floskell" ))
97
+ formatDoc doc (FormattingOptions 2 True )
98
+ documentContents doc >>= liftIO . (@?= formattedFloskell)
99
+ #endif
73
100
]
74
101
75
102
stylishHaskellTests :: TestTree
@@ -89,22 +116,26 @@ stylishHaskellTests = testGroup "stylish-haskell" [
89
116
brittanyTests :: TestTree
90
117
brittanyTests = testGroup " brittany" [
91
118
goldenVsStringDiff " formats a document with LF endings" goldenGitDiff " test/testdata/BrittanyLF.formatted_document.hs" $ runSession hieCommand fullCaps " test/testdata" $ do
119
+ sendNotification WorkspaceDidChangeConfiguration (DidChangeConfigurationParams (formatLspConfig " brittany" ))
92
120
doc <- openDoc " BrittanyLF.hs" " haskell"
93
121
formatDoc doc (FormattingOptions 4 True )
94
122
BS. fromStrict . T. encodeUtf8 <$> documentContents doc
95
123
96
124
, goldenVsStringDiff " formats a document with CRLF endings" goldenGitDiff " test/testdata/BrittanyCRLF.formatted_document.hs" $ runSession hieCommand fullCaps " test/testdata" $ do
125
+ sendNotification WorkspaceDidChangeConfiguration (DidChangeConfigurationParams (formatLspConfig " brittany" ))
97
126
doc <- openDoc " BrittanyCRLF.hs" " haskell"
98
127
formatDoc doc (FormattingOptions 4 True )
99
128
BS. fromStrict . T. encodeUtf8 <$> documentContents doc
100
129
101
130
, goldenVsStringDiff " formats a range with LF endings" goldenGitDiff " test/testdata/BrittanyLF.formatted_range.hs" $ runSession hieCommand fullCaps " test/testdata" $ do
131
+ sendNotification WorkspaceDidChangeConfiguration (DidChangeConfigurationParams (formatLspConfig " brittany" ))
102
132
doc <- openDoc " BrittanyLF.hs" " haskell"
103
133
let range = Range (Position 1 0 ) (Position 2 22 )
104
134
formatRange doc (FormattingOptions 4 True ) range
105
135
BS. fromStrict . T. encodeUtf8 <$> documentContents doc
106
136
107
137
, goldenVsStringDiff " formats a range with CRLF endings" goldenGitDiff " test/testdata/BrittanyCRLF.formatted_range.hs" $ runSession hieCommand fullCaps " test/testdata" $ do
138
+ sendNotification WorkspaceDidChangeConfiguration (DidChangeConfigurationParams (formatLspConfig " brittany" ))
108
139
doc <- openDoc " BrittanyCRLF.hs" " haskell"
109
140
let range = Range (Position 1 0 ) (Position 2 22 )
110
141
formatRange doc (FormattingOptions 4 True ) range
@@ -114,8 +145,6 @@ brittanyTests = testGroup "brittany" [
114
145
ormoluTests :: TestTree
115
146
ormoluTests = testGroup " ormolu" [
116
147
goldenVsStringDiff " formats correctly" goldenGitDiff (" test/testdata/Format.ormolu." ++ ormoluGoldenSuffix ++ " .hs" ) $ runSession hieCommand fullCaps " test/testdata" $ do
117
- let formatLspConfig provider =
118
- object [ " haskell" .= object [" formattingProvider" .= (provider :: Value )] ]
119
148
sendNotification WorkspaceDidChangeConfiguration (DidChangeConfigurationParams (formatLspConfig " ormolu" ))
120
149
doc <- openDoc " Format.hs" " haskell"
121
150
formatDoc doc (FormattingOptions 2 True )
@@ -131,49 +160,12 @@ ormoluTests = testGroup "ormolu" [
131
160
formatLspConfig :: Value -> Value
132
161
formatLspConfig provider = object [ " haskell" .= object [" formattingProvider" .= (provider :: Value )] ]
133
162
163
+ -- | The same as 'formatLspConfig' but using the legacy section name
164
+ formatLspConfigOld :: Value -> Value
165
+ formatLspConfigOld provider = object [ " languageServerHaskell" .= object [" formattingProvider" .= (provider :: Value )] ]
166
+
134
167
formatConfig :: Value -> SessionConfig
135
168
formatConfig provider = defaultConfig { lspConfig = Just (formatLspConfig provider) }
136
169
137
170
goldenGitDiff :: FilePath -> FilePath -> [String ]
138
171
goldenGitDiff fRef fNew = [" git" , " diff" , " --no-index" , " --text" , " --exit-code" , fRef, fNew]
139
-
140
-
141
- formattedBrittany :: T. Text
142
- formattedBrittany =
143
- " module Format where\n \
144
- \foo :: Int -> Int\n \
145
- \foo 3 = 2\n \
146
- \foo x = x\n \
147
- \bar :: String -> IO String\n \
148
- \bar s = do\n \
149
- \ x <- return \" hello\"\n \
150
- \ return \" asdf\"\n\n \
151
- \data Baz = Baz { a :: Int, b :: String }\n\n "
152
-
153
- formattedFloskell :: T. Text
154
- formattedFloskell =
155
- " module Format where\n \
156
- \\n \
157
- \foo :: Int -> Int\n \
158
- \foo 3 = 2\n \
159
- \foo x = x\n \
160
- \\n \
161
- \bar :: String -> IO String\n \
162
- \bar s = do\n \
163
- \ x <- return \" hello\"\n \
164
- \ return \" asdf\"\n\n \
165
- \data Baz = Baz { a :: Int, b :: String }\n\n "
166
-
167
- formattedBrittanyPostFloskell :: T. Text
168
- formattedBrittanyPostFloskell =
169
- " module Format where\n \
170
- \\n \
171
- \foo :: Int -> Int\n \
172
- \foo 3 = 2\n \
173
- \foo x = x\n \
174
- \\n \
175
- \bar :: String -> IO String\n \
176
- \bar s = do\n \
177
- \ x <- return \" hello\"\n \
178
- \ return \" asdf\"\n\n \
179
- \data Baz = Baz { a :: Int, b :: String }\n\n "
0 commit comments