]> git.immae.eu Git - github/fretlink/hmacaroons.git/blame - src/Crypto/Macaroon/Internal.hs
Documentation
[github/fretlink/hmacaroons.git] / src / Crypto / Macaroon / Internal.hs
CommitLineData
f6781456
JT
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
f6781456 24import Data.Hex
2aede11a 25import Data.List
f6781456
JT
26
27-- |Type alias for Macaroons and Caveat keys and identifiers
28type Key = BS.ByteString
29
1971e224 30-- |Type alias for Macaroons and Caveat locations
f6781456
JT
31type Location = BS.ByteString
32
1971e224 33-- |Type alias for Macaroons signatures
f6781456
JT
34type Sig = BS.ByteString
35
36-- | Main structure of a macaroon
37data Macaroon = MkMacaroon { location :: Location
38 -- ^ Target location
39 , identifier :: Key
40 -- ^ Macaroon Identifier
41 , caveats :: [Caveat]
42 -- ^ List of caveats
43 , signature :: Sig
44 -- ^ Macaroon HMAC signature
45 } deriving (Eq)
46
1971e224 47-- | show instance conforming to the @inspect@ "specification"
2aede11a
JT
48instance Show Macaroon where
49 -- We use intercalate because unlines would add a trailing newline
50 show (MkMacaroon l i c s) = intercalate "\n" [
51 "location " ++ B8.unpack l
52 , "identifier " ++ B8.unpack i
53 , concatMap show c
54 , "signature " ++ B8.unpack (hex s)
55 ]
f6781456 56
1971e224 57-- | NFData instance for use in the benchmark
f6781456
JT
58instance NFData Macaroon where
59 rnf (MkMacaroon loc ident cavs sig) = rnf loc `seq` rnf ident `seq` rnf cavs `seq` rnf sig
60
61
62-- | Caveat structure
63data Caveat = MkCaveat { cid :: Key
64 -- ^ Caveat identifier
65 , vid :: Key
66 -- ^ Caveat verification key identifier
67 , cl :: Location
68 -- ^ Caveat target location
69
70 } deriving (Eq)
71
1971e224 72-- | show instance conforming to the @inspect@ "specification"
2aede11a
JT
73instance Show Caveat where
74 show (MkCaveat c v l) | v == BS.empty = "cid " ++ B8.unpack c
75 | otherwise = unlines [ "cid " ++ B8.unpack c
76 , "vid " ++ B8.unpack v
77 , "cl " ++ B8.unpack l
78 ]
79
80
1971e224 81-- | NFData instance for use in the benchmark
f6781456
JT
82instance NFData Caveat where
83 rnf (MkCaveat cid vid cl) = rnf cid `seq` rnf vid `seq` rnf cl
84
1971e224
JT
85-- | Primitive to add a First or Third party caveat to a macaroon
86-- For internal use only
f6781456
JT
87addCaveat :: Location
88 -> Key
89 -> Key
90 -> Macaroon
91 -> Macaroon
92addCaveat loc cid vid m = m { caveats = cavs ++ [cav'], signature = sig}
93 where
94 cavs = caveats m
95 cav' = MkCaveat cid vid loc
2aede11a 96 sig = toBytes (hmac (signature m) (BS.append vid cid) :: HMAC SHA256)
f6781456 97