]> git.immae.eu Git - github/fretlink/hmacaroons.git/blame - src/Crypto/Macaroon.hs
Documentation
[github/fretlink/hmacaroons.git] / src / Crypto / Macaroon.hs
CommitLineData
f6781456
JT
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
f6781456
JT
11Pure haskell implementations of macaroons.
12
13Warning: this implementation has not been audited by security experts.
2aede11a 14Do not use in production
f6781456
JT
15
16
17References:
18
19- Macaroons: Cookies with Contextual Caveats for Decentralized Authorization in the Cloud <http://research.google.com/pubs/pub41892.html>
20- Time for better security in NoSQL <http://hackingdistributed.com/2014/11/23/macaroons-in-hyperdex>
f6781456
JT
21-}
22module Crypto.Macaroon (
23 -- * Types
24 Macaroon
25 , Caveat
26 , Key
27 , Location
1971e224 28 , Sig
f6781456
JT
29 -- * Accessing functions
30 -- ** Macaroons
31 , location
32 , identifier
33 , caveats
34 , signature
35 -- ** Caveats
36 , caveatLoc
37 , caveatId
38 , caveatVId
39
40 -- * Create Macaroons
41 , create
42 , inspect
43 , addFirstPartyCaveat
44 , addThirdPartyCaveat
45
46 -- * Prepare Macaroons for transfer
47 , serialize
48 ) where
49
50import Crypto.Cipher.AES
51import Crypto.Hash
2aede11a 52import Data.Char
f6781456
JT
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
2aede11a
JT
58import Data.Word
59import Data.Serialize
f6781456
JT
60
61import Crypto.Macaroon.Internal
62
63-- | Create a Macaroon from its key, identifier and location
64create :: Key -> Key -> Location -> Macaroon
65create secret ident loc = MkMacaroon loc ident [] (toBytes (hmac derivedKey ident :: HMAC SHA256))
66 where
2aede11a 67 derivedKey = toBytes (hmac "macaroons-key-generator" secret :: HMAC SHA256)
f6781456 68
1971e224 69-- | Caveat target location
f6781456
JT
70caveatLoc :: Caveat -> Location
71caveatLoc = cl
72
1971e224 73-- | Caveat identifier
f6781456
JT
74caveatId :: Caveat -> Key
75caveatId = cid
76
1971e224 77-- | Caveat verification identifier
f6781456
JT
78caveatVId :: Caveat -> Key
79caveatVId = vid
80
1971e224 81-- | Inspect a macaroon's contents. For debugging purposes.
f6781456 82inspect :: Macaroon -> String
2aede11a 83inspect = show
f6781456 84
1971e224 85-- | Serialize a macaroon in an URL-safe Base64 encoding
f6781456
JT
86serialize :: Macaroon -> BS.ByteString
87serialize m = B8.filter (/= '=') . B64.encode $ packets
88 where
89 packets = BS.concat [ putPacket "location" (location m)
90 , putPacket "identifier" (identifier m)
91 , caveatPackets
92 , putPacket "signature" (signature m)
93 ]
94 caveatPackets = BS.concat $ map (cavPacket (location m)) (caveats m)
95 cavPacket loc c | cl c == loc && vid c == BS.empty = putPacket "cid" (cid c)
96 | otherwise = BS.concat [ putPacket "cid" (cid c)
97 , putPacket "vid" (vid c)
98 , putPacket "cl" (cl c)
99 ]
2aede11a
JT
100 putPacket key dat = BS.concat [
101 B8.map toLower . hex . encode $ (fromIntegral size :: Word16)
102 , key
103 , " "
104 , dat
105 , "\n"
106 ]
107 where
108 size = 4 + 2 + BS.length key + BS.length dat
109
f6781456
JT
110
111
112
113-- | Add a first party Caveat to a Macaroon, with its identifier
114addFirstPartyCaveat :: Key -> Macaroon -> Macaroon
115addFirstPartyCaveat ident m = addCaveat (location m) ident BS.empty m
116
117-- |Add a third party Caveat to a Macaroon, using its location, identifier and
118-- verification key
119addThirdPartyCaveat :: Key
120 -> Key
121 -> Location
122 -> Macaroon
123 -> Macaroon
124addThirdPartyCaveat key cid loc m = addCaveat loc cid vid m
125 where
126 vid = encryptECB (initAES (signature m)) key
127
128