Skip to content

Commit

Permalink
Fix Brittany tests
Browse files Browse the repository at this point in the history
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
  • Loading branch information
lukel97 committed Jul 27, 2020
1 parent 9d3d0e6 commit 4d0b201
Show file tree
Hide file tree
Showing 9 changed files with 76 additions and 63 deletions.
2 changes: 1 addition & 1 deletion haskell-language-server.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -245,7 +245,7 @@ test-suite func-test
, haskell-lsp-types
, hspec-expectations
, lens
, lsp-test >= 0.10.0.3
, lsp-test >= 0.11.0.3
, tasty
, tasty-ant-xml >= 1.1.6
, tasty-expected-failure
Expand Down
80 changes: 28 additions & 52 deletions test/functional/Format.hs
Original file line number Diff line number Diff line change
@@ -1,18 +1,21 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE OverloadedStrings, CPP #-}
module Format (tests) where

import Control.Monad.IO.Class
import Data.Aeson
import qualified Data.ByteString.Lazy as BS
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import Language.Haskell.LSP.Test
import Language.Haskell.LSP.Types
import Test.Hls.Util
import Test.Tasty
import Test.Tasty.Golden
import Test.Tasty.HUnit
import Test.Hspec.Expectations

#if MIN_VERSION_GLASGOW_HASKELL(8,10,0,0) || !defined(AGPL)
#else
import qualified Data.Text.IO as T
#endif

tests :: TestTree
tests = testGroup "format document" [
Expand All @@ -27,7 +30,11 @@ tests = testGroup "format document" [
, rangeTests
, providerTests
, stylishHaskellTests
-- There's no Brittany formatter on the 8.10.1 builds (yet)
#if MIN_VERSION_GLASGOW_HASKELL(8,10,0,0) || !defined(AGPL)
#else
, brittanyTests
#endif
, ormoluTests
]

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

formatDoc doc (FormattingOptions 2 True)
documentContents doc >>= liftIO . (`shouldBe` orig)
documentContents doc >>= liftIO . (@?= orig)

formatRange doc (FormattingOptions 2 True) (Range (Position 1 0) (Position 3 10))
documentContents doc >>= liftIO . (`shouldBe` orig)
documentContents doc >>= liftIO . (@?= orig)

-- There's no Brittany formatter on the 8.10.1 builds (yet)
#if MIN_VERSION_GLASGOW_HASKELL(8,10,0,0) || !defined(AGPL)
#else
, testCase "can change on the fly" $ runSession hieCommand fullCaps "test/testdata" $ do
formattedBrittany <- liftIO $ T.readFile "test/testdata/Format.brittany.formatted.hs"
formattedFloskell <- liftIO $ T.readFile "test/testdata/Format.floskell.formatted.hs"
formattedBrittanyPostFloskell <- liftIO $ T.readFile "test/testdata/Format.brittany_post_floskell.formatted.hs"

doc <- openDoc "Format.hs" "haskell"

sendNotification WorkspaceDidChangeConfiguration (DidChangeConfigurationParams (formatLspConfig "brittany"))
formatDoc doc (FormattingOptions 2 True)
documentContents doc >>= liftIO . (`shouldBe` formattedBrittany)
documentContents doc >>= liftIO . (@?= formattedBrittany)

sendNotification WorkspaceDidChangeConfiguration (DidChangeConfigurationParams (formatLspConfig "floskell"))
formatDoc doc (FormattingOptions 2 True)
documentContents doc >>= liftIO . (`shouldBe` formattedFloskell)
documentContents doc >>= liftIO . (@?= formattedFloskell)

sendNotification WorkspaceDidChangeConfiguration (DidChangeConfigurationParams (formatLspConfig "brittany"))
formatDoc doc (FormattingOptions 2 True)
documentContents doc >>= liftIO . (`shouldBe` formattedBrittanyPostFloskell)
documentContents doc >>= liftIO . (@?= formattedBrittanyPostFloskell)
, testCase "supports both new and old configuration sections" $ runSession hieCommand fullCaps "test/testdata" $ do
formattedBrittany <- liftIO $ T.readFile "test/testdata/Format.brittany.formatted.hs"
formattedFloskell <- liftIO $ T.readFile "test/testdata/Format.floskell.formatted.hs"

doc <- openDoc "Format.hs" "haskell"

sendNotification WorkspaceDidChangeConfiguration (DidChangeConfigurationParams (formatLspConfigOld "brittany"))
formatDoc doc (FormattingOptions 2 True)
documentContents doc >>= liftIO . (`shouldBe` formattedBrittany)
documentContents doc >>= liftIO . (@?= formattedBrittany)

sendNotification WorkspaceDidChangeConfiguration (DidChangeConfigurationParams (formatLspConfigOld "floskell"))
formatDoc doc (FormattingOptions 2 True)
documentContents doc >>= liftIO . (`shouldBe` formattedFloskell)

documentContents doc >>= liftIO . (@?= formattedFloskell)
#endif
]

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

