{-# 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.Pinpoint.UpdateCampaign
-- 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 the configuration and other settings for a campaign.
module Amazonka.Pinpoint.UpdateCampaign
  ( -- * Creating a Request
    UpdateCampaign (..),
    newUpdateCampaign,

    -- * Request Lenses
    updateCampaign_campaignId,
    updateCampaign_applicationId,
    updateCampaign_writeCampaignRequest,

    -- * Destructuring the Response
    UpdateCampaignResponse (..),
    newUpdateCampaignResponse,

    -- * Response Lenses
    updateCampaignResponse_httpStatus,
    updateCampaignResponse_campaignResponse,
  )
where

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

-- | /See:/ 'newUpdateCampaign' smart constructor.
data UpdateCampaign = UpdateCampaign'
  { -- | The unique identifier for the campaign.
    UpdateCampaign -> Text
campaignId :: Prelude.Text,
    -- | The unique identifier for the application. This identifier is displayed
    -- as the __Project ID__ on the Amazon Pinpoint console.
    UpdateCampaign -> Text
applicationId :: Prelude.Text,
    UpdateCampaign -> WriteCampaignRequest
writeCampaignRequest :: WriteCampaignRequest
  }
  deriving (UpdateCampaign -> UpdateCampaign -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateCampaign -> UpdateCampaign -> Bool
$c/= :: UpdateCampaign -> UpdateCampaign -> Bool
== :: UpdateCampaign -> UpdateCampaign -> Bool
$c== :: UpdateCampaign -> UpdateCampaign -> Bool
Prelude.Eq, ReadPrec [UpdateCampaign]
ReadPrec UpdateCampaign
Int -> ReadS UpdateCampaign
ReadS [UpdateCampaign]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateCampaign]
$creadListPrec :: ReadPrec [UpdateCampaign]
readPrec :: ReadPrec UpdateCampaign
$creadPrec :: ReadPrec UpdateCampaign
readList :: ReadS [UpdateCampaign]
$creadList :: ReadS [UpdateCampaign]
readsPrec :: Int -> ReadS UpdateCampaign
$creadsPrec :: Int -> ReadS UpdateCampaign
Prelude.Read, Int -> UpdateCampaign -> ShowS
[UpdateCampaign] -> ShowS
UpdateCampaign -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateCampaign] -> ShowS
$cshowList :: [UpdateCampaign] -> ShowS
show :: UpdateCampaign -> String
$cshow :: UpdateCampaign -> String
showsPrec :: Int -> UpdateCampaign -> ShowS
$cshowsPrec :: Int -> UpdateCampaign -> ShowS
Prelude.Show, forall x. Rep UpdateCampaign x -> UpdateCampaign
forall x. UpdateCampaign -> Rep UpdateCampaign x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateCampaign x -> UpdateCampaign
$cfrom :: forall x. UpdateCampaign -> Rep UpdateCampaign x
Prelude.Generic)

-- |
-- Create a value of 'UpdateCampaign' 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:
--
-- 'campaignId', 'updateCampaign_campaignId' - The unique identifier for the campaign.
--
-- 'applicationId', 'updateCampaign_applicationId' - The unique identifier for the application. This identifier is displayed
-- as the __Project ID__ on the Amazon Pinpoint console.
--
-- 'writeCampaignRequest', 'updateCampaign_writeCampaignRequest' - Undocumented member.
newUpdateCampaign ::
  -- | 'campaignId'
  Prelude.Text ->
  -- | 'applicationId'
  Prelude.Text ->
  -- | 'writeCampaignRequest'
  WriteCampaignRequest ->
  UpdateCampaign
newUpdateCampaign :: Text -> Text -> WriteCampaignRequest -> UpdateCampaign
newUpdateCampaign
  Text
pCampaignId_
  Text
pApplicationId_
  WriteCampaignRequest
