]> git.immae.eu Git - github/fretlink/hmacaroons.git/blame - test/Crypto/Macaroon/Verifier/Tests.hs
Basic validation functions
[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
c830f7c2
JT
19import Test.Tasty.QuickCheck hiding (Success, Failure)
20import Data.Either
b92e3c15
JT
21
22import Crypto.Macaroon
23import Crypto.Macaroon.Verifier
24
25import Crypto.Macaroon.Instances
26
27tests :: TestTree
28tests = testGroup "Crypto.Macaroon.Verifier" [ sigs
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
c830f7c2
JT
48-- exTC = verifyExact "test" "caveat" (many' letter_ascii)
49-- exTZ = verifyExact "test" "bleh" (many' letter_ascii)
50-- exV42 = verifyExact "value" 42 decimal
51-- exV43 = verifyExact "value" 43 decimal
90695615 52
c830f7c2
JT
53-- funTCPre = verifyFun "test" (string "test = " *> many' letter_ascii)
54-- (\e -> if "cav" `isPrefixOf` e then Right e else Left "Does not start with cav" )
55-- funTV43lte = verifyFun "value" (string "value = " *> decimal)
56-- (\v -> if v <= 43 then Right v else Left "Greater than 43")
90695615 57
c830f7c2 58-- allvs = [exTC, exTZ, exV42, exV43, funTCPre, funTV43lte]
b92e3c15 59
5d1b7d51
JT
60{-
61 - Tests
62 -}
c830f7c2
JT
63sigs = testProperty "Signatures" $ \sm -> verifySig (secret sm) (macaroon sm) == Right (macaroon sm)
64
65-- TODO: Re-do tests
7f9f7386
JT
66{-
67firstParty = testGroup "First party caveats" [
68 testGroup "Pure verifiers" [
69 testProperty "Zero caveat" $
70 forAll (sublistOf allvs) (\vs -> Right m == verifyCavs vs m)
71 , testProperty "One caveat" $
72 forAll (sublistOf allvs) (\vs -> disjoin [
73 Right m2 == verifyCavs vs m2 .&&. any (`elem` vs) [exTC,funTCPre] .&&. (exTZ `notElem` vs)
74 , True === isLeft( verifyCavs vs m2)
75 ])
76 , testProperty "Two Exact" $
77 forAll (sublistOf allvs) (\vs -> disjoin [
78 Right m3 == verifyCavs vs m3 .&&.
79 any (`elem` vs) [exTC,funTCPre] .&&. (exTZ `notElem` vs) .&&.
80 any (`elem` vs) [exV42,funTV43lte] .&&. (exV43 `notElem` vs)
81 , True === isLeft (verifyCavs vs m3)
82 ])
83 ]
84 , testGroup "Pure verifiers with sig" [
85 testProperty "Zero caveat" $
86 forAll (sublistOf allvs) (\vs -> Right m == verifyMacaroon sec vs m)
87 , testProperty "One caveat" $
88 forAll (sublistOf allvs) (\vs -> disjoin [
89 Right m2 == verifyMacaroon sec vs m2 .&&. any (`elem` vs) [exTC,funTCPre] .&&. (exTZ `notElem` vs)
90 , True === isLeft (verifyMacaroon sec vs m2)
91 ])
92 , testProperty "Two Exact" $
93 forAll (sublistOf allvs) (\vs -> disjoin [
94 Right m3 == verifyMacaroon sec vs m3 .&&.
95 any (`elem` vs) [exTC,funTCPre] .&&. (exTZ `notElem` vs) .&&.
96 any (`elem` vs) [exV42,funTV43lte] .&&. (exV43 `notElem` vs)
97 , True === isLeft (verifyMacaroon sec vs m3)
98 ])
99 ]
100 ]
101 -}