commit 1f9978c336c20ecb6398818c09c80687da591fc9
parent 53e48849b212fcb5addc7953aec3b1b41feeafc8
Author: Jared Tobin <jared@jtobin.io>
Date: Tue, 17 Sep 2019 09:25:29 -0230
tests: add Co unit tests
Diffstat:
5 files changed, 60 insertions(+), 21 deletions(-)
diff --git a/test/Co.hs b/test/Co.hs
@@ -1,25 +1,12 @@
module Main where
-import Numeric.Natural
+import qualified Co.Tests.Property as P
+import qualified Co.Tests.Unit as U
import Test.Hspec
-import Test.Hspec.Core.QuickCheck (modifyMaxSuccess)
-import Test.QuickCheck
-import qualified Urbit.Ob.Co as Co
-
-nats :: Gen Natural
-nats = fmap fromIntegral (arbitrary `suchThat` (>= (0 :: Int)))
-
-patps :: Gen Co.Patp
-patps = fmap Co.patp nats
main :: IO ()
-main = hspec $ do
- describe "fromPatp" $
- modifyMaxSuccess (const 1000) $
- it "inverts patp" $
- forAll nats $ \x -> Co.fromPatp (Co.patp x) == x
+main =
+ hspec $ do
+ context "property tests" P.tests
+ context "unit tests" U.tests
- describe "patp" $
- modifyMaxSuccess (const 1000) $
- it "inverts fromPatp" $
- forAll patps $ \x -> Co.patp (Co.fromPatp x) == x
diff --git a/test/Co/Tests/Property.hs b/test/Co/Tests/Property.hs
@@ -0,0 +1,29 @@
+
+module Co.Tests.Property (
+ tests
+ ) where
+
+import Numeric.Natural
+import Test.Hspec
+import Test.Hspec.Core.QuickCheck (modifyMaxSuccess)
+import Test.QuickCheck
+import qualified Urbit.Ob.Co as Co
+
+nats :: Gen Natural
+nats = fmap fromIntegral (arbitrary `suchThat` (>= (0 :: Int)))
+
+patps :: Gen Co.Patp
+patps = fmap Co.patp nats
+
+tests :: Spec
+tests = do
+ describe "fromPatp" $
+ modifyMaxSuccess (const 1000) $
+ it "inverts patp" $
+ forAll nats $ \x -> Co.fromPatp (Co.patp x) == x
+
+ describe "patp" $
+ modifyMaxSuccess (const 1000) $
+ it "inverts fromPatp" $
+ forAll patps $ \x -> Co.patp (Co.fromPatp x) == x
+
diff --git a/test/Co/Tests/Unit.hs b/test/Co/Tests/Unit.hs
@@ -0,0 +1,22 @@
+{-# LANGUAGE OverloadedStrings #-}
+
+module Co.Tests.Unit (
+ tests
+ ) where
+
+import Data.Word (Word32)
+import Test.Hspec
+import qualified Urbit.Ob.Co as Co
+
+tests :: Spec
+tests =
+ describe "render" $
+ it "matches 32-bit reference values" $ do
+ Co.render (Co.patp 0) `shouldBe` "~zod"
+ Co.render (Co.patp 255) `shouldBe` "~fes"
+ Co.render (Co.patp 256) `shouldBe` "~marzod"
+ Co.render (Co.patp 65535) `shouldBe` "~fipfes"
+ Co.render (Co.patp 65536) `shouldBe` "~dapnep-ronmyl"
+ Co.render (Co.patp 15663360) `shouldBe` "~nidsut-tomdun"
+ Co.render (Co.patp 0xFFFFFFFF) `shouldBe` "~dostec-risfen"
+
diff --git a/test/Ob/Tests/Property.hs b/test/Ob/Tests/Property.hs
@@ -1,5 +1,3 @@
-{-# LANGUAGE RankNTypes #-}
-{-# LANGUAGE ScopedTypeVariables #-}
module Ob.Tests.Property (
tests
diff --git a/urbit-hob.cabal b/urbit-hob.cabal
@@ -85,6 +85,9 @@ Test-suite co
type: exitcode-stdio-1.0
hs-source-dirs: test
main-is: Co.hs
+ other-modules:
+ Co.Tests.Property
+ Co.Tests.Unit
default-language: Haskell2010
ghc-options:
-rtsopts