{-# LANGUAGE DataKinds          #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE FlexibleInstances  #-}
{-# LANGUAGE KindSignatures     #-}
{-# LANGUAGE NamedFieldPuns     #-}
{-# LANGUAGE RecordWildCards    #-}
{- HLINT ignore "Reduce duplication" -}
{-|
  Module      : Auth.Biscuit.Token
  Copyright   : © Clément Delafargue, 2021
  License     : MIT
  Maintainer  : clement@delafargue.name
  Module defining the main biscuit-related operations
-}
module Auth.Biscuit.Token
  ( Biscuit
  , rootKeyId
  , symbols
  , authority
  , blocks
  , proof
  , proofCheck
  , ParseError (..)
  , ExistingBlock
  , ParsedSignedBlock
  -- $openOrSealed
  , OpenOrSealed
  , Open
  , Sealed
  , BiscuitProof (..)
  , Verified
  , Unverified
  , mkBiscuit
  , addBlock
  , BiscuitEncoding (..)
  , ParserConfig (..)
  , parseBiscuitWith
  , parseBiscuitUnverified
  , checkBiscuitSignatures
  , serializeBiscuit
  , authorizeBiscuit
  , authorizeBiscuitWithLimits
  , fromOpen
  , fromSealed
  , asOpen
  , asSealed
  , seal

  , getRevocationIds
  , getVerifiedBiscuitPublicKey

  ) where

import           Control.Monad                       (join, when)
import           Data.Bifunctor                      (first)
import           Data.ByteString                     (ByteString)
import qualified Data.ByteString.Base64.URL          as B64
import           Data.List.NonEmpty                  (NonEmpty ((:|)))
import qualified Data.List.NonEmpty                  as NE
import           Data.Set                            (Set)
import qualified Data.Set                            as Set

import           Auth.Biscuit.Crypto                 (PublicKey, SecretKey,
                                                      Signature, SignedBlock,
                                                      convert,
                                                      getSignatureProof,
                                                      signBlock, toPublic,
                                                      verifyBlocks,
                                                      verifySecretProof,
                                                      verifySignatureProof)
import           Auth.Biscuit.Datalog.AST            (Authorizer, Block)
import           Auth.Biscuit.Datalog.Executor       (ExecutionError, Limits,
                                                      defaultLimits)
import           Auth.Biscuit.Datalog.ScopedExecutor (AuthorizationSuccess,
                                                      runAuthorizerWithLimits)
import qualified Auth.Biscuit.Proto                  as PB
import           Auth.Biscuit.ProtoBufAdapter        (Symbols, blockToPb,
                                                      commonSymbols,
                                                      extractSymbols, pbToBlock,
                                                      pbToProof,
                                                      pbToSignedBlock,
                                                      signedBlockToPb)

-- | Protobuf serialization does not have a guaranteed deterministic behaviour,
-- so we need to keep the initial serialized payload around in order to compute
-- a new signature when adding a block.
type ExistingBlock = (ByteString, Block)
type ParsedSignedBlock = (ExistingBlock, Signature, PublicKey)

-- $openOrSealed
--
-- Biscuit tokens can be /open/ (capable of being attenuated further) or
-- /sealed/ (not capable of being attenuated further). Some operations
-- like verification work on both kinds, while others (like attenuation)
-- only work on a single kind. The 'OpenOrSealed', 'Open' and 'Sealed' trio
-- represents the different possibilities. 'OpenOrSealed' is usually obtained
-- through parsing, while 'Open' is obtained by creating a new biscuit (or
-- attenuating an existing one), and 'Sealed' is obtained by sealing an open
-- biscuit

-- | This datatype represents the final proof of a biscuit, which can be either
-- /open/ or /sealed/. This is the typical state of a biscuit that's been parsed.
data OpenOrSealed
  = SealedProof Signature
  | OpenProof SecretKey
  deriving (OpenOrSealed -> OpenOrSealed -> Bool
(OpenOrSealed -> OpenOrSealed -> Bool)
-> (OpenOrSealed -> OpenOrSealed -> Bool) -> Eq OpenOrSealed
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OpenOrSealed -> OpenOrSealed -> Bool
$c/= :: OpenOrSealed -> OpenOrSealed -> Bool
== :: OpenOrSealed -> OpenOrSealed -> Bool
$c== :: OpenOrSealed -> OpenOrSealed -> Bool
Eq, Int -> OpenOrSealed -> ShowS
[OpenOrSealed] -> ShowS
OpenOrSealed -> String
(Int -> OpenOrSealed -> ShowS)
-> (OpenOrSealed -> String)
-> ([OpenOrSealed] -> ShowS)
-> Show OpenOrSealed
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OpenOrSealed] -> ShowS
$cshowList :: [OpenOrSealed] -> ShowS
show :: OpenOrSealed -> String
$cshow :: OpenOrSealed -> String
showsPrec :: Int -> OpenOrSealed -> ShowS
$cshowsPrec :: Int -> OpenOrSealed -> ShowS
Show)

-- | This datatype represents the final proof of a biscuit statically known to be
-- /open/ (capable of being attenuated further). In that case the proof is a secret
-- key that can be used to sign a new block.
newtype Open = Open SecretKey

-- | This datatype represents the final proof of a biscuit statically known to be
-- /sealed/ (not capable of being attenuated further). In that case the proof is a
-- signature proving that the party who sealed the token did know the last secret
-- key.
newtype Sealed = Sealed Signature

-- | This class allows functions working on both open and sealed biscuits to accept
-- indifferently 'OpenOrSealed', 'Open' or 'Sealed' biscuits. It has no laws, it only
-- projects 'Open' and 'Sealed' to the general 'OpenOrSealed' case.
class BiscuitProof a where
  toPossibleProofs :: a -> OpenOrSealed

instance BiscuitProof OpenOrSealed where
  toPossibleProofs :: OpenOrSealed -> OpenOrSealed
toPossibleProofs = OpenOrSealed -> OpenOrSealed
forall a. a -> a
id
instance BiscuitProof Sealed where
  toPossibleProofs :: Sealed -> OpenOrSealed
toPossibleProofs (Sealed Signature
sig) = Signature -> OpenOrSealed
SealedProof Signature
sig
instance BiscuitProof Open where
  toPossibleProofs :: Open -> OpenOrSealed
toPossibleProofs (Open SecretKey
sk) = SecretKey -> OpenOrSealed
OpenProof SecretKey
sk

-- $verifiedOrUnverified
--
-- The default parsing mechanism for biscuits checks the signature before parsing the blocks
-- contents (this reduces the attack surface, as only biscuits with a valid signature are parsed).
-- In some cases, we still want to operate on biscuits without knowing the public key necessary
-- to check signatures (eg for inspection, or for generically adding attenuation blocks). In that
-- case, we can have parsed tokens which signatures have /not/ been verified. In order to
-- accidentally forgetting to check signatures, parsed biscuits keep track of whether the
-- signatures have been verified with a dedicated type parameter, which can be instantiated with
-- two types: 'Verified' and 'Unverified'. 'Verified' additionally keeps track of the 'PublicKey'
-- that has been used to verify the signatures.

-- | Proof that a biscuit had its signatures verified with the carried root 'PublicKey'
newtype Verified = Verified PublicKey
  deriving stock (Verified -> Verified -> Bool
(Verified -> Verified -> Bool)
-> (Verified -> Verified -> Bool) -> Eq Verified
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Verified -> Verified -> Bool
$c/= :: Verified -> Verified -> Bool
== :: Verified -> Verified -> Bool
$c== :: Verified -> Verified -> Bool
Eq, Int -> Verified -> ShowS
[Verified] -> ShowS
Verified -> String
(Int -> Verified -> ShowS)
-> (Verified -> String) -> ([Verified] -> ShowS) -> Show Verified
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Verified] -> ShowS
$cshowList :: [Verified] -> ShowS
show :: Verified -> String
$cshow :: Verified -> String
showsPrec :: Int -> Verified -> ShowS
$cshowsPrec :: Int -> Verified -> ShowS
Show)

-- | Marker that a biscuit was parsed without having its signatures verified. Such a biscuit
-- cannot be trusted yet.
data Unverified = Unverified
  deriving stock (Unverified -> Unverified -> Bool
(Unverified -> Unverified -> Bool)
-> (Unverified -> Unverified -> Bool) -> Eq Unverified
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Unverified -> Unverified -> Bool
$c/= :: Unverified -> Unverified -> Bool
== :: Unverified -> Unverified -> Bool
$c== :: Unverified -> Unverified -> Bool
Eq, Int -> Unverified -> ShowS
[Unverified] -> ShowS
Unverified -> String
(Int -> Unverified -> ShowS)
-> (Unverified -> String)
-> ([Unverified] -> ShowS)
-> Show Unverified
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Unverified] -> ShowS
$cshowList :: [Unverified] -> ShowS
show :: Unverified -> String
$cshow :: Unverified -> String
showsPrec :: Int -> Unverified -> ShowS
$cshowsPrec :: Int -> Unverified -> ShowS
Show)

-- | A parsed biscuit. The @proof@ type param can be one of 'Open', 'Sealed' or 'OpenOrSealed'.
-- It describes whether a biscuit is open to further attenuation, or sealed and not modifyable
-- further.
--
-- The @check@ type param can be either 'Verified' or 'Unverified' and keeps track of whether
-- the blocks signatures (and final proof) have been verified with a given root 'PublicKey'.
--
-- The constructor is not exposed in order to ensure that 'Biscuit' values can only be created
-- by trusted code paths.
data Biscuit proof check
  = Biscuit
  { Biscuit proof check -> Maybe Int
rootKeyId  :: Maybe Int
  -- ^ an optional identifier for the expected public key
  , Biscuit proof check -> Symbols
symbols    :: Symbols
  -- ^ The symbols already defined in the contained blocks
  , Biscuit proof check -> ParsedSignedBlock
authority  :: ParsedSignedBlock
  -- ^ The authority block, along with the associated public key. The public key
  -- is kept around since it's embedded in the serialized biscuit, but should not
  -- be used for verification. An externally provided public key should be used instead.
  , Biscuit proof check -> [ParsedSignedBlock]
blocks     :: [ParsedSignedBlock]
  -- ^ The extra blocks, along with the public keys needed
  , Biscuit proof check -> proof
proof      :: proof
  -- ^ The final proof allowing to check the validity of a biscuit
  , Biscuit proof check -> check
proofCheck :: check
  -- ^ A value that keeps track of whether the biscuit signatures have been verified or not.
  }
  deriving (Biscuit proof check -> Biscuit proof check -> Bool
(Biscuit proof check -> Biscuit proof check -> Bool)
-> (Biscuit proof check -> Biscuit proof check -> Bool)
-> Eq (Biscuit proof check)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall proof check.
(Eq proof, Eq check) =>
Biscuit proof check -> Biscuit proof check -> Bool
/= :: Biscuit proof check -> Biscuit proof check -> Bool
$c/= :: forall proof check.
(Eq proof, Eq check) =>
Biscuit proof check -> Biscuit proof check -> Bool
== :: Biscuit proof check -> Biscuit proof check -> Bool
$c== :: forall proof check.
(Eq proof, Eq check) =>
Biscuit proof check -> Biscuit proof check -> Bool
Eq, Int -> Biscuit proof check -> ShowS
[Biscuit proof check] -> ShowS
Biscuit proof check -> String
(Int -> Biscuit proof check -> ShowS)
-> (Biscuit proof check -> String)
-> ([Biscuit proof check] -> ShowS)
-> Show (Biscuit proof check)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall proof check.
(Show proof, Show check) =>
Int -> Biscuit proof check -> ShowS
forall proof check.
(Show proof, Show check) =>
[Biscuit proof check] -> ShowS
forall proof check.
(Show proof, Show check) =>
Biscuit proof check -> String
showList :: [Biscuit proof check] -> ShowS
$cshowList :: forall proof check.
(Show proof, Show check) =>
[Biscuit proof check] -> ShowS
show :: Biscuit proof check -> String
$cshow :: forall proof check.
(Show proof, Show check) =>
Biscuit proof check -> String
showsPrec :: Int -> Biscuit proof check -> ShowS
$cshowsPrec :: forall proof check.
(Show proof, Show check) =>
Int -> Biscuit proof check -> ShowS
Show)

-- | Turn a 'Biscuit' statically known to be 'Open' into a more generic 'OpenOrSealed' 'Biscuit'
-- (essentially /forgetting/ about the fact it's 'Open')
fromOpen :: Biscuit Open check -> Biscuit OpenOrSealed check
fromOpen :: Biscuit Open check -> Biscuit OpenOrSealed check
fromOpen b :: Biscuit Open check
b@Biscuit{proof :: forall proof check. Biscuit proof check -> proof
proof = Open SecretKey
p } = Biscuit Open check
b { proof :: OpenOrSealed
proof = SecretKey -> OpenOrSealed
OpenProof SecretKey
p }

-- | Turn a 'Biscuit' statically known to be 'Sealed' into a more generic 'OpenOrSealed' 'Biscuit'
-- (essentially /forgetting/ about the fact it's 'Sealed')
fromSealed :: Biscuit Sealed check -> Biscuit OpenOrSealed check
fromSealed :: Biscuit Sealed check -> Biscuit OpenOrSealed check
fromSealed b :: Biscuit Sealed check
b@Biscuit{proof :: forall proof check. Biscuit proof check -> proof
proof = Sealed Signature
p } = Biscuit Sealed check
b { proof :: OpenOrSealed
proof = Signature -> OpenOrSealed
SealedProof Signature
p }

-- | Try to turn a 'Biscuit' that may be open or sealed into a biscuit that's statically known
-- to be 'Sealed'.
asSealed :: Biscuit OpenOrSealed check -> Maybe (Biscuit Sealed check)
asSealed :: Biscuit OpenOrSealed check -> Maybe (Biscuit Sealed check)
asSealed b :: Biscuit OpenOrSealed check
b@Biscuit{OpenOrSealed
proof :: OpenOrSealed
proof :: forall proof check. Biscuit proof check -> proof
proof} = case OpenOrSealed
proof of
  SealedProof Signature
p -> Biscuit Sealed check -> Maybe (Biscuit Sealed check)
forall a. a -> Maybe a
Just (Biscuit Sealed check -> Maybe (Biscuit Sealed check))
-> Biscuit Sealed check -> Maybe (Biscuit Sealed check)
forall a b. (a -> b) -> a -> b
$ Biscuit OpenOrSealed check
b { proof :: Sealed
proof = Signature -> Sealed
Sealed Signature
p }
  OpenOrSealed
_             -> Maybe (Biscuit Sealed check)
forall a. Maybe a
Nothing

-- | Try to turn a 'Biscuit' that may be open or sealed into a biscuit that's statically known
-- to be 'Open'.
asOpen :: Biscuit OpenOrSealed check -> Maybe (Biscuit Open check)
asOpen :: Biscuit OpenOrSealed check -> Maybe (Biscuit Open check)
asOpen b :: Biscuit OpenOrSealed check
b@Biscuit{OpenOrSealed
proof :: OpenOrSealed
proof :: forall proof check. Biscuit proof check -> proof
proof}   = case OpenOrSealed
proof of
  OpenProof SecretKey
p -> Biscuit Open check -> Maybe (Biscuit Open check)
forall a. a -> Maybe a
Just (Biscuit Open check -> Maybe (Biscuit Open check))
-> Biscuit Open check -> Maybe (Biscuit Open check)
forall a b. (a -> b) -> a -> b
$ Biscuit OpenOrSealed check
b { proof :: Open
proof = SecretKey -> Open
Open SecretKey
p }
  OpenOrSealed
_           -> Maybe (Biscuit Open check)
forall a. Maybe a
Nothing

toParsedSignedBlock :: Block -> SignedBlock -> ParsedSignedBlock
toParsedSignedBlock :: Block -> SignedBlock -> ParsedSignedBlock
toParsedSignedBlock Block
block (ByteString
serializedBlock, Signature
sig, PublicKey
pk) = ((ByteString
serializedBlock, Block
block), Signature
sig, PublicKey
pk)

-- | Create a new biscuit with the provided authority block. Such a biscuit is 'Open' to
-- further attenuation.
mkBiscuit :: SecretKey -> Block -> IO (Biscuit Open Verified)
mkBiscuit :: SecretKey -> Block -> IO (Biscuit Open Verified)
mkBiscuit SecretKey
sk Block
authority = do
  let (Symbols
authoritySymbols, ByteString
authoritySerialized) = Block -> ByteString
PB.encodeBlock (Block -> ByteString) -> (Symbols, Block) -> (Symbols, ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Symbols -> Block -> (Symbols, Block)
blockToPb Symbols
commonSymbols Block
authority
  (SignedBlock
signedBlock, SecretKey
nextSk) <- SecretKey -> ByteString -> IO (SignedBlock, SecretKey)
signBlock SecretKey
sk ByteString
authoritySerialized
  Biscuit Open Verified -> IO (Biscuit Open Verified)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Biscuit :: forall proof check.
Maybe Int
-> Symbols
-> ParsedSignedBlock
-> [ParsedSignedBlock]
-> proof
-> check
-> Biscuit proof check
Biscuit { rootKeyId :: Maybe Int
rootKeyId = Maybe Int
forall a. Maybe a
Nothing
               , authority :: ParsedSignedBlock
authority = Block -> SignedBlock -> ParsedSignedBlock
toParsedSignedBlock Block
authority SignedBlock
signedBlock
               , blocks :: [ParsedSignedBlock]
blocks = []
               , symbols :: Symbols
symbols = Symbols
commonSymbols Symbols -> Symbols -> Symbols
forall a. Semigroup a => a -> a -> a
<> Symbols
authoritySymbols
               , proof :: Open
proof = SecretKey -> Open
Open SecretKey
nextSk
               , proofCheck :: Verified
proofCheck = PublicKey -> Verified
Verified (PublicKey -> Verified) -> PublicKey -> Verified
forall a b. (a -> b) -> a -> b
$ SecretKey -> PublicKey
toPublic SecretKey
sk
               }

-- | Add a block to an existing biscuit. Only 'Open' biscuits can be attenuated; the
-- newly created biscuit is 'Open' as well.
addBlock :: Block
         -> Biscuit Open check
         -> IO (Biscuit Open check)
addBlock :: Block -> Biscuit Open check -> IO (Biscuit Open check)
addBlock Block
block b :: Biscuit Open check
b@Biscuit{check
[ParsedSignedBlock]
Maybe Int
ParsedSignedBlock
Symbols
Open
proofCheck :: check
proof :: Open
blocks :: [ParsedSignedBlock]
authority :: ParsedSignedBlock
symbols :: Symbols
rootKeyId :: Maybe Int
proofCheck :: forall proof check. Biscuit proof check -> check
proof :: forall proof check. Biscuit proof check -> proof
blocks :: forall proof check. Biscuit proof check -> [ParsedSignedBlock]
authority :: forall proof check. Biscuit proof check -> ParsedSignedBlock
symbols :: forall proof check. Biscuit proof check -> Symbols
rootKeyId :: forall proof check. Biscuit proof check -> Maybe Int
..} = do
  let (Symbols
blockSymbols, ByteString
blockSerialized) = Block -> ByteString
PB.encodeBlock (Block -> ByteString) -> (Symbols, Block) -> (Symbols, ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Symbols -> Block -> (Symbols, Block)
blockToPb Symbols
symbols Block
block
      Open SecretKey
p = Open
proof
  (SignedBlock
signedBlock, SecretKey
nextSk) <- SecretKey -> ByteString -> IO (SignedBlock, SecretKey)
signBlock SecretKey
p ByteString
blockSerialized
  Biscuit Open check -> IO (Biscuit Open check)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Biscuit Open check -> IO (Biscuit Open check))
-> Biscuit Open check -> IO (Biscuit Open check)
forall a b. (a -> b) -> a -> b
$ Biscuit Open check
b { blocks :: [ParsedSignedBlock]
blocks = [ParsedSignedBlock]
blocks [ParsedSignedBlock] -> [ParsedSignedBlock] -> [ParsedSignedBlock]
forall a. Semigroup a => a -> a -> a
<> [Block -> SignedBlock -> ParsedSignedBlock
toParsedSignedBlock Block
block SignedBlock
signedBlock]
           , symbols :: Symbols
symbols = Symbols
symbols Symbols -> Symbols -> Symbols
forall a. Semigroup a => a -> a -> a
<> Symbols
blockSymbols
           , proof :: Open
proof = SecretKey -> Open
Open SecretKey
nextSk
           }

-- | Turn an 'Open' biscuit into a 'Sealed' one, preventing it from being attenuated
-- further. A 'Sealed' biscuit cannot be turned into an 'Open' one.
seal :: Biscuit Open check -> Biscuit Sealed check
seal :: Biscuit Open check -> Biscuit Sealed check
seal b :: Biscuit Open check
b@Biscuit{check
[ParsedSignedBlock]
Maybe Int
ParsedSignedBlock
Symbols
Open
proofCheck :: check
proof :: Open
blocks :: [ParsedSignedBlock]
authority :: ParsedSignedBlock
symbols :: Symbols
rootKeyId :: Maybe Int
proofCheck :: forall proof check. Biscuit proof check -> check
proof :: forall proof check. Biscuit proof check -> proof
blocks :: forall proof check. Biscuit proof check -> [ParsedSignedBlock]
authority :: forall proof check. Biscuit proof check -> ParsedSignedBlock
symbols :: forall proof check. Biscuit proof check -> Symbols
rootKeyId :: forall proof check. Biscuit proof check -> Maybe Int
..} =
  let Open SecretKey
sk = Open
proof
      ((ByteString
lastPayload, Block
_), Signature
lastSig, PublicKey
lastPk) = NonEmpty ParsedSignedBlock -> ParsedSignedBlock
forall a. NonEmpty a -> a
NE.last (NonEmpty ParsedSignedBlock -> ParsedSignedBlock)
-> NonEmpty ParsedSignedBlock -> ParsedSignedBlock
forall a b. (a -> b) -> a -> b
$ ParsedSignedBlock
authority ParsedSignedBlock
-> [ParsedSignedBlock] -> NonEmpty ParsedSignedBlock
forall a. a -> [a] -> NonEmpty a
:| [ParsedSignedBlock]
blocks
      newProof :: Sealed
newProof = Signature -> Sealed
Sealed (Signature -> Sealed) -> Signature -> Sealed
forall a b. (a -> b) -> a -> b
$ SignedBlock -> SecretKey -> Signature
getSignatureProof (ByteString
lastPayload, Signature
lastSig, PublicKey
lastPk) SecretKey
sk
   in Biscuit Open check
b { proof :: Sealed
proof = Sealed
newProof }

-- | Serialize a biscuit to a raw bytestring
serializeBiscuit :: BiscuitProof p => Biscuit p Verified -> ByteString
serializeBiscuit :: Biscuit p Verified -> ByteString
serializeBiscuit Biscuit{p
[ParsedSignedBlock]
Maybe Int
ParsedSignedBlock
Symbols
Verified
proofCheck :: Verified
proof :: p
blocks :: [ParsedSignedBlock]
authority :: ParsedSignedBlock
symbols :: Symbols
rootKeyId :: Maybe Int
proofCheck :: forall proof check. Biscuit proof check -> check
proof :: forall proof check. Biscuit proof check -> proof
blocks :: forall proof check. Biscuit proof check -> [ParsedSignedBlock]
authority :: forall proof check. Biscuit proof check -> ParsedSignedBlock
symbols :: forall proof check. Biscuit proof check -> Symbols
rootKeyId :: forall proof check. Biscuit proof check -> Maybe Int
..} =
  let proofField :: Proof
proofField = case p -> OpenOrSealed
forall a. BiscuitProof a => a -> OpenOrSealed
toPossibleProofs p
proof of
          SealedProof Signature
sig -> Required 2 (Value ByteString) -> Proof
PB.ProofSignature (Required 2 (Value ByteString) -> Proof)
-> Required 2 (Value ByteString) -> Proof
forall a b. (a -> b) -> a -> b
$ FieldType (Field 2 (RequiredField (Always (Value ByteString))))
-> Field 2 (RequiredField (Always (Value ByteString)))
forall a. HasField a => FieldType a -> a
PB.putField (Signature -> ByteString
forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
bin -> bout
convert Signature
sig)
          OpenProof   SecretKey
sk  -> Required 1 (Value ByteString) -> Proof
PB.ProofSecret (Required 1 (Value ByteString) -> Proof)
-> Required 1 (Value ByteString) -> Proof
forall a b. (a -> b) -> a -> b
$ FieldType (Field 1 (RequiredField (Always (Value ByteString))))
-> Field 1 (RequiredField (Always (Value ByteString)))
forall a. HasField a => FieldType a -> a
PB.putField (SecretKey -> ByteString
forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
bin -> bout
convert SecretKey
sk)
   in Biscuit -> ByteString
PB.encodeBlockList Biscuit :: Optional 1 (Value Int32)
-> Required 2 (Message SignedBlock)
-> Repeated 3 (Message SignedBlock)
-> Required 4 (Message Proof)
-> Biscuit
PB.Biscuit
        { $sel:rootKeyId:Biscuit :: Optional 1 (Value Int32)
rootKeyId = FieldType (Field 1 (OptionalField (Last (Value Int32))))
-> Field 1 (OptionalField (Last (Value Int32)))
forall a. HasField a => FieldType a -> a
PB.putField FieldType (Field 1 (OptionalField (Last (Value Int32))))
forall a. Maybe a
Nothing -- TODO
        , $sel:authority:Biscuit :: Required 2 (Message SignedBlock)
authority = FieldType (Field 2 (RequiredField (Always (Message SignedBlock))))
-> Field 2 (RequiredField (Always (Message SignedBlock)))
forall a. HasField a => FieldType a -> a
PB.putField (FieldType (Field 2 (RequiredField (Always (Message SignedBlock))))
 -> Field 2 (RequiredField (Always (Message SignedBlock))))
-> FieldType
     (Field 2 (RequiredField (Always (Message SignedBlock))))
-> Field 2 (RequiredField (Always (Message SignedBlock)))
forall a b. (a -> b) -> a -> b
$ ParsedSignedBlock -> SignedBlock
toPBSignedBlock ParsedSignedBlock
authority
        , $sel:blocks:Biscuit :: Repeated 3 (Message SignedBlock)
blocks    = FieldType (Repeated 3 (Message SignedBlock))
-> Repeated 3 (Message SignedBlock)
forall a. HasField a => FieldType a -> a
PB.putField (FieldType (Repeated 3 (Message SignedBlock))
 -> Repeated 3 (Message SignedBlock))
-> FieldType (Repeated 3 (Message SignedBlock))
-> Repeated 3 (Message SignedBlock)
forall a b. (a -> b) -> a -> b
$ ParsedSignedBlock -> SignedBlock
toPBSignedBlock (ParsedSignedBlock -> SignedBlock)
-> [ParsedSignedBlock] -> [SignedBlock]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ParsedSignedBlock]
blocks
        , $sel:proof:Biscuit :: Required 4 (Message Proof)
proof     = FieldType (Field 4 (RequiredField (Always (Message Proof))))
-> Field 4 (RequiredField (Always (Message Proof)))
forall a. HasField a => FieldType a -> a
PB.putField FieldType (Field 4 (RequiredField (Always (Message Proof))))
Proof
proofField
        }

toPBSignedBlock :: ParsedSignedBlock -> PB.SignedBlock
toPBSignedBlock :: ParsedSignedBlock -> SignedBlock
toPBSignedBlock ((ByteString
block, Block
_), Signature
sig, PublicKey
pk) = SignedBlock -> SignedBlock
signedBlockToPb (ByteString
block, Signature
sig, PublicKey
pk)

-- | Errors that can happen when parsing a biscuit. Since complete parsing of a biscuit
-- requires a signature check, an invalid signature check is a parsing error
data ParseError
  = InvalidHexEncoding
  -- ^ The provided ByteString is not hex-encoded
  | InvalidB64Encoding
  -- ^ The provided ByteString is not base64-encoded
  | InvalidProtobufSer Bool String
  -- ^ The provided ByteString does not contain properly serialized protobuf values
  | InvalidProtobuf Bool String
  -- ^ The bytestring was correctly deserialized from protobuf, but the values can't be turned into a proper biscuit
  | InvalidSignatures
  -- ^ The signatures were invalid
  | InvalidProof
  -- ^ The biscuit final proof was invalid
  | RevokedBiscuit
  -- ^ The biscuit has been revoked
  deriving (ParseError -> ParseError -> Bool
(ParseError -> ParseError -> Bool)
-> (ParseError -> ParseError -> Bool) -> Eq ParseError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ParseError -> ParseError -> Bool
$c/= :: ParseError -> ParseError -> Bool
== :: ParseError -> ParseError -> Bool
$c== :: ParseError -> ParseError -> Bool
Eq, Int -> ParseError -> ShowS
[ParseError] -> ShowS
ParseError -> String
(Int -> ParseError -> ShowS)
-> (ParseError -> String)
-> ([ParseError] -> ShowS)
-> Show ParseError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ParseError] -> ShowS
$cshowList :: [ParseError] -> ShowS
show :: ParseError -> String
$cshow :: ParseError -> String
showsPrec :: Int -> ParseError -> ShowS
$cshowsPrec :: Int -> ParseError -> ShowS
Show)

data BiscuitWrapper
  = BiscuitWrapper
  { BiscuitWrapper -> SignedBlock
wAuthority :: SignedBlock
  , BiscuitWrapper -> [SignedBlock]
wBlocks    :: [SignedBlock]
  , BiscuitWrapper -> OpenOrSealed
wProof     :: OpenOrSealed
  , BiscuitWrapper -> Maybe Int
wRootKeyId :: Maybe Int
  }

parseBiscuitWrapper :: ByteString -> Either ParseError BiscuitWrapper
parseBiscuitWrapper :: ByteString -> Either ParseError BiscuitWrapper
parseBiscuitWrapper ByteString
bs = do
  Biscuit
blockList <- (String -> ParseError)
-> Either String Biscuit -> Either ParseError Biscuit
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (Bool -> String -> ParseError
InvalidProtobufSer Bool
True) (Either String Biscuit -> Either ParseError Biscuit)
-> Either String Biscuit -> Either ParseError Biscuit
forall a b. (a -> b) -> a -> b
$ ByteString -> Either String Biscuit
PB.decodeBlockList ByteString
bs
  let rootKeyId :: Maybe Int
rootKeyId = Int32 -> Int
forall a. Enum a => a -> Int
fromEnum (Int32 -> Int) -> Maybe Int32 -> Maybe Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Field 1 (OptionalField (Last (Value Int32)))
-> FieldType (Field 1 (OptionalField (Last (Value Int32))))
forall a. HasField a => a -> FieldType a
PB.getField (Biscuit -> Optional 1 (Value Int32)
PB.rootKeyId Biscuit
blockList)
  SignedBlock
signedAuthority <- (String -> ParseError)
-> Either String SignedBlock -> Either ParseError SignedBlock
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (Bool -> String -> ParseError
InvalidProtobuf Bool
True) (Either String SignedBlock -> Either ParseError SignedBlock)
-> Either String SignedBlock -> Either ParseError SignedBlock
forall a b. (a -> b) -> a -> b
$ SignedBlock -> Either String SignedBlock
pbToSignedBlock (SignedBlock -> Either String SignedBlock)
-> SignedBlock -> Either String SignedBlock
forall a b. (a -> b) -> a -> b
$ Field 2 (RequiredField (Always (Message SignedBlock)))
-> FieldType
     (Field 2 (RequiredField (Always (Message SignedBlock))))
forall a. HasField a => a -> FieldType a
PB.getField (Field 2 (RequiredField (Always (Message SignedBlock)))
 -> FieldType
      (Field 2 (RequiredField (Always (Message SignedBlock)))))
-> Field 2 (RequiredField (Always (Message SignedBlock)))
-> FieldType
     (Field 2 (RequiredField (Always (Message SignedBlock))))
forall a b. (a -> b) -> a -> b
$ Biscuit -> Required 2 (Message SignedBlock)
PB.authority Biscuit
blockList
  [SignedBlock]
signedBlocks    <- (String -> ParseError)
-> Either String [SignedBlock] -> Either ParseError [SignedBlock]
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (Bool -> String -> ParseError
InvalidProtobuf Bool
True) (Either String [SignedBlock] -> Either ParseError [SignedBlock])
-> Either String [SignedBlock] -> Either ParseError [SignedBlock]
forall a b. (a -> b) -> a -> b
$ (SignedBlock -> Either String SignedBlock)
-> [SignedBlock] -> Either String [SignedBlock]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse SignedBlock -> Either String SignedBlock
pbToSignedBlock ([SignedBlock] -> Either String [SignedBlock])
-> [SignedBlock] -> Either String [SignedBlock]
forall a b. (a -> b) -> a -> b
$ Repeated 3 (Message SignedBlock)
-> FieldType (Repeated 3 (Message SignedBlock))
forall a. HasField a => a -> FieldType a
PB.getField (Repeated 3 (Message SignedBlock)
 -> FieldType (Repeated 3 (Message SignedBlock)))
-> Repeated 3 (Message SignedBlock)
-> FieldType (Repeated 3 (Message SignedBlock))
forall a b. (a -> b) -> a -> b
$ Biscuit -> Repeated 3 (Message SignedBlock)
PB.blocks Biscuit
blockList
  Either Signature SecretKey
proof         <- (String -> ParseError)
-> Either String (Either Signature SecretKey)
-> Either ParseError (Either Signature SecretKey)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (Bool -> String -> ParseError
InvalidProtobuf Bool
True) (Either String (Either Signature SecretKey)
 -> Either ParseError (Either Signature SecretKey))
-> Either String (Either Signature SecretKey)
-> Either ParseError (Either Signature SecretKey)
forall a b. (a -> b) -> a -> b
$ Proof -> Either String (Either Signature SecretKey)
pbToProof (Proof -> Either String (Either Signature SecretKey))
-> Proof -> Either String (Either Signature SecretKey)
forall a b. (a -> b) -> a -> b
$ Field 4 (RequiredField (Always (Message Proof)))
-> FieldType (Field 4 (RequiredField (Always (Message Proof))))
forall a. HasField a => a -> FieldType a
PB.getField (Field 4 (RequiredField (Always (Message Proof)))
 -> FieldType (Field 4 (RequiredField (Always (Message Proof)))))
-> Field 4 (RequiredField (Always (Message Proof)))
-> FieldType (Field 4 (RequiredField (Always (Message Proof))))
forall a b. (a -> b) -> a -> b
$ Biscuit -> Required 4 (Message Proof)
PB.proof Biscuit
blockList

  BiscuitWrapper -> Either ParseError BiscuitWrapper
forall (f :: * -> *) a. Applicative f => a -> f a
pure (BiscuitWrapper -> Either ParseError BiscuitWrapper)
-> BiscuitWrapper -> Either ParseError BiscuitWrapper
forall a b. (a -> b) -> a -> b
$ BiscuitWrapper :: SignedBlock
-> [SignedBlock] -> OpenOrSealed -> Maybe Int -> BiscuitWrapper
BiscuitWrapper
    { wAuthority :: SignedBlock
wAuthority = SignedBlock
signedAuthority
    , wBlocks :: [SignedBlock]
wBlocks = [SignedBlock]
signedBlocks
    , wProof :: OpenOrSealed
wProof  = (Signature -> OpenOrSealed)
-> (SecretKey -> OpenOrSealed)
-> Either Signature SecretKey
-> OpenOrSealed
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either Signature -> OpenOrSealed
SealedProof
                       SecretKey -> OpenOrSealed
OpenProof
                       Either Signature SecretKey
proof
    , wRootKeyId :: Maybe Int
wRootKeyId = Maybe Int
rootKeyId
    , ..
    }

checkRevocation :: Applicative m
                => (Set ByteString -> m Bool)
                -> BiscuitWrapper
                -> m (Either ParseError BiscuitWrapper)
checkRevocation :: (Set ByteString -> m Bool)
-> BiscuitWrapper -> m (Either ParseError BiscuitWrapper)
checkRevocation Set ByteString -> m Bool
isRevoked bw :: BiscuitWrapper
bw@BiscuitWrapper{SignedBlock
wAuthority :: SignedBlock
wAuthority :: BiscuitWrapper -> SignedBlock
wAuthority,[SignedBlock]
wBlocks :: [SignedBlock]
wBlocks :: BiscuitWrapper -> [SignedBlock]
wBlocks} =
  let getRevocationId :: (a, bin, c) -> bout
getRevocationId (a
_, bin
sig, c
_) = bin -> bout
forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
bin -> bout
convert bin
sig
      revocationIds :: NonEmpty ByteString
revocationIds = SignedBlock -> ByteString
forall bout bin a c.
(ByteArray bout, ByteArrayAccess bin) =>
(a, bin, c) -> bout
getRevocationId (SignedBlock -> ByteString)
-> NonEmpty SignedBlock -> NonEmpty ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SignedBlock
wAuthority SignedBlock -> [SignedBlock] -> NonEmpty SignedBlock
forall a. a -> [a] -> NonEmpty a
:| [SignedBlock]
wBlocks
      keepIfNotRevoked :: Bool -> Either ParseError BiscuitWrapper
keepIfNotRevoked Bool
True  = ParseError -> Either ParseError BiscuitWrapper
forall a b. a -> Either a b
Left ParseError
RevokedBiscuit
      keepIfNotRevoked Bool
False = BiscuitWrapper -> Either ParseError BiscuitWrapper
forall a b. b -> Either a b
Right BiscuitWrapper
bw
   in Bool -> Either ParseError BiscuitWrapper
keepIfNotRevoked (Bool -> Either ParseError BiscuitWrapper)
-> m Bool -> m (Either ParseError BiscuitWrapper)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Set ByteString -> m Bool
isRevoked ([ByteString] -> Set ByteString
forall a. Ord a => [a] -> Set a
Set.fromList ([ByteString] -> Set ByteString) -> [ByteString] -> Set ByteString
forall a b. (a -> b) -> a -> b
$ NonEmpty ByteString -> [ByteString]
forall a. NonEmpty a -> [a]
NE.toList NonEmpty ByteString
revocationIds)

parseBlocks :: BiscuitWrapper -> Either ParseError (Symbols, NonEmpty ParsedSignedBlock)
parseBlocks :: BiscuitWrapper
-> Either ParseError (Symbols, NonEmpty ParsedSignedBlock)
parseBlocks BiscuitWrapper{[SignedBlock]
Maybe Int
SignedBlock
OpenOrSealed
wRootKeyId :: Maybe Int
wProof :: OpenOrSealed
wBlocks :: [SignedBlock]
wAuthority :: SignedBlock
wRootKeyId :: BiscuitWrapper -> Maybe Int
wProof :: BiscuitWrapper -> OpenOrSealed
wBlocks :: BiscuitWrapper -> [SignedBlock]
wAuthority :: BiscuitWrapper -> SignedBlock
..} = do
  let toRawSignedBlock :: (ByteString, b, c) -> Either ParseError ((ByteString, Block), b, c)
toRawSignedBlock (ByteString
payload, b
sig, c
pk') = do
        Block
pbBlock <- (String -> ParseError)
-> Either String Block -> Either ParseError Block
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (Bool -> String -> ParseError
InvalidProtobufSer Bool
False) (Either String Block -> Either ParseError Block)
-> Either String Block -> Either ParseError Block
forall a b. (a -> b) -> a -> b
$ ByteString -> Either String Block
PB.decodeBlock ByteString
payload
        ((ByteString, Block), b, c)
-> Either ParseError ((ByteString, Block), b, c)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((ByteString
payload, Block
pbBlock), b
sig, c
pk')

  ((ByteString, Block), Signature, PublicKey)
rawAuthority <- SignedBlock
-> Either ParseError ((ByteString, Block), Signature, PublicKey)
forall b c.
(ByteString, b, c) -> Either ParseError ((ByteString, Block), b, c)
toRawSignedBlock SignedBlock
wAuthority
  [((ByteString, Block), Signature, PublicKey)]
rawBlocks    <- (SignedBlock
 -> Either ParseError ((ByteString, Block), Signature, PublicKey))
-> [SignedBlock]
-> Either ParseError [((ByteString, Block), Signature, PublicKey)]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse SignedBlock
-> Either ParseError ((ByteString, Block), Signature, PublicKey)
forall b c.
(ByteString, b, c) -> Either ParseError ((ByteString, Block), b, c)
toRawSignedBlock [SignedBlock]
wBlocks

  let symbols :: Symbols
symbols = Symbols -> [Block] -> Symbols
extractSymbols Symbols
commonSymbols ([Block] -> Symbols) -> [Block] -> Symbols
forall a b. (a -> b) -> a -> b
$ (\((ByteString
_, Block
p), Signature
_, PublicKey
_) -> Block
p) (((ByteString, Block), Signature, PublicKey) -> Block)
-> [((ByteString, Block), Signature, PublicKey)] -> [Block]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((ByteString, Block), Signature, PublicKey)
rawAuthority ((ByteString, Block), Signature, PublicKey)
-> [((ByteString, Block), Signature, PublicKey)]
-> [((ByteString, Block), Signature, PublicKey)]
forall a. a -> [a] -> [a]
: [((ByteString, Block), Signature, PublicKey)]
rawBlocks

  ParsedSignedBlock
authority <- Symbols
-> ((ByteString, Block), Signature, PublicKey)
-> Either ParseError ParsedSignedBlock
rawSignedBlockToParsedSignedBlock Symbols
symbols ((ByteString, Block), Signature, PublicKey)
rawAuthority
  [ParsedSignedBlock]
blocks    <- (((ByteString, Block), Signature, PublicKey)
 -> Either ParseError ParsedSignedBlock)
-> [((ByteString, Block), Signature, PublicKey)]
-> Either ParseError [ParsedSignedBlock]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (Symbols
-> ((ByteString, Block), Signature, PublicKey)
-> Either ParseError ParsedSignedBlock
rawSignedBlockToParsedSignedBlock Symbols
symbols) [((ByteString, Block), Signature, PublicKey)]
rawBlocks
  (Symbols, NonEmpty ParsedSignedBlock)
-> Either ParseError (Symbols, NonEmpty ParsedSignedBlock)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Symbols
symbols, ParsedSignedBlock
authority ParsedSignedBlock
-> [ParsedSignedBlock] -> NonEmpty ParsedSignedBlock
forall a. a -> [a] -> NonEmpty a
:| [ParsedSignedBlock]
blocks)

-- | Parse a biscuit without performing any signatures check. This function is intended to
-- provide tooling (eg adding a block, or inspecting a biscuit) without having to verify
-- its signatures. Running an 'Authorizer' is not possible without checking signatures.
-- 'checkBiscuitSignatures' allows a delayed signature check. For normal auth workflows,
-- please use 'parseWith' (or 'parse', or 'parseB64') instead, as they check signatures
-- before completely parsing the biscuit.
parseBiscuitUnverified :: ByteString -> Either ParseError (Biscuit OpenOrSealed Unverified)
parseBiscuitUnverified :: ByteString -> Either ParseError (Biscuit OpenOrSealed Unverified)
parseBiscuitUnverified ByteString
bs = do
  w :: BiscuitWrapper
w@BiscuitWrapper{[SignedBlock]
Maybe Int
SignedBlock
OpenOrSealed
wRootKeyId :: Maybe Int
wProof :: OpenOrSealed
wBlocks :: [SignedBlock]
wAuthority :: SignedBlock
wRootKeyId :: BiscuitWrapper -> Maybe Int
wProof :: BiscuitWrapper -> OpenOrSealed
wBlocks :: BiscuitWrapper -> [SignedBlock]
wAuthority :: BiscuitWrapper -> SignedBlock
..} <- ByteString -> Either ParseError BiscuitWrapper
parseBiscuitWrapper ByteString
bs
  (Symbols
symbols, ParsedSignedBlock
authority :| [ParsedSignedBlock]
blocks) <- BiscuitWrapper
-> Either ParseError (Symbols, NonEmpty ParsedSignedBlock)
parseBlocks BiscuitWrapper
w
  Biscuit OpenOrSealed Unverified
-> Either ParseError (Biscuit OpenOrSealed Unverified)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Biscuit OpenOrSealed Unverified
 -> Either ParseError (Biscuit OpenOrSealed Unverified))
-> Biscuit OpenOrSealed Unverified
-> Either ParseError (Biscuit OpenOrSealed Unverified)
forall a b. (a -> b) -> a -> b
$ Biscuit :: forall proof check.
Maybe Int
-> Symbols
-> ParsedSignedBlock
-> [ParsedSignedBlock]
-> proof
-> check
-> Biscuit proof check
Biscuit { rootKeyId :: Maybe Int
rootKeyId = Maybe Int
wRootKeyId
                 , proof :: OpenOrSealed
proof = OpenOrSealed
wProof
                 , proofCheck :: Unverified
proofCheck = Unverified
Unverified
                 , [ParsedSignedBlock]
ParsedSignedBlock
Symbols
blocks :: [ParsedSignedBlock]
authority :: ParsedSignedBlock
symbols :: Symbols
blocks :: [ParsedSignedBlock]
authority :: ParsedSignedBlock
symbols :: Symbols
.. }

parseBiscuit' :: PublicKey -> BiscuitWrapper -> Either ParseError (Biscuit OpenOrSealed Verified)
parseBiscuit' :: PublicKey
-> BiscuitWrapper
-> Either ParseError (Biscuit OpenOrSealed Verified)
parseBiscuit' PublicKey
pk w :: BiscuitWrapper
w@BiscuitWrapper{[SignedBlock]
Maybe Int
SignedBlock
OpenOrSealed
wRootKeyId :: Maybe Int
wProof :: OpenOrSealed
wBlocks :: [SignedBlock]
wAuthority :: SignedBlock
wRootKeyId :: BiscuitWrapper -> Maybe Int
wProof :: BiscuitWrapper -> OpenOrSealed
wBlocks :: BiscuitWrapper -> [SignedBlock]
wAuthority :: BiscuitWrapper -> SignedBlock
..} = do
  let allBlocks :: NonEmpty SignedBlock
allBlocks = SignedBlock
wAuthority SignedBlock -> [SignedBlock] -> NonEmpty SignedBlock
forall a. a -> [a] -> NonEmpty a
:| [SignedBlock]
wBlocks
  let blocksResult :: Bool
blocksResult = NonEmpty SignedBlock -> PublicKey -> Bool
verifyBlocks NonEmpty SignedBlock
allBlocks PublicKey
pk
  let proofResult :: Bool
proofResult = case OpenOrSealed
wProof of
        SealedProof Signature
sig -> Signature -> SignedBlock -> Bool
verifySignatureProof Signature
sig (NonEmpty SignedBlock -> SignedBlock
forall a. NonEmpty a -> a
NE.last NonEmpty SignedBlock
allBlocks)
        OpenProof   SecretKey
sk  -> SecretKey -> SignedBlock -> Bool
verifySecretProof SecretKey
sk     (NonEmpty SignedBlock -> SignedBlock
forall a. NonEmpty a -> a
NE.last NonEmpty SignedBlock
allBlocks)
  Bool -> Either ParseError () -> Either ParseError ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not Bool
blocksResult Bool -> Bool -> Bool
|| Bool -> Bool
not Bool
proofResult) (Either ParseError () -> Either ParseError ())
-> Either ParseError () -> Either ParseError ()
forall a b. (a -> b) -> a -> b
$ ParseError -> Either ParseError ()
forall a b. a -> Either a b
Left ParseError
InvalidSignatures

  (Symbols
symbols, ParsedSignedBlock
authority :| [ParsedSignedBlock]
blocks) <- BiscuitWrapper
-> Either ParseError (Symbols, NonEmpty ParsedSignedBlock)
parseBlocks BiscuitWrapper
w
  Biscuit OpenOrSealed Verified
-> Either ParseError (Biscuit OpenOrSealed Verified)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Biscuit OpenOrSealed Verified
 -> Either ParseError (Biscuit OpenOrSealed Verified))
