happstack-authenticate-2.3.4.7: Happstack Authentication Library

Safe HaskellNone
LanguageHaskell98

Happstack.Authenticate.Core

Synopsis

Documentation

data AuthenticateConfig Source #

Various configuration options that apply to all authentication methods

Constructors

AuthenticateConfig 

Fields

Instances

Generic AuthenticateConfig Source # 
type Rep AuthenticateConfig Source # 
type Rep AuthenticateConfig = D1 (MetaData "AuthenticateConfig" "Happstack.Authenticate.Core" "happstack-authenticate-2.3.4.7-8NGvEJtsguz6HpkSzT4jIO" False) (C1 (MetaCons "AuthenticateConfig" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_isAuthAdmin") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (UserId -> IO Bool))) ((:*:) (S1 (MetaSel (Just Symbol "_usernameAcceptable") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Username -> Maybe CoreError))) (S1 (MetaSel (Just Symbol "_requireEmail") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))))

newtype UserId :: * #

a UserId uniquely identifies a user.

Constructors

UserId 

Fields

Instances

Enum UserId 
Eq UserId 

Methods

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

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

Data UserId 

Methods

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

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

toConstr :: UserId -> Constr #

dataTypeOf :: UserId -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord UserId 
Read UserId 
Show UserId 
Generic UserId 

Associated Types

type Rep UserId :: * -> * #

Methods

from :: UserId -> Rep UserId x #

to :: Rep UserId x -> UserId #

ToJSON UserId 
FromJSON UserId 
SafeCopy UserId 
PathInfo UserId 
Indexable UserIxs User # 
type Rep UserId 
type Rep UserId = D1 (MetaData "UserId" "Data.UserId" "userid-0.1.2.8-1VeN8gxTEuCAGC41vJtgd7" True) (C1 (MetaCons "UserId" PrefixI True) (S1 (MetaSel (Just Symbol "_unUserId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer)))

unUserId :: Functor f => (Integer -> f Integer) -> UserId -> f UserId #

succUserId :: UserId -> UserId #

get the next UserId

jsonOptions :: Options Source #

when creating JSON field names, drop the first character. Since we are using lens, the leading character should always be _.

toJSONResponse :: (RenderMessage HappstackAuthenticateI18N e, ToJSON a) => Either e a -> Response Source #

convert a value to a JSON encoded Response

toJSONSuccess :: ToJSON a => a -> Response Source #

convert a value to a JSON encoded Response

toJSONError :: forall e. RenderMessage HappstackAuthenticateI18N e => e -> Response Source #

convert an error to a JSON encoded Response

FIXME: I18N

newtype Username Source #

an arbitrary, but unique string that the user uses to identify themselves

Constructors

Username 

Fields

Instances

Eq Username Source # 
Data Username Source # 

Methods

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

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

toConstr :: Username -> Constr #

dataTypeOf :: Username -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Username Source # 
Read Username Source # 
Show Username Source # 
Generic Username Source # 

Associated Types

type Rep Username :: * -> * #

Methods

from :: Username -> Rep Username x #

to :: Rep Username x -> Username #

ToJSON Username Source # 
FromJSON Username Source # 
SafeCopy Username Source # 
PathInfo Username Source # 
Indexable UserIxs User Source # 
type Rep Username Source # 
type Rep Username = D1 (MetaData "Username" "Happstack.Authenticate.Core" "happstack-authenticate-2.3.4.7-8NGvEJtsguz6HpkSzT4jIO" True) (C1 (MetaCons "Username" PrefixI True) (S1 (MetaSel (Just Symbol "_unUsername") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

rUsername :: forall tok e r. Boomerang e tok ((:-) Text r) ((:-) Username r) Source #

usernamePolicy :: Username -> Maybe CoreError Source #

a very basic policy for userAcceptable

Enforces:

Username can not be empty

newtype Email Source #

an Email address. No validation in performed.

Constructors

Email 

Fields

Instances

Eq Email Source # 

Methods

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

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

Data Email Source # 

Methods

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

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

toConstr :: Email -> Constr #

dataTypeOf :: Email -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Email Source # 

Methods

compare :: Email -> Email -> Ordering #

(<) :: Email -> Email -> Bool #

(<=) :: Email -> Email -> Bool #

(>) :: Email -> Email -> Bool #

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

max :: Email -> Email -> Email #

min :: Email -> Email -> Email #

Read Email Source # 
Show Email Source # 

Methods

showsPrec :: Int -> Email -> ShowS #

show :: Email -> String #

showList :: [Email] -> ShowS #

Generic Email Source # 

Associated Types

type Rep Email :: * -> * #

Methods

from :: Email -> Rep Email x #

to :: Rep Email x -> Email #

ToJSON Email Source # 
FromJSON Email Source # 
SafeCopy Email Source # 
PathInfo Email Source # 
Indexable UserIxs User Source # 
type Rep Email Source # 
type Rep Email = D1 (MetaData "Email" "Happstack.Authenticate.Core" "happstack-authenticate-2.3.4.7-8NGvEJtsguz6HpkSzT4jIO" True) (C1 (MetaCons "Email" PrefixI True) (S1 (MetaSel (Just Symbol "_unEmail") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data User Source #

A unique User

Constructors

User 

Instances

Eq User Source # 

Methods

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

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

Data User Source # 

Methods

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

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

toConstr :: User -> Constr #

dataTypeOf :: User -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord User Source # 

Methods

compare :: User -> User -> Ordering #

(<) :: User -> User -> Bool #

(<=) :: User -> User -> Bool #

(>) :: User -> User -> Bool #

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

max :: User -> User -> User #

min :: User -> User -> User #

Read User Source # 
Show User Source # 

Methods

showsPrec :: Int -> User -> ShowS #

show :: User -> String #

showList :: [User] -> ShowS #

Generic User Source # 

Associated Types

type Rep User :: * -> * #

Methods

from :: User -> Rep User x #

to :: Rep User x -> User #

ToJSON User Source # 
FromJSON User Source # 
SafeCopy User Source # 
Indexable UserIxs User Source # 
type Rep User Source # 
type Rep User = D1 (MetaData "User" "Happstack.Authenticate.Core" "happstack-authenticate-2.3.4.7-8NGvEJtsguz6HpkSzT4jIO" False) (C1 (MetaCons "User" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_userId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UserId)) ((:*:) (S1 (MetaSel (Just Symbol "_username") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Username)) (S1 (MetaSel (Just Symbol "_email") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Email))))))

newtype SharedSecret Source #

The shared secret is used to encrypt a users data on a per-user basis. We can invalidate a JWT value by changing the shared secret.

Constructors

SharedSecret 

Instances

Eq SharedSecret Source # 
Data SharedSecret Source # 

Methods

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

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

toConstr :: SharedSecret -> Constr #

dataTypeOf :: SharedSecret -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SharedSecret Source # 
Read SharedSecret Source # 
Show SharedSecret Source # 
Generic SharedSecret Source # 

Associated Types

type Rep SharedSecret :: * -> * #

SafeCopy SharedSecret Source # 
type Rep SharedSecret Source # 
type Rep SharedSecret = D1 (MetaData "SharedSecret" "Happstack.Authenticate.Core" "happstack-authenticate-2.3.4.7-8NGvEJtsguz6HpkSzT4jIO" True) (C1 (MetaCons "SharedSecret" PrefixI True) (S1 (MetaSel (Just Symbol "_unSharedSecret") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

genSharedSecret :: MonadIO m => m SharedSecret Source #

Generate a Salt from 128 bits of data from /dev/urandom, with the system RNG as a fallback. This is the function used to generate salts by makePassword.

type SharedSecrets = Map UserId SharedSecret Source #

A map which stores the SharedSecret for each UserId

data CoreError Source #

the CoreError type is used to represent errors in a language agnostic manner. The errors are translated into human readable form via the I18N translations.

Instances

Eq CoreError Source # 
Data CoreError Source # 

Methods

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

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

toConstr :: CoreError -> Constr #

dataTypeOf :: CoreError -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CoreError Source # 
Read CoreError Source # 
Show CoreError Source # 
Generic CoreError Source # 

Associated Types

type Rep CoreError :: * -> * #

ToJSON CoreError Source # 
FromJSON CoreError Source # 
ToJExpr CoreError Source # 
SafeCopy CoreError Source # 
RenderMessage HappstackAuthenticateI18N CoreError Source # 
type Rep CoreError Source # 
type Rep CoreError = D1 (MetaData "CoreError" "Happstack.Authenticate.Core" "happstack-authenticate-2.3.4.7-8NGvEJtsguz6HpkSzT4jIO" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "HandlerNotFound" PrefixI False) U1) (C1 (MetaCons "URLDecodeFailed" PrefixI False) U1)) ((:+:) (C1 (MetaCons "UsernameAlreadyExists" PrefixI False) U1) ((:+:) (C1 (MetaCons "AuthorizationRequired" PrefixI False) U1) (C1 (MetaCons "Forbidden" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "JSONDecodeFailed" PrefixI False) U1) (C1 (MetaCons "InvalidUserId" PrefixI False) U1)) ((:+:) (C1 (MetaCons "UsernameNotAcceptable" PrefixI False) U1) ((:+:) (C1 (MetaCons "InvalidEmail" PrefixI False) U1) (C1 (MetaCons "TextError" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))))))

data NewAccountMode Source #

This value is used to configure the type of new user registrations permitted for this system.

Constructors

OpenRegistration

new users can create their own accounts

ModeratedRegistration

new users can apply to create their own accounts, but a moderator must approve them before they are active

ClosedRegistration

only the admin can create a new account

data AuthenticateState Source #

this acid-state value contains the state common to all authentication methods

Instances

Eq AuthenticateState Source # 
Show AuthenticateState Source # 
Generic AuthenticateState Source # 
IsAcidic AuthenticateState Source # 
SafeCopy AuthenticateState Source # 
type Rep AuthenticateState Source # 
type Rep AuthenticateState = D1 (MetaData "AuthenticateState" "Happstack.Authenticate.Core" "happstack-authenticate-2.3.4.7-8NGvEJtsguz6HpkSzT4jIO" False) (C1 (MetaCons "AuthenticateState" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_sharedSecrets") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SharedSecrets)) (S1 (MetaSel (Just Symbol "_users") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IxUser))) ((:*:) (S1 (MetaSel (Just Symbol "_nextUserId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UserId)) ((:*:) (S1 (MetaSel (Just Symbol "_defaultSessionTimeout") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) (S1 (MetaSel (Just Symbol "_newAccountMode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NewAccountMode))))))

getOrGenSharedSecret :: MonadIO m => AcidState AuthenticateState -> UserId -> m SharedSecret Source #

get the SharedSecret for UserId. Generate one if they don't have one yet.

data Token Source #

The Token type represents the encrypted data used to identify a user.

Constructors

Token 

Instances

Eq Token Source # 

Methods

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

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

Data Token Source # 

Methods

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

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

toConstr :: Token -> Constr #

dataTypeOf :: Token -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Token Source # 

Methods

compare :: Token -> Token -> Ordering #

(<) :: Token -> Token -> Bool #

(<=) :: Token -> Token -> Bool #

(>) :: Token -> Token -> Bool #

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

max :: Token -> Token -> Token #

min :: Token -> Token -> Token #

Read Token Source # 
Show Token Source # 

Methods

showsPrec :: Int -> Token -> ShowS #

show :: Token -> String #

showList :: [Token] -> ShowS #

Generic Token Source # 

Associated Types

type Rep Token :: * -> * #

Methods

from :: Token -> Rep Token x #

to :: Rep Token x -> Token #

ToJSON Token Source # 
FromJSON Token Source # 
type Rep Token Source # 
type Rep Token = D1 (MetaData "Token" "Happstack.Authenticate.Core" "happstack-authenticate-2.3.4.7-8NGvEJtsguz6HpkSzT4jIO" False) (C1 (MetaCons "Token" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_tokenUser") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 User)) (S1 (MetaSel (Just Symbol "_tokenIsAuthAdmin") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))))

type TokenText = Text Source #

TokenText is the encrypted form of the Token which is passed between the server and the client.

issueToken Source #

Arguments

:: MonadIO m 
=> AcidState AuthenticateState 
-> AuthenticateConfig 
-> User

the user

-> m TokenText 

create a Token for User

The isAuthAdmin paramater is a function which will be called to determine if UserId is a user who should be given Administrator privileges. This includes the ability to things such as set the OpenId realm, change the registeration mode, etc.

decodeAndVerifyToken :: MonadIO m => AcidState AuthenticateState -> UTCTime -> TokenText -> m (Maybe (Token, JWT VerifiedJWT)) Source #

decode and verify the TokenText. If successful, return the Token otherwise Nothing.

authCookieName :: String Source #

name of the Cookie used to hold the TokenText

getTokenCookie :: Happstack m => AcidState AuthenticateState -> m (Maybe (Token, JWT VerifiedJWT)) Source #

get, decode, and verify the Token from the Cookie.

getTokenHeader :: Happstack m => AcidState AuthenticateState -> m (Maybe (Token, JWT VerifiedJWT)) Source #

get, decode, and verify the Token from the Authorization HTTP header

getToken :: Happstack m => AcidState AuthenticateState -> m (Maybe (Token, JWT VerifiedJWT)) Source #

get, decode, and verify the Token looking first in the Authorization header and then in Cookie.

see also: getTokenHeader, getTokenCookie

getUserId :: Happstack m => AcidState AuthenticateState -> m (Maybe UserId) Source #

get the UserId

calls getToken but returns only the UserId

newtype AuthenticationMethod Source #

AuthenticationMethod is used by the routing system to select which authentication backend should handle this request.

Instances

Eq AuthenticationMethod Source # 
Data AuthenticationMethod Source # 

Methods

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

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

toConstr :: AuthenticationMethod -> Constr #

dataTypeOf :: AuthenticationMethod -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AuthenticationMethod Source # 
Read AuthenticationMethod Source # 
Show AuthenticationMethod Source # 
Generic AuthenticationMethod Source # 
ToJSON AuthenticationMethod Source # 
FromJSON AuthenticationMethod Source # 
SafeCopy AuthenticationMethod Source # 
PathInfo AuthenticationMethod Source # 
type Rep AuthenticationMethod Source # 
type Rep AuthenticationMethod = D1 (MetaData "AuthenticationMethod" "Happstack.Authenticate.Core" "happstack-authenticate-2.3.4.7-8NGvEJtsguz6HpkSzT4jIO" True) (C1 (MetaCons "AuthenticationMethod" PrefixI True) (S1 (MetaSel (Just Symbol "_unAuthenticationMethod") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data AuthenticateURL Source #

Instances

Eq AuthenticateURL Source # 
Data AuthenticateURL Source # 

Methods

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

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

toConstr :: AuthenticateURL -> Constr #

dataTypeOf :: AuthenticateURL -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AuthenticateURL Source # 
Read AuthenticateURL Source # 
Show AuthenticateURL Source # 
Generic AuthenticateURL Source # 
PathInfo AuthenticateURL Source # 
(Functor m, Monad m) => EmbedAsChild (Partial' m) PartialMsgs # 
(Functor m, Monad m) => EmbedAsChild (Partial' m) PartialMsgs # 
(Functor m, Monad m) => EmbedAsAttr (Partial' m) (Attr Text PartialMsgs) # 
(Functor m, Monad m) => EmbedAsAttr (Partial' m) (Attr Text PartialMsgs) # 
type Rep AuthenticateURL Source # 
type Rep AuthenticateURL = D1 (MetaData "AuthenticateURL" "Happstack.Authenticate.Core" "happstack-authenticate-2.3.4.7-8NGvEJtsguz6HpkSzT4jIO" False) ((:+:) (C1 (MetaCons "AuthenticationMethods" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (AuthenticationMethod, [Text]))))) (C1 (MetaCons "Controllers" PrefixI False) U1))

rControllers :: forall tok e r. Boomerang e tok r ((:-) AuthenticateURL r) Source #

authenticateURL :: Router () (AuthenticateURL :- ()) Source #

a Router for AuthenicateURL

nestAuthenticationMethod :: PathInfo methodURL => AuthenticationMethod -> RouteT methodURL m a -> RouteT AuthenticateURL m a Source #

helper function which converts a URL for an authentication backend into an AuthenticateURL.