{-# 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.GetApps
-- 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 all the applications that are associated
-- with your Amazon Pinpoint account.
module Amazonka.Pinpoint.GetApps
  ( -- * Creating a Request
    GetApps (..),
    newGetApps,

    -- * Request Lenses
    getApps_pageSize,
    getApps_token,

    -- * Destructuring the Response
    GetAppsResponse (..),
    newGetAppsResponse,

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

-- |
-- Create a value of 'GetApps' 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', 'getApps_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', 'getApps_token' - The NextToken string that specifies which page of results to return in a
-- paginated response.
newGetApps ::
  GetApps
newGetApps :: GetApps
newGetApps =
  GetApps'
    { $sel:pageSize:GetApps' :: Maybe Text
pageSize = forall a. Maybe a
Prelude.Nothing,
      $sel:token:GetApps' :: Maybe Text
token = forall a. Maybe a
Prelude.Nothing
    }

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

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

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

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

instance Data.ToHeaders GetApps where
  toHeaders :: GetApps -> 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 GetApps where
  toPath :: GetApps -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/v1/apps"

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

-- |
-- Create a value of 'GetAppsResponse' 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', 'getAppsResponse_httpStatus' - The response's http status code.
--
-- 'applicationsResponse', 'getAppsResponse_applicationsResponse' - Undocumented member.
newGetAppsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'applicationsResponse'
  ApplicationsResponse ->
  GetAppsResponse
newGetAppsResponse :: Int -> ApplicationsResponse -> GetAppsResponse
newGetAppsResponse
  Int
pHttpStatus_
  ApplicationsResponse
pApplicationsResponse_ =
    GetAppsResponse'
      { $sel:httpStatus:GetAppsResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:applicationsResponse:GetAppsResponse' :: ApplicationsResponse
applicationsResponse = ApplicationsResponse
pApplicationsResponse_
      }

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

-- | Undocumented member.
getAppsResponse_applicationsResponse :: Lens.Lens' GetAppsResponse ApplicationsResponse
getAppsResponse_applicationsResponse :: Lens' GetAppsResponse ApplicationsResponse
getAppsResponse_applicationsResponse = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAppsResponse' {ApplicationsResponse
applicationsResponse :: ApplicationsResponse
$sel:applicationsResponse:GetAppsResponse' :: GetAppsResponse -> ApplicationsResponse
applicationsResponse} -> ApplicationsResponse
applicationsResponse) (\s :: GetAppsResponse
s@GetAppsResponse' {} ApplicationsResponse
a -> GetAppsResponse
s {$sel:applicationsResponse:GetAppsResponse' :: ApplicationsResponse
applicationsResponse = ApplicationsResponse
a} :: GetAppsResponse)

instance Prelude.NFData GetAppsResponse where
  rnf :: GetAppsResponse -> ()
rnf GetAppsResponse' {Int
ApplicationsResponse
applicationsResponse :: ApplicationsResponse
httpStatus :: Int
$sel:applicationsResponse:GetAppsResponse' :: GetAppsResponse -> ApplicationsResponse
$sel:httpStatus:GetAppsResponse' :: GetAppsResponse -> 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 ApplicationsResponse
applicationsResponse