module OryKratos.Types.Registration
  ( RegistrationFlow (..),
    RegistrationFlowMethods (..),
    RegistrationFlowMethod (..),
    RegistrationFlowMethodConfig (..),
    RegistrationViaApiResponse (..),
  )
where

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

-- |
data RegistrationFlow = RegistrationFlow
  { -- | and so on.
    RegistrationFlow -> Maybe Text
active :: Maybe Text,
    -- | ExpiresAt is the time (UTC) when the flow expires. If the user still wishes to log in, a new flow has to be initiated.
    RegistrationFlow -> UTCTime
expires_at :: UTCTime,
    -- |
    RegistrationFlow -> UUID
id :: UUID,
    -- | IssuedAt is the time (UTC) when the flow occurred.
    RegistrationFlow -> UTCTime
issued_at :: UTCTime,
    -- |
    RegistrationFlow -> Maybe [Message]
messages :: Maybe [Message],
    -- | Methods contains context for all enabled registration methods. If a registration flow has been processed, but for example the password is incorrect, this will contain error messages.
    RegistrationFlow -> RegistrationFlowMethods
methods :: RegistrationFlowMethods,
    -- | 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.
    RegistrationFlow -> Text
request_url :: Text,
    -- | The flow type can either be `api` or `browser`.
    RegistrationFlow -> Maybe Text
_type :: Maybe Text
  }
  deriving stock (Int -> RegistrationFlow -> ShowS
[RegistrationFlow] -> ShowS
RegistrationFlow -> String
(Int -> RegistrationFlow -> ShowS)
-> (RegistrationFlow -> String)
-> ([RegistrationFlow] -> ShowS)
-> Show RegistrationFlow
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RegistrationFlow] -> ShowS
$cshowList :: [RegistrationFlow] -> ShowS
show :: RegistrationFlow -> String
$cshow :: RegistrationFlow -> String
showsPrec :: Int -> RegistrationFlow -> ShowS
$cshowsPrec :: Int -> RegistrationFlow -> ShowS
Show, RegistrationFlow -> RegistrationFlow -> Bool
(RegistrationFlow -> RegistrationFlow -> Bool)
-> (RegistrationFlow -> RegistrationFlow -> Bool)
-> Eq RegistrationFlow
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RegistrationFlow -> RegistrationFlow -> Bool
$c/= :: RegistrationFlow -> RegistrationFlow -> Bool
== :: RegistrationFlow -> RegistrationFlow -> Bool
$c== :: RegistrationFlow -> RegistrationFlow -> Bool
Eq, (forall x. RegistrationFlow -> Rep RegistrationFlow x)
-> (forall x. Rep RegistrationFlow x -> RegistrationFlow)
-> Generic RegistrationFlow
forall x. Rep RegistrationFlow x -> RegistrationFlow
forall x. RegistrationFlow -> Rep RegistrationFlow x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RegistrationFlow x -> RegistrationFlow
$cfrom :: forall x. RegistrationFlow -> Rep RegistrationFlow x
Generic, Typeable RegistrationFlow
DataType
Constr
Typeable RegistrationFlow
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> RegistrationFlow -> c RegistrationFlow)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c RegistrationFlow)
-> (RegistrationFlow -> Constr)
-> (RegistrationFlow -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c RegistrationFlow))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c RegistrationFlow))
-> ((forall b. Data b => b -> b)
    -> RegistrationFlow -> RegistrationFlow)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> RegistrationFlow -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> RegistrationFlow -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> RegistrationFlow -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> RegistrationFlow -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> RegistrationFlow -> m RegistrationFlow)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> RegistrationFlow -> m RegistrationFlow)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> RegistrationFlow -> m RegistrationFlow)
