{-# 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.Personalize.DescribeBatchSegmentJob
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets the properties of a batch segment job including name, Amazon
-- Resource Name (ARN), status, input and output configurations, and the
-- ARN of the solution version used to generate segments.
module Amazonka.Personalize.DescribeBatchSegmentJob
  ( -- * Creating a Request
    DescribeBatchSegmentJob (..),
    newDescribeBatchSegmentJob,

    -- * Request Lenses
    describeBatchSegmentJob_batchSegmentJobArn,

    -- * Destructuring the Response
    DescribeBatchSegmentJobResponse (..),
    newDescribeBatchSegmentJobResponse,

    -- * Response Lenses
    describeBatchSegmentJobResponse_batchSegmentJob,
    describeBatchSegmentJobResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Personalize.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newDescribeBatchSegmentJob' smart constructor.
data DescribeBatchSegmentJob = DescribeBatchSegmentJob'
  { -- | The ARN of the batch segment job to describe.
    DescribeBatchSegmentJob -> Text
batchSegmentJobArn :: Prelude.Text
  }
  deriving (DescribeBatchSegmentJob -> DescribeBatchSegmentJob -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeBatchSegmentJob -> DescribeBatchSegmentJob -> Bool
$c/= :: DescribeBatchSegmentJob -> DescribeBatchSegmentJob -> Bool
== :: DescribeBatchSegmentJob -> DescribeBatchSegmentJob -> Bool
$c== :: DescribeBatchSegmentJob -> DescribeBatchSegmentJob -> Bool
Prelude.Eq, ReadPrec [DescribeBatchSegmentJob]
ReadPrec DescribeBatchSegmentJob
Int -> ReadS DescribeBatchSegmentJob
ReadS [DescribeBatchSegmentJob]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeBatchSegmentJob]
$creadListPrec :: ReadPrec [DescribeBatchSegmentJob]
readPrec :: ReadPrec DescribeBatchSegmentJob
$creadPrec :: ReadPrec DescribeBatchSegmentJob
readList :: ReadS [DescribeBatchSegmentJob]
$creadList :: ReadS [DescribeBatchSegmentJob]
readsPrec :: Int -> ReadS DescribeBatchSegmentJob
$creadsPrec :: Int -> ReadS DescribeBatchSegmentJob
Prelude.Read, Int -> DescribeBatchSegmentJob -> ShowS
[DescribeBatchSegmentJob] -> ShowS
DescribeBatchSegmentJob -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeBatchSegmentJob] -> ShowS
$cshowList :: [DescribeBatchSegmentJob] -> ShowS
show :: DescribeBatchSegmentJob -> String
$cshow :: DescribeBatchSegmentJob -> String
showsPrec :: Int -> DescribeBatchSegmentJob -> ShowS
$cshowsPrec :: Int -> DescribeBatchSegmentJob -> ShowS
Prelude.Show, forall x. Rep DescribeBatchSegmentJob x -> DescribeBatchSegmentJob
forall x. DescribeBatchSegmentJob -> Rep DescribeBatchSegmentJob x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeBatchSegmentJob x -> DescribeBatchSegmentJob
$cfrom :: forall x. DescribeBatchSegmentJob -> Rep DescribeBatchSegmentJob x
Prelude.Generic)

-- |
-- Create a value of 'DescribeBatchSegmentJob' 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:
--
-- 'batchSegmentJobArn', 'describeBatchSegmentJob_batchSegmentJobArn' - The ARN of the batch segment job to describe.
newDescribeBatchSegmentJob ::
  -- | 'batchSegmentJobArn'
  Prelude.Text ->
  DescribeBatchSegmentJob
newDescribeBatchSegmentJob :: Text -> DescribeBatchSegmentJob
newDescribeBatchSegmentJob Text
pBatchSegmentJobArn_ =
  DescribeBatchSegmentJob'
    { $sel:batchSegmentJobArn:DescribeBatchSegmentJob' :: Text
batchSegmentJobArn =
        Text
pBatchSegmentJobArn_
    }

