]> git.immae.eu Git - github/fretlink/hmacaroons.git/blame - test/Crypto/Macaroon/Verifier/Tests.hs
Fix caveat verification
[github/fretlink/hmacaroons.git] / test / Crypto / Macaroon / Verifier / Tests.hs
CommitLineData
b92e3c15
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.Tests where
13
14
857f2f3b 15import Data.List
b92e3c15
JT
16import qualified Data.ByteString.Char8 as B8
17import Test.Tasty
90695615 18-- import Test.Tasty.HUnit
5d1b7d51 19import Test.Tasty.QuickCheck
b92e3c15
JT
20
21import Crypto.Macaroon
22import Crypto.Macaroon.Verifier
23
24import Crypto.Macaroon.Instances
25
26tests :: TestTree
27tests = testGroup "Crypto.Macaroon.Verifier" [ sigs
90695615 28 , firstParty
b92e3c15
JT
29 ]
30
5d1b7d51
JT
31{-
32 - Test fixtures
33 -}
b92e3c15
JT
34sec = B8.pack "this is our super secret key; only we should know it"
35
36m :: Macaroon
37m = create sec key loc
38 where
39 key = B8.pack "we used our sec key"
40 loc = B8.pack "http://mybank/"
41
42m2 :: Macaroon
43m2 = addFirstPartyCaveat "test = caveat" m
44
45m3 :: Macaroon
6f3c0dca
JT
46m3 = addFirstPartyCaveat "value = 42" m2
47
90695615
JT
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]
b92e3c15 57
5d1b7d51
JT
58{-
59 - Tests
60 -}
90695615
JT
61sigs = testProperty "Signatures" $ \sm -> verifySig (secret sm) (macaroon sm) == Ok
62
63firstParty = testGroup "First party caveats" [
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 ])
857f2f3b 79 ]
90695615 80 ]