Copyright | © Clément Delafargue 2021 |
---|---|
License | MIT |
Maintainer | clement@delafargue.name |
Safe Haskell | None |
Language | Haskell2010 |
Haskell data structures mapping the biscuit protobuf definitions
Synopsis
- data Biscuit = Biscuit {}
- data Signature = Signature {
- parameters :: Repeated 1 (Value ByteString)
- z :: Required 2 (Value ByteString)
- data Block = Block {}
- newtype FactV1 = FactV1 {
- predicate :: Required 1 (Message PredicateV1)
- data RuleV1 = RuleV1 {
- head :: Required 1 (Message PredicateV1)
- body :: Repeated 2 (Message PredicateV1)
- expressions :: Repeated 3 (Message ExpressionV1)
- newtype CheckV1 = CheckV1 {}
- data PredicateV1 = PredicateV1 {}
- data IDV1
- newtype ExpressionV1 = ExpressionV1 {}
- newtype IDSet = IDSet {}
- data Op
- newtype OpUnary = OpUnary {
- kind :: Required 1 (Enumeration UnaryKind)
- data UnaryKind
- newtype OpBinary = OpBinary {
- kind :: Required 1 (Enumeration BinaryKind)
- data BinaryKind
- = LessThan
- | GreaterThan
- | LessOrEqual
- | GreaterOrEqual
- | Equal
- | Contains
- | Prefix
- | Suffix
- | Regex
- | Add
- | Sub
- | Mul
- | Div
- | And
- | Or
- | Intersection
- | Union
- getField :: HasField a => a -> FieldType a
- putField :: HasField a => FieldType a -> a
- decodeBlockList :: ByteString -> Either String Biscuit
- decodeBlock :: ByteString -> Either String Block
- encodeBlockList :: Biscuit -> ByteString
- encodeBlock :: Block -> ByteString
Documentation
Instances
Show Biscuit Source # | |
Generic Biscuit Source # | |
Decode Biscuit Source # | |
Encode Biscuit Source # | |
Defined in Auth.Biscuit.Proto | |
type Rep Biscuit Source # | |
Defined in Auth.Biscuit.Proto type Rep Biscuit = D1 ('MetaData "Biscuit" "Auth.Biscuit.Proto" "biscuit-haskell-0.1.1.0-inplace" 'False) (C1 ('MetaCons "Biscuit" 'PrefixI 'True) ((S1 ('MetaSel ('Just "authority") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Required 1 (Value ByteString))) :*: S1 ('MetaSel ('Just "blocks") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Repeated 2 (Value ByteString)))) :*: (S1 ('MetaSel ('Just "keys") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Repeated 3 (Value ByteString))) :*: S1 ('MetaSel ('Just "signature") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Required 4 (Message Signature)))))) |
Signature | |
|
Instances
Show Signature Source # | |
Generic Signature Source # | |
Decode Signature Source # | |
Encode Signature Source # | |
Defined in Auth.Biscuit.Proto | |
type Rep Signature Source # | |
Defined in Auth.Biscuit.Proto type Rep Signature = D1 ('MetaData "Signature" "Auth.Biscuit.Proto" "biscuit-haskell-0.1.1.0-inplace" 'False) (C1 ('MetaCons "Signature" 'PrefixI 'True) (S1 ('MetaSel ('Just "parameters") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Repeated 1 (Value ByteString))) :*: S1 ('MetaSel ('Just "z") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Required 2 (Value ByteString))))) |
Instances
FactV1 | |
|
Instances
Show FactV1 Source # | |
Generic FactV1 Source # | |
Decode FactV1 Source # | |
Encode FactV1 Source # | |
Defined in Auth.Biscuit.Proto | |
type Rep FactV1 Source # | |
Defined in Auth.Biscuit.Proto type Rep FactV1 = D1 ('MetaData "FactV1" "Auth.Biscuit.Proto" "biscuit-haskell-0.1.1.0-inplace" 'True) (C1 ('MetaCons "FactV1" 'PrefixI 'True) (S1 ('MetaSel ('Just "predicate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Required 1 (Message PredicateV1))))) |
RuleV1 | |
|
Instances
Show RuleV1 Source # | |
Generic RuleV1 Source # | |
Decode RuleV1 Source # | |
Encode RuleV1 Source # | |
Defined in Auth.Biscuit.Proto | |
type Rep RuleV1 Source # | |
Defined in Auth.Biscuit.Proto type Rep RuleV1 = D1 ('MetaData "RuleV1" "Auth.Biscuit.Proto" "biscuit-haskell-0.1.1.0-inplace" 'False) (C1 ('MetaCons "RuleV1" 'PrefixI 'True) (S1 ('MetaSel ('Just "head") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Required 1 (Message PredicateV1))) :*: (S1 ('MetaSel ('Just "body") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Repeated 2 (Message PredicateV1))) :*: S1 ('MetaSel ('Just "expressions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Repeated 3 (Message ExpressionV1)))))) |
data PredicateV1 Source #
Instances
Show PredicateV1 Source # | |
Defined in Auth.Biscuit.Proto showsPrec :: Int -> PredicateV1 -> ShowS # show :: PredicateV1 -> String # showList :: [PredicateV1] -> ShowS # | |
Generic PredicateV1 Source # | |
Defined in Auth.Biscuit.Proto type Rep PredicateV1 :: Type -> Type # from :: PredicateV1 -> Rep PredicateV1 x # to :: Rep PredicateV1 x -> PredicateV1 # | |
Decode PredicateV1 Source # | |
Defined in Auth.Biscuit.Proto | |
Encode PredicateV1 Source # | |
Defined in Auth.Biscuit.Proto encode :: PredicateV1 -> Put # | |
type Rep PredicateV1 Source # | |
Defined in Auth.Biscuit.Proto type Rep PredicateV1 = D1 ('MetaData "PredicateV1" "Auth.Biscuit.Proto" "biscuit-haskell-0.1.1.0-inplace" 'False) (C1 ('MetaCons "PredicateV1" 'PrefixI 'True) (S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Required 1 (Value Int64))) :*: S1 ('MetaSel ('Just "ids") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Repeated 2 (Message IDV1))))) |
IDSymbol (Required 1 (Value Int64)) | |
IDVariable (Required 2 (Value Int32)) | |
IDInteger (Required 3 (Value Int64)) | |
IDString (Required 4 (Value Text)) | |
IDDate (Required 5 (Value Int64)) | |
IDBytes (Required 6 (Value ByteString)) | |
IDBool (Required 7 (Value Bool)) | |
IDIDSet (Required 8 (Message IDSet)) |
Instances
newtype ExpressionV1 Source #
Instances
Show ExpressionV1 Source # | |
Defined in Auth.Biscuit.Proto showsPrec :: Int -> ExpressionV1 -> ShowS # show :: ExpressionV1 -> String # showList :: [ExpressionV1] -> ShowS # | |
Generic ExpressionV1 Source # | |
Defined in Auth.Biscuit.Proto type Rep ExpressionV1 :: Type -> Type # from :: ExpressionV1 -> Rep ExpressionV1 x # to :: Rep ExpressionV1 x -> ExpressionV1 # | |
Decode ExpressionV1 Source # | |
Defined in Auth.Biscuit.Proto | |
Encode ExpressionV1 Source # | |
Defined in Auth.Biscuit.Proto encode :: ExpressionV1 -> Put # | |
type Rep ExpressionV1 Source # | |
Defined in Auth.Biscuit.Proto type Rep ExpressionV1 = D1 ('MetaData "ExpressionV1" "Auth.Biscuit.Proto" "biscuit-haskell-0.1.1.0-inplace" 'True) (C1 ('MetaCons "ExpressionV1" 'PrefixI 'True) (S1 ('MetaSel ('Just "ops") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Repeated 1 (Message Op))))) |
OpVValue (Required 1 (Message IDV1)) | |
OpVUnary (Required 2 (Message OpUnary)) | |
OpVBinary (Required 3 (Message OpBinary)) |
Instances
Show Op Source # | |
Generic Op Source # | |
Decode Op Source # | |
Encode Op Source # | |
Defined in Auth.Biscuit.Proto | |
type Rep Op Source # | |
Defined in Auth.Biscuit.Proto type Rep Op = D1 ('MetaData "Op" "Auth.Biscuit.Proto" "biscuit-haskell-0.1.1.0-inplace" 'False) (C1 ('MetaCons "OpVValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Required 1 (Message IDV1)))) :+: (C1 ('MetaCons "OpVUnary" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Required 2 (Message OpUnary)))) :+: C1 ('MetaCons "OpVBinary" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Required 3 (Message OpBinary)))))) |
OpUnary | |
|
Instances
Show OpUnary Source # | |
Generic OpUnary Source # | |
Decode OpUnary Source # | |
Encode OpUnary Source # | |
Defined in Auth.Biscuit.Proto | |
type Rep OpUnary Source # | |
Defined in Auth.Biscuit.Proto type Rep OpUnary = D1 ('MetaData "OpUnary" "Auth.Biscuit.Proto" "biscuit-haskell-0.1.1.0-inplace" 'True) (C1 ('MetaCons "OpUnary" 'PrefixI 'True) (S1 ('MetaSel ('Just "kind") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Required 1 (Enumeration UnaryKind))))) |
Instances
Bounded UnaryKind Source # | |
Enum UnaryKind Source # | |
Defined in Auth.Biscuit.Proto succ :: UnaryKind -> UnaryKind # pred :: UnaryKind -> UnaryKind # fromEnum :: UnaryKind -> Int # enumFrom :: UnaryKind -> [UnaryKind] # enumFromThen :: UnaryKind -> UnaryKind -> [UnaryKind] # enumFromTo :: UnaryKind -> UnaryKind -> [UnaryKind] # enumFromThenTo :: UnaryKind -> UnaryKind -> UnaryKind -> [UnaryKind] # | |
Show UnaryKind Source # | |
OpBinary | |
|
Instances
Show OpBinary Source # | |
Generic OpBinary Source # | |
Decode OpBinary Source # | |
Encode OpBinary Source # | |
Defined in Auth.Biscuit.Proto | |
type Rep OpBinary Source # | |
Defined in Auth.Biscuit.Proto type Rep OpBinary = D1 ('MetaData "OpBinary" "Auth.Biscuit.Proto" "biscuit-haskell-0.1.1.0-inplace" 'True) (C1 ('MetaCons "OpBinary" 'PrefixI 'True) (S1 ('MetaSel ('Just "kind") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Required 1 (Enumeration BinaryKind))))) |
data BinaryKind Source #
LessThan | |
GreaterThan | |
LessOrEqual | |
GreaterOrEqual | |
Equal | |
Contains | |
Prefix | |
Suffix | |
Regex | |
Add | |
Sub | |
Mul | |
Div | |
And | |
Or | |
Intersection | |
Union |
Instances
Bounded BinaryKind Source # | |
Defined in Auth.Biscuit.Proto minBound :: BinaryKind # maxBound :: BinaryKind # | |
Enum BinaryKind Source # | |
Defined in Auth.Biscuit.Proto succ :: BinaryKind -> BinaryKind # pred :: BinaryKind -> BinaryKind # toEnum :: Int -> BinaryKind # fromEnum :: BinaryKind -> Int # enumFrom :: BinaryKind -> [BinaryKind] # enumFromThen :: BinaryKind -> BinaryKind -> [BinaryKind] # enumFromTo :: BinaryKind -> BinaryKind -> [BinaryKind] # enumFromThenTo :: BinaryKind -> BinaryKind -> BinaryKind -> [BinaryKind] # | |
Show BinaryKind Source # | |
Defined in Auth.Biscuit.Proto showsPrec :: Int -> BinaryKind -> ShowS # show :: BinaryKind -> String # showList :: [BinaryKind] -> ShowS # |
decodeBlock :: ByteString -> Either String Block Source #
encodeBlockList :: Biscuit -> ByteString Source #
encodeBlock :: Block -> ByteString Source #