-- | The ARN of the batch segment job to describe.
describeBatchSegmentJob_batchSegmentJobArn :: Lens.Lens' DescribeBatchSegmentJob Prelude.Text
describeBatchSegmentJob_batchSegmentJobArn :: Lens' DescribeBatchSegmentJob Text
describeBatchSegmentJob_batchSegmentJobArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeBatchSegmentJob' {Text
batchSegmentJobArn :: Text
$sel:batchSegmentJobArn:DescribeBatchSegmentJob' :: DescribeBatchSegmentJob -> Text
batchSegmentJobArn} -> Text
batchSegmentJobArn) (\s :: DescribeBatchSegmentJob
s@DescribeBatchSegmentJob' {} Text
a -> DescribeBatchSegmentJob
s {$sel:batchSegmentJobArn:DescribeBatchSegmentJob' :: Text
batchSegmentJobArn = Text
a} :: DescribeBatchSegmentJob)

instance Core.AWSRequest DescribeBatchSegmentJob where
  type
    AWSResponse DescribeBatchSegmentJob =
      DescribeBatchSegmentJobResponse
  request :: (Service -> Service)
-> DescribeBatchSegmentJob -> Request DescribeBatchSegmentJob
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DescribeBatchSegmentJob
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeBatchSegmentJob)))
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 ->
          Maybe BatchSegmentJob -> Int -> DescribeBatchSegmentJobResponse
DescribeBatchSegmentJobResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"batchSegmentJob")
            forall (f :: * -> *) a b. Applicative f => 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))
      )

instance Prelude.Hashable DescribeBatchSegmentJob where
  hashWithSalt :: Int -> DescribeBatchSegmentJob -> Int
hashWithSalt Int
_salt DescribeBatchSegmentJob' {Text
batchSegmentJobArn :: Text
$sel:batchSegmentJobArn:DescribeBatchSegmentJob' :: DescribeBatchSegmentJob -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
batchSegmentJobArn

instance Prelude.NFData DescribeBatchSegmentJob where
  rnf :: DescribeBatchSegmentJob -> ()
rnf DescribeBatchSegmentJob' {Text
batchSegmentJobArn :: Text
$sel:batchSegmentJobArn:DescribeBatchSegmentJob' :: DescribeBatchSegmentJob -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
batchSegmentJobArn

instance Data.ToHeaders DescribeBatchSegmentJob where
  toHeaders :: DescribeBatchSegmentJob -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"AmazonPersonalize.DescribeBatchSegmentJob" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON DescribeBatchSegmentJob where
  toJSON :: DescribeBatchSegmentJob -> Value
toJSON DescribeBatchSegmentJob' {Text
batchSegmentJobArn :: Text
$sel:batchSegmentJobArn:DescribeBatchSegmentJob' :: DescribeBatchSegmentJob -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"batchSegmentJobArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
batchSegmentJobArn)
          ]
      )

instance Data.ToPath DescribeBatchSegmentJob where
  toPath :: DescribeBatchSegmentJob -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newDescribeBatchSegmentJobResponse' smart constructor.
