{-# 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.GetCampaignVersions
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves information about the status, configuration, and other
-- settings for all versions of a campaign.
module Amazonka.Pinpoint.GetCampaignVersions
  ( -- * Creating a Request
    GetCampaignVersions (..),
    newGetCampaignVersions,

    -- * Request Lenses
    getCampaignVersions_pageSize,
    getCampaignVersions_token,
    getCampaignVersions_applicationId,
    getCampaignVersions_campaignId,

    -- * Destructuring the Response
    GetCampaignVersionsResponse (..),
    newGetCampaignVersionsResponse,

    -- * Response Lenses
    getCampaignVersionsResponse_httpStatus,
    getCampaignVersionsResponse_campaignsResponse,
  )
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:/ 'newGetCampaignVersions' smart constructor.
data GetCampaignVersions = GetCampaignVersions'
  { -- | The maximum number of items to include in each page of a paginated
    -- response. This parameter is not supported for application, campaign, and
    -- journey metrics.
    GetCampaignVersions -> Maybe Text
pageSize :: Prelude.Maybe Prelude.Text,
    -- | The NextToken string that specifies which page of results to return in a
    -- paginated response.
    GetCampaignVersions -> Maybe Text
token :: Prelude.Maybe Prelude.Text,
    -- | The unique identifier for the application. This identifier is displayed
    -- as the __Project ID__ on the Amazon Pinpoint console.
    GetCampaignVersions -> Text
applicationId :: Prelude.Text,
    -- | The unique identifier for the campaign.
    GetCampaignVersions -> Text
campaignId :: Prelude.Text
  }
  deriving (GetCampaignVersions -> GetCampaignVersions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetCampaignVersions -> GetCampaignVersions -> Bool
$c/= :: GetCampaignVersions -> GetCampaignVersions -> Bool
== :: GetCampaignVersions -> GetCampaignVersions -> Bool
$c== :: GetCampaignVersions -> GetCampaignVersions -> Bool
Prelude.Eq, ReadPrec [GetCampaignVersions]
ReadPrec GetCampaignVersions
Int -> ReadS GetCampaignVersions
ReadS [GetCampaignVersions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetCampaignVersions]
$creadListPrec :: ReadPrec [GetCampaignVersions]
readPrec :: ReadPrec GetCampaignVersions
$creadPrec :: ReadPrec GetCampaignVersions
readList :: ReadS [GetCampaignVersions]
$creadList :: ReadS [GetCampaignVersions]
readsPrec :: Int -> ReadS GetCampaignVersions
$creadsPrec :: Int -> ReadS GetCampaignVersions
Prelude.Read, Int -> GetCampaignVersions -> ShowS
[GetCampaignVersions] -> ShowS
GetCampaignVersions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetCampaignVersions] -> ShowS
$cshowList :: [GetCampaignVersions] -> ShowS
show :: GetCampaignVersions -> String
$cshow :: GetCampaignVersions -> String
showsPrec :: Int -> GetCampaignVersions -> ShowS
$cshowsPrec :: Int -> GetCampaignVersions -> ShowS
Prelude.Show, forall x. Rep GetCampaignVersions x -> GetCampaignVersions
forall x. GetCampaignVersions -> Rep GetCampaignVersions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetCampaignVersions x -> GetCampaignVersions
$cfrom :: forall x. GetCampaignVersions -> Rep GetCampaignVersions x
Prelude.Generic)

-- |
-- Create a value of 'GetCampaignVersions' 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:
--
-- 'pageSize', 'getCampaignVersions_pageSize' - The maximum number of items to include in each page of a paginated
-- response. This parameter is not supported for application, campaign, and
-- journey metrics.
--
-- 'token', 'getCampaignVersions_token' - The NextToken string that specifies which page of results to return in a
-- paginated response.
--
-- 'applicationId', 'getCampaignVersions_applicationId' - The unique identifier for the application. This identifier is displayed
-- as the __Project ID__ on the Amazon Pinpoint console.
--
-- 'campaignId', 'getCampaignVersions_campaignId' - The unique identifier for the campaign.
newGetCampaignVersions ::
  -- | 'applicationId'
  Prelude.Text ->
  -- | 'campaignId'
  Prelude.Text ->
  GetCampaignVersions
