diff options
Diffstat (limited to 'src')
-rw-r--r-- | src/Crypto/Macaroon/Verifier.hs | 47 |
1 files changed, 43 insertions, 4 deletions
diff --git a/src/Crypto/Macaroon/Verifier.hs b/src/Crypto/Macaroon/Verifier.hs index e257f5f..cb64c9d 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,14 @@ Portability : portable | |||
11 | 12 | ||
12 | 13 | ||
13 | -} | 14 | -} |
14 | module Crypto.Macaroon.Verifier where | 15 | module Crypto.Macaroon.Verifier ( |
16 | Verified(..) | ||
17 | , verifySig | ||
18 | , verifyExact | ||
19 | , verifyCavs | ||
20 | -- , module Data.Attoparsec.ByteString | ||
21 | , module Data.Attoparsec.ByteString.Char8 | ||
22 | ) where | ||
15 | 23 | ||
16 | 24 | ||
17 | import Crypto.Hash | 25 | import Crypto.Hash |
@@ -19,16 +27,47 @@ import Data.Bool | |||
19 | import qualified Data.ByteString as BS | 27 | import qualified Data.ByteString as BS |
20 | import Data.Byteable | 28 | import Data.Byteable |
21 | import Data.Foldable | 29 | import Data.Foldable |
30 | import Data.Maybe | ||
31 | import Data.Attoparsec.ByteString | ||
32 | import Data.Attoparsec.ByteString.Char8 | ||
22 | 33 | ||
23 | import Crypto.Macaroon.Internal | 34 | import Crypto.Macaroon.Internal |
24 | 35 | ||
25 | 36 | ||
26 | -- | Opaque datatype for now. Might need more explicit errors | 37 | -- | Opaque datatype for now. Might need more explicit errors |
27 | data VResult = VSuccess | VFailure deriving (Show,Eq) | 38 | data Verified = Ok | Failed deriving (Show,Eq) |
28 | 39 | ||
29 | verifySig :: Key -> Macaroon -> VResult | 40 | instance Monoid Verified where |
30 | verifySig k m = bool VFailure VSuccess $ | 41 | mempty = Ok |
42 | mappend Ok Ok = Ok | ||
43 | mappend _ _ = Failed | ||
44 | |||
45 | |||
46 | type CaveatVerifier = Caveat -> Maybe Verified | ||
47 | |||
48 | verifySig :: Key -> Macaroon -> Verified | ||
49 | verifySig k m = bool Failed Ok $ | ||
31 | signature m == foldl' hash (toBytes (hmac derivedKey (identifier m) :: HMAC SHA256)) (caveats m) | 50 | signature m == foldl' hash (toBytes (hmac derivedKey (identifier m) :: HMAC SHA256)) (caveats m) |
32 | where | 51 | where |
33 | hash s c = toBytes (hmac s (vid c `BS.append` cid c) :: HMAC SHA256) | 52 | hash s c = toBytes (hmac s (vid c `BS.append` cid c) :: HMAC SHA256) |
34 | derivedKey = toBytes (hmac "macaroons-key-generator" k :: HMAC SHA256) | 53 | derivedKey = toBytes (hmac "macaroons-key-generator" k :: HMAC SHA256) |
54 | |||
55 | verifyCavs :: [Caveat -> Maybe Verified] -> Macaroon -> Verified | ||
56 | verifyCavs verifiers m = mconcat $ map (\c -> mconcat . catMaybes $ map ($ c) verifiers) (caveats m) | ||
57 | |||
58 | verifyExact :: (Show a, Eq a) => Key -> a -> Parser a -> Caveat -> Maybe Verified | ||
59 | verifyExact key expected parser cav = if key `BS.isPrefixOf` cid cav then | ||
60 | case parseOnly kvparser (cid cav) of | ||
61 | Right v -> verify <$> Just v | ||
62 | Left _ -> Just Failed | ||
63 | else Nothing | ||
64 | where | ||
65 | kvparser = do | ||
66 | key <- string key | ||
67 | skipSpace | ||
68 | string "=" | ||
69 | skipSpace | ||
70 | parser | ||
71 | |||
72 | -- *> skipSpace *> string "=" *> skipSpace *> parser <* endOfInput | ||
73 | verify a = bool Failed Ok (a == expected) | ||