{-# 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.GetCampaigns
-- 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 the campaigns that are associated with an application.
module Amazonka.Pinpoint.GetCampaigns
  ( -- * Creating a Request
    GetCampaigns (..),
    newGetCampaigns,

    -- * Request Lenses
    getCampaigns_pageSize,
    getCampaigns_token,
    getCampaigns_applicationId,

    -- * Destructuring the Response
    GetCampaignsResponse (..),
    newGetCampaignsResponse,

    -- * Response Lenses
    getCampaignsResponse_httpStatus,
    getCampaignsResponse_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:/ 'newGetCampaigns' smart constructor.
data GetCampaigns = GetCampaigns'
  { -- | 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.
    GetCampaigns -> Maybe Text
pageSize :: Prelude.Maybe Prelude.Text,
    -- | The NextToken string that specifies which page of results to return in a
    -- paginated response.
    GetCampaigns -> 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.
    GetCampaigns -> Text
applicationId :: Prelude.Text
  }
  deriving (GetCampaigns -> GetCampaigns -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetCampaigns -> GetCampaigns -> Bool
$c/= :: GetCampaigns -> GetCampaigns -> Bool
== :: GetCampaigns -> GetCampaigns -> Bool
$c== :: GetCampaigns -> GetCampaigns -> Bool
Prelude.Eq, ReadPrec [GetCampaigns]
ReadPrec GetCampaigns
Int -> ReadS GetCampaigns
ReadS [GetCampaigns]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetCampaigns]
$creadListPrec :: ReadPrec [GetCampaigns]
readPrec :: ReadPrec GetCampaigns
$creadPrec :: ReadPrec GetCampaigns
readList :: ReadS [GetCampaigns]
$creadList :: ReadS [GetCampaigns]
readsPrec :: Int -> ReadS GetCampaigns
$creadsPrec :: Int -> ReadS GetCampaigns
Prelude.Read, Int -> GetCampaigns -> ShowS
[GetCampaigns] -> ShowS
GetCampaigns -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetCampaigns] -> ShowS
$cshowList :: [GetCampaigns] -> ShowS
show :: GetCampaigns -> String
$cshow :: GetCampaigns -> String
showsPrec :: Int -> GetCampaigns -> ShowS
$cshowsPrec :: Int -> GetCampaigns -> ShowS
Prelude.Show, forall x. Rep GetCampaigns x -> GetCampaigns
forall x. GetCampaigns -> Rep GetCampaigns x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetCampaigns x -> GetCampaigns
$cfrom :: forall x. GetCampaigns -> Rep GetCampaigns x
Prelude.Generic)

-- |
-- Create a value of 'GetCampaigns' 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', 'getCampaigns_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', 'getCampaigns_token' - The NextToken string that specifies which page of results to return in a
-- paginated response.
--
-- 'applicationId', 'getCampaigns_applicationId' - The unique identifier for the application. This identifier is displayed
-- as the __Project ID__ on the Amazon Pinpoint console.
newGetCampaigns ::
  -- | 'applicationId'
  Prelude.Text ->
  GetCampaigns
newGetCampaigns :: Text -> GetCampaigns
newGetCampaigns Text
pApplicationId_ =
  GetCampaigns'
    { $sel:pageSize:GetCampaigns' :: Maybe Text
pageSize = forall a. Maybe a
Prelude.Nothing,
      $sel:token:GetCampaigns' :: Maybe Text
token = forall a. Maybe a
Prelude.Nothing,
      $sel:applicationId:GetCampaigns' :: Text
applicationId = Text
pApplicationId_
    }

-- | 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.
getCampaigns_pageSize :: Lens.Lens' GetCampaigns (Prelude.Maybe Prelude.Text)
getCampaigns_pageSize :: Lens' GetCampaigns (Maybe Text)
getCampaigns_pageSize = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCampaigns' {Maybe Text
pageSize :: Maybe Text
$sel:pageSize:GetCampaigns' :: GetCampaigns -> Maybe Text
pageSize} -> Maybe Text
pageSize) (\s :: GetCampaigns
s@GetCampaigns' {} Maybe Text
a -> GetCampaigns
s {$sel:pageSize:GetCampaigns' :: Maybe Text
pageSize = Maybe Text
a} :: GetCampaigns)

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

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

