happstack-authenticate-2.3.4.10: Happstack Authentication Library

Safe HaskellNone
LanguageHaskell98

Happstack.Authenticate.Password.Core

Synopsis

Documentation

data PasswordConfig Source #

Instances

Generic PasswordConfig Source # 

Associated Types

type Rep PasswordConfig :: * -> * #

type Rep PasswordConfig Source # 
type Rep PasswordConfig = D1 * (MetaData "PasswordConfig" "Happstack.Authenticate.Password.Core" "happstack-authenticate-2.3.4.10-KOaQ65BcddsFX2pXVA6rju" False) (C1 * (MetaCons "PasswordConfig" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_resetLink") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) ((:*:) * (S1 * (MetaSel (Just Symbol "_domain") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_passwordAcceptable") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Text -> Maybe Text))))))

data PasswordError Source #

Instances

Eq PasswordError Source # 
Data PasswordError Source # 

Methods

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

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

toConstr :: PasswordError -> Constr #

dataTypeOf :: PasswordError -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PasswordError Source # 
Read PasswordError Source # 
Show PasswordError Source # 
Generic PasswordError Source # 

Associated Types

type Rep PasswordError :: * -> * #

ToJSON PasswordError Source # 
FromJSON PasswordError Source # 
ToJExpr PasswordError Source # 
RenderMessage HappstackAuthenticateI18N PasswordError Source # 
type Rep PasswordError Source # 
type Rep PasswordError = D1 * (MetaData "PasswordError" "Happstack.Authenticate.Password.Core" "happstack-authenticate-2.3.4.10-KOaQ65BcddsFX2pXVA6rju" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "NotAuthenticated" PrefixI False) (U1 *)) (C1 * (MetaCons "NotAuthorized" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "InvalidUsername" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "InvalidPassword" PrefixI False) (U1 *)) (C1 * (MetaCons "InvalidUsernamePassword" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "NoEmailAddress" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "MissingResetToken" PrefixI False) (U1 *)) (C1 * (MetaCons "InvalidResetToken" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "PasswordMismatch" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "UnacceptablePassword" PrefixI True) (S1 * (MetaSel (Just Symbol "passwordErrorMessageMsg") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text))) (C1 * (MetaCons "CoreError" PrefixI True) (S1 * (MetaSel (Just Symbol "passwordErrorMessageE") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CoreError)))))))

newtype HashedPass Source #

Constructors

HashedPass 

Instances

Eq HashedPass Source # 
Data HashedPass Source # 

Methods

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

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

toConstr :: HashedPass -> Constr #

dataTypeOf :: HashedPass -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord HashedPass Source # 
Read HashedPass Source # 
Show HashedPass Source # 
Generic HashedPass Source # 

Associated Types

type Rep HashedPass :: * -> * #

SafeCopy HashedPass Source # 
type Rep HashedPass Source # 
type Rep HashedPass = D1 * (MetaData "HashedPass" "Happstack.Authenticate.Password.Core" "happstack-authenticate-2.3.4.10-KOaQ65BcddsFX2pXVA6rju" True) (C1 * (MetaCons "HashedPass" PrefixI True) (S1 * (MetaSel (Just Symbol "_unHashedPass") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ByteString)))

mkHashedPass Source #

Arguments

:: (Functor m, MonadIO m) 
=> Text

password in plain text

-> m HashedPass

salted and hashed

hash a password string

verifyHashedPass Source #

Arguments

:: Text

password in plain text

-> HashedPass

hashed version of password

-> Bool 

verify a password

data PasswordState Source #

Constructors

PasswordState 

Instances

Eq PasswordState Source # 
Data PasswordState Source # 

Methods

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

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

toConstr :: PasswordState -> Constr #

dataTypeOf :: PasswordState -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PasswordState Source # 
Read PasswordState Source # 
Show PasswordState Source # 
Generic PasswordState Source # 

Associated Types

type Rep PasswordState :: * -> * #

IsAcidic PasswordState Source # 
SafeCopy PasswordState Source # 
type Rep PasswordState Source # 
type Rep PasswordState = D1 * (MetaData "PasswordState" "Happstack.Authenticate.Password.Core" "happstack-authenticate-2.3.4.10-KOaQ65BcddsFX2pXVA6rju" False) (C1 * (MetaCons "PasswordState" PrefixI True) (S1 * (MetaSel (Just Symbol "_passwords") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Map UserId HashedPass))))

setPassword Source #

Arguments

:: UserId

UserId

-> HashedPass

the hashed password

-> Update PasswordState () 

set the password for UserId

deletePassword Source #

Arguments

:: UserId

UserId

-> Update PasswordState () 

delete the password for UserId

verifyPasswordForUserId Source #

Arguments

:: UserId

UserId

-> Text

plain-text password

-> Query PasswordState Bool 

verify that the supplied password matches the stored hashed password for UserId

verifyPassword :: MonadIO m => AcidState AuthenticateState -> AcidState PasswordState -> Username -> Text -> m Bool Source #

verify that the supplied username/password is valid

