{-# 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.AmplifyUiBuilder.UpdateComponent
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates an existing component.
module Amazonka.AmplifyUiBuilder.UpdateComponent
  ( -- * Creating a Request
    UpdateComponent (..),
    newUpdateComponent,

    -- * Request Lenses
    updateComponent_clientToken,
    updateComponent_appId,
    updateComponent_environmentName,
    updateComponent_id,
    updateComponent_updatedComponent,

    -- * Destructuring the Response
    UpdateComponentResponse (..),
    newUpdateComponentResponse,

    -- * Response Lenses
    updateComponentResponse_entity,
    updateComponentResponse_httpStatus,
  )
where

import Amazonka.AmplifyUiBuilder.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

-- | /See:/ 'newUpdateComponent' smart constructor.
data UpdateComponent = UpdateComponent'
  { -- | The unique client token.
    UpdateComponent -> Maybe Text
clientToken :: Prelude.Maybe Prelude.Text,
    -- | The unique ID for the Amplify app.
    UpdateComponent -> Text
appId :: Prelude.Text,
    -- | The name of the backend environment that is part of the Amplify app.
    UpdateComponent -> Text
environmentName :: Prelude.Text,
    -- | The unique ID for the component.
    UpdateComponent -> Text
id :: Prelude.Text,
    -- | The configuration of the updated component.
    UpdateComponent -> UpdateComponentData
updatedComponent :: UpdateComponentData
  }
  deriving (UpdateComponent -> UpdateComponent -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateComponent -> UpdateComponent -> Bool
$c/= :: UpdateComponent -> UpdateComponent -> Bool
== :: UpdateComponent -> UpdateComponent -> Bool
$c== :: UpdateComponent -> UpdateComponent -> Bool
Prelude.Eq, ReadPrec [UpdateComponent]
ReadPrec UpdateComponent
Int -> ReadS UpdateComponent
ReadS [UpdateComponent]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateComponent]
$creadListPrec :: ReadPrec [UpdateComponent]
readPrec :: ReadPrec UpdateComponent
$creadPrec :: ReadPrec UpdateComponent
readList :: ReadS [UpdateComponent]
$creadList :: ReadS [UpdateComponent]
readsPrec :: Int -> ReadS UpdateComponent
$creadsPrec :: Int -> ReadS UpdateComponent
Prelude.Read, Int -> UpdateComponent -> ShowS
[UpdateComponent] -> ShowS
UpdateComponent -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateComponent] -> ShowS
$cshowList :: [UpdateComponent] -> ShowS
show :: UpdateComponent -> String
$cshow :: UpdateComponent -> String
showsPrec :: Int -> UpdateComponent -> ShowS
$cshowsPrec :: Int -> UpdateComponent -> ShowS
Prelude.Show, forall x. Rep UpdateComponent x -> UpdateComponent
forall x. UpdateComponent -> Rep UpdateComponent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateComponent x -> UpdateComponent
$cfrom :: forall x. UpdateComponent -> Rep UpdateComponent x
Prelude.Generic)

-- |
-- Create a value of 'UpdateComponent' 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:
--
-- 'clientToken', 'updateComponent_clientToken' - The unique client token.
--
-- 'appId', 'updateComponent_appId' - The unique ID for the Amplify app.
--
-- 'environmentName', 'updateComponent_environmentName' - The name of the backend environment that is part of the Amplify app.
--
-- 'id', 'updateComponent_id' - The unique ID for the component.
--
-- 'updatedComponent', 'updateComponent_updatedComponent' - The configuration of the updated component.
newUpdateComponent ::
  -- | 'appId'
  Prelude.Text ->
  -- | 'environmentName'
  Prelude.Text ->
  -- | 'id'
  Prelude.Text ->
  -- | 'updatedComponent'
  UpdateComponentData ->
  UpdateComponent
newUpdateComponent :: Text -> Text -> Text -> UpdateComponentData -> UpdateComponent
newUpdateComponent
  Text
pAppId_
  Text
pEnvironmentName_
  Text
pId_
  UpdateComponentData
