biscuit-haskell-0.3.0.0: Library support for the Biscuit security token
Copyright© Clément Delafargue 2021
LicenseMIT
Maintainerclement@delafargue.name
Safe HaskellSafe-Inferred
LanguageHaskell2010

Auth.Biscuit.Datalog.AST

Description

The Datalog elements

Synopsis

Documentation

data Binary Source #

Instances

Instances details
Show Binary Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Eq Binary Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

(==) :: Binary -> Binary -> Bool #

(/=) :: Binary -> Binary -> Bool #

Ord Binary Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Lift Binary Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

lift :: Quote m => Binary -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Binary -> Code m Binary #

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

Constructors

Block 

Fields

Instances

Instances details
Show Block Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

showsPrec :: Int -> Block -> ShowS #

show :: Block -> String #

showList :: [Block] -> ShowS #

ToEvaluation Block' Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

(Lift (Predicate' 'InFact ctx), Lift (Rule' evalCtx ctx), Lift (QueryItem' evalCtx ctx), Lift (RuleScope' evalCtx ctx)) => Lift (Block' evalCtx ctx :: Type) Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

lift :: Quote m => Block' evalCtx ctx -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Block' evalCtx ctx -> Code m (Block' evalCtx ctx) #

Monoid (Block' evalCtx ctx) Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

mempty :: Block' evalCtx ctx #

mappend :: Block' evalCtx ctx -> Block' evalCtx ctx -> Block' evalCtx ctx #

mconcat :: [Block' evalCtx ctx] -> Block' evalCtx ctx #

Semigroup (Block' evalCtx ctx) Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

(<>) :: Block' evalCtx ctx -> Block' evalCtx ctx -> Block' evalCtx ctx #

sconcat :: NonEmpty (Block' evalCtx ctx) -> Block' evalCtx ctx #

stimes :: Integral b => b -> Block' evalCtx ctx -> Block' evalCtx ctx #

(Eq (Predicate' 'InFact ctx), Eq (Rule' evalCtx ctx), Eq (QueryItem' evalCtx ctx), Eq (RuleScope' evalCtx ctx)) => Eq (Block' evalCtx ctx) Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

(==) :: Block' evalCtx ctx -> Block' evalCtx ctx -> Bool #

(/=) :: Block' evalCtx ctx -> Block' evalCtx ctx -> Bool #

data BlockElement' evalCtx ctx Source #

Constructors

BlockFact (Predicate' 'InFact ctx) 
BlockRule (Rule' evalCtx ctx) 
BlockCheck (Check' evalCtx ctx) 
BlockComment 

Instances

Instances details
(Show (Predicate' 'InFact ctx), Show (Rule' evalCtx ctx), Show (QueryItem' evalCtx ctx)) => Show (BlockElement' evalCtx ctx) Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

showsPrec :: Int -> BlockElement' evalCtx ctx -> ShowS #

show :: BlockElement' evalCtx ctx -> String #

showList :: [BlockElement' evalCtx ctx] -> ShowS #

data CheckKind Source #

Constructors

One 
All 

Instances

Instances details
Show CheckKind Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Eq CheckKind Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Ord CheckKind Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Lift CheckKind Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

lift :: Quote m => CheckKind -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => CheckKind -> Code m CheckKind #

data Check' evalCtx ctx Source #

Constructors

Check 

Fields

Instances

Instances details
ToEvaluation Check' Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Lift (QueryItem' evalCtx ctx) => Lift (Check' evalCtx ctx :: Type) Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

lift :: Quote m => Check' evalCtx ctx -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Check' evalCtx ctx -> Code m (Check' evalCtx ctx) #

Show (QueryItem' evalCtx ctx) => Show (Check' evalCtx ctx) Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

showsPrec :: Int -> Check' evalCtx ctx -> ShowS #

show :: Check' evalCtx ctx -> String #

showList :: [Check' evalCtx ctx] -> ShowS #

Eq (QueryItem' evalCtx ctx) => Eq (Check' evalCtx ctx) Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

(==) :: Check' evalCtx ctx -> Check' evalCtx ctx -> Bool #

(/=) :: Check' evalCtx ctx -> Check' evalCtx ctx -> Bool #

Ord (QueryItem' evalCtx ctx) => Ord (Check' evalCtx ctx) Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

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 #

data Expression' (ctx :: DatalogContext) Source #

Instances

Instances details
Lift (Term' 'NotWithinSet 'InPredicate ctx) => Lift (Expression' ctx :: Type) Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

lift :: Quote m => Expression' ctx -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Expression' ctx -> Code m (Expression' ctx) #

Show (Term' 'NotWithinSet 'InPredicate ctx) => Show (Expression' ctx) Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

showsPrec :: Int -> Expression' ctx -> ShowS #

show :: Expression' ctx -> String #

showList :: [Expression' ctx] -> ShowS #

Eq (Term' 'NotWithinSet 'InPredicate ctx) => Eq (Expression' ctx) Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

(==) :: Expression' ctx -> Expression' ctx -> Bool #

(/=) :: Expression' ctx -> Expression' ctx -> Bool #

Ord (Term' 'NotWithinSet 'InPredicate ctx) => Ord (Expression' ctx) Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

compare :: Expression' ctx -> Expression' ctx -> Ordering #

(<) :: Expression' ctx -> Expression' ctx -> Bool #

(<=) :: Expression' ctx -> Expression' ctx -> Bool #

(>) :: Expression' ctx -> Expression' ctx -> Bool #

(>=) :: Expression' ctx -> Expression' ctx -> Bool #

max :: Expression' ctx -> Expression' ctx -> Expression' ctx #

min :: Expression' ctx -> Expression' ctx -> Expression' ctx #

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

Methods

toTerm :: t -> Term' inSet pof 'Representation Source #

How to turn a value into a datalog item

Instances

Instances details
ToTerm ByteString inSet pof Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

toTerm :: ByteString -> Term' inSet pof 'Representation Source #

ToTerm Text inSet pof Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

toTerm :: Text -> Term' inSet pof 'Representation Source #

ToTerm UTCTime inSet pof Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

toTerm :: UTCTime -> Term' inSet pof 'Representation Source #

ToTerm Integer inSet pof Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

toTerm :: Integer -> Term' inSet pof 'Representation Source #

ToTerm Bool inSet pof Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

toTerm :: Bool -> Term' inSet pof 'Representation Source #

ToTerm Int inSet pof Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

toTerm :: Int -> Term' inSet pof 'Representation Source #

(Foldable f, ToTerm a 'WithinSet 'InFact) => ToTerm (f a) 'NotWithinSet pof Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

class FromValue t where Source #

This class describes how to turn a datalog value into a regular haskell value.

Methods

fromValue :: Value -> Maybe t Source #

Instances

Instances details
FromValue Value Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

FromValue ByteString Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

FromValue Text Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

FromValue UTCTime Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

fromValue :: Value -> Maybe UTCTime Source #

FromValue Integer Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

FromValue Bool Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

FromValue Int Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

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

Constructors

Variable (VariableType inSet pof)

A variable (eg. $0)

LInteger Int

An integer literal (eg. 42)

LString Text

A string literal (eg. "file1")

LDate UTCTime

A date literal (eg. 2021-05-26T18:00:00Z)

LBytes ByteString

A hex literal (eg. hex:ff9900)

LBool Bool

A bool literal (eg. true)

Antiquote (SliceType ctx)

A slice (eg. {name})

TermSet (SetType inSet ctx)

A set (eg. [true, false])

Instances

Instances details
FromValue Value Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

(Lift (VariableType inSet pof), Lift (SetType inSet ctx), Lift (SliceType ctx)) => Lift (Term' inSet pof ctx :: Type) Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

lift :: Quote m => Term' inSet pof ctx -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Term' inSet pof ctx -> Code m (Term' inSet pof ctx) #

(Show (VariableType inSet pof), Show (SliceType ctx), Show (SetType inSet ctx)) => Show (Term' inSet pof ctx) Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

showsPrec :: Int -> Term' inSet pof ctx -> ShowS #

show :: Term' inSet pof ctx -> String #

showList :: [Term' inSet pof ctx] -> ShowS #

(Eq (VariableType inSet pof), Eq (SliceType ctx), Eq (SetType inSet ctx)) => Eq (Term' inSet pof ctx) Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

(==) :: Term' inSet pof ctx -> Term' inSet pof ctx -> Bool #

(/=) :: Term' inSet pof ctx -> Term' inSet pof ctx -> Bool #

(Ord (VariableType inSet pof), Ord (SliceType ctx), Ord (SetType inSet ctx)) => Ord (Term' inSet pof ctx) Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

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 Op Source #

Constructors

VOp Term 
UOp Unary 
BOp Binary 

data DatalogContext Source #

Constructors

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 #

Constructors

Repr 
Eval 

type Policy' evalCtx ctx = (PolicyType, Query' evalCtx ctx) Source #

data PolicyType Source #

Constructors

Allow 
Deny 

data Predicate' (pof :: PredicateOrFact) (ctx :: DatalogContext) Source #

Constructors

Predicate 

Fields

Instances

Instances details
Lift (Term' 'NotWithinSet pof ctx) => Lift (Predicate' pof ctx :: Type) Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

lift :: Quote m => Predicate' pof ctx -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Predicate' pof ctx -> Code m (Predicate' pof ctx) #

Show (Term' 'NotWithinSet pof ctx) => Show (Predicate' pof ctx) Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

showsPrec :: Int -> Predicate' pof ctx -> ShowS #

show :: Predicate' pof ctx -> String #

showList :: [Predicate' pof ctx] -> ShowS #

Eq (Term' 'NotWithinSet pof ctx) => Eq (Predicate' pof ctx) Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

(==) :: Predicate' pof ctx -> Predicate' pof ctx -> Bool #

(/=) :: Predicate' pof ctx -> Predicate' pof ctx -> Bool #

Ord (Term' 'NotWithinSet pof ctx) => Ord (Predicate' pof ctx) Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

compare :: Predicate' pof ctx -> Predicate' pof ctx -> Ordering #

(<) :: Predicate' pof ctx -> Predicate' pof ctx -> Bool #

(<=) :: Predicate' pof ctx -> Predicate' pof ctx -> Bool #

(>) :: Predicate' pof ctx -> Predicate' pof ctx -> Bool #

(>=) :: Predicate' pof ctx -> Predicate' pof ctx -> Bool #

max :: Predicate' pof ctx -> Predicate' pof ctx -> Predicate' pof ctx #

min :: Predicate' pof ctx -> Predicate' pof ctx -> Predicate' pof ctx #

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 #

Constructors

QueryItem 

Fields

Instances

Instances details
ToEvaluation QueryItem' Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

(Lift (Predicate' 'InPredicate ctx), Lift (Expression' ctx), Lift (RuleScope' evalCtx ctx)) => Lift (QueryItem' evalCtx ctx :: Type) Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

lift :: Quote m => QueryItem' evalCtx ctx -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => QueryItem' evalCtx ctx -> Code m (QueryItem' evalCtx ctx) #

(Show (Predicate' 'InPredicate ctx), Show (Expression' ctx), Show (RuleScope' evalCtx ctx)) => Show (QueryItem' evalCtx ctx) Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

showsPrec :: Int -> QueryItem' evalCtx ctx -> ShowS #

show :: QueryItem' evalCtx ctx -> String #

showList :: [QueryItem' evalCtx ctx] -> ShowS #

(Eq (Predicate' 'InPredicate ctx), Eq (Expression' ctx), Eq (RuleScope' evalCtx ctx)) => Eq (QueryItem' evalCtx ctx) Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

(==) :: QueryItem' evalCtx ctx -> QueryItem' evalCtx ctx -> Bool #

(/=) :: QueryItem' evalCtx ctx -> QueryItem' evalCtx ctx -> Bool #

(Ord (Predicate' 'InPredicate ctx), Ord (Expression' ctx), Ord (RuleScope' evalCtx ctx)) => Ord (QueryItem' evalCtx ctx) Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

compare :: QueryItem' evalCtx ctx -> QueryItem' evalCtx ctx -> Ordering #

(<) :: QueryItem' evalCtx ctx -> QueryItem' evalCtx ctx -> Bool #

(<=) :: QueryItem' evalCtx ctx -> QueryItem' evalCtx ctx -> Bool #

(>) :: QueryItem' evalCtx ctx -> QueryItem' evalCtx ctx -> Bool #

(>=) :: QueryItem' evalCtx ctx -> QueryItem' evalCtx ctx -> Bool #

max :: QueryItem' evalCtx ctx -> QueryItem' evalCtx ctx -> QueryItem' evalCtx ctx #

min :: QueryItem' evalCtx ctx -> QueryItem' evalCtx ctx -> QueryItem' evalCtx ctx #

data Rule' evalCtx ctx Source #

Constructors

Rule 

Fields

Instances

Instances details
ToEvaluation Rule' Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

(Lift (Predicate' 'InPredicate ctx), Lift (Expression' ctx), Lift (RuleScope' evalCtx ctx)) => Lift (Rule' evalCtx ctx :: Type) Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

lift :: Quote m => Rule' evalCtx ctx -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Rule' evalCtx ctx -> Code m (Rule' evalCtx ctx) #

(Show (Predicate' 'InPredicate ctx), Show (Expression' ctx), Show (RuleScope' evalCtx ctx)) => Show (Rule' evalCtx ctx) Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

showsPrec :: Int -> Rule' evalCtx ctx -> ShowS #

show :: Rule' evalCtx ctx -> String #

showList :: [Rule' evalCtx ctx] -> ShowS #

(Eq (Predicate' 'InPredicate ctx), Eq (Expression' ctx), Eq (RuleScope' evalCtx ctx)) => Eq (Rule' evalCtx ctx) Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

(==) :: Rule' evalCtx ctx -> Rule' evalCtx ctx -> Bool #

(/=) :: Rule' evalCtx ctx -> Rule' evalCtx ctx -> Bool #

(Ord (Predicate' 'InPredicate ctx), Ord (Expression' ctx), Ord (RuleScope' evalCtx ctx)) => Ord (Rule' evalCtx ctx) Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

compare :: Rule' evalCtx ctx -> Rule' evalCtx ctx -> Ordering #

(<) :: Rule' evalCtx ctx -> Rule' evalCtx ctx -> Bool #

(<=) :: Rule' evalCtx ctx -> Rule' evalCtx ctx -> Bool #

(>) :: Rule' evalCtx ctx -> Rule' evalCtx ctx -> Bool #

(>=) :: Rule' evalCtx ctx -> Rule' evalCtx ctx -> Bool #

max :: Rule' evalCtx ctx -> Rule' evalCtx ctx -> Rule' evalCtx ctx #

min :: Rule' evalCtx ctx -> Rule' evalCtx ctx -> Rule' evalCtx ctx #

data RuleScope' (evalCtx :: EvaluationContext) (ctx :: DatalogContext) Source #

Constructors

OnlyAuthority 
Previous 
BlockId (BlockIdType evalCtx ctx) 

Instances

Instances details
Lift (BlockIdType evalCtx ctx) => Lift (RuleScope' evalCtx ctx :: Type) Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

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 # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

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 # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

(==) :: RuleScope' evalCtx ctx -> RuleScope' evalCtx ctx -> Bool #

(/=) :: RuleScope' evalCtx ctx -> RuleScope' evalCtx ctx -> Bool #

Ord (BlockIdType evalCtx ctx) => Ord (RuleScope' evalCtx ctx) Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

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 family SetType (inSet :: IsWithinSet) (ctx :: DatalogContext) where ... Source #

Equations

SetType 'NotWithinSet ctx = Set (Term' 'WithinSet 'InFact ctx) 
SetType 'WithinSet ctx = Void 

newtype Slice Source #

Constructors

Slice Text 

Instances

Instances details
IsString Slice Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

fromString :: String -> Slice #

Show Slice Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

showsPrec :: Int -> Slice -> ShowS #

show :: Slice -> String #

showList :: [Slice] -> ShowS #

Eq Slice Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

(==) :: Slice -> Slice -> Bool #

(/=) :: Slice -> Slice -> Bool #

Ord Slice Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

compare :: Slice -> Slice -> Ordering #

(<) :: Slice -> Slice -> Bool #

(<=) :: Slice -> Slice -> Bool #

(>) :: Slice -> Slice -> Bool #

(>=) :: Slice -> Slice -> Bool #

max :: Slice -> Slice -> Slice #

min :: Slice -> Slice -> Slice #

Lift Slice Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

lift :: Quote m => Slice -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Slice -> Code m Slice #

data PkOrSlice Source #

Constructors

PkSlice Text 
Pk PublicKey 

Instances

Instances details
Show PkOrSlice Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Eq PkOrSlice Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Ord PkOrSlice Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Lift PkOrSlice Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

lift :: Quote m => PkOrSlice -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => PkOrSlice -> Code m PkOrSlice #

type family SliceType (ctx :: DatalogContext) where ... Source #

data Unary Source #

Constructors

Negate 
Parens 
Length 

Instances

Instances details
Show Unary Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

showsPrec :: Int -> Unary -> ShowS #

show :: Unary -> String #

showList :: [Unary] -> ShowS #

Eq Unary Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

(==) :: Unary -> Unary -> Bool #

(/=) :: Unary -> Unary -> Bool #

Ord Unary Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

compare :: Unary -> Unary -> Ordering #

(<) :: Unary -> Unary -> Bool #

(<=) :: Unary -> Unary -> Bool #

(>) :: Unary -> Unary -> Bool #

(>=) :: Unary -> Unary -> Bool #

max :: Unary -> Unary -> Unary #

min :: Unary -> Unary -> Unary #

Lift Unary Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

lift :: Quote m => Unary -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Unary -> Code m Unary #

type Value = Term' 'NotWithinSet 'InFact 'Representation Source #

A term that is not a variable

type family VariableType (inSet :: IsWithinSet) (pof :: PredicateOrFact) where ... Source #

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.

Constructors

Authorizer 

Fields

Instances

Instances details
ToEvaluation Authorizer' Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

(Lift (Block' evalCtx ctx), Lift (QueryItem' evalCtx ctx)) => Lift (Authorizer' evalCtx ctx :: Type) Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

lift :: Quote m => Authorizer' evalCtx ctx -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Authorizer' evalCtx ctx -> Code m (Authorizer' evalCtx ctx) #

Monoid (Authorizer' evalCtx ctx) Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

mempty :: Authorizer' evalCtx ctx #

mappend :: Authorizer' evalCtx ctx -> Authorizer' evalCtx ctx -> Authorizer' evalCtx ctx #

mconcat :: [Authorizer' evalCtx ctx] -> Authorizer' evalCtx ctx #

Semigroup (Authorizer' evalCtx ctx) Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

(<>) :: Authorizer' evalCtx ctx -> Authorizer' evalCtx ctx -> Authorizer' evalCtx ctx #

sconcat :: NonEmpty (Authorizer' evalCtx ctx) -> Authorizer' evalCtx ctx #

stimes :: Integral b => b -> Authorizer' evalCtx ctx -> Authorizer' evalCtx ctx #

(Show (Block' evalCtx ctx), Show (QueryItem' evalCtx ctx)) => Show (Authorizer' evalCtx ctx) Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

showsPrec :: Int -> Authorizer' evalCtx ctx -> ShowS #

show :: Authorizer' evalCtx ctx -> String #

showList :: [Authorizer' evalCtx ctx] -> ShowS #

(Eq (Block' evalCtx ctx), Eq (QueryItem' evalCtx ctx)) => Eq (Authorizer' evalCtx ctx) Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

(==) :: Authorizer' evalCtx ctx -> Authorizer' evalCtx ctx -> Bool #

(/=) :: Authorizer' evalCtx ctx -> Authorizer' evalCtx ctx -> Bool #

data AuthorizerElement' evalCtx ctx Source #

Constructors

AuthorizerPolicy (Policy' evalCtx ctx) 
BlockElement (BlockElement' evalCtx ctx) 

Instances

Instances details
(Show (Predicate' 'InFact ctx), Show (Rule' evalCtx ctx), Show (QueryItem' evalCtx ctx)) => Show (AuthorizerElement' evalCtx ctx) Source # 
Instance details

Defined in Auth.Biscuit.Datalog.AST

Methods

showsPrec :: Int -> AuthorizerElement' evalCtx ctx -> ShowS #

show :: AuthorizerElement' evalCtx ctx -> String #

showList :: [AuthorizerElement' evalCtx ctx] -> ShowS #

class ToEvaluation elem where Source #

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 #

elementToBlock :: BlockElement' evalCtx ctx -> Block' evalCtx ctx Source #

isCheckOne :: Check' evalCtx ctx -> Bool Source #