module OryKratos.Types.Recovery
  ( RecoveryFlow (..),
    RecoveryFlowMethods (..),
    RecoveryFlowMethod (..),
    RecoveryFlowMethodConfig (..),
    RecoveryLink (..),
  )
where

import OryKratos.Types.Misc (FormField, Message)
import Pre

-- | This request is used when an identity wants to recover their account.  We recommend reading the [Account Recovery Documentation](../self-service/flows/password-reset-account-recovery)
data RecoveryFlow = RecoveryFlow
  { -- | Active, if set, contains the registration method that is being used. It is initially not set.
    RecoveryFlow -> Maybe Text
active :: Maybe Text,
    -- | ExpiresAt is the time (UTC) when the request expires. If the user still wishes to update the setting, a new request has to be initiated.
    RecoveryFlow -> UTCTime
expires_at :: UTCTime,
    -- |
    RecoveryFlow -> UUID
id :: UUID,
    -- | IssuedAt is the time (UTC) when the request occurred.
    RecoveryFlow -> UTCTime
issued_at :: UTCTime,
    -- |
    RecoveryFlow -> Maybe [Message]
messages :: Maybe [Message],
    -- | Methods contains context for all account recovery methods. If a registration request has been processed, but for example the password is incorrect, this will contain error messages.
    RecoveryFlow -> RecoveryFlowMethods
methods :: RecoveryFlowMethods,
    -- | RequestURL is the initial URL that was requested from ORY Kratos. It can be used to forward information contained in the URL's path or query for example.
    RecoveryFlow -> Text
request_url :: Text,
    -- |
    RecoveryFlow -> Text
state :: Text,
    -- | The flow type can either be `api` or `browser`.
    RecoveryFlow -> Maybe Text
_type :: Maybe Text
  }
  deriving stock (Int -> RecoveryFlow -> ShowS
[RecoveryFlow] -> ShowS
RecoveryFlow -> String
(Int -> RecoveryFlow -> ShowS)
-> (RecoveryFlow -> String)
-> ([RecoveryFlow] -> ShowS)
-> Show RecoveryFlow
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RecoveryFlow] -> ShowS
$cshowList :: [RecoveryFlow] -> ShowS
show :: RecoveryFlow -> String
$cshow :: RecoveryFlow -> String
showsPrec :: Int -> RecoveryFlow -> ShowS
$cshowsPrec :: Int -> RecoveryFlow -> ShowS
Show, RecoveryFlow -> RecoveryFlow -> Bool
(RecoveryFlow -> RecoveryFlow -> Bool)
-> (RecoveryFlow -> RecoveryFlow -> Bool) -> Eq RecoveryFlow
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RecoveryFlow -> RecoveryFlow -> Bool
$c/= :: RecoveryFlow -> RecoveryFlow -> Bool
== :: RecoveryFlow -> RecoveryFlow -> Bool
$c== :: RecoveryFlow -> RecoveryFlow -> Bool
Eq, (forall x. RecoveryFlow -> Rep RecoveryFlow x)
-> (forall x. Rep RecoveryFlow x -> RecoveryFlow)
-> Generic RecoveryFlow
forall x. Rep RecoveryFlow x -> RecoveryFlow
forall x. RecoveryFlow -> Rep RecoveryFlow x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RecoveryFlow x -> RecoveryFlow
$cfrom :: forall x. RecoveryFlow -> Rep RecoveryFlow x
Generic, Typeable RecoveryFlow
DataType
Constr
Typeable RecoveryFlow
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> RecoveryFlow -> c RecoveryFlow)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c RecoveryFlow)
-> (RecoveryFlow -> Constr)
-> (RecoveryFlow -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c RecoveryFlow))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c RecoveryFlow))
-> ((forall b. Data b => b -> b) -> RecoveryFlow -> RecoveryFlow)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> RecoveryFlow -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> RecoveryFlow -> r)
-> (forall u. (forall d. Data d => d -> u) -> RecoveryFlow -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> RecoveryFlow -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> RecoveryFlow -> m RecoveryFlow)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> RecoveryFlow -> m RecoveryFlow)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> RecoveryFlow -> m RecoveryFlow)
-> Data RecoveryFlow
RecoveryFlow -> DataType
RecoveryFlow -> Constr
(forall b. Data b => b -> b) -> RecoveryFlow -> RecoveryFlow
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RecoveryFlow -> c RecoveryFlow
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RecoveryFlow
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) -> RecoveryFlow -> u
forall u. (forall d. Data d => d -> u) -> RecoveryFlow -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RecoveryFlow -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RecoveryFlow -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RecoveryFlow -> m RecoveryFlow
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RecoveryFlow -> m RecoveryFlow
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RecoveryFlow
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RecoveryFlow -> c RecoveryFlow
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RecoveryFlow)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RecoveryFlow)
$cRecoveryFlow :: Constr
$tRecoveryFlow :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> RecoveryFlow -> m RecoveryFlow
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RecoveryFlow -> m RecoveryFlow
gmapMp :: (forall d. Data d => d -> m d) -> RecoveryFlow -> m RecoveryFlow
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RecoveryFlow -> m RecoveryFlow
gmapM :: (forall d. Data d => d -> m d) -> RecoveryFlow -> m RecoveryFlow
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RecoveryFlow -> m RecoveryFlow
gmapQi :: Int -> (forall d. Data d => d -> u) -> RecoveryFlow -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RecoveryFlow -> u
gmapQ :: (forall d. Data d => d -> u) -> RecoveryFlow -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> RecoveryFlow -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RecoveryFlow -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RecoveryFlow -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RecoveryFlow -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RecoveryFlow -> r
gmapT :: (forall b. Data b => b -> b) -> RecoveryFlow -> RecoveryFlow
$cgmapT :: (forall b. Data b => b -> b) -> RecoveryFlow -> RecoveryFlow
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RecoveryFlow)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RecoveryFlow)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c RecoveryFlow)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RecoveryFlow)
dataTypeOf :: RecoveryFlow -> DataType
$cdataTypeOf :: RecoveryFlow -> DataType
toConstr :: RecoveryFlow -> Constr
$ctoConstr :: RecoveryFlow -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RecoveryFlow
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RecoveryFlow
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RecoveryFlow -> c RecoveryFlow
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RecoveryFlow -> c RecoveryFlow
$cp1Data :: Typeable RecoveryFlow
Data)

