| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Auth.Biscuit.Datalog.Parser
Synopsis
- block :: QuasiQuoter
- check :: QuasiQuoter
- fact :: QuasiQuoter
- predicate :: QuasiQuoter
- rule :: QuasiQuoter
- verifier :: 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 (ID' inSet pof ctx)
- verifierParser :: (HasParsers 'InPredicate ctx, HasParsers 'InFact ctx, Show (VerifierElement' ctx)) => Parser (Verifier' 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 #
Quasiquoter for a block expression. You can reference haskell variables
 like this: ${variableName}.
A typical use of block looks like this:
[block|
  resource(#authority, ${fileName});
  rule($variable) <- fact($value), other_fact($value);
  check if operation(#ambient, #read);
|]check :: QuasiQuoter Source #
fact :: QuasiQuoter Source #
rule :: QuasiQuoter Source #
verifier :: QuasiQuoter Source #
Quasiquoter for a verifier expression. You can reference haskell variables
 like this: ${variableName}.
A typical use of block looks like this:
[verifier|
  current_time(#ambient, ${now});
  allow if resource(#authority, "file1");
  deny if true;
|]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 (ID' inSet pof ctx) Source #
verifierParser :: (HasParsers 'InPredicate ctx, HasParsers 'InFact ctx, Show (VerifierElement' ctx)) => Parser (Verifier' 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 #