{-# LANGUAGE ExplicitForAll #-}
{-# LANGUAGE MultiWayIf #-}
-- CHANGE WITH CAUTION: This is a generated code file generated by https://github.com/Haskell-OpenAPI-Code-Generator/Haskell-OpenAPI-Client-Code-Generator.
{-# LANGUAGE OverloadedStrings #-}

-- | Contains the different functions to run the operation postAccountLinks
module StripeAPI.Operations.PostAccountLinks where

import qualified Control.Monad.Fail
import qualified Control.Monad.Trans.Reader
import qualified Data.Aeson
import qualified Data.Aeson as Data.Aeson.Encoding.Internal
import qualified Data.Aeson as Data.Aeson.Types
import qualified Data.Aeson as Data.Aeson.Types.FromJSON
import qualified Data.Aeson as Data.Aeson.Types.Internal
import qualified Data.Aeson as Data.Aeson.Types.ToJSON
import qualified Data.ByteString.Char8
import qualified Data.ByteString.Char8 as Data.ByteString.Internal
import qualified Data.Either
import qualified Data.Functor
import qualified Data.Scientific
import qualified Data.Text
import qualified Data.Text.Internal
import qualified Data.Time.Calendar as Data.Time.Calendar.Days
import qualified Data.Time.LocalTime as Data.Time.LocalTime.Internal.ZonedTime
import qualified Data.Vector
import qualified GHC.Base
import qualified GHC.Classes
import qualified GHC.Int
import qualified GHC.Show
import qualified GHC.Types
import qualified Network.HTTP.Client
import qualified Network.HTTP.Client as Network.HTTP.Client.Request
import qualified Network.HTTP.Client as Network.HTTP.Client.Types
import qualified Network.HTTP.Simple
import qualified Network.HTTP.Types
import qualified Network.HTTP.Types as Network.HTTP.Types.Status
import qualified Network.HTTP.Types as Network.HTTP.Types.URI
import qualified StripeAPI.Common
import StripeAPI.Types
import qualified Prelude as GHC.Integer.Type
import qualified Prelude as GHC.Maybe

-- | > POST /v1/account_links
--
-- \<p>Creates an AccountLink object that includes a single-use Stripe URL that the platform can redirect their user to in order to take them through the Connect Onboarding flow.\<\/p>
postAccountLinks ::
  forall m.
  StripeAPI.Common.MonadHTTP m =>
  -- | The request body to send
  PostAccountLinksRequestBody ->
  -- | Monadic computation which returns the result of the operation
  StripeAPI.Common.StripeT m (Network.HTTP.Client.Types.Response PostAccountLinksResponse)
postAccountLinks :: PostAccountLinksRequestBody
-> StripeT m (Response PostAccountLinksResponse)
postAccountLinks PostAccountLinksRequestBody
body =
  (Response ByteString -> Response PostAccountLinksResponse)
-> StripeT m (Response ByteString)
-> StripeT m (Response PostAccountLinksResponse)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
GHC.Base.fmap
    ( \Response ByteString
response_0 ->
        (ByteString -> PostAccountLinksResponse)
-> Response ByteString -> Response PostAccountLinksResponse
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
GHC.Base.fmap
          ( (String -> PostAccountLinksResponse)
-> (PostAccountLinksResponse -> PostAccountLinksResponse)
-> Either String PostAccountLinksResponse
-> PostAccountLinksResponse
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
Data.Either.either String -> PostAccountLinksResponse
PostAccountLinksResponseError PostAccountLinksResponse -> PostAccountLinksResponse
forall a. a -> a
GHC.Base.id
              (Either String PostAccountLinksResponse
 -> PostAccountLinksResponse)
-> (ByteString -> Either String PostAccountLinksResponse)
-> ByteString
-> PostAccountLinksResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. ( \Response ByteString
response ByteString
body ->
                             if
                                 | (\Status
status_1 -> Status -> Int
Network.HTTP.Types.Status.statusCode Status
status_1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Int
200) (Response ByteString -> Status
forall body. Response body -> Status
Network.HTTP.Client.Types.responseStatus Response ByteString
response) ->
                                   AccountLink -> PostAccountLinksResponse
PostAccountLinksResponse200
                                     (AccountLink -> PostAccountLinksResponse)
-> Either String AccountLink
-> Either String PostAccountLinksResponse
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> ( ByteString -> Either String AccountLink
forall a. FromJSON a => ByteString -> Either String a
Data.Aeson.eitherDecodeStrict ByteString
body ::
                                                          Data.Either.Either
                                                            GHC.Base.String
                                                            AccountLink
                                                      )
                                 | Bool -> Status -> Bool
forall a b. a -> b -> a
GHC.Base.const Bool
GHC.Types.True (Response ByteString -> Status
forall body. Response body -> Status
Network.HTTP.Client.Types.responseStatus Response ByteString
response) ->
                                   Error -> PostAccountLinksResponse
PostAccountLinksResponseDefault
                                     (Error -> PostAccountLinksResponse)
-> Either String Error -> Either String PostAccountLinksResponse
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> ( ByteString -> Either String Error
forall a. FromJSON a => ByteString -> Either String a
Data.Aeson.eitherDecodeStrict ByteString
body ::
                                                          Data.Either.Either
                                                            GHC.Base.String
                                                            Error
                                                      )
                                 | Bool
GHC.Base.otherwise -> String -> Either String PostAccountLinksResponse
forall a b. a -> Either a b
Data.Either.Left String
"Missing default response type"
                         )
                Response ByteString
response_0
          )
          Response ByteString
response_0
    )
    (Text
-> Text
-> [QueryParameter]
-> Maybe PostAccountLinksRequestBody
-> RequestBodyEncoding
-> StripeT m (Response ByteString)
forall (m :: * -> *) body.
(MonadHTTP m, ToJSON body) =>
Text
-> Text
-> [QueryParameter]
-> Maybe body
-> RequestBodyEncoding
-> StripeT m (Response ByteString)
StripeAPI.Common.doBodyCallWithConfigurationM (Text -> Text
Data.Text.toUpper (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
GHC.Base.$ String -> Text
Data.Text.pack String
"POST") (String -> Text
Data.Text.pack String
"/v1/account_links") [QueryParameter]
forall a. Monoid a => a
GHC.Base.mempty (PostAccountLinksRequestBody -> Maybe PostAccountLinksRequestBody
forall a. a -> Maybe a
GHC.Maybe.Just PostAccountLinksRequestBody
body) RequestBodyEncoding
StripeAPI.Common.RequestBodyEncodingFormData)

-- | Defines the object schema located at @paths.\/v1\/account_links.POST.requestBody.content.application\/x-www-form-urlencoded.schema@ in the specification.
data PostAccountLinksRequestBody = PostAccountLinksRequestBody
  { -- | account: The identifier of the account to create an account link for.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostAccountLinksRequestBody -> Text
postAccountLinksRequestBodyAccount :: Data.Text.Internal.Text,
    -- | collect: Which information the platform needs to collect from the user. One of \`currently_due\` or \`eventually_due\`. Default is \`currently_due\`.
    PostAccountLinksRequestBody
-> Maybe PostAccountLinksRequestBodyCollect'
postAccountLinksRequestBodyCollect :: (GHC.Maybe.Maybe PostAccountLinksRequestBodyCollect'),
    -- | expand: Specifies which fields in the response should be expanded.
    PostAccountLinksRequestBody -> Maybe [Text]
postAccountLinksRequestBodyExpand :: (GHC.Maybe.Maybe ([Data.Text.Internal.Text])),
    -- | refresh_url: The URL the user will be redirected to if the account link is expired, has been previously-visited, or is otherwise invalid. The URL you specify should attempt to generate a new account link with the same parameters used to create the original account link, then redirect the user to the new account link\'s URL so they can continue with Connect Onboarding. If a new account link cannot be generated or the redirect fails you should display a useful error to the user.
    PostAccountLinksRequestBody -> Maybe Text
postAccountLinksRequestBodyRefreshUrl :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | return_url: The URL that the user will be redirected to upon leaving or completing the linked flow.
    PostAccountLinksRequestBody -> Maybe Text
postAccountLinksRequestBodyReturnUrl :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | type: The type of account link the user is requesting. Possible values are \`account_onboarding\` or \`account_update\`.
    PostAccountLinksRequestBody -> PostAccountLinksRequestBodyType'
postAccountLinksRequestBodyType :: PostAccountLinksRequestBodyType'
  }
  deriving
    ( Int -> PostAccountLinksRequestBody -> ShowS
[PostAccountLinksRequestBody] -> ShowS
PostAccountLinksRequestBody -> String
(Int -> PostAccountLinksRequestBody -> ShowS)
-> (PostAccountLinksRequestBody -> String)
-> ([PostAccountLinksRequestBody] -> ShowS)
-> Show PostAccountLinksRequestBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostAccountLinksRequestBody] -> ShowS
$cshowList :: [PostAccountLinksRequestBody] -> ShowS
show :: PostAccountLinksRequestBody -> String
$cshow :: PostAccountLinksRequestBody -> String
showsPrec :: Int -> PostAccountLinksRequestBody -> ShowS
$cshowsPrec :: Int -> PostAccountLinksRequestBody -> ShowS
GHC.Show.Show,
      PostAccountLinksRequestBody -> PostAccountLinksRequestBody -> Bool
(PostAccountLinksRequestBody
 -> PostAccountLinksRequestBody -> Bool)
-> (PostAccountLinksRequestBody
    -> PostAccountLinksRequestBody -> Bool)
-> Eq PostAccountLinksRequestBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostAccountLinksRequestBody -> PostAccountLinksRequestBody -> Bool
$c/= :: PostAccountLinksRequestBody -> PostAccountLinksRequestBody -> Bool
== :: PostAccountLinksRequestBody -> PostAccountLinksRequestBody -> Bool
$c== :: PostAccountLinksRequestBody -> PostAccountLinksRequestBody -> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON PostAccountLinksRequestBody where
  toJSON :: PostAccountLinksRequestBody -> Value
toJSON PostAccountLinksRequestBody
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"account" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostAccountLinksRequestBody -> Text
postAccountLinksRequestBodyAccount PostAccountLinksRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"collect" Text -> Maybe PostAccountLinksRequestBodyCollect' -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostAccountLinksRequestBody
-> Maybe PostAccountLinksRequestBodyCollect'
postAccountLinksRequestBodyCollect PostAccountLinksRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"expand" Text -> Maybe [Text] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostAccountLinksRequestBody -> Maybe [Text]
postAccountLinksRequestBodyExpand PostAccountLinksRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"refresh_url" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostAccountLinksRequestBody -> Maybe Text
postAccountLinksRequestBodyRefreshUrl PostAccountLinksRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"return_url" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostAccountLinksRequestBody -> Maybe Text
postAccountLinksRequestBodyReturnUrl PostAccountLinksRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"type" Text -> PostAccountLinksRequestBodyType' -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostAccountLinksRequestBody -> PostAccountLinksRequestBodyType'
postAccountLinksRequestBodyType PostAccountLinksRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostAccountLinksRequestBody -> Encoding
toEncoding PostAccountLinksRequestBody
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"account" Text -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostAccountLinksRequestBody -> Text
postAccountLinksRequestBodyAccount PostAccountLinksRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"collect" Text -> Maybe PostAccountLinksRequestBodyCollect' -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostAccountLinksRequestBody
-> Maybe PostAccountLinksRequestBodyCollect'
postAccountLinksRequestBodyCollect PostAccountLinksRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"expand" Text -> Maybe [Text] -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostAccountLinksRequestBody -> Maybe [Text]
postAccountLinksRequestBodyExpand PostAccountLinksRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"refresh_url" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostAccountLinksRequestBody -> Maybe Text
postAccountLinksRequestBodyRefreshUrl PostAccountLinksRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"return_url" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostAccountLinksRequestBody -> Maybe Text
postAccountLinksRequestBodyReturnUrl PostAccountLinksRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"type" Text -> PostAccountLinksRequestBodyType' -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostAccountLinksRequestBody -> PostAccountLinksRequestBodyType'
postAccountLinksRequestBodyType PostAccountLinksRequestBody
obj))))))

instance Data.Aeson.Types.FromJSON.FromJSON PostAccountLinksRequestBody where
  parseJSON :: Value -> Parser PostAccountLinksRequestBody
parseJSON = String
-> (Object -> Parser PostAccountLinksRequestBody)
-> Value
-> Parser PostAccountLinksRequestBody
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostAccountLinksRequestBody" (\Object
obj -> ((((((Text
 -> Maybe PostAccountLinksRequestBodyCollect'
 -> Maybe [Text]
 -> Maybe Text
 -> Maybe Text
 -> PostAccountLinksRequestBodyType'
 -> PostAccountLinksRequestBody)
-> Parser
     (Text
      -> Maybe PostAccountLinksRequestBodyCollect'
      -> Maybe [Text]
      -> Maybe Text
      -> Maybe Text
      -> PostAccountLinksRequestBodyType'
      -> PostAccountLinksRequestBody)
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Text
-> Maybe PostAccountLinksRequestBodyCollect'
-> Maybe [Text]
-> Maybe Text
-> Maybe Text
-> PostAccountLinksRequestBodyType'
-> PostAccountLinksRequestBody
PostAccountLinksRequestBody Parser
  (Text
   -> Maybe PostAccountLinksRequestBodyCollect'
   -> Maybe [Text]
   -> Maybe Text
   -> Maybe Text
   -> PostAccountLinksRequestBodyType'
   -> PostAccountLinksRequestBody)
-> Parser Text
-> Parser
     (Maybe PostAccountLinksRequestBodyCollect'
      -> Maybe [Text]
      -> Maybe Text
      -> Maybe Text
      -> PostAccountLinksRequestBodyType'
      -> PostAccountLinksRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"account")) Parser
  (Maybe PostAccountLinksRequestBodyCollect'
   -> Maybe [Text]
   -> Maybe Text
   -> Maybe Text
   -> PostAccountLinksRequestBodyType'
   -> PostAccountLinksRequestBody)
-> Parser (Maybe PostAccountLinksRequestBodyCollect')
-> Parser
     (Maybe [Text]
      -> Maybe Text
      -> Maybe Text
      -> PostAccountLinksRequestBodyType'
      -> PostAccountLinksRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text -> Parser (Maybe PostAccountLinksRequestBodyCollect')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"collect")) Parser
  (Maybe [Text]
   -> Maybe Text
   -> Maybe Text
   -> PostAccountLinksRequestBodyType'
   -> PostAccountLinksRequestBody)
-> Parser (Maybe [Text])
-> Parser
     (Maybe Text
      -> Maybe Text
      -> PostAccountLinksRequestBodyType'
      -> PostAccountLinksRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe [Text])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"expand")) Parser
  (Maybe Text
   -> Maybe Text
   -> PostAccountLinksRequestBodyType'
   -> PostAccountLinksRequestBody)
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> PostAccountLinksRequestBodyType' -> PostAccountLinksRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"refresh_url")) Parser
  (Maybe Text
   -> PostAccountLinksRequestBodyType' -> PostAccountLinksRequestBody)
-> Parser (Maybe Text)
-> Parser
     (PostAccountLinksRequestBodyType' -> PostAccountLinksRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"return_url")) Parser
  (PostAccountLinksRequestBodyType' -> PostAccountLinksRequestBody)
-> Parser PostAccountLinksRequestBodyType'
-> Parser PostAccountLinksRequestBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser PostAccountLinksRequestBodyType'
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"type"))

-- | Create a new 'PostAccountLinksRequestBody' with all required fields.
mkPostAccountLinksRequestBody ::
  -- | 'postAccountLinksRequestBodyAccount'
  Data.Text.Internal.Text ->
  -- | 'postAccountLinksRequestBodyType'
  PostAccountLinksRequestBodyType' ->
  PostAccountLinksRequestBody
mkPostAccountLinksRequestBody :: Text
-> PostAccountLinksRequestBodyType' -> PostAccountLinksRequestBody
mkPostAccountLinksRequestBody Text
postAccountLinksRequestBodyAccount PostAccountLinksRequestBodyType'
postAccountLinksRequestBodyType =
  PostAccountLinksRequestBody :: Text
-> Maybe PostAccountLinksRequestBodyCollect'
-> Maybe [Text]
-> Maybe Text
-> Maybe Text
-> PostAccountLinksRequestBodyType'
-> PostAccountLinksRequestBody
PostAccountLinksRequestBody
    { postAccountLinksRequestBodyAccount :: Text
postAccountLinksRequestBodyAccount = Text
postAccountLinksRequestBodyAccount,
      postAccountLinksRequestBodyCollect :: Maybe PostAccountLinksRequestBodyCollect'
postAccountLinksRequestBodyCollect = Maybe PostAccountLinksRequestBodyCollect'
forall a. Maybe a
GHC.Maybe.Nothing,
      postAccountLinksRequestBodyExpand :: Maybe [Text]
postAccountLinksRequestBodyExpand = Maybe [Text]
forall a. Maybe a
GHC.Maybe.Nothing,
      postAccountLinksRequestBodyRefreshUrl :: Maybe Text
postAccountLinksRequestBodyRefreshUrl = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postAccountLinksRequestBodyReturnUrl :: Maybe Text
postAccountLinksRequestBodyReturnUrl = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postAccountLinksRequestBodyType :: PostAccountLinksRequestBodyType'
postAccountLinksRequestBodyType = PostAccountLinksRequestBodyType'
postAccountLinksRequestBodyType
    }

-- | Defines the enum schema located at @paths.\/v1\/account_links.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.collect@ in the specification.
--
-- Which information the platform needs to collect from the user. One of \`currently_due\` or \`eventually_due\`. Default is \`currently_due\`.
data PostAccountLinksRequestBodyCollect'
  = -- | This case is used if the value encountered during decoding does not match any of the provided cases in the specification.
    PostAccountLinksRequestBodyCollect'Other Data.Aeson.Types.Internal.Value
  | -- | This constructor can be used to send values to the server which are not present in the specification yet.
    PostAccountLinksRequestBodyCollect'Typed Data.Text.Internal.Text
  | -- | Represents the JSON value @"currently_due"@
    PostAccountLinksRequestBodyCollect'EnumCurrentlyDue
  | -- | Represents the JSON value @"eventually_due"@
    PostAccountLinksRequestBodyCollect'EnumEventuallyDue
  deriving (Int -> PostAccountLinksRequestBodyCollect' -> ShowS
[PostAccountLinksRequestBodyCollect'] -> ShowS
PostAccountLinksRequestBodyCollect' -> String
(Int -> PostAccountLinksRequestBodyCollect' -> ShowS)
-> (PostAccountLinksRequestBodyCollect' -> String)
-> ([PostAccountLinksRequestBodyCollect'] -> ShowS)
-> Show PostAccountLinksRequestBodyCollect'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostAccountLinksRequestBodyCollect'] -> ShowS
$cshowList :: [PostAccountLinksRequestBodyCollect'] -> ShowS
show :: PostAccountLinksRequestBodyCollect' -> String
$cshow :: PostAccountLinksRequestBodyCollect' -> String
showsPrec :: Int -> PostAccountLinksRequestBodyCollect' -> ShowS
$cshowsPrec :: Int -> PostAccountLinksRequestBodyCollect' -> ShowS
GHC.Show.Show, PostAccountLinksRequestBodyCollect'
-> PostAccountLinksRequestBodyCollect' -> Bool
(PostAccountLinksRequestBodyCollect'
 -> PostAccountLinksRequestBodyCollect' -> Bool)
-> (PostAccountLinksRequestBodyCollect'
    -> PostAccountLinksRequestBodyCollect' -> Bool)
-> Eq PostAccountLinksRequestBodyCollect'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostAccountLinksRequestBodyCollect'
-> PostAccountLinksRequestBodyCollect' -> Bool
$c/= :: PostAccountLinksRequestBodyCollect'
-> PostAccountLinksRequestBodyCollect' -> Bool
== :: PostAccountLinksRequestBodyCollect'
-> PostAccountLinksRequestBodyCollect' -> Bool
$c== :: PostAccountLinksRequestBodyCollect'
-> PostAccountLinksRequestBodyCollect' -> Bool
GHC.Classes.Eq)

instance Data.Aeson.Types.ToJSON.ToJSON PostAccountLinksRequestBodyCollect' where
  toJSON :: PostAccountLinksRequestBodyCollect' -> Value
toJSON (PostAccountLinksRequestBodyCollect'Other Value
val) = Value
val
  toJSON (PostAccountLinksRequestBodyCollect'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (PostAccountLinksRequestBodyCollect'
PostAccountLinksRequestBodyCollect'EnumCurrentlyDue) = Value
"currently_due"
  toJSON (PostAccountLinksRequestBodyCollect'
PostAccountLinksRequestBodyCollect'EnumEventuallyDue) = Value
"eventually_due"

instance Data.Aeson.Types.FromJSON.FromJSON PostAccountLinksRequestBodyCollect' where
  parseJSON :: Value -> Parser PostAccountLinksRequestBodyCollect'
parseJSON Value
val =
    PostAccountLinksRequestBodyCollect'
-> Parser PostAccountLinksRequestBodyCollect'
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure
      ( if
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"currently_due" -> PostAccountLinksRequestBodyCollect'
PostAccountLinksRequestBodyCollect'EnumCurrentlyDue
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"eventually_due" -> PostAccountLinksRequestBodyCollect'
PostAccountLinksRequestBodyCollect'EnumEventuallyDue
            | Bool
GHC.Base.otherwise -> Value -> PostAccountLinksRequestBodyCollect'
PostAccountLinksRequestBodyCollect'Other Value
val
      )

-- | Defines the enum schema located at @paths.\/v1\/account_links.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.type@ in the specification.
--
-- The type of account link the user is requesting. Possible values are \`account_onboarding\` or \`account_update\`.
data PostAccountLinksRequestBodyType'
  = -- | This case is used if the value encountered during decoding does not match any of the provided cases in the specification.
    PostAccountLinksRequestBodyType'Other Data.Aeson.Types.Internal.Value
  | -- | This constructor can be used to send values to the server which are not present in the specification yet.
    PostAccountLinksRequestBodyType'Typed Data.Text.Internal.Text
  | -- | Represents the JSON value @"account_onboarding"@
    PostAccountLinksRequestBodyType'EnumAccountOnboarding
  | -- | Represents the JSON value @"account_update"@
    PostAccountLinksRequestBodyType'EnumAccountUpdate
  deriving (Int -> PostAccountLinksRequestBodyType' -> ShowS
[PostAccountLinksRequestBodyType'] -> ShowS
PostAccountLinksRequestBodyType' -> String
(Int -> PostAccountLinksRequestBodyType' -> ShowS)
-> (PostAccountLinksRequestBodyType' -> String)
-> ([PostAccountLinksRequestBodyType'] -> ShowS)
-> Show PostAccountLinksRequestBodyType'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostAccountLinksRequestBodyType'] -> ShowS
$cshowList :: [PostAccountLinksRequestBodyType'] -> ShowS
show :: PostAccountLinksRequestBodyType' -> String
$cshow :: PostAccountLinksRequestBodyType' -> String
showsPrec :: Int -> PostAccountLinksRequestBodyType' -> ShowS
$cshowsPrec :: Int -> PostAccountLinksRequestBodyType' -> ShowS
GHC.Show.Show, PostAccountLinksRequestBodyType'
-> PostAccountLinksRequestBodyType' -> Bool
(PostAccountLinksRequestBodyType'
 -> PostAccountLinksRequestBodyType' -> Bool)
-> (PostAccountLinksRequestBodyType'
    -> PostAccountLinksRequestBodyType' -> Bool)
-> Eq PostAccountLinksRequestBodyType'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostAccountLinksRequestBodyType'
-> PostAccountLinksRequestBodyType' -> Bool
$c/= :: PostAccountLinksRequestBodyType'
-> PostAccountLinksRequestBodyType' -> Bool
== :: PostAccountLinksRequestBodyType'
-> PostAccountLinksRequestBodyType' -> Bool
$c== :: PostAccountLinksRequestBodyType'
-> PostAccountLinksRequestBodyType' -> Bool
GHC.Classes.Eq)

instance Data.Aeson.Types.ToJSON.ToJSON PostAccountLinksRequestBodyType' where
  toJSON :: PostAccountLinksRequestBodyType' -> Value
toJSON (PostAccountLinksRequestBodyType'Other Value
val) = Value
val
  toJSON (PostAccountLinksRequestBodyType'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (PostAccountLinksRequestBodyType'
PostAccountLinksRequestBodyType'EnumAccountOnboarding) = Value
"account_onboarding"
  toJSON (PostAccountLinksRequestBodyType'
PostAccountLinksRequestBodyType'EnumAccountUpdate) = Value
"account_update"

instance Data.Aeson.Types.FromJSON.FromJSON PostAccountLinksRequestBodyType' where
  parseJSON :: Value -> Parser PostAccountLinksRequestBodyType'
parseJSON Value
val =
    PostAccountLinksRequestBodyType'
-> Parser PostAccountLinksRequestBodyType'
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure
      ( if
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"account_onboarding" -> PostAccountLinksRequestBodyType'
PostAccountLinksRequestBodyType'EnumAccountOnboarding
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"account_update" -> PostAccountLinksRequestBodyType'
PostAccountLinksRequestBodyType'EnumAccountUpdate
            | Bool
GHC.Base.otherwise -> Value -> PostAccountLinksRequestBodyType'
PostAccountLinksRequestBodyType'Other Value
val
      )

-- | Represents a response of the operation 'postAccountLinks'.
--
-- The response constructor is chosen by the status code of the response. If no case matches (no specific case for the response code, no range case, no default case), 'PostAccountLinksResponseError' is used.
data PostAccountLinksResponse
  = -- | Means either no matching case available or a parse error
    PostAccountLinksResponseError GHC.Base.String
  | -- | Successful response.
    PostAccountLinksResponse200 AccountLink
  | -- | Error response.
    PostAccountLinksResponseDefault Error
  deriving (Int -> PostAccountLinksResponse -> ShowS
[PostAccountLinksResponse] -> ShowS
PostAccountLinksResponse -> String
(Int -> PostAccountLinksResponse -> ShowS)
-> (PostAccountLinksResponse -> String)
-> ([PostAccountLinksResponse] -> ShowS)
-> Show PostAccountLinksResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostAccountLinksResponse] -> ShowS
$cshowList :: [PostAccountLinksResponse] -> ShowS
show :: PostAccountLinksResponse -> String
$cshow :: PostAccountLinksResponse -> String
showsPrec :: Int -> PostAccountLinksResponse -> ShowS
$cshowsPrec :: Int -> PostAccountLinksResponse -> ShowS
GHC.Show.Show, PostAccountLinksResponse -> PostAccountLinksResponse -> Bool
(PostAccountLinksResponse -> PostAccountLinksResponse -> Bool)
-> (PostAccountLinksResponse -> PostAccountLinksResponse -> Bool)
-> Eq PostAccountLinksResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostAccountLinksResponse -> PostAccountLinksResponse -> Bool
$c/= :: PostAccountLinksResponse -> PostAccountLinksResponse -> Bool
== :: PostAccountLinksResponse -> PostAccountLinksResponse -> Bool
$c== :: PostAccountLinksResponse -> PostAccountLinksResponse -> Bool
GHC.Classes.Eq)