instance FromJSON RecoveryFlow where
  parseJSON :: Value -> Parser RecoveryFlow
parseJSON =
    Options -> Value -> Parser RecoveryFlow
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON
      Options
defaultOptions
        { constructorTagModifier :: ShowS
constructorTagModifier = ShowS
typeFieldRename,
          fieldLabelModifier :: ShowS
fieldLabelModifier = ShowS
typeFieldRename
        }

instance ToJSON RecoveryFlow where
  toEncoding :: RecoveryFlow -> Encoding
toEncoding =
    Options -> RecoveryFlow -> Encoding
forall a.
(Generic a, GToJSON' Encoding Zero (Rep a)) =>
Options -> a -> Encoding
genericToEncoding
      Options
defaultOptions
        { constructorTagModifier :: ShowS
constructorTagModifier = ShowS
typeFieldRename,
          fieldLabelModifier :: ShowS
fieldLabelModifier = ShowS
typeFieldRename
        }

-- |
data RecoveryFlowMethods = RecoveryFlowMethods
  { -- |
    RecoveryFlowMethods -> Maybe RecoveryFlowMethod
link :: Maybe RecoveryFlowMethod
  }
  deriving stock (Int -> RecoveryFlowMethods -> ShowS
[RecoveryFlowMethods] -> ShowS
RecoveryFlowMethods -> String
(Int -> RecoveryFlowMethods -> ShowS)
-> (RecoveryFlowMethods -> String)
-> ([RecoveryFlowMethods] -> ShowS)
-> Show RecoveryFlowMethods
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RecoveryFlowMethods] -> ShowS
$cshowList :: [RecoveryFlowMethods] -> ShowS
show :: RecoveryFlowMethods -> String
$cshow :: RecoveryFlowMethods -> String
showsPrec :: Int -> RecoveryFlowMethods -> ShowS
$cshowsPrec :: Int -> RecoveryFlowMethods -> ShowS
Show, RecoveryFlowMethods -> RecoveryFlowMethods -> Bool
(RecoveryFlowMethods -> RecoveryFlowMethods -> Bool)
-> (RecoveryFlowMethods -> RecoveryFlowMethods -> Bool)
-> Eq RecoveryFlowMethods
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RecoveryFlowMethods -> RecoveryFlowMethods -> Bool
$c/= :: RecoveryFlowMethods -> RecoveryFlowMethods -> Bool
== :: RecoveryFlowMethods -> RecoveryFlowMethods -> Bool
$c== :: RecoveryFlowMethods -> RecoveryFlowMethods -> Bool
Eq, (forall x. RecoveryFlowMethods -> Rep RecoveryFlowMethods x)
-> (forall x. Rep RecoveryFlowMethods x -> RecoveryFlowMethods)
-> Generic RecoveryFlowMethods
forall x. Rep RecoveryFlowMethods x -> RecoveryFlowMethods
forall x. RecoveryFlowMethods -> Rep RecoveryFlowMethods x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RecoveryFlowMethods x -> RecoveryFlowMethods
$cfrom :: forall x. RecoveryFlowMethods -> Rep RecoveryFlowMethods x
Generic, Typeable RecoveryFlowMethods
DataType
Constr
Typeable RecoveryFlowMethods
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g)
    -> RecoveryFlowMethods
    -> c RecoveryFlowMethods)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c RecoveryFlowMethods)