-> Biscuit OpenOrSealed Verified
-> Either ParseError (Biscuit OpenOrSealed Verified)
forall a b. (a -> b) -> a -> b
$ Biscuit :: forall proof check.
Maybe Int
-> Symbols
-> ParsedSignedBlock
-> [ParsedSignedBlock]
-> proof
-> check
-> Biscuit proof check
Biscuit { rootKeyId :: Maybe Int
rootKeyId = Maybe Int
wRootKeyId
                 , proof :: OpenOrSealed
proof = OpenOrSealed
wProof
                 , proofCheck :: Verified
proofCheck = PublicKey -> Verified
Verified PublicKey
pk
                 , [ParsedSignedBlock]
ParsedSignedBlock
Symbols
blocks :: [ParsedSignedBlock]
authority :: ParsedSignedBlock
symbols :: Symbols
blocks :: [ParsedSignedBlock]
authority :: ParsedSignedBlock
symbols :: Symbols
.. }

-- | Check the signatures (and final proof) of an already parsed biscuit. These checks normally
-- happen during the parsing phase, but can be delayed (or even ignored) in some cases. This
-- fuction allows to turn a 'Unverified' 'Biscuit' into a 'Verified' one after it has been parsed
-- with 'parseBiscuitUnverified'.
checkBiscuitSignatures :: BiscuitProof proof
                       => (Maybe Int -> PublicKey)
                       -> Biscuit proof Unverified
                       -> Either ParseError (Biscuit proof Verified)
