{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.AmplifyBackend.CreateBackendConfig
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a config object for a backend.
module Amazonka.AmplifyBackend.CreateBackendConfig
  ( -- * Creating a Request
    CreateBackendConfig (..),
    newCreateBackendConfig,

    -- * Request Lenses
    createBackendConfig_backendManagerAppId,
    createBackendConfig_appId,

    -- * Destructuring the Response
    CreateBackendConfigResponse (..),
    newCreateBackendConfigResponse,

    -- * Response Lenses
    createBackendConfigResponse_appId,
    createBackendConfigResponse_backendEnvironmentName,
    createBackendConfigResponse_jobId,
    createBackendConfigResponse_status,
    createBackendConfigResponse_httpStatus,
  )
where

import Amazonka.AmplifyBackend.Types
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | The request body for CreateBackendConfig.
--
-- /See:/ 'newCreateBackendConfig' smart constructor.
data CreateBackendConfig = CreateBackendConfig'
  { -- | The app ID for the backend manager.
    CreateBackendConfig -> Maybe Text
backendManagerAppId :: Prelude.Maybe Prelude.Text,
    -- | The app ID.
    CreateBackendConfig -> Text
appId :: Prelude.Text
  }
  deriving (CreateBackendConfig -> CreateBackendConfig -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateBackendConfig -> CreateBackendConfig -> Bool
$c/= :: CreateBackendConfig -> CreateBackendConfig -> Bool
== :: CreateBackendConfig -> CreateBackendConfig -> Bool
$c== :: CreateBackendConfig -> CreateBackendConfig -> Bool
Prelude.Eq, ReadPrec [CreateBackendConfig]
ReadPrec CreateBackendConfig
Int -> ReadS CreateBackendConfig
ReadS [CreateBackendConfig]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateBackendConfig]
$creadListPrec :: ReadPrec [CreateBackendConfig]
readPrec :: ReadPrec CreateBackendConfig
$creadPrec :: ReadPrec CreateBackendConfig
readList :: ReadS [CreateBackendConfig]
$creadList :: ReadS [CreateBackendConfig]
readsPrec :: Int -> ReadS CreateBackendConfig
$creadsPrec :: Int -> ReadS CreateBackendConfig
Prelude.Read, Int -> CreateBackendConfig -> ShowS
[CreateBackendConfig] -> ShowS
CreateBackendConfig -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateBackendConfig] -> ShowS
$cshowList :: [CreateBackendConfig] -> ShowS
show :: CreateBackendConfig -> String
$cshow :: CreateBackendConfig -> String
showsPrec :: Int -> CreateBackendConfig -> ShowS
$cshowsPrec :: Int -> CreateBackendConfig -> ShowS
Prelude.Show, forall x. Rep CreateBackendConfig x -> CreateBackendConfig
forall x. CreateBackendConfig -> Rep CreateBackendConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateBackendConfig x -> CreateBackendConfig
$cfrom :: forall x. CreateBackendConfig -> Rep CreateBackendConfig x
Prelude.Generic)

-- |
-- Create a value of 'CreateBackendConfig' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'backendManagerAppId', 'createBackendConfig_backendManagerAppId' - The app ID for the backend manager.
--
-- 'appId', 'createBackendConfig_appId' - The app ID.
newCreateBackendConfig ::
  -- | 'appId'
  Prelude.Text ->
  CreateBackendConfig
newCreateBackendConfig :: Text -> CreateBackendConfig
newCreateBackendConfig Text
pAppId_ =
  CreateBackendConfig'
    { $sel:backendManagerAppId:CreateBackendConfig' :: Maybe Text
backendManagerAppId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:appId:CreateBackendConfig' :: Text
appId = Text
pAppId_
    }

-- | The app ID for the backend manager.
createBackendConfig_backendManagerAppId :: Lens.Lens' CreateBackendConfig (Prelude.Maybe Prelude.Text)
createBackendConfig_backendManagerAppId :: Lens' CreateBackendConfig (Maybe Text)
createBackendConfig_backendManagerAppId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateBackendConfig' {Maybe Text
backendManagerAppId :: Maybe Text
$sel:backendManagerAppId:CreateBackendConfig' :: CreateBackendConfig -> Maybe Text
backendManagerAppId} -> Maybe Text
backendManagerAppId) (\s :: CreateBackendConfig
s@CreateBackendConfig' {} Maybe Text
a -> CreateBackendConfig
s {$sel:backendManagerAppId:CreateBackendConfig' :: Maybe Text
backendManagerAppId = Maybe Text
a} :: CreateBackendConfig)