newGetCampaignVersions :: Text -> Text -> GetCampaignVersions
newGetCampaignVersions Text
pApplicationId_ Text
pCampaignId_ =
  GetCampaignVersions'
    { $sel:pageSize:GetCampaignVersions' :: Maybe Text
pageSize = forall a. Maybe a
Prelude.Nothing,
      $sel:token:GetCampaignVersions' :: Maybe Text
token = forall a. Maybe a
Prelude.Nothing,
      $sel:applicationId:GetCampaignVersions' :: Text
applicationId = Text
pApplicationId_,
      $sel:campaignId:GetCampaignVersions' :: Text
campaignId = Text
pCampaignId_
    }

-- | The maximum number of items to include in each page of a paginated
-- response. This parameter is not supported for application, campaign, and
-- journey metrics.
getCampaignVersions_pageSize :: Lens.Lens' GetCampaignVersions (Prelude.Maybe Prelude.Text)
getCampaignVersions_pageSize :: Lens' GetCampaignVersions (Maybe Text)
getCampaignVersions_pageSize = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCampaignVersions' {Maybe Text
pageSize :: Maybe Text
$sel:pageSize:GetCampaignVersions' :: GetCampaignVersions -> Maybe Text
pageSize} -> Maybe Text
pageSize) (\s :: GetCampaignVersions
s@GetCampaignVersions' {} Maybe Text
a -> GetCampaignVersions
s {$sel:pageSize:GetCampaignVersions' :: Maybe Text
pageSize = Maybe Text
a} :: GetCampaignVersions)

-- | The NextToken string that specifies which page of results to return in a
-- paginated response.
getCampaignVersions_token :: Lens.Lens' GetCampaignVersions (Prelude.Maybe Prelude.Text)
getCampaignVersions_token :: Lens' GetCampaignVersions (Maybe Text)
getCampaignVersions_token = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCampaignVersions' {Maybe Text
token :: Maybe Text
$sel:token:GetCampaignVersions' :: GetCampaignVersions -> Maybe Text
token} -> Maybe Text
token) (\s :: GetCampaignVersions
s@GetCampaignVersions' {} Maybe Text
a -> GetCampaignVersions
s {$sel:token:GetCampaignVersions' :: Maybe Text
token = Maybe Text
a} :: GetCampaignVersions)

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

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

instance Core.AWSRequest GetCampaignVersions where
  type
    AWSResponse GetCampaignVersions =
      GetCampaignVersionsResponse
  request :: (Service -> Service)
-> GetCampaignVersions -> Request GetCampaignVersions
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetCampaignVersions
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetCampaignVersions)))
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 -> CampaignsResponse -> GetCampaignVersionsResponse
GetCampaignVersionsResponse'
            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 GetCampaignVersions where
  hashWithSalt :: Int -> GetCampaignVersions -> Int
hashWithSalt Int
_salt GetCampaignVersions' {Maybe Text
Text
campaignId :: Text
applicationId :: Text
token :: Maybe Text
pageSize :: Maybe Text
$sel:campaignId:GetCampaignVersions' :: GetCampaignVersions -> Text
$sel:applicationId:GetCampaignVersions' :: GetCampaignVersions -> Text
$sel:token:GetCampaignVersions' :: GetCampaignVersions -> Maybe Text
$sel:pageSize:GetCampaignVersions' :: GetCampaignVersions -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
pageSize
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
token
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
applicationId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
campaignId

instance Prelude.NFData GetCampaignVersions where
  rnf :: GetCampaignVersions -> ()
rnf GetCampaignVersions' {Maybe Text
Text
campaignId :: Text
applicationId :: Text
token :: Maybe Text
pageSize :: Maybe Text
$sel:campaignId:GetCampaignVersions' :: GetCampaignVersions -> Text
$sel:applicationId:GetCampaignVersions' :: GetCampaignVersions -> Text
$sel:token:GetCampaignVersions' :: GetCampaignVersions -> Maybe Text
$sel:pageSize:GetCampaignVersions' :: GetCampaignVersions -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
pageSize
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
token
      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 Text
