{-# LANGUAGE OverloadedStrings #-}
module Authorize.Macaroon.Types (
MacaroonId (..),
Macaroon (..),
Caveat (..),
SealedMacaroon (..),
Key (..),
KeyId (..),
Signature (..),
Location,
) where
import Authorize.Macaroon.Serialize qualified as MS
import Control.Monad (unless)
import Data.ByteArray (
ByteArray,
ByteArrayAccess,
ScrubbedBytes,
)
import Data.ByteString (ByteString)
import Data.ByteString qualified as BS
import Data.Maybe (fromMaybe)
import Data.Serialize (Serialize (..))
import Data.Serialize qualified as S
type Location = ByteString
newtype MacaroonId = MacaroonId {MacaroonId -> ByteString
unMacaroonId :: ByteString}
deriving (MacaroonId -> MacaroonId -> Bool
(MacaroonId -> MacaroonId -> Bool)
-> (MacaroonId -> MacaroonId -> Bool) -> Eq MacaroonId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MacaroonId -> MacaroonId -> Bool
== :: MacaroonId -> MacaroonId -> Bool
$c/= :: MacaroonId -> MacaroonId -> Bool
/= :: MacaroonId -> MacaroonId -> Bool
Eq, Eq MacaroonId
Eq MacaroonId =>
(MacaroonId -> MacaroonId -> Ordering)
-> (MacaroonId -> MacaroonId -> Bool)
-> (MacaroonId -> MacaroonId -> Bool)
-> (MacaroonId -> MacaroonId -> Bool)
-> (MacaroonId -> MacaroonId -> Bool)
-> (MacaroonId -> MacaroonId -> MacaroonId)
-> (MacaroonId -> MacaroonId -> MacaroonId)
-> Ord MacaroonId
MacaroonId -> MacaroonId -> Bool
MacaroonId -> MacaroonId -> Ordering
MacaroonId -> MacaroonId -> MacaroonId
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: MacaroonId -> MacaroonId -> Ordering
compare :: MacaroonId -> MacaroonId -> Ordering
$c< :: MacaroonId -> MacaroonId -> Bool
< :: MacaroonId -> MacaroonId -> Bool
$c<= :: MacaroonId -> MacaroonId -> Bool
<= :: MacaroonId -> MacaroonId -> Bool
$c> :: MacaroonId -> MacaroonId -> Bool
> :: MacaroonId -> MacaroonId -> Bool
$c>= :: MacaroonId -> MacaroonId -> Bool
>= :: MacaroonId -> MacaroonId -> Bool
$cmax :: MacaroonId -> MacaroonId -> MacaroonId
max :: MacaroonId -> MacaroonId -> MacaroonId
$cmin :: MacaroonId -> MacaroonId -> MacaroonId
min :: MacaroonId -> MacaroonId -> MacaroonId
Ord, Int -> MacaroonId -> ShowS
[MacaroonId] -> ShowS
MacaroonId -> String
(Int -> MacaroonId -> ShowS)
-> (MacaroonId -> String)
-> ([MacaroonId] -> ShowS)
-> Show MacaroonId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MacaroonId -> ShowS
showsPrec :: Int -> MacaroonId -> ShowS
$cshow :: MacaroonId -> String
show :: MacaroonId -> String
$cshowList :: [MacaroonId] -> ShowS
showList :: [MacaroonId] -> ShowS
Show, MacaroonId -> Int
(MacaroonId -> Int)
-> (forall p a. MacaroonId -> (Ptr p -> IO a) -> IO a)
-> (forall p. MacaroonId -> Ptr p -> IO ())
-> ByteArrayAccess MacaroonId
forall p. MacaroonId -> Ptr p -> IO ()
forall ba.
(ba -> Int)
-> (forall p a. ba -> (Ptr p -> IO a) -> IO a)
-> (forall p. ba -> Ptr p -> IO ())
-> ByteArrayAccess ba
forall p a. MacaroonId -> (Ptr p -> IO a) -> IO a
$clength :: MacaroonId -> Int
length :: MacaroonId -> Int
$cwithByteArray :: forall p a. MacaroonId -> (Ptr p -> IO a) -> IO a
withByteArray :: forall p a. MacaroonId -> (Ptr p -> IO a) -> IO a
$ccopyByteArrayToPtr :: forall p. MacaroonId -> Ptr p -> IO ()
copyByteArrayToPtr :: forall p. MacaroonId -> Ptr p -> IO ()
ByteArrayAccess, Get MacaroonId
Putter MacaroonId
Putter MacaroonId -> Get MacaroonId -> Serialize MacaroonId
forall t. Putter t -> Get t -> Serialize t
$cput :: Putter MacaroonId
put :: Putter MacaroonId
$cget :: Get MacaroonId
get :: Get MacaroonId
Serialize)
newtype Key = Key {Key -> ScrubbedBytes
unKey :: ScrubbedBytes} deriving (Key -> Key -> Bool
(Key -> Key -> Bool) -> (Key -> Key -> Bool) -> Eq Key
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Key -> Key -> Bool
== :: Key -> Key -> Bool
$c/= :: Key -> Key -> Bool
/= :: Key -> Key -> Bool
Eq, Eq Key
Eq Key =>
(Key -> Key -> Ordering)
-> (Key -> Key -> Bool)
-> (Key -> Key -> Bool)
-> (Key -> Key -> Bool)
-> (Key -> Key -> Bool)
-> (Key -> Key -> Key)
-> (Key -> Key -> Key)
-> Ord Key
Key -> Key -> Bool
Key -> Key -> Ordering
Key -> Key -> Key
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Key -> Key -> Ordering
compare :: Key -> Key -> Ordering
$c< :: Key -> Key -> Bool
< :: Key -> Key -> Bool
$c<= :: Key -> Key -> Bool
<= :: Key -> Key -> Bool
$c> :: Key -> Key -> Bool
> :: Key -> Key -> Bool
$c>= :: Key -> Key -> Bool
>= :: Key -> Key -> Bool
$cmax :: Key -> Key -> Key
max :: Key -> Key -> Key
$cmin :: Key -> Key -> Key
min :: Key -> Key -> Key
Ord, Int -> Key -> ShowS
[Key] -> ShowS
Key -> String
(Int -> Key -> ShowS)
-> (Key -> String) -> ([Key] -> ShowS) -> Show Key
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Key -> ShowS
showsPrec :: Int -> Key -> ShowS
$cshow :: Key -> String
show :: Key -> String
$cshowList :: [Key] -> ShowS
showList :: [Key] -> ShowS
Show, Key -> Int
(Key -> Int)
-> (forall p a. Key -> (Ptr p -> IO a) -> IO a)
-> (forall p. Key -> Ptr p -> IO ())
-> ByteArrayAccess Key
forall p. Key -> Ptr p -> IO ()
forall ba.
(ba -> Int)
-> (forall p a. ba -> (Ptr p -> IO a) -> IO a)
-> (forall p. ba -> Ptr p -> IO ())
-> ByteArrayAccess ba
forall p a. Key -> (Ptr p -> IO a) -> IO a
$clength :: Key -> Int
length :: Key -> Int
$cwithByteArray :: forall p a. Key -> (Ptr p -> IO a) -> IO a
withByteArray :: forall p a. Key -> (Ptr p -> IO a) -> IO a
$ccopyByteArrayToPtr :: forall p. Key -> Ptr p -> IO ()
copyByteArrayToPtr :: forall p. Key -> Ptr p -> IO ()
ByteArrayAccess)
newtype KeyId = KeyId {KeyId -> ByteString
unKeyId :: ByteString} deriving (KeyId -> KeyId -> Bool
(KeyId -> KeyId -> Bool) -> (KeyId -> KeyId -> Bool) -> Eq KeyId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: KeyId -> KeyId -> Bool
== :: KeyId -> KeyId -> Bool
$c/= :: KeyId -> KeyId -> Bool
/= :: KeyId -> KeyId -> Bool
Eq, Eq KeyId
Eq KeyId =>
(KeyId -> KeyId -> Ordering)
-> (KeyId -> KeyId -> Bool)
-> (KeyId -> KeyId -> Bool)
-> (KeyId -> KeyId -> Bool)
-> (KeyId -> KeyId -> Bool)
-> (KeyId -> KeyId -> KeyId)
-> (KeyId -> KeyId -> KeyId)
-> Ord KeyId
KeyId -> KeyId -> Bool
KeyId -> KeyId -> Ordering
KeyId -> KeyId -> KeyId
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: KeyId -> KeyId -> Ordering
compare :: KeyId -> KeyId -> Ordering
$c< :: KeyId -> KeyId -> Bool
< :: KeyId -> KeyId -> Bool
$c<= :: KeyId -> KeyId -> Bool
<= :: KeyId -> KeyId -> Bool
$c> :: KeyId -> KeyId -> Bool
> :: KeyId -> KeyId -> Bool
$c>= :: KeyId -> KeyId -> Bool
>= :: KeyId -> KeyId -> Bool
$cmax :: KeyId -> KeyId -> KeyId
max :: KeyId -> KeyId -> KeyId
$cmin :: KeyId -> KeyId -> KeyId
min :: KeyId -> KeyId -> KeyId
Ord, Int -> KeyId -> ShowS
[KeyId] -> ShowS
KeyId -> String
(Int -> KeyId -> ShowS)
-> (KeyId -> String) -> ([KeyId] -> ShowS) -> Show KeyId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> KeyId -> ShowS
showsPrec :: Int -> KeyId -> ShowS
$cshow :: KeyId -> String
show :: KeyId -> String
$cshowList :: [KeyId] -> ShowS
showList :: [KeyId] -> ShowS
Show, KeyId -> Int
(KeyId -> Int)
-> (forall p a. KeyId -> (Ptr p -> IO a) -> IO a)
-> (forall p. KeyId -> Ptr p -> IO ())
-> ByteArrayAccess KeyId
forall p. KeyId -> Ptr p -> IO ()
forall ba.
(ba -> Int)
-> (forall p a. ba -> (Ptr p -> IO a) -> IO a)
-> (forall p. ba -> Ptr p -> IO ())
-> ByteArrayAccess ba
forall p a. KeyId -> (Ptr p -> IO a) -> IO a
$clength :: KeyId -> Int
length :: KeyId -> Int
$cwithByteArray :: forall p a. KeyId -> (Ptr p -> IO a) -> IO a
withByteArray :: forall p a. KeyId -> (Ptr p -> IO a) -> IO a
$ccopyByteArrayToPtr :: forall p. KeyId -> Ptr p -> IO ()
copyByteArrayToPtr :: forall p. KeyId -> Ptr p -> IO ()
ByteArrayAccess)
newtype Signature = Signature {Signature -> ByteString
unSignature :: ByteString}
deriving
( Signature -> Signature -> Bool
(Signature -> Signature -> Bool)
-> (Signature -> Signature -> Bool) -> Eq Signature
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Signature -> Signature -> Bool
== :: Signature -> Signature -> Bool
$c/= :: Signature -> Signature -> Bool
/= :: Signature -> Signature -> Bool
Eq
, Eq Signature
Eq Signature =>
(Signature -> Signature -> Ordering)
-> (Signature -> Signature -> Bool)
-> (Signature -> Signature -> Bool)
-> (Signature -> Signature -> Bool)
-> (Signature -> Signature -> Bool)
-> (Signature -> Signature -> Signature)
-> (Signature -> Signature -> Signature)
-> Ord Signature
Signature -> Signature -> Bool
Signature -> Signature -> Ordering
Signature -> Signature -> Signature
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Signature -> Signature -> Ordering
compare :: Signature -> Signature -> Ordering
$c< :: Signature -> Signature -> Bool
< :: Signature -> Signature -> Bool
$c<= :: Signature -> Signature -> Bool
<= :: Signature -> Signature -> Bool
$c> :: Signature -> Signature -> Bool
> :: Signature -> Signature -> Bool
$c>= :: Signature -> Signature -> Bool
>= :: Signature -> Signature -> Bool
$cmax :: Signature -> Signature -> Signature
max :: Signature -> Signature -> Signature
$cmin :: Signature -> Signature -> Signature
min :: Signature -> Signature -> Signature
Ord
, NonEmpty Signature -> Signature
Signature -> Signature -> Signature
(Signature -> Signature -> Signature)
-> (NonEmpty Signature -> Signature)
-> (forall b. Integral b => b -> Signature -> Signature)
-> Semigroup Signature
forall b. Integral b => b -> Signature -> Signature
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
$c<> :: Signature -> Signature -> Signature
<> :: Signature -> Signature -> Signature
$csconcat :: NonEmpty Signature -> Signature
sconcat :: NonEmpty Signature -> Signature
$cstimes :: forall b. Integral b => b -> Signature -> Signature
stimes :: forall b. Integral b => b -> Signature -> Signature
Semigroup
, Semigroup Signature
Signature
Semigroup Signature =>
Signature
-> (Signature -> Signature -> Signature)
-> ([Signature] -> Signature)
-> Monoid Signature
[Signature] -> Signature
Signature -> Signature -> Signature
forall a.
Semigroup a =>
a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
$cmempty :: Signature
mempty :: Signature
$cmappend :: Signature -> Signature -> Signature
mappend :: Signature -> Signature -> Signature
$cmconcat :: [Signature] -> Signature
mconcat :: [Signature] -> Signature
Monoid
, Eq Signature
Ord Signature
Monoid Signature
ByteArrayAccess Signature
(Eq Signature, Ord Signature, Monoid Signature,
ByteArrayAccess Signature) =>
(forall p a. Int -> (Ptr p -> IO a) -> IO (a, Signature))
-> ByteArray Signature
forall ba.
(Eq ba, Ord ba, Monoid ba, ByteArrayAccess ba) =>
(forall p a. Int -> (Ptr p -> IO a) -> IO (a, ba)) -> ByteArray ba
forall p a. Int -> (Ptr p -> IO a) -> IO (a, Signature)
$callocRet :: forall p a. Int -> (Ptr p -> IO a) -> IO (a, Signature)
allocRet :: forall p a. Int -> (Ptr p -> IO a) -> IO (a, Signature)
ByteArray
, Signature -> Int
(Signature -> Int)
-> (forall p a. Signature -> (Ptr p -> IO a) -> IO a)
-> (forall p. Signature -> Ptr p -> IO ())
-> ByteArrayAccess Signature
forall p. Signature -> Ptr p -> IO ()
forall ba.
(ba -> Int)
-> (forall p a. ba -> (Ptr p -> IO a) -> IO a)
-> (forall p. ba -> Ptr p -> IO ())
-> ByteArrayAccess ba
forall p a. Signature -> (Ptr p -> IO a) -> IO a
$clength :: Signature -> Int
length :: Signature -> Int
$cwithByteArray :: forall p a. Signature -> (Ptr p -> IO a) -> IO a
withByteArray :: forall p a. Signature -> (Ptr p -> IO a) -> IO a
$ccopyByteArrayToPtr :: forall p. Signature -> Ptr p -> IO ()
copyByteArrayToPtr :: forall p. Signature -> Ptr p -> IO ()
ByteArrayAccess
, Get Signature
Putter Signature
Putter Signature -> Get Signature -> Serialize Signature
forall t. Putter t -> Get t -> Serialize t
$cput :: Putter Signature
put :: Putter Signature
$cget :: Get Signature
get :: Get Signature
Serialize
, Int -> Signature -> ShowS
[Signature] -> ShowS
Signature -> String
(Int -> Signature -> ShowS)
-> (Signature -> String)
-> ([Signature] -> ShowS)
-> Show Signature
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Signature -> ShowS
showsPrec :: Int -> Signature -> ShowS
$cshow :: Signature -> String
show :: Signature -> String
$cshowList :: [Signature] -> ShowS
showList :: [Signature] -> ShowS
Show
)
data Macaroon = Macaroon
{ Macaroon -> ByteString
locationHint :: Location
, Macaroon -> MacaroonId
identifier :: MacaroonId
, Macaroon -> [Caveat]
caveats :: [Caveat]
, Macaroon -> Signature
macaroonSignature :: Signature
}
deriving (Macaroon -> Macaroon -> Bool
(Macaroon -> Macaroon -> Bool)
-> (Macaroon -> Macaroon -> Bool) -> Eq Macaroon
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Macaroon -> Macaroon -> Bool
== :: Macaroon -> Macaroon -> Bool
$c/= :: Macaroon -> Macaroon -> Bool
/= :: Macaroon -> Macaroon -> Bool
Eq, Int -> Macaroon -> ShowS
[Macaroon] -> ShowS
Macaroon -> String
(Int -> Macaroon -> ShowS)
-> (Macaroon -> String) -> ([Macaroon] -> ShowS) -> Show Macaroon
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Macaroon -> ShowS
showsPrec :: Int -> Macaroon -> ShowS
$cshow :: Macaroon -> String
show :: Macaroon -> String
$cshowList :: [Macaroon] -> ShowS
showList :: [Macaroon] -> ShowS
Show)
instance Serialize Macaroon where
put :: Putter Macaroon
put (Macaroon ByteString
loc MacaroonId
i [Caveat]
cs Signature
sig) = do
Putter Word8
S.putWord8 Word8
2
Bool -> Put -> Put
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (ByteString -> Bool
BS.null ByteString
loc) (Put -> Put) -> Put -> Put
forall a b. (a -> b) -> a -> b
$ Word8 -> Putter ByteString
MS.putField Word8
MS.fieldLocation ByteString
loc
Word8 -> Putter ByteString
MS.putField Word8
MS.fieldIdentifier Putter ByteString -> Putter ByteString
forall a b. (a -> b) -> a -> b
$ MacaroonId -> ByteString
unMacaroonId MacaroonId
i
Putter Word8
forall t. Serialize t => Putter t
put Word8
MS.fieldEOS
(Caveat -> Put) -> [Caveat] -> Put
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Caveat -> Put
forall t. Serialize t => Putter t
put [Caveat]
cs
Putter Word8
forall t. Serialize t => Putter t
put Word8
MS.fieldEOS
Word8 -> Putter ByteString
MS.putField Word8
MS.fieldSignature Putter ByteString -> Putter ByteString
forall a b. (a -> b) -> a -> b
$ Signature -> ByteString
unSignature Signature
sig
get :: Get Macaroon
get = do
Get ()
getVersion
Maybe ByteString
mloc <- Word8 -> Get (Maybe ByteString)
MS.getOptionalField Word8
MS.fieldLocation
MacaroonId
mid <- ByteString -> MacaroonId
MacaroonId (ByteString -> MacaroonId) -> Get ByteString -> Get MacaroonId
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Word8 -> Get ByteString
MS.getField Word8
MS.fieldIdentifier
Get ()
MS.getEOS
[Caveat]
cs <- Get [Caveat]
getCaveats
Get ()
MS.getEOS
Signature
sig <- ByteString -> Signature
Signature (ByteString -> Signature) -> Get ByteString -> Get Signature
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Word8 -> Get ByteString
MS.getField Word8
MS.fieldSignature
Macaroon -> Get Macaroon
forall a. a -> Get a
forall (m :: * -> *) a. Monad m => a -> m a
return (Macaroon -> Get Macaroon) -> Macaroon -> Get Macaroon
forall a b. (a -> b) -> a -> b
$ ByteString -> MacaroonId -> [Caveat] -> Signature -> Macaroon
Macaroon (ByteString -> Maybe ByteString -> ByteString
forall a. a -> Maybe a -> a
fromMaybe ByteString
forall a. Monoid a => a
mempty Maybe ByteString
mloc) MacaroonId
mid [Caveat]
cs Signature
sig
where
getVersion :: Get ()
getVersion = do
Word8
v <- Get Word8
S.getWord8
if Word8
v Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
2 then () -> Get ()
forall a. a -> Get a
forall (m :: * -> *) a. Monad m => a -> m a
return () else String -> Get ()
forall a. String -> Get a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Unsupported macaroon version"
getCaveats :: Get [Caveat]
getCaveats = do
Bool
eos <- Get Bool
MS.atEOS
if Bool
eos then [Caveat] -> Get [Caveat]
forall a. a -> Get a
forall (m :: * -> *) a. Monad m => a -> m a
return [] else (:) (Caveat -> [Caveat] -> [Caveat])
-> Get Caveat -> Get ([Caveat] -> [Caveat])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Caveat
forall t. Serialize t => Get t
get Get ([Caveat] -> [Caveat]) -> Get [Caveat] -> Get [Caveat]
forall a b. Get (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get [Caveat]
getCaveats
data Caveat = Caveat
{ Caveat -> ByteString
caveatLocationHint :: Location
, Caveat -> Maybe KeyId
caveatKeyId :: Maybe KeyId
, Caveat -> ByteString
caveatContent :: ByteString
}
deriving (Caveat -> Caveat -> Bool
(Caveat -> Caveat -> Bool)
-> (Caveat -> Caveat -> Bool) -> Eq Caveat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Caveat -> Caveat -> Bool
== :: Caveat -> Caveat -> Bool
$c/= :: Caveat -> Caveat -> Bool
/= :: Caveat -> Caveat -> Bool
Eq, Int -> Caveat -> ShowS
[Caveat] -> ShowS
Caveat -> String
(Int -> Caveat -> ShowS)
-> (Caveat -> String) -> ([Caveat] -> ShowS) -> Show Caveat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Caveat -> ShowS
showsPrec :: Int -> Caveat -> ShowS
$cshow :: Caveat -> String
show :: Caveat -> String
$cshowList :: [Caveat] -> ShowS
showList :: [Caveat] -> ShowS
Show)
instance Serialize Caveat where
put :: Caveat -> Put
put (Caveat ByteString
loc Maybe KeyId
mk ByteString
c) = do
Bool -> Put -> Put
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (ByteString -> Bool
BS.null ByteString
loc) (Put -> Put) -> Put -> Put
forall a b. (a -> b) -> a -> b
$ Word8 -> Putter ByteString
MS.putField Word8
MS.fieldLocation ByteString
loc
Word8 -> Putter ByteString
MS.putField Word8
MS.fieldIdentifier ByteString
c
(KeyId -> Put) -> Maybe KeyId -> Put
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (Word8 -> Putter ByteString
MS.putField Word8
MS.fieldVerificationId Putter ByteString -> (KeyId -> ByteString) -> KeyId -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. KeyId -> ByteString
unKeyId) Maybe KeyId
mk
Putter Word8
forall t. Serialize t => Putter t
put Word8
MS.fieldEOS
get :: Get Caveat
get =
Maybe ByteString -> ByteString -> Maybe ByteString -> Caveat
makeCaveat
(Maybe ByteString -> ByteString -> Maybe ByteString -> Caveat)
-> Get (Maybe ByteString)
-> Get (ByteString -> Maybe ByteString -> Caveat)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Word8 -> Get (Maybe ByteString)
MS.getOptionalField Word8
MS.fieldLocation
Get (ByteString -> Maybe ByteString -> Caveat)
-> Get ByteString -> Get (Maybe ByteString -> Caveat)
forall a b. Get (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Word8 -> Get ByteString
MS.getField Word8
MS.fieldIdentifier
Get (Maybe ByteString -> Caveat)
-> Get (Maybe ByteString) -> Get Caveat
forall a b. Get (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Word8 -> Get (Maybe ByteString)
MS.getOptionalField Word8
MS.fieldVerificationId
Get Caveat -> Get () -> Get Caveat
forall a b. Get a -> Get b -> Get a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Get ()
MS.getEOS
where
makeCaveat :: Maybe ByteString -> ByteString -> Maybe ByteString -> Caveat
makeCaveat Maybe ByteString
mloc ByteString
c Maybe ByteString
mkeyid = ByteString -> Maybe KeyId -> ByteString -> Caveat
Caveat (ByteString -> Maybe ByteString -> ByteString
forall a. a -> Maybe a -> a
fromMaybe ByteString
forall a. Monoid a => a
mempty Maybe ByteString
mloc) (ByteString -> KeyId
KeyId (ByteString -> KeyId) -> Maybe ByteString -> Maybe KeyId
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe ByteString
mkeyid) ByteString
c
data SealedMacaroon = SealedMacaroon
{ SealedMacaroon -> Macaroon
rootMacaroon :: Macaroon
, SealedMacaroon -> [Macaroon]
dischargeMacaroons :: [Macaroon]
}
deriving (SealedMacaroon -> SealedMacaroon -> Bool
(SealedMacaroon -> SealedMacaroon -> Bool)
-> (SealedMacaroon -> SealedMacaroon -> Bool) -> Eq SealedMacaroon
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SealedMacaroon -> SealedMacaroon -> Bool
== :: SealedMacaroon -> SealedMacaroon -> Bool
$c/= :: SealedMacaroon -> SealedMacaroon -> Bool
/= :: SealedMacaroon -> SealedMacaroon -> Bool
Eq, Int -> SealedMacaroon -> ShowS
[SealedMacaroon] -> ShowS
SealedMacaroon -> String
(Int -> SealedMacaroon -> ShowS)
-> (SealedMacaroon -> String)
-> ([SealedMacaroon] -> ShowS)
-> Show SealedMacaroon
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SealedMacaroon -> ShowS
showsPrec :: Int -> SealedMacaroon -> ShowS
$cshow :: SealedMacaroon -> String
show :: SealedMacaroon -> String
$cshowList :: [SealedMacaroon] -> ShowS
showList :: [SealedMacaroon] -> ShowS
Show)
instance Serialize SealedMacaroon where
put :: Putter SealedMacaroon
put (SealedMacaroon Macaroon
r [Macaroon]
ds) = Putter Macaroon
forall t. Serialize t => Putter t
put Macaroon
r Put -> Put -> Put
forall a b. PutM a -> PutM b -> PutM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Putter Macaroon -> [Macaroon] -> Put
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Putter Macaroon
forall t. Serialize t => Putter t
put [Macaroon]
ds
get :: Get SealedMacaroon
get = Macaroon -> [Macaroon] -> SealedMacaroon
SealedMacaroon (Macaroon -> [Macaroon] -> SealedMacaroon)
-> Get Macaroon -> Get ([Macaroon] -> SealedMacaroon)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Macaroon
forall t. Serialize t => Get t
get Get ([Macaroon] -> SealedMacaroon)
-> Get [Macaroon] -> Get SealedMacaroon
forall a b. Get (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get [Macaroon]
getMacaroons
where
getMacaroons :: Get [Macaroon]
getMacaroons = do
Int
n <- Get Int
S.remaining
if Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 then (:) (Macaroon -> [Macaroon] -> [Macaroon])
-> Get Macaroon -> Get ([Macaroon] -> [Macaroon])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Macaroon
forall t. Serialize t => Get t
get Get ([Macaroon] -> [Macaroon]) -> Get [Macaroon] -> Get [Macaroon]
forall a b. Get (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get [Macaroon]
getMacaroons else [Macaroon] -> Get [Macaroon]
forall a. a -> Get a
forall (m :: * -> *) a. Monad m => a -> m a
return []