checkBiscuitSignatures :: (Maybe Int -> PublicKey)
-> Biscuit proof Unverified
-> Either ParseError (Biscuit proof Verified)
checkBiscuitSignatures Maybe Int -> PublicKey
getPublicKey b :: Biscuit proof Unverified
b@Biscuit{proof
[ParsedSignedBlock]
Maybe Int
ParsedSignedBlock
Symbols
Unverified
proofCheck :: Unverified
proof :: proof
blocks :: [ParsedSignedBlock]
authority :: ParsedSignedBlock
symbols :: Symbols
rootKeyId :: Maybe Int
proofCheck :: forall proof check. Biscuit proof check -> check
proof :: forall proof check. Biscuit proof check -> proof
blocks :: forall proof check. Biscuit proof check -> [ParsedSignedBlock]
authority :: forall proof check. Biscuit proof check -> ParsedSignedBlock
symbols :: forall proof check. Biscuit proof check -> Symbols
rootKeyId :: forall proof check. Biscuit proof check -> Maybe Int
..} = do
  let pk :: PublicKey
pk = Maybe Int -> PublicKey
getPublicKey Maybe Int
rootKeyId
      toSignedBlock :: ((a, b), b, c) -> (a, b, c)
toSignedBlock ((a
payload, b
_), b
sig, c
nextPk) = (a
payload, b
sig, c
nextPk)
      allBlocks :: NonEmpty SignedBlock
