aboutsummaryrefslogtreecommitdiffhomepage
path: root/test/Crypto/Macaroon
diff options
context:
space:
mode:
Diffstat (limited to 'test/Crypto/Macaroon')
-rw-r--r--test/Crypto/Macaroon/Instances.hs21
-rw-r--r--test/Crypto/Macaroon/Serializer/Base64/Tests.hs2
-rw-r--r--test/Crypto/Macaroon/Verifier/Tests.hs79
3 files changed, 79 insertions, 23 deletions
diff --git a/test/Crypto/Macaroon/Instances.hs b/test/Crypto/Macaroon/Instances.hs
index 4e2f39f..c82bbd3 100644
--- a/test/Crypto/Macaroon/Instances.hs
+++ b/test/Crypto/Macaroon/Instances.hs
@@ -26,9 +26,16 @@ import Crypto.Macaroon
26 26
27-- | Adjust the size parameter, by transforming it with the given 27-- | Adjust the size parameter, by transforming it with the given
28-- function. 28-- function.
29-- Copied over from QuickCheck 2.8
29scale :: (Int -> Int) -> Gen a -> Gen a 30scale :: (Int -> Int) -> Gen a -> Gen a
30scale f g = sized (\n -> resize (f n) g) 31scale f g = sized (\n -> resize (f n) g)
31 32
33
34-- | Generates a random subsequence of the given list.
35-- Copied over from QuickCheck 2.8
36sublistOf :: [a] -> Gen [a]
37sublistOf = filterM (\_ -> choose (False, True))
38
32newtype Url = Url { unUrl :: BS.ByteString } deriving (Show) 39newtype Url = Url { unUrl :: BS.ByteString } deriving (Show)
33 40
34instance Arbitrary Url where 41instance Arbitrary Url where
@@ -48,6 +55,16 @@ newtype Identifier = Identifier { unIdent :: BS.ByteString } deriving (Show)
48instance Arbitrary Identifier where 55instance Arbitrary Identifier where
49 arbitrary = Identifier . B8.pack <$>(scale (*3) . listOf1 . elements $ ['a'..'z']) 56 arbitrary = Identifier . B8.pack <$>(scale (*3) . listOf1 . elements $ ['a'..'z'])
50 57
58newtype EquationLike = EquationLike { unEqlike :: BS.ByteString } deriving (Show)
59
60instance Arbitrary EquationLike where
61 arbitrary = do
62 keylen <- choose (3,8)
63 key <- B8.pack <$> vectorOf keylen (elements ['a'..'z'])
64 val <- B8.pack <$> (scale (*3) . listOf1 . elements $ ['a'..'z'])
65 return $ EquationLike (BS.concat [ key, " = ", val])
66
67
51data SimpleMac = SimpleMac { secret :: BS.ByteString, macaroon :: Macaroon } deriving Show 68data SimpleMac = SimpleMac { secret :: BS.ByteString, macaroon :: Macaroon } deriving Show
52 69
53instance Arbitrary SimpleMac where 70instance Arbitrary SimpleMac where
@@ -55,6 +72,8 @@ instance Arbitrary SimpleMac where
55 secret <- unSecret <$> arbitrary 72 secret <- unSecret <$> arbitrary
56 location <- unUrl <$> arbitrary 73 location <- unUrl <$> arbitrary
57 ident <- unIdent <$> arbitrary 74 ident <- unIdent <$> arbitrary
58 return $ SimpleMac secret (create secret ident location) 75 fpcavs <- listOf arbitrary
76 let mac = foldl (flip addFirstPartyCaveat) (create secret ident location) (map unEqlike fpcavs)
77 return $ SimpleMac secret mac
59 78
60 79
diff --git a/test/Crypto/Macaroon/Serializer/Base64/Tests.hs b/test/Crypto/Macaroon/Serializer/Base64/Tests.hs
index 19084af..ea3bed9 100644
--- a/test/Crypto/Macaroon/Serializer/Base64/Tests.hs
+++ b/test/Crypto/Macaroon/Serializer/Base64/Tests.hs
@@ -30,7 +30,7 @@ tests = testGroup "Crypto.Macaroon.Serializer.Base64" [ basic
30 ] 30 ]
31 31
32basicQC = testProperty "Reversibility" $ 32basicQC = testProperty "Reversibility" $
33 forAll (macaroon <$> arbitrary) (\m -> deserialize (serialize m) == Right m) 33 \sm -> deserialize (serialize (macaroon sm)) == Right (macaroon sm)
34 34
35m :: Macaroon 35m :: Macaroon
36m = create secret key loc 36m = create secret key loc
diff --git a/test/Crypto/Macaroon/Verifier/Tests.hs b/test/Crypto/Macaroon/Verifier/Tests.hs
index 92a8a21..101fa26 100644
--- a/test/Crypto/Macaroon/Verifier/Tests.hs
+++ b/test/Crypto/Macaroon/Verifier/Tests.hs
@@ -12,9 +12,11 @@ This test suite is based on the pymacaroons test suite:
12module Crypto.Macaroon.Verifier.Tests where 12module Crypto.Macaroon.Verifier.Tests where
13 13
14 14
15import Data.List
15import qualified Data.ByteString.Char8 as B8 16import qualified Data.ByteString.Char8 as B8
16import Test.Tasty 17import Test.Tasty
17import Test.Tasty.HUnit 18-- import Test.Tasty.HUnit
19import Test.Tasty.QuickCheck
18 20
19import Crypto.Macaroon 21import Crypto.Macaroon
20import Crypto.Macaroon.Verifier 22import Crypto.Macaroon.Verifier
@@ -23,8 +25,12 @@ import Crypto.Macaroon.Instances
23 25
24tests :: TestTree 26tests :: TestTree
25tests = testGroup "Crypto.Macaroon.Verifier" [ sigs 27tests = testGroup "Crypto.Macaroon.Verifier" [ sigs
28 , firstParty
26 ] 29 ]
27 30
31{-
32 - Test fixtures
33 -}
28sec = B8.pack "this is our super secret key; only we should know it" 34sec = B8.pack "this is our super secret key; only we should know it"
29 35
30m :: Macaroon 36m :: Macaroon
@@ -37,23 +43,54 @@ m2 :: Macaroon
37m2 = addFirstPartyCaveat "test = caveat" m 43m2 = addFirstPartyCaveat "test = caveat" m
38 44
39m3 :: Macaroon 45m3 :: Macaroon
40m3 = addFirstPartyCaveat "test = acaveat" m 46m3 = addFirstPartyCaveat "value = 42" m2
41 47
42sigs = testGroup "Signatures" [ basic 48exTC = verifyExact "test" "caveat" (many' letter_ascii) <???> "test = caveat"
43 , minted 49exTZ = verifyExact "test" "bleh" (many' letter_ascii) <???> "test = bleh"
44 ] 50exV42 = verifyExact "value" 42 decimal <???> "value = 42"
45 51exV43 = verifyExact "value" 43 decimal <???> "value = 43"
46basic = testCase "Basic Macaroon Signature" $ 52
47 Success @=? verifySig sec m 53funTCPre = verifyFun "test" ("cav" `isPrefixOf`) (many' letter_ascii) <???> "test startsWith cav"
48 54funTV43lte = verifyFun "value" (<= 43) decimal <???> "value <= 43"
49 55
50minted :: TestTree 56allvs = [exTC, exTZ, exV42, exV43, funTCPre, funTV43lte]
51minted = testGroup "Macaroon with first party caveats" [ one 57
52 , two 58{-
53 ] 59 - Tests
54one = testCase "One caveat" $ 60 -}
55 Success @=? verifySig sec m2 61sigs = testProperty "Signatures" $ \sm -> verifySig (secret sm) (macaroon sm) == Ok
56 62
57two = testCase "Two caveats" $ 63firstParty = testGroup "First party caveats" [
58 Success @=? verifySig sec m3 64 testGroup "Pure verifiers" [
59 65 testProperty "Zero caveat" $
66 forAll (sublistOf allvs) (\vs -> Ok == verifyCavs vs m)
67 , testProperty "One caveat" $
68 forAll (sublistOf allvs) (\vs -> disjoin [
69 Ok == verifyCavs vs m2 .&&. any (`elem` vs) [exTC,funTCPre] .&&. (exTZ `notElem` vs)
70 , Failed === verifyCavs vs m2
71 ])
72 , testProperty "Two Exact" $
73 forAll (sublistOf allvs) (\vs -> disjoin [
74 Ok == verifyCavs vs m3 .&&.
75 any (`elem` vs) [exTC,funTCPre] .&&. (exTZ `notElem` vs) .&&.
76 any (`elem` vs) [exV42,funTV43lte] .&&. (exV43 `notElem` vs)
77 , Failed === verifyCavs vs m3
78 ])
79 ]
80 , testGroup "Pure verifiers with sig" [
81 testProperty "Zero caveat" $
82 forAll (sublistOf allvs) (\vs -> Ok == verifyMacaroon sec vs m)
83 , testProperty "One caveat" $
84 forAll (sublistOf allvs) (\vs -> disjoin [
85 Ok == verifyMacaroon sec vs m2 .&&. any (`elem` vs) [exTC,funTCPre] .&&. (exTZ `notElem` vs)
86 , Failed === verifyMacaroon sec vs m2
87 ])
88 , testProperty "Two Exact" $
89 forAll (sublistOf allvs) (\vs -> disjoin [
90 Ok == verifyMacaroon sec vs m3 .&&.
91 any (`elem` vs) [exTC,funTCPre] .&&. (exTZ `notElem` vs) .&&.
92 any (`elem` vs) [exV42,funTV43lte] .&&. (exV43 `notElem` vs)
93 , Failed === verifyMacaroon sec vs m3
94 ])
95 ]
96 ]