happstack-authenticate-2.3.4.6: Happstack Authentication Library

Safe HaskellNone
LanguageHaskell98

Happstack.Authenticate.OpenId.Core

Contents

Synopsis

Documentation

data OpenIdError Source #

Instances

Eq OpenIdError Source # 
Data OpenIdError Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OpenIdError -> c OpenIdError #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OpenIdError #

toConstr :: OpenIdError -> Constr #

dataTypeOf :: OpenIdError -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c OpenIdError) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OpenIdError) #

gmapT :: (forall b. Data b => b -> b) -> OpenIdError -> OpenIdError #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OpenIdError -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OpenIdError -> r #

gmapQ :: (forall d. Data d => d -> u) -> OpenIdError -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OpenIdError -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OpenIdError -> m OpenIdError #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OpenIdError -> m OpenIdError #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OpenIdError -> m OpenIdError #

Ord OpenIdError Source # 
Read OpenIdError Source # 
Show OpenIdError Source # 
Generic OpenIdError Source # 

Associated Types

type Rep OpenIdError :: * -> * #

FromJSON OpenIdError Source # 
ToJSON OpenIdError Source # 
ToJExpr OpenIdError Source # 
RenderMessage HappstackAuthenticateI18N OpenIdError Source # 
type Rep OpenIdError Source # 
type Rep OpenIdError = D1 (MetaData "OpenIdError" "Happstack.Authenticate.OpenId.Core" "happstack-authenticate-2.3.4.6-5pBasiUguPUCo67L8Lv56j" False) ((:+:) (C1 (MetaCons "UnknownIdentifier" PrefixI False) U1) (C1 (MetaCons "CoreError" PrefixI True) (S1 (MetaSel (Just Symbol "openIdErrorMessageE") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CoreError))))

data OpenIdState_1 Source #

Instances

Eq OpenIdState_1 Source # 
Data OpenIdState_1 Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OpenIdState_1 -> c OpenIdState_1 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OpenIdState_1 #

toConstr :: OpenIdState_1 -> Constr #

dataTypeOf :: OpenIdState_1 -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c OpenIdState_1) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OpenIdState_1) #

gmapT :: (forall b. Data b => b -> b) -> OpenIdState_1 -> OpenIdState_1 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OpenIdState_1 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OpenIdState_1 -> r #

gmapQ :: (forall d. Data d => d -> u) -> OpenIdState_1 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OpenIdState_1 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OpenIdState_1 -> m OpenIdState_1 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OpenIdState_1 -> m OpenIdState_1 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OpenIdState_1 -> m OpenIdState_1 #

Ord OpenIdState_1 Source # 
Read OpenIdState_1 Source # 
Show OpenIdState_1 Source # 
Generic OpenIdState_1 Source # 

Associated Types

type Rep OpenIdState_1 :: * -> * #

SafeCopy OpenIdState_1 Source # 
type Rep OpenIdState_1 Source # 
type Rep OpenIdState_1 = D1 (MetaData "OpenIdState_1" "Happstack.Authenticate.OpenId.Core" "happstack-authenticate-2.3.4.6-5pBasiUguPUCo67L8Lv56j" False) (C1 (MetaCons "OpenIdState_1" PrefixI True) (S1 (MetaSel (Just Symbol "_identifiers_1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map Identifier UserId))))

data OpenIdState Source #

Instances

Eq OpenIdState Source # 
Data OpenIdState Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OpenIdState -> c OpenIdState #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OpenIdState #

toConstr :: OpenIdState -> Constr #

dataTypeOf :: OpenIdState -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c OpenIdState) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OpenIdState) #

gmapT :: (forall b. Data b => b -> b) -> OpenIdState -> OpenIdState #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OpenIdState -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OpenIdState -> r #

gmapQ :: (forall d. Data d => d -> u) -> OpenIdState -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OpenIdState -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OpenIdState -> m OpenIdState #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OpenIdState -> m OpenIdState #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OpenIdState -> m OpenIdState #

Ord OpenIdState Source # 
Read OpenIdState Source # 
Show OpenIdState Source # 
Generic OpenIdState Source # 

Associated Types

type Rep OpenIdState :: * -> * #

IsAcidic OpenIdState Source # 
Migrate OpenIdState Source # 

Associated Types

type MigrateFrom OpenIdState :: * #

SafeCopy OpenIdState Source # 
type Rep OpenIdState Source # 
type Rep OpenIdState = D1 (MetaData "OpenIdState" "Happstack.Authenticate.OpenId.Core" "happstack-authenticate-2.3.4.6-5pBasiUguPUCo67L8Lv56j" False) (C1 (MetaCons "OpenIdState" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_identifiers") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map Identifier UserId))) (S1 (MetaSel (Just Symbol "_openIdRealm") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text)))))
type MigrateFrom OpenIdState Source # 

getOpenIdRealm :: Query OpenIdState (Maybe Text) Source #

Get the OpenId realm to use for authentication

setOpenIdRealm :: Maybe Text -> Update OpenIdState () Source #

set the realm used for OpenId Authentication

IMPORTANT: Changing this value after users have registered is likely to invalidate existing OpenId tokens resulting in users no longer being able to access their old accounts.

data SetRealmData Source #

Constructors

SetRealmData 

Instances

Eq SetRealmData Source # 
Data SetRealmData Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SetRealmData -> c SetRealmData #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SetRealmData #

toConstr :: SetRealmData -> Constr #

dataTypeOf :: SetRealmData -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SetRealmData) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SetRealmData) #

gmapT :: (forall b. Data b => b -> b) -> SetRealmData -> SetRealmData #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SetRealmData -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SetRealmData -> r #

gmapQ :: (forall d. Data d => d -> u) -> SetRealmData -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SetRealmData -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SetRealmData -> m SetRealmData #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SetRealmData -> m SetRealmData #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SetRealmData -> m SetRealmData #

Ord SetRealmData Source # 
Read SetRealmData Source # 
Show SetRealmData Source # 
Generic SetRealmData Source # 

Associated Types

type Rep SetRealmData :: * -> * #

FromJSON SetRealmData Source # 
ToJSON SetRealmData Source # 
type Rep SetRealmData Source # 
type Rep SetRealmData = D1 (MetaData "SetRealmData" "Happstack.Authenticate.OpenId.Core" "happstack-authenticate-2.3.4.6-5pBasiUguPUCo67L8Lv56j" False) (C1 (MetaCons "SetRealmData" PrefixI True) (S1 (MetaSel (Just Symbol "_srOpenIdRealm") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))

Orphan instances