-> (RecoveryFlowMethods -> Constr)
-> (RecoveryFlowMethods -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c RecoveryFlowMethods))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c RecoveryFlowMethods))
-> ((forall b. Data b => b -> b)
    -> RecoveryFlowMethods -> RecoveryFlowMethods)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> RecoveryFlowMethods -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> RecoveryFlowMethods -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> RecoveryFlowMethods -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> RecoveryFlowMethods -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> RecoveryFlowMethods -> m RecoveryFlowMethods)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> RecoveryFlowMethods -> m RecoveryFlowMethods)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> RecoveryFlowMethods -> m RecoveryFlowMethods)
-> Data RecoveryFlowMethods
RecoveryFlowMethods -> DataType
RecoveryFlowMethods -> Constr
(forall b. Data b => b -> b)
-> RecoveryFlowMethods -> RecoveryFlowMethods
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> RecoveryFlowMethods
-> c RecoveryFlowMethods
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RecoveryFlowMethods
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) -> RecoveryFlowMethods -> u
forall u.
(forall d. Data d => d -> u) -> RecoveryFlowMethods -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RecoveryFlowMethods -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RecoveryFlowMethods -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> RecoveryFlowMethods -> m RecoveryFlowMethods
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> RecoveryFlowMethods -> m RecoveryFlowMethods
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RecoveryFlowMethods
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> RecoveryFlowMethods
-> c RecoveryFlowMethods
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RecoveryFlowMethods)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RecoveryFlowMethods)
$cRecoveryFlowMethods :: Constr
$tRecoveryFlowMethods :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> RecoveryFlowMethods -> m RecoveryFlowMethods
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> RecoveryFlowMethods -> m RecoveryFlowMethods
gmapMp :: (forall d. Data d => d -> m d)
-> RecoveryFlowMethods -> m RecoveryFlowMethods
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> RecoveryFlowMethods -> m RecoveryFlowMethods
gmapM :: (forall d. Data d => d -> m d)
-> RecoveryFlowMethods -> m RecoveryFlowMethods
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> RecoveryFlowMethods -> m RecoveryFlowMethods
gmapQi :: Int -> (forall d. Data d => d -> u) -> RecoveryFlowMethods -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> RecoveryFlowMethods -> u
gmapQ :: (forall d. Data d => d -> u) -> RecoveryFlowMethods -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> RecoveryFlowMethods -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RecoveryFlowMethods -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RecoveryFlowMethods -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RecoveryFlowMethods -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RecoveryFlowMethods -> r
gmapT :: (forall b. Data b => b -> b)
-> RecoveryFlowMethods -> RecoveryFlowMethods
$cgmapT :: (forall b. Data b => b -> b)
-> RecoveryFlowMethods -> RecoveryFlowMethods
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RecoveryFlowMethods)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RecoveryFlowMethods)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c RecoveryFlowMethods)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RecoveryFlowMethods)
dataTypeOf :: RecoveryFlowMethods -> DataType
$cdataTypeOf :: RecoveryFlowMethods -> DataType
toConstr :: RecoveryFlowMethods -> Constr
$ctoConstr :: RecoveryFlowMethods -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RecoveryFlowMethods
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RecoveryFlowMethods
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> RecoveryFlowMethods
-> c RecoveryFlowMethods
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> RecoveryFlowMethods
-> c RecoveryFlowMethods
$cp1Data :: Typeable RecoveryFlowMethods
Data)