-> Data RegistrationFlow
RegistrationFlow -> DataType
RegistrationFlow -> Constr
(forall b. Data b => b -> b)
-> RegistrationFlow -> RegistrationFlow
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RegistrationFlow -> c RegistrationFlow
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RegistrationFlow
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) -> RegistrationFlow -> u
forall u. (forall d. Data d => d -> u) -> RegistrationFlow -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RegistrationFlow -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RegistrationFlow -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> RegistrationFlow -> m RegistrationFlow
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> RegistrationFlow -> m RegistrationFlow
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RegistrationFlow
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RegistrationFlow -> c RegistrationFlow
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RegistrationFlow)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RegistrationFlow)
$cRegistrationFlow :: Constr
$tRegistrationFlow :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> RegistrationFlow -> m RegistrationFlow
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> RegistrationFlow -> m RegistrationFlow
gmapMp :: (forall d. Data d => d -> m d)
-> RegistrationFlow -> m RegistrationFlow
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> RegistrationFlow -> m RegistrationFlow
gmapM :: (forall d. Data d => d -> m d)
-> RegistrationFlow -> m RegistrationFlow
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> RegistrationFlow -> m RegistrationFlow
gmapQi :: Int -> (forall d. Data d => d -> u) -> RegistrationFlow -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> RegistrationFlow -> u
gmapQ :: (forall d. Data d => d -> u) -> RegistrationFlow -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> RegistrationFlow -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RegistrationFlow -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RegistrationFlow -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RegistrationFlow -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RegistrationFlow -> r
gmapT :: (forall b. Data b => b -> b)
-> RegistrationFlow -> RegistrationFlow
$cgmapT :: (forall b. Data b => b -> b)
-> RegistrationFlow -> RegistrationFlow
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RegistrationFlow)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RegistrationFlow)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c RegistrationFlow)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RegistrationFlow)
dataTypeOf :: RegistrationFlow -> DataType
$cdataTypeOf :: RegistrationFlow -> DataType
toConstr :: RegistrationFlow -> Constr
$ctoConstr :: RegistrationFlow -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RegistrationFlow
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RegistrationFlow
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RegistrationFlow -> c RegistrationFlow
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RegistrationFlow -> c RegistrationFlow
$cp1Data :: Typeable RegistrationFlow
Data)

instance FromJSON RegistrationFlow where
  parseJSON :: Value -> Parser RegistrationFlow
parseJSON =
    Options -> Value -> Parser RegistrationFlow
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 RegistrationFlow where
  toEncoding :: RegistrationFlow -> Encoding
toEncoding =
    Options -> RegistrationFlow -> 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 RegistrationFlowMethods = RegistrationFlowMethods
  { -- |
    RegistrationFlowMethods -> Maybe RegistrationFlowMethod
password :: Maybe RegistrationFlowMethod,
    -- | and so on.
    RegistrationFlowMethods -> Maybe RegistrationFlowMethod
oidc :: Maybe RegistrationFlowMethod
  }
  deriving stock (Int -> RegistrationFlowMethods -> ShowS
[RegistrationFlowMethods] -> ShowS
RegistrationFlowMethods -> String
(Int -> RegistrationFlowMethods -> ShowS)
-> (RegistrationFlowMethods -> String)
-> ([RegistrationFlowMethods] -> ShowS)
-> Show RegistrationFlowMethods
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RegistrationFlowMethods] -> ShowS
$cshowList :: [RegistrationFlowMethods] -> ShowS
show :: RegistrationFlowMethods -> String
$cshow :: RegistrationFlowMethods -> String
showsPrec :: Int -> RegistrationFlowMethods -> ShowS
$cshowsPrec :: Int -> RegistrationFlowMethods -> ShowS
Show, RegistrationFlowMethods -> RegistrationFlowMethods -> Bool
(RegistrationFlowMethods -> RegistrationFlowMethods -> Bool)
-> (RegistrationFlowMethods -> RegistrationFlowMethods -> Bool)
-> Eq RegistrationFlowMethods
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RegistrationFlowMethods -> RegistrationFlowMethods -> Bool
$c/= :: RegistrationFlowMethods -> RegistrationFlowMethods -> Bool
== :: RegistrationFlowMethods -> RegistrationFlowMethods -> Bool
$c== :: RegistrationFlowMethods -> RegistrationFlowMethods -> Bool
Eq, (forall x.
 RegistrationFlowMethods -> Rep RegistrationFlowMethods x)
