Copyright | © Clément Delafargue 2021 |
---|---|
License | MIT |
Maintainer | clement@delafargue.name |
Safe Haskell | None |
Language | Haskell2010 |
The Datalog engine, tasked with deriving new facts from existing facts and rules, as well as matching available facts against checks and policies
Synopsis
- data BlockWithRevocationIds = BlockWithRevocationIds {}
- data ExecutionError
- data Limits = Limits {
- maxFacts :: Int
- maxIterations :: Int
- maxTime :: Int
- allowRegexes :: Bool
- allowBlockFacts :: Bool
- checkRevocationId :: ByteString -> IO (Either () ())
- data ResultError
- data World = World {}
- type Bindings = Map Name Value
- type Name = Text
- computeAllFacts :: Limits -> World -> Either ExecutionError (Set Fact)
- defaultLimits :: Limits
- evaluateExpression :: Limits -> Bindings -> Expression -> Either String Value
- runVerifier :: BlockWithRevocationIds -> [BlockWithRevocationIds] -> Verifier -> IO (Either ExecutionError Query)
- runVerifierWithLimits :: Limits -> BlockWithRevocationIds -> [BlockWithRevocationIds] -> Verifier -> IO (Either ExecutionError Query)
Documentation
data BlockWithRevocationIds Source #
A parsed block, along with the associated revocation ids.
BlockWithRevocationIds | |
|
data ExecutionError Source #
The result of running verification
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 checks and policies were not fulfilled after evaluation |
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 # |
Settings for the executor restrictions
See defaultLimits
for default values.
Limits | |
|
data ResultError Source #
The result of matching the checks and policies against all the available facts.
NoPoliciesMatched [Check] | No policy matched. additionally some checks may have failed |
FailedChecks (NonEmpty Check) | An allow rule matched, but at least one check failed |
DenyRuleMatched [Check] Query | A deny rule matched. additionally some checks may have failed |
Instances
Eq ResultError Source # | |
Defined in Auth.Biscuit.Datalog.Executor (==) :: ResultError -> ResultError -> Bool # (/=) :: ResultError -> ResultError -> Bool # | |
Show ResultError Source # | |
Defined in Auth.Biscuit.Datalog.Executor showsPrec :: Int -> ResultError -> ShowS # show :: ResultError -> String # showList :: [ResultError] -> ShowS # |
A collection of facts and rules used to derive new facts. Rules coming from blocks are stored separately since they are subject to specific restrictions regarding the facts they can generate.
:: Limits | The maximum amount of iterations that can be reached |
-> World | The initial rules and facts |
-> Either ExecutionError (Set Fact) |
Compute all possible facts, recursively calling itself until it can't generate new facts or a limit is reached
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)
evaluateExpression :: Limits -> Bindings -> Expression -> Either String Value Source #
Given bindings for variables, reduce an expression to a single datalog value
:: BlockWithRevocationIds | The authority block |
-> [BlockWithRevocationIds] | The extra blocks |
-> Verifier | A verifier |
-> IO (Either ExecutionError Query) |
Given a series of blocks and a verifier, ensure that all the checks and policies match
runVerifierWithLimits Source #
:: Limits | custom limits |
-> BlockWithRevocationIds | The authority block |
-> [BlockWithRevocationIds] | The extra blocks |
-> Verifier | A verifier |
-> IO (Either ExecutionError Query) |
Given a series of blocks and a verifier, ensure that all the checks and policies match, with provided execution constraints