]> git.immae.eu Git - github/fretlink/hmacaroons.git/blame - src/Crypto/Macaroon/Internal.hs
Merge branch 'verification'
[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
f6781456
JT
18import Crypto.Hash
19import Data.Byteable
20import qualified Data.ByteString as BS
21import qualified Data.ByteString.Base64 as B64
22import qualified Data.ByteString.Char8 as B8
f6781456 23import Data.Hex
2aede11a 24import Data.List
f6781456 25
86f38823
JT
26
27-- |Type alias for Macaroons secret keys
28type Secret = BS.ByteString
29
30-- |Type alias for Macaroons and Caveat and identifiers
f6781456
JT
31type Key = BS.ByteString
32
1971e224 33-- |Type alias for Macaroons and Caveat locations
f6781456
JT
34type Location = BS.ByteString
35
1971e224 36-- |Type alias for Macaroons signatures
f6781456
JT
37type Sig = BS.ByteString
38
39-- | Main structure of a macaroon
40data Macaroon = MkMacaroon { location :: Location
41 -- ^ Target location
42 , identifier :: Key
43 -- ^ Macaroon Identifier
44 , caveats :: [Caveat]
45 -- ^ List of caveats
46 , signature :: Sig
47 -- ^ Macaroon HMAC signature
30c4b925
JT
48 }
49
7986de7c 50-- | Constant-time Eq instance
30c4b925
JT
51instance Eq Macaroon where
52 (MkMacaroon l1 i1 c1 s1) == (MkMacaroon l2 i2 c2 s2) =
53 (l1 `constEqBytes` l2) &&!
54 (i1 `constEqBytes` i2) &&!
55 (c1 == c2) &&!
56 (s1 `constEqBytes` s2)
57
f6781456 58
1971e224 59-- | show instance conforming to the @inspect@ "specification"
2aede11a
JT
60instance Show Macaroon where
61 -- We use intercalate because unlines would add a trailing newline
62 show (MkMacaroon l i c s) = intercalate "\n" [
63 "location " ++ B8.unpack l
64 , "identifier " ++ B8.unpack i
b7889567 65 , intercalate "\n" (map show c)
2aede11a
JT
66 , "signature " ++ B8.unpack (hex s)
67 ]
f6781456 68
1971e224 69-- | NFData instance for use in the benchmark
f6781456
JT
70instance NFData Macaroon where
71 rnf (MkMacaroon loc ident cavs sig) = rnf loc `seq` rnf ident `seq` rnf cavs `seq` rnf sig
72
73
74-- | Caveat structure
75data Caveat = MkCaveat { cid :: Key
76 -- ^ Caveat identifier
77 , vid :: Key
78 -- ^ Caveat verification key identifier
79 , cl :: Location
80 -- ^ Caveat target location
30c4b925 81 }
f6781456 82
7986de7c 83-- | Constant-time Eq instance
30c4b925
JT
84instance Eq Caveat where
85 (MkCaveat c1 v1 l1) == (MkCaveat c2 v2 l2) =
86 (c1 `constEqBytes` c2) &&!
87 (v1 `constEqBytes` v2) &&!
88 (l1 `constEqBytes` l2)
f6781456 89
1971e224 90-- | show instance conforming to the @inspect@ "specification"
2aede11a
JT
91instance Show Caveat where
92 show (MkCaveat c v l) | v == BS.empty = "cid " ++ B8.unpack c
93 | otherwise = unlines [ "cid " ++ B8.unpack c
94 , "vid " ++ B8.unpack v
95 , "cl " ++ B8.unpack l
96 ]
97
98
1971e224 99-- | NFData instance for use in the benchmark
f6781456
JT
100instance NFData Caveat where
101 rnf (MkCaveat cid vid cl) = rnf cid `seq` rnf vid `seq` rnf cl
102
1971e224
JT
103-- | Primitive to add a First or Third party caveat to a macaroon
104-- For internal use only
f6781456
JT
105addCaveat :: Location
106 -> Key
107 -> Key
108 -> Macaroon
109 -> Macaroon
110addCaveat loc cid vid m = m { caveats = cavs ++ [cav'], signature = sig}
111 where
112 cavs = caveats m
113 cav' = MkCaveat cid vid loc
2aede11a 114 sig = toBytes (hmac (signature m) (BS.append vid cid) :: HMAC SHA256)
f6781456 115
30c4b925
JT
116-- | Utility non-short circuiting '&&' function.
117(&&!) :: Bool -> Bool -> Bool
118True &&! True = True
119True &&! False = False
120False &&! True = False
121False &&! False = False
122