]> git.immae.eu Git - github/fretlink/hmacaroons.git/commitdiff
Refactor tests
authorJulien Tanguy <julien.tanguy@jhome.fr>
Tue, 14 Apr 2015 16:18:26 +0000 (18:18 +0200)
committerJulien Tanguy <julien.tanguy@jhome.fr>
Tue, 14 Apr 2015 16:18:26 +0000 (18:18 +0200)
src/Crypto/Macaroon/Serializer/Base64.hs
test/Crypto/Macaroon/Serializer/Base64/Tests.hs [new file with mode: 0644]
test/Crypto/Macaroon/Tests.hs
test/tests.hs

index 6fc8fcba4681d52fd7987ac23442e24f76cc9df8..f6527c2e6432aa008d1a425c288c217c25cc9972 100644 (file)
@@ -16,22 +16,22 @@ module Crypto.Macaroon.Serializer.Base64 (
       , deserialize
       ) where
 
-import Control.Applicative
-import Control.Monad
-import qualified Data.ByteString            as BS
-import qualified Data.ByteString.Base64.URL as B64
-import qualified Data.ByteString.Char8      as B8
-import Data.Attoparsec.ByteString
+import           Control.Applicative
+import           Control.Monad
+import           Crypto.Macaroon.Internal
+import           Data.Attoparsec.ByteString
 import qualified Data.Attoparsec.ByteString.Char8 as A8
 import           Data.Bits
+import qualified Data.ByteString                  as BS
+import qualified Data.ByteString.Base64.URL       as B64
+import qualified Data.ByteString.Char8            as B8
 import           Data.Char
 import           Data.Hex
 import           Data.Int
 import           Data.List
 import           Data.Maybe
-import           Data.Word
 import           Data.Serialize
-import Crypto.Macaroon.Internal
+import           Data.Word
 
 
 -- | Serialize a macaroon in an URL-safe Base64 encoding
