| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Keycloak.Types
Synopsis
- type Keycloak a = ReaderT KCConfig (ExceptT KCError IO) a
- data KCError
- data KCConfig = KCConfig {}
- defaultKCConfig :: KCConfig
- runKeycloak :: Keycloak a -> KCConfig -> IO (Either KCError a)
- type Path = Text
- newtype Token = Token {}
- extractBearerAuth :: ByteString -> Maybe ByteString
- tokNonce :: Text
- tokAuthTime :: Text
- tokSessionState :: Text
- tokAtHash :: Text
- tokCHash :: Text
- tokName :: Text
- tokGivenName :: Text
- tokFamilyName :: Text
- tokMiddleName :: Text
- tokNickName :: Text
- tokPreferredUsername :: Text
- tokProfile :: Text
- tokPicture :: Text
- tokWebsite :: Text
- tokEmail :: Text
- tokEmailVerified :: Text
- tokGender :: Text
- tokBirthdate :: Text
- tokZoneinfo :: Text
- tokLocale :: Text
- tokPhoneNumber :: Text
- tokPhoneNumberVerified :: Text
- tokAddress :: Text
- tokUpdateAt :: Text
- tokClaimsLocales :: Text
- tokACR :: Text
- data TokenRep = TokenRep {
- accessToken :: Text
- expiresIn :: Int
- refreshExpriresIn :: Int
- refreshToken :: Text
- tokenType :: Text
- notBeforePolicy :: Int
- sessionState :: Text
- tokenScope :: Text
- newtype ScopeName = ScopeName {
- unScopeName :: Text
- newtype ScopeId = ScopeId {}
- data Scope = Scope {}
- data Permission = Permission {}
- data PermReq = PermReq {}
- type Username = Text
- type Password = Text
- type First = Int
- type Max = Int
- newtype UserId = UserId {}
- data User = User {
- userId :: Maybe UserId
- userUsername :: Username
- userFirstName :: Maybe Text
- userLastName :: Maybe Text
- userEmail :: Maybe Text
- userAttributes :: Maybe (Map Text [Text])
- unCapitalize :: String -> String
- data Owner = Owner {}
- type ResourceName = Text
- type ResourceType = Text
- newtype ResourceId = ResourceId {}
- data Resource = Resource {
- resId :: Maybe ResourceId
- resName :: ResourceName
- resType :: Maybe ResourceType
- resUris :: [Text]
- resScopes :: [Scope]
- resOwner :: Owner
- resOwnerManagedAccess :: Bool
- resAttributes :: [Attribute]
- data Attribute = Attribute {}
- realm :: Lens' KCConfig Text
- clientSecret :: Lens' KCConfig Text
- clientId :: Lens' KCConfig Text
- baseUrl :: Lens' KCConfig Text
Keycloak Monad
type Keycloak a = ReaderT KCConfig (ExceptT KCError IO) a Source #
Keycloak Monad stack: a simple Reader monad containing the config, and an ExceptT to handle HTTPErrors and parse errors.
Contains HTTP errors and parse errors.
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. |
Configuration of Keycloak.
defaultKCConfig :: KCConfig Source #
Default configuration
runKeycloak :: Keycloak a -> KCConfig -> IO (Either KCError a) Source #
Run a Keycloak monad within IO.
Token
Wrapper for tokens.
Constructors
| Token | |
Fields | |
Instances
| Eq Token Source # | |
| Show Token Source # | |
| Generic Token Source # | |
| ToJSON Token Source # | |
Defined in Keycloak.Types | |
| ToHttpApiData Token Source # | Create Authorization header |
Defined in Keycloak.Types Methods toUrlPiece :: Token -> Text # toEncodedUrlPiece :: Token -> Builder # toHeader :: Token -> ByteString # toQueryParam :: Token -> Text # | |
| FromHttpApiData Token Source # | parser for Authorization header |
Defined in Keycloak.Types | |
| type Rep Token Source # | |
Defined in Keycloak.Types type Rep Token = D1 (MetaData "Token" "Keycloak.Types" "keycloak-hs-1.0.1-Dv1gYbAOFZ7EsyySRU9vHf" True) (C1 (MetaCons "Token" PrefixI True) (S1 (MetaSel (Just "unToken") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString))) | |
tokAuthTime :: Text Source #
Keycloak Token additional claims
tokSessionState :: Text Source #
Keycloak Token additional claims
tokGivenName :: Text Source #
Keycloak Token additional claims
tokFamilyName :: Text Source #
Keycloak Token additional claims
tokMiddleName :: Text Source #
Keycloak Token additional claims
tokNickName :: Text Source #
Keycloak Token additional claims
tokPreferredUsername :: Text Source #
Keycloak Token additional claims
tokProfile :: Text Source #
Keycloak Token additional claims
tokPicture :: Text Source #
Keycloak Token additional claims
tokWebsite :: Text Source #
Keycloak Token additional claims
tokEmailVerified :: Text Source #
Keycloak Token additional claims
tokBirthdate :: Text Source #
Keycloak Token additional claims
tokZoneinfo :: Text Source #
Keycloak Token additional claims
tokPhoneNumber :: Text Source #
Keycloak Token additional claims
tokPhoneNumberVerified :: Text Source #
Keycloak Token additional claims
tokAddress :: Text Source #
Keycloak Token additional claims
tokUpdateAt :: Text Source #
Keycloak Token additional claims
tokClaimsLocales :: Text Source #
Keycloak Token additional claims
Token reply from Keycloak
Constructors
| TokenRep | |
Fields
| |
Permissions
Scope name
Constructors
| ScopeName | |
Fields
| |
Instances
| Eq ScopeName Source # | |
| Ord ScopeName Source # | |
| Show ScopeName Source # | |
| Generic ScopeName Source # | |
| ToJSON ScopeName Source # | |
Defined in Keycloak.Types | |
| FromJSON ScopeName Source # | |
| type Rep ScopeName Source # | |
Defined in Keycloak.Types | |
Scope Id
Keycloak scope
Instances
| Eq Scope Source # | |
| Show Scope Source # | |
| Generic Scope Source # | |
| ToJSON Scope Source # | |
Defined in Keycloak.Types | |
| FromJSON Scope Source # | |
| type Rep Scope Source # | |
Defined in Keycloak.Types type Rep Scope = D1 (MetaData "Scope" "Keycloak.Types" "keycloak-hs-1.0.1-Dv1gYbAOFZ7EsyySRU9vHf" False) (C1 (MetaCons "Scope" PrefixI True) (S1 (MetaSel (Just "scopeId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ScopeId)) :*: S1 (MetaSel (Just "scopeName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ScopeName))) | |
data Permission Source #
Keycloak permission on a resource
Constructors
| Permission | |
Fields
| |
Instances
permission request
Constructors
| PermReq | |
Fields | |
Instances
| Eq PermReq Source # | |
| Ord PermReq Source # | |
| Show PermReq Source # | |
| Generic PermReq Source # | |
| type Rep PermReq Source # | |
Defined in Keycloak.Types type Rep PermReq = D1 (MetaData "PermReq" "Keycloak.Types" "keycloak-hs-1.0.1-Dv1gYbAOFZ7EsyySRU9vHf" False) (C1 (MetaCons "PermReq" PrefixI True) (S1 (MetaSel (Just "permReqResourceId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ResourceId)) :*: S1 (MetaSel (Just "permReqScopes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ScopeName]))) | |
User
Id of a user
User
Constructors
| User | |
Fields
| |
Instances
| Eq User Source # | |
| Show User Source # | |
| Generic User Source # | |
| ToJSON User Source # | |
Defined in Keycloak.Types | |
| FromJSON User Source # | |
| type Rep User Source # | |
Defined in Keycloak.Types type Rep User = D1 (MetaData "User" "Keycloak.Types" "keycloak-hs-1.0.1-Dv1gYbAOFZ7EsyySRU9vHf" False) (C1 (MetaCons "User" PrefixI True) ((S1 (MetaSel (Just "userId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe UserId)) :*: (S1 (MetaSel (Just "userUsername") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Username) :*: S1 (MetaSel (Just "userFirstName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text)))) :*: (S1 (MetaSel (Just "userLastName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "userEmail") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "userAttributes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Map Text [Text]))))))) | |
unCapitalize :: String -> String Source #
Owner
A resource owner
Instances
| Show Owner Source # | |
| Generic Owner Source # | |
| ToJSON Owner Source # | |
Defined in Keycloak.Types | |
| FromJSON Owner Source # | |
| type Rep Owner Source # | |
Defined in Keycloak.Types type Rep Owner = D1 (MetaData "Owner" "Keycloak.Types" "keycloak-hs-1.0.1-Dv1gYbAOFZ7EsyySRU9vHf" False) (C1 (MetaCons "Owner" PrefixI True) (S1 (MetaSel (Just "ownId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "ownName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Username)))) | |
Resource
type ResourceName = Text Source #
type ResourceType = Text Source #
newtype ResourceId Source #
A resource Id
Constructors
| ResourceId | |
Instances
A complete resource
Constructors
| Resource | |
Fields
| |
Instances
A resource attribute
Instances
| Show Attribute Source # | |
| Generic Attribute Source # | |
| ToJSON Attribute Source # | |
Defined in Keycloak.Types | |
| FromJSON Attribute Source # | |
| type Rep Attribute Source # | |
Defined in Keycloak.Types type Rep Attribute = D1 (MetaData "Attribute" "Keycloak.Types" "keycloak-hs-1.0.1-Dv1gYbAOFZ7EsyySRU9vHf" False) (C1 (MetaCons "Attribute" PrefixI True) (S1 (MetaSel (Just "attName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "attValues") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Text]))) | |