instance FromJSON RecoveryFlowMethods

instance ToJSON RecoveryFlowMethods where
  toEncoding :: RecoveryFlowMethods -> Encoding
toEncoding = Options -> RecoveryFlowMethods -> Encoding
forall a.
(Generic a, GToJSON' Encoding Zero (Rep a)) =>
Options -> a -> Encoding
genericToEncoding Options
defaultOptions

-- |
data RecoveryFlowMethod = RecoveryFlowMethod
  { -- |
    RecoveryFlowMethod -> RecoveryFlowMethodConfig
config :: RecoveryFlowMethodConfig,
    -- | Method contains the request credentials type.
    RecoveryFlowMethod -> Text
method :: Text
  }
  deriving stock (Int -> RecoveryFlowMethod -> ShowS
[RecoveryFlowMethod] -> ShowS
RecoveryFlowMethod -> String
(Int -> RecoveryFlowMethod -> ShowS)
-> (RecoveryFlowMethod -> String)
-> ([RecoveryFlowMethod] -> ShowS)
-> Show RecoveryFlowMethod
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RecoveryFlowMethod] -> ShowS
$cshowList :: [RecoveryFlowMethod] -> ShowS
show :: RecoveryFlowMethod -> String
$cshow :: RecoveryFlowMethod -> String
showsPrec :: Int -> RecoveryFlowMethod -> ShowS
$cshowsPrec :: Int -> RecoveryFlowMethod -> ShowS
Show, RecoveryFlowMethod -> RecoveryFlowMethod -> Bool
(RecoveryFlowMethod -> RecoveryFlowMethod -> Bool)
-> (RecoveryFlowMethod -> RecoveryFlowMethod -> Bool)
-> Eq RecoveryFlowMethod
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RecoveryFlowMethod -> RecoveryFlowMethod -> Bool
$c/= :: RecoveryFlowMethod -> RecoveryFlowMethod -> Bool
== :: RecoveryFlowMethod -> RecoveryFlowMethod -> Bool
$c== :: RecoveryFlowMethod -> RecoveryFlowMethod -> Bool
Eq, (forall x. RecoveryFlowMethod -> Rep RecoveryFlowMethod x)
-> (forall x. Rep RecoveryFlowMethod x -> RecoveryFlowMethod)
-> Generic RecoveryFlowMethod
forall x. Rep RecoveryFlowMethod x -> RecoveryFlowMethod
forall x. RecoveryFlowMethod -> Rep RecoveryFlowMethod x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RecoveryFlowMethod x -> RecoveryFlowMethod
$cfrom :: forall x. RecoveryFlowMethod -> Rep RecoveryFlowMethod x
Generic, Typeable RecoveryFlowMethod
DataType
Constr
Typeable RecoveryFlowMethod
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g)
    -> RecoveryFlowMethod
    -> c RecoveryFlowMethod)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c RecoveryFlowMethod)
-> (RecoveryFlowMethod -> Constr)
-> (RecoveryFlowMethod -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c RecoveryFlowMethod))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c RecoveryFlowMethod))
-> ((forall b. Data b => b -> b)
    -> RecoveryFlowMethod -> RecoveryFlowMethod)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> RecoveryFlowMethod -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> RecoveryFlowMethod -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> RecoveryFlowMethod -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> RecoveryFlowMethod -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> RecoveryFlowMethod -> m RecoveryFlowMethod)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> RecoveryFlowMethod -> m RecoveryFlowMethod)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> RecoveryFlowMethod -> m RecoveryFlowMethod)