data UserPass Source #

Constructors

UserPass 

Fields

Instances

Eq UserPass Source # 
Data UserPass Source # 

Methods

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

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

toConstr :: UserPass -> Constr #

dataTypeOf :: UserPass -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord UserPass Source # 
Read UserPass Source # 
Show UserPass Source # 
Generic UserPass Source # 

Associated Types

type Rep UserPass :: * -> * #

Methods

from :: UserPass -> Rep UserPass x #

to :: Rep UserPass x -> UserPass #

ToJSON UserPass Source # 
FromJSON UserPass Source # 
ToJExpr UserPass Source # 
type Rep UserPass Source # 
type Rep UserPass = D1 * (MetaData "UserPass" "Happstack.Authenticate.Password.Core" "happstack-authenticate-2.3.4.10-KOaQ65BcddsFX2pXVA6rju" False) (C1 * (MetaCons "UserPass" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_user") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Username)) (S1 * (MetaSel (Just Symbol "_password") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text))))

data NewAccountData Source #

JSON record for new account data

Instances

Eq NewAccountData Source # 
Data NewAccountData Source # 

Methods

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

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

toConstr :: NewAccountData -> Constr #

dataTypeOf :: NewAccountData -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord NewAccountData Source # 
Read NewAccountData Source # 
Show NewAccountData Source # 
Generic NewAccountData Source # 

Associated Types

type Rep NewAccountData :: * -> * #

ToJSON NewAccountData Source # 
FromJSON NewAccountData Source # 
type Rep NewAccountData Source # 
type Rep NewAccountData = D1 * (MetaData "NewAccountData" "Happstack.Authenticate.Password.Core" "happstack-authenticate-2.3.4.10-KOaQ65BcddsFX2pXVA6rju" False) (C1 * (MetaCons "NewAccountData" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_naUser") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * User)) ((:*:) * (S1 * (MetaSel (Just Symbol "_naPassword") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_naPasswordConfirm") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))))

data ChangePasswordData Source #

JSON record for change password data

Instances

Eq ChangePasswordData Source # 
Data ChangePasswordData Source # 

Methods

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

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

toConstr :: ChangePasswordData -> Constr #

dataTypeOf :: ChangePasswordData -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ChangePasswordData Source # 
Read ChangePasswordData Source # 
Show ChangePasswordData Source # 
Generic ChangePasswordData Source # 
ToJSON ChangePasswordData Source # 
FromJSON ChangePasswordData Source # 
type Rep ChangePasswordData Source # 
type Rep ChangePasswordData = D1 * (MetaData "ChangePasswordData" "Happstack.Authenticate.Password.Core" "happstack-authenticate-2.3.4.10-KOaQ65BcddsFX2pXVA6rju" False) (C1 * (MetaCons "ChangePasswordData" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_cpOldPassword") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) ((:*:) * (S1 * (MetaSel (Just Symbol "_cpNewPassword") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_cpNewPasswordConfirm") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))))

data RequestResetPasswordData Source #

JSON record for new account data

Instances

Eq RequestResetPasswordData Source # 
Data RequestResetPasswordData Source # 

Methods

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

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

toConstr :: RequestResetPasswordData -> Constr #

dataTypeOf :: RequestResetPasswordData -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RequestResetPasswordData Source # 
Read RequestResetPasswordData Source # 
Show RequestResetPasswordData Source # 
Generic RequestResetPasswordData Source # 
ToJSON RequestResetPasswordData Source # 
FromJSON RequestResetPasswordData Source # 
type Rep RequestResetPasswordData Source # 
type Rep RequestResetPasswordData = D1 * (MetaData "RequestResetPasswordData" "Happstack.Authenticate.Password.Core" "happstack-authenticate-2.3.4.10-KOaQ65BcddsFX2pXVA6rju" False) (C1 * (MetaCons "RequestResetPasswordData" PrefixI True) (S1 * (MetaSel (Just Symbol "_rrpUsername") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Username)))

sendResetEmail :: MonadIO m => Email -> Email -> Text -> m () Source #

data ResetPasswordData Source #

JSON record for new account data

Instances

Eq ResetPasswordData Source # 
Data ResetPasswordData Source # 

Methods

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

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

toConstr :: ResetPasswordData -> Constr #

dataTypeOf :: ResetPasswordData -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ResetPasswordData Source # 
Read ResetPasswordData Source # 
Show ResetPasswordData Source # 
Generic ResetPasswordData Source # 
ToJSON ResetPasswordData Source # 
FromJSON ResetPasswordData Source # 
type Rep ResetPasswordData Source # 
type Rep ResetPasswordData = D1 * (MetaData "ResetPasswordData" "Happstack.Authenticate.Password.Core" "happstack-authenticate-2.3.4.10-KOaQ65BcddsFX2pXVA6rju" False) (C1 * (MetaCons "ResetPasswordData" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_rpPassword") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) ((:*:) * (S1 * (MetaSel (Just Symbol "_rpPasswordConfirm") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_rpResetToken") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))))