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

Auth.Biscuit.Proto

Description

Haskell data structures mapping the biscuit protobuf definitions

Synopsis

Documentation

data Biscuit Source #

Instances

Instances details
Show Biscuit Source # 
Instance details

Defined in Auth.Biscuit.Proto

Generic Biscuit Source # 
Instance details

Defined in Auth.Biscuit.Proto

Associated Types

type Rep Biscuit :: Type -> Type #

Methods

from :: Biscuit -> Rep Biscuit x #

to :: Rep Biscuit x -> Biscuit #

Decode Biscuit Source # 
Instance details

Defined in Auth.Biscuit.Proto

Encode Biscuit Source # 
Instance details

Defined in Auth.Biscuit.Proto

Methods

encode :: Biscuit -> Put #

type Rep Biscuit Source # 
Instance details

Defined in Auth.Biscuit.Proto

data Signature Source #

Constructors

Signature 

Instances

Instances details
Show Signature Source # 
Instance details

Defined in Auth.Biscuit.Proto

Generic Signature Source # 
Instance details

Defined in Auth.Biscuit.Proto

Associated Types

type Rep Signature :: Type -> Type #

Decode Signature Source # 
Instance details

Defined in Auth.Biscuit.Proto

Encode Signature Source # 
Instance details

Defined in Auth.Biscuit.Proto

Methods

encode :: Signature -> Put #

type Rep Signature Source # 
Instance details

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)))))

data Block Source #

Instances

Instances details
Show Block Source # 
Instance details

Defined in Auth.Biscuit.Proto

Methods

showsPrec :: Int -> Block -> ShowS #

show :: Block -> String #

showList :: [Block] -> ShowS #

Generic Block Source # 
Instance details

Defined in Auth.Biscuit.Proto

Associated Types

type Rep Block :: Type -> Type #

Methods

from :: Block -> Rep Block x #

to :: Rep Block x -> Block #

Decode Block Source # 
Instance details

Defined in Auth.Biscuit.Proto

Encode Block Source # 
Instance details

Defined in Auth.Biscuit.Proto

Methods

encode :: Block -> Put #

type Rep Block Source # 
Instance details

Defined in Auth.Biscuit.Proto

newtype FactV1 Source #

Constructors

FactV1 

Instances

Instances details
Show FactV1 Source # 
Instance details

Defined in Auth.Biscuit.Proto

Generic FactV1 Source # 
Instance details

Defined in Auth.Biscuit.Proto

Associated Types

type Rep FactV1 :: Type -> Type #

Methods

from :: FactV1 -> Rep FactV1 x #

to :: Rep FactV1 x -> FactV1 #

Decode FactV1 Source # 
Instance details

Defined in Auth.Biscuit.Proto

Encode FactV1 Source # 
Instance details

Defined in Auth.Biscuit.Proto

Methods

encode :: FactV1 -> Put #

type Rep FactV1 Source # 
Instance details

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)))))

data RuleV1 Source #

Instances

Instances details
Show RuleV1 Source # 
Instance details

Defined in Auth.Biscuit.Proto

Generic RuleV1 Source # 
Instance details

Defined in Auth.Biscuit.Proto

Associated Types

type Rep RuleV1 :: Type -> Type #

Methods

from :: RuleV1 -> Rep RuleV1 x #

to :: Rep RuleV1 x -> RuleV1 #

Decode RuleV1 Source # 
Instance details

Defined in Auth.Biscuit.Proto

Encode RuleV1 Source # 
Instance details

Defined in Auth.Biscuit.Proto

Methods

encode :: RuleV1 -> Put #

type Rep RuleV1 Source # 
Instance details

Defined in Auth.Biscuit.Proto

newtype CheckV1 Source #

Constructors

CheckV1 

Instances

Instances details
Show CheckV1 Source # 
Instance details

Defined in Auth.Biscuit.Proto

Generic CheckV1 Source # 
Instance details

Defined in Auth.Biscuit.Proto

Associated Types

type Rep CheckV1 :: Type -> Type #

Methods

from :: CheckV1 -> Rep CheckV1 x #

to :: Rep CheckV1 x -> CheckV1 #

Decode CheckV1 Source # 
Instance details

Defined in Auth.Biscuit.Proto

Encode CheckV1 Source # 
Instance details

Defined in Auth.Biscuit.Proto

Methods

encode :: CheckV1 -> Put #

type Rep CheckV1 Source # 
Instance details

Defined in Auth.Biscuit.Proto

type Rep CheckV1 = D1 ('MetaData "CheckV1" "Auth.Biscuit.Proto" "biscuit-haskell-0.1.1.0-inplace" 'True) (C1 ('MetaCons "CheckV1" 'PrefixI 'True) (S1 ('MetaSel ('Just "queries") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Repeated 1 (Message RuleV1)))))

data PredicateV1 Source #

Constructors

PredicateV1 

Fields

Instances

Instances details
Show PredicateV1 Source # 
Instance details

Defined in Auth.Biscuit.Proto

Generic PredicateV1 Source # 
Instance details

Defined in Auth.Biscuit.Proto

Associated Types

type Rep PredicateV1 :: Type -> Type #

Decode PredicateV1 Source # 
Instance details

Defined in Auth.Biscuit.Proto

Encode PredicateV1 Source # 
Instance details

Defined in Auth.Biscuit.Proto

Methods

encode :: PredicateV1 -> Put #

type Rep PredicateV1 Source # 
Instance details

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)))))

data IDV1 Source #

Instances

Instances details
Show IDV1 Source # 
Instance details

Defined in Auth.Biscuit.Proto

Methods

showsPrec :: Int -> IDV1 -> ShowS #

show :: IDV1 -> String #

showList :: [IDV1] -> ShowS #

Generic IDV1 Source # 
Instance details