-> Data RecoveryFlowMethod
RecoveryFlowMethod -> DataType
RecoveryFlowMethod -> Constr
(forall b. Data b => b -> b)
-> RecoveryFlowMethod -> RecoveryFlowMethod
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> RecoveryFlowMethod
-> c RecoveryFlowMethod
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RecoveryFlowMethod
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) -> RecoveryFlowMethod -> u
forall u. (forall d. Data d => d -> u) -> RecoveryFlowMethod -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RecoveryFlowMethod -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RecoveryFlowMethod -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> RecoveryFlowMethod -> m RecoveryFlowMethod
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> RecoveryFlowMethod -> m RecoveryFlowMethod
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RecoveryFlowMethod
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> RecoveryFlowMethod
-> c RecoveryFlowMethod
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RecoveryFlowMethod)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RecoveryFlowMethod)
$cRecoveryFlowMethod :: Constr
$tRecoveryFlowMethod :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> RecoveryFlowMethod -> m RecoveryFlowMethod
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> RecoveryFlowMethod -> m RecoveryFlowMethod
gmapMp :: (forall d. Data d => d -> m d)
-> RecoveryFlowMethod -> m RecoveryFlowMethod
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> RecoveryFlowMethod -> m RecoveryFlowMethod
gmapM :: (forall d. Data d => d -> m d)
-> RecoveryFlowMethod -> m RecoveryFlowMethod
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> RecoveryFlowMethod -> m RecoveryFlowMethod
gmapQi :: Int -> (forall d. Data d => d -> u) -> RecoveryFlowMethod -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> RecoveryFlowMethod -> u
gmapQ :: (forall d. Data d => d -> u) -> RecoveryFlowMethod -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> RecoveryFlowMethod -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RecoveryFlowMethod -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RecoveryFlowMethod -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RecoveryFlowMethod -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RecoveryFlowMethod -> r
gmapT :: (forall b. Data b => b -> b)
-> RecoveryFlowMethod -> RecoveryFlowMethod
$cgmapT :: (forall b. Data b => b -> b)
-> RecoveryFlowMethod -> RecoveryFlowMethod
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RecoveryFlowMethod)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RecoveryFlowMethod)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c RecoveryFlowMethod)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RecoveryFlowMethod)
dataTypeOf :: RecoveryFlowMethod -> DataType
$cdataTypeOf :: RecoveryFlowMethod -> DataType
toConstr :: RecoveryFlowMethod -> Constr
$ctoConstr :: RecoveryFlowMethod -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RecoveryFlowMethod
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RecoveryFlowMethod
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> RecoveryFlowMethod
-> c RecoveryFlowMethod
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> RecoveryFlowMethod
-> c RecoveryFlowMethod
$cp1Data :: Typeable RecoveryFlowMethod
Data)

instance FromJSON RecoveryFlowMethod

instance ToJSON RecoveryFlowMethod where
  toEncoding :: RecoveryFlowMethod -> Encoding
