commit 6bf64c0c31752578980a858c733cfd73ef7ddf33
parent f25d94a20b98ebe7a67712a49d6e834654846157
Author: Jared Tobin <jared@jtobin.io>
Date: Fri, 13 Sep 2019 19:34:57 -0230
tests: test feis and tail over planets
Previously these were tested over all Word32 values, but they aren't
supposed to be inverses for galaxies and stars (i.e. values < 65536),
leading to spurious failures.
Diffstat:
2 files changed, 27 insertions(+), 3 deletions(-)
diff --git a/test/Ob/Tests/Property.hs b/test/Ob/Tests/Property.hs
@@ -1,22 +1,45 @@
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE ScopedTypeVariables #-}
module Ob.Tests.Property (
tests
) where
+import Data.Word (Word32, Word64)
import Test.Hspec
import Test.Hspec.Core.QuickCheck (modifyMaxSuccess)
import Test.QuickCheck
import qualified Urbit.Ob.Ob as Ob
+planets :: Gen Word32
+planets = arbitrary `suchThat` (> 0xFFFF)
+
+word64 :: Gen Word64
+word64 = arbitrary
+
tests :: Spec
tests = do
+ describe "fynd" $
+ modifyMaxSuccess (const 1000) $
+ it "inverts fein" $
+ forAll word64 $ \x ->
+ Ob.fynd (Ob.fein x) == x
+
+ describe "fein" $
+ modifyMaxSuccess (const 1000) $
+ it "inverts fynd" $
+ forAll word64 $ \x ->
+ Ob.fein (Ob.fynd x) == x
+
describe "feis" $
modifyMaxSuccess (const 1000) $
it "inverts tail" $
- property $ \x -> Ob.feis (Ob.tail x) == x
+ forAll planets $ \planet -> property $
+ Ob.feis (Ob.tail planet) == planet
describe "tail" $
modifyMaxSuccess (const 1000) $
it "inverts feis" $
- property $ \x -> Ob.tail (Ob.feis x) == x
+ forAll planets $ \planet -> property $
+ Ob.tail (Ob.feis planet) == planet
diff --git a/test/Ob/Tests/Unit.hs b/test/Ob/Tests/Unit.hs
@@ -8,7 +8,8 @@ import qualified Urbit.Ob.Ob as Ob
tests :: Spec
tests =
- describe "tail . feis" $
+ describe "tail . feis" $ do
+
context "when applied to 2052065766" $
it "should be the identity function" $
Ob.tail (Ob.feis 2052065766) `shouldBe` 2052065766