version: 0.2.0.0
synopsis: Haskell implementation of macaroons
description:
- = Macaroons: Pure haskell implementation of macaroons
- #macaroons-pure-haskell-implementation-of-macaroons#
- .
- Macaroons is a pure haskell implementation of macaroons. It aims to
+ Hmacaroons is a pure haskell implementation of macaroons. It aims to
provide compatibility at a serialized level with the
<https://github.com/rescrv/libmacaroons reference implementation> and
the <https://github.com/ecordell/pymacaroons python implementation>
.
__WARNING: This library has not been audited by security experts.__
- __There is no error handling at the moment, everyhting is silently accepted__
+ __There is no error handling at the moment, everything is silently accepted__
.
It is developed in the purpose of exploration purposes, and would need
much more attention if it were to be used in production.
(ValidatorError e) `mappend` (ParseError _) = ValidatorError e
(ParseError _) `mappend` (ValidatorError e) = ValidatorError e
-
+-- | Check that the given macaroon has a correct signature
verifySig :: Key -> Macaroon -> Either ValidationError Macaroon
verifySig k m = bool (Left SigMismatch) (Right m) $
signature m == foldl' hash (toBytes (hmac derivedKey (identifier m) :: HMAC SHA256)) (caveats m)
-{-#LANGUAGE OverloadedStrings#-}
+{-# LANGUAGE OverloadedStrings #-}
module Sanity where
import Crypto.Hash
-import Data.ByteString (ByteString)
-import qualified Data.ByteString as B
-import Data.Hex
-import Data.Byteable
+import Data.Byteable
+import Data.ByteString (ByteString)
+import qualified Data.ByteString as B
+import Data.Hex
-import Test.Tasty
-import Test.Tasty.HUnit
+import Test.Tasty
+import Test.Tasty.HUnit
-import qualified Crypto.Macaroon.Tests
import qualified Crypto.Macaroon.Serializer.Base64.Tests
+import qualified Crypto.Macaroon.Tests
tests :: TestTree
tests = testGroup "Python HMAC Sanity check" [ checkKey
mac4 = toBytes (hmac mac3 "email = alice@example.org" :: HMAC SHA256)
-checkKey = testCase "Truncated key" $
+checkKey = testCase "Truncated key" $
key @?= "this is our super secret key; on"
-checkMac1 = testCase "HMAC key" $
+checkMac1 = testCase "HMAC key" $
"C60B4B3540BB1B2F2EF28D1C895691CC4A5E07A38A9D3B1C3379FB485293372F" @=? hex mac1
-checkMac2 = testCase "HMAC key account" $
+checkMac2 = testCase "HMAC key account" $
"5C933DC9A7D036DFCD1740B4F26D737397A1FF635EAC900F3226973503CAAAA5" @=? hex mac2
-checkMac3 = testCase "HMAC key account time" $
+checkMac3 = testCase "HMAC key account time" $
"7A559B20C8B607009EBCE138C200585E9D0DECA6D23B3EAD6C5E0BA6861D3858" @=? hex mac3
-checkMac4 = testCase "HMAC key account time email" $
+checkMac4 = testCase "HMAC key account time email" $
"E42BBB02A9A5A303483CB6295C497AE51AD1D5CB10003CBE548D907E7E62F5E4" @=? hex mac4