data DescribeBatchSegmentJobResponse = DescribeBatchSegmentJobResponse'
  { -- | Information on the specified batch segment job.
    DescribeBatchSegmentJobResponse -> Maybe BatchSegmentJob
batchSegmentJob :: Prelude.Maybe BatchSegmentJob,
    -- | The response's http status code.
    DescribeBatchSegmentJobResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeBatchSegmentJobResponse
-> DescribeBatchSegmentJobResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeBatchSegmentJobResponse
-> DescribeBatchSegmentJobResponse -> Bool
$c/= :: DescribeBatchSegmentJobResponse
-> DescribeBatchSegmentJobResponse -> Bool
== :: DescribeBatchSegmentJobResponse
-> DescribeBatchSegmentJobResponse -> Bool
$c== :: DescribeBatchSegmentJobResponse
-> DescribeBatchSegmentJobResponse -> Bool
Prelude.Eq, ReadPrec [DescribeBatchSegmentJobResponse]
ReadPrec DescribeBatchSegmentJobResponse
Int -> ReadS DescribeBatchSegmentJobResponse
ReadS [DescribeBatchSegmentJobResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeBatchSegmentJobResponse]
$creadListPrec :: ReadPrec [DescribeBatchSegmentJobResponse]
readPrec :: ReadPrec DescribeBatchSegmentJobResponse
$creadPrec :: ReadPrec DescribeBatchSegmentJobResponse
readList :: ReadS [DescribeBatchSegmentJobResponse]
$creadList :: ReadS [DescribeBatchSegmentJobResponse]
readsPrec :: Int -> ReadS DescribeBatchSegmentJobResponse
$creadsPrec :: Int -> ReadS DescribeBatchSegmentJobResponse
Prelude.Read, Int -> DescribeBatchSegmentJobResponse -> ShowS
[DescribeBatchSegmentJobResponse] -> ShowS
DescribeBatchSegmentJobResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeBatchSegmentJobResponse] -> ShowS
$cshowList :: [DescribeBatchSegmentJobResponse] -> ShowS
show :: DescribeBatchSegmentJobResponse -> String
$cshow :: DescribeBatchSegmentJobResponse -> String
showsPrec :: Int -> DescribeBatchSegmentJobResponse -> ShowS
$cshowsPrec :: Int -> DescribeBatchSegmentJobResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeBatchSegmentJobResponse x
-> DescribeBatchSegmentJobResponse
forall x.
DescribeBatchSegmentJobResponse
-> Rep DescribeBatchSegmentJobResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeBatchSegmentJobResponse x
-> DescribeBatchSegmentJobResponse
$cfrom :: forall x.
DescribeBatchSegmentJobResponse
-> Rep DescribeBatchSegmentJobResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeBatchSegmentJobResponse' 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:
--
-- 'batchSegmentJob', 'describeBatchSegmentJobResponse_batchSegmentJob' - Information on the specified batch segment job.
--
-- 'httpStatus', 'describeBatchSegmentJobResponse_httpStatus' - The response's http status code.
newDescribeBatchSegmentJobResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeBatchSegmentJobResponse
newDescribeBatchSegmentJobResponse :: Int -> DescribeBatchSegmentJobResponse
newDescribeBatchSegmentJobResponse Int
pHttpStatus_ =
  DescribeBatchSegmentJobResponse'
    { $sel:batchSegmentJob:DescribeBatchSegmentJobResponse' :: Maybe BatchSegmentJob
batchSegmentJob =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeBatchSegmentJobResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Information on the specified batch segment job.
describeBatchSegmentJobResponse_batchSegmentJob :: Lens.Lens' DescribeBatchSegmentJobResponse (Prelude.Maybe BatchSegmentJob)
describeBatchSegmentJobResponse_batchSegmentJob :: Lens' DescribeBatchSegmentJobResponse (Maybe BatchSegmentJob)
describeBatchSegmentJobResponse_batchSegmentJob = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeBatchSegmentJobResponse' {Maybe BatchSegmentJob
batchSegmentJob :: Maybe BatchSegmentJob
$sel:batchSegmentJob:DescribeBatchSegmentJobResponse' :: DescribeBatchSegmentJobResponse -> Maybe BatchSegmentJob
batchSegmentJob} -> Maybe BatchSegmentJob
batchSegmentJob) (\s :: DescribeBatchSegmentJobResponse
s@DescribeBatchSegmentJobResponse' {} Maybe BatchSegmentJob
a -> DescribeBatchSegmentJobResponse
s {$sel:batchSegmentJob:DescribeBatchSegmentJobResponse' :: Maybe BatchSegmentJob
batchSegmentJob = Maybe BatchSegmentJob
a} :: DescribeBatchSegmentJobResponse)

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

instance
  Prelude.NFData
    DescribeBatchSegmentJobResponse
  where
  rnf :: DescribeBatchSegmentJobResponse -> ()
rnf DescribeBatchSegmentJobResponse' {Int
Maybe BatchSegmentJob
httpStatus :: Int
batchSegmentJob :: Maybe BatchSegmentJob
$sel:httpStatus:DescribeBatchSegmentJobResponse' :: DescribeBatchSegmentJobResponse -> Int
$sel:batchSegmentJob:DescribeBatchSegmentJobResponse' :: DescribeBatchSegmentJobResponse -> Maybe BatchSegmentJob
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe BatchSegmentJob
batchSegmentJob
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus