biscuit-haskell-0.2.0.0: Library support for the Biscuit security token
Copyright© Clément Delafargue 2021
LicenseMIT
Maintainerclement@delafargue.name
Safe HaskellNone
LanguageHaskell2010

Auth.Biscuit.Token

Description

Module defining the main biscuit-related operations

Synopsis

Documentation

data Biscuit proof check Source #

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.

Instances

Instances details
(Eq proof, Eq check) => Eq (Biscuit proof check) Source # 
Instance details

Defined in Auth.Biscuit.Token

Methods

(==) :: Biscuit proof check -> Biscuit proof check -> Bool #

(/=) :: Biscuit proof check -> Biscuit proof check -> Bool #

(Show proof, Show check) => Show (Biscuit proof check) Source # 
Instance details

Defined in Auth.Biscuit.Token

Methods

showsPrec :: Int -> Biscuit proof check -> ShowS #

show :: Biscuit proof check -> String #

showList :: [Biscuit proof check] -> ShowS #

rootKeyId :: Biscuit proof check -> Maybe Int Source #

an optional identifier for the expected public key

symbols :: Biscuit proof check -> Symbols Source #

The symbols already defined in the contained blocks

authority :: Biscuit proof check -> ParsedSignedBlock Source #

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.

blocks :: Biscuit proof check -> [ParsedSignedBlock] Source #

The extra blocks, along with the public keys needed

proof :: Biscuit proof check -> proof Source #

The final proof allowing to check the validity of a biscuit

proofCheck :: Biscuit proof check -> check Source #

A value that keeps track of whether the biscuit signatures have been verified or not.

data ParseError Source #

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

Constructors

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

Instances

Instances details
Eq ParseError Source # 
Instance details

Defined in Auth.Biscuit.Token

Show ParseError Source # 
Instance details

Defined in Auth.Biscuit.Token

type ExistingBlock = (ByteString, Block) Source #

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.

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

data OpenOrSealed Source #

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.

Instances

Instances details
Eq OpenOrSealed Source # 
Instance details

Defined in Auth.Biscuit.Token

Show OpenOrSealed Source # 
Instance details

Defined in Auth.Biscuit.Token

BiscuitProof OpenOrSealed Source # 
Instance details

Defined in Auth.Biscuit.Token

data Open Source #

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.

Instances

Instances details
BiscuitProof Open Source # 
Instance details

Defined in Auth.Biscuit.Token

data Sealed Source #

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.

Instances

Instances details
BiscuitProof Sealed Source # 
Instance details

Defined in Auth.Biscuit.Token

class BiscuitProof a where Source #

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.

Instances

Instances details
BiscuitProof Sealed Source # 
Instance details

Defined in Auth.Biscuit.Token

BiscuitProof Open Source # 
Instance details

Defined in Auth.Biscuit.Token

BiscuitProof OpenOrSealed Source # 
Instance details

Defined in Auth.Biscuit.Token

data Verified Source #

Proof that a biscuit had its signatures verified with the carried root PublicKey

Instances

Instances details
Eq Verified Source # 
Instance details

Defined in Auth.Biscuit.Token

Show Verified Source # 
Instance details

Defined in Auth.Biscuit.Token

data Unverified Source #

Marker that a biscuit was parsed without having its signatures verified. Such a biscuit cannot be trusted yet.

Instances

Instances details
Eq Unverified Source # 
Instance details

Defined in Auth.Biscuit.Token

Show Unverified Source # 
Instance details

Defined in Auth.Biscuit.Token

mkBiscuit :: SecretKey -> Block -> IO (Biscuit Open Verified) Source #

Create a new biscuit with the provided authority block. Such a biscuit is Open to further attenuation.

addBlock :: Block -> Biscuit Open check -> IO (Biscuit Open check) Source #

Add a block to an existing biscuit. Only Open biscuits can be attenuated; the newly created biscuit is Open as well.

data BiscuitEncoding Source #

Biscuits can be transmitted as raw bytes, or as base64-encoded text. This datatype lets the parser know about the expected encoding.

Constructors

RawBytes 
UrlBase64 

data ParserConfig m Source #

Parsing a biscuit involves various steps. This data type allows configuring those steps.

Constructors

ParserConfig 

Fields

parseBiscuitUnverified :: ByteString -> Either ParseError (Biscuit OpenOrSealed Unverified) Source #

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.

checkBiscuitSignatures :: BiscuitProof proof => (Maybe Int -> PublicKey) -> Biscuit proof Unverified -> Either ParseError (Biscuit proof Verified) Source #

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.

serializeBiscuit :: BiscuitProof p => Biscuit p Verified -> ByteString Source #

Serialize a biscuit to a raw bytestring

authorizeBiscuit :: Biscuit proof Verified -> Authorizer -> IO (Either ExecutionError AuthorizationSuccess) Source #

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.

fromOpen :: Biscuit Open check -> Biscuit OpenOrSealed check Source #

Turn a Biscuit statically known to be Open into a more generic OpenOrSealed Biscuit (essentially forgetting about the fact it's Open)

fromSealed :: Biscuit Sealed check -> Biscuit OpenOrSealed check Source #

Turn a Biscuit statically known to be Sealed into a more generic OpenOrSealed Biscuit (essentially forgetting about the fact it's Sealed)

asOpen :: Biscuit OpenOrSealed check -> Maybe (Biscuit Open check) Source #

Try to turn a Biscuit that may be open or sealed into a biscuit that's statically known to be Open.

asSealed :: Biscuit OpenOrSealed check -> Maybe (Biscuit Sealed check) Source #

Try to turn a Biscuit that may be open or sealed into a biscuit that's statically known to be Sealed.

seal :: Biscuit Open check -> Biscuit Sealed check Source #

Turn an Open biscuit into a Sealed one, preventing it from being attenuated further. A Sealed biscuit cannot be turned into an Open one.

getRevocationIds :: Biscuit proof check -> NonEmpty ByteString Source #

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.

getVerifiedBiscuitPublicKey :: Biscuit a Verified -> PublicKey Source #

Retrieve the PublicKey which was used to verify the Biscuit signatures