allBlocks = ParsedSignedBlock -> SignedBlock
forall a b b c. ((a, b), b, c) -> (a, b, c)
toSignedBlock (ParsedSignedBlock -> SignedBlock)
-> NonEmpty ParsedSignedBlock -> NonEmpty SignedBlock
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ParsedSignedBlock
authority ParsedSignedBlock
-> [ParsedSignedBlock] -> NonEmpty ParsedSignedBlock
forall a. a -> [a] -> NonEmpty a
:| [ParsedSignedBlock]
blocks)
      blocksResult :: Bool
blocksResult = NonEmpty SignedBlock -> PublicKey -> Bool
verifyBlocks NonEmpty SignedBlock
allBlocks PublicKey
pk
      proofResult :: Bool
proofResult = case proof -> OpenOrSealed
forall a. BiscuitProof a => a -> OpenOrSealed
toPossibleProofs proof
proof of
        SealedProof Signature
sig -> Signature -> SignedBlock -> Bool
verifySignatureProof Signature
sig (NonEmpty SignedBlock -> SignedBlock
forall a. NonEmpty a -> a
NE.last NonEmpty SignedBlock
allBlocks)
        OpenProof   SecretKey
sk  -> SecretKey -> SignedBlock -> Bool
verifySecretProof SecretKey
sk     (NonEmpty SignedBlock -> SignedBlock
forall a. NonEmpty a -> a
NE.last NonEmpty SignedBlock
allBlocks)
  Bool -> Either ParseError () -> Either ParseError ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not Bool
