]> git.immae.eu Git - github/fretlink/hmacaroons.git/blame - test/Crypto/Macaroon/Verifier/Internal/Tests.hs
Merge branch 'verification'
[github/fretlink/hmacaroons.git] / test / Crypto / Macaroon / Verifier / Internal / Tests.hs
CommitLineData
86f38823
JT
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
cb1ee5df
JT
14import Data.Bool
15import qualified Data.ByteString as BS
86f38823 16import qualified Data.ByteString.Char8 as B8
cb1ee5df
JT
17import Data.Either
18import Data.Either.Validation
86f38823
JT
19import Data.List
20import Test.Tasty
cb1ee5df 21import Test.Tasty.HUnit
86f38823
JT
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
cb1ee5df 31 , firstParty
86f38823
JT
32 ]
33
cb1ee5df
JT
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
86f38823 67sigs = testProperty "Signatures" $ \sm -> verifySig (secret sm) (macaroon sm) == Right (macaroon sm)
cb1ee5df
JT
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 ]