Skip to content

Commit

Permalink
[#187] Remove tasty* dependencies (#198)
Browse files Browse the repository at this point in the history
* [#187] Remove tasty* dependencies

* Remove imports made redundant by [#187]

* [#187] Update CHANGELOG

* [#187] Replace tasty functions in tests.

* fix indentation, naming

* Use checkParellel instead of checkSequential

* Refactor to use membrain style
  • Loading branch information
dalpd authored and vrom911 committed Oct 1, 2019
1 parent cb02810 commit d1be9f1
Show file tree
Hide file tree
Showing 4 changed files with 36 additions and 31 deletions.
2 changes: 2 additions & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,8 @@ The changelog is available [on GitHub][2].

## Unreleased: 0.6.0.0

* [#187](https://github.com/kowainik/relude/issues/187):
Remove `tasty` and `tasty-hedgehog` dependencies and their redundant imports.
* [#195](https://github.com/kowainik/relude/pull/195):
Implement `foldMap1` for `NonEmpty` in terms of `foldr`.
* [#194](https://github.com/kowainik/relude/pull/194):
Expand Down
2 changes: 0 additions & 2 deletions relude.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -188,8 +188,6 @@ test-suite relude-test
, bytestring
, text
, hedgehog ^>= 1.0
, tasty
, tasty-hedgehog ^>= 1.0

ghc-options: -threaded

Expand Down
15 changes: 11 additions & 4 deletions test/Spec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,9 +10,16 @@ module Main where

import Relude

import Test.Tasty (defaultMain)

import Test.Relude.Property (hedgehogTestTree)
import Hedgehog (checkParallel)
import System.IO (hSetEncoding, utf8)
import Test.Relude.Property (hedgehogTestList)

main :: IO ()
main = defaultMain hedgehogTestTree
main = do
-- fix terminal encoding
hSetEncoding stdout utf8
hSetEncoding stderr utf8

mapM checkParallel hedgehogTestList >>= \p -> if and p then exitSuccess else exitFailure


48 changes: 23 additions & 25 deletions test/Test/Relude/Property.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,33 +7,31 @@ Maintainer: Kowainik <xrom.xkov@gmail.com>
-}

module Test.Relude.Property
( hedgehogTestTree
( hedgehogTestList
) where

import Relude

import Data.List (nub)
import Hedgehog (Gen, Property, assert, forAll, property, (===))
import Test.Tasty (TestTree, testGroup)
import Test.Tasty.Hedgehog
import Hedgehog (Gen, Property, Group (..), assert, forAll, property, (===))

import qualified Hedgehog.Gen as Gen
import qualified Hedgehog.Range as Range

hedgehogTestTree :: TestTree
hedgehogTestTree = testGroup "Tests" [utfProps, listProps, boolMProps]
hedgehogTestList :: [Group]
hedgehogTestList = [utfProps, listProps, logicProps]

----------------------------------------------------------------------------
-- utf8 conversion
----------------------------------------------------------------------------

utfProps :: TestTree
utfProps = testGroup "utf8 conversion property tests"
[ testProperty "String to ByteString invertible" prop_StringToBytes
, testProperty "Text to ByteString invertible" prop_TextToBytes
, testProperty "ByteString to Text or String invertible" prop_BytesTo
utfProps :: Group
utfProps = Group "utf8 conversion property tests"
[ ("String to ByteString invertible:", prop_StringToBytes)
, ("Text to ByteString invertible:", prop_TextToBytes)
, ("ByteString to Text or String invertible:" , prop_BytesTo)
]

utf8String :: Gen String
utf8String = Gen.string (Range.linear 0 1000) Gen.unicode

Expand Down Expand Up @@ -72,14 +70,14 @@ prop_BytesTo = property $ do
-- ordNub
----------------------------------------------------------------------------

listProps :: TestTree
listProps = testGroup "list function property tests"
[ testProperty "ordNub xs == nub xs" prop_ordNubCorrect
, testProperty "hashNub xs == nub xs" prop_hashNubCorrect
, testProperty "sortNub xs == sort (nub xs)" prop_sortNubCorrect
, testProperty "sort (unstableNub xs) == sort (nub xs)" prop_unstableNubCorrect
listProps :: Group
listProps = Group "list function property tests"
[ ("ordNub xs == nub xs:", prop_ordNubCorrect)
, ("hashNub xs == nub xs:", prop_hashNubCorrect)
, ("sortNub xs == sort (nub xs):" , prop_sortNubCorrect)
, ("sort (unstableNub xs) == sort (nub xs):" , prop_unstableNubCorrect)
]

genIntList :: Gen [Int]
genIntList = Gen.list (Range.linear 0 1000) Gen.enumBounded

Expand Down Expand Up @@ -107,15 +105,15 @@ prop_unstableNubCorrect = property $ do
-- logicM
----------------------------------------------------------------------------

logicProps :: Group
logicProps = Group "lifted logic function property tests"
[ ("andM:", prop_andM)
, ("orM:", prop_orM)
]

genBoolList :: Gen [Bool]
genBoolList = Gen.list (Range.linear 0 1000) Gen.bool

boolMProps :: TestTree
boolMProps = testGroup "lifted logic function property tests"
[ testProperty "andM" prop_andM
, testProperty "orM" prop_orM
]

prop_andM :: Property
prop_andM = property $ do
bs <- forAll genBoolList
Expand Down

0 comments on commit d1be9f1

Please sign in to comment.