goldenGitDiff :: FilePath -> FilePath -> [String]
goldenGitDiff fRef fNew = ["git", "diff", "--no-index", "--text", "--exit-code", fRef, fNew]


formattedBrittany :: T.Text
formattedBrittany =
"module Format where\n\
\foo :: Int -> Int\n\
\foo 3 = 2\n\
\foo x = x\n\
\bar :: String -> IO String\n\
\bar s = do\n\
\ x <- return \"hello\"\n\
\ return \"asdf\"\n\n\
\data Baz = Baz { a :: Int, b :: String }\n\n"

formattedFloskell :: T.Text
formattedFloskell =
"module Format where\n\
\\n\
\foo :: Int -> Int\n\
\foo 3 = 2\n\
\foo x = x\n\
\\n\
\bar :: String -> IO String\n\
\bar s = do\n\
\ x <- return \"hello\"\n\
\ return \"asdf\"\n\n\
\data Baz = Baz { a :: Int, b :: String }\n\n"

formattedBrittanyPostFloskell :: T.Text
formattedBrittanyPostFloskell =
"module Format where\n\
\\n\
\foo :: Int -> Int\n\
\foo 3 = 2\n\
\foo x = x\n\
\\n\
\bar :: String -> IO String\n\
\bar s = do\n\
\ x <- return \"hello\"\n\
\ return \"asdf\"\n\n\
\data Baz = Baz { a :: Int, b :: String }\n\n"
4 changes: 2 additions & 2 deletions test/testdata/BrittanyCRLF.formatted_document.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
foo :: Int -> String -> IO ()
foo x y = do
print x
return 42
print x
return 42
6 changes: 3 additions & 3 deletions test/testdata/BrittanyCRLF.formatted_range.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
foo :: Int -> String -> IO ()
foo :: Int -> String-> IO ()
foo x y = do
print x
return 42
print x
return 42
4 changes: 2 additions & 2 deletions test/testdata/BrittanyLF.formatted_document.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
foo :: Int -> String -> IO ()
foo x y = do
print x
return 42
print x
return 42
6 changes: 3 additions & 3 deletions test/testdata/BrittanyLF.formatted_range.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
foo :: Int -> String -> IO ()
foo :: Int -> String-> IO ()
foo x y = do
print x
return 42
print x
return 42
11 changes: 11 additions & 0 deletions test/testdata/Format.brittany.formatted.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,11 @@
module Format where
foo :: Int -> Int
foo 3 = 2
foo x = x
bar :: String -> IO String
bar s = do
x <- return "hello"
return "asdf"

data Baz = Baz { a :: Int, b :: String }

13 changes: 13 additions & 0 deletions test/testdata/Format.brittany_post_floskell.formatted.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,13 @@
module Format where

foo :: Int -> Int
foo 3 = 2
foo x = x

bar :: String -> IO String
bar s = do
x <- return "hello"
return "asdf"

data Baz = Baz { a :: Int, b :: String }

13 changes: 13 additions & 0 deletions test/testdata/Format.floskell.formatted.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,13 @@
module Format where

foo :: Int -> Int
foo 3 = 2
foo x = x

bar :: String -> IO String
bar s = do
x <- return "hello"
return "asdf"

data Baz = Baz { a :: Int, b :: String }

0 comments on commit 4d0b201

Please sign in to comment.