-}
module Crypto.Macaroon.Verifier (
Verified(..)
+ , CaveatVerifier(..)
+ , (<???>)
, verifySig
, verifyExact
, verifyFun
import qualified Data.ByteString as BS
import Data.Byteable
import Data.Foldable
+import Data.Function
import Data.Maybe
+import Data.Traversable
import Data.Attoparsec.ByteString
import Data.Attoparsec.ByteString.Char8
mappend _ _ = Failed
-type CaveatVerifier = Caveat -> Maybe Verified
+data CaveatVerifier = CV { vFun :: Caveat -> Maybe Verified , helpText :: String}
+
+instance Eq CaveatVerifier where
+ (==) = (==) `on` helpText
+
+instance Show CaveatVerifier where
+ show = helpText
+
+(<???>) :: (Caveat -> Maybe Verified) -> String -> CaveatVerifier
+f <???> t = CV f t
verifySig :: Key -> Macaroon -> Verified
verifySig k m = bool Failed Ok $
hash s c = toBytes (hmac s (vid c `BS.append` cid c) :: HMAC SHA256)
derivedKey = toBytes (hmac "macaroons-key-generator" k :: HMAC SHA256)
-verifyCavs :: [Caveat -> Maybe Verified] -> Macaroon -> Verified
-verifyCavs verifiers m = mconcat $ map (\c -> mconcat . catMaybes $ map ($ c) verifiers) (caveats m)
+verifyCavs :: [CaveatVerifier] -> Macaroon -> Verified
+verifyCavs verifiers m = foldMap (\c -> fromMaybe Failed $ foldMap (($ c) . vFun) verifiers) (caveats m)
verifyExact :: (Eq a) => Key -> a -> Parser a -> Caveat -> Maybe Verified
verifyExact k expected = verifyFun k (expected ==)
import Data.List
import qualified Data.ByteString.Char8 as B8
import Test.Tasty
-import Test.Tasty.HUnit
+-- import Test.Tasty.HUnit
import Test.Tasty.QuickCheck
import Crypto.Macaroon
tests :: TestTree
tests = testGroup "Crypto.Macaroon.Verifier" [ sigs
- , exactCavs
+ , firstParty
]
{-
m3 :: Macaroon
m3 = addFirstPartyCaveat "value = 42" m2
-exVerifiers = [ verifyExact "test" "caveat" (many' letter_ascii)
- , verifyExact "value" 42 decimal
- ]
-exVerifiers' = [ verifyExact "test" "caveat" (many' letter_ascii)
- , verifyExact "value" 43 decimal
- ]
-funVerifiers = [ verifyFun "test" ("cav" `isPrefixOf`) (many' letter_ascii)
- , verifyFun "value" (<= 43) decimal
- ]
+exTC = verifyExact "test" "caveat" (many' letter_ascii) <???> "test = caveat"
+exTZ = verifyExact "test" "bleh" (many' letter_ascii) <???> "test = bleh"
+exV42 = verifyExact "value" 42 decimal <???> "value = 42"
+exV43 = verifyExact "value" 43 decimal <???> "value = 43"
+
+funTCPre = verifyFun "test" ("cav" `isPrefixOf`) (many' letter_ascii) <???> "test startsWith cav"
+funTV43lte = verifyFun "value" (<= 43) decimal <???> "value <= 43"
+
+allvs = [exTC, exTZ, exV42, exV43, funTCPre, funTV43lte]
{-
- Tests
-}
-sigs = testGroup "Signatures" [ basic
- , one
- , two
- ]
-
-basic = testGroup "Basic Macaroon" [ none , sigQC ]
-
-none = testCase "No caveat" $
- Ok @=? verifySig sec m
-
-sigQC = testProperty "Random" $
- \sm -> verifySig (secret sm) (macaroon sm) == Ok
-
-one = testCase "Macaroon with one caveat" $
- Ok @=? verifySig sec m2
-
-two = testCase "Macaroon with two caveats" $
- Ok @=? verifySig sec m3
-
-exactCavs = testGroup "Exact Caveats" [
- testGroup "Ignoring non-relevant" [
- testCase "Zero caveat" $ Ok @=? verifyCavs exVerifiers m
- , testCase "One caveat" $ Ok @=? verifyCavs exVerifiers' m2
+sigs = testProperty "Signatures" $ \sm -> verifySig (secret sm) (macaroon sm) == Ok
+
+firstParty = testGroup "First party caveats" [
+ testGroup "Pure verifiers" [
+ testProperty "Zero caveat" $
+ forAll (sublistOf allvs) (\vs -> Ok == verifyCavs vs m)
+ , testProperty "One caveat" $
+ forAll (sublistOf allvs) (\vs -> disjoin [
+ Ok == verifyCavs vs m2 .&&. any (`elem` vs) [exTC,funTCPre] .&&. (exTZ `notElem` vs)
+ , Failed === verifyCavs vs m2
+ ])
+ , testProperty "Two Exact" $
+ forAll (sublistOf allvs) (\vs -> disjoin [
+ Ok == verifyCavs vs m3 .&&.
+ any (`elem` vs) [exTC,funTCPre] .&&. (exTZ `notElem` vs) .&&.
+ any (`elem` vs) [exV42,funTV43lte] .&&. (exV43 `notElem` vs)
+ , Failed === verifyCavs vs m3
+ ])
]
- , testCase "One caveat win" $ Ok @=? verifyCavs exVerifiers m2
- , testCase "Two caveat win" $ Ok @=? verifyCavs exVerifiers m3
- , testCase "Two caveat fail" $ Failed @=? verifyCavs exVerifiers' m3
- ]
-
-funCavs = testGroup "Function Caveats" [
- testCase "One caveat win" $ Ok @=? verifyCavs funVerifiers m2
- , testCase "Two caveat win" $ Ok @=? verifyCavs funVerifiers m3
- ]
+ ]