-- | The app ID.
createBackendConfig_appId :: Lens.Lens' CreateBackendConfig Prelude.Text
createBackendConfig_appId :: Lens' CreateBackendConfig Text
createBackendConfig_appId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateBackendConfig' {Text
appId :: Text
$sel:appId:CreateBackendConfig' :: CreateBackendConfig -> Text
appId} -> Text
appId) (\s :: CreateBackendConfig
s@CreateBackendConfig' {} Text
a -> CreateBackendConfig
s {$sel:appId:CreateBackendConfig' :: Text
appId = Text
a} :: CreateBackendConfig)

instance Core.AWSRequest CreateBackendConfig where
  type
    AWSResponse CreateBackendConfig =
      CreateBackendConfigResponse
  request :: (Service -> Service)
-> CreateBackendConfig -> Request CreateBackendConfig
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy CreateBackendConfig
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateBackendConfig)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Int
-> CreateBackendConfigResponse
CreateBackendConfigResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"appId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"backendEnvironmentName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"jobId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"status")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable CreateBackendConfig where
  hashWithSalt :: Int -> CreateBackendConfig -> Int
hashWithSalt Int
_salt CreateBackendConfig' {Maybe Text
Text
appId :: Text
backendManagerAppId :: Maybe Text
$sel:appId:CreateBackendConfig' :: CreateBackendConfig -> Text
$sel:backendManagerAppId:CreateBackendConfig' :: CreateBackendConfig -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
backendManagerAppId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
appId

instance Prelude.NFData CreateBackendConfig where
  rnf :: CreateBackendConfig -> ()
rnf CreateBackendConfig' {Maybe Text
Text
appId :: Text
backendManagerAppId :: Maybe Text
$sel:appId:CreateBackendConfig' :: CreateBackendConfig -> Text
$sel:backendManagerAppId:CreateBackendConfig' :: CreateBackendConfig -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
backendManagerAppId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
appId

instance Data.ToHeaders CreateBackendConfig where
  toHeaders :: CreateBackendConfig -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON CreateBackendConfig where
  toJSON :: CreateBackendConfig -> Value
toJSON CreateBackendConfig' {Maybe Text
Text
appId :: Text
backendManagerAppId :: Maybe Text
$sel:appId:CreateBackendConfig' :: CreateBackendConfig -> Text
$sel:backendManagerAppId:CreateBackendConfig' :: CreateBackendConfig -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"backendManagerAppId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
backendManagerAppId
          ]
      )

instance Data.ToPath CreateBackendConfig where
  toPath :: CreateBackendConfig -> ByteString
toPath CreateBackendConfig' {Maybe Text
Text
appId :: Text
backendManagerAppId :: Maybe Text
$sel:appId:CreateBackendConfig' :: CreateBackendConfig -> Text
$sel:backendManagerAppId:CreateBackendConfig' :: CreateBackendConfig -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/backend/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
appId, ByteString
"/config"]

instance Data.ToQuery CreateBackendConfig where
  toQuery :: CreateBackendConfig -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newCreateBackendConfigResponse' smart constructor.
