aboutsummaryrefslogtreecommitdiffhomepage
path: root/src/Crypto/Macaroon/Verifier.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Crypto/Macaroon/Verifier.hs')
-rw-r--r--src/Crypto/Macaroon/Verifier.hs141
1 files changed, 70 insertions, 71 deletions
diff --git a/src/Crypto/Macaroon/Verifier.hs b/src/Crypto/Macaroon/Verifier.hs
index 02cb448..a739437 100644
--- a/src/Crypto/Macaroon/Verifier.hs
+++ b/src/Crypto/Macaroon/Verifier.hs
@@ -1,5 +1,8 @@
1{-# LANGUAGE OverloadedStrings #-} 1{-# LANGUAGE FlexibleInstances #-}
2{-# LANGUAGE RankNTypes #-} 2{-# LANGUAGE OverloadedStrings #-}
3{-# LANGUAGE RankNTypes #-}
4{-# LANGUAGE TypeSynonymInstances #-}
5{-# LANGUAGE UndecidableInstances #-}
3{-| 6{-|
4Module : Crypto.Macaroon.Verifier 7Module : Crypto.Macaroon.Verifier
5Copyright : (c) 2015 Julien Tanguy 8Copyright : (c) 2015 Julien Tanguy
@@ -13,79 +16,75 @@ Portability : portable
13 16
14-} 17-}
15module Crypto.Macaroon.Verifier ( 18module Crypto.Macaroon.Verifier (
16 Verified(..) 19 verify
17 , CaveatVerifier 20 , ValidationError(ValidatorError, ParseError)
18 , (<???>) 21 -- , (.<), (.<=), (.==), (.>), (.>=)
19 , verifyMacaroon 22 -- , module Data.Attoparsec.ByteString.Char8
20 , verifySig
21 , verifyExact
22 , verifyFun
23 , module Data.Attoparsec.ByteString.Char8
24 , verifyCavs
25) where 23) where
26 24
27 25
28import Crypto.Hash 26import Control.Monad
27import Control.Monad.IO.Class
28import Data.Attoparsec.ByteString
29import Data.Attoparsec.ByteString.Char8
29import Data.Bool 30import Data.Bool
30import qualified Data.ByteString as BS 31import qualified Data.ByteString as BS
31import Data.Byteable 32import Data.Either.Combinators
32import Data.Foldable
33import Data.Function
34import Data.Maybe
35import Data.Traversable
36import Data.Attoparsec.ByteString
37import Data.Attoparsec.ByteString.Char8
38 33
39import Crypto.Macaroon.Internal 34import Crypto.Macaroon.Internal
35import Crypto.Macaroon.Verifier.Internal
36
37
38
39
40-- (.<) :: (MonadIO m, Ord a, Parsable a) => Key -> m a -> Caveat -> m (Maybe (Either ValidationError Caveat))
41-- (.<) = verifyOpBool "Greater or equal" (<) "<"
42
43-- (.<=) :: (MonadIO m, Ord a, Parsable a) => Key -> m a -> Caveat -> m (Maybe (Either ValidationError Caveat))
44-- (.<=) = verifyOpBool "Strictly greater" (<=) "<="
45
46-- (.==) :: (MonadIO m, Eq a, Parsable a) => Key -> m a -> Caveat -> m (Maybe (Either ValidationError Caveat))
47-- (.==) = verifyOpBool "Not equal" (==) "="
48
49-- (.>) :: (MonadIO m, Ord a, Parsable a) => Key -> m a -> Caveat -> m (Maybe (Either ValidationError Caveat))
50-- (.>) = verifyOpBool "Less or equal" (>) ">"
51
52-- (.>=) :: (MonadIO m, Ord a, Parsable a) => Key -> m a -> Caveat -> m (Maybe (Either ValidationError Caveat))
53-- (.>=) = verifyOpBool "Strictly less" (>=) ">="
54
55-- | Verify a Macaroon's signature and caveats, given the corresponding Secret
56-- and verifiers.
57--
58-- A verifier is a function of type
59-- @'MonadIO' m => 'Caveat' -> m ('Maybe' ('Either' 'ValidatorError' 'Caveat'))@.
60--
61-- It should return:
62--
63-- * 'Nothing' if the caveat is not related to the verifier
64-- (for instance a time verifier is given an action caveat);
65-- * 'Just' ('Left' ('ParseError' reason)) if the verifier is related to the
66-- caveat, but failed to parse it completely;
67-- * 'Just' ('Left' ('ValidatorError' reason)) if the verifier is related to the
68-- caveat, parsed it and invalidated it;
69-- * 'Just' ('Right' '()') if the verifier has successfully verified the
70-- given caveat
71verify :: MonadIO m => Secret -> [Caveat -> m (Maybe (Either ValidationError ()))] -> Macaroon -> m (Either ValidationError Macaroon)
72verify secret verifiers m = join <$> forM (verifySig secret m) (verifyCavs verifiers)
73
74
75-- verifyOpBool :: MonadIO m => String -> Parser a -> (a -> a -> Bool) -> BS.ByteString -> Key -> m a -> Caveat -> m (Maybe (Either ValidationError Caveat))
76-- verifyOpBool err p f op k val = verifyParser k valueParser $ \s -> do
77-- expected <- val
78-- return $ bool (Left $ ValidatorError err) (Right Win) =<< f expected <$> mapLeft ParseError (parseOnly p s)
79-- where
80-- valueParser = string op *> skipSpace *> takeByteString
81
82-- verifyParser :: (MonadIO m) => Key -> Parser a -> (a -> m (Either ValidationError Win)) -> Caveat -> m (Maybe (Either ValidationError Caveat))
83-- verifyParser k p f c = case parseOnly keyParser . cid $ c of
84-- Left _ -> return Nothing
85-- Right bs -> Just <$> case parseOnly p bs of
86-- Left err -> return $ Left $ ParseError err
87-- Right a -> fmap (const c) <$> f a
88-- where
89-- keyParser = string k *> skipSpace *> takeByteString
40 90
41
42-- | Opaque datatype for now. Might need more explicit errors
43data Verified = Ok | Failed deriving (Show,Eq)
44
45instance Monoid Verified where
46 mempty = Ok
47 mappend Ok Ok = Ok
48 mappend _ _ = Failed
49
50
51data CaveatVerifier = CV { vFun :: Caveat -> Maybe Verified , helpText :: String}
52
53instance Eq CaveatVerifier where
54 (==) = (==) `on` helpText
55
56instance Show CaveatVerifier where
57 show = helpText
58
59(<???>) :: (Caveat -> Maybe Verified) -> String -> CaveatVerifier
60f <???> t = CV f t
61
62verifySig :: Key -> Macaroon -> Verified
63verifySig k m = bool Failed Ok $
64 signature m == foldl' hash (toBytes (hmac derivedKey (identifier m) :: HMAC SHA256)) (caveats m)
65 where
66 hash s c = toBytes (hmac s (vid c `BS.append` cid c) :: HMAC SHA256)
67 derivedKey = toBytes (hmac "macaroons-key-generator" k :: HMAC SHA256)
68
69verifyMacaroon :: Key -> [CaveatVerifier] -> Macaroon -> Verified
70verifyMacaroon secret verifiers m = verifySig secret m `mappend` verifyCavs verifiers m
71
72
73verifyCavs :: [CaveatVerifier] -> Macaroon -> Verified
74verifyCavs verifiers m = foldMap (\c -> fromMaybe Failed $ foldMap (($ c) . vFun) verifiers) (caveats m)
75
76verifyExact :: (Eq a) => Key -> a -> Parser a -> Caveat -> Maybe Verified
77verifyExact k expected = verifyFun k (expected ==)
78
79verifyFun :: Key -> (a -> Bool) -> Parser a -> Caveat -> Maybe Verified
80verifyFun key f parser cav = if key `BS.isPrefixOf` cid cav then
81 case parseOnly kvparser (cid cav) of
82 Right v -> (bool Failed Ok . f) <$> Just v
83 Left _ -> Just Failed
84 else Nothing
85 where
86 kvparser = do
87 key <- string key
88 skipSpace
89 string "="
90 skipSpace
91 parser <* endOfInput