Copyright | © Clément Delafargue 2021 |
---|---|
License | MIT |
Maintainer | clement@delafargue.name |
Safe Haskell | Safe-Inferred |
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
- | BitwiseAnd
- | BitwiseOr
- | BitwiseXor
- | NotEqual
- type Block = Block' 'Repr 'Representation
- type EvalBlock = Block' 'Eval 'Representation
- data Block' (evalCtx :: EvaluationContext) (ctx :: DatalogContext) = Block {}
- data BlockElement' evalCtx ctx
- = BlockFact (Predicate' 'InFact ctx)
- | BlockRule (Rule' evalCtx ctx)
- | BlockCheck (Check' evalCtx ctx)
- | BlockComment
- data CheckKind
- type Check = Check' 'Repr 'Representation
- type EvalCheck = Check' 'Eval 'Representation
- data Check' evalCtx ctx = Check {}
- type Expression = Expression' 'Representation
- data Expression' (ctx :: DatalogContext)
- = EValue (Term' 'NotWithinSet 'InPredicate ctx)
- | EUnary Unary (Expression' ctx)
- | EBinary Binary (Expression' ctx) (Expression' ctx)
- type Fact = Predicate' 'InFact 'Representation
- class ToTerm t inSet pof where
- toTerm :: t -> Term' inSet pof 'Representation
- class FromValue t where
- type Term = Term' 'NotWithinSet 'InPredicate 'Representation
- data Term' (inSet :: IsWithinSet) (pof :: PredicateOrFact) (ctx :: DatalogContext)
- data IsWithinSet
- data Op
- data DatalogContext
- data EvaluationContext
- type Policy = Policy' 'Repr 'Representation
- type EvalPolicy = Policy' 'Eval 'Representation
- type Policy' evalCtx ctx = (PolicyType, Query' evalCtx ctx)
- data PolicyType
- type Predicate = Predicate' 'InPredicate 'Representation
- data Predicate' (pof :: PredicateOrFact) (ctx :: DatalogContext) = Predicate {
- name :: Text
- terms :: [Term' 'NotWithinSet pof ctx]
- data PredicateOrFact
- type QQTerm = Term' 'NotWithinSet 'InPredicate 'WithSlices
- type Query = Query' 'Repr 'Representation
- type Query' evalCtx ctx = [QueryItem' evalCtx ctx]
- data QueryItem' evalCtx ctx = QueryItem {
- qBody :: [Predicate' 'InPredicate ctx]
- qExpressions :: [Expression' ctx]
- qScope :: Set (RuleScope' evalCtx ctx)
- type Rule = Rule' 'Repr 'Representation
- type EvalRule = Rule' 'Eval 'Representation
- data Rule' evalCtx ctx = Rule {
- rhead :: Predicate' 'InPredicate ctx
- body :: [Predicate' 'InPredicate ctx]
- expressions :: [Expression' ctx]
- scope :: Set (RuleScope' evalCtx ctx)
- data RuleScope' (evalCtx :: EvaluationContext) (ctx :: DatalogContext)
- = OnlyAuthority
- | Previous
- | BlockId (BlockIdType evalCtx ctx)
- type RuleScope = RuleScope' 'Repr 'Representation
- type EvalRuleScope = RuleScope' 'Eval 'Representation
- type family SetType (inSet :: IsWithinSet) (ctx :: DatalogContext) where ...
- newtype Slice = Slice Text
- data PkOrSlice
- type family SliceType (ctx :: DatalogContext) where ...
- type family BlockIdType (evalCtx :: EvaluationContext) (ctx :: DatalogContext) where ...
- data Unary
- type Value = Term' 'NotWithinSet 'InFact 'Representation
- type family VariableType (inSet :: IsWithinSet) (pof :: PredicateOrFact) where ...
- type Authorizer = Authorizer' 'Repr 'Representation
- data Authorizer' (evalCtx :: EvaluationContext) (ctx :: DatalogContext) = Authorizer {}
- data AuthorizerElement' evalCtx ctx
- = AuthorizerPolicy (Policy' evalCtx ctx)
- | BlockElement (BlockElement' evalCtx ctx)
- class ToEvaluation elem where
- toEvaluation :: [Maybe PublicKey] -> elem 'Repr 'Representation -> elem 'Eval 'Representation
- toRepresentation :: elem 'Eval 'Representation -> elem 'Repr 'Representation
- makeRule :: Predicate' 'InPredicate ctx -> [Predicate' 'InPredicate ctx] -> [Expression' ctx] -> Set (RuleScope' 'Repr ctx) -> Validation (NonEmpty Text) (Rule' 'Repr ctx)
- makeQueryItem :: [Predicate' 'InPredicate ctx] -> [Expression' ctx] -> Set (RuleScope' 'Repr ctx) -> Validation (NonEmpty Text) (QueryItem' 'Repr ctx)
- checkToEvaluation :: [Maybe PublicKey] -> Check -> EvalCheck
- policyToEvaluation :: [Maybe PublicKey] -> Policy -> EvalPolicy
- elementToBlock :: BlockElement' evalCtx ctx -> Block' evalCtx ctx
- elementToAuthorizer :: AuthorizerElement' evalCtx ctx -> Authorizer' evalCtx ctx
- extractVariables :: [Predicate' 'InPredicate ctx] -> Set Text
- fromStack :: [Op] -> Either String Expression
- listSymbolsInBlock :: Block -> Set Text
- listPublicKeysInBlock :: Block -> Set PublicKey
- queryHasNoScope :: Query -> Bool
- queryHasNoV4Operators :: Query -> Bool
- ruleHasNoScope :: Rule -> Bool
- ruleHasNoV4Operators :: Rule -> Bool
- isCheckOne :: Check' evalCtx ctx -> Bool
- renderBlock :: Block -> Text
- renderAuthorizer :: Authorizer -> Text
- renderFact :: Fact -> Text
- renderRule :: Rule -> Text
- valueToSetTerm :: Value -> Maybe (Term' 'WithinSet 'InFact 'Representation)
- toStack :: Expression -> [Op]
- substituteAuthorizer :: Map Text Value -> Map Text PublicKey -> Authorizer' 'Repr 'WithSlices -> Validation (NonEmpty Text) Authorizer
- substituteBlock :: Map Text Value -> Map Text PublicKey -> Block' 'Repr 'WithSlices -> Validation (NonEmpty Text) Block
- substituteCheck :: Map Text Value -> Map Text PublicKey -> Check' 'Repr 'WithSlices -> Validation (NonEmpty Text) Check
- substituteExpression :: Map Text Value -> Expression' 'WithSlices -> Validation (NonEmpty Text) Expression
- substituteFact :: Map Text Value -> Predicate' 'InFact 'WithSlices -> Validation (NonEmpty Text) Fact
- substitutePolicy :: Map Text Value -> Map Text PublicKey -> Policy' 'Repr 'WithSlices -> Validation (NonEmpty Text) Policy
- substitutePredicate :: Map Text Value -> Predicate' 'InPredicate 'WithSlices -> Validation (NonEmpty Text) (Predicate' 'InPredicate 'Representation)
- substitutePTerm :: Map Text Value -> Term' 'NotWithinSet 'InPredicate 'WithSlices -> Validation (NonEmpty Text) (Term' 'NotWithinSet 'InPredicate 'Representation)
- substituteQuery :: Map Text Value -> Map Text PublicKey -> QueryItem' 'Repr 'WithSlices -> Validation (NonEmpty Text) (QueryItem' 'Repr 'Representation)
- substituteRule :: Map Text Value -> Map Text PublicKey -> Rule' 'Repr 'WithSlices -> Validation (NonEmpty Text) Rule
- substituteTerm :: Map Text Value -> Term' 'NotWithinSet 'InFact 'WithSlices -> Validation (NonEmpty Text) Value
Documentation
LessThan | |
GreaterThan | |
LessOrEqual | |
GreaterOrEqual | |
Equal | |
Contains | |
Prefix | |
Suffix | |
Regex | |
Add | |
Sub | |
Mul | |
Div | |
And | |
Or | |
Intersection | |
Union | |
BitwiseAnd | |
BitwiseOr | |
BitwiseXor | |
NotEqual |
type Block = Block' 'Repr 'Representation 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' (evalCtx :: EvaluationContext) (ctx :: DatalogContext) Source #
A biscuit block, that may or may not contain slices referencing haskell variables
Instances
Show Block Source # | |
ToEvaluation Block' Source # | |
Defined in Auth.Biscuit.Datalog.AST toEvaluation :: [Maybe PublicKey] -> Block' 'Repr 'Representation -> Block' 'Eval 'Representation Source # toRepresentation :: Block' 'Eval 'Representation -> Block' 'Repr 'Representation Source # | |
(Lift (Predicate' 'InFact ctx), Lift (Rule' evalCtx ctx), Lift (QueryItem' evalCtx ctx), Lift (RuleScope' evalCtx ctx)) => Lift (Block' evalCtx ctx :: Type) Source # | |
Monoid (Block' evalCtx ctx) Source # | |
Semigroup (Block' evalCtx ctx) Source # | |
(Eq (Predicate' 'InFact ctx), Eq (Rule' evalCtx ctx), Eq (QueryItem' evalCtx ctx), Eq (RuleScope' evalCtx ctx)) => Eq (Block' evalCtx ctx) Source # | |
data BlockElement' evalCtx ctx Source #
BlockFact (Predicate' 'InFact ctx) | |
BlockRule (Rule' evalCtx ctx) | |
BlockCheck (Check' evalCtx ctx) | |
BlockComment |
Instances
(Show (Predicate' 'InFact ctx), Show (Rule' evalCtx ctx), Show (QueryItem' evalCtx ctx)) => Show (BlockElement' evalCtx ctx) Source # | |
Defined in Auth.Biscuit.Datalog.AST showsPrec :: Int -> BlockElement' evalCtx ctx -> ShowS # show :: BlockElement' evalCtx ctx -> String # showList :: [BlockElement' evalCtx ctx] -> ShowS # |
data Check' evalCtx ctx Source #
Instances
ToEvaluation Check' Source # | |
Defined in Auth.Biscuit.Datalog.AST toEvaluation :: [Maybe PublicKey] -> Check' 'Repr 'Representation -> Check' 'Eval 'Representation Source # toRepresentation :: Check' 'Eval 'Representation -> Check' 'Repr 'Representation Source # | |
Lift (QueryItem' evalCtx ctx) => Lift (Check' evalCtx ctx :: Type) Source # | |
Show (QueryItem' evalCtx ctx) => Show (Check' evalCtx ctx) Source # | |
Eq (QueryItem' evalCtx ctx) => Eq (Check' evalCtx ctx) Source # | |
Ord (QueryItem' evalCtx ctx) => Ord (Check' evalCtx ctx) Source # | |
Defined in Auth.Biscuit.Datalog.AST compare :: Check' evalCtx ctx -> Check' evalCtx ctx -> Ordering # (<) :: Check' evalCtx ctx -> Check' evalCtx ctx -> Bool # (<=) :: Check' evalCtx ctx -> Check' evalCtx ctx -> Bool # (>) :: Check' evalCtx ctx -> Check' evalCtx ctx -> Bool # (>=) :: Check' evalCtx ctx -> Check' evalCtx ctx -> Bool # max :: Check' evalCtx ctx -> Check' evalCtx ctx -> Check' evalCtx ctx # min :: Check' evalCtx ctx -> Check' evalCtx ctx -> Check' evalCtx ctx # |
type Expression = Expression' 'Representation Source #
data Expression' (ctx :: DatalogContext) Source #
EValue (Term' 'NotWithinSet 'InPredicate ctx) | |
EUnary Unary (Expression' ctx) | |
EBinary Binary (Expression' ctx) (Expression' ctx) |
Instances
type Fact = Predicate' 'InFact 'Representation Source #
class ToTerm t inSet pof where 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 'Representation Source #
How to turn a value into a datalog item
Instances
ToTerm ByteString inSet pof Source # | |
Defined in Auth.Biscuit.Datalog.AST toTerm :: ByteString -> Term' inSet pof 'Representation Source # | |
ToTerm Text inSet pof Source # | |
Defined in Auth.Biscuit.Datalog.AST | |
ToTerm UTCTime inSet pof Source # | |
Defined in Auth.Biscuit.Datalog.AST | |
ToTerm Integer inSet pof Source # | |
Defined in Auth.Biscuit.Datalog.AST | |
ToTerm Bool inSet pof Source # | |
Defined in Auth.Biscuit.Datalog.AST | |
ToTerm Int inSet pof Source # | |
Defined in Auth.Biscuit.Datalog.AST | |
(Foldable f, ToTerm a 'WithinSet 'InFact) => ToTerm (f a) 'NotWithinSet pof Source # | |
Defined in Auth.Biscuit.Datalog.AST toTerm :: f a -> Term' 'NotWithinSet pof 'Representation Source # |
class FromValue t where Source #
This class describes how to turn a datalog value into a regular haskell value.
type Term = Term' 'NotWithinSet 'InPredicate 'Representation Source #
In a regular AST, slices have already been eliminated
data Term' (inSet :: IsWithinSet) (pof :: PredicateOrFact) (ctx :: DatalogContext) 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 Int64 | 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 # | |
(Show (VariableType inSet pof), Show (SliceType ctx), Show (SetType inSet ctx)) => Show (Term' inSet pof ctx) 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 # |
data DatalogContext Source #
WithSlices | Intermediate Datalog representation, which may contain references to external variables (currently, only sliced in through TemplateHaskell, but it could also be done at runtime, a bit like parameter substitution in SQL queries) |
Representation | A datalog representation faithful to its text display. There are no external variables, and the authorized blocks are identified through their public keys |
data EvaluationContext Source #
type EvalPolicy = Policy' 'Eval 'Representation Source #
type Policy' evalCtx ctx = (PolicyType, Query' evalCtx ctx) Source #
data PolicyType Source #
Instances
Show PolicyType Source # | |
Defined in Auth.Biscuit.Datalog.AST showsPrec :: Int -> PolicyType -> ShowS # show :: PolicyType -> String # showList :: [PolicyType] -> ShowS # | |
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 # | |
Lift PolicyType Source # | |
Defined in Auth.Biscuit.Datalog.AST lift :: Quote m => PolicyType -> m Exp # liftTyped :: forall (m :: Type -> Type). Quote m => PolicyType -> Code m PolicyType # |
type Predicate = Predicate' 'InPredicate 'Representation Source #
data Predicate' (pof :: PredicateOrFact) (ctx :: DatalogContext) Source #
Instances
type QQTerm = Term' 'NotWithinSet 'InPredicate 'WithSlices Source #
In an AST parsed from a WithSlicesr, there might be references to haskell variables
type Query' evalCtx ctx = [QueryItem' evalCtx ctx] Source #
data QueryItem' evalCtx ctx Source #
QueryItem | |
|
Instances
data Rule' evalCtx ctx Source #
Rule | |
|
Instances
data RuleScope' (evalCtx :: EvaluationContext) (ctx :: DatalogContext) Source #
OnlyAuthority | |
Previous | |
BlockId (BlockIdType evalCtx ctx) |
Instances
Lift (BlockIdType evalCtx ctx) => Lift (RuleScope' evalCtx ctx :: Type) Source # | |
Defined in Auth.Biscuit.Datalog.AST lift :: Quote m => RuleScope' evalCtx ctx -> m Exp # liftTyped :: forall (m :: Type -> Type). Quote m => RuleScope' evalCtx ctx -> Code m (RuleScope' evalCtx ctx) # | |
Show (BlockIdType evalCtx ctx) => Show (RuleScope' evalCtx ctx) Source # | |
Defined in Auth.Biscuit.Datalog.AST showsPrec :: Int -> RuleScope' evalCtx ctx -> ShowS # show :: RuleScope' evalCtx ctx -> String # showList :: [RuleScope' evalCtx ctx] -> ShowS # | |
Eq (BlockIdType evalCtx ctx) => Eq (RuleScope' evalCtx ctx) Source # | |
Defined in Auth.Biscuit.Datalog.AST (==) :: RuleScope' evalCtx ctx -> RuleScope' evalCtx ctx -> Bool # (/=) :: RuleScope' evalCtx ctx -> RuleScope' evalCtx ctx -> Bool # | |
Ord (BlockIdType evalCtx ctx) => Ord (RuleScope' evalCtx ctx) Source # | |
Defined in Auth.Biscuit.Datalog.AST compare :: RuleScope' evalCtx ctx -> RuleScope' evalCtx ctx -> Ordering # (<) :: RuleScope' evalCtx ctx -> RuleScope' evalCtx ctx -> Bool # (<=) :: RuleScope' evalCtx ctx -> RuleScope' evalCtx ctx -> Bool # (>) :: RuleScope' evalCtx ctx -> RuleScope' evalCtx ctx -> Bool # (>=) :: RuleScope' evalCtx ctx -> RuleScope' evalCtx ctx -> Bool # max :: RuleScope' evalCtx ctx -> RuleScope' evalCtx ctx -> RuleScope' evalCtx ctx # min :: RuleScope' evalCtx ctx -> RuleScope' evalCtx ctx -> RuleScope' evalCtx ctx # |
type RuleScope = RuleScope' 'Repr 'Representation Source #
type EvalRuleScope = RuleScope' 'Eval 'Representation Source #
type family SetType (inSet :: IsWithinSet) (ctx :: DatalogContext) where ... Source #
type family SliceType (ctx :: DatalogContext) where ... Source #
type family BlockIdType (evalCtx :: EvaluationContext) (ctx :: DatalogContext) where ... Source #
type Value = Term' 'NotWithinSet 'InFact 'Representation 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' 'Repr 'Representation Source #
A biscuit authorizer, containing, facts, rules, checks and policies
data Authorizer' (evalCtx :: EvaluationContext) (ctx :: DatalogContext) 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' evalCtx ctx Source #
AuthorizerPolicy (Policy' evalCtx ctx) | |
BlockElement (BlockElement' evalCtx ctx) |
Instances
(Show (Predicate' 'InFact ctx), Show (Rule' evalCtx ctx), Show (QueryItem' evalCtx ctx)) => Show (AuthorizerElement' evalCtx ctx) Source # | |
Defined in Auth.Biscuit.Datalog.AST showsPrec :: Int -> AuthorizerElement' evalCtx ctx -> ShowS # show :: AuthorizerElement' evalCtx ctx -> String # showList :: [AuthorizerElement' evalCtx ctx] -> ShowS # |
class ToEvaluation elem where Source #
toEvaluation :: [Maybe PublicKey] -> elem 'Repr 'Representation -> elem 'Eval 'Representation Source #
toRepresentation :: elem 'Eval 'Representation -> elem 'Repr 'Representation Source #
Instances
makeRule :: Predicate' 'InPredicate ctx -> [Predicate' 'InPredicate ctx] -> [Expression' ctx] -> Set (RuleScope' 'Repr ctx) -> Validation (NonEmpty Text) (Rule' 'Repr ctx) Source #
makeQueryItem :: [Predicate' 'InPredicate ctx] -> [Expression' ctx] -> Set (RuleScope' 'Repr ctx) -> Validation (NonEmpty Text) (QueryItem' 'Repr ctx) Source #
policyToEvaluation :: [Maybe PublicKey] -> Policy -> EvalPolicy Source #
elementToBlock :: BlockElement' evalCtx ctx -> Block' evalCtx ctx Source #
elementToAuthorizer :: AuthorizerElement' evalCtx ctx -> Authorizer' evalCtx ctx Source #
extractVariables :: [Predicate' 'InPredicate ctx] -> Set Text Source #
queryHasNoScope :: Query -> Bool Source #
queryHasNoV4Operators :: Query -> Bool Source #
ruleHasNoScope :: Rule -> Bool Source #
ruleHasNoV4Operators :: Rule -> Bool Source #
isCheckOne :: Check' evalCtx ctx -> Bool Source #
renderBlock :: Block -> Text Source #
renderAuthorizer :: Authorizer -> Text Source #
renderFact :: Fact -> Text Source #
renderRule :: Rule -> Text Source #
valueToSetTerm :: Value -> Maybe (Term' 'WithinSet 'InFact 'Representation) Source #
toStack :: Expression -> [Op] Source #
substituteAuthorizer :: Map Text Value -> Map Text PublicKey -> Authorizer' 'Repr 'WithSlices -> Validation (NonEmpty Text) Authorizer Source #
substituteBlock :: Map Text Value -> Map Text PublicKey -> Block' 'Repr 'WithSlices -> Validation (NonEmpty Text) Block Source #
substituteCheck :: Map Text Value -> Map Text PublicKey -> Check' 'Repr 'WithSlices -> Validation (NonEmpty Text) Check Source #
substituteExpression :: Map Text Value -> Expression' 'WithSlices -> Validation (NonEmpty Text) Expression Source #
substituteFact :: Map Text Value -> Predicate' 'InFact 'WithSlices -> Validation (NonEmpty Text) Fact Source #
substitutePolicy :: Map Text Value -> Map Text PublicKey -> Policy' 'Repr 'WithSlices -> Validation (NonEmpty Text) Policy Source #
substitutePredicate :: Map Text Value -> Predicate' 'InPredicate 'WithSlices -> Validation (NonEmpty Text) (Predicate' 'InPredicate 'Representation) Source #
substitutePTerm :: Map Text Value -> Term' 'NotWithinSet 'InPredicate 'WithSlices -> Validation (NonEmpty Text) (Term' 'NotWithinSet 'InPredicate 'Representation) Source #
substituteQuery :: Map Text Value -> Map Text PublicKey -> QueryItem' 'Repr 'WithSlices -> Validation (NonEmpty Text) (QueryItem' 'Repr 'Representation) Source #
substituteRule :: Map Text Value -> Map Text PublicKey -> Rule' 'Repr 'WithSlices -> Validation (NonEmpty Text) Rule Source #
substituteTerm :: Map Text Value -> Term' 'NotWithinSet 'InFact 'WithSlices -> Validation (NonEmpty Text) Value Source #