data CreateBackendConfigResponse = CreateBackendConfigResponse'
  { -- | The app ID.
    CreateBackendConfigResponse -> Maybe Text
appId :: Prelude.Maybe Prelude.Text,
    -- | The name of the backend environment.
    CreateBackendConfigResponse -> Maybe Text
backendEnvironmentName :: Prelude.Maybe Prelude.Text,
    -- | The ID for the job.
    CreateBackendConfigResponse -> Maybe Text
jobId :: Prelude.Maybe Prelude.Text,
    -- | The current status of the request.
    CreateBackendConfigResponse -> Maybe Text
status :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    CreateBackendConfigResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateBackendConfigResponse -> CreateBackendConfigResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateBackendConfigResponse -> CreateBackendConfigResponse -> Bool
$c/= :: CreateBackendConfigResponse -> CreateBackendConfigResponse -> Bool
== :: CreateBackendConfigResponse -> CreateBackendConfigResponse -> Bool
$c== :: CreateBackendConfigResponse -> CreateBackendConfigResponse -> Bool
Prelude.Eq, ReadPrec [CreateBackendConfigResponse]
ReadPrec CreateBackendConfigResponse
Int -> ReadS CreateBackendConfigResponse
ReadS [CreateBackendConfigResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateBackendConfigResponse]
$creadListPrec :: ReadPrec [CreateBackendConfigResponse]
readPrec :: ReadPrec CreateBackendConfigResponse
$creadPrec :: ReadPrec CreateBackendConfigResponse
readList :: ReadS [CreateBackendConfigResponse]
$creadList :: ReadS [CreateBackendConfigResponse]
readsPrec :: Int -> ReadS CreateBackendConfigResponse
$creadsPrec :: Int -> ReadS CreateBackendConfigResponse
Prelude.Read, Int -> CreateBackendConfigResponse -> ShowS
[CreateBackendConfigResponse] -> ShowS
CreateBackendConfigResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateBackendConfigResponse] -> ShowS
$cshowList :: [CreateBackendConfigResponse] -> ShowS
show :: CreateBackendConfigResponse -> String
$cshow :: CreateBackendConfigResponse -> String
showsPrec :: Int -> CreateBackendConfigResponse -> ShowS
$cshowsPrec :: Int -> CreateBackendConfigResponse -> ShowS
Prelude.Show, forall x.
Rep CreateBackendConfigResponse x -> CreateBackendConfigResponse
forall x.
CreateBackendConfigResponse -> Rep CreateBackendConfigResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateBackendConfigResponse x -> CreateBackendConfigResponse
$cfrom :: forall x.
CreateBackendConfigResponse -> Rep CreateBackendConfigResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateBackendConfigResponse' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'appId', 'createBackendConfigResponse_appId' - The app ID.
--
-- 'backendEnvironmentName', 'createBackendConfigResponse_backendEnvironmentName' - The name of the backend environment.
--
-- 'jobId', 'createBackendConfigResponse_jobId' - The ID for the job.
--
-- 'status', 'createBackendConfigResponse_status' - The current status of the request.
--
-- 'httpStatus', 'createBackendConfigResponse_httpStatus' - The response's http status code.
newCreateBackendConfigResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateBackendConfigResponse
newCreateBackendConfigResponse :: Int -> CreateBackendConfigResponse
newCreateBackendConfigResponse Int
pHttpStatus_ =
  CreateBackendConfigResponse'
    { $sel:appId:CreateBackendConfigResponse' :: Maybe Text
appId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:backendEnvironmentName:CreateBackendConfigResponse' :: Maybe Text
backendEnvironmentName = forall a. Maybe a
Prelude.Nothing,
      $sel:jobId:CreateBackendConfigResponse' :: Maybe Text
jobId = forall a. Maybe a
Prelude.Nothing,
      $sel:status:CreateBackendConfigResponse' :: Maybe Text
status = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateBackendConfigResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The app ID.
createBackendConfigResponse_appId :: Lens.Lens' CreateBackendConfigResponse (Prelude.Maybe Prelude.Text)
createBackendConfigResponse_appId :: Lens' CreateBackendConfigResponse (Maybe Text)
createBackendConfigResponse_appId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateBackendConfigResponse' {Maybe Text
appId :: Maybe Text
$sel:appId:CreateBackendConfigResponse' :: CreateBackendConfigResponse -> Maybe Text
appId} -> Maybe Text
appId) (\s :: CreateBackendConfigResponse
s@CreateBackendConfigResponse' {} Maybe Text
a -> CreateBackendConfigResponse
s {$sel:appId:CreateBackendConfigResponse' :: Maybe Text
appId = Maybe Text
a} :: CreateBackendConfigResponse)

-- | The name of the backend environment.
createBackendConfigResponse_backendEnvironmentName :: Lens.Lens' CreateBackendConfigResponse (Prelude.Maybe Prelude.Text)
createBackendConfigResponse_backendEnvironmentName :: Lens' CreateBackendConfigResponse (Maybe Text)
createBackendConfigResponse_backendEnvironmentName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateBackendConfigResponse' {Maybe Text
backendEnvironmentName :: Maybe Text
$sel:backendEnvironmentName:CreateBackendConfigResponse' :: CreateBackendConfigResponse -> Maybe Text
backendEnvironmentName} -> Maybe Text
backendEnvironmentName) (\s :: CreateBackendConfigResponse
s@CreateBackendConfigResponse' {} Maybe Text
a -> CreateBackendConfigResponse
s {$sel:backendEnvironmentName:CreateBackendConfigResponse' :: Maybe Text
backendEnvironmentName = Maybe Text
a} :: CreateBackendConfigResponse)

-- | The ID for the job.
createBackendConfigResponse_jobId :: Lens.Lens' CreateBackendConfigResponse (Prelude.Maybe Prelude.Text)
createBackendConfigResponse_jobId :: Lens' CreateBackendConfigResponse (Maybe Text)
createBackendConfigResponse_jobId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateBackendConfigResponse' {Maybe Text
jobId :: Maybe Text
$sel:jobId:CreateBackendConfigResponse' :: CreateBackendConfigResponse -> Maybe Text
jobId} -> Maybe Text
jobId) (\s :: CreateBackendConfigResponse
s@CreateBackendConfigResponse' {} Maybe Text
a -> CreateBackendConfigResponse
s {$sel:jobId:CreateBackendConfigResponse' :: Maybe Text
jobId = Maybe Text
a} :: CreateBackendConfigResponse)

-- | The current status of the request.
createBackendConfigResponse_status :: Lens.Lens' CreateBackendConfigResponse (Prelude.Maybe Prelude.Text)
createBackendConfigResponse_status :: Lens' CreateBackendConfigResponse (Maybe Text)
createBackendConfigResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateBackendConfigResponse' {Maybe Text
status :: Maybe Text
$sel:status:CreateBackendConfigResponse' :: CreateBackendConfigResponse -> Maybe Text
status} -> Maybe Text
status) (\s :: CreateBackendConfigResponse
s@CreateBackendConfigResponse' {} Maybe Text
a -> CreateBackendConfigResponse
s {$sel:status:CreateBackendConfigResponse' :: Maybe Text
status = Maybe Text
a} :: CreateBackendConfigResponse)

-- | The response's http status code.
createBackendConfigResponse_httpStatus :: Lens.Lens' CreateBackendConfigResponse Prelude.Int
createBackendConfigResponse_httpStatus :: Lens' CreateBackendConfigResponse Int
createBackendConfigResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateBackendConfigResponse' {Int
httpStatus :: Int
$sel:httpStatus:CreateBackendConfigResponse' :: CreateBackendConfigResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: CreateBackendConfigResponse
s@CreateBackendConfigResponse' {} Int
a -> CreateBackendConfigResponse
s {$sel:httpStatus:CreateBackendConfigResponse' :: Int
httpStatus = Int
a} :: CreateBackendConfigResponse)

instance Prelude.NFData CreateBackendConfigResponse where
  rnf :: CreateBackendConfigResponse -> ()
rnf CreateBackendConfigResponse' {Int
Maybe Text
httpStatus :: Int
status :: Maybe Text
jobId :: Maybe Text
backendEnvironmentName :: Maybe Text
appId :: Maybe Text
$sel:httpStatus:CreateBackendConfigResponse' :: CreateBackendConfigResponse -> Int
$sel:status:CreateBackendConfigResponse' :: CreateBackendConfigResponse -> Maybe Text
$sel:jobId:CreateBackendConfigResponse' :: CreateBackendConfigResponse -> Maybe Text
$sel:backendEnvironmentName:CreateBackendConfigResponse' :: CreateBackendConfigResponse -> Maybe Text
$sel:appId:CreateBackendConfigResponse' :: CreateBackendConfigResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
appId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
backendEnvironmentName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
jobId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus