]> git.immae.eu Git - github/fretlink/hmacaroons.git/commitdiff
Add quickchecked serialization properties
authorJulien Tanguy <julien.tanguy@jhome.fr>
Wed, 15 Apr 2015 13:30:28 +0000 (15:30 +0200)
committerJulien Tanguy <julien.tanguy@jhome.fr>
Wed, 15 Apr 2015 13:30:28 +0000 (15:30 +0200)
hmacaroons.cabal
test/Crypto/Macaroon/Instances.hs [new file with mode: 0644]
test/Crypto/Macaroon/Serializer/Base64/Tests.hs

index 92d435d3ea8ae8b7a2308430eec27ed12fe71b17..2b23c89c32ceb4032da476330cfd31567cfa5a00 100644 (file)
@@ -64,4 +64,5 @@ test-suite test
                   hex >= 0.1,
                   tasty >= 0.10,
                   tasty-hunit >= 0.9,
+                  tasty-quickcheck >= 0.8,
                   hmacaroons
diff --git a/test/Crypto/Macaroon/Instances.hs b/test/Crypto/Macaroon/Instances.hs
new file mode 100644 (file)
index 0000000..5d4b062
--- /dev/null
@@ -0,0 +1,54 @@
+{-# LANGUAGE OverloadedStrings #-}
+{-|
+Copyright   : (c) 2015 Julien Tanguy
+License     : BSD3
+
+Maintainer  : julien.tanguy@jhome.fr
+
+
+This test suite is based on the pymacaroons test suite:
+<https://github.com/ecordell/pymacaroons>
+-}
+module Crypto.Macaroon.Instances where
+
+import Control.Monad
+import           Data.Byteable
+import qualified Data.ByteString as BS
+import qualified Data.ByteString.Char8 as B8
+import           Data.Hex
+import           Data.List
+import           Test.Tasty
+import           Test.Tasty.HUnit
+import           Test.Tasty.QuickCheck
+
+import           Crypto.Macaroon
+
+newtype Url = Url { unUrl :: BS.ByteString } deriving (Show)
+
+instance Arbitrary Url where
+    arbitrary = do
+        protocol <- elements ["http://"]
+        name <-  fmap (intercalate ".") <$> listOf1 . listOf1 $ elements ['a'..'z']
+        domain <- elements [".com",".net"]
+        return . Url . B8.pack $ (protocol ++ name ++ domain)
+
+newtype Secret = Secret { unSecret :: BS.ByteString } deriving (Show)
+
+instance Arbitrary Secret where
+    arbitrary = Secret . B8.pack <$> scale (*3) arbitrary
+
+newtype Identifier = Identifier { unIdent :: BS.ByteString } deriving (Show)
+
+instance Arbitrary Identifier where
+    arbitrary = Identifier . B8.pack <$>(scale (*3) . listOf1 . elements $ ['a'..'z'])
+
+data SimpleMac = SimpleMac { secret :: BS.ByteString, macaroon :: Macaroon } deriving Show
+
+instance Arbitrary SimpleMac where
+    arbitrary = do
+        secret <- unSecret <$> arbitrary
+        location <- unUrl <$> arbitrary
+        ident <- unIdent <$> arbitrary
+        return $ SimpleMac secret (create secret ident location)
+
+
index 9c49e9677ac8ece0a01e4722526c8a15635bc8e3..fe5352e85053e1d445f48de7f2032ca8b35b6966 100644 (file)
@@ -15,17 +15,23 @@ module Crypto.Macaroon.Serializer.Base64.Tests where
 import qualified Data.ByteString.Char8 as B8
 import Test.Tasty
 import Test.Tasty.HUnit
+import           Test.Tasty.QuickCheck
 
 import           Crypto.Macaroon
 import           Crypto.Macaroon.Serializer.Base64
 
+import Crypto.Macaroon.Instances
+
 tests :: TestTree
 tests = testGroup "Crypto.Macaroon.Serializer.Base64" [ basic
+                                                      , basicQC
                                                       , minted
                                                       , minted2
                                                       -- , minted3
                                                       ]
 
+basicQC = testProperty "Reversibility" $
+    forAll (macaroon <$> arbitrary) (\m -> deserialize (serialize m) == Right m)
 
 m :: Macaroon
 m = create secret key loc