| Copyright | © Clément Delafargue 2021 | 
|---|---|
| License | MIT | 
| Maintainer | clement@delafargue.name | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
Auth.Biscuit.Datalog.Executor
Description
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
 
- data ResultError
- type Bindings = Map Name Value
- type Name = Text
- data MatchedQuery = MatchedQuery {- matchedQuery :: Query
- bindings :: Set Bindings
 
- type Scoped a = (Set Natural, a)
- newtype FactGroup = FactGroup {}
- countFacts :: FactGroup -> Int
- toScopedFacts :: FactGroup -> Set (Scoped Fact)
- fromScopedFacts :: Set (Scoped Fact) -> FactGroup
- keepAuthorized' :: Bool -> Natural -> FactGroup -> Set EvalRuleScope -> Natural -> FactGroup
- defaultLimits :: Limits
- evaluateExpression :: Limits -> Bindings -> Expression -> Either String Value
- getFactsForRule :: Limits -> Set (Scoped Fact) -> EvalRule -> Set (Scoped Fact)
- checkCheck :: Limits -> Natural -> Natural -> FactGroup -> EvalCheck -> Validation (NonEmpty Check) ()
- checkPolicy :: Limits -> Natural -> FactGroup -> EvalPolicy -> Maybe (Either MatchedQuery MatchedQuery)
- getBindingsForRuleBody :: Limits -> Set (Scoped Fact) -> [Predicate] -> [Expression] -> Set (Scoped Bindings)
- getCombinations :: [[Scoped Bindings]] -> [Scoped [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).
Constructors
| 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 | 
| InvalidRule | Some rules were malformed: every variable present in their head must appear in their body | 
| ResultError ResultError | The evaluation ran to completion, but checks and policies were not fulfilled. | 
Instances
| Show ExecutionError Source # | |
| Defined in Auth.Biscuit.Datalog.Executor Methods showsPrec :: Int -> ExecutionError -> ShowS # show :: ExecutionError -> String # showList :: [ExecutionError] -> ShowS # | |
| Eq ExecutionError Source # | |
| Defined in Auth.Biscuit.Datalog.Executor Methods (==) :: ExecutionError -> ExecutionError -> Bool # (/=) :: ExecutionError -> ExecutionError -> Bool # | |
Settings for the executor runtime restrictions.
 See defaultLimits for default values.
Constructors
| Limits | |
| Fields 
 | |
Instances
data ResultError Source #
The result of matching the checks and policies against all the available facts.
Constructors
| 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
| Show ResultError Source # | |
| Defined in Auth.Biscuit.Datalog.Executor Methods showsPrec :: Int -> ResultError -> ShowS # show :: ResultError -> String # showList :: [ResultError] -> ShowS # | |
| Eq ResultError Source # | |
| Defined in Auth.Biscuit.Datalog.Executor | |
data MatchedQuery Source #
A datalog query that was matched, along with the values that matched
Constructors
| MatchedQuery | |
| Fields 
 | |
Instances
| Show MatchedQuery Source # | |
| Defined in Auth.Biscuit.Datalog.Executor Methods showsPrec :: Int -> MatchedQuery -> ShowS # show :: MatchedQuery -> String # showList :: [MatchedQuery] -> ShowS # | |
| Eq MatchedQuery Source # | |
| Defined in Auth.Biscuit.Datalog.Executor | |
countFacts :: FactGroup -> Int Source #
keepAuthorized' :: Bool -> Natural -> FactGroup -> Set EvalRuleScope -> Natural -> FactGroup Source #
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
getFactsForRule :: Limits -> Set (Scoped Fact) -> EvalRule -> Set (Scoped Fact) Source #
Given a rule and a set of available (scoped) facts, we find all fact combinations that match the rule body, and generate new facts by applying the bindings to the rule head (while keeping track of the facts origins)
checkCheck :: Limits -> Natural -> Natural -> FactGroup -> EvalCheck -> Validation (NonEmpty Check) () Source #
checkPolicy :: Limits -> Natural -> FactGroup -> EvalPolicy -> Maybe (Either MatchedQuery MatchedQuery) Source #