]> git.immae.eu Git - github/fretlink/hmacaroons.git/blame - src/Crypto/Macaroon/Verifier/Internal.hs
Import Control.Applicative
[github/fretlink/hmacaroons.git] / src / Crypto / Macaroon / Verifier / Internal.hs
CommitLineData
86f38823
JT
1{-# LANGUAGE OverloadedStrings #-}
2{-# LANGUAGE RankNTypes #-}
7f9f7386
JT
3{-|
4Module : Crypto.Macaroon.Verifier.Internal
5Copyright : (c) 2015 Julien Tanguy
6License : BSD3
7
8Maintainer : julien.tanguy@jhome.fr
9Stability : experimental
10Portability : portable
11
12
13
14-}
15module Crypto.Macaroon.Verifier.Internal where
16
1fcdeab5 17import Control.Applicative
7f9f7386
JT
18import Control.Monad
19import Control.Monad.IO.Class
20import Crypto.Hash
21import Data.Bool
22import Data.Byteable
86f38823 23import qualified Data.ByteString as BS
7f9f7386
JT
24import Data.Either
25import Data.Either.Validation
26import Data.Foldable
27import Data.Maybe
86f38823 28import Data.Monoid
7f9f7386
JT
29
30import Crypto.Macaroon.Internal
31
86f38823
JT
32-- | Type representing different validation errors.
33-- Only 'ParseError' and 'ValidatorError' are exported, 'SigMismatch' and
34-- 'NoVerifier' are used internally and should not be used by the user
35data ValidationError = SigMismatch -- ^ Signatures do not match
36 | NoVerifier -- ^ No verifier can handle a given caveat
37 | ParseError String -- ^ A verifier had a parse error
38 | ValidatorError String -- ^ A verifier failed
39 deriving (Show,Eq)
7f9f7386 40
86f38823
JT
41-- | The 'Monoid' instance is written so 'SigMismatch' is an annihilator,
42-- and 'NoVerifier' is the identity element
7f9f7386
JT
43instance Monoid ValidationError where
44 mempty = NoVerifier
45 NoVerifier `mappend` e = e
46 e `mappend` NoVerifier = e
47 SigMismatch `mappend` _ = SigMismatch
48 _ `mappend` SigMismatch = SigMismatch
49 (ValidatorError e) `mappend` (ParseError _) = ValidatorError e
50 (ParseError _) `mappend` (ValidatorError e) = ValidatorError e
51
bf31e290 52-- | Check that the given macaroon has a correct signature
7f9f7386
JT
53verifySig :: Key -> Macaroon -> Either ValidationError Macaroon
54verifySig k m = bool (Left SigMismatch) (Right m) $
55 signature m == foldl' hash (toBytes (hmac derivedKey (identifier m) :: HMAC SHA256)) (caveats m)
56 where
57 hash s c = toBytes (hmac s (vid c `BS.append` cid c) :: HMAC SHA256)
58 derivedKey = toBytes (hmac "macaroons-key-generator" k :: HMAC SHA256)
59
86f38823 60-- | Given a list of verifiers, verify each caveat of the given macaroon
7f9f7386 61verifyCavs :: MonadIO m
86f38823 62 => [Caveat -> m (Maybe (Either ValidationError ()))]
7f9f7386
JT
63 -> Macaroon
64 -> m (Either ValidationError Macaroon)
65verifyCavs verifiers m = gatherEithers <$> mapM validateCaveat (caveats m)
66 where
67 {-
68 - validateCaveat :: Caveat -> m (Validation String Caveat)
69 - We can use fromJust here safely since we use a `Just Failure` as a
70 - starting value for the foldM. We are guaranteed to have a `Just something`
71 - from it.
72 -}
86f38823 73 validateCaveat c = fmap (const c) . fromJust <$> foldM (\res v -> mappend res . fmap eitherToValidation <$> v c) (defErr c) verifiers
7f9f7386
JT
74 -- defErr :: Caveat -> Maybe (Validation String Caveat)
75 defErr c = Just $ Failure NoVerifier
76 -- gatherEithers :: [Validation String Caveat] -> Either String Caveat
77 gatherEithers vs = case partitionEithers . map validationToEither $ vs of
78 ([],_) -> Right m
79 (errs,_) -> Left (mconcat errs)