]> git.immae.eu Git - github/fretlink/hmacaroons.git/blame - test/Crypto/Macaroon/Instances.hs
Change verifier api and split Verifier module
[github/fretlink/hmacaroons.git] / test / Crypto / Macaroon / Instances.hs
CommitLineData
a22bcdb6
JT
1{-# LANGUAGE OverloadedStrings #-}
2{-|
3Copyright : (c) 2015 Julien Tanguy
4License : BSD3
5
6Maintainer : julien.tanguy@jhome.fr
7
8
9This test suite is based on the pymacaroons test suite:
10<https://github.com/ecordell/pymacaroons>
11-}
12module Crypto.Macaroon.Instances where
13
bf31e290 14import Control.Monad
a22bcdb6 15import Data.Byteable
bf31e290 16import qualified Data.ByteString as BS
a22bcdb6
JT
17import qualified Data.ByteString.Char8 as B8
18import Data.Hex
19import Data.List
20import Test.Tasty
21import Test.Tasty.HUnit
22import Test.Tasty.QuickCheck
23
24import Crypto.Macaroon
25
26newtype Url = Url { unUrl :: BS.ByteString } deriving (Show)
27
28instance Arbitrary Url where
29 arbitrary = do
30 protocol <- elements ["http://"]
31 name <- fmap (intercalate ".") <$> listOf1 . listOf1 $ elements ['a'..'z']
32 domain <- elements [".com",".net"]
33 return . Url . B8.pack $ (protocol ++ name ++ domain)
34
86f38823 35newtype BSSecret = BSSecret { unSecret :: BS.ByteString } deriving (Show)
a22bcdb6 36
86f38823
JT
37instance Arbitrary BSSecret where
38 arbitrary = BSSecret . B8.pack <$> scale (*3) arbitrary
a22bcdb6
JT
39
40newtype Identifier = Identifier { unIdent :: BS.ByteString } deriving (Show)
41
42instance Arbitrary Identifier where
43 arbitrary = Identifier . B8.pack <$>(scale (*3) . listOf1 . elements $ ['a'..'z'])
44
2ba8d1c3
JT
45newtype EquationLike = EquationLike { unEqlike :: BS.ByteString } deriving (Show)
46
47instance Arbitrary EquationLike where
48 arbitrary = do
49 keylen <- choose (3,8)
50 key <- B8.pack <$> vectorOf keylen (elements ['a'..'z'])
51 val <- B8.pack <$> (scale (*3) . listOf1 . elements $ ['a'..'z'])
52 return $ EquationLike (BS.concat [ key, " = ", val])
53
54
a22bcdb6
JT
55data SimpleMac = SimpleMac { secret :: BS.ByteString, macaroon :: Macaroon } deriving Show
56
57instance Arbitrary SimpleMac where
58 arbitrary = do
59 secret <- unSecret <$> arbitrary
60 location <- unUrl <$> arbitrary
61 ident <- unIdent <$> arbitrary
2ba8d1c3
JT
62 fpcavs <- listOf arbitrary
63 let mac = foldl (flip addFirstPartyCaveat) (create secret ident location) (map unEqlike fpcavs)
64 return $ SimpleMac secret mac
a22bcdb6
JT
65
66