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 0af2122
Show file tree
Hide file tree
Showing 4 changed files with 44 additions and 45 deletions.
53 changes: 26 additions & 27 deletions test/Spec.hs → test/Main.hs
Original file line number Diff line number Diff line change
@@ -1,38 +1,45 @@
module Main (main) where

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

import Data.Maybe
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.Hspec
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
args <- getArgs
testOutputFiles <- fmap sortTests discoverIntegrationTests
let hieDirectories = map (dropExtension . snd) testOutputFiles
drawDots = mapM_ (drawDot . (<.> ".dot")) hieDirectories
graphviz = "--graphviz" `elem` args
withArgs (filter (/="--graphviz") args) $
hspec $ afterAll_ (when graphviz drawDots) $ do
describe "Weeder.Run" $
describe "runWeeder" $
zipWithM_ (uncurry integrationTestSpec) testOutputFiles hieDirectories
UnitTests.spec
defaultMain $
testGroup "Weeder"
[ testGroup "Weeder.Run" $
[ testGroup "runWeeder" $
zipWith (uncurry integrationTest)
testOutputFiles
hieDirectories
]
, UnitTests.Weeder.ConfigSpec.tests
]
where
-- Draw a dotfile via graphviz
drawDot f = callCommand $ "dot -Tpng " ++ f ++ " -o " ++ (f -<.> ".png")
-- Sort the output files such that the failing ones go last
sortTests = sortOn (isJust . fst)

Expand All @@ -44,18 +51,10 @@ main = do
-- 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@.
integrationTestSpec :: Maybe FilePath -> FilePath -> FilePath -> Spec
integrationTestSpec failingFile stdoutFile hieDirectory = do
it (integrationTestText ++ hieDirectory) $ do
expectedOutput <- readFile stdoutFile
actualOutput <- integrationTestOutput hieDirectory
case failingFile of
Just f -> do
failingOutput <- readFile f
actualOutput `shouldNotBe` expectedOutput
actualOutput `shouldBe` failingOutput
Nothing ->
actualOutput `shouldBe` expectedOutput
integrationTest :: Maybe FilePath -> FilePath -> FilePath -> TestTree
integrationTest failingFile stdoutFile hieDirectory = do
goldenVsString (integrationTestText ++ hieDirectory) (fromMaybe stdoutFile failingFile) $
integrationTestOutput hieDirectory
where
integrationTestText = case failingFile of
Nothing -> "produces the expected output for "
Expand All @@ -74,7 +73,7 @@ discoverIntegrationTests = do

-- | 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 String
integrationTestOutput :: FilePath -> IO LBS.ByteString
integrationTestOutput hieDirectory = do
hieFiles <- Weeder.Main.getHieFiles ".hie" [hieDirectory] True
weederConfig <- TOML.decodeFile configExpr >>= either throwIO pure
Expand All @@ -83,6 +82,6 @@ integrationTestOutput hieDirectory = do
graph' = export (defaultStyle (occNameString . Weeder.declOccName)) graph
handle (\e -> hPrint stderr (e :: IOException)) $
writeFile (hieDirectory <.> ".dot") graph'
pure (unlines $ map Weeder.Run.formatWeed weeds)
pure (LBS.fromStrict $ encodeUtf8 $ pack $ unlines $ map Weeder.Run.formatWeed weeds)
where
configExpr = hieDirectory <.> ".toml"
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 0af2122

Please sign in to comment.