aboutsummaryrefslogtreecommitdiffhomepage
path: root/test/Crypto/Macaroon
diff options
context:
space:
mode:
Diffstat (limited to 'test/Crypto/Macaroon')
-rw-r--r--test/Crypto/Macaroon/Instances.hs11
-rw-r--r--test/Crypto/Macaroon/Tests.hs2
-rw-r--r--test/Crypto/Macaroon/Verifier/Internal/Tests.hs86
-rw-r--r--test/Crypto/Macaroon/Verifier/Tests.hs63
4 files changed, 102 insertions, 60 deletions
diff --git a/test/Crypto/Macaroon/Instances.hs b/test/Crypto/Macaroon/Instances.hs
index 6955637..019c094 100644
--- a/test/Crypto/Macaroon/Instances.hs
+++ b/test/Crypto/Macaroon/Instances.hs
@@ -11,9 +11,10 @@ This test suite is based on the pymacaroons test suite:
11-} 11-}
12module Crypto.Macaroon.Instances where 12module Crypto.Macaroon.Instances where
13 13
14import Control.Monad 14import Control.Applicative
15import Control.Monad
15import Data.Byteable 16import Data.Byteable
16import qualified Data.ByteString as BS 17import qualified Data.ByteString as BS
17import qualified Data.ByteString.Char8 as B8 18import qualified Data.ByteString.Char8 as B8
18import Data.Hex 19import Data.Hex
19import Data.List 20import Data.List
@@ -32,10 +33,10 @@ instance Arbitrary Url where
32 domain <- elements [".com",".net"] 33 domain <- elements [".com",".net"]
33 return . Url . B8.pack $ (protocol ++ name ++ domain) 34 return . Url . B8.pack $ (protocol ++ name ++ domain)
34 35
35newtype Secret = Secret { unSecret :: BS.ByteString } deriving (Show) 36newtype BSSecret = BSSecret { unSecret :: BS.ByteString } deriving (Show)
36 37
37instance Arbitrary Secret where 38instance Arbitrary BSSecret where
38 arbitrary = Secret . B8.pack <$> scale (*3) arbitrary 39 arbitrary = BSSecret . B8.pack <$> scale (*3) arbitrary
39 40
40newtype Identifier = Identifier { unIdent :: BS.ByteString } deriving (Show) 41newtype Identifier = Identifier { unIdent :: BS.ByteString } deriving (Show)
41 42
diff --git a/test/Crypto/Macaroon/Tests.hs b/test/Crypto/Macaroon/Tests.hs
index 25d77c8..c934cc1 100644
--- a/test/Crypto/Macaroon/Tests.hs
+++ b/test/Crypto/Macaroon/Tests.hs
@@ -12,7 +12,7 @@ This test suite is based on the pymacaroons test suite:
12module Crypto.Macaroon.Tests where 12module Crypto.Macaroon.Tests where
13 13
14import Data.Byteable 14import Data.Byteable
15import qualified Data.ByteString.Char8 as B8 15import qualified Data.ByteString.Char8 as B8
16import Data.Hex 16import Data.Hex
17import Test.Tasty 17import Test.Tasty
18import Test.Tasty.HUnit 18import Test.Tasty.HUnit
diff --git a/test/Crypto/Macaroon/Verifier/Internal/Tests.hs b/test/Crypto/Macaroon/Verifier/Internal/Tests.hs
new file mode 100644
index 0000000..826b631
--- /dev/null
+++ b/test/Crypto/Macaroon/Verifier/Internal/Tests.hs
@@ -0,0 +1,86 @@
1{-# LANGUAGE OverloadedStrings #-}
2{-|
3Copyright : (c) 2015 Julien Tanguy
4License : BSD3
5
6Maintainer : julien.tanguy@jhome.fr
7
8
9This test suite is based on the pymacaroons test suite:
10<https://github.com/ecordell/pymacaroons>
11-}
12module Crypto.Macaroon.Verifier.Internal.Tests where
13
14import Data.Bool
15import qualified Data.ByteString as BS
16import qualified Data.ByteString.Char8 as B8
17import Data.Either
18import Data.Either.Validation
19import Data.List
20import Test.Tasty
21import Test.Tasty.HUnit
22import Test.Tasty.QuickCheck hiding (Failure, Success)
23
24import Crypto.Macaroon
25import Crypto.Macaroon.Verifier.Internal
26
27import Crypto.Macaroon.Instances
28
29tests :: TestTree
30tests = testGroup "Crypto.Macaroon.Verifier.Internal" [ sigs
31 , firstParty
32 ]
33
34{-
35 - Test fixtures
36 -}
37sec = B8.pack "this is our super secret key; only we should know it"
38
39m :: Macaroon
40m = create sec key loc
41 where
42 key = B8.pack "we used our sec key"
43 loc = B8.pack "http://mybank/"
44
45m2 :: Macaroon
46m2 = addFirstPartyCaveat "test = caveat" m
47
48vtest :: Caveat -> IO (Maybe (Either ValidationError ()))
49vtest c = return $ if "test" `BS.isPrefixOf` cid c then
50 Just $ bool (Left (ValidatorError "Failed")) (Right ()) $ "test = caveat" == cid c
51 else Nothing
52
53
54m3 :: Macaroon
55m3 = addFirstPartyCaveat "value = 42" m2
56
57vval :: Caveat -> IO (Maybe (Either ValidationError ()))
58vval c = return $ if "value" `BS.isPrefixOf` cid c then
59 Just $ bool (Left (ValidatorError "Failed")) (Right ()) $ "value = 42" == cid c
60 else Nothing
61
62
63{-
64 - Tests
65 -}
66
67sigs = testProperty "Signatures" $ \sm -> verifySig (secret sm) (macaroon sm) == Right (macaroon sm)
68
69
70firstParty = testGroup "First party caveats" [
71 testCase "Zero caveat" $ do
72 res <- verifyCavs [] m :: IO (Either ValidationError Macaroon)
73 Right m @=? res
74 , testCase "One caveat empty" $ do
75 res <- verifyCavs [] m2 :: IO (Either ValidationError Macaroon)
76 Left NoVerifier @=? res
77 , testCase "One caveat fail" $ do
78 res <- verifyCavs [vval] m2 :: IO (Either ValidationError Macaroon)
79 Left NoVerifier @=? res
80 , testCase "One caveat win" $ do
81 res <- verifyCavs [vtest] m2 :: IO (Either ValidationError Macaroon)
82 Right m2 @=? res
83 , testCase "Two caveat win" $ do
84 res <- verifyCavs [vtest, vval] m3 :: IO (Either ValidationError Macaroon)
85 Right m3 @=? res
86 ]
diff --git a/test/Crypto/Macaroon/Verifier/Tests.hs b/test/Crypto/Macaroon/Verifier/Tests.hs
index 101fa26..d69ad8d 100644
--- a/test/Crypto/Macaroon/Verifier/Tests.hs
+++ b/test/Crypto/Macaroon/Verifier/Tests.hs
@@ -12,21 +12,20 @@ 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 Data.Either
17import Test.Tasty 17import Data.List
18-- import Test.Tasty.HUnit 18import Test.Tasty
19import Test.Tasty.QuickCheck 19import Test.Tasty.HUnit
20import Test.Tasty.QuickCheck
20 21
21import Crypto.Macaroon 22import Crypto.Macaroon
22import Crypto.Macaroon.Verifier 23import Crypto.Macaroon.Verifier
23 24
24import Crypto.Macaroon.Instances 25import Crypto.Macaroon.Instances
25 26
26tests :: TestTree 27tests :: TestTree
27tests = testGroup "Crypto.Macaroon.Verifier" [ sigs 28tests = testGroup "Crypto.Macaroon.Verifier" [ ]
28 , firstParty
29 ]
30 29
31{- 30{-
32 - Test fixtures 31 - Test fixtures
@@ -45,52 +44,8 @@ m2 = addFirstPartyCaveat "test = caveat" m
45m3 :: Macaroon 44m3 :: Macaroon
46m3 = addFirstPartyCaveat "value = 42" m2 45m3 = addFirstPartyCaveat "value = 42" m2
47 46
48exTC = verifyExact "test" "caveat" (many' letter_ascii) <???> "test = caveat"
49exTZ = verifyExact "test" "bleh" (many' letter_ascii) <???> "test = bleh"
50exV42 = verifyExact "value" 42 decimal <???> "value = 42"
51exV43 = verifyExact "value" 43 decimal <???> "value = 43"
52
53funTCPre = verifyFun "test" ("cav" `isPrefixOf`) (many' letter_ascii) <???> "test startsWith cav"
54funTV43lte = verifyFun "value" (<= 43) decimal <???> "value <= 43"
55
56allvs = [exTC, exTZ, exV42, exV43, funTCPre, funTV43lte]
57
58{- 47{-
59 - Tests 48 - Tests
60 -} 49 -}
61sigs = testProperty "Signatures" $ \sm -> verifySig (secret sm) (macaroon sm) == Ok
62 50
63firstParty = testGroup "First party caveats" [ 51-- TODO
64 testGroup "Pure verifiers" [
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 ]