instance Core.AWSRequest GetCampaigns where
  type AWSResponse GetCampaigns = GetCampaignsResponse
  request :: (Service -> Service) -> GetCampaigns -> Request GetCampaigns
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 GetCampaigns
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetCampaigns)))
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 -> GetCampaignsResponse
GetCampaignsResponse'
            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 GetCampaigns where
  hashWithSalt :: Int -> GetCampaigns -> Int
hashWithSalt Int
_salt GetCampaigns' {Maybe Text
Text
applicationId :: Text
token :: Maybe Text
pageSize :: Maybe Text
$sel:applicationId:GetCampaigns' :: GetCampaigns -> Text
$sel:token:GetCampaigns' :: GetCampaigns -> Maybe Text
$sel:pageSize:GetCampaigns' :: GetCampaigns -> 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

instance Prelude.NFData GetCampaigns where
  rnf :: GetCampaigns -> ()
rnf GetCampaigns' {Maybe Text
Text
applicationId :: Text
token :: Maybe Text
pageSize :: Maybe Text
$sel:applicationId:GetCampaigns' :: GetCampaigns -> Text
$sel:token:GetCampaigns' :: GetCampaigns -> Maybe Text
$sel:pageSize:GetCampaigns' :: GetCampaigns -> 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

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

instance Data.ToQuery GetCampaigns where
  toQuery :: GetCampaigns -> QueryString
toQuery GetCampaigns' {Maybe Text
Text
applicationId :: Text
token :: Maybe Text
pageSize :: Maybe Text
$sel:applicationId:GetCampaigns' :: GetCampaigns -> Text
$sel:token:GetCampaigns' :: GetCampaigns -> Maybe Text
$sel:pageSize:GetCampaigns' :: GetCampaigns -> 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:/ 'newGetCampaignsResponse' smart constructor.
data GetCampaignsResponse = GetCampaignsResponse'
  { -- | The response's http status code.
    GetCampaignsResponse -> Int
httpStatus :: Prelude.Int,
    GetCampaignsResponse -> CampaignsResponse
campaignsResponse :: CampaignsResponse
  }
  deriving (GetCampaignsResponse -> GetCampaignsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetCampaignsResponse -> GetCampaignsResponse -> Bool
$c/= :: GetCampaignsResponse -> GetCampaignsResponse -> Bool
== :: GetCampaignsResponse -> GetCampaignsResponse -> Bool
$c== :: GetCampaignsResponse -> GetCampaignsResponse -> Bool
Prelude.Eq, ReadPrec [GetCampaignsResponse]
ReadPrec GetCampaignsResponse
Int -> ReadS GetCampaignsResponse
ReadS [GetCampaignsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetCampaignsResponse]
$creadListPrec :: ReadPrec [GetCampaignsResponse]
readPrec :: ReadPrec GetCampaignsResponse
$creadPrec :: ReadPrec GetCampaignsResponse
readList :: ReadS [GetCampaignsResponse]
$creadList :: ReadS [GetCampaignsResponse]
readsPrec :: Int -> ReadS GetCampaignsResponse
$creadsPrec :: Int -> ReadS GetCampaignsResponse
Prelude.Read, Int -> GetCampaignsResponse -> ShowS
[GetCampaignsResponse] -> ShowS
GetCampaignsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetCampaignsResponse] -> ShowS
$cshowList :: [GetCampaignsResponse] -> ShowS
show :: GetCampaignsResponse -> String
$cshow :: GetCampaignsResponse -> String
showsPrec :: Int -> GetCampaignsResponse -> ShowS
$cshowsPrec :: Int -> GetCampaignsResponse -> ShowS
Prelude.Show, forall x. Rep GetCampaignsResponse x -> GetCampaignsResponse
forall x. GetCampaignsResponse -> Rep GetCampaignsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetCampaignsResponse x -> GetCampaignsResponse
$cfrom :: forall x. GetCampaignsResponse -> Rep GetCampaignsResponse x
Prelude.Generic)

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

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

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

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