orion-hs-0.1.3

Safe HaskellNone
LanguageHaskell2010

Orion.Types

Contents

Synopsis

Orion monad

data OrionError Source #

Constructors

HTTPError HttpException

Keycloak returned an HTTP error.

ParseError Text

Failed when parsing the response

EmptyError

Empty error to serve as a zero element for Monoid.

Orion config

data OrionConfig Source #

Constructors

OrionConfig 
Instances
Eq OrionConfig Source # 
Instance details

Defined in Orion.Types

Show OrionConfig Source # 
Instance details

Defined in Orion.Types

runOrion :: Orion a -> OrionConfig -> IO (Either OrionError a) Source #

Run an Orion monad within IO.

Entities

newtype EntityId Source #

Constructors

EntityId 

Fields

Instances
Eq EntityId Source # 
Instance details

Defined in Orion.Types

Show EntityId Source # 
Instance details

Defined in Orion.Types

Generic EntityId Source # 
Instance details

Defined in Orion.Types

Associated Types

type Rep EntityId :: Type -> Type #

Methods

from :: EntityId -> Rep EntityId x #

to :: Rep EntityId x -> EntityId #

ToJSON EntityId Source # 
Instance details

Defined in Orion.Types

FromJSON EntityId Source # 
Instance details

Defined in Orion.Types

type Rep EntityId Source # 
Instance details

Defined in Orion.Types

