urbit-hob

Haskell utilities for phonetic base wrangling.
Log | Files | Refs | README | LICENSE

commit c62488fa57f4096d354f1aeaf02d1bbe23a6dca6
parent 6bf64c0c31752578980a858c733cfd73ef7ddf33
Author: Jared Tobin <jared@jtobin.io>
Date:   Tue, 17 Sep 2019 08:12:20 -0230

co: use Natural instead of Int

'patp' and 'fromPatp' previously targeted Int, whereas Natural is a far
more.. *natural*.. choice.

Diffstat:
Mlib/Urbit/Ob/Co.hs | 17+++++++----------
Mtest/Co.hs | 15+++++++++++++--
2 files changed, 20 insertions(+), 12 deletions(-)

diff --git a/lib/Urbit/Ob/Co.hs b/lib/Urbit/Ob/Co.hs @@ -14,26 +14,23 @@ import qualified Data.Vector as V import qualified Data.Serialize as C import qualified Data.Text as T import Data.Word (Word8, Word16, Word) +import Numeric.Natural (Natural) import Urbit.Ob.Ob (fein, fynd) newtype Patp = Patp BS.ByteString deriving (Eq, Show) --- | Convert a nonnegative Int to a Patp value. -patp :: Int -> Patp +-- | Convert a Natural to a Patp value. +patp :: Natural -> Patp patp n - | n >= 0 = _patp - | otherwise = error "urbit-hob (patp): input out of range" + | met 3 sxz <= 1 = Patp (BS.cons 0 (BS.singleton sxz8)) + | otherwise = Patp (C.encode (fromIntegral sxz :: Word)) where sxz = fein n sxz8 = fromIntegral sxz :: Word8 - _patp - | met 3 sxz <= 1 = Patp (BS.cons 0 (BS.singleton sxz8)) - | otherwise = Patp (C.encode (fromIntegral sxz :: Word)) - --- | Convert a Patp value to an Int. -fromPatp :: Patp -> Int +-- | Convert a Patp value to a Natural. +fromPatp :: Patp -> Natural fromPatp (Patp p) = decoded where decoded = case BS.length p of 2 -> case C.decode p :: Either String Word16 of diff --git a/test/Co.hs b/test/Co.hs @@ -1,14 +1,25 @@ module Main 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 + main :: IO () -main = hspec $ +main = hspec $ do describe "fromPatp" $ modifyMaxSuccess (const 1000) $ it "inverts patp" $ - property $ \(NonNegative x) -> Co.fromPatp (Co.patp x) == x + 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