diff options
-rw-r--r-- | src/Crypto/Macaroon/Internal.hs | 2 | ||||
-rw-r--r-- | src/Crypto/Macaroon/Verifier.hs | 65 | ||||
-rw-r--r-- | test/Crypto/Macaroon/Instances.hs | 21 | ||||
-rw-r--r-- | test/Crypto/Macaroon/Serializer/Base64/Tests.hs | 2 | ||||
-rw-r--r-- | test/Crypto/Macaroon/Verifier/Tests.hs | 79 |
5 files changed, 141 insertions, 28 deletions
diff --git a/src/Crypto/Macaroon/Internal.hs b/src/Crypto/Macaroon/Internal.hs index 116f5ed..2f56512 100644 --- a/src/Crypto/Macaroon/Internal.hs +++ b/src/Crypto/Macaroon/Internal.hs | |||
@@ -58,7 +58,7 @@ instance Show Macaroon where | |||
58 | show (MkMacaroon l i c s) = intercalate "\n" [ | 58 | show (MkMacaroon l i c s) = intercalate "\n" [ |
59 | "location " ++ B8.unpack l | 59 | "location " ++ B8.unpack l |
60 | , "identifier " ++ B8.unpack i | 60 | , "identifier " ++ B8.unpack i |
61 | , concatMap show c | 61 | , intercalate "\n" (map show c) |
62 | , "signature " ++ B8.unpack (hex s) | 62 | , "signature " ++ B8.unpack (hex s) |
63 | ] | 63 | ] |
64 | 64 | ||
diff --git a/src/Crypto/Macaroon/Verifier.hs b/src/Crypto/Macaroon/Verifier.hs index 0d1636c..02cb448 100644 --- a/src/Crypto/Macaroon/Verifier.hs +++ b/src/Crypto/Macaroon/Verifier.hs | |||
@@ -1,4 +1,5 @@ | |||
1 | {-# LANGUAGE OverloadedStrings #-} | 1 | {-# LANGUAGE OverloadedStrings #-} |
2 | {-# LANGUAGE RankNTypes #-} | ||
2 | {-| | 3 | {-| |
3 | Module : Crypto.Macaroon.Verifier | 4 | Module : Crypto.Macaroon.Verifier |
4 | Copyright : (c) 2015 Julien Tanguy | 5 | Copyright : (c) 2015 Julien Tanguy |
@@ -11,7 +12,17 @@ Portability : portable | |||
11 | 12 | ||
12 | 13 | ||
13 | -} | 14 | -} |
14 | module Crypto.Macaroon.Verifier where | 15 | module Crypto.Macaroon.Verifier ( |
16 | Verified(..) | ||
17 | , CaveatVerifier | ||
18 | , (<???>) | ||
19 | , verifyMacaroon | ||
20 | , verifySig | ||
21 | , verifyExact | ||
22 | , verifyFun | ||
23 | , module Data.Attoparsec.ByteString.Char8 | ||
24 | , verifyCavs | ||
25 | ) where | ||
15 | 26 | ||
16 | 27 | ||
17 | import Crypto.Hash | 28 | import Crypto.Hash |
@@ -19,16 +30,62 @@ import Data.Bool | |||
19 | import qualified Data.ByteString as BS | 30 | import qualified Data.ByteString as BS |
20 | import Data.Byteable | 31 | import Data.Byteable |
21 | import Data.Foldable | 32 | import Data.Foldable |
33 | import Data.Function | ||
34 | import Data.Maybe | ||
35 | import Data.Traversable | ||
36 | import Data.Attoparsec.ByteString | ||
37 | import Data.Attoparsec.ByteString.Char8 | ||
22 | 38 | ||
23 | import Crypto.Macaroon.Internal | 39 | import Crypto.Macaroon.Internal |
24 | 40 | ||
25 | 41 | ||
26 | -- | Opaque datatype for now. Might need more explicit errors | 42 | -- | Opaque datatype for now. Might need more explicit errors |
27 | data Result = Success | Failure deriving (Show,Eq) | 43 | data Verified = Ok | Failed deriving (Show,Eq) |
28 | 44 | ||
29 | verifySig :: Key -> Macaroon -> Result | 45 | instance Monoid Verified where |
30 | verifySig k m = bool Failure Success $ | 46 | mempty = Ok |
47 | mappend Ok Ok = Ok | ||
48 | mappend _ _ = Failed | ||
49 | |||
50 | |||
51 | data CaveatVerifier = CV { vFun :: Caveat -> Maybe Verified , helpText :: String} | ||
52 | |||
53 | instance Eq CaveatVerifier where | ||
54 | (==) = (==) `on` helpText | ||
55 | |||
56 | instance Show CaveatVerifier where | ||
57 | show = helpText | ||
58 | |||
59 | (<???>) :: (Caveat -> Maybe Verified) -> String -> CaveatVerifier | ||
60 | f <???> t = CV f t | ||
61 | |||
62 | verifySig :: Key -> Macaroon -> Verified | ||
63 | verifySig k m = bool Failed Ok $ | ||
31 | signature m == foldl' hash (toBytes (hmac derivedKey (identifier m) :: HMAC SHA256)) (caveats m) | 64 | signature m == foldl' hash (toBytes (hmac derivedKey (identifier m) :: HMAC SHA256)) (caveats m) |
32 | where | 65 | where |
33 | hash s c = toBytes (hmac s (vid c `BS.append` cid c) :: HMAC SHA256) | 66 | hash s c = toBytes (hmac s (vid c `BS.append` cid c) :: HMAC SHA256) |
34 | derivedKey = toBytes (hmac "macaroons-key-generator" k :: HMAC SHA256) | 67 | derivedKey = toBytes (hmac "macaroons-key-generator" k :: HMAC SHA256) |
68 | |||
69 | verifyMacaroon :: Key -> [CaveatVerifier] -> Macaroon -> Verified | ||
70 | verifyMacaroon secret verifiers m = verifySig secret m `mappend` verifyCavs verifiers m | ||
71 | |||
72 | |||
73 | verifyCavs :: [CaveatVerifier] -> Macaroon -> Verified | ||
74 | verifyCavs verifiers m = foldMap (\c -> fromMaybe Failed $ foldMap (($ c) . vFun) verifiers) (caveats m) | ||
75 | |||
76 | verifyExact :: (Eq a) => Key -> a -> Parser a -> Caveat -> Maybe Verified | ||
77 | verifyExact k expected = verifyFun k (expected ==) | ||
78 | |||
79 | verifyFun :: Key -> (a -> Bool) -> Parser a -> Caveat -> Maybe Verified | ||
80 | verifyFun key f parser cav = if key `BS.isPrefixOf` cid cav then | ||
81 | case parseOnly kvparser (cid cav) of | ||
82 | Right v -> (bool Failed Ok . f) <$> Just v | ||
83 | Left _ -> Just Failed | ||
84 | else Nothing | ||
85 | where | ||
86 | kvparser = do | ||
87 | key <- string key | ||
88 | skipSpace | ||
89 | string "=" | ||
90 | skipSpace | ||
91 | parser <* endOfInput | ||
diff --git a/test/Crypto/Macaroon/Instances.hs b/test/Crypto/Macaroon/Instances.hs index 4e2f39f..c82bbd3 100644 --- a/test/Crypto/Macaroon/Instances.hs +++ b/test/Crypto/Macaroon/Instances.hs | |||
@@ -26,9 +26,16 @@ import Crypto.Macaroon | |||
26 | 26 | ||
27 | -- | Adjust the size parameter, by transforming it with the given | 27 | -- | Adjust the size parameter, by transforming it with the given |
28 | -- function. | 28 | -- function. |
29 | -- Copied over from QuickCheck 2.8 | ||
29 | scale :: (Int -> Int) -> Gen a -> Gen a | 30 | scale :: (Int -> Int) -> Gen a -> Gen a |
30 | scale f g = sized (\n -> resize (f n) g) | 31 | scale f g = sized (\n -> resize (f n) g) |
31 | 32 | ||
33 | |||
34 | -- | Generates a random subsequence of the given list. | ||
35 | -- Copied over from QuickCheck 2.8 | ||
36 | sublistOf :: [a] -> Gen [a] | ||
37 | sublistOf = filterM (\_ -> choose (False, True)) | ||
38 | |||
32 | newtype Url = Url { unUrl :: BS.ByteString } deriving (Show) | 39 | newtype Url = Url { unUrl :: BS.ByteString } deriving (Show) |
33 | 40 | ||
34 | instance Arbitrary Url where | 41 | instance Arbitrary Url where |
@@ -48,6 +55,16 @@ newtype Identifier = Identifier { unIdent :: BS.ByteString } deriving (Show) | |||
48 | instance Arbitrary Identifier where | 55 | instance Arbitrary Identifier where |
49 | arbitrary = Identifier . B8.pack <$>(scale (*3) . listOf1 . elements $ ['a'..'z']) | 56 | arbitrary = Identifier . B8.pack <$>(scale (*3) . listOf1 . elements $ ['a'..'z']) |
50 | 57 | ||
58 | newtype EquationLike = EquationLike { unEqlike :: BS.ByteString } deriving (Show) | ||
59 | |||
60 | instance Arbitrary EquationLike where | ||
61 | arbitrary = do | ||
62 | keylen <- choose (3,8) | ||
63 | key <- B8.pack <$> vectorOf keylen (elements ['a'..'z']) | ||
64 | val <- B8.pack <$> (scale (*3) . listOf1 . elements $ ['a'..'z']) | ||
65 | return $ EquationLike (BS.concat [ key, " = ", val]) | ||
66 | |||
67 | |||
51 | data SimpleMac = SimpleMac { secret :: BS.ByteString, macaroon :: Macaroon } deriving Show | 68 | data SimpleMac = SimpleMac { secret :: BS.ByteString, macaroon :: Macaroon } deriving Show |
52 | 69 | ||
53 | instance Arbitrary SimpleMac where | 70 | instance Arbitrary SimpleMac where |
@@ -55,6 +72,8 @@ instance Arbitrary SimpleMac where | |||
55 | secret <- unSecret <$> arbitrary | 72 | secret <- unSecret <$> arbitrary |
56 | location <- unUrl <$> arbitrary | 73 | location <- unUrl <$> arbitrary |
57 | ident <- unIdent <$> arbitrary | 74 | ident <- unIdent <$> arbitrary |
58 | return $ SimpleMac secret (create secret ident location) | 75 | fpcavs <- listOf arbitrary |
76 | let mac = foldl (flip addFirstPartyCaveat) (create secret ident location) (map unEqlike fpcavs) | ||
77 | return $ SimpleMac secret mac | ||
59 | 78 | ||
60 | 79 | ||
diff --git a/test/Crypto/Macaroon/Serializer/Base64/Tests.hs b/test/Crypto/Macaroon/Serializer/Base64/Tests.hs index 19084af..ea3bed9 100644 --- a/test/Crypto/Macaroon/Serializer/Base64/Tests.hs +++ b/test/Crypto/Macaroon/Serializer/Base64/Tests.hs | |||
@@ -30,7 +30,7 @@ tests = testGroup "Crypto.Macaroon.Serializer.Base64" [ basic | |||
30 | ] | 30 | ] |
31 | 31 | ||
32 | basicQC = testProperty "Reversibility" $ | 32 | basicQC = testProperty "Reversibility" $ |
33 | forAll (macaroon <$> arbitrary) (\m -> deserialize (serialize m) == Right m) | 33 | \sm -> deserialize (serialize (macaroon sm)) == Right (macaroon sm) |
34 | 34 | ||
35 | m :: Macaroon | 35 | m :: Macaroon |
36 | m = create secret key loc | 36 | m = create secret key loc |
diff --git a/test/Crypto/Macaroon/Verifier/Tests.hs b/test/Crypto/Macaroon/Verifier/Tests.hs index 92a8a21..101fa26 100644 --- a/test/Crypto/Macaroon/Verifier/Tests.hs +++ b/test/Crypto/Macaroon/Verifier/Tests.hs | |||
@@ -12,9 +12,11 @@ This test suite is based on the pymacaroons test suite: | |||
12 | module Crypto.Macaroon.Verifier.Tests where | 12 | module Crypto.Macaroon.Verifier.Tests where |
13 | 13 | ||
14 | 14 | ||
15 | import Data.List | ||
15 | import qualified Data.ByteString.Char8 as B8 | 16 | import qualified Data.ByteString.Char8 as B8 |
16 | import Test.Tasty | 17 | import Test.Tasty |
17 | import Test.Tasty.HUnit | 18 | -- import Test.Tasty.HUnit |
19 | import Test.Tasty.QuickCheck | ||
18 | 20 | ||
19 | import Crypto.Macaroon | 21 | import Crypto.Macaroon |
20 | import Crypto.Macaroon.Verifier | 22 | import Crypto.Macaroon.Verifier |
@@ -23,8 +25,12 @@ import Crypto.Macaroon.Instances | |||
23 | 25 | ||
24 | tests :: TestTree | 26 | tests :: TestTree |
25 | tests = testGroup "Crypto.Macaroon.Verifier" [ sigs | 27 | tests = testGroup "Crypto.Macaroon.Verifier" [ sigs |
28 | , firstParty | ||
26 | ] | 29 | ] |
27 | 30 | ||
31 | {- | ||
32 | - Test fixtures | ||
33 | -} | ||
28 | sec = B8.pack "this is our super secret key; only we should know it" | 34 | sec = B8.pack "this is our super secret key; only we should know it" |
29 | 35 | ||
30 | m :: Macaroon | 36 | m :: Macaroon |
@@ -37,23 +43,54 @@ m2 :: Macaroon | |||
37 | m2 = addFirstPartyCaveat "test = caveat" m | 43 | m2 = addFirstPartyCaveat "test = caveat" m |
38 | 44 | ||
39 | m3 :: Macaroon | 45 | m3 :: Macaroon |
40 | m3 = addFirstPartyCaveat "test = acaveat" m | 46 | m3 = addFirstPartyCaveat "value = 42" m2 |
41 | 47 | ||
42 | sigs = testGroup "Signatures" [ basic | 48 | exTC = verifyExact "test" "caveat" (many' letter_ascii) <???> "test = caveat" |
43 | , minted | 49 | exTZ = verifyExact "test" "bleh" (many' letter_ascii) <???> "test = bleh" |
44 | ] | 50 | exV42 = verifyExact "value" 42 decimal <???> "value = 42" |
45 | 51 | exV43 = verifyExact "value" 43 decimal <???> "value = 43" | |
46 | basic = testCase "Basic Macaroon Signature" $ | 52 | |
47 | Success @=? verifySig sec m | 53 | funTCPre = verifyFun "test" ("cav" `isPrefixOf`) (many' letter_ascii) <???> "test startsWith cav" |
48 | 54 | funTV43lte = verifyFun "value" (<= 43) decimal <???> "value <= 43" | |
49 | 55 | ||
50 | minted :: TestTree | 56 | allvs = [exTC, exTZ, exV42, exV43, funTCPre, funTV43lte] |
51 | minted = testGroup "Macaroon with first party caveats" [ one | 57 | |
52 | , two | 58 | {- |
53 | ] | 59 | - Tests |
54 | one = testCase "One caveat" $ | 60 | -} |
55 | Success @=? verifySig sec m2 | 61 | sigs = testProperty "Signatures" $ \sm -> verifySig (secret sm) (macaroon sm) == Ok |
56 | 62 | ||
57 | two = testCase "Two caveats" $ | 63 | firstParty = testGroup "First party caveats" [ |
58 | Success @=? verifySig sec m3 | 64 | testGroup "Pure verifiers" [ |
59 | 65 | testProperty "Zero caveat" $ | |
66 | forAll (sublistOf allvs) (\vs -> Ok == verifyCavs vs m) | ||
67 | , testProperty "One caveat" $ | ||
68 | forAll (sublistOf allvs) (\vs -> disjoin [ | ||
69 | Ok == verifyCavs vs m2 .&&. any (`elem` vs) [exTC,funTCPre] .&&. (exTZ `notElem` vs) | ||
70 | , Failed === verifyCavs vs m2 | ||
71 | ]) | ||
72 | , testProperty "Two Exact" $ | ||
73 | forAll (sublistOf allvs) (\vs -> disjoin [ | ||
74 | Ok == verifyCavs vs m3 .&&. | ||
75 | any (`elem` vs) [exTC,funTCPre] .&&. (exTZ `notElem` vs) .&&. | ||
76 | any (`elem` vs) [exV42,funTV43lte] .&&. (exV43 `notElem` vs) | ||
77 | , Failed === verifyCavs vs m3 | ||
78 | ]) | ||
79 | ] | ||
80 | , testGroup "Pure verifiers with sig" [ | ||
81 | testProperty "Zero caveat" $ | ||
82 | forAll (sublistOf allvs) (\vs -> Ok == verifyMacaroon sec vs m) | ||
83 | , testProperty "One caveat" $ | ||
84 | forAll (sublistOf allvs) (\vs -> disjoin [ | ||
85 | Ok == verifyMacaroon sec vs m2 .&&. any (`elem` vs) [exTC,funTCPre] .&&. (exTZ `notElem` vs) | ||
86 | , Failed === verifyMacaroon sec vs m2 | ||
87 | ]) | ||
88 | , testProperty "Two Exact" $ | ||
89 | forAll (sublistOf allvs) (\vs -> disjoin [ | ||
90 | Ok == verifyMacaroon sec vs m3 .&&. | ||
91 | any (`elem` vs) [exTC,funTCPre] .&&. (exTZ `notElem` vs) .&&. | ||
92 | any (`elem` vs) [exV42,funTV43lte] .&&. (exV43 `notElem` vs) | ||
93 | , Failed === verifyMacaroon sec vs m3 | ||
94 | ]) | ||
95 | ] | ||
96 | ] | ||