{-# LANGUAGE DataKinds, DeriveDataTypeable, DeriveGeneric, FlexibleInstances, MultiParamTypeClasses, RecordWildCards, TemplateHaskell, TypeFamilies, TypeSynonymInstances, TypeOperators, OverloadedStrings #-}
module Happstack.Authenticate.Password.URL where
import Control.Category ((.), id)
import Data.Data (Data, Typeable)
import Data.UserId (UserId(..), rUserId)
import GHC.Generics (Generic)
import Prelude hiding ((.), id)
import Web.Routes (RouteT(..))
import Web.Routes.TH (derivePathInfo)
import Happstack.Authenticate.Core (AuthenticateURL, AuthenticationMethod(..), nestAuthenticationMethod)
import Happstack.Authenticate.Password.PartialsURL (PartialURL(..), partialURL)
import Text.Boomerang.TH (makeBoomerangs)
import Web.Routes (PathInfo(..))
import Web.Routes.Boomerang
passwordAuthenticationMethod :: AuthenticationMethod
passwordAuthenticationMethod :: AuthenticationMethod
passwordAuthenticationMethod = Text -> AuthenticationMethod
AuthenticationMethod Text
"password"
data AccountURL
= Password
deriving (AccountURL -> AccountURL -> Bool
(AccountURL -> AccountURL -> Bool)
-> (AccountURL -> AccountURL -> Bool) -> Eq AccountURL
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AccountURL -> AccountURL -> Bool
$c/= :: AccountURL -> AccountURL -> Bool
== :: AccountURL -> AccountURL -> Bool
$c== :: AccountURL -> AccountURL -> Bool
Eq, Eq AccountURL
Eq AccountURL
-> (AccountURL -> AccountURL -> Ordering)
-> (AccountURL -> AccountURL -> Bool)
-> (AccountURL -> AccountURL -> Bool)
-> (AccountURL -> AccountURL -> Bool)
-> (AccountURL -> AccountURL -> Bool)
-> (AccountURL -> AccountURL -> AccountURL)
-> (AccountURL -> AccountURL -> AccountURL)
-> Ord AccountURL
AccountURL -> AccountURL -> Bool
AccountURL -> AccountURL -> Ordering
AccountURL -> AccountURL -> AccountURL
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AccountURL -> AccountURL -> AccountURL
$cmin :: AccountURL -> AccountURL -> AccountURL
max :: AccountURL -> AccountURL -> AccountURL
$cmax :: AccountURL -> AccountURL -> AccountURL
>= :: AccountURL -> AccountURL -> Bool
$c>= :: AccountURL -> AccountURL -> Bool
> :: AccountURL -> AccountURL -> Bool
$c> :: AccountURL -> AccountURL -> Bool
<= :: AccountURL -> AccountURL -> Bool
$c<= :: AccountURL -> AccountURL -> Bool
< :: AccountURL -> AccountURL -> Bool
$c< :: AccountURL -> AccountURL -> Bool
compare :: AccountURL -> AccountURL -> Ordering
$ccompare :: AccountURL -> AccountURL -> Ordering
$cp1Ord :: Eq AccountURL
Ord, ReadPrec [AccountURL]
ReadPrec AccountURL
Int -> ReadS AccountURL
ReadS [AccountURL]
(Int -> ReadS AccountURL)
-> ReadS [AccountURL]
-> ReadPrec AccountURL
-> ReadPrec [AccountURL]
-> Read AccountURL
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AccountURL]
$creadListPrec :: ReadPrec [AccountURL]
readPrec :: ReadPrec AccountURL
$creadPrec :: ReadPrec AccountURL
readList :: ReadS [AccountURL]
$creadList :: ReadS [AccountURL]
readsPrec :: Int -> ReadS AccountURL
$creadsPrec :: Int -> ReadS AccountURL
Read, Int -> AccountURL -> ShowS
[AccountURL] -> ShowS
AccountURL -> String
(Int -> AccountURL -> ShowS)
-> (AccountURL -> String)
-> ([AccountURL] -> ShowS)
-> Show AccountURL
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AccountURL] -> ShowS
$cshowList :: [AccountURL] -> ShowS
show :: AccountURL -> String
$cshow :: AccountURL -> String
showsPrec :: Int -> AccountURL -> ShowS
$cshowsPrec :: Int -> AccountURL -> ShowS
Show, Typeable AccountURL
DataType
Constr
Typeable AccountURL
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AccountURL -> c AccountURL)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AccountURL)
-> (AccountURL -> Constr)
-> (AccountURL -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c AccountURL))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c AccountURL))
-> ((forall b. Data b => b -> b) -> AccountURL -> AccountURL)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AccountURL -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AccountURL -> r)
-> (forall u. (forall d. Data d => d -> u) -> AccountURL -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> AccountURL -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> AccountURL -> m AccountURL)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> AccountURL -> m AccountURL)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> AccountURL -> m AccountURL)
-> Data AccountURL
AccountURL -> DataType
AccountURL -> Constr
(forall b. Data b => b -> b) -> AccountURL -> AccountURL
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AccountURL -> c AccountURL
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AccountURL
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> AccountURL -> u
forall u. (forall d. Data d => d -> u) -> AccountURL -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AccountURL -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AccountURL -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> AccountURL -> m AccountURL
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> AccountURL -> m AccountURL
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AccountURL
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AccountURL -> c AccountURL
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c AccountURL)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AccountURL)
$cPassword :: Constr
$tAccountURL :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> AccountURL -> m AccountURL
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> AccountURL -> m AccountURL
gmapMp :: (forall d. Data d => d -> m d) -> AccountURL -> m AccountURL
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> AccountURL -> m AccountURL
gmapM :: (forall d. Data d => d -> m d) -> AccountURL -> m AccountURL
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> AccountURL -> m AccountURL
gmapQi :: Int -> (forall d. Data d => d -> u) -> AccountURL -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> AccountURL -> u
gmapQ :: (forall d. Data d => d -> u) -> AccountURL -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> AccountURL -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AccountURL -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AccountURL -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AccountURL -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AccountURL -> r
gmapT :: (forall b. Data b => b -> b) -> AccountURL -> AccountURL
$cgmapT :: (forall b. Data b => b -> b) -> AccountURL -> AccountURL
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AccountURL)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AccountURL)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c AccountURL)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c AccountURL)
dataTypeOf :: AccountURL -> DataType
$cdataTypeOf :: AccountURL -> DataType
toConstr :: AccountURL -> Constr
$ctoConstr :: AccountURL -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AccountURL
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AccountURL
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AccountURL -> c AccountURL
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AccountURL -> c AccountURL
$cp1Data :: Typeable AccountURL
Data, Typeable, (forall x. AccountURL -> Rep AccountURL x)
-> (forall x. Rep AccountURL x -> AccountURL) -> Generic AccountURL
forall x. Rep AccountURL x -> AccountURL
forall x. AccountURL -> Rep AccountURL x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AccountURL x -> AccountURL
$cfrom :: forall x. AccountURL -> Rep AccountURL x
Generic)
makeBoomerangs ''AccountURL
accountURL :: Router () (AccountURL :- ())
accountURL :: Router () (AccountURL :- ())
accountURL =
( Router () (AccountURL :- ())
forall tok e r. Boomerang e tok r (AccountURL :- r)
rPassword Router () (AccountURL :- ())
-> Boomerang TextsError [Text] () ()
-> Router () (AccountURL :- ())
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Boomerang TextsError [Text] () ()
"password"
)
instance PathInfo AccountURL where
fromPathSegments :: URLParser AccountURL
fromPathSegments = Router () (AccountURL :- ()) -> URLParser AccountURL
forall url.
Boomerang TextsError [Text] () (url :- ()) -> URLParser url
boomerangFromPathSegments Router () (AccountURL :- ())
accountURL
toPathSegments :: AccountURL -> [Text]
toPathSegments = Router () (AccountURL :- ()) -> AccountURL -> [Text]
forall url.
Boomerang TextsError [Text] () (url :- ()) -> url -> [Text]
boomerangToPathSegments Router () (AccountURL :- ())
accountURL
data PasswordURL
= Token
| Account (Maybe (UserId, AccountURL))
| Partial PartialURL
| PasswordRequestReset
| PasswordReset
| UsernamePasswordCtrl
deriving (PasswordURL -> PasswordURL -> Bool
(PasswordURL -> PasswordURL -> Bool)
-> (PasswordURL -> PasswordURL -> Bool) -> Eq PasswordURL
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PasswordURL -> PasswordURL -> Bool
$c/= :: PasswordURL -> PasswordURL -> Bool
== :: PasswordURL -> PasswordURL -> Bool
$c== :: PasswordURL -> PasswordURL -> Bool
Eq, Eq PasswordURL
Eq PasswordURL
-> (PasswordURL -> PasswordURL -> Ordering)
-> (PasswordURL -> PasswordURL -> Bool)
-> (PasswordURL -> PasswordURL -> Bool)
-> (PasswordURL -> PasswordURL -> Bool)
-> (PasswordURL -> PasswordURL -> Bool)
-> (PasswordURL -> PasswordURL -> PasswordURL)
-> (PasswordURL -> PasswordURL -> PasswordURL)
-> Ord PasswordURL
PasswordURL -> PasswordURL -> Bool
PasswordURL -> PasswordURL -> Ordering
PasswordURL -> PasswordURL -> PasswordURL
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PasswordURL -> PasswordURL -> PasswordURL
$cmin :: PasswordURL -> PasswordURL -> PasswordURL
max :: PasswordURL -> PasswordURL -> PasswordURL
$cmax :: PasswordURL -> PasswordURL -> PasswordURL
>= :: PasswordURL -> PasswordURL -> Bool
$c>= :: PasswordURL -> PasswordURL -> Bool
> :: PasswordURL -> PasswordURL -> Bool
$c> :: PasswordURL -> PasswordURL -> Bool
<= :: PasswordURL -> PasswordURL -> Bool
$c<= :: PasswordURL -> PasswordURL -> Bool
< :: PasswordURL -> PasswordURL -> Bool
$c< :: PasswordURL -> PasswordURL -> Bool
compare :: PasswordURL -> PasswordURL -> Ordering
$ccompare :: PasswordURL -> PasswordURL -> Ordering
$cp1Ord :: Eq PasswordURL
Ord, Typeable PasswordURL
DataType
Constr
Typeable PasswordURL
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PasswordURL -> c PasswordURL)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PasswordURL)
-> (PasswordURL -> Constr)
-> (PasswordURL -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PasswordURL))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PasswordURL))
-> ((forall b. Data b => b -> b) -> PasswordURL -> PasswordURL)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PasswordURL -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PasswordURL -> r)
-> (forall u. (forall d. Data d => d -> u) -> PasswordURL -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> PasswordURL -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PasswordURL -> m PasswordURL)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PasswordURL -> m PasswordURL)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PasswordURL -> m PasswordURL)
-> Data PasswordURL
PasswordURL -> DataType
PasswordURL -> Constr
(forall b. Data b => b -> b) -> PasswordURL -> PasswordURL
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PasswordURL -> c PasswordURL
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PasswordURL
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> PasswordURL -> u
forall u. (forall d. Data d => d -> u) -> PasswordURL -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PasswordURL -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PasswordURL -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PasswordURL -> m PasswordURL
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PasswordURL -> m PasswordURL
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PasswordURL
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PasswordURL -> c PasswordURL
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PasswordURL)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PasswordURL)
$cUsernamePasswordCtrl :: Constr
$cPasswordReset :: Constr
$cPasswordRequestReset :: Constr
$cPartial :: Constr
$cAccount :: Constr
$cToken :: Constr
$tPasswordURL :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> PasswordURL -> m PasswordURL
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PasswordURL -> m PasswordURL
gmapMp :: (forall d. Data d => d -> m d) -> PasswordURL -> m PasswordURL
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PasswordURL -> m PasswordURL
gmapM :: (forall d. Data d => d -> m d) -> PasswordURL -> m PasswordURL
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PasswordURL -> m PasswordURL
gmapQi :: Int -> (forall d. Data d => d -> u) -> PasswordURL -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> PasswordURL -> u
gmapQ :: (forall d. Data d => d -> u) -> PasswordURL -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> PasswordURL -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PasswordURL -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PasswordURL -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PasswordURL -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PasswordURL -> r
gmapT :: (forall b. Data b => b -> b) -> PasswordURL -> PasswordURL
$cgmapT :: (forall b. Data b => b -> b) -> PasswordURL -> PasswordURL
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PasswordURL)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PasswordURL)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c PasswordURL)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PasswordURL)
dataTypeOf :: PasswordURL -> DataType
$cdataTypeOf :: PasswordURL -> DataType
toConstr :: PasswordURL -> Constr
$ctoConstr :: PasswordURL -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PasswordURL
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PasswordURL
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PasswordURL -> c PasswordURL
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PasswordURL -> c PasswordURL
$cp1Data :: Typeable PasswordURL
Data, Typeable, (forall x. PasswordURL -> Rep PasswordURL x)
-> (forall x. Rep PasswordURL x -> PasswordURL)
-> Generic PasswordURL
forall x. Rep PasswordURL x -> PasswordURL
forall x. PasswordURL -> Rep PasswordURL x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PasswordURL x -> PasswordURL
$cfrom :: forall x. PasswordURL -> Rep PasswordURL x
Generic)
makeBoomerangs ''PasswordURL
passwordURL :: Router () (PasswordURL :- ())
passwordURL :: Router () (PasswordURL :- ())
passwordURL =
( Boomerang TextsError [Text] (PasswordURL :- ()) (PasswordURL :- ())
"token" Boomerang TextsError [Text] (PasswordURL :- ()) (PasswordURL :- ())
-> Router () (PasswordURL :- ()) -> Router () (PasswordURL :- ())
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Router () (PasswordURL :- ())
forall tok e r. Boomerang e tok r (PasswordURL :- r)
rToken
Router () (PasswordURL :- ())
-> Router () (PasswordURL :- ()) -> Router () (PasswordURL :- ())
forall a. Semigroup a => a -> a -> a
<> Boomerang TextsError [Text] (PasswordURL :- ()) (PasswordURL :- ())
"account" Boomerang TextsError [Text] (PasswordURL :- ()) (PasswordURL :- ())
-> Router () (PasswordURL :- ()) -> Router () (PasswordURL :- ())
forall b c a.
Boomerang TextsError [Text] b c
-> Boomerang TextsError [Text] a b
-> Boomerang TextsError [Text] a c
</> Boomerang
TextsError
[Text]
(Maybe (UserId, AccountURL) :- ())
(PasswordURL :- ())
forall tok e r.
Boomerang
e tok (Maybe (UserId, AccountURL) :- r) (PasswordURL :- r)
rAccount Boomerang
TextsError
[Text]
(Maybe (UserId, AccountURL) :- ())
(PasswordURL :- ())
-> Boomerang
TextsError [Text] () (Maybe (UserId, AccountURL) :- ())
-> Router () (PasswordURL :- ())
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Boomerang TextsError [Text] () ((UserId, AccountURL) :- ())
-> Boomerang
TextsError [Text] () (Maybe (UserId, AccountURL) :- ())
forall e tok r a.
Boomerang e tok r (a :- r) -> Boomerang e tok r (Maybe a :- r)
rMaybe (Boomerang
TextsError
[Text]
(UserId :- (AccountURL :- ()))
((UserId, AccountURL) :- ())
forall e tok f s r. Boomerang e tok (f :- (s :- r)) ((f, s) :- r)
rPair Boomerang
TextsError
[Text]
(UserId :- (AccountURL :- ()))
((UserId, AccountURL) :- ())
-> Boomerang TextsError [Text] () (UserId :- (AccountURL :- ()))
-> Boomerang TextsError [Text] () ((UserId, AccountURL) :- ())
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (Boomerang
TextsError
[Text]
(Integer :- (AccountURL :- ()))
(UserId :- (AccountURL :- ()))
forall tok e r. Boomerang e tok (Integer :- r) (UserId :- r)
rUserId Boomerang
TextsError
[Text]
(Integer :- (AccountURL :- ()))
(UserId :- (AccountURL :- ()))
-> Boomerang
TextsError
[Text]
(AccountURL :- ())
(Integer :- (AccountURL :- ()))
-> Boomerang
TextsError [Text] (AccountURL :- ()) (UserId :- (AccountURL :- ()))
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Boomerang
TextsError
[Text]
(AccountURL :- ())
(Integer :- (AccountURL :- ()))
forall r. Boomerang TextsError [Text] r (Integer :- r)
integer) Boomerang
TextsError [Text] (AccountURL :- ()) (UserId :- (AccountURL :- ()))
-> Router () (AccountURL :- ())
-> Boomerang TextsError [Text] () (UserId :- (AccountURL :- ()))
forall b c a.
Boomerang TextsError [Text] b c
-> Boomerang TextsError [Text] a b
-> Boomerang TextsError [Text] a c
</> Router () (AccountURL :- ())
accountURL)
Router () (PasswordURL :- ())
-> Router () (PasswordURL :- ()) -> Router () (PasswordURL :- ())
forall a. Semigroup a => a -> a -> a
<> Boomerang TextsError [Text] (PasswordURL :- ()) (PasswordURL :- ())
"partial" Boomerang TextsError [Text] (PasswordURL :- ()) (PasswordURL :- ())
-> Router () (PasswordURL :- ()) -> Router () (PasswordURL :- ())
forall b c a.
Boomerang TextsError [Text] b c
-> Boomerang TextsError [Text] a b
-> Boomerang TextsError [Text] a c
</> Boomerang TextsError [Text] (PartialURL :- ()) (PasswordURL :- ())
forall tok e r.
Boomerang e tok (PartialURL :- r) (PasswordURL :- r)
rPartial Boomerang TextsError [Text] (PartialURL :- ()) (PasswordURL :- ())
-> Boomerang TextsError [Text] () (PartialURL :- ())
-> Router () (PasswordURL :- ())
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Boomerang TextsError [Text] () (PartialURL :- ())
partialURL
Router () (PasswordURL :- ())
-> Router () (PasswordURL :- ()) -> Router () (PasswordURL :- ())
forall a. Semigroup a => a -> a -> a
<> Boomerang TextsError [Text] (PasswordURL :- ()) (PasswordURL :- ())
"password-request-reset" Boomerang TextsError [Text] (PasswordURL :- ()) (PasswordURL :- ())
-> Router () (PasswordURL :- ()) -> Router () (PasswordURL :- ())
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Router () (PasswordURL :- ())
forall tok e r. Boomerang e tok r (PasswordURL :- r)
rPasswordRequestReset
Router () (PasswordURL :- ())
-> Router () (PasswordURL :- ()) -> Router () (PasswordURL :- ())
forall a. Semigroup a => a -> a -> a
<> Boomerang TextsError [Text] (PasswordURL :- ()) (PasswordURL :- ())
"password-reset" Boomerang TextsError [Text] (PasswordURL :- ()) (PasswordURL :- ())
-> Router () (PasswordURL :- ()) -> Router () (PasswordURL :- ())
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Router () (PasswordURL :- ())
forall tok e r. Boomerang e tok r (PasswordURL :- r)
rPasswordReset
Router () (PasswordURL :- ())
-> Router () (PasswordURL :- ()) -> Router () (PasswordURL :- ())
forall a. Semigroup a => a -> a -> a
<> Boomerang TextsError [Text] (PasswordURL :- ()) (PasswordURL :- ())
"js" Boomerang TextsError [Text] (PasswordURL :- ()) (PasswordURL :- ())
-> Router () (PasswordURL :- ()) -> Router () (PasswordURL :- ())
forall b c a.
Boomerang TextsError [Text] b c
-> Boomerang TextsError [Text] a b
-> Boomerang TextsError [Text] a c
</> Router () (PasswordURL :- ())
forall tok e r. Boomerang e tok r (PasswordURL :- r)
rUsernamePasswordCtrl
)
instance PathInfo PasswordURL where
fromPathSegments :: URLParser PasswordURL
fromPathSegments = Router () (PasswordURL :- ()) -> URLParser PasswordURL
forall url.
Boomerang TextsError [Text] () (url :- ()) -> URLParser url
boomerangFromPathSegments Router () (PasswordURL :- ())
passwordURL
toPathSegments :: PasswordURL -> [Text]
toPathSegments = Router () (PasswordURL :- ()) -> PasswordURL -> [Text]
forall url.
Boomerang TextsError [Text] () (url :- ()) -> url -> [Text]
boomerangToPathSegments Router () (PasswordURL :- ())
passwordURL
nestPasswordURL :: RouteT PasswordURL m a -> RouteT AuthenticateURL m a
nestPasswordURL :: RouteT PasswordURL m a -> RouteT AuthenticateURL m a
nestPasswordURL =
AuthenticationMethod
-> RouteT PasswordURL m a -> RouteT AuthenticateURL m a
forall methodURL (m :: * -> *) a.
PathInfo methodURL =>
AuthenticationMethod
-> RouteT methodURL m a -> RouteT AuthenticateURL m a
nestAuthenticationMethod AuthenticationMethod
passwordAuthenticationMethod