Defined in Auth.Biscuit.Proto

Associated Types

type Rep IDV1 :: Type -> Type #

Methods

from :: IDV1 -> Rep IDV1 x #

to :: Rep IDV1 x -> IDV1 #

Decode IDV1 Source # 
Instance details

Defined in Auth.Biscuit.Proto

Encode IDV1 Source # 
Instance details

Defined in Auth.Biscuit.Proto

Methods

encode :: IDV1 -> Put #

type Rep IDV1 Source # 
Instance details

Defined in Auth.Biscuit.Proto

type Rep IDV1 = D1 ('MetaData "IDV1" "Auth.Biscuit.Proto" "biscuit-haskell-0.1.1.0-inplace" 'False) (((C1 ('MetaCons "IDSymbol" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Required 1 (Value Int64)))) :+: C1 ('MetaCons "IDVariable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Required 2 (Value Int32))))) :+: (C1 ('MetaCons "IDInteger" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Required 3 (Value Int64)))) :+: C1 ('MetaCons "IDString" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Required 4 (Value Text)))))) :+: ((C1 ('MetaCons "IDDate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Required 5 (Value Int64)))) :+: C1 ('MetaCons "IDBytes" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Required 6 (Value ByteString))))) :+: (C1 ('MetaCons "IDBool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Required 7 (Value Bool)))) :+: C1 ('MetaCons "IDIDSet" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Required 8 (Message IDSet)))))))

newtype ExpressionV1 Source #

Constructors

ExpressionV1 

Fields

Instances

Instances details
Show ExpressionV1 Source # 
Instance details

Defined in Auth.Biscuit.Proto

Generic ExpressionV1 Source # 
Instance details

Defined in Auth.Biscuit.Proto

Associated Types

type Rep ExpressionV1 :: Type -> Type #

Decode ExpressionV1 Source # 
Instance details

Defined in Auth.Biscuit.Proto

Encode ExpressionV1 Source # 
Instance details

Defined in Auth.Biscuit.Proto

Methods

encode :: ExpressionV1 -> Put #

type Rep ExpressionV1 Source # 
Instance details

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)))))

newtype IDSet Source #

Constructors

IDSet 

Fields

Instances

Instances details
Show IDSet Source # 
Instance details

Defined in Auth.Biscuit.Proto

Methods

showsPrec :: Int -> IDSet -> ShowS #

show :: IDSet -> String #

showList :: [IDSet] -> ShowS #

Generic IDSet Source # 
Instance details

Defined in Auth.Biscuit.Proto

Associated Types

type Rep IDSet :: Type -> Type #

Methods

from :: IDSet -> Rep IDSet x #

to :: Rep IDSet x -> IDSet #

Decode IDSet Source # 
Instance details

Defined in Auth.Biscuit.Proto

Encode IDSet Source # 
Instance details

Defined in Auth.Biscuit.Proto

Methods

encode :: IDSet -> Put #

type Rep IDSet Source # 
Instance details

Defined in Auth.Biscuit.Proto

type Rep IDSet = D1 ('MetaData "IDSet" "Auth.Biscuit.Proto" "biscuit-haskell-0.1.1.0-inplace" 'True) (C1 ('MetaCons "IDSet" 'PrefixI 'True) (S1 ('MetaSel ('Just "set") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Repeated 1 (Message IDV1)))))

data Op Source #

Instances

Instances details
Show Op Source # 
Instance details

Defined in Auth.Biscuit.Proto

Methods

showsPrec :: Int -> Op -> ShowS #

show :: Op -> String #

showList :: [Op] -> ShowS #

Generic Op Source # 
Instance details

Defined in Auth.Biscuit.Proto

Associated Types

type Rep Op :: Type -> Type #

Methods

from :: Op -> Rep Op x #

to :: Rep Op x -> Op #

Decode Op Source # 
Instance details

Defined in Auth.Biscuit.Proto

Methods

decode :: HashMap Tag [WireField] -> Get Op #

Encode Op Source # 
Instance details

Defined in Auth.Biscuit.Proto

Methods

encode :: Op -> Put #

type Rep Op Source # 
Instance details

Defined in Auth.Biscuit.Proto

newtype OpUnary Source #

Constructors

OpUnary 

Instances

Instances details
Show OpUnary Source # 
Instance details

Defined in Auth.Biscuit.Proto

Generic OpUnary Source # 
Instance details

Defined in Auth.Biscuit.Proto

Associated Types

type Rep OpUnary :: Type -> Type #

Methods

from :: OpUnary -> Rep OpUnary x #

to :: Rep OpUnary x -> OpUnary #

Decode OpUnary Source # 
Instance details

Defined in Auth.Biscuit.Proto

Encode OpUnary Source # 
Instance details

Defined in Auth.Biscuit.Proto

Methods

encode :: OpUnary -> Put #

type Rep OpUnary Source # 
Instance details

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)))))

newtype OpBinary Source #

Constructors

OpBinary 

Instances

Instances details
Show OpBinary Source # 
Instance details

Defined in Auth.Biscuit.Proto

Generic OpBinary Source # 
Instance details

Defined in Auth.Biscuit.Proto

Associated Types

type Rep OpBinary :: Type -> Type #

Methods

from :: OpBinary -> Rep OpBinary x #

to :: Rep OpBinary x -> OpBinary #

Decode OpBinary Source # 
Instance details

Defined in Auth.Biscuit.Proto

Encode OpBinary Source # 
Instance details

Defined in Auth.Biscuit.Proto

Methods

encode :: OpBinary -> Put #

type Rep OpBinary Source # 
Instance details

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)))))

getField :: HasField a => a -> FieldType a #

Extract a value from it's Field representation.

putField :: HasField a => FieldType a -> a #

Wrap it back up again.