diff options
-rw-r--r-- | default.nix | 6 | ||||
-rw-r--r-- | hmacaroons.cabal | 4 | ||||
-rw-r--r-- | shell.nix | 4 | ||||
-rw-r--r-- | src/Crypto/Macaroon/Verifier.hs | 81 | ||||
-rw-r--r-- | src/Crypto/Macaroon/Verifier/Internal.hs | 74 | ||||
-rw-r--r-- | test/Crypto/Macaroon/Verifier/Tests.hs | 36 |
6 files changed, 165 insertions, 40 deletions
diff --git a/default.nix b/default.nix index bd725a9..b1404ef 100644 --- a/default.nix +++ b/default.nix | |||
@@ -1,14 +1,14 @@ | |||
1 | { mkDerivation, attoparsec, base, base64-bytestring, byteable | 1 | { mkDerivation, attoparsec, base, base64-bytestring, byteable |
2 | , bytestring, cereal, cryptohash, deepseq, either, hex, QuickCheck | 2 | , bytestring, cereal, cryptohash, deepseq, either, hex, QuickCheck |
3 | , stdenv, tasty, tasty-hunit, tasty-quickcheck | 3 | , stdenv, tasty, tasty-hunit, tasty-quickcheck, transformers |
4 | }: | 4 | }: |
5 | mkDerivation { | 5 | mkDerivation { |
6 | pname = "hmacaroons"; | 6 | pname = "hmacaroons"; |
7 | version = "0.1.0.0"; | 7 | version = "0.2.0.0"; |
8 | src = ./.; | 8 | src = ./.; |
9 | buildDepends = [ | 9 | buildDepends = [ |
10 | attoparsec base base64-bytestring byteable bytestring cereal | 10 | attoparsec base base64-bytestring byteable bytestring cereal |
11 | cryptohash deepseq either hex | 11 | cryptohash deepseq either hex transformers |
12 | ]; | 12 | ]; |
13 | testDepends = [ | 13 | testDepends = [ |
14 | attoparsec base base64-bytestring byteable bytestring cereal | 14 | attoparsec base base64-bytestring byteable bytestring cereal |
diff --git a/hmacaroons.cabal b/hmacaroons.cabal index 3aa338a..7b5a0dd 100644 --- a/hmacaroons.cabal +++ b/hmacaroons.cabal | |||
@@ -1,5 +1,5 @@ | |||
1 | name: hmacaroons | 1 | name: hmacaroons |
2 | version: 0.1.0.0 | 2 | version: 0.2.0.0 |
3 | synopsis: Haskell implementation of macaroons | 3 | synopsis: Haskell implementation of macaroons |
4 | description: | 4 | description: |
5 | = Macaroons: Pure haskell implementation of macaroons | 5 | = Macaroons: Pure haskell implementation of macaroons |
@@ -60,12 +60,14 @@ library | |||
60 | other-modules: Crypto.Macaroon.Internal | 60 | other-modules: Crypto.Macaroon.Internal |
61 | build-depends: base >=4 && < 5, | 61 | build-depends: base >=4 && < 5, |
62 | attoparsec >=0.12, | 62 | attoparsec >=0.12, |
63 | transformers >= 0.4, | ||
63 | bytestring >=0.10, | 64 | bytestring >=0.10, |
64 | base64-bytestring >= 1.0, | 65 | base64-bytestring >= 1.0, |
65 | byteable >= 0.1 && <0.2, | 66 | byteable >= 0.1 && <0.2, |
66 | cereal >= 0.4, | 67 | cereal >= 0.4, |
67 | cryptohash >=0.11 && <0.12, | 68 | cryptohash >=0.11 && <0.12, |
68 | either >=4.4, | 69 | either >=4.4, |
70 | -- nonce, | ||
69 | -- cipher-aes >=0.2 && <0.3, | 71 | -- cipher-aes >=0.2 && <0.3, |
70 | deepseq >= 1.1, | 72 | deepseq >= 1.1, |
71 | hex >= 0.1 | 73 | hex >= 0.1 |
@@ -1,5 +1,5 @@ | |||
1 | with (import <nixpkgs> {}).pkgs; | 1 | { pkgs ? import <nixpkgs> {}, compiler ? "ghc7101" }: |
2 | let hspkgs = haskell-ng.packages.ghc7101.override { | 2 | let hspkgs = pkgs.haskell.packages.${compiler}.override { |
3 | overrides = self: super: { | 3 | overrides = self: super: { |
4 | hmacaroons = self.callPackage ./. {}; | 4 | hmacaroons = self.callPackage ./. {}; |
5 | }; | 5 | }; |
diff --git a/src/Crypto/Macaroon/Verifier.hs b/src/Crypto/Macaroon/Verifier.hs index 713a971..7d5f094 100644 --- a/src/Crypto/Macaroon/Verifier.hs +++ b/src/Crypto/Macaroon/Verifier.hs | |||
@@ -1,5 +1,8 @@ | |||
1 | {-# LANGUAGE OverloadedStrings #-} | 1 | {-# LANGUAGE FlexibleInstances #-} |
2 | {-# LANGUAGE RankNTypes #-} | 2 | {-# LANGUAGE OverloadedStrings #-} |
3 | {-# LANGUAGE RankNTypes #-} | ||
4 | {-# LANGUAGE TypeSynonymInstances #-} | ||
5 | {-# LANGUAGE UndecidableInstances #-} | ||
3 | {-| | 6 | {-| |
4 | Module : Crypto.Macaroon.Verifier | 7 | Module : Crypto.Macaroon.Verifier |
5 | Copyright : (c) 2015 Julien Tanguy | 8 | Copyright : (c) 2015 Julien Tanguy |
@@ -13,50 +16,60 @@ Portability : portable | |||
13 | 16 | ||
14 | -} | 17 | -} |
15 | module Crypto.Macaroon.Verifier ( | 18 | module Crypto.Macaroon.Verifier ( |
16 | Verifier | 19 | verify |
17 | , verifyMacaroon | 20 | , ValidationError(ValidatorError, ParseError) |
18 | , verifySig | 21 | -- , (.<), (.<=), (.==), (.>), (.>=) |
19 | -- , verifyExact | 22 | -- , module Data.Attoparsec.ByteString.Char8 |
20 | -- , verifyFun | ||
21 | , module Data.Attoparsec.ByteString.Char8 | ||
22 | , verifyCavs | ||
23 | ) where | 23 | ) where |
24 | 24 | ||
25 | 25 | ||
26 | import Crypto.Hash | 26 | import Control.Monad |
27 | import Control.Monad.IO.Class | ||
27 | import Data.Attoparsec.ByteString | 28 | import Data.Attoparsec.ByteString |
28 | import Data.Attoparsec.ByteString.Char8 | 29 | import Data.Attoparsec.ByteString.Char8 |
29 | import Data.Bool | 30 | import Data.Bool |
30 | import Data.Byteable | ||
31 | import qualified Data.ByteString as BS | 31 | import qualified Data.ByteString as BS |
32 | import Data.Either | 32 | import Data.Either.Combinators |
33 | import Data.Either.Validation | ||
34 | import Data.Foldable | ||
35 | import Data.Function | ||
36 | import Data.Maybe | ||
37 | import Data.Traversable | ||
38 | 33 | ||
39 | import Crypto.Macaroon.Internal | 34 | import Crypto.Macaroon.Internal |
35 | import Crypto.Macaroon.Verifier.Internal | ||
40 | 36 | ||
41 | type Verifier = Caveat -> Maybe (Either String Caveat) | ||
42 | 37 | ||
43 | verifySig :: Key -> Macaroon -> Either String Macaroon | ||
44 | verifySig k m = bool (Left "Signatures do not match") (Right m) $ | ||
45 | signature m == foldl' hash (toBytes (hmac derivedKey (identifier m) :: HMAC SHA256)) (caveats m) | ||
46 | where | ||
47 | hash s c = toBytes (hmac s (vid c `BS.append` cid c) :: HMAC SHA256) | ||
48 | derivedKey = toBytes (hmac "macaroons-key-generator" k :: HMAC SHA256) | ||
49 | 38 | ||
50 | verifyMacaroon :: Key -> [Verifier] -> Macaroon -> Either String Macaroon | ||
51 | verifyMacaroon secret verifiers m = verifySig secret m >>= verifyCavs verifiers | ||
52 | 39 | ||
53 | verifyCavs :: [Verifier] -> Macaroon -> Either String Macaroon | 40 | -- (.<) :: (MonadIO m, Ord a, Parsable a) => Key -> m a -> Caveat -> m (Maybe (Either ValidationError Caveat)) |
54 | verifyCavs verifiers m = case partitionEithers verifiedCaveats of | 41 | -- (.<) = verifyOpBool "Greater or equal" (<) "<" |
55 | ([],_) -> Right m | 42 | |
56 | (errs,_) -> Left (mconcat errs) | 43 | -- (.<=) :: (MonadIO m, Ord a, Parsable a) => Key -> m a -> Caveat -> m (Maybe (Either ValidationError Caveat)) |
57 | where | 44 | -- (.<=) = verifyOpBool "Strictly greater" (<=) "<=" |
58 | verifiedCaveats = map (\c -> defaultFail c $ foldMap (fmap eitherToValidation . ($c)) verifiers) $ caveats m | 45 | |
59 | defaultFail c = maybe (Left ("No validation for this caveat: " ++ show c)) validationToEither | 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" (>=) ">=" | ||
60 | 54 | ||
61 | 55 | ||
62 | -- TODO: define API | 56 | verify :: MonadIO m => Key -> [Caveat -> m (Maybe (Either ValidationError Caveat))] -> Macaroon -> m (Either ValidationError Macaroon) |
57 | verify secret verifiers m = join <$> forM (verifySig secret m) (verifyCavs verifiers) | ||
58 | |||
59 | |||
60 | -- verifyOpBool :: MonadIO m => String -> Parser a -> (a -> a -> Bool) -> BS.ByteString -> Key -> m a -> Caveat -> m (Maybe (Either ValidationError Caveat)) | ||
61 | -- verifyOpBool err p f op k val = verifyParser k valueParser $ \s -> do | ||
62 | -- expected <- val | ||
63 | -- return $ bool (Left $ ValidatorError err) (Right Win) =<< f expected <$> mapLeft ParseError (parseOnly p s) | ||
64 | -- where | ||
65 | -- valueParser = string op *> skipSpace *> takeByteString | ||
66 | |||
67 | verifyParser :: (MonadIO m) => Key -> Parser a -> (a -> m (Either ValidationError Win)) -> Caveat -> m (Maybe (Either ValidationError Caveat)) | ||
68 | verifyParser k p f c = case parseOnly keyParser . cid $ c of | ||
69 | Left _ -> return Nothing | ||
70 | Right bs -> Just <$> case parseOnly p bs of | ||
71 | Left err -> return $ Left $ ParseError err | ||
72 | Right a -> fmap (const c) <$> f a | ||
73 | where | ||
74 | keyParser = string k *> skipSpace *> takeByteString | ||
75 | |||
diff --git a/src/Crypto/Macaroon/Verifier/Internal.hs b/src/Crypto/Macaroon/Verifier/Internal.hs new file mode 100644 index 0000000..63d826d --- /dev/null +++ b/src/Crypto/Macaroon/Verifier/Internal.hs | |||
@@ -0,0 +1,74 @@ | |||
1 | {-# LANGUAGE OverloadedStrings #-} | ||
2 | {-# LANGUAGE RankNTypes #-} | ||
3 | {-| | ||
4 | Module : Crypto.Macaroon.Verifier.Internal | ||
5 | Copyright : (c) 2015 Julien Tanguy | ||
6 | License : BSD3 | ||
7 | |||
8 | Maintainer : julien.tanguy@jhome.fr | ||
9 | Stability : experimental | ||
10 | Portability : portable | ||
11 | |||
12 | |||
13 | |||
14 | -} | ||
15 | module Crypto.Macaroon.Verifier.Internal where | ||
16 | |||
17 | import Control.Monad | ||
18 | import Control.Monad.IO.Class | ||
19 | import Crypto.Hash | ||
20 | import Data.Bool | ||
21 | import Data.Byteable | ||
22 | import qualified Data.ByteString as BS | ||
23 | import Data.Either | ||
24 | import Data.Either.Validation | ||
25 | import Data.Foldable | ||
26 | import Data.Maybe | ||
27 | |||
28 | import Crypto.Macaroon.Internal | ||
29 | |||
30 | data Win = Win | ||
31 | |||
32 | data ValidationError = SigMismatch | ||
33 | | NoVerifier | ||
34 | | ParseError String | ||
35 | | ValidatorError String | ||
36 | deriving Show | ||
37 | |||
38 | instance Monoid ValidationError where | ||
39 | mempty = NoVerifier | ||
40 | NoVerifier `mappend` e = e | ||
41 | e `mappend` NoVerifier = e | ||
42 | SigMismatch `mappend` _ = SigMismatch | ||
43 | _ `mappend` SigMismatch = SigMismatch | ||
44 | (ValidatorError e) `mappend` (ParseError _) = ValidatorError e | ||
45 | (ParseError _) `mappend` (ValidatorError e) = ValidatorError e | ||
46 | |||
47 | |||
48 | verifySig :: Key -> Macaroon -> Either ValidationError Macaroon | ||
49 | verifySig k m = bool (Left SigMismatch) (Right m) $ | ||
50 | signature m == foldl' hash (toBytes (hmac derivedKey (identifier m) :: HMAC SHA256)) (caveats m) | ||
51 | where | ||
52 | hash s c = toBytes (hmac s (vid c `BS.append` cid c) :: HMAC SHA256) | ||
53 | derivedKey = toBytes (hmac "macaroons-key-generator" k :: HMAC SHA256) | ||
54 | |||
55 | |||
56 | verifyCavs :: MonadIO m | ||
57 | => [Caveat -> m (Maybe (Either ValidationError Caveat))] | ||
58 | -> Macaroon | ||
59 | -> m (Either ValidationError Macaroon) | ||
60 | verifyCavs verifiers m = gatherEithers <$> mapM validateCaveat (caveats m) | ||
61 | where | ||
62 | {- | ||
63 | - validateCaveat :: Caveat -> m (Validation String Caveat) | ||
64 | - We can use fromJust here safely since we use a `Just Failure` as a | ||
65 | - starting value for the foldM. We are guaranteed to have a `Just something` | ||
66 | - from it. | ||
67 | -} | ||
68 | validateCaveat c = fromJust <$> foldM (\res v -> mappend res . fmap eitherToValidation <$> v c) (defErr c) verifiers | ||
69 | -- defErr :: Caveat -> Maybe (Validation String Caveat) | ||
70 | defErr c = Just $ Failure NoVerifier | ||
71 | -- gatherEithers :: [Validation String Caveat] -> Either String Caveat | ||
72 | gatherEithers vs = case partitionEithers . map validationToEither $ vs of | ||
73 | ([],_) -> Right m | ||
74 | (errs,_) -> Left (mconcat errs) | ||
diff --git a/test/Crypto/Macaroon/Verifier/Tests.hs b/test/Crypto/Macaroon/Verifier/Tests.hs index 4a9295f..670c991 100644 --- a/test/Crypto/Macaroon/Verifier/Tests.hs +++ b/test/Crypto/Macaroon/Verifier/Tests.hs | |||
@@ -63,3 +63,39 @@ m3 = addFirstPartyCaveat "value = 42" m2 | |||
63 | sigs = testProperty "Signatures" $ \sm -> verifySig (secret sm) (macaroon sm) == Right (macaroon sm) | 63 | sigs = testProperty "Signatures" $ \sm -> verifySig (secret sm) (macaroon sm) == Right (macaroon sm) |
64 | 64 | ||
65 | -- TODO: Re-do tests | 65 | -- TODO: Re-do tests |
66 | {- | ||
67 | firstParty = testGroup "First party caveats" [ | ||
68 | testGroup "Pure verifiers" [ | ||
69 | testProperty "Zero caveat" $ | ||
70 | forAll (sublistOf allvs) (\vs -> Right m == verifyCavs vs m) | ||
71 | , testProperty "One caveat" $ | ||
72 | forAll (sublistOf allvs) (\vs -> disjoin [ | ||
73 | Right m2 == verifyCavs vs m2 .&&. any (`elem` vs) [exTC,funTCPre] .&&. (exTZ `notElem` vs) | ||
74 | , True === isLeft( verifyCavs vs m2) | ||
75 | ]) | ||
76 | , testProperty "Two Exact" $ | ||
77 | forAll (sublistOf allvs) (\vs -> disjoin [ | ||
78 | Right m3 == verifyCavs vs m3 .&&. | ||
79 | any (`elem` vs) [exTC,funTCPre] .&&. (exTZ `notElem` vs) .&&. | ||
80 | any (`elem` vs) [exV42,funTV43lte] .&&. (exV43 `notElem` vs) | ||
81 | , True === isLeft (verifyCavs vs m3) | ||
82 | ]) | ||
83 | ] | ||
84 | , testGroup "Pure verifiers with sig" [ | ||
85 | testProperty "Zero caveat" $ | ||
86 | forAll (sublistOf allvs) (\vs -> Right m == verifyMacaroon sec vs m) | ||
87 | , testProperty "One caveat" $ | ||
88 | forAll (sublistOf allvs) (\vs -> disjoin [ | ||
89 | Right m2 == verifyMacaroon sec vs m2 .&&. any (`elem` vs) [exTC,funTCPre] .&&. (exTZ `notElem` vs) | ||
90 | , True === isLeft (verifyMacaroon sec vs m2) | ||
91 | ]) | ||
92 | , testProperty "Two Exact" $ | ||
93 | forAll (sublistOf allvs) (\vs -> disjoin [ | ||
94 | Right m3 == verifyMacaroon sec vs m3 .&&. | ||
95 | any (`elem` vs) [exTC,funTCPre] .&&. (exTZ `notElem` vs) .&&. | ||
96 | any (`elem` vs) [exV42,funTV43lte] .&&. (exV43 `notElem` vs) | ||
97 | , True === isLeft (verifyMacaroon sec vs m3) | ||
98 | ]) | ||
99 | ] | ||
100 | ] | ||
101 | -} | ||