]> git.immae.eu Git - github/fretlink/hmacaroons.git/blame - src/Crypto/Macaroon/Internal.hs
Haddock markup
[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
30c4b925
JT
45 }
46
7986de7c 47-- | Constant-time Eq instance
30c4b925
JT
48instance Eq Macaroon where
49 (MkMacaroon l1 i1 c1 s1) == (MkMacaroon l2 i2 c2 s2) =
50 (l1 `constEqBytes` l2) &&!
51 (i1 `constEqBytes` i2) &&!
52 (c1 == c2) &&!
53 (s1 `constEqBytes` s2)
54
f6781456 55
1971e224 56-- | show instance conforming to the @inspect@ "specification"
2aede11a
JT
57instance Show Macaroon where
58 -- We use intercalate because unlines would add a trailing newline
59 show (MkMacaroon l i c s) = intercalate "\n" [
60 "location " ++ B8.unpack l
61 , "identifier " ++ B8.unpack i
62 , concatMap show c
63 , "signature " ++ B8.unpack (hex s)
64 ]
f6781456 65
1971e224 66-- | NFData instance for use in the benchmark
f6781456
JT
67instance NFData Macaroon where
68 rnf (MkMacaroon loc ident cavs sig) = rnf loc `seq` rnf ident `seq` rnf cavs `seq` rnf sig
69
70
71-- | Caveat structure
72data Caveat = MkCaveat { cid :: Key
73 -- ^ Caveat identifier
74 , vid :: Key
75 -- ^ Caveat verification key identifier
76 , cl :: Location
77 -- ^ Caveat target location
30c4b925 78 }
f6781456 79
7986de7c 80-- | Constant-time Eq instance
30c4b925
JT
81instance Eq Caveat where
82 (MkCaveat c1 v1 l1) == (MkCaveat c2 v2 l2) =
83 (c1 `constEqBytes` c2) &&!
84 (v1 `constEqBytes` v2) &&!
85 (l1 `constEqBytes` l2)
f6781456 86
1971e224 87-- | show instance conforming to the @inspect@ "specification"
2aede11a
JT
88instance Show Caveat where
89 show (MkCaveat c v l) | v == BS.empty = "cid " ++ B8.unpack c
90 | otherwise = unlines [ "cid " ++ B8.unpack c
91 , "vid " ++ B8.unpack v
92 , "cl " ++ B8.unpack l
93 ]
94
95
1971e224 96-- | NFData instance for use in the benchmark
f6781456
JT
97instance NFData Caveat where
98 rnf (MkCaveat cid vid cl) = rnf cid `seq` rnf vid `seq` rnf cl
99
1971e224
JT
100-- | Primitive to add a First or Third party caveat to a macaroon
101-- For internal use only
f6781456
JT
102addCaveat :: Location
103 -> Key
104 -> Key
105 -> Macaroon
106 -> Macaroon
107addCaveat loc cid vid m = m { caveats = cavs ++ [cav'], signature = sig}
108 where
109 cavs = caveats m
110 cav' = MkCaveat cid vid loc
2aede11a 111 sig = toBytes (hmac (signature m) (BS.append vid cid) :: HMAC SHA256)
f6781456 112
30c4b925
JT
113-- | Utility non-short circuiting '&&' function.
114(&&!) :: Bool -> Bool -> Bool
115True &&! True = True
116True &&! False = False
117False &&! True = False
118False &&! False = False
119