{-# 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.GetSegment
-- 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 a specific segment that\'s associated with an application.
module Amazonka.Pinpoint.GetSegment
  ( -- * Creating a Request
    GetSegment (..),
    newGetSegment,

    -- * Request Lenses
    getSegment_segmentId,
    getSegment_applicationId,

    -- * Destructuring the Response
    GetSegmentResponse (..),
    newGetSegmentResponse,

    -- * Response Lenses
    getSegmentResponse_httpStatus,
    getSegmentResponse_segmentResponse,
  )
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:/ 'newGetSegment' smart constructor.
data GetSegment = GetSegment'
  { -- | The unique identifier for the segment.
    GetSegment -> Text
segmentId :: Prelude.Text,
    -- | The unique identifier for the application. This identifier is displayed
    -- as the __Project ID__ on the Amazon Pinpoint console.
    GetSegment -> Text
applicationId :: Prelude.Text
  }
  deriving (GetSegment -> GetSegment -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetSegment -> GetSegment -> Bool
$c/= :: GetSegment -> GetSegment -> Bool
== :: GetSegment -> GetSegment -> Bool
$c== :: GetSegment -> GetSegment -> Bool
Prelude.Eq, ReadPrec [GetSegment]
ReadPrec GetSegment
Int -> ReadS GetSegment
ReadS [GetSegment]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetSegment]
$creadListPrec :: ReadPrec [GetSegment]
readPrec :: ReadPrec GetSegment
$creadPrec :: ReadPrec GetSegment
readList :: ReadS [GetSegment]
$creadList :: ReadS [GetSegment]
readsPrec :: Int -> ReadS GetSegment
$creadsPrec :: Int -> ReadS GetSegment
Prelude.Read, Int -> GetSegment -> ShowS
[GetSegment] -> ShowS
GetSegment -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetSegment] -> ShowS
$cshowList :: [GetSegment] -> ShowS
show :: GetSegment -> String
$cshow :: GetSegment -> String
showsPrec :: Int -> GetSegment -> ShowS
$cshowsPrec :: Int -> GetSegment -> ShowS
Prelude.Show, forall x. Rep GetSegment x -> GetSegment
forall x. GetSegment -> Rep GetSegment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetSegment x -> GetSegment
$cfrom :: forall x. GetSegment -> Rep GetSegment x
Prelude.Generic)

-- |
-- Create a value of 'GetSegment' 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:
--
-- 'segmentId', 'getSegment_segmentId' - The unique identifier for the segment.
--
-- 'applicationId', 'getSegment_applicationId' - The unique identifier for the application. This identifier is displayed
-- as the __Project ID__ on the Amazon Pinpoint console.
newGetSegment ::
  -- | 'segmentId'
  Prelude.Text ->
  -- | 'applicationId'
  Prelude.Text ->
  GetSegment
newGetSegment :: Text -> Text -> GetSegment
newGetSegment Text
pSegmentId_ Text
pApplicationId_ =
  GetSegment'
    { $sel:segmentId:GetSegment' :: Text
segmentId = Text
pSegmentId_,
      $sel:applicationId:GetSegment' :: Text
applicationId = Text
pApplicationId_
    }

-- | The unique identifier for the segment.
getSegment_segmentId :: Lens.Lens' GetSegment Prelude.Text
getSegment_segmentId :: Lens' GetSegment Text
getSegment_segmentId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSegment' {Text
segmentId :: Text
$sel:segmentId:GetSegment' :: GetSegment -> Text
segmentId} -> Text
segmentId) (\s :: GetSegment
s@GetSegment' {} Text
a -> GetSegment
s {$sel:segmentId:GetSegment' :: Text
segmentId = Text
a} :: GetSegment)

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

instance Core.AWSRequest GetSegment where
  type AWSResponse GetSegment = GetSegmentResponse
  request :: (Service -> Service) -> GetSegment -> Request GetSegment
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 GetSegment
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetSegment)))
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 -> SegmentResponse -> GetSegmentResponse
GetSegmentResponse'
            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 GetSegment where
  hashWithSalt :: Int -> GetSegment -> Int
hashWithSalt Int
_salt GetSegment' {Text
applicationId :: Text
segmentId :: Text
$sel:applicationId:GetSegment' :: GetSegment -> Text
$sel:segmentId:GetSegment' :: GetSegment -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
segmentId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
applicationId

instance Prelude.NFData GetSegment where
  rnf :: GetSegment -> ()
rnf GetSegment' {Text
applicationId :: Text
segmentId :: Text
$sel:applicationId:GetSegment' :: GetSegment -> Text
$sel:segmentId:GetSegment' :: GetSegment -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
segmentId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
applicationId

instance Data.ToHeaders GetSegment where
  toHeaders :: GetSegment -> 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 GetSegment where
  toPath :: GetSegment -> ByteString
toPath GetSegment' {Text
applicationId :: Text
segmentId :: Text
$sel:applicationId:GetSegment' :: GetSegment -> Text
$sel:segmentId:GetSegment' :: GetSegment -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/v1/apps/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
applicationId,
        ByteString
"/segments/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
segmentId
      ]

instance Data.ToQuery GetSegment where
  toQuery :: GetSegment -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

-- |
-- Create a value of 'GetSegmentResponse' 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', 'getSegmentResponse_httpStatus' - The response's http status code.
--
-- 'segmentResponse', 'getSegmentResponse_segmentResponse' - Undocumented member.
newGetSegmentResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'segmentResponse'
  SegmentResponse ->
  GetSegmentResponse
newGetSegmentResponse :: Int -> SegmentResponse -> GetSegmentResponse
newGetSegmentResponse Int
pHttpStatus_ SegmentResponse
pSegmentResponse_ =
  GetSegmentResponse'
    { $sel:httpStatus:GetSegmentResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:segmentResponse:GetSegmentResponse' :: SegmentResponse
segmentResponse = SegmentResponse
pSegmentResponse_
    }

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

-- | Undocumented member.
getSegmentResponse_segmentResponse :: Lens.Lens' GetSegmentResponse SegmentResponse
getSegmentResponse_segmentResponse :: Lens' GetSegmentResponse SegmentResponse
getSegmentResponse_segmentResponse = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSegmentResponse' {SegmentResponse
segmentResponse :: SegmentResponse
$sel:segmentResponse:GetSegmentResponse' :: GetSegmentResponse -> SegmentResponse
segmentResponse} -> SegmentResponse
segmentResponse) (\s :: GetSegmentResponse
s@GetSegmentResponse' {} SegmentResponse
a -> GetSegmentResponse
s {$sel:segmentResponse:GetSegmentResponse' :: SegmentResponse
segmentResponse = SegmentResponse
a} :: GetSegmentResponse)

instance Prelude.NFData GetSegmentResponse where
  rnf :: GetSegmentResponse -> ()
rnf GetSegmentResponse' {Int
SegmentResponse
segmentResponse :: SegmentResponse
httpStatus :: Int
$sel:segmentResponse:GetSegmentResponse' :: GetSegmentResponse -> SegmentResponse
$sel:httpStatus:GetSegmentResponse' :: GetSegmentResponse -> 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 SegmentResponse
segmentResponse