planb-token-introspection-0.1.4.0: Token Introspection for PlanB

Safe HaskellNone
LanguageHaskell2010

Network.PlanB.Introspection

Synopsis

Documentation

data TokenInfo Source #

Information returned on a successful token introspection.

Instances
Show TokenInfo Source # 
Instance details

Defined in Network.PlanB.Introspection.Internal.Types

Generic TokenInfo Source # 
Instance details

Defined in Network.PlanB.Introspection.Internal.Types

Associated Types

type Rep TokenInfo :: Type -> Type #

ToJSON TokenInfo Source # 
Instance details

Defined in Network.PlanB.Introspection.Internal.Types

FromJSON TokenInfo Source # 
Instance details

Defined in Network.PlanB.Introspection.Internal.Types

type Rep TokenInfo Source # 
Instance details

Defined in Network.PlanB.Introspection.Internal.Types

type Rep TokenInfo = D1 (MetaData "TokenInfo" "Network.PlanB.Introspection.Internal.Types" "planb-token-introspection-0.1.4.0-BcrjmGCfBxW3UAbM4QCMBf" False) (C1 (MetaCons "TokenInfo" PrefixI True) ((S1 (MetaSel (Just "tokenInfoExpiresIn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "tokenInfoScope") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Set Text))) :*: (S1 (MetaSel (Just "tokenInfoUid") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "tokenInfoRealm") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))))

data IntrospectionError Source #

This type models the error scenarios specific to a token introspection attempt. These can be used as exceptions and are in fact thrown by a PlanB token introspector.

Instances
Eq IntrospectionError Source # 
Instance details

Defined in Network.PlanB.Introspection.Internal.Types

Show IntrospectionError Source # 
Instance details

Defined in Network.PlanB.Introspection.Internal.Types

Generic IntrospectionError Source # 
Instance details

Defined in Network.PlanB.Introspection.Internal.Types

Associated Types

type Rep IntrospectionError :: Type -> Type #

Exception IntrospectionError Source # 
Instance details

Defined in Network.PlanB.Introspection.Internal.Types

type Rep IntrospectionError Source # 
Instance details

Defined in Network.PlanB.Introspection.Internal.Types

data ErrorResponse Source #

Contains the error response data returned from a PlanB server in case of an introspection error.

Instances
Eq ErrorResponse Source # 
Instance details

Defined in Network.PlanB.Introspection.Internal.Types

Show ErrorResponse Source # 
Instance details

Defined in Network.PlanB.Introspection.Internal.Types

Generic ErrorResponse Source # 
Instance details

Defined in Network.PlanB.Introspection.Internal.Types

Associated Types

type Rep ErrorResponse :: Type -> Type #

ToJSON ErrorResponse Source # 
Instance details

Defined in Network.PlanB.Introspection.Internal.Types

FromJSON ErrorResponse Source # 
Instance details

Defined in Network.PlanB.Introspection.Internal.Types

type Rep ErrorResponse Source # 
Instance details

Defined in Network.PlanB.Introspection.Internal.Types

type Rep ErrorResponse = D1 (MetaData "ErrorResponse" "Network.PlanB.Introspection.Internal.Types" "planb-token-introspection-0.1.4.0-BcrjmGCfBxW3UAbM4QCMBf" False) (C1 (MetaCons "ErrorResponse" PrefixI True) (S1 (MetaSel (Just "errorResponseError") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "errorResponseErrorDescription") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))

data TokenIntrospector m Source #

A TokenIntrospector can be used for introspecting tokens.

Constructors

TokenIntrospector 

Fields

new :: (MonadThrow m, MonadIO m) => Text -> m (TokenIntrospector m) Source #

Create a new PlanB token introspector using the provided endpoint. Uses a global default HTTP manager.

newWithManager :: (MonadThrow m, MonadIO m) => Manager -> Text -> m (TokenIntrospector m) Source #

Create a new PlanB toke introspector using the provided endpoint and HTTP manager.

newFromEnv :: (MonadThrow m, MonadIO m) => Maybe Manager -> m (TokenIntrospector m) Source #

Convenience function. Create a new PlanB introspector using the provided manager. The PlanB server to use is retrieved from the environment variable PLANB_INTROSPECTION_ENDPOINT.