Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- block :: QuasiQuoter
- check :: QuasiQuoter
- fact :: QuasiQuoter
- predicate :: QuasiQuoter
- rule :: QuasiQuoter
- authorizer :: QuasiQuoter
- query :: QuasiQuoter
- checkParser :: HasParsers 'InPredicate ctx => Parser (Check' ctx)
- expressionParser :: HasParsers 'InPredicate ctx => Parser (Expression' ctx)
- policyParser :: HasParsers 'InPredicate ctx => Parser (Policy' ctx)
- predicateParser :: HasParsers pof ctx => Parser (Predicate' pof ctx)
- ruleParser :: HasParsers 'InPredicate ctx => Parser (Rule' ctx)
- termParser :: forall inSet pof ctx. HasTermParsers inSet pof ctx => Parser (Term' inSet pof ctx)
- blockParser :: (HasParsers 'InPredicate ctx, HasParsers 'InFact ctx, Show (BlockElement' ctx)) => Parser (Block' ctx)
- authorizerParser :: (HasParsers 'InPredicate ctx, HasParsers 'InFact ctx, Show (AuthorizerElement' ctx)) => Parser (Authorizer' ctx)
- type HasParsers pof ctx = HasTermParsers 'NotWithinSet pof ctx
- type HasTermParsers inSet pof ctx = (ConditionalParse (SliceType 'QuasiQuote) (SliceType ctx), ConditionalParse (VariableType 'NotWithinSet 'InPredicate) (VariableType inSet pof), SetParser inSet ctx)
Documentation
block :: QuasiQuoter Source #
Compile-time parser for a block expression, intended to be used with the
QuasiQuotes
extension.
A typical use of block
looks like this:
let fileName = "data.pdf" in [block| // datalog can reference haskell variables with ${variableName} resource(${fileName}); rule($variable) <- fact($value), other_fact($value); check if operation("read"); |]
check :: QuasiQuoter Source #
Quasiquoter for a check expression. You can reference haskell variables
like this: ${variableName}
.
You most likely want to directly use block
or authorizer
instead.
fact :: QuasiQuoter Source #
Quasiquoter for a fact expression. You can reference haskell variables
like this: ${variableName}
.
You most likely want to directly use block
or authorizer
instead.
predicate :: QuasiQuoter Source #
Quasiquoter for a predicate expression. You can reference haskell variables
like this: ${variableName}
.
You most likely want to directly use block
or authorizer
instead.
rule :: QuasiQuoter Source #
Quasiquoter for a rule expression. You can reference haskell variables
like this: ${variableName}
.
You most likely want to directly use block
or authorizer
instead.
authorizer :: QuasiQuoter Source #
Compile-time parser for an authorizer expression, intended to be used with the
QuasiQuotes
extension.
A typical use of authorizer
looks like this:
do now <- getCurrentTime pure [authorizer| // datalog can reference haskell variables with ${variableName} current_time(${now}); // authorizers can contain facts, rules and checks like blocks, but // also declare policies. While every check has to pass for a biscuit to // be valid, policies are tried in order. The first one to match decides // if the token is valid or not allow if resource("file1"); deny if true; |]
query :: QuasiQuoter Source #
Compile-time parser for a query expression, intended to be used with the
QuasiQuotes
extension.
A typical use of query
looks like this:
[query|user($user_id) or group($group_id)|]
checkParser :: HasParsers 'InPredicate ctx => Parser (Check' ctx) Source #
expressionParser :: HasParsers 'InPredicate ctx => Parser (Expression' ctx) Source #
policyParser :: HasParsers 'InPredicate ctx => Parser (Policy' ctx) Source #
predicateParser :: HasParsers pof ctx => Parser (Predicate' pof ctx) Source #
ruleParser :: HasParsers 'InPredicate ctx => Parser (Rule' ctx) Source #
termParser :: forall inSet pof ctx. HasTermParsers inSet pof ctx => Parser (Term' inSet pof ctx) Source #
blockParser :: (HasParsers 'InPredicate ctx, HasParsers 'InFact ctx, Show (BlockElement' ctx)) => Parser (Block' ctx) Source #
authorizerParser :: (HasParsers 'InPredicate ctx, HasParsers 'InFact ctx, Show (AuthorizerElement' ctx)) => Parser (Authorizer' ctx) Source #
type HasParsers pof ctx = HasTermParsers 'NotWithinSet pof ctx Source #
type HasTermParsers inSet pof ctx = (ConditionalParse (SliceType 'QuasiQuote) (SliceType ctx), ConditionalParse (VariableType 'NotWithinSet 'InPredicate) (VariableType inSet pof), SetParser inSet ctx) Source #