blob: a3bf5d4f56680ee72af4217cc010baa4fcfd8cbd (
plain) (
blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
|
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-|
Module : Crypto.Macaroon.Verifier
Copyright : (c) 2015 Julien Tanguy
License : BSD3
Maintainer : julien.tanguy@jhome.fr
Stability : experimental
Portability : portable
-}
module Crypto.Macaroon.Verifier (
verify
, VerifierResult(..)
, ValidationError(ValidatorError, ParseError)
) where
import Control.Applicative
import Control.Monad hiding (forM)
import Control.Monad.IO.Class
import Data.Attoparsec.ByteString
import Data.Attoparsec.ByteString.Char8
import Data.Bool
import Data.Traversable
import qualified Data.ByteString as BS
import Data.Either.Combinators
import Crypto.Macaroon.Internal
import Crypto.Macaroon.Verifier.Internal
-- | Verify a Macaroon's signature and caveats, given the corresponding Secret
-- and verifiers.
--
-- A verifier is a function of type
-- @'MonadIO' m => 'Caveat' -> m VerifierResult@.
--
-- It should return:
--
-- * 'Unrelated' if the caveat is not related to the verifier
-- (for instance a time verifier is given an action caveat);
-- * 'Refused' ('ParseError' reason) if the verifier is related to the
-- caveat, but failed to parse it completely;
-- * 'Refused' ('ValidatorError' reason) if the verifier is related to the
-- caveat, parsed it and invalidated it;
-- * 'Verified' if the verifier has successfully verified the
-- given caveat
verify :: (Functor m, MonadIO m) => Secret -> [Caveat -> m VerifierResult] -> Macaroon -> m (Either ValidationError Macaroon)
verify secret verifiers m = join <$> forM (verifySig secret m) (verifyCavs verifiers)
|