]> git.immae.eu Git - github/fretlink/hmacaroons.git/blame - src/Crypto/Macaroon/Verifier.hs
ghc<7.10.1 compat
[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
JT
19 verify
20 , ValidationError(ValidatorError, ParseError)
21 -- , (.<), (.<=), (.==), (.>), (.>=)
22 -- , module Data.Attoparsec.ByteString.Char8
6f3c0dca 23) where
b92e3c15
JT
24
25
a11f20be
JT
26import Control.Applicative
27import Control.Monad hiding (forM)
7f9f7386 28import Control.Monad.IO.Class
c830f7c2
JT
29import Data.Attoparsec.ByteString
30import Data.Attoparsec.ByteString.Char8
b92e3c15 31import Data.Bool
a11f20be 32import Data.Traversable
c830f7c2 33import qualified Data.ByteString as BS
7f9f7386 34import Data.Either.Combinators
b92e3c15
JT
35
36import Crypto.Macaroon.Internal
7f9f7386 37import Crypto.Macaroon.Verifier.Internal
b92e3c15
JT
38
39
6f3c0dca 40
62576139 41
7f9f7386
JT
42-- (.<) :: (MonadIO m, Ord a, Parsable a) => Key -> m a -> Caveat -> m (Maybe (Either ValidationError Caveat))
43-- (.<) = verifyOpBool "Greater or equal" (<) "<"
44
45-- (.<=) :: (MonadIO m, Ord a, Parsable a) => Key -> m a -> Caveat -> m (Maybe (Either ValidationError Caveat))
46-- (.<=) = verifyOpBool "Strictly greater" (<=) "<="
47
48-- (.==) :: (MonadIO m, Eq a, Parsable a) => Key -> m a -> Caveat -> m (Maybe (Either ValidationError Caveat))
49-- (.==) = verifyOpBool "Not equal" (==) "="
50
51-- (.>) :: (MonadIO m, Ord a, Parsable a) => Key -> m a -> Caveat -> m (Maybe (Either ValidationError Caveat))
52-- (.>) = verifyOpBool "Less or equal" (>) ">"
53
54-- (.>=) :: (MonadIO m, Ord a, Parsable a) => Key -> m a -> Caveat -> m (Maybe (Either ValidationError Caveat))
55-- (.>=) = verifyOpBool "Strictly less" (>=) ">="
6f3c0dca 56
86f38823
JT
57-- | Verify a Macaroon's signature and caveats, given the corresponding Secret
58-- and verifiers.
59--
60-- A verifier is a function of type
61-- @'MonadIO' m => 'Caveat' -> m ('Maybe' ('Either' 'ValidatorError' 'Caveat'))@.
62--
63-- It should return:
64--
65-- * 'Nothing' if the caveat is not related to the verifier
66-- (for instance a time verifier is given an action caveat);
67-- * 'Just' ('Left' ('ParseError' reason)) if the verifier is related to the
68-- caveat, but failed to parse it completely;
69-- * 'Just' ('Left' ('ValidatorError' reason)) if the verifier is related to the
70-- caveat, parsed it and invalidated it;
71-- * 'Just' ('Right' '()') if the verifier has successfully verified the
72-- given caveat
a11f20be 73verify :: (Functor m, MonadIO m) => Secret -> [Caveat -> m (Maybe (Either ValidationError ()))] -> Macaroon -> m (Either ValidationError Macaroon)
7f9f7386
JT
74verify secret verifiers m = join <$> forM (verifySig secret m) (verifyCavs verifiers)
75
76
77-- verifyOpBool :: MonadIO m => String -> Parser a -> (a -> a -> Bool) -> BS.ByteString -> Key -> m a -> Caveat -> m (Maybe (Either ValidationError Caveat))
78-- verifyOpBool err p f op k val = verifyParser k valueParser $ \s -> do
79-- expected <- val
80-- return $ bool (Left $ ValidatorError err) (Right Win) =<< f expected <$> mapLeft ParseError (parseOnly p s)
81-- where
82-- valueParser = string op *> skipSpace *> takeByteString
83
86f38823
JT
84-- verifyParser :: (MonadIO m) => Key -> Parser a -> (a -> m (Either ValidationError Win)) -> Caveat -> m (Maybe (Either ValidationError Caveat))
85-- verifyParser k p f c = case parseOnly keyParser . cid $ c of
86-- Left _ -> return Nothing
87-- Right bs -> Just <$> case parseOnly p bs of
88-- Left err -> return $ Left $ ParseError err
89-- Right a -> fmap (const c) <$> f a
90-- where
91-- keyParser = string k *> skipSpace *> takeByteString
7f9f7386 92