blocksResult Bool -> Bool -> Bool
|| Bool -> Bool
not Bool
proofResult) (Either ParseError () -> Either ParseError ())
-> Either ParseError () -> Either ParseError ()
forall a b. (a -> b) -> a -> b
$ ParseError -> Either ParseError ()
forall a b. a -> Either a b
Left ParseError
InvalidSignatures
  Biscuit proof Verified
-> Either ParseError (Biscuit proof Verified)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Biscuit proof Verified
 -> Either ParseError (Biscuit proof Verified))
-> Biscuit proof Verified
-> Either ParseError (Biscuit proof Verified)
forall a b. (a -> b) -> a -> b
$ Biscuit proof Unverified
b { proofCheck :: Verified
proofCheck = PublicKey -> Verified
Verified PublicKey
pk }

-- | Biscuits can be transmitted as raw bytes, or as base64-encoded text. This datatype
-- lets the parser know about the expected encoding.
data BiscuitEncoding
  = RawBytes
  | UrlBase64

-- | Parsing a biscuit involves various steps. This data type allows configuring those steps.
data ParserConfig m
  = ParserConfig
  { ParserConfig m -> BiscuitEncoding
encoding     :: BiscuitEncoding
  -- ^ Is the biscuit base64-encoded, or is it raw binary?
  , ParserConfig m -> Set ByteString -> m Bool
isRevoked    :: Set ByteString -> m Bool
  -- ^ Has one of the token blocks been revoked?
  -- 'fromRevocationList' lets you build this function from a static revocation list
  , ParserConfig m -> Maybe Int -> PublicKey
getPublicKey :: Maybe Int -> PublicKey
  -- ^ How to select the public key based on the token 'rootKeyId'
  }

