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