pUpdatedComponent_ =
    UpdateComponent'
      { $sel:clientToken:UpdateComponent' :: Maybe Text
clientToken = forall a. Maybe a
Prelude.Nothing,
        $sel:appId:UpdateComponent' :: Text
appId = Text
pAppId_,
        $sel:environmentName:UpdateComponent' :: Text
environmentName = Text
pEnvironmentName_,
        $sel:id:UpdateComponent' :: Text
id = Text
pId_,
        $sel:updatedComponent:UpdateComponent' :: UpdateComponentData
updatedComponent = UpdateComponentData
pUpdatedComponent_
      }

-- | The unique client token.
updateComponent_clientToken :: Lens.Lens' UpdateComponent (Prelude.Maybe Prelude.Text)
updateComponent_clientToken :: Lens' UpdateComponent (Maybe Text)
updateComponent_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateComponent' {Maybe Text
clientToken :: Maybe Text
$sel:clientToken:UpdateComponent' :: UpdateComponent -> Maybe Text
clientToken} -> Maybe Text
clientToken) (\s :: UpdateComponent
s@UpdateComponent' {} Maybe Text
a -> UpdateComponent
s {$sel:clientToken:UpdateComponent' :: Maybe Text
clientToken = Maybe Text
a} :: UpdateComponent)

-- | The unique ID for the Amplify app.
updateComponent_appId :: Lens.Lens' UpdateComponent Prelude.Text
updateComponent_appId :: Lens' UpdateComponent Text
updateComponent_appId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateComponent' {Text
appId :: Text
$sel:appId:UpdateComponent' :: UpdateComponent -> Text
appId} -> Text
appId) (\s :: UpdateComponent
s@UpdateComponent' {} Text
a -> UpdateComponent
s {$sel:appId:UpdateComponent' :: Text
appId = Text
a} :: UpdateComponent)

-- | The name of the backend environment that is part of the Amplify app.
updateComponent_environmentName :: Lens.Lens' UpdateComponent Prelude.Text
updateComponent_environmentName :: Lens' UpdateComponent Text
updateComponent_environmentName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateComponent' {Text
environmentName :: Text
$sel:environmentName:UpdateComponent' :: UpdateComponent -> Text
environmentName} -> Text
environmentName) (\s :: UpdateComponent
s@UpdateComponent' {} Text
a -> UpdateComponent
s {$sel:environmentName:UpdateComponent' :: Text
environmentName = Text
a} :: UpdateComponent)

-- | The unique ID for the component.
updateComponent_id :: Lens.Lens' UpdateComponent Prelude.Text
updateComponent_id :: Lens' UpdateComponent Text
updateComponent_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateComponent' {Text
id :: Text
$sel:id:UpdateComponent' :: UpdateComponent -> Text
id} -> Text
id) (\s :: UpdateComponent
s@UpdateComponent' {} Text
a -> UpdateComponent
s {$sel:id:UpdateComponent' :: Text
id = Text
a} :: UpdateComponent)

-- | The configuration of the updated component.
updateComponent_updatedComponent :: Lens.Lens' UpdateComponent UpdateComponentData
updateComponent_updatedComponent :: Lens' UpdateComponent UpdateComponentData
updateComponent_updatedComponent = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateComponent' {UpdateComponentData
updatedComponent :: UpdateComponentData
$sel:updatedComponent:UpdateComponent' :: UpdateComponent -> UpdateComponentData
updatedComponent} -> UpdateComponentData
updatedComponent) (\s :: UpdateComponent
s@UpdateComponent' {} UpdateComponentData
a -> UpdateComponent
s {$sel:updatedComponent:UpdateComponent' :: UpdateComponentData
updatedComponent = UpdateComponentData
a} :: UpdateComponent)

instance Core.AWSRequest UpdateComponent where
  type
    AWSResponse UpdateComponent =
      UpdateComponentResponse
  request :: (Service -> Service) -> UpdateComponent -> Request UpdateComponent
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.patchJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateComponent
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateComponent)))
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 Component -> Int -> UpdateComponentResponse
UpdateComponentResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (forall a. FromJSON a => Object -> Either String a
Data.eitherParseJSON Object
x)
            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 UpdateComponent where
  hashWithSalt :: Int -> UpdateComponent -> Int
