Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- type BlockWithRevocationId = (Block, ByteString, Maybe PublicKey)
- runAuthorizer :: BlockWithRevocationId -> [BlockWithRevocationId] -> Authorizer -> IO (Either ExecutionError AuthorizationSuccess)
- runAuthorizerWithLimits :: Limits -> BlockWithRevocationId -> [BlockWithRevocationId] -> Authorizer -> IO (Either ExecutionError AuthorizationSuccess)
- runAuthorizerNoTimeout :: Limits -> BlockWithRevocationId -> [BlockWithRevocationId] -> Authorizer -> Either ExecutionError AuthorizationSuccess
- runFactGeneration :: Limits -> Natural -> Map Natural (Set EvalRule) -> FactGroup -> Either PureExecError FactGroup
- data PureExecError
- = Facts
- | Iterations
- | BadRule
- data AuthorizationSuccess = AuthorizationSuccess {}
- getBindings :: AuthorizationSuccess -> Set Bindings
- queryGeneratedFacts :: [Maybe PublicKey] -> AuthorizationSuccess -> Query -> Set Bindings
- queryAvailableFacts :: [Maybe PublicKey] -> FactGroup -> Limits -> Query -> Set Bindings
- getVariableValues :: (Ord t, FromValue t) => Set Bindings -> Text -> Set t
- getSingleVariableValue :: (Ord t, FromValue t) => Set Bindings -> Text -> Maybe t
- newtype FactGroup = FactGroup {}
- collectWorld :: Natural -> EvalBlock -> (Map Natural (Set EvalRule), FactGroup)
Documentation
type BlockWithRevocationId = (Block, ByteString, Maybe PublicKey) Source #
:: BlockWithRevocationId | The authority block |
-> [BlockWithRevocationId] | The extra blocks |
-> Authorizer | A authorizer |
-> IO (Either ExecutionError AuthorizationSuccess) |
Given a series of blocks and an authorizer, ensure that all the checks and policies match
runAuthorizerWithLimits Source #
:: Limits | custom limits |
-> BlockWithRevocationId | The authority block |
-> [BlockWithRevocationId] | The extra blocks |
-> Authorizer | A authorizer |
-> IO (Either ExecutionError AuthorizationSuccess) |
Given a series of blocks and an authorizer, ensure that all the checks and policies match, with provided execution constraints
runAuthorizerNoTimeout :: Limits -> BlockWithRevocationId -> [BlockWithRevocationId] -> Authorizer -> Either ExecutionError AuthorizationSuccess Source #
runFactGeneration :: Limits -> Natural -> Map Natural (Set EvalRule) -> FactGroup -> Either PureExecError FactGroup Source #
Small helper used in tests to directly provide rules and facts without creating a biscuit token
data PureExecError Source #
A subset of ExecutionError
that can only happen during fact generation
Instances
Show PureExecError Source # | |
Defined in Auth.Biscuit.Datalog.ScopedExecutor showsPrec :: Int -> PureExecError -> ShowS # show :: PureExecError -> String # showList :: [PureExecError] -> ShowS # | |
Eq PureExecError Source # | |
Defined in Auth.Biscuit.Datalog.ScopedExecutor (==) :: PureExecError -> PureExecError -> Bool # (/=) :: PureExecError -> PureExecError -> Bool # |
data AuthorizationSuccess Source #
Proof that a biscuit was authorized successfully. In addition to the matched
allow query
, the generated facts are kept around for further querying.
Since only authority facts can be trusted, they are kept separate.
AuthorizationSuccess | |
|
Instances
Show AuthorizationSuccess Source # | |
Defined in Auth.Biscuit.Datalog.ScopedExecutor showsPrec :: Int -> AuthorizationSuccess -> ShowS # show :: AuthorizationSuccess -> String # showList :: [AuthorizationSuccess] -> ShowS # | |
Eq AuthorizationSuccess Source # | |
Defined in Auth.Biscuit.Datalog.ScopedExecutor (==) :: AuthorizationSuccess -> AuthorizationSuccess -> Bool # (/=) :: AuthorizationSuccess -> AuthorizationSuccess -> Bool # |
getBindings :: AuthorizationSuccess -> Set Bindings Source #
Get the matched variables from the allow
query used to authorize the biscuit.
This can be used in conjuction with getVariableValues
or getSingleVariableValue
to extract the actual values
queryGeneratedFacts :: [Maybe PublicKey] -> AuthorizationSuccess -> Query -> Set Bindings Source #
getVariableValues :: (Ord t, FromValue t) => Set Bindings -> Text -> Set t Source #
Extract a set of values from a matched variable for a specific type.
Returning Set Value
allows to get all values, whatever their type.
getSingleVariableValue :: (Ord t, FromValue t) => Set Bindings -> Text -> Maybe t Source #
Extract exactly one value from a matched variable. If the variable has 0
matches or more than one match, Nothing
will be returned