Skip to content

Commit

Permalink
Support for tasty-discover
Browse files Browse the repository at this point in the history
  • Loading branch information
newhoggy committed Jan 14, 2025
1 parent a7dcda2 commit e42e922
Show file tree
Hide file tree
Showing 5 changed files with 31 additions and 23 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -2,22 +2,22 @@

module Effectful.Zoo.Hedgehog.Test.PropertySpec where

import Effectful.Zoo.Hedgehog
import Effectful.Zoo.Hedgehog.Effect.Run
import HaskellWorks.Prelude
import Hedgehog hiding (property, forAll)
import Hedgehog qualified as H
import Hedgehog.Gen qualified as G
import Hedgehog.Range qualified as R

property_spec :: H.PropertyT IO ()
property_spec = property do
tasty_property_spec :: PropertyT IO ()
tasty_property_spec = property do
a <- forAll $ G.int (R.linear 0 100)
True === True
a === a
H.success

test_spec :: H.TestT IO ()
test_spec = unit do
tasty_unit_spec :: TestT IO ()
tasty_unit_spec = unit do
True === True
True === True
H.success
18 changes: 1 addition & 17 deletions components/hedgehog-test/Main.hs
Original file line number Diff line number Diff line change
@@ -1,17 +1 @@
module Main where

import Effectful.Zoo.Hedgehog.Api.Tasty
import Effectful.Zoo.Hedgehog.Test.PropertySpec
import Test.Tasty (TestTree, defaultMain, testGroup)
import HaskellWorks.Prelude

tests :: TestTree
tests =
testGroup "all"
[ toTestTree "Simple property spec" property_spec
, toTestTree "Simple test spec" test_spec
]

main :: IO ()
main =
defaultMain tests
{-# OPTIONS_GHC -F -pgmF tasty-discover #-}
1 change: 1 addition & 0 deletions components/hedgehog/Effectful/Zoo/Hedgehog/Api.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,4 +13,5 @@ import Effectful.Zoo.Hedgehog.Api.Assert
import Effectful.Zoo.Hedgehog.Api.Failure
import Effectful.Zoo.Hedgehog.Api.Hedgehog
import Effectful.Zoo.Hedgehog.Api.Journal
import Effectful.Zoo.Hedgehog.Api.Tasty.Orphans ()
import Hedgehog
18 changes: 18 additions & 0 deletions components/hedgehog/Effectful/Zoo/Hedgehog/Api/Tasty/Orphans.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,18 @@
{-# OPTIONS_GHC -fno-warn-orphans #-}

module Effectful.Zoo.Hedgehog.Api.Tasty.Orphans where

import Data.Monoid
import HaskellWorks.Prelude
import Hedgehog (PropertyT, TestT)
import Hedgehog qualified as H
import Test.Tasty.Discover
import Test.Tasty.Discover.TastyInfo
import Test.Tasty.Hedgehog

instance Tasty (PropertyT IO ()) where
tasty info = pure . testProperty testName . H.property
where testName = fromMaybe "" $ getLast info.name

instance Tasty (TestT IO ()) where
tasty info = tasty info . H.test
7 changes: 6 additions & 1 deletion effectful-zoo.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -58,6 +58,7 @@ common resourcet { build-depends: resourcet >=
common resourcet-effectful { build-depends: resourcet-effectful >= 1.0.1 && < 2 }
common stm { build-depends: stm >= 2.5.1 && < 3 }
common tasty { build-depends: tasty >= 1.5 && < 2 }
common tasty-discover { build-depends: tasty-discover >= 5 && < 6 }
common tasty-hedgehog { build-depends: tasty-hedgehog >= 1.1.0.0 && < 1.5 }
common temporary { build-depends: temporary >= 1.3 && < 2 }
common testcontainers { build-depends: testcontainers >= 0.5 && < 0.6 }
Expand Down Expand Up @@ -300,6 +301,7 @@ library hedgehog
lifted-base,
resourcet,
stm,
tasty-discover,
tasty-hedgehog,
tasty,
text,
Expand Down Expand Up @@ -327,6 +329,7 @@ library hedgehog
Effectful.Zoo.Hedgehog.Api.Range
Effectful.Zoo.Hedgehog.Api.Stack
Effectful.Zoo.Hedgehog.Api.Tasty
Effectful.Zoo.Hedgehog.Api.Tasty.Orphans
Effectful.Zoo.Hedgehog.Api.Workspace
Effectful.Zoo.Hedgehog.Data
Effectful.Zoo.Hedgehog.Data.PackagePath
Expand Down Expand Up @@ -372,14 +375,16 @@ library testcontainers-localstack
hs-source-dirs: components/testcontainers-localstack

test-suite effectful-zoo-test
import: project-config,
import: base, project-config,
effectful-zoo-hedgehog,
hedgehog,
hw-prelude,
tasty,
tasty-discover,
type: exitcode-stdio-1.0
main-is: Main.hs
other-modules: Effectful.Zoo.Hedgehog.Test.PropertySpec
build-tool-depends: tasty-discover:tasty-discover
hs-source-dirs: components/hedgehog-test
ghc-options: -threaded
-rtsopts
Expand Down

0 comments on commit e42e922

Please sign in to comment.