Skip to content

Commit 4c2011a

Browse files
committed
Extract tests into a standalone testsuite
1 parent 63c7d9c commit 4c2011a

12 files changed

+112
-76
lines changed

plugins/hls-brittany-plugin/hls-brittany-plugin.cabal

Lines changed: 39 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -28,3 +28,42 @@ library
2828
, transformers
2929

3030
default-language: Haskell2010
31+
32+
executable test-server
33+
default-language: Haskell2010
34+
build-depends:
35+
, base
36+
, data-default
37+
, ghcide
38+
, hls-brittany-plugin
39+
, hls-plugin-api
40+
, shake
41+
main-is: Server.hs
42+
hs-source-dirs: test
43+
ghc-options: -threaded
44+
45+
test-suite tests
46+
type: exitcode-stdio-1.0
47+
default-language: Haskell2010
48+
build-tool-depends:
49+
hls-brittany-plugin:test-server -any,
50+
hs-source-dirs: test
51+
main-is: Main.hs
52+
build-depends:
53+
, aeson
54+
, base
55+
, bytestring
56+
, data-default
57+
, deepseq
58+
, ghcide >= 0.7.5.0
59+
, hls-brittany-plugin
60+
, hspec-expectations
61+
, megaparsec
62+
, lens
63+
, lsp-test
64+
, tasty
65+
, tasty-ant-xml >=1.1.6
66+
, tasty-hunit
67+
, tasty-golden
68+
, tasty-rerun
69+
, text
Lines changed: 54 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,54 @@
1+
{-# LANGUAGE OverloadedStrings #-}
2+
module Main(main) where
3+
4+
import Control.Monad.IO.Class
5+
import Data.Aeson
6+
import qualified Data.ByteString.Lazy as BS
7+
import qualified Data.Text.Encoding as T
8+
import qualified Data.Text.IO as T
9+
import Language.LSP.Test
10+
import Language.LSP.Types
11+
import Test.Tasty
12+
import Test.Tasty.Golden
13+
import Test.Tasty.HUnit
14+
import Test.Tasty.Runners (
15+
consoleTestReporter,
16+
listingTests,
17+
)
18+
import Test.Tasty.Ingredients.Rerun
19+
import Test.Tasty.Runners.AntXML
20+
21+
main :: IO ()
22+
main = defaultMainWithIngredients
23+
[antXMLRunner, rerunningTests [listingTests, consoleTestReporter]]
24+
tests
25+
26+
testCommand = "test-server"
27+
28+
tests :: TestTree
29+
tests = testGroup "brittany" [
30+
goldenVsStringDiff "formats a document with LF endings" goldenGitDiff "test/testdata/BrittanyLF.formatted_document.hs" $ runSession testCommand fullCaps "test/testdata" $ do
31+
doc <- openDoc "BrittanyLF.hs" "haskell"
32+
formatDoc doc (FormattingOptions 4 True Nothing Nothing Nothing)
33+
BS.fromStrict . T.encodeUtf8 <$> documentContents doc
34+
35+
, goldenVsStringDiff "formats a document with CRLF endings" goldenGitDiff "test/testdata/BrittanyCRLF.formatted_document.hs" $ runSession testCommand fullCaps "test/testdata" $ do
36+
doc <- openDoc "BrittanyCRLF.hs" "haskell"
37+
formatDoc doc (FormattingOptions 4 True Nothing Nothing Nothing)
38+
BS.fromStrict . T.encodeUtf8 <$> documentContents doc
39+
40+
, goldenVsStringDiff "formats a range with LF endings" goldenGitDiff "test/testdata/BrittanyLF.formatted_range.hs" $ runSession testCommand fullCaps "test/testdata" $ do
41+
doc <- openDoc "BrittanyLF.hs" "haskell"
42+
let range = Range (Position 1 0) (Position 2 22)
43+
formatRange doc (FormattingOptions 4 True Nothing Nothing Nothing) range
44+
BS.fromStrict . T.encodeUtf8 <$> documentContents doc
45+
46+
, goldenVsStringDiff "formats a range with CRLF endings" goldenGitDiff "test/testdata/BrittanyCRLF.formatted_range.hs" $ runSession testCommand fullCaps "test/testdata" $ do
47+
doc <- openDoc "BrittanyCRLF.hs" "haskell"
48+
let range = Range (Position 1 0) (Position 2 22)
49+
formatRange doc (FormattingOptions 4 True Nothing Nothing Nothing) range
50+
BS.fromStrict . T.encodeUtf8 <$> documentContents doc
51+
]
52+
53+
goldenGitDiff :: FilePath -> FilePath -> [String]
54+
goldenGitDiff fRef fNew = ["git", "diff", "--no-index", "--text", "--exit-code", fRef, fNew]
Lines changed: 19 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,19 @@
1+
{-# LANGUAGE ViewPatterns #-}
2+
{-# LANGUAGE OverloadedStrings #-}
3+
module Main(main) where
4+
5+
import Data.Default
6+
import Development.IDE.Main
7+
import qualified Development.IDE.Plugin.HLS.GhcIde as Ghcide
8+
import Ide.Plugin.Config
9+
import Ide.Plugin.Brittany as B
10+
import Ide.PluginUtils
11+
12+
main :: IO ()
13+
main = defaultMain def
14+
{ argsHlsPlugins = pluginDescToIdePlugins $
15+
[ B.descriptor "brittany"
16+
] <>
17+
Ghcide.descriptors
18+
, argsDefaultHlsConfig = def { formattingProvider = "brittany" }
19+
}

test/functional/Format.hs

Lines changed: 0 additions & 38 deletions
Original file line numberDiff line numberDiff line change
@@ -14,9 +14,7 @@ import Test.Tasty.Golden
1414
import Test.Tasty.HUnit
1515
import Control.Lens ((^.))
1616

17-
#if AGPL
1817
import qualified Data.Text.IO as T
19-
#endif
2018

2119
tests :: TestTree
2220
tests = testGroup "format document" [
@@ -31,9 +29,6 @@ tests = testGroup "format document" [
3129
, rangeTests
3230
, providerTests
3331
, stylishHaskellTests
34-
#if AGPL
35-
, brittanyTests
36-
#endif
3732
, ormoluTests
3833
, fourmoluTests
3934
]
@@ -110,37 +105,6 @@ stylishHaskellTests = testGroup "stylish-haskell" [
110105
BS.fromStrict . T.encodeUtf8 <$> documentContents doc
111106
]
112107

113-
#if AGPL
114-
brittanyTests :: TestTree
115-
brittanyTests = testGroup "brittany" [
116-
goldenVsStringDiff "formats a document with LF endings" goldenGitDiff "test/testdata/format/BrittanyLF.formatted_document.hs" $ runSession hlsCommand fullCaps "test/testdata/format" $ do
117-
sendNotification SWorkspaceDidChangeConfiguration (DidChangeConfigurationParams (formatLspConfig "brittany"))
118-
doc <- openDoc "BrittanyLF.hs" "haskell"
119-
formatDoc doc (FormattingOptions 4 True Nothing Nothing Nothing)
120-
BS.fromStrict . T.encodeUtf8 <$> documentContents doc
121-
122-
, goldenVsStringDiff "formats a document with CRLF endings" goldenGitDiff "test/testdata/format/BrittanyCRLF.formatted_document.hs" $ runSession hlsCommand fullCaps "test/testdata/format" $ do
123-
sendNotification SWorkspaceDidChangeConfiguration (DidChangeConfigurationParams (formatLspConfig "brittany"))
124-
doc <- openDoc "BrittanyCRLF.hs" "haskell"
125-
formatDoc doc (FormattingOptions 4 True Nothing Nothing Nothing)
126-
BS.fromStrict . T.encodeUtf8 <$> documentContents doc
127-
128-
, goldenVsStringDiff "formats a range with LF endings" goldenGitDiff "test/testdata/format/BrittanyLF.formatted_range.hs" $ runSession hlsCommand fullCaps "test/testdata/format" $ do
129-
sendNotification SWorkspaceDidChangeConfiguration (DidChangeConfigurationParams (formatLspConfig "brittany"))
130-
doc <- openDoc "BrittanyLF.hs" "haskell"
131-
let range = Range (Position 1 0) (Position 2 22)
132-
formatRange doc (FormattingOptions 4 True Nothing Nothing Nothing) range
133-
BS.fromStrict . T.encodeUtf8 <$> documentContents doc
134-
135-
, goldenVsStringDiff "formats a range with CRLF endings" goldenGitDiff "test/testdata/format/BrittanyCRLF.formatted_range.hs" $ runSession hlsCommand fullCaps "test/testdata/format" $ do
136-
sendNotification SWorkspaceDidChangeConfiguration (DidChangeConfigurationParams (formatLspConfig "brittany"))
137-
doc <- openDoc "BrittanyCRLF.hs" "haskell"
138-
let range = Range (Position 1 0) (Position 2 22)
139-
formatRange doc (FormattingOptions 4 True Nothing Nothing Nothing) range
140-
BS.fromStrict . T.encodeUtf8 <$> documentContents doc
141-
]
142-
#endif
143-
144108
ormoluTests :: TestTree
145109
ormoluTests = testGroup "ormolu"
146110
[ goldenVsStringDiff "formats correctly" goldenGitDiff "test/testdata/format/Format.ormolu.formatted.hs" $ runSession hlsCommand fullCaps "test/testdata/format" $ do
@@ -172,11 +136,9 @@ fourmoluTests = testGroup "fourmolu"
172136
formatLspConfig :: Value -> Value
173137
formatLspConfig provider = object [ "haskell" .= object ["formattingProvider" .= (provider :: Value)] ]
174138

175-
#if AGPL
176139
-- | The same as 'formatLspConfig' but using the legacy section name
177140
formatLspConfigOld :: Value -> Value
178141
formatLspConfigOld provider = object [ "languageServerHaskell" .= object ["formattingProvider" .= (provider :: Value)] ]
179-
#endif
180142

181143
formatConfig :: Value -> SessionConfig
182144
formatConfig provider = defaultConfig { lspConfig = Just (formatLspConfig provider) }

test/testdata/format/Format.brittany.formatted.hs

Lines changed: 0 additions & 18 deletions
This file was deleted.

test/testdata/format/Format.brittany_post_floskell.formatted.hs

Lines changed: 0 additions & 20 deletions
This file was deleted.

0 commit comments

Comments
 (0)