-> (forall x.
    Rep RegistrationFlowMethods x -> RegistrationFlowMethods)
-> Generic RegistrationFlowMethods
forall x. Rep RegistrationFlowMethods x -> RegistrationFlowMethods
forall x. RegistrationFlowMethods -> Rep RegistrationFlowMethods x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RegistrationFlowMethods x -> RegistrationFlowMethods
$cfrom :: forall x. RegistrationFlowMethods -> Rep RegistrationFlowMethods x
Generic, Typeable RegistrationFlowMethods
DataType
Constr
Typeable RegistrationFlowMethods
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g)
    -> RegistrationFlowMethods
    -> c RegistrationFlowMethods)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c RegistrationFlowMethods)
-> (RegistrationFlowMethods -> Constr)
-> (RegistrationFlowMethods -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c RegistrationFlowMethods))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c RegistrationFlowMethods))
-> ((forall b. Data b => b -> b)
    -> RegistrationFlowMethods -> RegistrationFlowMethods)
-> (forall r r'.
    (r -> r' -> r)
    -> r
    -> (forall d. Data d => d -> r')
    -> RegistrationFlowMethods
    -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r
    -> (forall d. Data d => d -> r')
    -> RegistrationFlowMethods
    -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> RegistrationFlowMethods -> [u])
-> (forall u.
    Int
    -> (forall d. Data d => d -> u) -> RegistrationFlowMethods -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> RegistrationFlowMethods -> m RegistrationFlowMethods)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> RegistrationFlowMethods -> m RegistrationFlowMethods)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> RegistrationFlowMethods -> m RegistrationFlowMethods)
-> Data RegistrationFlowMethods
RegistrationFlowMethods -> DataType
RegistrationFlowMethods -> Constr
(forall b. Data b => b -> b)
-> RegistrationFlowMethods -> RegistrationFlowMethods
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> RegistrationFlowMethods
-> c RegistrationFlowMethods
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RegistrationFlowMethods
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) -> RegistrationFlowMethods -> u
forall u.
(forall d. Data d => d -> u) -> RegistrationFlowMethods -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> RegistrationFlowMethods
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> RegistrationFlowMethods
-> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> RegistrationFlowMethods -> m RegistrationFlowMethods
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> RegistrationFlowMethods -> m RegistrationFlowMethods
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RegistrationFlowMethods
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> RegistrationFlowMethods
-> c RegistrationFlowMethods
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RegistrationFlowMethods)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RegistrationFlowMethods)
$cRegistrationFlowMethods :: Constr
$tRegistrationFlowMethods :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> RegistrationFlowMethods -> m RegistrationFlowMethods
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> RegistrationFlowMethods -> m RegistrationFlowMethods
gmapMp :: (forall d. Data d => d -> m d)
-> RegistrationFlowMethods -> m RegistrationFlowMethods
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> RegistrationFlowMethods -> m RegistrationFlowMethods
gmapM :: (forall d. Data d => d -> m d)
-> RegistrationFlowMethods -> m RegistrationFlowMethods
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> RegistrationFlowMethods -> m RegistrationFlowMethods
gmapQi :: Int -> (forall d. Data d => d -> u) -> RegistrationFlowMethods -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> RegistrationFlowMethods -> u
gmapQ :: (forall d. Data d => d -> u) -> RegistrationFlowMethods -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> RegistrationFlowMethods -> [u]
gmapQr :: (r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> RegistrationFlowMethods
-> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> RegistrationFlowMethods
-> r
gmapQl :: (r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> RegistrationFlowMethods
-> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> RegistrationFlowMethods
-> r
gmapT :: (forall b. Data b => b -> b)
-> RegistrationFlowMethods -> RegistrationFlowMethods
$cgmapT :: (forall b. Data b => b -> b)
-> RegistrationFlowMethods -> RegistrationFlowMethods
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RegistrationFlowMethods)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RegistrationFlowMethods)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c RegistrationFlowMethods)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RegistrationFlowMethods)
dataTypeOf :: RegistrationFlowMethods -> DataType
$cdataTypeOf :: RegistrationFlowMethods -> DataType
toConstr :: RegistrationFlowMethods -> Constr
$ctoConstr :: RegistrationFlowMethods -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RegistrationFlowMethods
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RegistrationFlowMethods
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> RegistrationFlowMethods
-> c RegistrationFlowMethods
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> RegistrationFlowMethods
-> c RegistrationFlowMethods
$cp1Data :: Typeable RegistrationFlowMethods
Data)