parseBiscuitWith :: Applicative m
                 => ParserConfig m
                 -> ByteString
                 -> m (Either ParseError (Biscuit OpenOrSealed Verified))
parseBiscuitWith :: ParserConfig m
-> ByteString
-> m (Either ParseError (Biscuit OpenOrSealed Verified))
parseBiscuitWith ParserConfig{BiscuitEncoding
Maybe Int -> PublicKey
Set ByteString -> m Bool
getPublicKey :: Maybe Int -> PublicKey
isRevoked :: Set ByteString -> m Bool
encoding :: BiscuitEncoding
getPublicKey :: forall (m :: * -> *). ParserConfig m -> Maybe Int -> PublicKey
isRevoked :: forall (m :: * -> *). ParserConfig m -> Set ByteString -> m Bool
encoding :: forall (m :: * -> *). ParserConfig m -> BiscuitEncoding
..} ByteString
bs =
  let input :: Either ParseError ByteString
input = case BiscuitEncoding
encoding of
        BiscuitEncoding
RawBytes  -> ByteString -> Either ParseError ByteString
forall a b. b -> Either a b
Right ByteString
bs
        BiscuitEncoding
UrlBase64 -> (Text -> ParseError)
-> Either Text ByteString -> Either ParseError ByteString
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (ParseError -> Text -> ParseError
forall a b. a -> b -> a
const ParseError
InvalidB64Encoding) (Either Text ByteString -> Either ParseError ByteString)
-> (ByteString -> Either Text ByteString)
-> ByteString
-> Either ParseError ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either Text ByteString
B64.decodeBase64 (ByteString -> Either ParseError ByteString)
-> ByteString -> Either ParseError ByteString
forall a b. (a -> b) -> a -> b
$ ByteString
bs
      parsedWrapper :: Either ParseError BiscuitWrapper
