Verified(..)
, verifySig
, verifyExact
+ , verifyFun
, verifyCavs
-- , module Data.Attoparsec.ByteString
, module Data.Attoparsec.ByteString.Char8
verifyCavs :: [Caveat -> Maybe Verified] -> Macaroon -> Verified
verifyCavs verifiers m = mconcat $ map (\c -> mconcat . catMaybes $ map ($ c) verifiers) (caveats m)
-verifyExact :: (Show a, Eq a) => Key -> a -> Parser a -> Caveat -> Maybe Verified
-verifyExact key expected parser cav = if key `BS.isPrefixOf` cid cav then
+verifyExact :: (Eq a) => Key -> a -> Parser a -> Caveat -> Maybe Verified
+verifyExact k expected = verifyFun k (expected ==)
+
+verifyFun :: Key -> (a -> Bool) -> Parser a -> Caveat -> Maybe Verified
+verifyFun key f parser cav = if key `BS.isPrefixOf` cid cav then
case parseOnly kvparser (cid cav) of
- Right v -> verify <$> Just v
+ Right v -> (bool Failed Ok . f) <$> Just v
Left _ -> Just Failed
else Nothing
where
skipSpace
string "="
skipSpace
- parser
-
- -- *> skipSpace *> string "=" *> skipSpace *> parser <* endOfInput
- verify a = bool Failed Ok (a == expected)
+ parser <* endOfInput
module Crypto.Macaroon.Verifier.Tests where
+import Data.List
import qualified Data.ByteString.Char8 as B8
import Test.Tasty
import Test.Tasty.HUnit
exVerifiers' = [ verifyExact "test" "caveat" (many' letter_ascii)
, verifyExact "value" 43 decimal
]
+funVerifiers = [ verifyFun "test" ("cav" `isPrefixOf`) (many' letter_ascii)
+ , verifyFun "value" (<= 43) decimal
+ ]
{-
- Tests
two = testCase "Macaroon with two caveats" $
Ok @=? verifySig sec m3
-exactCavs = testGroup "Exact Caveats" [ zero', one', two' , one'', two'']
-
-zero' = testCase "Zero caveat win" $
- Ok @=? verifyCavs exVerifiers m
-one' = testCase "One caveat win" $
- Ok @=? verifyCavs exVerifiers m2
-one'' = testCase "Ignoring non-relevant" $
- Ok @=? verifyCavs exVerifiers' m2
-two' = testCase "Two caveat win" $
- Ok @=? verifyCavs exVerifiers m3
-two'' = testCase "Two caveat fail" $
- Failed @=? verifyCavs exVerifiers' m3
+exactCavs = testGroup "Exact Caveats" [
+ testGroup "Ignoring non-relevant" [
+ testCase "Zero caveat" $ Ok @=? verifyCavs exVerifiers m
+ , testCase "One caveat" $ Ok @=? verifyCavs exVerifiers' m2
+ ]
+ , 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
+ ]