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