parsedWrapper = ByteString -> Either ParseError BiscuitWrapper
parseBiscuitWrapper (ByteString -> Either ParseError BiscuitWrapper)
-> Either ParseError ByteString -> Either ParseError BiscuitWrapper
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Either ParseError ByteString
input
      wrapperToBiscuit :: BiscuitWrapper
-> m (Either ParseError (Biscuit OpenOrSealed Verified))
wrapperToBiscuit w :: BiscuitWrapper
w@BiscuitWrapper{Maybe Int
wRootKeyId :: Maybe Int
wRootKeyId :: BiscuitWrapper -> Maybe Int
wRootKeyId} =
        let pk :: PublicKey
pk = Maybe Int -> PublicKey
getPublicKey Maybe Int
wRootKeyId
         in (PublicKey
-> BiscuitWrapper
-> Either ParseError (Biscuit OpenOrSealed Verified)
parseBiscuit' PublicKey
pk (BiscuitWrapper
 -> Either ParseError (Biscuit OpenOrSealed Verified))
-> Either ParseError BiscuitWrapper
-> Either ParseError (Biscuit OpenOrSealed Verified)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<<) (Either ParseError BiscuitWrapper
 -> Either ParseError (Biscuit OpenOrSealed Verified))
-> m (Either ParseError BiscuitWrapper)
-> m (Either ParseError (Biscuit OpenOrSealed Verified))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Set ByteString -> m Bool)
-> BiscuitWrapper -> m (Either ParseError BiscuitWrapper)
forall (m :: * -> *).
Applicative m =>
(Set ByteString -> m Bool)
-> BiscuitWrapper -> m (Either ParseError BiscuitWrapper)
checkRevocation Set ByteString -> m Bool
isRevoked BiscuitWrapper
w
   in Either
  ParseError (Either ParseError (Biscuit OpenOrSealed Verified))
