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 ExecutionError
- data Limits = Limits {
- maxFacts :: Int
- maxIterations :: Int
- maxTime :: Int
- allowRegexes :: Bool
- allowBlockFacts :: Bool
- data ResultError
- type Bindings = Map Name Value
- type Name = Text
- data MatchedQuery = MatchedQuery {
- matchedQuery :: Query
- bindings :: Set Bindings
- defaultLimits :: Limits
- evaluateExpression :: Limits -> Bindings -> Expression -> Either String Value
- getFactsForRule :: Limits -> Set Fact -> Rule -> Set Fact
- checkCheck :: Limits -> Set Fact -> Check -> Validation (NonEmpty Check) ()
- checkPolicy :: Limits -> Set Fact -> Policy -> Maybe (Either MatchedQuery MatchedQuery)
- getBindingsForRuleBody :: Limits -> Set Fact -> [Predicate] -> [Expression] -> Set Bindings
Documentation
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 # |
Settings for the executor runtime 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] MatchedQuery | 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 # |
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 # |
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
checkCheck :: Limits -> Set Fact -> Check -> Validation (NonEmpty Check) () Source #
checkPolicy :: Limits -> Set Fact -> Policy -> Maybe (Either MatchedQuery MatchedQuery) Source #
getBindingsForRuleBody :: Limits -> Set Fact -> [Predicate] -> [Expression] -> Set Bindings Source #