Copyright | © Clément Delafargue 2021 |
---|---|
License | MIT |
Maintainer | clement@delafargue.name |
Safe Haskell | None |
Language | Haskell2010 |
Haskell implementation for the Biscuit token.
Synopsis
- newSecret :: IO SecretKey
- toPublic :: SecretKey -> PublicKey
- data SecretKey
- data PublicKey
- serializeSecretKeyHex :: SecretKey -> ByteString
- serializePublicKeyHex :: PublicKey -> ByteString
- parseSecretKeyHex :: ByteString -> Maybe SecretKey
- parsePublicKeyHex :: ByteString -> Maybe PublicKey
- serializeSecretKey :: SecretKey -> ByteString
- serializePublicKey :: PublicKey -> ByteString
- parseSecretKey :: ByteString -> Maybe SecretKey
- parsePublicKey :: ByteString -> Maybe PublicKey
- mkBiscuit :: SecretKey -> Block -> IO (Biscuit Open Verified)
- block :: QuasiQuoter
- blockContext :: Text -> Block
- data Biscuit proof check
- data OpenOrSealed
- data Open
- data Sealed
- data Verified
- data Unverified
- class BiscuitProof a
- type Block = Block' 'RegularString
- parseB64 :: PublicKey -> ByteString -> Either ParseError (Biscuit OpenOrSealed Verified)
- parse :: PublicKey -> ByteString -> Either ParseError (Biscuit OpenOrSealed Verified)
- parseWith :: Applicative m => ParserConfig m -> ByteString -> m (Either ParseError (Biscuit OpenOrSealed Verified))
- parseBiscuitUnverified :: ByteString -> Either ParseError (Biscuit OpenOrSealed Unverified)
- checkBiscuitSignatures :: BiscuitProof proof => (Maybe Int -> PublicKey) -> Biscuit proof Unverified -> Either ParseError (Biscuit proof Verified)
- data BiscuitEncoding
- data ParserConfig m = ParserConfig {
- encoding :: BiscuitEncoding
- isRevoked :: Set ByteString -> m Bool
- getPublicKey :: Maybe Int -> PublicKey
- fromRevocationList :: (Applicative m, Foldable t) => t ByteString -> Set ByteString -> m Bool
- serializeB64 :: BiscuitProof p => Biscuit p Verified -> ByteString
- serialize :: BiscuitProof p => Biscuit p Verified -> ByteString
- fromHex :: MonadFail m => ByteString -> m ByteString
- addBlock :: Block -> Biscuit Open check -> IO (Biscuit Open check)
- seal :: Biscuit Open check -> Biscuit Sealed check
- fromOpen :: Biscuit Open check -> Biscuit OpenOrSealed check
- fromSealed :: Biscuit Sealed check -> Biscuit OpenOrSealed check
- asOpen :: Biscuit OpenOrSealed check -> Maybe (Biscuit Open check)
- asSealed :: Biscuit OpenOrSealed check -> Maybe (Biscuit Sealed check)
- authorizer :: QuasiQuoter
- type Authorizer = Authorizer' 'RegularString
- authorizeBiscuit :: Biscuit proof Verified -> Authorizer -> IO (Either ExecutionError AuthorizationSuccess)
- authorizeBiscuitWithLimits :: Limits -> Biscuit a Verified -> Authorizer -> IO (Either ExecutionError AuthorizationSuccess)
- data Limits = Limits {
- maxFacts :: Int
- maxIterations :: Int
- maxTime :: Int
- allowRegexes :: Bool
- allowBlockFacts :: Bool
- defaultLimits :: Limits
- data ParseError
- data ExecutionError
- data AuthorizationSuccess = AuthorizationSuccess {}
- data MatchedQuery = MatchedQuery {
- matchedQuery :: Query
- bindings :: Set Bindings
- query :: QuasiQuoter
- queryAuthorizerFacts :: AuthorizationSuccess -> Query -> Set Bindings
- getBindings :: AuthorizationSuccess -> Set Bindings
- getVariableValues :: (Ord t, FromValue t) => Set Bindings -> Text -> Set t
- getSingleVariableValue :: (Ord t, FromValue t) => Set Bindings -> Text -> Maybe t
- class ToTerm t where
- toTerm :: t -> Term' inSet pof 'RegularString
- class FromValue t where
- type Term = Term' 'NotWithinSet 'InPredicate 'RegularString
- data Term' (inSet :: IsWithinSet) (pof :: PredicateOrFact) (ctx :: ParsedAs)
- getRevocationIds :: Biscuit proof check -> NonEmpty ByteString
- getVerifiedBiscuitPublicKey :: Biscuit a Verified -> PublicKey
The biscuit auth token
Biscuit is a bearer token,
allowing offline attenuation (meaning that anyone having a token can craft a new, more
restricted token),
and PublicKey
verification. Token rights and attenuation are expressed using a logic
language, derived from datalog. Such a language can describe facts (things we know
about the world), rules (describing how to derive new facts from existing ones) and checks
(ensuring that facts hold). Facts and checks let you describe access control rules, while
rules make them modular. Authorizer policies lets the verifying party ensure that a
provided biscuit grants access to the required operations.
Here's how to create a biscuit token:
-- Biscuit Open Verified means the token has valid signatures -- and is open to further restriction buildToken :: Keypair -> IO (Biscuit Open Verified) buildToken keypair = -- the logic language has its own syntax, which can be typed directly in haskell -- source code thanks to QuasiQuotes. The datalog snippets are parsed at compile -- time, so a datalog error results in a compilation error, not a runtime error mkBiscuit keypair [block| // the two first lines describe facts: // the token holder is identified as `user_1234` user("user_1234"); // the token holder is granted access to resource `file1` resource("file1"); // this last line defines a restriction: properties that need // to be verified for the token to be verified: // the token can only be used before a specified date check if time($time), $time < 2021-05-08T00:00:00Z; |]
Here's how to attenuate a biscuit token:
restrictToken :: Biscuit Open Verified -> IO Biscuit Open Verified restrictToken = addBlock [block| // restrict the token to local use only check if user_ip_address("127.0.0.1"); |]
To verify a biscuit token, we need two things:
- a public key, that will let us verify the token has been emitted by a trusted authority
- an authorizer, that will make sure all the checks declared in the token are fulfilled, as well as providing its own checks, and policies which decide if the token is verified or not
Here's how to verify a base64-serialized biscuit token:
verifyToken :: PublicKey -> ByteString -> IO Bool verifyToken publicKey token = do -- complete parsing is only attempted if signatures can be verified, -- that's the reason why 'parseB64' takes a public key as a parameter parseResult <- parseB64 publicKey token case parseResult of Left e -> print e $> False Right biscuit -> do now <- getCurrentTime let verif = [authorizer| // the datalog snippets can reference haskell variables // with the ${variableName} syntax time(${now}); // policies are tried in order. The first matching policy // will decide if the token is valid or not. If no policies // match, the token will fail validation allow if resource("file1"); // catch-all policy if the previous ones did not match deny if true; |] result <- authorizeBiscuit biscuit [authorizer|current_time()|] case result of Left e -> print e $> False Right _ -> pure True
Creating keypairs
Biscuits rely on public key cryptography: biscuits are signed with a secret key only known to the party which emits it. Verifying a biscuit, on the other hand, can be done with a public key that can be widely distributed. A private key and its corresponding public key is called a keypair, but since a public key can be deterministically computed from a private key, owning a private key is the same as owning a keypair.
An Ed25519 Secret key
Instances
An Ed25519 public key
Instances
Parsing and serializing keypairs
serializeSecretKeyHex :: SecretKey -> ByteString Source #
Serialize a SecretKey
to a hex-encoded bytestring
serializePublicKeyHex :: PublicKey -> ByteString Source #
Serialize a PublicKey
to a hex-encoded bytestring
parseSecretKeyHex :: ByteString -> Maybe SecretKey Source #
Read a SecretKey
from an hex bytestring
parsePublicKeyHex :: ByteString -> Maybe PublicKey Source #
Read a PublicKey
from an hex bytestring
serializeSecretKey :: SecretKey -> ByteString Source #
Serialize a SecretKey
to raw bytes, without any encoding
serializePublicKey :: PublicKey -> ByteString Source #
Serialize a PublicKey
to raw bytes, without any encoding
parseSecretKey :: ByteString -> Maybe SecretKey Source #
Read a SecretKey
from raw bytes
parsePublicKey :: ByteString -> Maybe PublicKey Source #
Read a PublicKey
from raw bytes
Creating a biscuit
The core of a biscuit is its authority block. This block declares facts and rules and is signed by its creator with a secret key. In addition to this trusted, authority block, a biscuit may carry extra blocks that can only restrict what it can do. By default, biscuits can be restricted, but it's possible to seal a biscuit and prevent further modifications.
Blocks are defined with a logic language (datalog) that can be used directly from haskell
with the QuasiQuotes
extension.
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.
block :: QuasiQuoter Source #
Compile-time parser for a block expression, intended to be used with the
QuasiQuotes
extension.
A typical use of block
looks like this:
let fileName = "data.pdf" in [block| // datalog can reference haskell variables with ${variableName} resource(${fileName}); rule($variable) <- fact($value), other_fact($value); check if operation("read"); |]
blockContext :: Text -> Block Source #
Build a block containing an explicit context value.
The context of a block can't be parsed from datalog currently,
so you'll need an explicit call to blockContext
to add it
[block|check if time($t), $t < 2021-01-01;|] <> blockContext "ttl-check"
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.
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
Eq OpenOrSealed Source # | |
Defined in Auth.Biscuit.Token (==) :: OpenOrSealed -> OpenOrSealed -> Bool # (/=) :: OpenOrSealed -> OpenOrSealed -> Bool # | |
Show OpenOrSealed Source # | |
Defined in Auth.Biscuit.Token showsPrec :: Int -> OpenOrSealed -> ShowS # show :: OpenOrSealed -> String # showList :: [OpenOrSealed] -> ShowS # | |
BiscuitProof OpenOrSealed Source # | |
Defined in Auth.Biscuit.Token |
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
BiscuitProof Open Source # | |
Defined in Auth.Biscuit.Token toPossibleProofs :: Open -> OpenOrSealed 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
BiscuitProof Sealed Source # | |
Defined in Auth.Biscuit.Token |
Proof that a biscuit had its signatures verified with the carried root PublicKey
data Unverified Source #
Marker that a biscuit was parsed without having its signatures verified. Such a biscuit cannot be trusted yet.
Instances
Eq Unverified Source # | |
Defined in Auth.Biscuit.Token (==) :: Unverified -> Unverified -> Bool # (/=) :: Unverified -> Unverified -> Bool # | |
Show Unverified Source # | |
Defined in Auth.Biscuit.Token showsPrec :: Int -> Unverified -> ShowS # show :: Unverified -> String # showList :: [Unverified] -> ShowS # |
class BiscuitProof a 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
BiscuitProof Sealed Source # | |
Defined in Auth.Biscuit.Token | |
BiscuitProof Open Source # | |
Defined in Auth.Biscuit.Token toPossibleProofs :: Open -> OpenOrSealed Source # | |
BiscuitProof OpenOrSealed Source # | |
Defined in Auth.Biscuit.Token |
type Block = Block' 'RegularString Source #
A biscuit block, containing facts, rules and checks.
Block
has a Monoid
instance, which is the expected way
to build composite blocks (eg if you need to generate a list of facts):
-- build a block from multiple variables v1, v2, v3 [block| value(${v1}); |] <> [block| value(${v2}); |] <> [block| value(${v3}); |]
Parsing and serializing biscuits
parseB64 :: PublicKey -> ByteString -> Either ParseError (Biscuit OpenOrSealed Verified) Source #
Parse a biscuit from a URL-compatible base 64 encoded bytestring
parse :: PublicKey -> ByteString -> Either ParseError (Biscuit OpenOrSealed Verified) Source #
Parse a biscuit from a raw bytestring. If you want to parse
from a URL-compatible base 64 bytestring, consider using parseB64
instead.
The biscuit signature is verified with the provided PublicKey
before
completely decoding blocks
The revocation ids are not verified before completely decoding blocks.
If you need to check revocation ids before decoding blocks, use parseWith
(or parseB64With
instead).
parseWith :: Applicative m => ParserConfig m -> ByteString -> m (Either ParseError (Biscuit OpenOrSealed Verified)) Source #
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
.
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.
data ParserConfig m Source #
Parsing a biscuit involves various steps. This data type allows configuring those steps.
ParserConfig | |
|
fromRevocationList :: (Applicative m, Foldable t) => t ByteString -> Set ByteString -> m Bool Source #
Helper for building a revocation check from a static list, suitable for use with
parseWith
and ParserConfig
.
serializeB64 :: BiscuitProof p => Biscuit p Verified -> ByteString Source #
Serialize a biscuit to URL-compatible base 64, as recommended by the spec
serialize :: BiscuitProof p => Biscuit p Verified -> ByteString Source #
Serialize a biscuit to a binary format. If you intend to send
the biscuit over a text channel, consider using serializeB64
instead
fromHex :: MonadFail m => ByteString -> m ByteString Source #
Decode a base16-encoded bytestring, reporting errors via MonadFail
Attenuating biscuits
By default, biscuits can be attenuated. It means that any party that holds a biscuit can craft a new biscuit with fewer rights. A common example is taking a long-lived biscuit and adding a short TTL right before sending it over the wire.
An Open
biscuit can be turned into a Sealed
one, meaning it won't be possible
to attenuate it further.
mkBiscuit
creates Open
biscuits, while parse
returns an OpenOrSealed
biscuit (since
when you're verifying a biscuit, you're not caring about whether it can be extended further
or not). authorizeBiscuit
does not care whether a biscuit is Open
or Sealed
and can be
used with both. addBlock
and seal
only work with Open
biscuits.
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
)
Verifying a biscuit
Verifying a biscuit requires providing a list of policies (allow or deny), which will decide if the biscuit is accepted. Policies are tried in order, and the first one to match decides whether the biscuit is accepted.
In addition to policies, an authorizer typically provides facts (such as the current time) so that checks and policies can be verified.
The authorizer checks and policies only see the content of the authority (first) block. Extra blocks can only carry restrictions and cannot interfere with the authority facts.
authorizer :: QuasiQuoter Source #
Compile-time parser for an authorizer expression, intended to be used with the
QuasiQuotes
extension.
A typical use of authorizer
looks like this:
do now <- getCurrentTime pure [authorizer| // datalog can reference haskell variables with ${variableName} current_time(${now}); // authorizers can contain facts, rules and checks like blocks, but // also declare policies. While every check has to pass for a biscuit to // be valid, policies are tried in order. The first one to match decides // if the token is valid or not allow if resource("file1"); deny if true; |]
type Authorizer = Authorizer' 'RegularString Source #
A biscuit authorizer, containing, facts, rules, checks and policies
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
.
authorizeBiscuitWithLimits :: Limits -> Biscuit a Verified -> Authorizer -> IO (Either ExecutionError AuthorizationSuccess) Source #
Generic version of authorizeBiscuitWithLimits
which takes custom Limits
.
Settings for the executor runtime restrictions.
See defaultLimits
for default values.
Limits | |
|
defaultLimits :: Limits Source #
Default settings for the executor restrictions. - 1000 facts - 100 iterations - 1000μs max - regexes are allowed - facts and rules are allowed in blocks
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
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
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 ExecutionError Source #
An error that can happen while running a datalog verification.
The datalog computation itself can be aborted by runtime failsafe
mechanisms, or it can run to completion but fail to fullfil checks
and policies (ResultError
).
Timeout | Verification took too much time |
TooManyFacts | Too many facts were generated during evaluation |
TooManyIterations | Evaluation did not converge in the alloted number of iterations |
FactsInBlocks | Some blocks contained either rules or facts while it was forbidden |
ResultError ResultError | The evaluation ran to completion, but checks and policies were not fulfilled. |
Instances
Eq ExecutionError Source # | |
Defined in Auth.Biscuit.Datalog.Executor (==) :: ExecutionError -> ExecutionError -> Bool # (/=) :: ExecutionError -> ExecutionError -> Bool # | |
Show ExecutionError Source # | |
Defined in Auth.Biscuit.Datalog.Executor showsPrec :: Int -> ExecutionError -> ShowS # show :: ExecutionError -> String # showList :: [ExecutionError] -> ShowS # |
data AuthorizationSuccess Source #
Proof that a biscuit was authorized successfully. In addition to the matched
allow query
, the generated facts are kept around for further querying.
Since only authority facts can be trusted, they are kept separate.
AuthorizationSuccess | |
|
Instances
Eq AuthorizationSuccess Source # | |
Defined in Auth.Biscuit.Datalog.ScopedExecutor (==) :: AuthorizationSuccess -> AuthorizationSuccess -> Bool # (/=) :: AuthorizationSuccess -> AuthorizationSuccess -> Bool # | |
Show AuthorizationSuccess Source # | |
Defined in Auth.Biscuit.Datalog.ScopedExecutor showsPrec :: Int -> AuthorizationSuccess -> ShowS # show :: AuthorizationSuccess -> String # showList :: [AuthorizationSuccess] -> ShowS # |
data MatchedQuery Source #
A datalog query that was matched, along with the values that matched
Instances
Eq MatchedQuery Source # | |
Defined in Auth.Biscuit.Datalog.Executor (==) :: MatchedQuery -> MatchedQuery -> Bool # (/=) :: MatchedQuery -> MatchedQuery -> Bool # | |
Show MatchedQuery Source # | |
Defined in Auth.Biscuit.Datalog.Executor showsPrec :: Int -> MatchedQuery -> ShowS # show :: MatchedQuery -> String # showList :: [MatchedQuery] -> ShowS # |
query :: QuasiQuoter Source #
Compile-time parser for a query expression, intended to be used with the
QuasiQuotes
extension.
A typical use of query
looks like this:
[query|user($user_id) or group($group_id)|]
queryAuthorizerFacts :: AuthorizationSuccess -> Query -> Set Bindings Source #
Query the facts generated by the authority and authorizer blocks
during authorization. This can be used in conjuction with getVariableValues
and getSingleVariableValue
to retrieve actual values.
⚠ Only the facts generated by the authority and authorizer blocks are queried. Block facts are not queried (since they can't be trusted).
💁 If the facts you want to query are part of an allow query in the authorizer,
you can directly get values from AuthorizationSuccess
.
getBindings :: AuthorizationSuccess -> Set Bindings Source #
Get the matched variables from the allow
query used to authorize the biscuit.
This can be used in conjuction with getVariableValues
or getSingleVariableValue
to extract the actual values
getVariableValues :: (Ord t, FromValue t) => Set Bindings -> Text -> Set t Source #
Extract a set of values from a matched variable for a specific type.
Returning Set Value
allows to get all values, whatever their type.
getSingleVariableValue :: (Ord t, FromValue t) => Set Bindings -> Text -> Maybe t Source #
Extract exactly one value from a matched variable. If the variable has 0
matches or more than one match, Nothing
will be returned
This class describes how to turn a haskell value into a datalog value. | This is used when slicing a haskell variable in a datalog expression
toTerm :: t -> Term' inSet pof 'RegularString Source #
How to turn a value into a datalog item
Instances
class FromValue t where Source #
This class describes how to turn a datalog value into a regular haskell value.
type Term = Term' 'NotWithinSet 'InPredicate 'RegularString Source #
In a regular AST, slices have already been eliminated
data Term' (inSet :: IsWithinSet) (pof :: PredicateOrFact) (ctx :: ParsedAs) Source #
A single datalog item. | This can be a value, a set of items, or a slice (a value that will be injected later), | depending on the context
Variable (VariableType inSet pof) | A variable (eg. |
LInteger Int | An integer literal (eg. |
LString Text | A string literal (eg. |
LDate UTCTime | A date literal (eg. |
LBytes ByteString | A hex literal (eg. |
LBool Bool | A bool literal (eg. |
Antiquote (SliceType ctx) | A slice (eg. |
TermSet (SetType inSet ctx) | A set (eg. |
Instances
FromValue Value Source # | |
(Lift (VariableType inSet pof), Lift (SetType inSet ctx), Lift (SliceType ctx)) => Lift (Term' inSet pof ctx :: Type) Source # | |
(Eq (VariableType inSet pof), Eq (SliceType ctx), Eq (SetType inSet ctx)) => Eq (Term' inSet pof ctx) Source # | |
(Ord (VariableType inSet pof), Ord (SliceType ctx), Ord (SetType inSet ctx)) => Ord (Term' inSet pof ctx) Source # | |
Defined in Auth.Biscuit.Datalog.AST compare :: Term' inSet pof ctx -> Term' inSet pof ctx -> Ordering # (<) :: Term' inSet pof ctx -> Term' inSet pof ctx -> Bool # (<=) :: Term' inSet pof ctx -> Term' inSet pof ctx -> Bool # (>) :: Term' inSet pof ctx -> Term' inSet pof ctx -> Bool # (>=) :: Term' inSet pof ctx -> Term' inSet pof ctx -> Bool # max :: Term' inSet pof ctx -> Term' inSet pof ctx -> Term' inSet pof ctx # min :: Term' inSet pof ctx -> Term' inSet pof ctx -> Term' inSet pof ctx # | |
(Show (VariableType inSet pof), Show (SliceType ctx), Show (SetType inSet ctx)) => Show (Term' inSet pof ctx) Source # | |
Retrieving information from a biscuit
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.