aboutsummaryrefslogtreecommitdiffhomepage
path: root/test/Crypto/Macaroon
diff options
context:
space:
mode:
Diffstat (limited to 'test/Crypto/Macaroon')
-rw-r--r--test/Crypto/Macaroon/Instances.hs10
-rw-r--r--test/Crypto/Macaroon/Tests.hs2
-rw-r--r--test/Crypto/Macaroon/Verifier/Internal/Tests.hs30
-rw-r--r--test/Crypto/Macaroon/Verifier/Tests.hs49
4 files changed, 56 insertions, 35 deletions
diff --git a/test/Crypto/Macaroon/Instances.hs b/test/Crypto/Macaroon/Instances.hs
index 6955637..6348c56 100644
--- a/test/Crypto/Macaroon/Instances.hs
+++ b/test/Crypto/Macaroon/Instances.hs
@@ -11,9 +11,9 @@ 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.Monad
15import Data.Byteable 15import Data.Byteable
16import qualified Data.ByteString as BS 16import qualified Data.ByteString as BS
17import qualified Data.ByteString.Char8 as B8 17import qualified Data.ByteString.Char8 as B8
18import Data.Hex 18import Data.Hex
19import Data.List 19import Data.List
@@ -32,10 +32,10 @@ instance Arbitrary Url where
32 domain <- elements [".com",".net"] 32 domain <- elements [".com",".net"]
33 return . Url . B8.pack $ (protocol ++ name ++ domain) 33 return . Url . B8.pack $ (protocol ++ name ++ domain)
34 34
35newtype Secret = Secret { unSecret :: BS.ByteString } deriving (Show) 35newtype BSSecret = BSSecret { unSecret :: BS.ByteString } deriving (Show)
36 36
37instance Arbitrary Secret where 37instance Arbitrary BSSecret where
38 arbitrary = Secret . B8.pack <$> scale (*3) arbitrary 38 arbitrary = BSSecret . B8.pack <$> scale (*3) arbitrary
39 39
40newtype Identifier = Identifier { unIdent :: BS.ByteString } deriving (Show) 40newtype Identifier = Identifier { unIdent :: BS.ByteString } deriving (Show)
41 41
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..cd75118
--- /dev/null
+++ b/test/Crypto/Macaroon/Verifier/Internal/Tests.hs
@@ -0,0 +1,30 @@
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 qualified Data.ByteString.Char8 as B8
15import Data.List
16import Test.Tasty
17-- import Test.Tasty.HUnit
18import Data.Either
19import Test.Tasty.QuickCheck hiding (Failure, Success)
20
21import Crypto.Macaroon
22import Crypto.Macaroon.Verifier.Internal
23
24import Crypto.Macaroon.Instances
25
26tests :: TestTree
27tests = testGroup "Crypto.Macaroon.Verifier.Internal" [ sigs
28 ]
29
30sigs = testProperty "Signatures" $ \sm -> verifySig (secret sm) (macaroon sm) == Right (macaroon sm)
diff --git a/test/Crypto/Macaroon/Verifier/Tests.hs b/test/Crypto/Macaroon/Verifier/Tests.hs
index 101fa26..b6220eb 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.List
17import Test.Tasty 17import Test.Tasty
18-- import Test.Tasty.HUnit 18-- import Test.Tasty.HUnit
19import Test.Tasty.QuickCheck 19import Data.Either
20import Test.Tasty.QuickCheck hiding (Failure, Success)
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,44 @@ 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
51-- TODO: Re-do tests
52{-
63firstParty = testGroup "First party caveats" [ 53firstParty = testGroup "First party caveats" [
64 testGroup "Pure verifiers" [ 54 testGroup "Pure verifiers" [
65 testProperty "Zero caveat" $ 55 testProperty "Zero caveat" $
66 forAll (sublistOf allvs) (\vs -> Ok == verifyCavs vs m) 56 forAll (sublistOf allvs) (\vs -> Right m == verifyCavs vs m)
67 , testProperty "One caveat" $ 57 , testProperty "One caveat" $
68 forAll (sublistOf allvs) (\vs -> disjoin [ 58 forAll (sublistOf allvs) (\vs -> disjoin [
69 Ok == verifyCavs vs m2 .&&. any (`elem` vs) [exTC,funTCPre] .&&. (exTZ `notElem` vs) 59 Right m2 == verifyCavs vs m2 .&&. any (`elem` vs) [exTC,funTCPre] .&&. (exTZ `notElem` vs)
70 , Failed === verifyCavs vs m2 60 , True === isLeft( verifyCavs vs m2)
71 ]) 61 ])
72 , testProperty "Two Exact" $ 62 , testProperty "Two Exact" $
73 forAll (sublistOf allvs) (\vs -> disjoin [ 63 forAll (sublistOf allvs) (\vs -> disjoin [
74 Ok == verifyCavs vs m3 .&&. 64 Right m3 == verifyCavs vs m3 .&&.
75 any (`elem` vs) [exTC,funTCPre] .&&. (exTZ `notElem` vs) .&&. 65 any (`elem` vs) [exTC,funTCPre] .&&. (exTZ `notElem` vs) .&&.
76 any (`elem` vs) [exV42,funTV43lte] .&&. (exV43 `notElem` vs) 66 any (`elem` vs) [exV42,funTV43lte] .&&. (exV43 `notElem` vs)
77 , Failed === verifyCavs vs m3 67 , True === isLeft (verifyCavs vs m3)
78 ]) 68 ])
79 ] 69 ]
80 , testGroup "Pure verifiers with sig" [ 70 , testGroup "Pure verifiers with sig" [
81 testProperty "Zero caveat" $ 71 testProperty "Zero caveat" $
82 forAll (sublistOf allvs) (\vs -> Ok == verifyMacaroon sec vs m) 72 forAll (sublistOf allvs) (\vs -> Right m == verifyMacaroon sec vs m)
83 , testProperty "One caveat" $ 73 , testProperty "One caveat" $
84 forAll (sublistOf allvs) (\vs -> disjoin [ 74 forAll (sublistOf allvs) (\vs -> disjoin [
85 Ok == verifyMacaroon sec vs m2 .&&. any (`elem` vs) [exTC,funTCPre] .&&. (exTZ `notElem` vs) 75 Right m2 == verifyMacaroon sec vs m2 .&&. any (`elem` vs) [exTC,funTCPre] .&&. (exTZ `notElem` vs)
86 , Failed === verifyMacaroon sec vs m2 76 , True === isLeft (verifyMacaroon sec vs m2)
87 ]) 77 ])
88 , testProperty "Two Exact" $ 78 , testProperty "Two Exact" $
89 forAll (sublistOf allvs) (\vs -> disjoin [ 79 forAll (sublistOf allvs) (\vs -> disjoin [
90 Ok == verifyMacaroon sec vs m3 .&&. 80 Right m3 == verifyMacaroon sec vs m3 .&&.
91 any (`elem` vs) [exTC,funTCPre] .&&. (exTZ `notElem` vs) .&&. 81 any (`elem` vs) [exTC,funTCPre] .&&. (exTZ `notElem` vs) .&&.
92 any (`elem` vs) [exV42,funTV43lte] .&&. (exV43 `notElem` vs) 82 any (`elem` vs) [exV42,funTV43lte] .&&. (exV43 `notElem` vs)
93 , Failed === verifyMacaroon sec vs m3 83 , True === isLeft (verifyMacaroon sec vs m3)
94 ]) 84 ])
95 ] 85 ]
96 ] 86 ]
87 -}