type Rep EntityId = D1 (MetaData "EntityId" "Orion.Types" "orion-hs-0.1.3-22eqz65bH53ZTEYnAh5lP" True) (C1 (MetaCons "EntityId" PrefixI True) (S1 (MetaSel (Just "unEntityId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data Entity Source #

Instances
Show Entity Source # 
Instance details

Defined in Orion.Types

Generic Entity Source # 
Instance details

Defined in Orion.Types

Associated Types

type Rep Entity :: Type -> Type #

Methods

from :: Entity -> Rep Entity x #

to :: Rep Entity x -> Entity #

ToJSON Entity Source # 
Instance details

Defined in Orion.Types

FromJSON Entity Source # 
Instance details

Defined in Orion.Types

type Rep Entity Source # 
Instance details

Defined in Orion.Types

Attributes

newtype AttributeId Source #

Constructors

AttributeId 

Fields

Instances
Eq AttributeId Source # 
Instance details

Defined in Orion.Types

Ord AttributeId Source # 
Instance details

Defined in Orion.Types

Show AttributeId Source # 
Instance details

Defined in Orion.Types

IsString AttributeId Source # 
Instance details

Defined in Orion.Types

Generic AttributeId Source # 
Instance details

Defined in Orion.Types

Associated Types

type Rep AttributeId :: Type -> Type #

ToJSON AttributeId Source # 
Instance details

Defined in Orion.Types

ToJSONKey AttributeId Source # 
Instance details

Defined in Orion.Types

FromJSON AttributeId Source # 
Instance details

Defined in Orion.Types

FromJSONKey AttributeId Source # 
Instance details

Defined in Orion.Types

type Rep AttributeId Source # 
Instance details

Defined in Orion.Types

type Rep AttributeId = D1 (MetaData "AttributeId" "Orion.Types" "orion-hs-0.1.3-22eqz65bH53ZTEYnAh5lP" True) (C1 (MetaCons "AttributeId" PrefixI True) (S1 (MetaSel (Just "unAttributeId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data Attribute Source #

Instances
Show Attribute Source # 
Instance details

Defined in Orion.Types

Generic Attribute Source # 
Instance details

Defined in Orion.Types

Associated Types

type Rep Attribute :: Type -> Type #

ToJSON Attribute Source # 
Instance details

Defined in Orion.Types

FromJSON Attribute Source # 
Instance details

Defined in Orion.Types

type Rep Attribute Source # 
Instance details

Defined in Orion.Types

Metadata

newtype MetadataId Source #

Constructors

MetadataId 

Fields

Instances
Eq MetadataId Source # 
Instance details

Defined in Orion.Types

Ord MetadataId Source # 
Instance details

Defined in Orion.Types

Show MetadataId Source # 
Instance details

Defined in Orion.Types

IsString MetadataId Source # 
Instance details

Defined in Orion.Types

Generic MetadataId Source # 
Instance details

Defined in Orion.Types

Associated Types

type Rep MetadataId :: Type -> Type #

ToJSON MetadataId Source # 
Instance details

Defined in Orion.Types

ToJSONKey MetadataId Source # 
Instance details

Defined in Orion.Types

FromJSON MetadataId Source # 
Instance details

Defined in Orion.Types

FromJSONKey MetadataId Source # 
Instance details

Defined in Orion.Types

type Rep MetadataId Source # 
Instance details

Defined in Orion.Types

type Rep MetadataId = D1 (MetaData "MetadataId" "Orion.Types" "orion-hs-0.1.3-22eqz65bH53ZTEYnAh5lP" True) (C1 (MetaCons "MetadataId" PrefixI True) (S1 (MetaSel (Just "unMeetadataId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data Metadata Source #

Constructors

Metadata 
Instances
Show Metadata Source # 
Instance details

Defined in Orion.Types

Generic Metadata Source # 
Instance details

Defined in Orion.Types

Associated Types

type Rep Metadata :: Type -> Type #

Methods

from :: Metadata -> Rep Metadata x #

to :: Rep Metadata x -> Metadata #

ToJSON Metadata Source # 
Instance details

Defined in Orion.Types

FromJSON Metadata Source # 
Instance details

Defined in Orion.Types

type Rep Metadata Source # 
Instance details

Defined in Orion.Types

type Rep Metadata = D1 (MetaData "Metadata" "Orion.Types" "orion-hs-0.1.3-22eqz65bH53ZTEYnAh5lP" False) (C1 (MetaCons "Metadata" PrefixI True) (S1 (MetaSel (Just "metType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe MetadataType)) :*: S1 (MetaSel (Just "metValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Value))))

Subscriptions

data SubStatus Source #

Instances
Eq SubStatus Source # 
Instance details

Defined in Orion.Types

Show SubStatus Source # 
Instance details

Defined in Orion.Types

Generic SubStatus Source # 
Instance details

Defined in Orion.Types

Associated Types

type Rep SubStatus :: Type -> Type #

ToJSON SubStatus Source # 
Instance details

Defined in Orion.Types

FromJSON SubStatus Source # 
Instance details

Defined in Orion.Types

type Rep SubStatus Source # 
Instance details

Defined in Orion.Types

type Rep SubStatus = D1 (MetaData "SubStatus" "Orion.Types" "orion-hs-0.1.3-22eqz65bH53ZTEYnAh5lP" False) ((C1 (MetaCons "SubActive" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SubInactive" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "SubFailed" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SubExpired" PrefixI False) (U1 :: Type -> Type)))

newtype SubId Source #

Constructors

SubId 

Fields

Instances
Eq SubId Source # 
Instance details

Defined in Orion.Types

Methods

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

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

Show SubId Source # 
Instance details

Defined in Orion.Types

Methods

showsPrec :: Int -> SubId -> ShowS #

show :: SubId -> String #

showList :: [SubId] -> ShowS #

Generic SubId Source # 
Instance details

Defined in Orion.Types

Associated Types

type Rep SubId :: Type -> Type #

Methods

from :: SubId -> Rep SubId x #

to :: Rep SubId x -> SubId #

ToJSON SubId Source # 
Instance details

Defined in Orion.Types

FromJSON SubId Source # 
Instance details

Defined in Orion.Types

type Rep SubId Source # 
Instance details

Defined in Orion.Types

type Rep SubId = D1 (MetaData "SubId" "Orion.Types" "orion-hs-0.1.3-22eqz65bH53ZTEYnAh5lP" True) (C1 (MetaCons "SubId" PrefixI True) (S1 (MetaSel (Just "unSubId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data Subscription Source #

one subscription

Constructors

Subscription 

Fields

Instances
Eq Subscription Source # 
Instance details

Defined in Orion.Types

Show Subscription Source # 
Instance details

Defined in Orion.Types

Generic Subscription Source # 
Instance details

Defined in Orion.Types

Associated Types

type Rep Subscription :: Type -> Type #

ToJSON Subscription Source # 
Instance details

Defined in Orion.Types

FromJSON Subscription Source # 
Instance details

Defined in Orion.Types

type Rep Subscription Source # 
Instance details

Defined in Orion.Types

data SubSubject Source #

Instances
Eq SubSubject Source # 
Instance details

Defined in Orion.Types

Show SubSubject Source # 
Instance details

Defined in Orion.Types

Generic SubSubject Source # 
Instance details

Defined in Orion.Types

Associated Types

type Rep SubSubject :: Type -> Type #

ToJSON SubSubject Source # 
Instance details

Defined in Orion.Types

FromJSON SubSubject Source # 
Instance details

Defined in Orion.Types

type Rep SubSubject Source # 
Instance details

Defined in Orion.Types

type Rep SubSubject = D1 (MetaData "SubSubject" "Orion.Types" "orion-hs-0.1.3-22eqz65bH53ZTEYnAh5lP" False) (C1 (MetaCons "SubSubject" PrefixI True) (S1 (MetaSel (Just "subEntities") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [SubEntity]) :*: S1 (MetaSel (Just "subCondition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SubCondition)))

data SubEntity Source #

Constructors

SubEntity 
Instances
Eq SubEntity Source # 
Instance details

Defined in Orion.Types

Show SubEntity Source # 
Instance details

Defined in Orion.Types

Generic SubEntity Source # 
Instance details

Defined in Orion.Types

Associated Types

type Rep SubEntity :: Type -> Type #

ToJSON SubEntity Source # 
Instance details

Defined in Orion.Types

FromJSON SubEntity Source # 
Instance details

Defined in Orion.Types

type Rep SubEntity Source # 
Instance details

Defined in Orion.Types

type Rep SubEntity = D1 (MetaData "SubEntity" "Orion.Types" "orion-hs-0.1.3-22eqz65bH53ZTEYnAh5lP" False) (C1 (MetaCons "SubEntity" PrefixI True) (S1 (MetaSel (Just "subEntId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EntityId) :*: S1 (MetaSel (Just "subEntType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))

data SubNotif Source #

Instances
Eq SubNotif Source # 
Instance details

Defined in Orion.Types

Show SubNotif Source # 
Instance details

Defined in Orion.Types

Generic SubNotif Source # 
Instance details

Defined in Orion.Types

Associated Types

type Rep SubNotif :: Type -> Type #

Methods

from :: SubNotif -> Rep SubNotif x #

to :: Rep SubNotif x -> SubNotif #

ToJSON SubNotif Source # 
Instance details

Defined in Orion.Types

FromJSON SubNotif Source # 
Instance details

Defined in Orion.Types

type Rep SubNotif Source # 
Instance details

Defined in Orion.Types

data SubCondition Source #

Instances
Eq SubCondition Source # 
Instance details

Defined in Orion.Types

Show SubCondition Source # 
Instance details

Defined in Orion.Types

Generic SubCondition Source # 
Instance details

Defined in Orion.Types

Associated Types

type Rep SubCondition :: Type -> Type #

ToJSON SubCondition Source # 
Instance details

Defined in Orion.Types

FromJSON SubCondition Source # 
Instance details

Defined in Orion.Types

type Rep SubCondition Source # 
Instance details

Defined in Orion.Types

type Rep SubCondition = D1 (MetaData "SubCondition" "Orion.Types" "orion-hs-0.1.3-22eqz65bH53ZTEYnAh5lP" False) (C1 (MetaCons "SubCondition" PrefixI True) (S1 (MetaSel (Just "subCondAttrs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [AttributeId]) :*: S1 (MetaSel (Just "subCondExpression") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map Text Text))))

data SubHttpCustom Source #

Instances
Eq SubHttpCustom Source # 
Instance details

Defined in Orion.Types

Show SubHttpCustom Source # 
Instance details

Defined in Orion.Types

Generic SubHttpCustom Source # 
Instance details

Defined in Orion.Types

Associated Types

type Rep SubHttpCustom :: Type -> Type #

ToJSON SubHttpCustom Source # 
Instance details

Defined in Orion.Types

FromJSON SubHttpCustom Source # 
Instance details

Defined in Orion.Types

type Rep SubHttpCustom Source # 
Instance details

Defined in Orion.Types

type Path = Text Source #