Skip to content

Commit ff578b8

Browse files
authored
Merge pull request #69 from fendor/fix-warnings-brittany-pr-cleanup
Fix Brittany test suite
2 parents cfe4369 + 910696a commit ff578b8

File tree

2 files changed

+11
-13
lines changed

2 files changed

+11
-13
lines changed

test/functional/FormatSpec.hs

Lines changed: 11 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -92,33 +92,34 @@ spec = do
9292
sendNotification WorkspaceDidChangeConfiguration (DidChangeConfigurationParams (formatLspConfig "brittany"))
9393
let opts = DocumentFormattingParams doc (FormattingOptions 4 True) Nothing
9494
ResponseMessage _ _ (Just edits) _ <- request TextDocumentFormatting opts
95-
liftIO $ edits `shouldBe` [TextEdit (Range (Position 0 0) (Position 3 0))
96-
"foo :: Int -> String -> IO ()\nfoo x y = do\n print x\n return 42\n"]
95+
liftIO $ edits `shouldBe` [TextEdit (Range (Position 0 0) (Position 5 0))
96+
"module BrittanyLF where\n\nfoo :: Int -> String -> IO ()\nfoo x y = do\n print x\n return ()\n"]
9797

9898
it "formats a document with CRLF endings" $ runSession hieCommand fullCaps "test/testdata" $ do
9999
doc <- openDoc "BrittanyCRLF.hs" "haskell"
100100
sendNotification WorkspaceDidChangeConfiguration (DidChangeConfigurationParams (formatLspConfig "brittany"))
101101
let opts = DocumentFormattingParams doc (FormattingOptions 4 True) Nothing
102102
ResponseMessage _ _ (Just edits) _ <- request TextDocumentFormatting opts
103-
liftIO $ edits `shouldBe` [TextEdit (Range (Position 0 0) (Position 3 0))
104-
"foo :: Int -> String -> IO ()\nfoo x y = do\n print x\n return 42\n"]
103+
liftIO $ edits `shouldBe` [TextEdit (Range (Position 0 0) (Position 5 0))
104+
"module BrittanyCRLF where\n\nfoo :: Int -> String -> IO ()\nfoo x y = do\n print x\n return ()\n"]
105105

106106
it "formats a range with LF endings" $ runSession hieCommand fullCaps "test/testdata" $ do
107107
doc <- openDoc "BrittanyLF.hs" "haskell"
108108
sendNotification WorkspaceDidChangeConfiguration (DidChangeConfigurationParams (formatLspConfig "brittany"))
109-
let range = Range (Position 1 0) (Position 2 22)
109+
let range = Range (Position 3 0) (Position 5 22)
110110
opts = DocumentRangeFormattingParams doc range (FormattingOptions 4 True) Nothing
111111
ResponseMessage _ _ (Just edits) _ <- request TextDocumentRangeFormatting opts
112-
liftIO $ edits `shouldBe` [TextEdit (Range (Position 1 0) (Position 3 0))
113-
"foo x y = do\n print x\n return 42\n"]
112+
liftIO $ edits `shouldBe` [TextEdit (Range (Position 3 0) (Position 6 0))
113+
"foo x y = do\n print x\n return ()\n"]
114114

115115
it "formats a range with CRLF endings" $ runSession hieCommand fullCaps "test/testdata" $ do
116116
doc <- openDoc "BrittanyCRLF.hs" "haskell"
117-
let range = Range (Position 1 0) (Position 2 22)
117+
sendNotification WorkspaceDidChangeConfiguration (DidChangeConfigurationParams (formatLspConfig "brittany"))
118+
let range = Range (Position 3 0) (Position 5 22)
118119
opts = DocumentRangeFormattingParams doc range (FormattingOptions 4 True) Nothing
119120
ResponseMessage _ _ (Just edits) _ <- request TextDocumentRangeFormatting opts
120-
liftIO $ edits `shouldBe` [TextEdit (Range (Position 1 0) (Position 3 0))
121-
"foo x y = do\n print x\n return 42\n"]
121+
liftIO $ edits `shouldBe` [TextEdit (Range (Position 3 0) (Position 6 0))
122+
"foo x y = do\n print x\n return ()\n"]
122123

123124
-- ---------------------------------
124125

test/utils/TestUtils.hs

Lines changed: 0 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -24,12 +24,9 @@ where
2424

2525
-- import Control.Concurrent.STM
2626
import Control.Monad
27-
import Data.Aeson.Types (typeMismatch)
2827
import Data.Default
2928
import Data.List (intercalate)
30-
import Data.Text (pack)
3129
-- import Data.Typeable
32-
import Data.Yaml
3330
-- import qualified Data.Map as Map
3431
import Data.Maybe
3532
import Language.Haskell.LSP.Core

0 commit comments

Comments
 (0)