diff --git a/test/Crypto/Macaroon/Serializer/Base64/Tests.hs b/test/Crypto/Macaroon/Serializer/Base64/Tests.hs
new file mode 100644 (file)
index 0000000..9c49e96
--- /dev/null
@@ -0,0 +1,83 @@
+{-# 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.Serializer.Base64.Tests where
+
+
+import qualified Data.ByteString.Char8 as B8
+import Test.Tasty
+import Test.Tasty.HUnit
+
+import           Crypto.Macaroon
+import           Crypto.Macaroon.Serializer.Base64
+
+tests :: TestTree
+tests = testGroup "Crypto.Macaroon.Serializer.Base64" [ basic
+                                                      , minted
+                                                      , minted2
+                                                      -- , minted3
+                                                      ]
+
+
+m :: Macaroon
+m = create secret key loc
+  where
+    secret = B8.pack "this is our super secret key; only we should know it"
+    key = B8.pack "we used our secret key"
+    loc = B8.pack "http://mybank/"
+
+basic :: TestTree
+basic = testGroup "Basic macaroon" [ basicSerialize
+                                   , basicDeserialize
+                                   ]
+
+basicSerialize = testCase "Serialization" $
+    "MDAxY2xvY2F0aW9uIGh0dHA6Ly9teWJhbmsvCjAwMjZpZGVudG\
+    \lmaWVyIHdlIHVzZWQgb3VyIHNlY3JldCBrZXkKMDAyZnNpZ25h\
+    \dHVyZSDj2eApCFJsTAA5rhURQRXZf91ovyujebNCqvD2F9BVLwo" @=? serialize m
+
+basicDeserialize = testCase "Deserialization" $
+    Right m @=? (deserialize . serialize) m
+
+m2 :: Macaroon
+m2 = addFirstPartyCaveat "test = caveat" m
+
+minted :: TestTree
+minted = testGroup "Macaroon with first party caveat" [ mintSerialize
+                                                      , mintDeserialize
+                                                      ]
+
+
+mintSerialize = testCase "Serialization" $
+    "MDAxY2xvY2F0aW9uIGh0dHA6Ly9teWJhbmsvCjAwMjZpZGVudGlmaWVyIHdlIHVzZ\
+    \WQgb3VyIHNlY3JldCBrZXkKMDAxNmNpZCB0ZXN0ID0gY2F2ZWF0CjAwMmZzaWduYXR1cmUgGXusegR\
+    \K8zMyhluSZuJtSTvdZopmDkTYjOGpmMI9vWcK" @=? serialize m2
+
+mintDeserialize = testCase "Deserialization" $
+    Right m2 @=? (deserialize . serialize) m2
+
+
+m3 :: Macaroon
+m3 = addFirstPartyCaveat "test = acaveat" m
+
+minted2 :: TestTree
+minted2 = testGroup "Macaroon with first party caveats" [ mint2Trimmed
+                                                        , mint2Des
+                                                        ]
+
+mint2Trimmed = testCase "Serialization" $
+    "MDAxY2xvY2F0aW9uIGh0dHA6Ly9teWJhbmsvCjAwMjZpZGVudGlmaWVyIHdlIHVz\
+    \ZWQgb3VyIHNlY3JldCBrZXkKMDAxN2NpZCB0ZXN0ID0gYWNhdmVhdAowMDJmc2ln\
+    \bmF0dXJlIJRJ_V3WNJQnqlVq5eez7spnltwU_AXs8NIRY739sHooCg" @=? serialize m3
+
+mint2Des = testCase "Deserialization" $
+    Right m3 @=? (deserialize . serialize) m3
+
index 244ec50418f9b7fb751eec139cd0d50ab3a83760..25d77c88cf8b7736dff37e7aea086a5bcc3d3cac 100644 (file)
@@ -23,8 +23,6 @@ import           Crypto.Macaroon.Serializer.Base64
 tests :: TestTree
 tests = testGroup "Crypto.Macaroon" [ basic
                                     , minted
-                                    , minted2
-                                    -- , minted3
                                     ]
 
 
@@ -36,29 +34,24 @@ m = create secret key loc
     loc = B8.pack "http://mybank/"
 
 basic :: TestTree
-basic = testGroup "Basic macaroon" [ basicSignature
-                                   , basicSerialize
-                                   , basicDeserialize
+basic = testGroup "Basic macaroon" [ basicInspect
+                                   , basicSignature
                                    ]
 
+basicInspect = testCase "Inspect" $
+    "location http://mybank/\nidentifier we used\
+    \ our secret key\n\nsignature E3D9E02908526C4C\
+    \0039AE15114115D97FDD68BF2BA379B342AAF0F617D0552F" @=? inspect m
+
 basicSignature = testCase "Signature" $
     "E3D9E02908526C4C0039AE15114115D97FDD68BF2BA379B342AAF0F617D0552F" @=? (hex . signature) m
 
-basicSerialize = testCase "Serialization" $
-    "MDAxY2xvY2F0aW9uIGh0dHA6Ly9teWJhbmsvCjAwMjZpZGVudG\
-    \lmaWVyIHdlIHVzZWQgb3VyIHNlY3JldCBrZXkKMDAyZnNpZ25h\
-    \dHVyZSDj2eApCFJsTAA5rhURQRXZf91ovyujebNCqvD2F9BVLwo" @=? serialize m
-
-basicDeserialize = testCase "Deserialization" $
-    Right m @=? (deserialize . serialize) m
-
 m2 :: Macaroon
 m2 = addFirstPartyCaveat "test = caveat" m
 
 minted :: TestTree
 minted = testGroup "Macaroon with first party caveat" [ mintInspect
-                                                      , mintSerialize
-                                                      , mintDeserialize
+                                                      , mintSignature
                                                       ]
 
 mintInspect = testCase "Inspect" $
@@ -68,30 +61,8 @@ mintInspect = testCase "Inspect" $
     \3BDD668A660E44D88CE1A998C23DBD67" @=? inspect m2
 
 
-mintSerialize = testCase "Serialization" $
-    "MDAxY2xvY2F0aW9uIGh0dHA6Ly9teWJhbmsvCjAwMjZpZGVudGlmaWVyIHdlIHVzZ\
-    \WQgb3VyIHNlY3JldCBrZXkKMDAxNmNpZCB0ZXN0ID0gY2F2ZWF0CjAwMmZzaWduYXR1cmUgGXusegR\
-    \K8zMyhluSZuJtSTvdZopmDkTYjOGpmMI9vWcK" @=? serialize m2
-
-mintDeserialize = testCase "Deserialization" $
-    Right m2 @=? (deserialize . serialize) m2
-
-
-m3 :: Macaroon
-m3 = addFirstPartyCaveat "test = acaveat" m
-
-minted2 :: TestTree
-minted2 = testGroup "Macaroon with first party caveats" [ mint2Trimmed
-                                                        , mint2Des
-                                                        ]
-
-mint2Trimmed = testCase "Serialization" $
-    "MDAxY2xvY2F0aW9uIGh0dHA6Ly9teWJhbmsvCjAwMjZpZGVudGlmaWVyIHdlIHVz\
-    \ZWQgb3VyIHNlY3JldCBrZXkKMDAxN2NpZCB0ZXN0ID0gYWNhdmVhdAowMDJmc2ln\
-    \bmF0dXJlIJRJ_V3WNJQnqlVq5eez7spnltwU_AXs8NIRY739sHooCg" @=? serialize m3
-
-mint2Des = testCase "Deserialization" $
-    Right m3 @=? (deserialize . serialize) m3
+mintSignature = testCase "Signature" $
+    "197BAC7A044AF33332865B9266E26D493BDD668A660E44D88CE1A998C23DBD67" @=? (hex . signature) m2
 
 -- m4 :: Macaroon
 -- m4 = addThirdPartyCaveat caveat_key caveat_id caveat_loc n
index ba5dafd7556ba3d3da448045bce3b2ba8a94a282..85564f08ee8e988a8ffd7623c646acb04665c495 100644 (file)
@@ -10,12 +10,14 @@ import Test.Tasty
 import Test.Tasty.HUnit
 
 import qualified Crypto.Macaroon.Tests
+import qualified Crypto.Macaroon.Serializer.Base64.Tests
 
 main = defaultMain tests
 
 tests :: TestTree
 tests = testGroup "Tests" [ sanityCheck
                           , Crypto.Macaroon.Tests.tests
+                          , Crypto.Macaroon.Serializer.Base64.Tests.tests
                           ]
 
 sanityCheck :: TestTree