instance FromJSON RegistrationFlowMethods

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

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

instance FromJSON RegistrationFlowMethod

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

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

instance FromJSON RegistrationFlowMethodConfig

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

-- | The Response for Registration Flows via API
data RegistrationViaApiResponse = RegistrationViaApiResponse
  { -- |
    RegistrationViaApiResponse -> Identity
identity :: Identity,
    -- |
    RegistrationViaApiResponse -> Maybe Session
session :: Maybe Session,
    -- | The Session Token  This field is only set when the session hook is configured as a post-registration hook.  A session token is equivalent to a session cookie, but it can be sent in the HTTP Authorization Header:  Authorization: bearer ${session-token}  The session token is only issued for API flows, not for Browser flows!
    RegistrationViaApiResponse -> Text
session_token :: Text
  }
  deriving stock (Int -> RegistrationViaApiResponse -> ShowS
[RegistrationViaApiResponse] -> ShowS
RegistrationViaApiResponse -> String
(Int -> RegistrationViaApiResponse -> ShowS)
-> (RegistrationViaApiResponse -> String)
-> ([RegistrationViaApiResponse] -> ShowS)
-> Show RegistrationViaApiResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RegistrationViaApiResponse] -> ShowS
$cshowList :: [RegistrationViaApiResponse] -> ShowS
show :: RegistrationViaApiResponse -> String
$cshow :: RegistrationViaApiResponse -> String
showsPrec :: Int -> RegistrationViaApiResponse -> ShowS
$cshowsPrec :: Int -> RegistrationViaApiResponse -> ShowS
Show, RegistrationViaApiResponse -> RegistrationViaApiResponse -> Bool
(RegistrationViaApiResponse -> RegistrationViaApiResponse -> Bool)
-> (RegistrationViaApiResponse
    -> RegistrationViaApiResponse -> Bool)
-> Eq RegistrationViaApiResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RegistrationViaApiResponse -> RegistrationViaApiResponse -> Bool
$c/= :: RegistrationViaApiResponse -> RegistrationViaApiResponse -> Bool
== :: RegistrationViaApiResponse -> RegistrationViaApiResponse -> Bool
$c== :: RegistrationViaApiResponse -> RegistrationViaApiResponse -> Bool
Eq, (forall x.
 RegistrationViaApiResponse -> Rep RegistrationViaApiResponse x)
-> (forall x.
    Rep RegistrationViaApiResponse x -> RegistrationViaApiResponse)
-> Generic RegistrationViaApiResponse
forall x.
Rep RegistrationViaApiResponse x -> RegistrationViaApiResponse
forall x.
RegistrationViaApiResponse -> Rep RegistrationViaApiResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep RegistrationViaApiResponse x -> RegistrationViaApiResponse
$cfrom :: forall x.
RegistrationViaApiResponse -> Rep RegistrationViaApiResponse x
Generic, Typeable RegistrationViaApiResponse
DataType
Constr
Typeable RegistrationViaApiResponse
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g)
    -> RegistrationViaApiResponse
    -> c RegistrationViaApiResponse)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c RegistrationViaApiResponse)
-> (RegistrationViaApiResponse -> Constr)
-> (RegistrationViaApiResponse -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d))
    -> Maybe (c RegistrationViaApiResponse))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c RegistrationViaApiResponse))
