Copyright | © Clément Delafargue 2021 |
---|---|
License | MIT |
Maintainer | clement@delafargue.name |
Safe Haskell | None |
Language | Haskell2010 |
Module defining the main biscuit-related operations
Synopsis
- data Biscuit = Biscuit {
- symbols :: Symbols
- authority :: (PublicKey, ExistingBlock)
- blocks :: [(PublicKey, ExistingBlock)]
- signature :: Signature
- data ParseError
- data VerificationError
- type ExistingBlock = (ByteString, Block)
- mkBiscuit :: Keypair -> Block -> IO Biscuit
- addBlock :: Block -> Biscuit -> IO Biscuit
- checkBiscuitSignature :: Biscuit -> PublicKey -> IO Bool
- parseBiscuit :: ByteString -> Either ParseError Biscuit
- serializeBiscuit :: Biscuit -> ByteString
- verifyBiscuit :: Biscuit -> Verifier -> PublicKey -> IO (Either VerificationError Query)
- verifyBiscuitWithLimits :: Limits -> Biscuit -> Verifier -> PublicKey -> IO (Either VerificationError Query)
- data BlockWithRevocationIds = BlockWithRevocationIds {}
- getRevocationIds :: Biscuit -> IO (NonEmpty BlockWithRevocationIds)
Documentation
A parsed biscuit
Biscuit | |
|
data ParseError Source #
Errors that can happen when parsing a biscuit
InvalidHexEncoding | The provided ByteString is not hex-encoded |
InvalidB64Encoding | The provided ByteString is not base64-encoded |
InvalidProtobufSer String | The provided ByteString does not contain properly serialized protobuf values |
InvalidProtobuf String | The bytestring was correctly deserialized from protobuf, but the values can't be turned into a proper biscuit |
Instances
Eq ParseError Source # | |
Defined in Auth.Biscuit.Token (==) :: ParseError -> ParseError -> Bool # (/=) :: ParseError -> ParseError -> Bool # | |
Show ParseError Source # | |
Defined in Auth.Biscuit.Token showsPrec :: Int -> ParseError -> ShowS # show :: ParseError -> String # showList :: [ParseError] -> ShowS # |
data VerificationError Source #
An error that can happen when verifying a biscuit
SignatureError | The signature is invalid |
DatalogError ExecutionError | The checks and policies could not be verified |
Instances
Eq VerificationError Source # | |
Defined in Auth.Biscuit.Token (==) :: VerificationError -> VerificationError -> Bool # (/=) :: VerificationError -> VerificationError -> Bool # | |
Show VerificationError Source # | |
Defined in Auth.Biscuit.Token showsPrec :: Int -> VerificationError -> ShowS # show :: VerificationError -> String # showList :: [VerificationError] -> ShowS # |
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.
mkBiscuit :: Keypair -> Block -> IO Biscuit Source #
Create a new biscuit with the provided authority block
addBlock :: Block -> Biscuit -> IO Biscuit Source #
Add a block to an existing biscuit. The block will be signed with a randomly-generated keypair
checkBiscuitSignature :: Biscuit -> PublicKey -> IO Bool Source #
Only check a biscuit signature. This can be used to perform an early check, before bothering with constructing a verifier.
parseBiscuit :: ByteString -> Either ParseError Biscuit Source #
Parse a biscuit from a raw bytestring.
serializeBiscuit :: Biscuit -> ByteString Source #
Serialize a biscuit to a raw bytestring
verifyBiscuit :: Biscuit -> Verifier -> PublicKey -> IO (Either VerificationError Query) Source #
Same as verifyBiscuitWithLimits
, but with default limits (1ms timeout, max 1000 facts, max 100 iterations)
verifyBiscuitWithLimits :: Limits -> Biscuit -> Verifier -> PublicKey -> IO (Either VerificationError Query) Source #
Given a provided verifier (a set of facts, rules, checks and policies), and a public key, verify a biscuit:
- make sure the biscuit has been signed with the private key associated to the public key
- make sure the biscuit is valid for the provided verifier
data BlockWithRevocationIds Source #
A parsed block, along with the associated revocation ids.
BlockWithRevocationIds | |
|
getRevocationIds :: Biscuit -> IO (NonEmpty BlockWithRevocationIds) Source #
Compute the revocation ids for a given biscuit