{-# 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.Amplify.GetJob
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns a job for a branch of an Amplify app.
module Amazonka.Amplify.GetJob
  ( -- * Creating a Request
    GetJob (..),
    newGetJob,

    -- * Request Lenses
    getJob_appId,
    getJob_branchName,
    getJob_jobId,

    -- * Destructuring the Response
    GetJobResponse (..),
    newGetJobResponse,

    -- * Response Lenses
    getJobResponse_httpStatus,
    getJobResponse_job,
  )
where

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

-- | The request structure for the get job request.
--
-- /See:/ 'newGetJob' smart constructor.
data GetJob = GetJob'
  { -- | The unique ID for an Amplify app.
    GetJob -> Text
appId :: Prelude.Text,
    -- | The branch name for the job.
    GetJob -> Text
branchName :: Prelude.Text,
    -- | The unique ID for the job.
    GetJob -> Text
jobId :: Prelude.Text
  }
  deriving (GetJob -> GetJob -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetJob -> GetJob -> Bool
$c/= :: GetJob -> GetJob -> Bool
== :: GetJob -> GetJob -> Bool
$c== :: GetJob -> GetJob -> Bool
Prelude.Eq, ReadPrec [GetJob]
ReadPrec GetJob
Int -> ReadS GetJob
ReadS [GetJob]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetJob]
$creadListPrec :: ReadPrec [GetJob]
readPrec :: ReadPrec GetJob
$creadPrec :: ReadPrec GetJob
readList :: ReadS [GetJob]
$creadList :: ReadS [GetJob]
readsPrec :: Int -> ReadS GetJob
$creadsPrec :: Int -> ReadS GetJob
Prelude.Read, Int -> GetJob -> ShowS
[GetJob] -> ShowS
GetJob -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetJob] -> ShowS
$cshowList :: [GetJob] -> ShowS
show :: GetJob -> String
$cshow :: GetJob -> String
showsPrec :: Int -> GetJob -> ShowS
$cshowsPrec :: Int -> GetJob -> ShowS
Prelude.Show, forall x. Rep GetJob x -> GetJob
forall x. GetJob -> Rep GetJob x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetJob x -> GetJob
$cfrom :: forall x. GetJob -> Rep GetJob x
Prelude.Generic)

-- |
-- Create a value of 'GetJob' 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:
--
-- 'appId', 'getJob_appId' - The unique ID for an Amplify app.
--
-- 'branchName', 'getJob_branchName' - The branch name for the job.
--
-- 'jobId', 'getJob_jobId' - The unique ID for the job.
newGetJob ::
  -- | 'appId'
  Prelude.Text ->
  -- | 'branchName'
  Prelude.Text ->
  -- | 'jobId'
  Prelude.Text ->
  GetJob
newGetJob :: Text -> Text -> Text -> GetJob
newGetJob Text
pAppId_ Text
pBranchName_ Text
pJobId_ =
  GetJob'
    { $sel:appId:GetJob' :: Text
appId = Text
pAppId_,
      $sel:branchName:GetJob' :: Text
branchName = Text
pBranchName_,
      $sel:jobId:GetJob' :: Text
jobId = Text
pJobId_
    }

-- | The unique ID for an Amplify app.
getJob_appId :: Lens.Lens' GetJob Prelude.Text
getJob_appId :: Lens' GetJob Text
getJob_appId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetJob' {Text
appId :: Text
$sel:appId:GetJob' :: GetJob -> Text
appId} -> Text
appId) (\s :: GetJob
s@GetJob' {} Text
a -> GetJob
s {$sel:appId:GetJob' :: Text
appId = Text
a} :: GetJob)

-- | The branch name for the job.
getJob_branchName :: Lens.Lens' GetJob Prelude.Text
getJob_branchName :: Lens' GetJob Text
getJob_branchName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetJob' {Text
branchName :: Text
$sel:branchName:GetJob' :: GetJob -> Text
branchName} -> Text
branchName) (\s :: GetJob
s@GetJob' {} Text
a -> GetJob
s {$sel:branchName:GetJob' :: Text
branchName = Text
a} :: GetJob)

-- | The unique ID for the job.
getJob_jobId :: Lens.Lens' GetJob Prelude.Text
getJob_jobId :: Lens' GetJob Text
getJob_jobId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetJob' {Text
jobId :: Text
$sel:jobId:GetJob' :: GetJob -> Text
jobId} -> Text
jobId) (\s :: GetJob
s@GetJob' {} Text
a -> GetJob
s {$sel:jobId:GetJob' :: Text
jobId = Text
a} :: GetJob)

instance Core.AWSRequest GetJob where
  type AWSResponse GetJob = GetJobResponse
  request :: (Service -> Service) -> GetJob -> Request GetJob
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 GetJob
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetJob)))
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 -> Job -> GetJobResponse
GetJobResponse'
            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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"job")
      )

instance Prelude.Hashable GetJob where
  hashWithSalt :: Int -> GetJob -> Int
hashWithSalt Int
_salt GetJob' {Text
jobId :: Text
branchName :: Text
appId :: Text
$sel:jobId:GetJob' :: GetJob -> Text
$sel:branchName:GetJob' :: GetJob -> Text
$sel:appId:GetJob' :: GetJob -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
appId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
branchName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
jobId

instance Prelude.NFData GetJob where
  rnf :: GetJob -> ()
rnf GetJob' {Text
jobId :: Text
branchName :: Text
appId :: Text
$sel:jobId:GetJob' :: GetJob -> Text
$sel:branchName:GetJob' :: GetJob -> Text
$sel:appId:GetJob' :: GetJob -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
appId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
branchName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
jobId

instance Data.ToHeaders GetJob where
  toHeaders :: GetJob -> 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 GetJob where
  toPath :: GetJob -> ByteString
toPath GetJob' {Text
jobId :: Text
branchName :: Text
appId :: Text
$sel:jobId:GetJob' :: GetJob -> Text
$sel:branchName:GetJob' :: GetJob -> Text
$sel:appId:GetJob' :: GetJob -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/apps/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
appId,
        ByteString
"/branches/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
branchName,
        ByteString
"/jobs/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
jobId
      ]

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

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

-- |
-- Create a value of 'GetJobResponse' 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', 'getJobResponse_httpStatus' - The response's http status code.
--
-- 'job', 'getJobResponse_job' - Undocumented member.
newGetJobResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'job'
  Job ->
  GetJobResponse
newGetJobResponse :: Int -> Job -> GetJobResponse
newGetJobResponse Int
pHttpStatus_ Job
pJob_ =
  GetJobResponse'
    { $sel:httpStatus:GetJobResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:job:GetJobResponse' :: Job
job = Job
pJob_
    }

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

-- | Undocumented member.
getJobResponse_job :: Lens.Lens' GetJobResponse Job
getJobResponse_job :: Lens' GetJobResponse Job
getJobResponse_job = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetJobResponse' {Job
job :: Job
$sel:job:GetJobResponse' :: GetJobResponse -> Job
job} -> Job
job) (\s :: GetJobResponse
s@GetJobResponse' {} Job
a -> GetJobResponse
s {$sel:job:GetJobResponse' :: Job
job = Job
a} :: GetJobResponse)

instance Prelude.NFData GetJobResponse where
  rnf :: GetJobResponse -> ()
rnf GetJobResponse' {Int
Job
job :: Job
httpStatus :: Int
$sel:job:GetJobResponse' :: GetJobResponse -> Job
$sel:httpStatus:GetJobResponse' :: GetJobResponse -> 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 Job
job