Skip to content

Commit

Permalink
Extract tests into a standalone testsuite
Browse files Browse the repository at this point in the history
  • Loading branch information
pepeiborra committed Feb 21, 2021
1 parent 63c7d9c commit 4c2011a
Show file tree
Hide file tree
Showing 12 changed files with 112 additions and 76 deletions.
39 changes: 39 additions & 0 deletions plugins/hls-brittany-plugin/hls-brittany-plugin.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -28,3 +28,42 @@ library
, transformers

default-language: Haskell2010

executable test-server
default-language: Haskell2010
build-depends:
, base
, data-default
, ghcide
, hls-brittany-plugin
, hls-plugin-api
, shake
main-is: Server.hs
hs-source-dirs: test
ghc-options: -threaded

test-suite tests
type: exitcode-stdio-1.0
default-language: Haskell2010
build-tool-depends:
hls-brittany-plugin:test-server -any,
hs-source-dirs: test
main-is: Main.hs
build-depends:
, aeson
, base
, bytestring
, data-default
, deepseq
, ghcide >= 0.7.5.0
, hls-brittany-plugin
, hspec-expectations
, megaparsec
, lens
, lsp-test
, tasty
, tasty-ant-xml >=1.1.6
, tasty-hunit
, tasty-golden
, tasty-rerun
, text
54 changes: 54 additions & 0 deletions plugins/hls-brittany-plugin/test/Main.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,54 @@
{-# LANGUAGE OverloadedStrings #-}
module Main(main) where

import Control.Monad.IO.Class
import Data.Aeson
import qualified Data.ByteString.Lazy as BS
import qualified Data.Text.Encoding as T
import qualified Data.Text.IO as T
import Language.LSP.Test
import Language.LSP.Types
import Test.Tasty
import Test.Tasty.Golden
import Test.Tasty.HUnit
import Test.Tasty.Runners (
consoleTestReporter,
listingTests,
)
import Test.Tasty.Ingredients.Rerun
import Test.Tasty.Runners.AntXML

main :: IO ()
main = defaultMainWithIngredients
[antXMLRunner, rerunningTests [listingTests, consoleTestReporter]]
tests

testCommand = "test-server"

tests :: TestTree
tests = testGroup "brittany" [
goldenVsStringDiff "formats a document with LF endings" goldenGitDiff "test/testdata/BrittanyLF.formatted_document.hs" $ runSession testCommand fullCaps "test/testdata" $ do
doc <- openDoc "BrittanyLF.hs" "haskell"
formatDoc doc (FormattingOptions 4 True Nothing Nothing Nothing)
BS.fromStrict . T.encodeUtf8 <$> documentContents doc

, goldenVsStringDiff "formats a document with CRLF endings" goldenGitDiff "test/testdata/BrittanyCRLF.formatted_document.hs" $ runSession testCommand fullCaps "test/testdata" $ do
doc <- openDoc "BrittanyCRLF.hs" "haskell"
formatDoc doc (FormattingOptions 4 True Nothing Nothing Nothing)
BS.fromStrict . T.encodeUtf8 <$> documentContents doc

, goldenVsStringDiff "formats a range with LF endings" goldenGitDiff "test/testdata/BrittanyLF.formatted_range.hs" $ runSession testCommand fullCaps "test/testdata" $ do
doc <- openDoc "BrittanyLF.hs" "haskell"
let range = Range (Position 1 0) (Position 2 22)
formatRange doc (FormattingOptions 4 True Nothing Nothing Nothing) range
BS.fromStrict . T.encodeUtf8 <$> documentContents doc

, goldenVsStringDiff "formats a range with CRLF endings" goldenGitDiff "test/testdata/BrittanyCRLF.formatted_range.hs" $ runSession testCommand fullCaps "test/testdata" $ do
doc <- openDoc "BrittanyCRLF.hs" "haskell"
let range = Range (Position 1 0) (Position 2 22)
formatRange doc (FormattingOptions 4 True Nothing Nothing Nothing) range
BS.fromStrict . T.encodeUtf8 <$> documentContents doc
]

goldenGitDiff :: FilePath -> FilePath -> [String]
goldenGitDiff fRef fNew = ["git", "diff", "--no-index", "--text", "--exit-code", fRef, fNew]
19 changes: 19 additions & 0 deletions plugins/hls-brittany-plugin/test/Server.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,19 @@
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE OverloadedStrings #-}
module Main(main) where

import Data.Default
import Development.IDE.Main
import qualified Development.IDE.Plugin.HLS.GhcIde as Ghcide
import Ide.Plugin.Config
import Ide.Plugin.Brittany as B
import Ide.PluginUtils

main :: IO ()
main = defaultMain def
{ argsHlsPlugins = pluginDescToIdePlugins $
[ B.descriptor "brittany"
] <>
Ghcide.descriptors
, argsDefaultHlsConfig = def { formattingProvider = "brittany" }
}
File renamed without changes.
File renamed without changes.
38 changes: 0 additions & 38 deletions test/functional/Format.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,9 +14,7 @@ import Test.Tasty.Golden
import Test.Tasty.HUnit
import Control.Lens ((^.))

#if AGPL
import qualified Data.Text.IO as T
#endif

tests :: TestTree
tests = testGroup "format document" [
Expand All @@ -31,9 +29,6 @@ tests = testGroup "format document" [
, rangeTests
, providerTests
, stylishHaskellTests
#if AGPL
, brittanyTests
#endif
, ormoluTests
, fourmoluTests
]
Expand Down Expand Up @@ -110,37 +105,6 @@ stylishHaskellTests = testGroup "stylish-haskell" [
BS.fromStrict . T.encodeUtf8 <$> documentContents doc
]

#if AGPL
brittanyTests :: TestTree
brittanyTests = testGroup "brittany" [
goldenVsStringDiff "formats a document with LF endings" goldenGitDiff "test/testdata/format/BrittanyLF.formatted_document.hs" $ runSession hlsCommand fullCaps "test/testdata/format" $ do
sendNotification SWorkspaceDidChangeConfiguration (DidChangeConfigurationParams (formatLspConfig "brittany"))
doc <- openDoc "BrittanyLF.hs" "haskell"
formatDoc doc (FormattingOptions 4 True Nothing Nothing Nothing)
BS.fromStrict . T.encodeUtf8 <$> documentContents doc

, goldenVsStringDiff "formats a document with CRLF endings" goldenGitDiff "test/testdata/format/BrittanyCRLF.formatted_document.hs" $ runSession hlsCommand fullCaps "test/testdata/format" $ do
sendNotification SWorkspaceDidChangeConfiguration (DidChangeConfigurationParams (formatLspConfig "brittany"))
doc <- openDoc "BrittanyCRLF.hs" "haskell"
formatDoc doc (FormattingOptions 4 True Nothing Nothing Nothing)
BS.fromStrict . T.encodeUtf8 <$> documentContents doc

, goldenVsStringDiff "formats a range with LF endings" goldenGitDiff "test/testdata/format/BrittanyLF.formatted_range.hs" $ runSession hlsCommand fullCaps "test/testdata/format" $ do
sendNotification SWorkspaceDidChangeConfiguration (DidChangeConfigurationParams (formatLspConfig "brittany"))
doc <- openDoc "BrittanyLF.hs" "haskell"
let range = Range (Position 1 0) (Position 2 22)
formatRange doc (FormattingOptions 4 True Nothing Nothing Nothing) range
BS.fromStrict . T.encodeUtf8 <$> documentContents doc

, goldenVsStringDiff "formats a range with CRLF endings" goldenGitDiff "test/testdata/format/BrittanyCRLF.formatted_range.hs" $ runSession hlsCommand fullCaps "test/testdata/format" $ do
sendNotification SWorkspaceDidChangeConfiguration (DidChangeConfigurationParams (formatLspConfig "brittany"))
doc <- openDoc "BrittanyCRLF.hs" "haskell"
let range = Range (Position 1 0) (Position 2 22)
formatRange doc (FormattingOptions 4 True Nothing Nothing Nothing) range
BS.fromStrict . T.encodeUtf8 <$> documentContents doc
]
#endif

ormoluTests :: TestTree
ormoluTests = testGroup "ormolu"
[ goldenVsStringDiff "formats correctly" goldenGitDiff "test/testdata/format/Format.ormolu.formatted.hs" $ runSession hlsCommand fullCaps "test/testdata/format" $ do
Expand Down Expand Up @@ -172,11 +136,9 @@ fourmoluTests = testGroup "fourmolu"
formatLspConfig :: Value -> Value
formatLspConfig provider = object [ "haskell" .= object ["formattingProvider" .= (provider :: Value)] ]

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

formatConfig :: Value -> SessionConfig
formatConfig provider = defaultConfig { lspConfig = Just (formatLspConfig provider) }
Expand Down
18 changes: 0 additions & 18 deletions test/testdata/format/Format.brittany.formatted.hs

This file was deleted.

20 changes: 0 additions & 20 deletions test/testdata/format/Format.brittany_post_floskell.formatted.hs

This file was deleted.

1 comment on commit 4c2011a

@isovector
Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Marvelous. Thanks so much!

Please sign in to comment.