-> ((forall b. Data b => b -> b)
    -> RegistrationViaApiResponse -> RegistrationViaApiResponse)
-> (forall r r'.
    (r -> r' -> r)
    -> r
    -> (forall d. Data d => d -> r')
    -> RegistrationViaApiResponse
    -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r
    -> (forall d. Data d => d -> r')
    -> RegistrationViaApiResponse
    -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> RegistrationViaApiResponse -> [u])
-> (forall u.
    Int
    -> (forall d. Data d => d -> u) -> RegistrationViaApiResponse -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> RegistrationViaApiResponse -> m RegistrationViaApiResponse)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> RegistrationViaApiResponse -> m RegistrationViaApiResponse)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> RegistrationViaApiResponse -> m RegistrationViaApiResponse)
-> Data RegistrationViaApiResponse
RegistrationViaApiResponse -> DataType
RegistrationViaApiResponse -> Constr
(forall b. Data b => b -> b)
-> RegistrationViaApiResponse -> RegistrationViaApiResponse
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> RegistrationViaApiResponse
-> c RegistrationViaApiResponse
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RegistrationViaApiResponse
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) -> RegistrationViaApiResponse -> u
forall u.
(forall d. Data d => d -> u) -> RegistrationViaApiResponse -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> RegistrationViaApiResponse
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> RegistrationViaApiResponse
-> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> RegistrationViaApiResponse -> m RegistrationViaApiResponse
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> RegistrationViaApiResponse -> m RegistrationViaApiResponse
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RegistrationViaApiResponse
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> RegistrationViaApiResponse
-> c RegistrationViaApiResponse
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c RegistrationViaApiResponse)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RegistrationViaApiResponse)
$cRegistrationViaApiResponse :: Constr
$tRegistrationViaApiResponse :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> RegistrationViaApiResponse -> m RegistrationViaApiResponse
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> RegistrationViaApiResponse -> m RegistrationViaApiResponse
gmapMp :: (forall d. Data d => d -> m d)
-> RegistrationViaApiResponse -> m RegistrationViaApiResponse
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> RegistrationViaApiResponse -> m RegistrationViaApiResponse
gmapM :: (forall d. Data d => d -> m d)
-> RegistrationViaApiResponse -> m RegistrationViaApiResponse
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> RegistrationViaApiResponse -> m RegistrationViaApiResponse
gmapQi :: Int
-> (forall d. Data d => d -> u) -> RegistrationViaApiResponse -> u
$cgmapQi :: forall u.
Int
-> (forall d. Data d => d -> u) -> RegistrationViaApiResponse -> u
gmapQ :: (forall d. Data d => d -> u) -> RegistrationViaApiResponse -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> RegistrationViaApiResponse -> [u]
gmapQr :: (r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> RegistrationViaApiResponse
-> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> RegistrationViaApiResponse
-> r
gmapQl :: (r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> RegistrationViaApiResponse
-> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> RegistrationViaApiResponse
-> r
gmapT :: (forall b. Data b => b -> b)
-> RegistrationViaApiResponse -> RegistrationViaApiResponse
$cgmapT :: (forall b. Data b => b -> b)
-> RegistrationViaApiResponse -> RegistrationViaApiResponse
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RegistrationViaApiResponse)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RegistrationViaApiResponse)
dataCast1 :: (forall d. Data d => c (t d))
-> Maybe (c RegistrationViaApiResponse)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c RegistrationViaApiResponse)
dataTypeOf :: RegistrationViaApiResponse -> DataType
$cdataTypeOf :: RegistrationViaApiResponse -> DataType
toConstr :: RegistrationViaApiResponse -> Constr
$ctoConstr :: RegistrationViaApiResponse -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RegistrationViaApiResponse
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RegistrationViaApiResponse
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> RegistrationViaApiResponse
-> c RegistrationViaApiResponse
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> RegistrationViaApiResponse
-> c RegistrationViaApiResponse
$cp1Data :: Typeable RegistrationViaApiResponse
Data)

instance FromJSON RegistrationViaApiResponse

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