campaignId

instance Data.ToHeaders GetCampaignVersions where
  toHeaders :: GetCampaignVersions -> 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.ToPath GetCampaignVersions where
  toPath :: GetCampaignVersions -> ByteString
toPath GetCampaignVersions' {Maybe Text
Text
campaignId :: Text
applicationId :: Text
token :: Maybe Text
pageSize :: Maybe Text
$sel:campaignId:GetCampaignVersions' :: GetCampaignVersions -> Text
$sel:applicationId:GetCampaignVersions' :: GetCampaignVersions -> Text
$sel:token:GetCampaignVersions' :: GetCampaignVersions -> Maybe Text
$sel:pageSize:GetCampaignVersions' :: GetCampaignVersions -> Maybe 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,
        ByteString
"/versions"
      ]

instance Data.ToQuery GetCampaignVersions where
  toQuery :: GetCampaignVersions -> QueryString
toQuery GetCampaignVersions' {Maybe Text
Text
campaignId :: Text
applicationId :: Text
token :: Maybe Text
pageSize :: Maybe Text
$sel:campaignId:GetCampaignVersions' :: GetCampaignVersions -> Text
$sel:applicationId:GetCampaignVersions' :: GetCampaignVersions -> Text
$sel:token:GetCampaignVersions' :: GetCampaignVersions -> Maybe Text
$sel:pageSize:GetCampaignVersions' :: GetCampaignVersions -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"page-size" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
pageSize, ByteString
"token" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
token]

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

-- |
-- Create a value of 'GetCampaignVersionsResponse' 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', 'getCampaignVersionsResponse_httpStatus' - The response's http status code.
--
-- 'campaignsResponse', 'getCampaignVersionsResponse_campaignsResponse' - Undocumented member.
newGetCampaignVersionsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'campaignsResponse'
  CampaignsResponse ->
  GetCampaignVersionsResponse
newGetCampaignVersionsResponse :: Int -> CampaignsResponse -> GetCampaignVersionsResponse
newGetCampaignVersionsResponse
  Int
pHttpStatus_
  CampaignsResponse
pCampaignsResponse_ =
    GetCampaignVersionsResponse'
      { $sel:httpStatus:GetCampaignVersionsResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:campaignsResponse:GetCampaignVersionsResponse' :: CampaignsResponse
campaignsResponse = CampaignsResponse
pCampaignsResponse_
      }

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

-- | Undocumented member.
getCampaignVersionsResponse_campaignsResponse :: Lens.Lens' GetCampaignVersionsResponse CampaignsResponse
getCampaignVersionsResponse_campaignsResponse :: Lens' GetCampaignVersionsResponse CampaignsResponse
getCampaignVersionsResponse_campaignsResponse = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCampaignVersionsResponse' {CampaignsResponse
campaignsResponse :: CampaignsResponse
$sel:campaignsResponse:GetCampaignVersionsResponse' :: GetCampaignVersionsResponse -> CampaignsResponse
campaignsResponse} -> CampaignsResponse
campaignsResponse) (\s :: GetCampaignVersionsResponse
s@GetCampaignVersionsResponse' {} CampaignsResponse
a -> GetCampaignVersionsResponse
s {$sel:campaignsResponse:GetCampaignVersionsResponse' :: CampaignsResponse
campaignsResponse = CampaignsResponse
a} :: GetCampaignVersionsResponse)

instance Prelude.NFData GetCampaignVersionsResponse where
  rnf :: GetCampaignVersionsResponse -> ()
rnf GetCampaignVersionsResponse' {Int
CampaignsResponse
campaignsResponse :: CampaignsResponse
httpStatus :: Int
$sel:campaignsResponse:GetCampaignVersionsResponse' :: GetCampaignVersionsResponse -> CampaignsResponse
$sel:httpStatus:GetCampaignVersionsResponse' :: GetCampaignVersionsResponse -> 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 CampaignsResponse
campaignsResponse