pWriteCampaignRequest_ =
    UpdateCampaign'
      { $sel:campaignId:UpdateCampaign' :: Text
campaignId = Text
pCampaignId_,
        $sel:applicationId:UpdateCampaign' :: Text
applicationId = Text
pApplicationId_,
        $sel:writeCampaignRequest:UpdateCampaign' :: WriteCampaignRequest
writeCampaignRequest = WriteCampaignRequest
pWriteCampaignRequest_
      }

-- | The unique identifier for the campaign.
updateCampaign_campaignId :: Lens.Lens' UpdateCampaign Prelude.Text
updateCampaign_campaignId :: Lens' UpdateCampaign Text
updateCampaign_campaignId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCampaign' {Text
campaignId :: Text
$sel:campaignId:UpdateCampaign' :: UpdateCampaign -> Text
campaignId} -> Text
campaignId) (\s :: UpdateCampaign
s@UpdateCampaign' {} Text
a -> UpdateCampaign
s {$sel:campaignId:UpdateCampaign' :: Text
campaignId = Text
a} :: UpdateCampaign)

-- | The unique identifier for the application. This identifier is displayed
-- as the __Project ID__ on the Amazon Pinpoint console.
updateCampaign_applicationId :: Lens.Lens' UpdateCampaign Prelude.Text
updateCampaign_applicationId :: Lens' UpdateCampaign Text
updateCampaign_applicationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCampaign' {Text
applicationId :: Text
$sel:applicationId:UpdateCampaign' :: UpdateCampaign -> Text
applicationId} -> Text
applicationId) (\s :: UpdateCampaign
s@UpdateCampaign' {} Text
a -> UpdateCampaign
s {$sel:applicationId:UpdateCampaign' :: Text
applicationId = Text
a} :: UpdateCampaign)

-- | Undocumented member.
updateCampaign_writeCampaignRequest :: Lens.Lens' UpdateCampaign WriteCampaignRequest
updateCampaign_writeCampaignRequest :: Lens' UpdateCampaign WriteCampaignRequest
updateCampaign_writeCampaignRequest = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCampaign' {WriteCampaignRequest
writeCampaignRequest :: WriteCampaignRequest
$sel:writeCampaignRequest:UpdateCampaign' :: UpdateCampaign -> WriteCampaignRequest
writeCampaignRequest} -> WriteCampaignRequest
writeCampaignRequest) (\s :: UpdateCampaign
s@UpdateCampaign' {} WriteCampaignRequest
a -> UpdateCampaign
s {$sel:writeCampaignRequest:UpdateCampaign' :: WriteCampaignRequest
writeCampaignRequest = WriteCampaignRequest
a} :: UpdateCampaign)

instance Core.AWSRequest UpdateCampaign where
  type
    AWSResponse UpdateCampaign =
      UpdateCampaignResponse
  request :: (Service -> Service) -> UpdateCampaign -> Request UpdateCampaign
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.putJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateCampaign
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateCampaign)))
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 ->
          Int -> CampaignResponse -> UpdateCampaignResponse
UpdateCampaignResponse'
            forall (f :: * -> *) a b. Functor 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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall a. FromJSON a => Object -> Either String a
Data.eitherParseJSON Object
x)
      )

instance Prelude.Hashable UpdateCampaign where
  hashWithSalt :: Int -> UpdateCampaign -> Int
