happstack-authenticate-2.4.1: Happstack Authentication Library

Safe HaskellNone
LanguageHaskell2010

Happstack.Authenticate.Password.Core

Synopsis

Documentation

data PasswordConfig Source #

Instances
Generic PasswordConfig Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

Associated Types

type Rep PasswordConfig :: Type -> Type #

type Rep PasswordConfig Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

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

data PasswordError Source #

Instances
Eq PasswordError Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

Data PasswordError Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

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 # 
Instance details

Defined in Happstack.Authenticate.Password.Core

Read PasswordError Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

Show PasswordError Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

Generic PasswordError Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

Associated Types

type Rep PasswordError :: Type -> Type #

ToJSON PasswordError Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

FromJSON PasswordError Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

ToJExpr PasswordError Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

RenderMessage HappstackAuthenticateI18N PasswordError Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

type Rep PasswordError Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

type Rep PasswordError = D1 (MetaData "PasswordError" "Happstack.Authenticate.Password.Core" "happstack-authenticate-2.4.1-1ovIfMIVOnoEaCpOHmRxnh" False) (((C1 (MetaCons "NotAuthenticated" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NotAuthorized" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "InvalidUsername" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "InvalidPassword" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "InvalidUsernamePassword" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "NoEmailAddress" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "MissingResetToken" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "InvalidResetToken" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "PasswordMismatch" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "UnacceptablePassword" PrefixI True) (S1 (MetaSel (Just "passwordErrorMessageMsg") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) :+: C1 (MetaCons "CoreError" PrefixI True) (S1 (MetaSel (Just "passwordErrorMessageE") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CoreError))))))

newtype HashedPass Source #

Constructors

HashedPass 
Instances
Eq HashedPass Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

Data HashedPass Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

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 # 
Instance details

Defined in Happstack.Authenticate.Password.Core

Read HashedPass Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

Show HashedPass Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

Generic HashedPass Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

Associated Types

type Rep HashedPass :: Type -> Type #

SafeCopy HashedPass Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

type Rep HashedPass Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

type Rep HashedPass = D1 (MetaData "HashedPass" "Happstack.Authenticate.Password.Core" "happstack-authenticate-2.4.1-1ovIfMIVOnoEaCpOHmRxnh" True) (C1 (MetaCons "HashedPass" PrefixI True) (S1 (MetaSel (Just "_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 # 
Instance details

Defined in Happstack.Authenticate.Password.Core

Data PasswordState Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

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 # 
Instance details

Defined in Happstack.Authenticate.Password.Core

Read PasswordState Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

Show PasswordState Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

Generic PasswordState Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

Associated Types

type Rep PasswordState :: Type -> Type #

SafeCopy PasswordState Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

IsAcidic PasswordState Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

type Rep PasswordState Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

type Rep PasswordState = D1 (MetaData "PasswordState" "Happstack.Authenticate.Password.Core" "happstack-authenticate-2.4.1-1ovIfMIVOnoEaCpOHmRxnh" False) (C1 (MetaCons "PasswordState" PrefixI True) (S1 (MetaSel (Just "_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 # 
Instance details

Defined in Happstack.Authenticate.Password.Core

Data UserPass Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

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 # 
Instance details

Defined in Happstack.Authenticate.Password.Core

Read UserPass Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

Show UserPass Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

Generic UserPass Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

Associated Types

type Rep UserPass :: Type -> Type #

Methods

from :: UserPass -> Rep UserPass x #

to :: Rep UserPass x -> UserPass #

ToJSON UserPass Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

FromJSON UserPass Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

ToJExpr UserPass Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

type Rep UserPass Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

type Rep UserPass = D1 (MetaData "UserPass" "Happstack.Authenticate.Password.Core" "happstack-authenticate-2.4.1-1ovIfMIVOnoEaCpOHmRxnh" False) (C1 (MetaCons "UserPass" PrefixI True) (S1 (MetaSel (Just "_user") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Username) :*: S1 (MetaSel (Just "_password") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data NewAccountData Source #

JSON record for new account data

Instances
Eq NewAccountData Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

Data NewAccountData Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

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 # 
Instance details

Defined in Happstack.Authenticate.Password.Core

Read NewAccountData Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

Show NewAccountData Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

Generic NewAccountData Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

Associated Types

type Rep NewAccountData :: Type -> Type #

ToJSON NewAccountData Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

FromJSON NewAccountData Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

type Rep NewAccountData Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

type Rep NewAccountData = D1 (MetaData "NewAccountData" "Happstack.Authenticate.Password.Core" "happstack-authenticate-2.4.1-1ovIfMIVOnoEaCpOHmRxnh" False) (C1 (MetaCons "NewAccountData" PrefixI True) (S1 (MetaSel (Just "_naUser") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 User) :*: (S1 (MetaSel (Just "_naPassword") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "_naPasswordConfirm") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))))

data ChangePasswordData Source #

JSON record for change password data

Instances
Eq ChangePasswordData Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

Data ChangePasswordData Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

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 # 
Instance details

Defined in Happstack.Authenticate.Password.Core

Read ChangePasswordData Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

Show ChangePasswordData Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

Generic ChangePasswordData Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

Associated Types

type Rep ChangePasswordData :: Type -> Type #

ToJSON ChangePasswordData Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

FromJSON ChangePasswordData Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

type Rep ChangePasswordData Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

type Rep ChangePasswordData = D1 (MetaData "ChangePasswordData" "Happstack.Authenticate.Password.Core" "happstack-authenticate-2.4.1-1ovIfMIVOnoEaCpOHmRxnh" False) (C1 (MetaCons "ChangePasswordData" PrefixI True) (S1 (MetaSel (Just "_cpOldPassword") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: (S1 (MetaSel (Just "_cpNewPassword") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "_cpNewPasswordConfirm") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))))

data RequestResetPasswordData Source #

JSON record for new account data

Instances
Eq RequestResetPasswordData Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

Data RequestResetPasswordData Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

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 # 
Instance details

Defined in Happstack.Authenticate.Password.Core

Read RequestResetPasswordData Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

Show RequestResetPasswordData Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

Generic RequestResetPasswordData Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

Associated Types

type Rep RequestResetPasswordData :: Type -> Type #

ToJSON RequestResetPasswordData Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

FromJSON RequestResetPasswordData Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

type Rep RequestResetPasswordData Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

type Rep RequestResetPasswordData = D1 (MetaData "RequestResetPasswordData" "Happstack.Authenticate.Password.Core" "happstack-authenticate-2.4.1-1ovIfMIVOnoEaCpOHmRxnh" False) (C1 (MetaCons "RequestResetPasswordData" PrefixI True) (S1 (MetaSel (Just "_rrpUsername") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Username)))

data ResetPasswordData Source #

JSON record for new account data

Instances
Eq ResetPasswordData Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

Data ResetPasswordData Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

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 # 
Instance details

Defined in Happstack.Authenticate.Password.Core

Read ResetPasswordData Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

Show ResetPasswordData Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

Generic ResetPasswordData Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

Associated Types

type Rep ResetPasswordData :: Type -> Type #

ToJSON ResetPasswordData Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

FromJSON ResetPasswordData Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

type Rep ResetPasswordData Source # 
Instance details

Defined in Happstack.Authenticate.Password.Core

type Rep ResetPasswordData = D1 (MetaData "ResetPasswordData" "Happstack.Authenticate.Password.Core" "happstack-authenticate-2.4.1-1ovIfMIVOnoEaCpOHmRxnh" False) (C1 (MetaCons "ResetPasswordData" PrefixI True) (S1 (MetaSel (Just "_rpPassword") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: (S1 (MetaSel (Just "_rpPasswordConfirm") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "_rpResetToken") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))))