Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- type Parser = Parsec SemanticError Text
- type Span = (Int, Int)
- data SemanticError
- run :: Parser a -> Text -> Either String a
- l :: Parser a -> Parser a
- getSpan :: Parser a -> Parser (Span, a)
- registerError :: (Span -> SemanticError) -> Span -> Parser a
- forbid :: (Span -> SemanticError) -> Parser a -> Parser b
- variableParser :: Parser Text
- haskellVariableParser :: Parser Text
- setParser :: Parser (Set (Term' 'WithinSet 'InFact 'WithSlices))
- factTermParser :: Parser (Term' 'NotWithinSet 'InFact 'WithSlices)
- predicateTermParser :: Parser (Term' 'NotWithinSet 'InPredicate 'WithSlices)
- termParser :: Parser (VariableType inSet pof) -> Parser (SetType inSet 'WithSlices) -> Parser (Term' inSet pof 'WithSlices)
- intParser :: Parser Int64
- hexParser :: Parser ByteString
- publicKeyParser :: Parser PublicKey
- rfc3339DateParser :: Parser UTCTime
- predicateParser' :: Parser (Term' 'NotWithinSet pof 'WithSlices) -> Parser (Predicate' pof 'WithSlices)
- factParser :: Parser (Predicate' 'InFact 'WithSlices)
- predicateParser :: Parser (Predicate' 'InPredicate 'WithSlices)
- expressionParser :: Parser (Expression' 'WithSlices)
- table :: [[Operator Parser (Expression' 'WithSlices)]]
- binaryMethodParser :: Parser (Expression' 'WithSlices -> Expression' 'WithSlices)
- unaryMethodParser :: Parser (Expression' 'WithSlices -> Expression' 'WithSlices)
- methodsParser :: Parser (Expression' 'WithSlices)
- unaryParens :: Parser (Expression' 'WithSlices)
- exprTerm :: Parser (Expression' 'WithSlices)
- ruleParser :: Bool -> Parser (Rule' 'Repr 'WithSlices)
- ruleBodyParser :: Bool -> Parser ([Predicate' 'InPredicate 'WithSlices], [Expression' 'WithSlices], Set (RuleScope' 'Repr 'WithSlices))
- scopeParser :: Bool -> Parser (Set (RuleScope' 'Repr 'WithSlices))
- queryItemParser :: Bool -> Parser (QueryItem' 'Repr 'WithSlices)
- queryParser :: Bool -> Parser [QueryItem' 'Repr 'WithSlices]
- checkParser :: Bool -> Parser (Check' 'Repr 'WithSlices)
- policyParser :: Parser (Policy' 'Repr 'WithSlices)
- blockElementParser :: Bool -> Parser (BlockElement' 'Repr 'WithSlices)
- authorizerElementParser :: Parser (AuthorizerElement' 'Repr 'WithSlices)
- blockParser :: Parser (Block' 'Repr 'WithSlices)
- authorizerParser :: Parser (Authorizer' 'Repr 'WithSlices)
- parseWithParams :: Parser (a 'WithSlices) -> (Map Text Value -> Map Text PublicKey -> a 'WithSlices -> Validation (NonEmpty Text) (a 'Representation)) -> Text -> Map Text Value -> Map Text PublicKey -> Either (NonEmpty Text) (a 'Representation)
- parseBlock :: Text -> Map Text Value -> Map Text PublicKey -> Either (NonEmpty Text) Block
- parseAuthorizer :: Text -> Map Text Value -> Map Text PublicKey -> Either (NonEmpty Text) Authorizer
- compileParser :: Lift a => Parser a -> (a -> Q Exp) -> String -> Q Exp
- rule :: QuasiQuoter
- predicate :: QuasiQuoter
- fact :: QuasiQuoter
- check :: QuasiQuoter
- block :: QuasiQuoter
- authorizer :: QuasiQuoter
- query :: QuasiQuoter
Documentation
data SemanticError Source #
VarInFact Span | |
VarInSet Span | |
NestedSet Span | |
InvalidBs Text Span | |
InvalidPublicKey Text Span | |
UnboundVariables (NonEmpty Text) Span | |
PreviousInAuthorizer Span |
Instances
Eq SemanticError Source # | |
Defined in Auth.Biscuit.Datalog.Parser (==) :: SemanticError -> SemanticError -> Bool # (/=) :: SemanticError -> SemanticError -> Bool # | |
Ord SemanticError Source # | |
Defined in Auth.Biscuit.Datalog.Parser compare :: SemanticError -> SemanticError -> Ordering # (<) :: SemanticError -> SemanticError -> Bool # (<=) :: SemanticError -> SemanticError -> Bool # (>) :: SemanticError -> SemanticError -> Bool # (>=) :: SemanticError -> SemanticError -> Bool # max :: SemanticError -> SemanticError -> SemanticError # min :: SemanticError -> SemanticError -> SemanticError # | |
ShowErrorComponent SemanticError Source # | |
Defined in Auth.Biscuit.Datalog.Parser showErrorComponent :: SemanticError -> String # errorComponentLen :: SemanticError -> Int # |
registerError :: (Span -> SemanticError) -> Span -> Parser a Source #
factTermParser :: Parser (Term' 'NotWithinSet 'InFact 'WithSlices) Source #
termParser :: Parser (VariableType inSet pof) -> Parser (SetType inSet 'WithSlices) -> Parser (Term' inSet pof 'WithSlices) Source #
predicateParser' :: Parser (Term' 'NotWithinSet pof 'WithSlices) -> Parser (Predicate' pof 'WithSlices) Source #
factParser :: Parser (Predicate' 'InFact 'WithSlices) Source #
table :: [[Operator Parser (Expression' 'WithSlices)]] Source #
exprTerm :: Parser (Expression' 'WithSlices) Source #
ruleParser :: Bool -> Parser (Rule' 'Repr 'WithSlices) Source #
ruleBodyParser :: Bool -> Parser ([Predicate' 'InPredicate 'WithSlices], [Expression' 'WithSlices], Set (RuleScope' 'Repr 'WithSlices)) Source #
scopeParser :: Bool -> Parser (Set (RuleScope' 'Repr 'WithSlices)) Source #
queryItemParser :: Bool -> Parser (QueryItem' 'Repr 'WithSlices) Source #
queryParser :: Bool -> Parser [QueryItem' 'Repr 'WithSlices] Source #
checkParser :: Bool -> Parser (Check' 'Repr 'WithSlices) Source #
policyParser :: Parser (Policy' 'Repr 'WithSlices) Source #
blockElementParser :: Bool -> Parser (BlockElement' 'Repr 'WithSlices) Source #
blockParser :: Parser (Block' 'Repr 'WithSlices) Source #
parseWithParams :: Parser (a 'WithSlices) -> (Map Text Value -> Map Text PublicKey -> a 'WithSlices -> Validation (NonEmpty Text) (a 'Representation)) -> Text -> Map Text Value -> Map Text PublicKey -> Either (NonEmpty Text) (a 'Representation) Source #
parseAuthorizer :: Text -> Map Text Value -> Map Text PublicKey -> Either (NonEmpty Text) Authorizer Source #
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.
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.
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.
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.
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"); |]
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)|]