toEncoding = Options -> RecoveryFlowMethod -> Encoding
forall a.
(Generic a, GToJSON' Encoding Zero (Rep a)) =>
Options -> a -> Encoding
genericToEncoding Options
defaultOptions

-- |
data RecoveryFlowMethodConfig = RecoveryFlowMethodConfig
  { -- | Action should be used as the form action URL `<form action=\"{{ .Action }}\" method=\"post\">`.
    RecoveryFlowMethodConfig -> Text
action :: Text,
    -- | Fields contains multiple fields
    RecoveryFlowMethodConfig -> [FormField]
fields :: [FormField],
    -- |
    RecoveryFlowMethodConfig -> Maybe [Message]
messages :: Maybe [Message],
    -- | Method is the form method (e.g. POST)
    RecoveryFlowMethodConfig -> Text
method :: Text
  }
  deriving stock (Int -> RecoveryFlowMethodConfig -> ShowS
[RecoveryFlowMethodConfig] -> ShowS
RecoveryFlowMethodConfig -> String
(Int -> RecoveryFlowMethodConfig -> ShowS)
-> (RecoveryFlowMethodConfig -> String)
-> ([RecoveryFlowMethodConfig] -> ShowS)
-> Show RecoveryFlowMethodConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RecoveryFlowMethodConfig] -> ShowS
$cshowList :: [RecoveryFlowMethodConfig] -> ShowS
show :: RecoveryFlowMethodConfig -> String
$cshow :: RecoveryFlowMethodConfig -> String
showsPrec :: Int -> RecoveryFlowMethodConfig -> ShowS
$cshowsPrec :: Int -> RecoveryFlowMethodConfig -> ShowS
Show, RecoveryFlowMethodConfig -> RecoveryFlowMethodConfig -> Bool
(RecoveryFlowMethodConfig -> RecoveryFlowMethodConfig -> Bool)
-> (RecoveryFlowMethodConfig -> RecoveryFlowMethodConfig -> Bool)
-> Eq RecoveryFlowMethodConfig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RecoveryFlowMethodConfig -> RecoveryFlowMethodConfig -> Bool
$c/= :: RecoveryFlowMethodConfig -> RecoveryFlowMethodConfig -> Bool
== :: RecoveryFlowMethodConfig -> RecoveryFlowMethodConfig -> Bool
$c== :: RecoveryFlowMethodConfig -> RecoveryFlowMethodConfig -> Bool
Eq, (forall x.
 RecoveryFlowMethodConfig -> Rep RecoveryFlowMethodConfig x)
-> (forall x.
    Rep RecoveryFlowMethodConfig x -> RecoveryFlowMethodConfig)
-> Generic RecoveryFlowMethodConfig
forall x.
Rep RecoveryFlowMethodConfig x -> RecoveryFlowMethodConfig
forall x.
RecoveryFlowMethodConfig -> Rep RecoveryFlowMethodConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep RecoveryFlowMethodConfig x -> RecoveryFlowMethodConfig
$cfrom :: forall x.
RecoveryFlowMethodConfig -> Rep RecoveryFlowMethodConfig x
Generic, Typeable RecoveryFlowMethodConfig
DataType
Constr
Typeable RecoveryFlowMethodConfig
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g)
    -> RecoveryFlowMethodConfig
    -> c RecoveryFlowMethodConfig)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c RecoveryFlowMethodConfig)
-> (RecoveryFlowMethodConfig -> Constr)
-> (RecoveryFlowMethodConfig -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d))
    -> Maybe (c RecoveryFlowMethodConfig))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c RecoveryFlowMethodConfig))
-> ((forall b. Data b => b -> b)
    -> RecoveryFlowMethodConfig -> RecoveryFlowMethodConfig)