-> Either ParseError (Biscuit OpenOrSealed Verified)
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (Either
   ParseError (Either ParseError (Biscuit OpenOrSealed Verified))
 -> Either ParseError (Biscuit OpenOrSealed Verified))
-> m (Either
        ParseError (Either ParseError (Biscuit OpenOrSealed Verified)))
-> m (Either ParseError (Biscuit OpenOrSealed Verified))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (BiscuitWrapper
 -> m (Either ParseError (Biscuit OpenOrSealed Verified)))
-> Either ParseError BiscuitWrapper
-> m (Either
        ParseError (Either ParseError (Biscuit OpenOrSealed Verified)))
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse BiscuitWrapper
-> m (Either ParseError (Biscuit OpenOrSealed Verified))
wrapperToBiscuit Either ParseError BiscuitWrapper
parsedWrapper

rawSignedBlockToParsedSignedBlock :: Symbols
                                  -> ((ByteString, PB.Block), Signature, PublicKey)
                                  -> Either ParseError ParsedSignedBlock
rawSignedBlockToParsedSignedBlock :: Symbols
-> ((ByteString, Block), Signature, PublicKey)
-> Either ParseError ParsedSignedBlock
rawSignedBlockToParsedSignedBlock Symbols
s ((ByteString
payload, Block
pbBlock), Signature
sig, PublicKey
pk) = do
  Block
block   <- (String -> ParseError)
-> Either String Block -> Either ParseError Block
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (Bool -> String -> ParseError
InvalidProtobuf Bool
False) (Either String Block -> Either ParseError Block)
-> Either String Block -> Either ParseError Block
forall a b. (a -> b) -> a -> b
$ Symbols -> Block -> Either String Block
pbToBlock Symbols
s Block
pbBlock
  ParsedSignedBlock -> Either ParseError ParsedSignedBlock
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((ByteString
payload, Block
block), Signature
sig, PublicKey
pk)

-- | Extract the list of revocation ids from a biscuit.
-- To reject revoked biscuits, please use 'parseWith' instead. This function
-- should only be used for debugging purposes.
getRevocationIds :: Biscuit proof check -> NonEmpty ByteString
getRevocationIds :: Biscuit proof check -> NonEmpty ByteString
getRevocationIds Biscuit{ParsedSignedBlock
authority :: ParsedSignedBlock
authority :: forall proof check. Biscuit proof check -> ParsedSignedBlock
authority, [ParsedSignedBlock]
blocks :: [ParsedSignedBlock]
blocks :: forall proof check. Biscuit proof check -> [ParsedSignedBlock]
blocks} =
  let allBlocks :: NonEmpty ParsedSignedBlock
allBlocks = ParsedSignedBlock
authority ParsedSignedBlock
-> [ParsedSignedBlock] -> NonEmpty ParsedSignedBlock
forall a. a -> [a] -> NonEmpty a
:| [ParsedSignedBlock]
blocks
      getRevocationId :: (a, bin, c) -> bout
getRevocationId (a
_, bin
sig, c
_) = bin -> bout
forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
bin -> bout
convert bin
sig
   in ParsedSignedBlock -> ByteString
forall bout bin a c.
(ByteArray bout, ByteArrayAccess bin) =>
(a, bin, c) -> bout
getRevocationId (ParsedSignedBlock -> ByteString)
-> NonEmpty ParsedSignedBlock -> NonEmpty ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NonEmpty ParsedSignedBlock
allBlocks

-- | Generic version of 'authorizeBiscuitWithLimits' which takes custom 'Limits'.
authorizeBiscuitWithLimits :: Limits -> Biscuit a Verified -> Authorizer -> IO (Either ExecutionError AuthorizationSuccess)
authorizeBiscuitWithLimits :: Limits
-> Biscuit a Verified
-> Authorizer
-> IO (Either ExecutionError AuthorizationSuccess)
authorizeBiscuitWithLimits Limits
l Biscuit{a
[ParsedSignedBlock]
Maybe Int
ParsedSignedBlock
Symbols
Verified
proofCheck :: Verified
proof :: a
blocks :: [ParsedSignedBlock]
authority :: ParsedSignedBlock
symbols :: Symbols
rootKeyId :: Maybe Int
proofCheck :: forall proof check. Biscuit proof check -> check
proof :: forall proof check. Biscuit proof check -> proof
blocks :: forall proof check. Biscuit proof check -> [ParsedSignedBlock]
authority :: forall proof check. Biscuit proof check -> ParsedSignedBlock
symbols :: forall proof check. Biscuit proof check -> Symbols
rootKeyId :: forall proof check. Biscuit proof check -> Maybe Int
..} Authorizer
authorizer =
  let toBlockWithRevocationId :: ((a, a), bin, c) -> (a, b)
toBlockWithRevocationId ((a
_, a
block), bin
sig, c
_) = (a
block, bin -> b
forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
bin -> bout
convert bin
sig)
   in Limits
-> BlockWithRevocationId
-> [BlockWithRevocationId]
-> Authorizer
-> IO (Either ExecutionError AuthorizationSuccess)
runAuthorizerWithLimits Limits
l
        (ParsedSignedBlock -> BlockWithRevocationId
forall b bin a a c.
(ByteArray b, ByteArrayAccess bin) =>
((a, a), bin, c) -> (a, b)
toBlockWithRevocationId ParsedSignedBlock
authority)
        (ParsedSignedBlock -> BlockWithRevocationId
forall b bin a a c.
(ByteArray b, ByteArrayAccess bin) =>
((a, a), bin, c) -> (a, b)
toBlockWithRevocationId (ParsedSignedBlock -> BlockWithRevocationId)
-> [ParsedSignedBlock] -> [BlockWithRevocationId]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ParsedSignedBlock]
blocks)
        Authorizer
authorizer

-- | Given a biscuit with a verified signature and an authorizer (a set of facts, rules, checks
-- and policies), verify a biscuit:
--
-- - all the checks declared in the biscuit and authorizer must pass
-- - an allow policy provided by the authorizer has to match (policies are tried in order)
-- - the datalog computation must happen in an alloted time, with a capped number of generated
--   facts and a capped number of iterations
--
-- checks and policies declared in the authorizer only operate on the authority block. Facts
-- declared by extra blocks cannot interfere with previous blocks.
--
-- Specific runtime limits can be specified by using 'authorizeBiscuitWithLimits'. 'authorizeBiscuit'
-- uses a set of defaults defined in 'defaultLimits'.
authorizeBiscuit :: Biscuit proof Verified -> Authorizer -> IO (Either ExecutionError AuthorizationSuccess)
authorizeBiscuit :: Biscuit proof Verified
-> Authorizer -> IO (Either ExecutionError AuthorizationSuccess)
authorizeBiscuit = Limits
-> Biscuit proof Verified
-> Authorizer
-> IO (Either ExecutionError AuthorizationSuccess)
forall a.
Limits
-> Biscuit a Verified
-> Authorizer
-> IO (Either ExecutionError AuthorizationSuccess)
authorizeBiscuitWithLimits Limits
defaultLimits

-- | Retrieve the `PublicKey` which was used to verify the `Biscuit` signatures
getVerifiedBiscuitPublicKey :: Biscuit a Verified -> PublicKey
getVerifiedBiscuitPublicKey :: Biscuit a Verified -> PublicKey
getVerifiedBiscuitPublicKey Biscuit{Verified
proofCheck :: Verified
proofCheck :: forall proof check. Biscuit proof check -> check
proofCheck} =
  let Verified PublicKey
pk = Verified
proofCheck
   in PublicKey
pk