Copyright | © Clément Delafargue 2021 |
---|---|
License | MIT |
Maintainer | clement@delafargue.name |
Safe Haskell | None |
Language | Haskell2010 |
The Datalog elements
Synopsis
- data Binary
- = LessThan
- | GreaterThan
- | LessOrEqual
- | GreaterOrEqual
- | Equal
- | Contains
- | Prefix
- | Suffix
- | Regex
- | Add
- | Sub
- | Mul
- | Div
- | And
- | Or
- | Intersection
- | Union
- type Block = Block' 'RegularString
- data Block' (ctx :: ParsedAs) = Block {}
- data BlockElement' ctx
- = BlockFact (Predicate' 'InFact ctx)
- | BlockRule (Rule' ctx)
- | BlockCheck (Check' ctx)
- | BlockComment
- type Check = Query
- type Check' ctx = Query' ctx
- type Expression = Expression' 'RegularString
- data Expression' (ctx :: ParsedAs)
- = EValue (Term' 'NotWithinSet 'InPredicate ctx)
- | EUnary Unary (Expression' ctx)
- | EBinary Binary (Expression' ctx) (Expression' ctx)
- type Fact = Predicate' 'InFact 'RegularString
- 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)
- data IsWithinSet
- data Op
- data ParsedAs
- type Policy = (PolicyType, Query)
- type Policy' ctx = (PolicyType, Query' ctx)
- data PolicyType
- type Predicate = Predicate' 'InPredicate 'RegularString
- data Predicate' (pof :: PredicateOrFact) (ctx :: ParsedAs) = Predicate {
- name :: Text
- terms :: [Term' 'NotWithinSet pof ctx]
- data PredicateOrFact
- type QQTerm = Term' 'NotWithinSet 'InPredicate 'QuasiQuote
- type Query = Query' 'RegularString
- type Query' ctx = [QueryItem' ctx]
- data QueryItem' ctx = QueryItem {
- qBody :: [Predicate' 'InPredicate ctx]
- qExpressions :: [Expression' ctx]
- qScope :: Maybe RuleScope
- type Rule = Rule' 'RegularString
- data Rule' ctx = Rule {
- rhead :: Predicate' 'InPredicate ctx
- body :: [Predicate' 'InPredicate ctx]
- expressions :: [Expression' ctx]
- scope :: Maybe RuleScope
- data RuleScope
- type family SetType (inSet :: IsWithinSet) (ctx :: ParsedAs) where ...
- newtype Slice = Slice String
- type family SliceType (ctx :: ParsedAs) where ...
- data Unary
- type Value = Term' 'NotWithinSet 'InFact 'RegularString
- type family VariableType (inSet :: IsWithinSet) (pof :: PredicateOrFact) where ...
- type Authorizer = Authorizer' 'RegularString
- data Authorizer' (ctx :: ParsedAs) = Authorizer {}
- data AuthorizerElement' ctx
- = AuthorizerPolicy (Policy' ctx)
- | BlockElement (BlockElement' ctx)
- elementToBlock :: BlockElement' ctx -> Block' ctx
- elementToAuthorizer :: AuthorizerElement' ctx -> Authorizer' ctx
- fromStack :: [Op] -> Either String Expression
- listSymbolsInBlock :: Block' 'RegularString -> Set Text
- renderBlock :: Block -> Text
- renderFact :: Fact -> Text
- renderRule :: Rule' 'RegularString -> Text
- toSetTerm :: Value -> Maybe (Term' 'WithinSet 'InFact 'RegularString)
- toStack :: Expression -> [Op]
Documentation
LessThan | |
GreaterThan | |
LessOrEqual | |
GreaterOrEqual | |
Equal | |
Contains | |
Prefix | |
Suffix | |
Regex | |
Add | |
Sub | |
Mul | |
Div | |
And | |
Or | |
Intersection | |
Union |
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}); |]
data Block' (ctx :: ParsedAs) Source #
A biscuit block, that may or may not contain slices referencing haskell variables
data BlockElement' ctx Source #
BlockFact (Predicate' 'InFact ctx) | |
BlockRule (Rule' ctx) | |
BlockCheck (Check' ctx) | |
BlockComment |
Instances
(Show (Predicate' 'InFact ctx), Show (Rule' ctx), Show (QueryItem' ctx)) => Show (BlockElement' ctx) Source # | |
Defined in Auth.Biscuit.Datalog.AST showsPrec :: Int -> BlockElement' ctx -> ShowS # show :: BlockElement' ctx -> String # showList :: [BlockElement' ctx] -> ShowS # |
type Expression = Expression' 'RegularString Source #
data Expression' (ctx :: ParsedAs) Source #
EValue (Term' 'NotWithinSet 'InPredicate ctx) | |
EUnary Unary (Expression' ctx) | |
EBinary Binary (Expression' ctx) (Expression' ctx) |
Instances
type Fact = Predicate' 'InFact 'RegularString Source #
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 # | |
type Policy = (PolicyType, Query) Source #
type Policy' ctx = (PolicyType, Query' ctx) Source #
data PolicyType Source #
Instances
Eq PolicyType Source # | |
Defined in Auth.Biscuit.Datalog.AST (==) :: PolicyType -> PolicyType -> Bool # (/=) :: PolicyType -> PolicyType -> Bool # | |
Ord PolicyType Source # | |
Defined in Auth.Biscuit.Datalog.AST compare :: PolicyType -> PolicyType -> Ordering # (<) :: PolicyType -> PolicyType -> Bool # (<=) :: PolicyType -> PolicyType -> Bool # (>) :: PolicyType -> PolicyType -> Bool # (>=) :: PolicyType -> PolicyType -> Bool # max :: PolicyType -> PolicyType -> PolicyType # min :: PolicyType -> PolicyType -> PolicyType # | |
Show PolicyType Source # | |
Defined in Auth.Biscuit.Datalog.AST showsPrec :: Int -> PolicyType -> ShowS # show :: PolicyType -> String # showList :: [PolicyType] -> ShowS # | |
Lift PolicyType Source # | |
Defined in Auth.Biscuit.Datalog.AST lift :: PolicyType -> Q Exp # liftTyped :: PolicyType -> Q (TExp PolicyType) # |
type Predicate = Predicate' 'InPredicate 'RegularString Source #
data Predicate' (pof :: PredicateOrFact) (ctx :: ParsedAs) Source #
Instances
type QQTerm = Term' 'NotWithinSet 'InPredicate 'QuasiQuote Source #
In an AST parsed from a QuasiQuoter, there might be references to haskell variables
type Query = Query' 'RegularString Source #
type Query' ctx = [QueryItem' ctx] Source #
data QueryItem' ctx Source #
QueryItem | |
|
Instances
type Rule = Rule' 'RegularString Source #
Rule | |
|
Instances
(Lift (Predicate' 'InPredicate ctx), Lift (Expression' ctx)) => Lift (Rule' ctx :: Type) Source # | |
(Eq (Predicate' 'InPredicate ctx), Eq (Expression' ctx)) => Eq (Rule' ctx) Source # | |
(Ord (Predicate' 'InPredicate ctx), Ord (Expression' ctx)) => Ord (Rule' ctx) Source # | |
Defined in Auth.Biscuit.Datalog.AST | |
(Show (Predicate' 'InPredicate ctx), Show (Expression' ctx)) => Show (Rule' ctx) Source # | |
type family SetType (inSet :: IsWithinSet) (ctx :: ParsedAs) where ... Source #
type Value = Term' 'NotWithinSet 'InFact 'RegularString Source #
A term that is not a variable
type family VariableType (inSet :: IsWithinSet) (pof :: PredicateOrFact) where ... Source #
VariableType 'NotWithinSet 'InPredicate = Text | |
VariableType inSet pof = Void |
type Authorizer = Authorizer' 'RegularString Source #
A biscuit authorizer, containing, facts, rules, checks and policies
data Authorizer' (ctx :: ParsedAs) Source #
The context in which a biscuit policies and checks are verified. A authorizer may add policies (`deny if` / `allow if` conditions), as well as rules, facts, and checks. A authorizer may or may not contain slices referencing haskell variables.
Instances
data AuthorizerElement' ctx Source #
AuthorizerPolicy (Policy' ctx) | |
BlockElement (BlockElement' ctx) |
Instances
(Show (Predicate' 'InFact ctx), Show (Rule' ctx), Show (QueryItem' ctx)) => Show (AuthorizerElement' ctx) Source # | |
Defined in Auth.Biscuit.Datalog.AST showsPrec :: Int -> AuthorizerElement' ctx -> ShowS # show :: AuthorizerElement' ctx -> String # showList :: [AuthorizerElement' ctx] -> ShowS # |
elementToBlock :: BlockElement' ctx -> Block' ctx Source #
elementToAuthorizer :: AuthorizerElement' ctx -> Authorizer' ctx Source #
listSymbolsInBlock :: Block' 'RegularString -> Set Text Source #
renderBlock :: Block -> Text Source #
renderFact :: Fact -> Text Source #
renderRule :: Rule' 'RegularString -> Text Source #
toStack :: Expression -> [Op] Source #