hashWithSalt Int
_salt UpdateComponent' {Maybe Text
Text
UpdateComponentData
updatedComponent :: UpdateComponentData
id :: Text
environmentName :: Text
appId :: Text
clientToken :: Maybe Text
$sel:updatedComponent:UpdateComponent' :: UpdateComponent -> UpdateComponentData
$sel:id:UpdateComponent' :: UpdateComponent -> Text
$sel:environmentName:UpdateComponent' :: UpdateComponent -> Text
$sel:appId:UpdateComponent' :: UpdateComponent -> Text
$sel:clientToken:UpdateComponent' :: UpdateComponent -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
appId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
environmentName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
id
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` UpdateComponentData
updatedComponent

instance Prelude.NFData UpdateComponent where
  rnf :: UpdateComponent -> ()
rnf UpdateComponent' {Maybe Text
Text
UpdateComponentData
updatedComponent :: UpdateComponentData
id :: Text
environmentName :: Text
appId :: Text
clientToken :: Maybe Text
$sel:updatedComponent:UpdateComponent' :: UpdateComponent -> UpdateComponentData
$sel:id:UpdateComponent' :: UpdateComponent -> Text
$sel:environmentName:UpdateComponent' :: UpdateComponent -> Text
$sel:appId:UpdateComponent' :: UpdateComponent -> Text
$sel:clientToken:UpdateComponent' :: UpdateComponent -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
appId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
environmentName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
id
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf UpdateComponentData
updatedComponent

instance Data.ToHeaders UpdateComponent where
  toHeaders :: UpdateComponent -> 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 UpdateComponent where
  toJSON :: UpdateComponent -> Value
toJSON UpdateComponent' {Maybe Text
Text
UpdateComponentData
updatedComponent :: UpdateComponentData
id :: Text
environmentName :: Text
appId :: Text
clientToken :: Maybe Text
$sel:updatedComponent:UpdateComponent' :: UpdateComponent -> UpdateComponentData
$sel:id:UpdateComponent' :: UpdateComponent -> Text
$sel:environmentName:UpdateComponent' :: UpdateComponent -> Text
$sel:appId:UpdateComponent' :: UpdateComponent -> Text
$sel:clientToken:UpdateComponent' :: UpdateComponent -> Maybe Text
..} =
    forall a. ToJSON a => a -> Value
Data.toJSON UpdateComponentData
updatedComponent

instance Data.ToPath UpdateComponent where
  toPath :: UpdateComponent -> ByteString
toPath UpdateComponent' {Maybe Text
Text
UpdateComponentData
updatedComponent :: UpdateComponentData
id :: Text
environmentName :: Text
appId :: Text
clientToken :: Maybe Text
$sel:updatedComponent:UpdateComponent' :: UpdateComponent -> UpdateComponentData
$sel:id:UpdateComponent' :: UpdateComponent -> Text
$sel:environmentName:UpdateComponent' :: UpdateComponent -> Text
$sel:appId:UpdateComponent' :: UpdateComponent -> Text
$sel:clientToken:UpdateComponent' :: UpdateComponent -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/app/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
appId,
        ByteString
"/environment/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
environmentName,
        ByteString
"/components/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
id
      ]

instance Data.ToQuery UpdateComponent where
  toQuery :: UpdateComponent -> QueryString
toQuery UpdateComponent' {Maybe Text
Text
UpdateComponentData
updatedComponent :: UpdateComponentData
id :: Text
environmentName :: Text
appId :: Text
clientToken :: Maybe Text
$sel:updatedComponent:UpdateComponent' :: UpdateComponent -> UpdateComponentData
$sel:id:UpdateComponent' :: UpdateComponent -> Text
$sel:environmentName:UpdateComponent' :: UpdateComponent -> Text
$sel:appId:UpdateComponent' :: UpdateComponent -> Text
$sel:clientToken:UpdateComponent' :: UpdateComponent -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"clientToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
clientToken]

-- | /See:/ 'newUpdateComponentResponse' smart constructor.
data UpdateComponentResponse = UpdateComponentResponse'
  { -- | Describes the configuration of the updated component.
    UpdateComponentResponse -> Maybe Component
entity :: Prelude.Maybe Component,
    -- | The response's http status code.
    UpdateComponentResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateComponentResponse -> UpdateComponentResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateComponentResponse -> UpdateComponentResponse -> Bool
$c/= :: UpdateComponentResponse -> UpdateComponentResponse -> Bool
== :: UpdateComponentResponse -> UpdateComponentResponse -> Bool
$c== :: UpdateComponentResponse -> UpdateComponentResponse -> Bool
Prelude.Eq, ReadPrec [UpdateComponentResponse]
ReadPrec UpdateComponentResponse
Int -> ReadS UpdateComponentResponse
ReadS [UpdateComponentResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateComponentResponse]
$creadListPrec :: ReadPrec [UpdateComponentResponse]
readPrec :: ReadPrec UpdateComponentResponse
$creadPrec :: ReadPrec UpdateComponentResponse
readList :: ReadS [UpdateComponentResponse]
$creadList :: ReadS [UpdateComponentResponse]
readsPrec :: Int -> ReadS UpdateComponentResponse
$creadsPrec :: Int -> ReadS UpdateComponentResponse
Prelude.Read, Int -> UpdateComponentResponse -> ShowS
[UpdateComponentResponse] -> ShowS
UpdateComponentResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateComponentResponse] -> ShowS
$cshowList :: [UpdateComponentResponse] -> ShowS
show :: UpdateComponentResponse -> String
$cshow :: UpdateComponentResponse -> String
showsPrec :: Int -> UpdateComponentResponse -> ShowS
$cshowsPrec :: Int -> UpdateComponentResponse -> ShowS
Prelude.Show, forall x. Rep UpdateComponentResponse x -> UpdateComponentResponse
forall x. UpdateComponentResponse -> Rep UpdateComponentResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateComponentResponse x -> UpdateComponentResponse
$cfrom :: forall x. UpdateComponentResponse -> Rep UpdateComponentResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateComponentResponse' 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:
--
-- 'entity', 'updateComponentResponse_entity' - Describes the configuration of the updated component.
--
-- 'httpStatus', 'updateComponentResponse_httpStatus' - The response's http status code.
newUpdateComponentResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateComponentResponse
newUpdateComponentResponse :: Int -> UpdateComponentResponse
newUpdateComponentResponse Int
pHttpStatus_ =
  UpdateComponentResponse'
    { $sel:entity:UpdateComponentResponse' :: Maybe Component
entity = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateComponentResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Describes the configuration of the updated component.
updateComponentResponse_entity :: Lens.Lens' UpdateComponentResponse (Prelude.Maybe Component)
updateComponentResponse_entity :: Lens' UpdateComponentResponse (Maybe Component)
updateComponentResponse_entity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateComponentResponse' {Maybe Component
entity :: Maybe Component
$sel:entity:UpdateComponentResponse' :: UpdateComponentResponse -> Maybe Component
entity} -> Maybe Component
entity) (\s :: UpdateComponentResponse
s@UpdateComponentResponse' {} Maybe Component
a -> UpdateComponentResponse
s {$sel:entity:UpdateComponentResponse' :: Maybe Component
entity = Maybe Component
a} :: UpdateComponentResponse)

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

instance Prelude.NFData UpdateComponentResponse where
  rnf :: UpdateComponentResponse -> ()
rnf UpdateComponentResponse' {Int
Maybe Component
httpStatus :: Int
entity :: Maybe Component
$sel:httpStatus:UpdateComponentResponse' :: UpdateComponentResponse -> Int
$sel:entity:UpdateComponentResponse' :: UpdateComponentResponse -> Maybe Component
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Component
entity
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus