1- {-# LANGUAGE OverloadedStrings #-}
1+ {-# LANGUAGE OverloadedStrings, CPP #-}
22module Format (tests ) where
33
44import Control.Monad.IO.Class
55import Data.Aeson
66import qualified Data.ByteString.Lazy as BS
7- import qualified Data.Text as T
87import qualified Data.Text.Encoding as T
98import Language.Haskell.LSP.Test
109import Language.Haskell.LSP.Types
1110import Test.Hls.Util
1211import Test.Tasty
1312import Test.Tasty.Golden
1413import 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
1720tests :: TestTree
1821tests = 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
85102stylishHaskellTests :: TestTree
@@ -152,44 +169,3 @@ formatConfig provider = defaultConfig { lspConfig = Just (formatLspConfig provid
152169
153170goldenGitDiff :: FilePath -> FilePath -> [String ]
154171goldenGitDiff 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