-> (forall r r'.
    (r -> r' -> r)
    -> r
    -> (forall d. Data d => d -> r')
    -> RecoveryFlowMethodConfig
    -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r
    -> (forall d. Data d => d -> r')
    -> RecoveryFlowMethodConfig
    -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> RecoveryFlowMethodConfig -> [u])
-> (forall u.
    Int
    -> (forall d. Data d => d -> u) -> RecoveryFlowMethodConfig -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> RecoveryFlowMethodConfig -> m RecoveryFlowMethodConfig)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> RecoveryFlowMethodConfig -> m RecoveryFlowMethodConfig)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> RecoveryFlowMethodConfig -> m RecoveryFlowMethodConfig)
-> Data RecoveryFlowMethodConfig
RecoveryFlowMethodConfig -> DataType
RecoveryFlowMethodConfig -> Constr
(forall b. Data b => b -> b)
-> RecoveryFlowMethodConfig -> RecoveryFlowMethodConfig
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> RecoveryFlowMethodConfig
-> c RecoveryFlowMethodConfig
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RecoveryFlowMethodConfig
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) -> RecoveryFlowMethodConfig -> u
forall u.
(forall d. Data d => d -> u) -> RecoveryFlowMethodConfig -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> RecoveryFlowMethodConfig
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> RecoveryFlowMethodConfig
-> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> RecoveryFlowMethodConfig -> m RecoveryFlowMethodConfig
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> RecoveryFlowMethodConfig -> m RecoveryFlowMethodConfig
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RecoveryFlowMethodConfig
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> RecoveryFlowMethodConfig
-> c RecoveryFlowMethodConfig
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RecoveryFlowMethodConfig)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RecoveryFlowMethodConfig)
$cRecoveryFlowMethodConfig :: Constr
$tRecoveryFlowMethodConfig :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> RecoveryFlowMethodConfig -> m RecoveryFlowMethodConfig
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> RecoveryFlowMethodConfig -> m RecoveryFlowMethodConfig
gmapMp :: (forall d. Data d => d -> m d)
-> RecoveryFlowMethodConfig -> m RecoveryFlowMethodConfig
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> RecoveryFlowMethodConfig -> m RecoveryFlowMethodConfig
gmapM :: (forall d. Data d => d -> m d)
-> RecoveryFlowMethodConfig -> m RecoveryFlowMethodConfig
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> RecoveryFlowMethodConfig -> m RecoveryFlowMethodConfig
gmapQi :: Int
-> (forall d. Data d => d -> u) -> RecoveryFlowMethodConfig -> u
$cgmapQi :: forall u.
Int
-> (forall d. Data d => d -> u) -> RecoveryFlowMethodConfig -> u
gmapQ :: (forall d. Data d => d -> u) -> RecoveryFlowMethodConfig -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> RecoveryFlowMethodConfig -> [u]
gmapQr :: (r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> RecoveryFlowMethodConfig
-> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> RecoveryFlowMethodConfig
-> r
gmapQl :: (r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> RecoveryFlowMethodConfig
-> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> RecoveryFlowMethodConfig
-> r
gmapT :: (forall b. Data b => b -> b)
-> RecoveryFlowMethodConfig -> RecoveryFlowMethodConfig
$cgmapT :: (forall b. Data b => b -> b)
-> RecoveryFlowMethodConfig -> RecoveryFlowMethodConfig
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RecoveryFlowMethodConfig)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RecoveryFlowMethodConfig)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c RecoveryFlowMethodConfig)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RecoveryFlowMethodConfig)
dataTypeOf :: RecoveryFlowMethodConfig -> DataType
$cdataTypeOf :: RecoveryFlowMethodConfig -> DataType
toConstr :: RecoveryFlowMethodConfig -> Constr
$ctoConstr :: RecoveryFlowMethodConfig -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RecoveryFlowMethodConfig
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RecoveryFlowMethodConfig
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> RecoveryFlowMethodConfig
-> c RecoveryFlowMethodConfig
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> RecoveryFlowMethodConfig
-> c RecoveryFlowMethodConfig
$cp1Data :: Typeable RecoveryFlowMethodConfig
Data)

instance FromJSON RecoveryFlowMethodConfig

instance ToJSON RecoveryFlowMethodConfig where
  toEncoding :: RecoveryFlowMethodConfig -> Encoding