hashWithSalt Int
_salt UpdateCampaign' {Text
WriteCampaignRequest
writeCampaignRequest :: WriteCampaignRequest
applicationId :: Text
campaignId :: Text
$sel:writeCampaignRequest:UpdateCampaign' :: UpdateCampaign -> WriteCampaignRequest
$sel:applicationId:UpdateCampaign' :: UpdateCampaign -> Text
$sel:campaignId:UpdateCampaign' :: UpdateCampaign -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
campaignId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
applicationId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` WriteCampaignRequest
writeCampaignRequest

instance Prelude.NFData UpdateCampaign where
  rnf :: UpdateCampaign -> ()
rnf UpdateCampaign' {Text
WriteCampaignRequest
writeCampaignRequest :: WriteCampaignRequest
applicationId :: Text
campaignId :: Text
$sel:writeCampaignRequest:UpdateCampaign' :: UpdateCampaign -> WriteCampaignRequest
$sel:applicationId:UpdateCampaign' :: UpdateCampaign -> Text
$sel:campaignId:UpdateCampaign' :: UpdateCampaign -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
campaignId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
applicationId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf WriteCampaignRequest
writeCampaignRequest

instance Data.ToHeaders UpdateCampaign where
  toHeaders :: UpdateCampaign -> 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 UpdateCampaign where
  toJSON :: UpdateCampaign -> Value
toJSON UpdateCampaign' {Text
WriteCampaignRequest
writeCampaignRequest :: WriteCampaignRequest
applicationId :: Text
campaignId :: Text
$sel:writeCampaignRequest:UpdateCampaign' :: UpdateCampaign -> WriteCampaignRequest
$sel:applicationId:UpdateCampaign' :: UpdateCampaign -> Text
$sel:campaignId:UpdateCampaign' :: UpdateCampaign -> Text
..} =
    forall a. ToJSON a => a -> Value
Data.toJSON WriteCampaignRequest
writeCampaignRequest

instance Data.ToPath UpdateCampaign where
  toPath :: UpdateCampaign -> ByteString
toPath UpdateCampaign' {Text
WriteCampaignRequest
writeCampaignRequest :: WriteCampaignRequest
applicationId :: Text
campaignId :: Text
$sel:writeCampaignRequest:UpdateCampaign' :: UpdateCampaign -> WriteCampaignRequest
$sel:applicationId:UpdateCampaign' :: UpdateCampaign -> Text
$sel:campaignId:UpdateCampaign' :: UpdateCampaign -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/v1/apps/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
applicationId,
        ByteString
"/campaigns/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
campaignId
      ]

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

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

-- |
-- Create a value of 'UpdateCampaignResponse' 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:
--
-- 'httpStatus', 'updateCampaignResponse_httpStatus' - The response's http status code.
--
-- 'campaignResponse', 'updateCampaignResponse_campaignResponse' - Undocumented member.
newUpdateCampaignResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'campaignResponse'
  CampaignResponse ->
  UpdateCampaignResponse
newUpdateCampaignResponse :: Int -> CampaignResponse -> UpdateCampaignResponse
newUpdateCampaignResponse
  Int
pHttpStatus_
  CampaignResponse
pCampaignResponse_ =
    UpdateCampaignResponse'
      { $sel:httpStatus:UpdateCampaignResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:campaignResponse:UpdateCampaignResponse' :: CampaignResponse
campaignResponse = CampaignResponse
pCampaignResponse_
      }

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

-- | Undocumented member.
updateCampaignResponse_campaignResponse :: Lens.Lens' UpdateCampaignResponse CampaignResponse
updateCampaignResponse_campaignResponse :: Lens' UpdateCampaignResponse CampaignResponse
updateCampaignResponse_campaignResponse = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCampaignResponse' {CampaignResponse
campaignResponse :: CampaignResponse
$sel:campaignResponse:UpdateCampaignResponse' :: UpdateCampaignResponse -> CampaignResponse
campaignResponse} -> CampaignResponse
campaignResponse) (\s :: UpdateCampaignResponse
s@UpdateCampaignResponse' {} CampaignResponse
a -> UpdateCampaignResponse
s {$sel:campaignResponse:UpdateCampaignResponse' :: CampaignResponse
campaignResponse = CampaignResponse
a} :: UpdateCampaignResponse)

instance Prelude.NFData UpdateCampaignResponse where
  rnf :: UpdateCampaignResponse -> ()
rnf UpdateCampaignResponse' {Int
CampaignResponse
campaignResponse :: CampaignResponse
httpStatus :: Int
$sel:campaignResponse:UpdateCampaignResponse' :: UpdateCampaignResponse -> CampaignResponse
$sel:httpStatus:UpdateCampaignResponse' :: UpdateCampaignResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf CampaignResponse
campaignResponse