Skip to content

Commit

Permalink
Merge pull request #424 from sorki/fixRotateProp
Browse files Browse the repository at this point in the history
Fix rotate property
  • Loading branch information
julialongtin authored Jun 12, 2022
2 parents 5ce28f0 + 3f2e352 commit c59d29f
Showing 1 changed file with 5 additions and 13 deletions.
18 changes: 5 additions & 13 deletions tests/ImplicitSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,8 +8,8 @@

module ImplicitSpec (spec) where

import Prelude (Fractional, fmap, pure, negate, (+), String, Show, Monoid, mempty, (*), (/), (<>), (-), (/=), ($), (.), pi, id)
import Test.Hspec (xit, SpecWith, describe, Spec)
import Prelude (Fractional, fmap, pure, negate, (+), Show, Monoid, mempty, (*), (/), (<>), (-), (/=), ($), (.), pi, id)
import Test.Hspec (describe, Spec)
import Graphics.Implicit
( difference,
rotate,
Expand All @@ -29,10 +29,7 @@ import Graphics.Implicit
withRounding,
Object )
import Graphics.Implicit.Primitives (rotateQ)
import Test.QuickCheck
(Testable, property, expectFailure, Arbitrary(arbitrary),
suchThat,
forAll)
import Test.QuickCheck (Arbitrary(arbitrary), suchThat, forAll)
import Data.Foldable ( for_ )
import Test.Hspec.QuickCheck (prop)
import Linear (V2(V2), V3(V3), V4(V4), (^*))
Expand Down Expand Up @@ -172,8 +169,8 @@ rotation2dSpec = describe "2d rotation" $ do
rotate (2 * pi - rads) . rotate rads
=~= id

failingProp "rotate" $ \rads1 rads2 ->
rotate rads2 . rotate rads2
prop "rotate" $ \rads1 rads2 ->
rotate rads1 . rotate rads2
=~= rotate (rads1 + rads2)

prop "full idempotent wrt rotate" $ \rads ->
Expand Down Expand Up @@ -341,8 +338,3 @@ homomorphismSpec = describe "homomorphism" $ do
prop "withRounding/intersectR" $ \r_obj r_combo ->
withRounding @obj r_obj . intersectR r_combo
=~= intersectR r_combo . fmap (withRounding r_obj)

------------------------------------------------------------------------------
-- | Like 'prop', but for tests that are currently expected to fail.
failingProp :: Testable prop => String -> prop -> SpecWith ()
failingProp x = xit (x <> " (currently failing)") . expectFailure . property

0 comments on commit c59d29f

Please sign in to comment.