Skip to content

Commit

Permalink
Replace tasty by hspec
Browse files Browse the repository at this point in the history
  • Loading branch information
memowe committed Apr 29, 2024
1 parent 895d074 commit 90279b4
Show file tree
Hide file tree
Showing 2 changed files with 26 additions and 37 deletions.
57 changes: 24 additions & 33 deletions test/Main.hs
Original file line number Diff line number Diff line change
@@ -1,12 +1,12 @@
module Main where

import Test.Tasty ( defaultMain, testGroup, TestTree, withResource )
import Test.Tasty.HUnit ( testCase, (@?=) )
import Trivialini ( Ini(..), IniMap, readIniFile )
import Data.Map ( fromList )
import System.FilePath ( (</>) )
import System.Directory ( getTemporaryDirectory, removeFile )
import Trivialini
import Test.Hspec
import Data.Map
import System.IO.Temp
import System.IO

exampleIni :: String
exampleIni = "[xnorfzt]\n\
\foo = bar\n\
\\n\
Expand All @@ -16,37 +16,28 @@ exampleIni = "[xnorfzt]\n\
\ baz quux = quuux\n\
\"

expectedIni :: Ini
expectedIni = Ini $ fromList [
("xnorfzt", fromList [("foo", "bar"), ("x", "17"), ("answer", "42")]),
("section name", fromList [("baz quux", "quuux")])
]

testIniParsing = testGroup "Ini parsing"
[ testCase "Complex ini data" $
read exampleIni @?= expectedIni
, testCase "parse . show . parse = parse" $
let intermediatini = read exampleIni :: Ini
in (read . show) intermediatini @?= expectedIni
]

testIniIO :: IO (FilePath, IniMap) -> TestTree
testIniIO ioData = testGroup "Read ini file"
[ testCase "Expected complete ini data" $ do
iniMap <- snd <$> ioData
iniMap @?= sections expectedIni
]
testIniParsing :: Spec
testIniParsing = describe "Ini parsing" $ do
it "Complex ini data" $
read exampleIni `shouldBe` expectedIni
it "parse . show . parse = parse" $
let intermediatini = read exampleIni :: Ini
in (read . show) intermediatini `shouldBe` expectedIni

testIniFileReading = withResource io cleanup testIniIO
where io = do name <- write
ini <- readIniFile name
return (name, ini)
write = do name <- tmpFile
writeFile name exampleIni
return name
tmpFile = (</> "trivialini-test.ini") <$> getTemporaryDirectory
cleanup = removeFile . fst
testIniFileReading :: Spec
testIniFileReading = describe "Read ini file" $ do
loadedIni <- runIO $ withSystemTempFile "trivialini-test.ini" $ \fp h -> do
hPutStr h exampleIni >> hClose h
readIniFile fp
it "Expected complete ini data" $ loadedIni `shouldBe` sections expectedIni

main = defaultMain $ testGroup "Unit tests"
[ testIniParsing
, testIniFileReading
]
main :: IO ()
main = hspec $ describe "Unit tests" $ do
testIniParsing
testIniFileReading
6 changes: 2 additions & 4 deletions trivialini.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -26,9 +26,7 @@ Test-Suite test-trivialini
type: exitcode-stdio-1.0
build-depends:
trivialini,
tasty,
tasty-hunit,
filepath,
directory
hspec,
temporary
hs-source-dirs: test
main-is: Main.hs

0 comments on commit 90279b4

Please sign in to comment.