{-# 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.GetSegments
-- 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 configuration, dimension, and other
-- settings for all the segments that are associated with an application.
module Amazonka.Pinpoint.GetSegments
  ( -- * Creating a Request
    GetSegments (..),
    newGetSegments,

    -- * Request Lenses
    getSegments_pageSize,
    getSegments_token,
    getSegments_applicationId,

    -- * Destructuring the Response
    GetSegmentsResponse (..),
    newGetSegmentsResponse,

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

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

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

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

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

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

-- |
-- Create a value of 'GetSegmentsResponse' 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', 'getSegmentsResponse_httpStatus' - The response's http status code.
--
-- 'segmentsResponse', 'getSegmentsResponse_segmentsResponse' - Undocumented member.
newGetSegmentsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'segmentsResponse'
  SegmentsResponse ->
  GetSegmentsResponse
newGetSegmentsResponse :: Int -> SegmentsResponse -> GetSegmentsResponse
newGetSegmentsResponse
  Int
pHttpStatus_
  SegmentsResponse
pSegmentsResponse_ =
    GetSegmentsResponse'
      { $sel:httpStatus:GetSegmentsResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:segmentsResponse:GetSegmentsResponse' :: SegmentsResponse
segmentsResponse = SegmentsResponse
pSegmentsResponse_
      }

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

-- | Undocumented member.
getSegmentsResponse_segmentsResponse :: Lens.Lens' GetSegmentsResponse SegmentsResponse
getSegmentsResponse_segmentsResponse :: Lens' GetSegmentsResponse SegmentsResponse
getSegmentsResponse_segmentsResponse = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSegmentsResponse' {SegmentsResponse
segmentsResponse :: SegmentsResponse
$sel:segmentsResponse:GetSegmentsResponse' :: GetSegmentsResponse -> SegmentsResponse
segmentsResponse} -> SegmentsResponse
segmentsResponse) (\s :: GetSegmentsResponse
s@GetSegmentsResponse' {} SegmentsResponse
a -> GetSegmentsResponse
s {$sel:segmentsResponse:GetSegmentsResponse' :: SegmentsResponse
segmentsResponse = SegmentsResponse
a} :: GetSegmentsResponse)

instance Prelude.NFData GetSegmentsResponse where
  rnf :: GetSegmentsResponse -> ()
rnf GetSegmentsResponse' {Int
SegmentsResponse
segmentsResponse :: SegmentsResponse
httpStatus :: Int
$sel:segmentsResponse:GetSegmentsResponse' :: GetSegmentsResponse -> SegmentsResponse
$sel:httpStatus:GetSegmentsResponse' :: GetSegmentsResponse -> 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 SegmentsResponse
segmentsResponse