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