diff options
Diffstat (limited to 'src')
-rw-r--r-- | src/Crypto/Macaroon/Internal.hs | 2 | ||||
-rw-r--r-- | src/Crypto/Macaroon/Verifier.hs | 65 |
2 files changed, 62 insertions, 5 deletions
diff --git a/src/Crypto/Macaroon/Internal.hs b/src/Crypto/Macaroon/Internal.hs index 116f5ed..2f56512 100644 --- a/src/Crypto/Macaroon/Internal.hs +++ b/src/Crypto/Macaroon/Internal.hs | |||
@@ -58,7 +58,7 @@ instance Show Macaroon where | |||
58 | show (MkMacaroon l i c s) = intercalate "\n" [ | 58 | show (MkMacaroon l i c s) = intercalate "\n" [ |
59 | "location " ++ B8.unpack l | 59 | "location " ++ B8.unpack l |
60 | , "identifier " ++ B8.unpack i | 60 | , "identifier " ++ B8.unpack i |
61 | , concatMap show c | 61 | , intercalate "\n" (map show c) |
62 | , "signature " ++ B8.unpack (hex s) | 62 | , "signature " ++ B8.unpack (hex s) |
63 | ] | 63 | ] |
64 | 64 | ||
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 | {-| |
3 | Module : Crypto.Macaroon.Verifier | 4 | Module : Crypto.Macaroon.Verifier |
4 | Copyright : (c) 2015 Julien Tanguy | 5 | Copyright : (c) 2015 Julien Tanguy |
@@ -11,7 +12,17 @@ Portability : portable | |||
11 | 12 | ||
12 | 13 | ||
13 | -} | 14 | -} |
14 | module Crypto.Macaroon.Verifier where | 15 | module 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 | ||
17 | import Crypto.Hash | 28 | import Crypto.Hash |
@@ -19,16 +30,62 @@ import Data.Bool | |||
19 | import qualified Data.ByteString as BS | 30 | import qualified Data.ByteString as BS |
20 | import Data.Byteable | 31 | import Data.Byteable |
21 | import Data.Foldable | 32 | import Data.Foldable |
33 | import Data.Function | ||
34 | import Data.Maybe | ||
35 | import Data.Traversable | ||
36 | import Data.Attoparsec.ByteString | ||
37 | import Data.Attoparsec.ByteString.Char8 | ||
22 | 38 | ||
23 | import Crypto.Macaroon.Internal | 39 | import 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 |
27 | data Result = Success | Failure deriving (Show,Eq) | 43 | data Verified = Ok | Failed deriving (Show,Eq) |
28 | 44 | ||
29 | verifySig :: Key -> Macaroon -> Result | 45 | instance Monoid Verified where |
30 | verifySig k m = bool Failure Success $ | 46 | mempty = Ok |
47 | mappend Ok Ok = Ok | ||
48 | mappend _ _ = Failed | ||
49 | |||
50 | |||
51 | data CaveatVerifier = CV { vFun :: Caveat -> Maybe Verified , helpText :: String} | ||
52 | |||
53 | instance Eq CaveatVerifier where | ||
54 | (==) = (==) `on` helpText | ||
55 | |||
56 | instance Show CaveatVerifier where | ||
57 | show = helpText | ||
58 | |||
59 | (<???>) :: (Caveat -> Maybe Verified) -> String -> CaveatVerifier | ||
60 | f <???> t = CV f t | ||
61 | |||
62 | verifySig :: Key -> Macaroon -> Verified | ||
63 | verifySig 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 | |||
69 | verifyMacaroon :: Key -> [CaveatVerifier] -> Macaroon -> Verified | ||
70 | verifyMacaroon secret verifiers m = verifySig secret m `mappend` verifyCavs verifiers m | ||
71 | |||
72 | |||
73 | verifyCavs :: [CaveatVerifier] -> Macaroon -> Verified | ||
74 | verifyCavs verifiers m = foldMap (\c -> fromMaybe Failed $ foldMap (($ c) . vFun) verifiers) (caveats m) | ||
75 | |||
76 | verifyExact :: (Eq a) => Key -> a -> Parser a -> Caveat -> Maybe Verified | ||
77 | verifyExact k expected = verifyFun k (expected ==) | ||
78 | |||
79 | verifyFun :: Key -> (a -> Bool) -> Parser a -> Caveat -> Maybe Verified | ||
80 | verifyFun 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 | ||