location: https://github.com/jtanguy/hmacaroons
library
- exposed-modules: Crypto.Macaroon,
+ exposed-modules: Crypto.Macaroon
Crypto.Macaroon.Binder
Crypto.Macaroon.Serializer.Base64
+ Crypto.Macaroon.Verifier
other-modules: Crypto.Macaroon.Internal
build-depends: base >=4 && < 5,
attoparsec >=0.12,
--- /dev/null
+{-# LANGUAGE OverloadedStrings #-}
+{-|
+Module : Crypto.Macaroon.Verifier
+Copyright : (c) 2015 Julien Tanguy
+License : BSD3
+
+Maintainer : julien.tanguy@jhome.fr
+Stability : experimental
+Portability : portable
+
+
+
+-}
+module Crypto.Macaroon.Verifier where
+
+
+import Crypto.Hash
+import Data.Bool
+import qualified Data.ByteString as BS
+import Data.Byteable
+import Data.Foldable
+
+import Crypto.Macaroon.Internal
+
+
+-- | Opaque datatype for now. Might need more explicit errors
+data Result = Success | Failure deriving (Show,Eq)
+
+verifySig :: Key -> Macaroon -> Result
+verifySig k m = bool Failure Success $
+ signature m == foldl' hash (toBytes (hmac derivedKey (identifier m) :: HMAC SHA256)) (caveats m)
+ where
+ hash s c = toBytes (hmac s (vid c `BS.append` cid c) :: HMAC SHA256)
+ derivedKey = toBytes (hmac "macaroons-key-generator" k :: HMAC SHA256)
--- /dev/null
+{-# LANGUAGE OverloadedStrings #-}
+{-|
+Copyright : (c) 2015 Julien Tanguy
+License : BSD3
+
+Maintainer : julien.tanguy@jhome.fr
+
+
+This test suite is based on the pymacaroons test suite:
+<https://github.com/ecordell/pymacaroons>
+-}
+module Crypto.Macaroon.Verifier.Tests where
+
+
+import qualified Data.ByteString.Char8 as B8
+import Test.Tasty
+import Test.Tasty.HUnit
+
+import Crypto.Macaroon
+import Crypto.Macaroon.Verifier
+
+import Crypto.Macaroon.Instances
+
+tests :: TestTree
+tests = testGroup "Crypto.Macaroon.Verifier" [ sigs
+ ]
+
+sec = B8.pack "this is our super secret key; only we should know it"
+
+m :: Macaroon
+m = create sec key loc
+ where
+ key = B8.pack "we used our sec key"
+ loc = B8.pack "http://mybank/"
+
+m2 :: Macaroon
+m2 = addFirstPartyCaveat "test = caveat" m
+
+m3 :: Macaroon
+m3 = addFirstPartyCaveat "test = acaveat" m
+
+sigs = testGroup "Signatures" [ basic
+ , minted
+ ]
+
+basic = testCase "Basic Macaroon Signature" $
+ Success @=? verifySig sec m
+
+
+minted :: TestTree
+minted = testGroup "Macaroon with first party caveats" [ one
+ , two
+ ]
+one = testCase "One caveat" $
+ Success @=? verifySig sec m2
+
+two = testCase "Two caveats" $
+ Success @=? verifySig sec m3
+
import qualified Sanity
import qualified Crypto.Macaroon.Tests
import qualified Crypto.Macaroon.Serializer.Base64.Tests
+import qualified Crypto.Macaroon.Verifier.Tests
main = defaultMain tests
tests = testGroup "Tests" [ Sanity.tests
, Crypto.Macaroon.Tests.tests
, Crypto.Macaroon.Serializer.Base64.Tests.tests
+ , Crypto.Macaroon.Verifier.Tests.tests
]