aboutsummaryrefslogtreecommitdiffhomepage
path: root/src/Crypto
diff options
context:
space:
mode:
authorJulien Tanguy <julien.tanguy@jhome.fr>2015-04-09 01:12:36 +0200
committerJulien Tanguy <julien.tanguy@jhome.fr>2015-04-09 01:12:36 +0200
commitf678145637ba6f42c36d07c19f8c764e5d537f72 (patch)
tree3e8578900501968de7404131a89e8e063dd0f12e /src/Crypto
downloadhmacaroons-f678145637ba6f42c36d07c19f8c764e5d537f72.tar.gz
hmacaroons-f678145637ba6f42c36d07c19f8c764e5d537f72.tar.zst
hmacaroons-f678145637ba6f42c36d07c19f8c764e5d537f72.zip
Initial commit
Diffstat (limited to 'src/Crypto')
-rw-r--r--src/Crypto/Macaroon.hs121
-rw-r--r--src/Crypto/Macaroon/Binder.hs28
-rw-r--r--src/Crypto/Macaroon/Internal.hs88
3 files changed, 237 insertions, 0 deletions
diff --git a/src/Crypto/Macaroon.hs b/src/Crypto/Macaroon.hs
new file mode 100644
index 0000000..819a9eb
--- /dev/null
+++ b/src/Crypto/Macaroon.hs
@@ -0,0 +1,121 @@
1{-# LANGUAGE OverloadedStrings #-}
2{-|
3Module : Crypto.Macaroon
4Copyright : (c) 2015 Julien Tanguy
5License : BSD3
6
7Maintainer : julien.tanguy@jhome.fr
8Stability : experimental
9Portability : portable
10
11
12Pure haskell implementations of macaroons.
13
14Warning: this implementation has not been audited by security experts.
15Use it with caution.
16
17
18References:
19
20- Macaroons: Cookies with Contextual Caveats for Decentralized Authorization in the Cloud <http://research.google.com/pubs/pub41892.html>
21- Time for better security in NoSQL <http://hackingdistributed.com/2014/11/23/macaroons-in-hyperdex>
22
23-}
24module Crypto.Macaroon (
25 -- * Types
26 Macaroon
27 , Caveat
28 , Key
29 , Location
30 -- * Accessing functions
31 -- ** Macaroons
32 , location
33 , identifier
34 , caveats
35 , signature
36 -- ** Caveats
37 , caveatLoc
38 , caveatId
39 , caveatVId
40
41 -- * Create Macaroons
42 , create
43 , inspect
44 , addFirstPartyCaveat
45 , addThirdPartyCaveat
46
47 -- * Prepare Macaroons for transfer
48 , serialize
49 ) where
50
51import Crypto.Cipher.AES
52import Crypto.Hash
53import Data.Byteable
54import qualified Data.ByteString as BS
55import qualified Data.ByteString.Base64.URL as B64
56import qualified Data.ByteString.Char8 as B8
57import Data.Hex
58
59import Crypto.Macaroon.Internal
60
61-- | Create a Macaroon from its key, identifier and location
62create :: Key -> Key -> Location -> Macaroon
63create secret ident loc = MkMacaroon loc ident [] (toBytes (hmac derivedKey ident :: HMAC SHA256))
64 where
65 derivedKey = toBytes $ (hmac "macaroons-key-generator" secret :: HMAC SHA256)
66
67caveatLoc :: Caveat -> Location
68caveatLoc = cl
69
70caveatId :: Caveat -> Key
71caveatId = cid
72
73caveatVId :: Caveat -> Key
74caveatVId = vid
75
76inspect :: Macaroon -> String
77inspect m = unlines [ "location " ++ show (location m)
78 , "identifier " ++ show (identifier m)
79 , (concatMap (showCav (location m)) (caveats m))
80 , "signature " ++ show (hex $ signature m)
81 ]
82 where
83 showCav loc c | cl c == loc && vid c == BS.empty = "cid " ++ show (cid c)
84 | otherwise = unlines [ "cid " ++ show (cid c)
85 , "vid " ++ show (vid c)
86 , "cl " ++ show (cl c)
87 ]
88
89serialize :: Macaroon -> BS.ByteString
90serialize m = B8.filter (/= '=') . B64.encode $ packets
91 where
92 packets = BS.concat [ putPacket "location" (location m)
93 , putPacket "identifier" (identifier m)
94 , caveatPackets
95 , putPacket "signature" (signature m)
96 ]
97 caveatPackets = BS.concat $ map (cavPacket (location m)) (caveats m)
98 cavPacket loc c | cl c == loc && vid c == BS.empty = putPacket "cid" (cid c)
99 | otherwise = BS.concat [ putPacket "cid" (cid c)
100 , putPacket "vid" (vid c)
101 , putPacket "cl" (cl c)
102 ]
103
104
105
106-- | Add a first party Caveat to a Macaroon, with its identifier
107addFirstPartyCaveat :: Key -> Macaroon -> Macaroon
108addFirstPartyCaveat ident m = addCaveat (location m) ident BS.empty m
109
110-- |Add a third party Caveat to a Macaroon, using its location, identifier and
111-- verification key
112addThirdPartyCaveat :: Key
113 -> Key
114 -> Location
115 -> Macaroon
116 -> Macaroon
117addThirdPartyCaveat key cid loc m = addCaveat loc cid vid m
118 where
119 vid = encryptECB (initAES (signature m)) key
120
121
diff --git a/src/Crypto/Macaroon/Binder.hs b/src/Crypto/Macaroon/Binder.hs
new file mode 100644
index 0000000..3ec3d67
--- /dev/null
+++ b/src/Crypto/Macaroon/Binder.hs
@@ -0,0 +1,28 @@
1{-|
2Module : Crypto.Macaroon.Binder
3Copyright : (c) 2015 Julien Tanguy
4License : BSD3
5
6Maintainer : julien.tanguy@jhome.fr
7Stability : experimental
8Portability : portable
9
10
11
12-}
13module Crypto.Macaroon.Binder where
14
15import Crypto.Hash
16import Data.Byteable
17import qualified Data.ByteString as BS
18
19import Crypto.Macaroon.Internal
20
21-- | Datatype for binding discharging and authorizing macaroons together
22newtype Binder = Binder { bind :: Macaroon -> Macaroon -> BS.ByteString }
23
24
25-- | Binder which concatenates the two signatures and hashes them
26hashSigs :: Binder
27hashSigs = Binder $ \m m' -> toBytes $ (HMAC . hash $ BS.append (toBytes $ signature m') (toBytes $ signature m) :: HMAC SHA256)
28
diff --git a/src/Crypto/Macaroon/Internal.hs b/src/Crypto/Macaroon/Internal.hs
new file mode 100644
index 0000000..fc50486
--- /dev/null
+++ b/src/Crypto/Macaroon/Internal.hs
@@ -0,0 +1,88 @@
1{-# LANGUAGE OverloadedStrings #-}
2{-|
3Module : Crypto.Macaroon.Internal
4Copyright : (c) 2015 Julien Tanguy
5License : BSD3
6
7Maintainer : julien.tanguy@jhome.fr
8Stability : experimental
9Portability : portable
10
11
12Internal representation of a macaroon
13-}
14module Crypto.Macaroon.Internal where
15
16
17import Control.DeepSeq
18import Crypto.Cipher.AES
19import Crypto.Hash
20import Data.Byteable
21import qualified Data.ByteString as BS
22import qualified Data.ByteString.Base64 as B64
23import qualified Data.ByteString.Char8 as B8
24import Data.Char
25import Data.Hex
26import Data.Serialize
27import Data.Word
28
29-- |Type alias for Macaroons and Caveat keys and identifiers
30type Key = BS.ByteString
31
32-- |Type alias For Macaroons and Caveat locations
33type Location = BS.ByteString
34
35type Sig = BS.ByteString
36
37-- | Main structure of a macaroon
38data Macaroon = MkMacaroon { location :: Location
39 -- ^ Target location
40 , identifier :: Key
41 -- ^ Macaroon Identifier
42 , caveats :: [Caveat]
43 -- ^ List of caveats
44 , signature :: Sig
45 -- ^ Macaroon HMAC signature
46 } deriving (Eq)
47
48
49instance NFData Macaroon where
50 rnf (MkMacaroon loc ident cavs sig) = rnf loc `seq` rnf ident `seq` rnf cavs `seq` rnf sig
51
52
53-- | Caveat structure
54data Caveat = MkCaveat { cid :: Key
55 -- ^ Caveat identifier
56 , vid :: Key
57 -- ^ Caveat verification key identifier
58 , cl :: Location
59 -- ^ Caveat target location
60
61 } deriving (Eq)
62
63instance NFData Caveat where
64 rnf (MkCaveat cid vid cl) = rnf cid `seq` rnf vid `seq` rnf cl
65
66
67putPacket :: BS.ByteString -> BS.ByteString -> BS.ByteString
68putPacket key dat = BS.concat [
69 B8.map toLower . hex . encode $ (fromIntegral size :: Word16)
70 , key
71 , " "
72 , dat
73 , "\n"
74 ]
75 where
76 size = 4 + 2 + BS.length key + BS.length dat
77
78addCaveat :: Location
79 -> Key
80 -> Key
81 -> Macaroon
82 -> Macaroon
83addCaveat loc cid vid m = m { caveats = cavs ++ [cav'], signature = sig}
84 where
85 cavs = caveats m
86 cav' = MkCaveat cid vid loc
87 sig = toBytes $ (hmac (signature m) (BS.append vid cid) :: HMAC SHA256)
88