{-# 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.GetExportJobs
-- 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 and settings of all the export
-- jobs for an application.
module Amazonka.Pinpoint.GetExportJobs
  ( -- * Creating a Request
    GetExportJobs (..),
    newGetExportJobs,

    -- * Request Lenses
    getExportJobs_pageSize,
    getExportJobs_token,
    getExportJobs_applicationId,

    -- * Destructuring the Response
    GetExportJobsResponse (..),
    newGetExportJobsResponse,

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

-- |
-- Create a value of 'GetExportJobs' 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', 'getExportJobs_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', 'getExportJobs_token' - The NextToken string that specifies which page of results to return in a
-- paginated response.
--
-- 'applicationId', 'getExportJobs_applicationId' - The unique identifier for the application. This identifier is displayed
-- as the __Project ID__ on the Amazon Pinpoint console.
newGetExportJobs ::
  -- | 'applicationId'
  Prelude.Text ->
  GetExportJobs
newGetExportJobs :: Text -> GetExportJobs
newGetExportJobs Text
pApplicationId_ =
  GetExportJobs'
    { $sel:pageSize:GetExportJobs' :: Maybe Text
pageSize = forall a. Maybe a
Prelude.Nothing,
      $sel:token:GetExportJobs' :: Maybe Text
token = forall a. Maybe a
Prelude.Nothing,
      $sel:applicationId:GetExportJobs' :: 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.
getExportJobs_pageSize :: Lens.Lens' GetExportJobs (Prelude.Maybe Prelude.Text)
getExportJobs_pageSize :: Lens' GetExportJobs (Maybe Text)
getExportJobs_pageSize = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetExportJobs' {Maybe Text
pageSize :: Maybe Text
$sel:pageSize:GetExportJobs' :: GetExportJobs -> Maybe Text
pageSize} -> Maybe Text
pageSize) (\s :: GetExportJobs
s@GetExportJobs' {} Maybe Text
a -> GetExportJobs
s {$sel:pageSize:GetExportJobs' :: Maybe Text
pageSize = Maybe Text
a} :: GetExportJobs)

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

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

instance Core.AWSRequest GetExportJobs where
  type
    AWSResponse GetExportJobs =
      GetExportJobsResponse
  request :: (Service -> Service) -> GetExportJobs -> Request GetExportJobs
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 GetExportJobs
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetExportJobs)))
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 -> ExportJobsResponse -> GetExportJobsResponse
GetExportJobsResponse'
            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 GetExportJobs where
  hashWithSalt :: Int -> GetExportJobs -> Int
hashWithSalt Int
_salt GetExportJobs' {Maybe Text
Text
applicationId :: Text
token :: Maybe Text
pageSize :: Maybe Text
$sel:applicationId:GetExportJobs' :: GetExportJobs -> Text
$sel:token:GetExportJobs' :: GetExportJobs -> Maybe Text
$sel:pageSize:GetExportJobs' :: GetExportJobs -> 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 GetExportJobs where
  rnf :: GetExportJobs -> ()
rnf GetExportJobs' {Maybe Text
Text
applicationId :: Text
token :: Maybe Text
pageSize :: Maybe Text
$sel:applicationId:GetExportJobs' :: GetExportJobs -> Text
$sel:token:GetExportJobs' :: GetExportJobs -> Maybe Text
$sel:pageSize:GetExportJobs' :: GetExportJobs -> 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 GetExportJobs where
  toHeaders :: GetExportJobs -> 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 GetExportJobs where
  toPath :: GetExportJobs -> ByteString
toPath GetExportJobs' {Maybe Text
Text
applicationId :: Text
token :: Maybe Text
pageSize :: Maybe Text
$sel:applicationId:GetExportJobs' :: GetExportJobs -> Text
$sel:token:GetExportJobs' :: GetExportJobs -> Maybe Text
$sel:pageSize:GetExportJobs' :: GetExportJobs -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/v1/apps/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
applicationId,
        ByteString
"/jobs/export"
      ]

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

-- |
-- Create a value of 'GetExportJobsResponse' 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', 'getExportJobsResponse_httpStatus' - The response's http status code.
--
-- 'exportJobsResponse', 'getExportJobsResponse_exportJobsResponse' - Undocumented member.
newGetExportJobsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'exportJobsResponse'
  ExportJobsResponse ->
  GetExportJobsResponse
newGetExportJobsResponse :: Int -> ExportJobsResponse -> GetExportJobsResponse
newGetExportJobsResponse
  Int
pHttpStatus_
  ExportJobsResponse
pExportJobsResponse_ =
    GetExportJobsResponse'
      { $sel:httpStatus:GetExportJobsResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:exportJobsResponse:GetExportJobsResponse' :: ExportJobsResponse
exportJobsResponse = ExportJobsResponse
pExportJobsResponse_
      }

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

-- | Undocumented member.
getExportJobsResponse_exportJobsResponse :: Lens.Lens' GetExportJobsResponse ExportJobsResponse
getExportJobsResponse_exportJobsResponse :: Lens' GetExportJobsResponse ExportJobsResponse
getExportJobsResponse_exportJobsResponse = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetExportJobsResponse' {ExportJobsResponse
exportJobsResponse :: ExportJobsResponse
$sel:exportJobsResponse:GetExportJobsResponse' :: GetExportJobsResponse -> ExportJobsResponse
exportJobsResponse} -> ExportJobsResponse
exportJobsResponse) (\s :: GetExportJobsResponse
s@GetExportJobsResponse' {} ExportJobsResponse
a -> GetExportJobsResponse
s {$sel:exportJobsResponse:GetExportJobsResponse' :: ExportJobsResponse
exportJobsResponse = ExportJobsResponse
a} :: GetExportJobsResponse)

instance Prelude.NFData GetExportJobsResponse where
  rnf :: GetExportJobsResponse -> ()
rnf GetExportJobsResponse' {Int
ExportJobsResponse
exportJobsResponse :: ExportJobsResponse
httpStatus :: Int
$sel:exportJobsResponse:GetExportJobsResponse' :: GetExportJobsResponse -> ExportJobsResponse
$sel:httpStatus:GetExportJobsResponse' :: GetExportJobsResponse -> 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 ExportJobsResponse
exportJobsResponse