toEncoding = Options -> RecoveryFlowMethodConfig -> Encoding
forall a.
(Generic a, GToJSON' Encoding Zero (Rep a)) =>
Options -> a -> Encoding
genericToEncoding Options
defaultOptions

-- |
data RecoveryLink = RecoveryLink
  { -- | Recovery Link Expires At  The timestamp when the recovery link expires.
    RecoveryLink -> Maybe UTCTime
expires_at :: Maybe UTCTime,
    -- | Recovery Link  This link can be used to recover the account.
    RecoveryLink -> Text
recovery_link :: Text
  }
  deriving stock (Int -> RecoveryLink -> ShowS
[RecoveryLink] -> ShowS
RecoveryLink -> String
(Int -> RecoveryLink -> ShowS)
-> (RecoveryLink -> String)
-> ([RecoveryLink] -> ShowS)
-> Show RecoveryLink
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RecoveryLink] -> ShowS
$cshowList :: [RecoveryLink] -> ShowS
show :: RecoveryLink -> String
$cshow :: RecoveryLink -> String
showsPrec :: Int -> RecoveryLink -> ShowS
$cshowsPrec :: Int -> RecoveryLink -> ShowS
Show, RecoveryLink -> RecoveryLink -> Bool
(RecoveryLink -> RecoveryLink -> Bool)
-> (RecoveryLink -> RecoveryLink -> Bool) -> Eq RecoveryLink
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RecoveryLink -> RecoveryLink -> Bool
$c/= :: RecoveryLink -> RecoveryLink -> Bool
== :: RecoveryLink -> RecoveryLink -> Bool
$c== :: RecoveryLink -> RecoveryLink -> Bool
Eq, (forall x. RecoveryLink -> Rep RecoveryLink x)
-> (forall x. Rep RecoveryLink x -> RecoveryLink)
-> Generic RecoveryLink
forall x. Rep RecoveryLink x -> RecoveryLink
forall x. RecoveryLink -> Rep RecoveryLink x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RecoveryLink x -> RecoveryLink
$cfrom :: forall x. RecoveryLink -> Rep RecoveryLink x
Generic, Typeable RecoveryLink
DataType
Constr
Typeable RecoveryLink
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> RecoveryLink -> c RecoveryLink)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c RecoveryLink)
-> (RecoveryLink -> Constr)
-> (RecoveryLink -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c RecoveryLink))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c RecoveryLink))
-> ((forall b. Data b => b -> b) -> RecoveryLink -> RecoveryLink)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> RecoveryLink -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> RecoveryLink -> r)
-> (forall u. (forall d. Data d => d -> u) -> RecoveryLink -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> RecoveryLink -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> RecoveryLink -> m RecoveryLink)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> RecoveryLink -> m RecoveryLink)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> RecoveryLink -> m RecoveryLink)
-> Data RecoveryLink
RecoveryLink -> DataType
RecoveryLink -> Constr
(forall b. Data b => b -> b) -> RecoveryLink -> RecoveryLink
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RecoveryLink -> c RecoveryLink
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RecoveryLink
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) -> RecoveryLink -> u
forall u. (forall d. Data d => d -> u) -> RecoveryLink -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RecoveryLink -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RecoveryLink -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RecoveryLink -> m RecoveryLink
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RecoveryLink -> m RecoveryLink
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RecoveryLink
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RecoveryLink -> c RecoveryLink
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RecoveryLink)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RecoveryLink)
$cRecoveryLink :: Constr
$tRecoveryLink :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> RecoveryLink -> m RecoveryLink
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RecoveryLink -> m RecoveryLink
gmapMp :: (forall d. Data d => d -> m d) -> RecoveryLink -> m RecoveryLink
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RecoveryLink -> m RecoveryLink
gmapM :: (forall d. Data d => d -> m d) -> RecoveryLink -> m RecoveryLink
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RecoveryLink -> m RecoveryLink
gmapQi :: Int -> (forall d. Data d => d -> u) -> RecoveryLink -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RecoveryLink -> u
gmapQ :: (forall d. Data d => d -> u) -> RecoveryLink -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> RecoveryLink -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RecoveryLink -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RecoveryLink -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RecoveryLink -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RecoveryLink -> r
gmapT :: (forall b. Data b => b -> b) -> RecoveryLink -> RecoveryLink
$cgmapT :: (forall b. Data b => b -> b) -> RecoveryLink -> RecoveryLink
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RecoveryLink)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RecoveryLink)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c RecoveryLink)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RecoveryLink)
dataTypeOf :: RecoveryLink -> DataType
$cdataTypeOf :: RecoveryLink -> DataType
toConstr :: RecoveryLink -> Constr
$ctoConstr :: RecoveryLink -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RecoveryLink
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RecoveryLink
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RecoveryLink -> c RecoveryLink
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RecoveryLink -> c RecoveryLink
$cp1Data :: Typeable RecoveryLink
Data)

instance FromJSON RecoveryLink

instance ToJSON RecoveryLink where
  toEncoding :: RecoveryLink -> Encoding
toEncoding = Options -> RecoveryLink -> Encoding
forall a.
(Generic a, GToJSON' Encoding Zero (Rep a)) =>
Options -> a -> Encoding
genericToEncoding Options
defaultOptions