aboutsummaryrefslogtreecommitdiffhomepage
path: root/src/Crypto/Macaroon/Verifier.hs
diff options
context:
space:
mode:
authorJulien Tanguy <julien.tanguy@jhome.fr>2015-10-05 18:35:03 +0200
committerJulien Tanguy <julien.tanguy@jhome.fr>2015-10-05 18:36:55 +0200
commitbe278da91e6c97e31c5611721b1bbd593fcd99b9 (patch)
treea7a0e90bc843a592e88da10fda21e63ddcaea6a8 /src/Crypto/Macaroon/Verifier.hs
parent27d15c27e396a98f445cdc16b2325d5838e6c734 (diff)
downloadhmacaroons-be278da91e6c97e31c5611721b1bbd593fcd99b9.tar.gz
hmacaroons-be278da91e6c97e31c5611721b1bbd593fcd99b9.tar.zst
hmacaroons-be278da91e6c97e31c5611721b1bbd593fcd99b9.zip
Dedicated VerifierResult
The Maybe (Either ValidationError ()) return type was too cryptic, now there is a real datatype for it. The validation part is unchanged and still uses the Maybe Either type
Diffstat (limited to 'src/Crypto/Macaroon/Verifier.hs')
-rw-r--r--src/Crypto/Macaroon/Verifier.hs48
1 files changed, 7 insertions, 41 deletions
diff --git a/src/Crypto/Macaroon/Verifier.hs b/src/Crypto/Macaroon/Verifier.hs
index 4fc6aff..a3bf5d4 100644
--- a/src/Crypto/Macaroon/Verifier.hs
+++ b/src/Crypto/Macaroon/Verifier.hs
@@ -17,9 +17,8 @@ Portability : portable
17-} 17-}
18module Crypto.Macaroon.Verifier ( 18module Crypto.Macaroon.Verifier (
19 verify 19 verify
20 , VerifierResult(..)
20 , ValidationError(ValidatorError, ParseError) 21 , ValidationError(ValidatorError, ParseError)
21 -- , (.<), (.<=), (.==), (.>), (.>=)
22 -- , module Data.Attoparsec.ByteString.Char8
23) where 22) where
24 23
25 24
@@ -38,55 +37,22 @@ import Crypto.Macaroon.Verifier.Internal
38 37
39 38
40 39
41
42-- (.<) :: (MonadIO m, Ord a, Parsable a) => Key -> m a -> Caveat -> m (Maybe (Either ValidationError Caveat))
43-- (.<) = verifyOpBool "Greater or equal" (<) "<"
44
45-- (.<=) :: (MonadIO m, Ord a, Parsable a) => Key -> m a -> Caveat -> m (Maybe (Either ValidationError Caveat))
46-- (.<=) = verifyOpBool "Strictly greater" (<=) "<="
47
48-- (.==) :: (MonadIO m, Eq a, Parsable a) => Key -> m a -> Caveat -> m (Maybe (Either ValidationError Caveat))
49-- (.==) = verifyOpBool "Not equal" (==) "="
50
51-- (.>) :: (MonadIO m, Ord a, Parsable a) => Key -> m a -> Caveat -> m (Maybe (Either ValidationError Caveat))
52-- (.>) = verifyOpBool "Less or equal" (>) ">"
53
54-- (.>=) :: (MonadIO m, Ord a, Parsable a) => Key -> m a -> Caveat -> m (Maybe (Either ValidationError Caveat))
55-- (.>=) = verifyOpBool "Strictly less" (>=) ">="
56
57-- | Verify a Macaroon's signature and caveats, given the corresponding Secret 40-- | Verify a Macaroon's signature and caveats, given the corresponding Secret
58-- and verifiers. 41-- and verifiers.
59-- 42--
60-- A verifier is a function of type 43-- A verifier is a function of type
61-- @'MonadIO' m => 'Caveat' -> m ('Maybe' ('Either' 'ValidatorError' 'Caveat'))@. 44-- @'MonadIO' m => 'Caveat' -> m VerifierResult@.
62-- 45--
63-- It should return: 46-- It should return:
64-- 47--
65-- * 'Nothing' if the caveat is not related to the verifier 48-- * 'Unrelated' if the caveat is not related to the verifier
66-- (for instance a time verifier is given an action caveat); 49-- (for instance a time verifier is given an action caveat);
67-- * 'Just' ('Left' ('ParseError' reason)) if the verifier is related to the 50-- * 'Refused' ('ParseError' reason) if the verifier is related to the
68-- caveat, but failed to parse it completely; 51-- caveat, but failed to parse it completely;
69-- * 'Just' ('Left' ('ValidatorError' reason)) if the verifier is related to the 52-- * 'Refused' ('ValidatorError' reason) if the verifier is related to the
70-- caveat, parsed it and invalidated it; 53-- caveat, parsed it and invalidated it;
71-- * 'Just' ('Right' '()') if the verifier has successfully verified the 54-- * 'Verified' if the verifier has successfully verified the
72-- given caveat 55-- given caveat
73verify :: (Functor m, MonadIO m) => Secret -> [Caveat -> m (Maybe (Either ValidationError ()))] -> Macaroon -> m (Either ValidationError Macaroon) 56verify :: (Functor m, MonadIO m) => Secret -> [Caveat -> m VerifierResult] -> Macaroon -> m (Either ValidationError Macaroon)
74verify secret verifiers m = join <$> forM (verifySig secret m) (verifyCavs verifiers) 57verify secret verifiers m = join <$> forM (verifySig secret m) (verifyCavs verifiers)
75 58
76
77-- verifyOpBool :: MonadIO m => String -> Parser a -> (a -> a -> Bool) -> BS.ByteString -> Key -> m a -> Caveat -> m (Maybe (Either ValidationError Caveat))
78-- verifyOpBool err p f op k val = verifyParser k valueParser $ \s -> do
79-- expected <- val
80-- return $ bool (Left $ ValidatorError err) (Right Win) =<< f expected <$> mapLeft ParseError (parseOnly p s)
81-- where
82-- valueParser = string op *> skipSpace *> takeByteString
83
84-- verifyParser :: (MonadIO m) => Key -> Parser a -> (a -> m (Either ValidationError Win)) -> Caveat -> m (Maybe (Either ValidationError Caveat))
85-- verifyParser k p f c = case parseOnly keyParser . cid $ c of
86-- Left _ -> return Nothing
87-- Right bs -> Just <$> case parseOnly p bs of
88-- Left err -> return $ Left $ ParseError err
89-- Right a -> fmap (const c) <$> f a
90-- where
91-- keyParser = string k *> skipSpace *> takeByteString
92