Copyright | © Clément Delafargue 2021 |
---|---|
License | MIT |
Maintainer | clement@delafargue.name |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Haskell data structures mapping the biscuit protobuf definitions
Documentation
Biscuit | |
|
Instances
Generic Biscuit Source # | |
Show Biscuit Source # | |
Decode Biscuit Source # | |
Defined in Auth.Biscuit.Proto | |
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.3.0.0-inplace" 'False) (C1 ('MetaCons "Biscuit" 'PrefixI 'True) ((S1 ('MetaSel ('Just "rootKeyId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Optional 1 (Value Int32))) :*: S1 ('MetaSel ('Just "authority") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Required 2 (Message SignedBlock)))) :*: (S1 ('MetaSel ('Just "blocks") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Repeated 3 (Message SignedBlock))) :*: S1 ('MetaSel ('Just "proof") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Required 4 (Message Proof)))))) |
data SignedBlock Source #
SignedBlock | |
|
Instances
PublicKey | |
|
Instances
Generic PublicKey Source # | |
Show PublicKey Source # | |
Decode PublicKey Source # | |
Defined in Auth.Biscuit.Proto | |
Encode PublicKey Source # | |
Defined in Auth.Biscuit.Proto | |
type Rep PublicKey Source # | |
Defined in Auth.Biscuit.Proto type Rep PublicKey = D1 ('MetaData "PublicKey" "Auth.Biscuit.Proto" "biscuit-haskell-0.3.0.0-inplace" 'False) (C1 ('MetaCons "PublicKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "algorithm") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Required 1 (Enumeration Algorithm))) :*: S1 ('MetaSel ('Just "key") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Required 2 (Value ByteString))))) |
Instances
Bounded Algorithm Source # | |
Enum Algorithm Source # | |
Defined in Auth.Biscuit.Proto succ :: Algorithm -> Algorithm # pred :: Algorithm -> Algorithm # fromEnum :: Algorithm -> Int # enumFrom :: Algorithm -> [Algorithm] # enumFromThen :: Algorithm -> Algorithm -> [Algorithm] # enumFromTo :: Algorithm -> Algorithm -> [Algorithm] # enumFromThenTo :: Algorithm -> Algorithm -> Algorithm -> [Algorithm] # | |
Show Algorithm Source # | |
data ExternalSig Source #
ExternalSig | |
|
Instances
ProofSecret (Required 1 (Value ByteString)) | |
ProofSignature (Required 2 (Value ByteString)) |
Instances
Generic Proof Source # | |
Show Proof Source # | |
Decode Proof Source # | |
Defined in Auth.Biscuit.Proto | |
Encode Proof Source # | |
Defined in Auth.Biscuit.Proto | |
type Rep Proof Source # | |
Defined in Auth.Biscuit.Proto type Rep Proof = D1 ('MetaData "Proof" "Auth.Biscuit.Proto" "biscuit-haskell-0.3.0.0-inplace" 'False) (C1 ('MetaCons "ProofSecret" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Required 1 (Value ByteString)))) :+: C1 ('MetaCons "ProofSignature" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Required 2 (Value ByteString))))) |
Block | |
|
Instances
Instances
Generic Scope Source # | |
Show Scope Source # | |
Decode Scope Source # | |
Defined in Auth.Biscuit.Proto | |
Encode Scope Source # | |
Defined in Auth.Biscuit.Proto | |
type Rep Scope Source # | |
Defined in Auth.Biscuit.Proto type Rep Scope = D1 ('MetaData "Scope" "Auth.Biscuit.Proto" "biscuit-haskell-0.3.0.0-inplace" 'False) (C1 ('MetaCons "ScType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Required 1 (Enumeration ScopeType)))) :+: C1 ('MetaCons "ScBlock" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Required 2 (Value Int64))))) |
Instances
Bounded ScopeType Source # | |
Enum ScopeType Source # | |
Defined in Auth.Biscuit.Proto succ :: ScopeType -> ScopeType # pred :: ScopeType -> ScopeType # fromEnum :: ScopeType -> Int # enumFrom :: ScopeType -> [ScopeType] # enumFromThen :: ScopeType -> ScopeType -> [ScopeType] # enumFromTo :: ScopeType -> ScopeType -> [ScopeType] # enumFromThenTo :: ScopeType -> ScopeType -> ScopeType -> [ScopeType] # | |
Show ScopeType Source # | |
FactV2 | |
|
Instances
Generic FactV2 Source # | |
Show FactV2 Source # | |
Decode FactV2 Source # | |
Defined in Auth.Biscuit.Proto | |
Encode FactV2 Source # | |
Defined in Auth.Biscuit.Proto | |
type Rep FactV2 Source # | |
Defined in Auth.Biscuit.Proto type Rep FactV2 = D1 ('MetaData "FactV2" "Auth.Biscuit.Proto" "biscuit-haskell-0.3.0.0-inplace" 'True) (C1 ('MetaCons "FactV2" 'PrefixI 'True) (S1 ('MetaSel ('Just "predicate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Required 1 (Message PredicateV2))))) |
RuleV2 | |
|
Instances
Generic RuleV2 Source # | |
Show RuleV2 Source # | |
Decode RuleV2 Source # | |
Defined in Auth.Biscuit.Proto | |
Encode RuleV2 Source # | |
Defined in Auth.Biscuit.Proto | |
type Rep RuleV2 Source # | |
Defined in Auth.Biscuit.Proto type Rep RuleV2 = D1 ('MetaData "RuleV2" "Auth.Biscuit.Proto" "biscuit-haskell-0.3.0.0-inplace" 'False) (C1 ('MetaCons "RuleV2" 'PrefixI 'True) ((S1 ('MetaSel ('Just "head") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Required 1 (Message PredicateV2))) :*: S1 ('MetaSel ('Just "body") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Repeated 2 (Message PredicateV2)))) :*: (S1 ('MetaSel ('Just "expressions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Repeated 3 (Message ExpressionV2))) :*: S1 ('MetaSel ('Just "scope") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Repeated 4 (Message Scope)))))) |
Instances
Bounded CheckKind Source # | |
Enum CheckKind Source # | |
Defined in Auth.Biscuit.Proto succ :: CheckKind -> CheckKind # pred :: CheckKind -> CheckKind # fromEnum :: CheckKind -> Int # enumFrom :: CheckKind -> [CheckKind] # enumFromThen :: CheckKind -> CheckKind -> [CheckKind] # enumFromTo :: CheckKind -> CheckKind -> [CheckKind] # enumFromThenTo :: CheckKind -> CheckKind -> CheckKind -> [CheckKind] # | |
Show CheckKind Source # | |
Instances
Generic CheckV2 Source # | |
Show CheckV2 Source # | |
Decode CheckV2 Source # | |
Defined in Auth.Biscuit.Proto | |
Encode CheckV2 Source # | |
Defined in Auth.Biscuit.Proto | |
type Rep CheckV2 Source # | |
Defined in Auth.Biscuit.Proto type Rep CheckV2 = D1 ('MetaData "CheckV2" "Auth.Biscuit.Proto" "biscuit-haskell-0.3.0.0-inplace" 'False) (C1 ('MetaCons "CheckV2" 'PrefixI 'True) (S1 ('MetaSel ('Just "queries") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Repeated 1 (Message RuleV2))) :*: S1 ('MetaSel ('Just "kind") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Optional 2 (Enumeration CheckKind))))) |
data PredicateV2 Source #
Instances
TermVariable (Required 1 (Value Int64)) | |
TermInteger (Required 2 (Value Int64)) | |
TermString (Required 3 (Value Int64)) | |
TermDate (Required 4 (Value Int64)) | |
TermBytes (Required 5 (Value ByteString)) | |
TermBool (Required 6 (Value Bool)) | |
TermTermSet (Required 7 (Message TermSet)) |
Instances
newtype ExpressionV2 Source #
Instances
Generic ExpressionV2 Source # | |
Defined in Auth.Biscuit.Proto type Rep ExpressionV2 :: Type -> Type # from :: ExpressionV2 -> Rep ExpressionV2 x # to :: Rep ExpressionV2 x -> ExpressionV2 # | |
Show ExpressionV2 Source # | |
Defined in Auth.Biscuit.Proto showsPrec :: Int -> ExpressionV2 -> ShowS # show :: ExpressionV2 -> String # showList :: [ExpressionV2] -> ShowS # | |
Decode ExpressionV2 Source # | |
Defined in Auth.Biscuit.Proto decode :: HashMap Tag [WireField] -> Get ExpressionV2 | |
Encode ExpressionV2 Source # | |
Defined in Auth.Biscuit.Proto encode :: ExpressionV2 -> Put | |
type Rep ExpressionV2 Source # | |
Defined in Auth.Biscuit.Proto type Rep ExpressionV2 = D1 ('MetaData "ExpressionV2" "Auth.Biscuit.Proto" "biscuit-haskell-0.3.0.0-inplace" 'True) (C1 ('MetaCons "ExpressionV2" 'PrefixI 'True) (S1 ('MetaSel ('Just "ops") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Repeated 1 (Message Op))))) |
OpVValue (Required 1 (Message TermV2)) | |
OpVUnary (Required 2 (Message OpUnary)) | |
OpVBinary (Required 3 (Message OpBinary)) |
Instances
Generic Op Source # | |
Show Op Source # | |
Decode Op Source # | |
Defined in Auth.Biscuit.Proto | |
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.3.0.0-inplace" 'False) (C1 ('MetaCons "OpVValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Required 1 (Message TermV2)))) :+: (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)))))) |
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
Generic OpBinary Source # | |
Show OpBinary Source # | |
Decode OpBinary Source # | |
Defined in Auth.Biscuit.Proto | |
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.3.0.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 | |
BitwiseAnd | |
BitwiseOr | |
BitwiseXor |
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 # |
OpTernary | |
|
Instances
Generic OpTernary Source # | |
Show OpTernary Source # | |
Decode OpTernary Source # | |
Defined in Auth.Biscuit.Proto | |
Encode OpTernary Source # | |
Defined in Auth.Biscuit.Proto | |
type Rep OpTernary Source # | |
Defined in Auth.Biscuit.Proto type Rep OpTernary = D1 ('MetaData "OpTernary" "Auth.Biscuit.Proto" "biscuit-haskell-0.3.0.0-inplace" 'True) (C1 ('MetaCons "OpTernary" 'PrefixI 'True) (S1 ('MetaSel ('Just "kind") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Required 1 (Enumeration TernaryKind))))) |
data TernaryKind Source #
Instances
Bounded TernaryKind Source # | |
Defined in Auth.Biscuit.Proto minBound :: TernaryKind # maxBound :: TernaryKind # | |
Enum TernaryKind Source # | |
Defined in Auth.Biscuit.Proto succ :: TernaryKind -> TernaryKind # pred :: TernaryKind -> TernaryKind # toEnum :: Int -> TernaryKind # fromEnum :: TernaryKind -> Int # enumFrom :: TernaryKind -> [TernaryKind] # enumFromThen :: TernaryKind -> TernaryKind -> [TernaryKind] # enumFromTo :: TernaryKind -> TernaryKind -> [TernaryKind] # enumFromThenTo :: TernaryKind -> TernaryKind -> TernaryKind -> [TernaryKind] # | |
Show TernaryKind Source # | |
Defined in Auth.Biscuit.Proto showsPrec :: Int -> TernaryKind -> ShowS # show :: TernaryKind -> String # showList :: [TernaryKind] -> ShowS # |
data ThirdPartyBlockContents Source #
ThirdPartyBlockContents | |
|
Instances
data ThirdPartyBlockRequest Source #
ThirdPartyBlockRequest | |
|
Instances
decodeBlock :: ByteString -> Either String Block Source #
encodeBlockList :: Biscuit -> ByteString Source #
encodeBlock :: Block -> ByteString Source #