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.hs65
1 files changed, 61 insertions, 4 deletions
diff --git a/src/Crypto/Macaroon/Verifier.hs b/src/Crypto/Macaroon/Verifier.hs
index 0d1636c..02cb448 100644
--- a/src/Crypto/Macaroon/Verifier.hs
+++ b/src/Crypto/Macaroon/Verifier.hs
@@ -1,4 +1,5 @@
1{-# LANGUAGE OverloadedStrings #-} 1{-# LANGUAGE OverloadedStrings #-}
2{-# LANGUAGE RankNTypes #-}
2{-| 3{-|
3Module : Crypto.Macaroon.Verifier 4Module : Crypto.Macaroon.Verifier
4Copyright : (c) 2015 Julien Tanguy 5Copyright : (c) 2015 Julien Tanguy
@@ -11,7 +12,17 @@ Portability : portable
11 12
12 13
13-} 14-}
14module Crypto.Macaroon.Verifier where 15module Crypto.Macaroon.Verifier (
16 Verified(..)
17 , CaveatVerifier
18 , (<???>)
19 , verifyMacaroon
20 , verifySig
21 , verifyExact
22 , verifyFun
23 , module Data.Attoparsec.ByteString.Char8
24 , verifyCavs
25) where
15 26
16 27
17import Crypto.Hash 28import Crypto.Hash
@@ -19,16 +30,62 @@ import Data.Bool
19import qualified Data.ByteString as BS 30import qualified Data.ByteString as BS
20import Data.Byteable 31import Data.Byteable
21import Data.Foldable 32import Data.Foldable
33import Data.Function
34import Data.Maybe
35import Data.Traversable
36import Data.Attoparsec.ByteString
37import Data.Attoparsec.ByteString.Char8
22 38
23import Crypto.Macaroon.Internal 39import Crypto.Macaroon.Internal
24 40
25 41
26-- | Opaque datatype for now. Might need more explicit errors 42-- | Opaque datatype for now. Might need more explicit errors
27data Result = Success | Failure deriving (Show,Eq) 43data Verified = Ok | Failed deriving (Show,Eq)
28 44
29verifySig :: Key -> Macaroon -> Result 45instance Monoid Verified where
30verifySig k m = bool Failure Success $ 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 $
31 signature m == foldl' hash (toBytes (hmac derivedKey (identifier m) :: HMAC SHA256)) (caveats m) 64 signature m == foldl' hash (toBytes (hmac derivedKey (identifier m) :: HMAC SHA256)) (caveats m)
32 where 65 where
33 hash s c = toBytes (hmac s (vid c `BS.append` cid c) :: HMAC SHA256) 66 hash s c = toBytes (hmac s (vid c `BS.append` cid c) :: HMAC SHA256)
34 derivedKey = toBytes (hmac "macaroons-key-generator" k :: 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