Skip to content

Commit

Permalink
Rewrite tests to use tasty & tasty-golden
Browse files Browse the repository at this point in the history
  • Loading branch information
ocharles committed Jun 8, 2024
1 parent 66fbba0 commit 44a6a02
Show file tree
Hide file tree
Showing 9 changed files with 100 additions and 20 deletions.
80 changes: 80 additions & 0 deletions test/Main.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,80 @@
module Main (main) where

import qualified Weeder.Main
import qualified Weeder.Run
import qualified Weeder
import qualified TOML
import qualified UnitTests.Weeder.ConfigSpec

import Algebra.Graph.Export.Dot
import GHC.Types.Name.Occurrence (occNameString)
import System.Directory
import System.Environment (getArgs, withArgs)
import System.FilePath
import System.Process
import System.IO (stderr, hPrint)
import Test.Tasty (TestTree, defaultMain, testGroup)
import Control.Monad (zipWithM_, when)
import Control.Exception ( throwIO, IOException, handle )
import Data.Maybe (isJust)
import Data.List (find, sortOn)
import Data.ByteString (ByteString)
import qualified Data.ByteString.Lazy as LBS
import Data.Text (Text, pack)
import Data.Text.Encoding (encodeUtf8)
import Test.Tasty.Golden

main :: IO ()
main = do
testOutputFiles <- discoverIntegrationTests
let hieDirectories = map dropExtension testOutputFiles
defaultMain $
testGroup "Weeder"
[ testGroup "Weeder.Run" $
[ testGroup "runWeeder" $
zipWith integrationTest
testOutputFiles
hieDirectories
]
, UnitTests.Weeder.ConfigSpec.tests
]

-- | Run weeder on @hieDirectory@, comparing the output to @stdoutFile@.
--
-- The directory containing @hieDirectory@ must also have a @.toml@ file
-- with the same name as @hieDirectory@.
--
-- If @failingFile@ is @Just@, it is used as the expected output instead of
-- @stdoutFile@, and a different failure message is printed if the output
-- matches @stdoutFile@.
integrationTest :: FilePath -> FilePath -> TestTree
integrationTest stdoutFile hieDirectory = do
goldenVsString (integrationTestText ++ hieDirectory) stdoutFile $
integrationTestOutput hieDirectory
where
integrationTestText = "produces the expected output for "

-- | Returns detected .failing and .stdout files in ./test/Spec
discoverIntegrationTests :: IO [FilePath]
discoverIntegrationTests = do
contents <- listDirectory testPath
let stdoutFiles = map (testPath </>) $
filter (".stdout" `isExtensionOf`) contents
pure stdoutFiles
where
testPath = "./test/Spec"

-- | Run weeder on the given directory for .hie files, returning stdout
-- Also creates a dotfile containing the dependency graph as seen by Weeder
integrationTestOutput :: FilePath -> IO LBS.ByteString
integrationTestOutput hieDirectory = do
hieFiles <- Weeder.Main.getHieFiles ".hie" [hieDirectory] True
weederConfig <- TOML.decodeFile configExpr >>= either throwIO pure
let (weeds, analysis) = Weeder.Run.runWeeder weederConfig hieFiles
graph = Weeder.dependencyGraph analysis
graph' = export (defaultStyle (occNameString . Weeder.declOccName)) graph
handle (\e -> hPrint stderr (e :: IOException)) $
writeFile (hieDirectory <.> ".dot") graph'
pure (LBS.fromStrict $ encodeUtf8 $ pack $ unlines $ map Weeder.Run.formatWeed weeds)
where
configExpr = hieDirectory <.> ".toml"
1 change: 0 additions & 1 deletion test/Spec/OverloadedLists.failing

This file was deleted.

1 change: 1 addition & 0 deletions test/Spec/OverloadedLists.stdout
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
test/Spec/OverloadedLists/OverloadedLists.hs:9: (Instance) :: IsList (BetterList x)
1 change: 1 addition & 0 deletions test/Spec/OverloadedStrings.stdout
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
test/Spec/OverloadedStrings/OverloadedStrings.hs:10: (Instance) :: IsString BetterString
Empty file removed test/Spec/RangeEnum.stdout
Empty file.
1 change: 0 additions & 1 deletion test/Spec/TypeFamilies.stdout

This file was deleted.

1 change: 0 additions & 1 deletion test/UnitTests.hs

This file was deleted.

23 changes: 11 additions & 12 deletions test/UnitTests/Weeder/ConfigSpec.hs
Original file line number Diff line number Diff line change
@@ -1,25 +1,24 @@
module UnitTests.Weeder.ConfigSpec (spec) where
module UnitTests.Weeder.ConfigSpec (tests) where

import Weeder.Config
import qualified TOML
import qualified Data.Text as T
import Test.Hspec (Spec, describe, it)
import Test.Tasty.HUnit
import Test.Hspec.Expectations (shouldBe)
import Test.Tasty (TestTree, testGroup)

spec :: Spec
spec =
describe "Weeder.Config" $
describe "configToToml" $
it "passes prop_configToToml" prop_configToToml
tests :: TestTree
tests =
testGroup "Weeder.Config"
[ testCase "configToToml" configToTomlTests ]

-- >>> prop_configToToml
-- True
prop_configToToml :: Bool
prop_configToToml =
configToTomlTests :: Assertion
configToTomlTests =
let cf = Config
{ rootPatterns = mempty
, typeClassRoots = True
, rootInstances = [InstanceOnly "Quux\\\\[\\]", ClassOnly "[\\[\\\\[baz" <> ModuleOnly "[Quuux]", InstanceOnly "[\\[\\\\[baz" <> ClassOnly "[Quuux]" <> ModuleOnly "[Quuuux]"]
, unusedTypes = True
}
cf' = T.pack $ configToToml cf
in TOML.decode cf' == Right cf
in TOML.decode cf' `shouldBe` Right cf
12 changes: 7 additions & 5 deletions weeder.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -70,19 +70,21 @@ test-suite weeder-test
, directory
, filepath
, ghc
, hspec
, process
, tasty
, tasty-hunit-compat
, tasty-golden
, text
, toml-reader
, weeder
, hspec-expectations
, text
, bytestring
type: exitcode-stdio-1.0
main-is: Spec.hs
main-is: Main.hs
hs-source-dirs: test
autogen-modules:
Paths_weeder
other-modules:
Paths_weeder
UnitTests
-- Tests
Spec.ApplicativeDo.ApplicativeDo
Spec.BasicExample.BasicExample
Expand Down

0 comments on commit 44a6a02

Please sign in to comment.