{-# 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.CodeDeploy.GetApplicationRevision
-- 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 information about an application revision.
module Amazonka.CodeDeploy.GetApplicationRevision
  ( -- * Creating a Request
    GetApplicationRevision (..),
    newGetApplicationRevision,

    -- * Request Lenses
    getApplicationRevision_applicationName,
    getApplicationRevision_revision,

    -- * Destructuring the Response
    GetApplicationRevisionResponse (..),
    newGetApplicationRevisionResponse,

    -- * Response Lenses
    getApplicationRevisionResponse_applicationName,
    getApplicationRevisionResponse_revision,
    getApplicationRevisionResponse_revisionInfo,
    getApplicationRevisionResponse_httpStatus,
  )
where

import Amazonka.CodeDeploy.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

-- | Represents the input of a @GetApplicationRevision@ operation.
--
-- /See:/ 'newGetApplicationRevision' smart constructor.
data GetApplicationRevision = GetApplicationRevision'
  { -- | The name of the application that corresponds to the revision.
    GetApplicationRevision -> Text
applicationName :: Prelude.Text,
    -- | Information about the application revision to get, including type and
    -- location.
    GetApplicationRevision -> RevisionLocation
revision :: RevisionLocation
  }
  deriving (GetApplicationRevision -> GetApplicationRevision -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetApplicationRevision -> GetApplicationRevision -> Bool
$c/= :: GetApplicationRevision -> GetApplicationRevision -> Bool
== :: GetApplicationRevision -> GetApplicationRevision -> Bool
$c== :: GetApplicationRevision -> GetApplicationRevision -> Bool
Prelude.Eq, ReadPrec [GetApplicationRevision]
ReadPrec GetApplicationRevision
Int -> ReadS GetApplicationRevision
ReadS [GetApplicationRevision]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetApplicationRevision]
$creadListPrec :: ReadPrec [GetApplicationRevision]
readPrec :: ReadPrec GetApplicationRevision
$creadPrec :: ReadPrec GetApplicationRevision
readList :: ReadS [GetApplicationRevision]
$creadList :: ReadS [GetApplicationRevision]
readsPrec :: Int -> ReadS GetApplicationRevision
$creadsPrec :: Int -> ReadS GetApplicationRevision
Prelude.Read, Int -> GetApplicationRevision -> ShowS
[GetApplicationRevision] -> ShowS
GetApplicationRevision -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetApplicationRevision] -> ShowS
$cshowList :: [GetApplicationRevision] -> ShowS
show :: GetApplicationRevision -> String
$cshow :: GetApplicationRevision -> String
showsPrec :: Int -> GetApplicationRevision -> ShowS
$cshowsPrec :: Int -> GetApplicationRevision -> ShowS
Prelude.Show, forall x. Rep GetApplicationRevision x -> GetApplicationRevision
forall x. GetApplicationRevision -> Rep GetApplicationRevision x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetApplicationRevision x -> GetApplicationRevision
$cfrom :: forall x. GetApplicationRevision -> Rep GetApplicationRevision x
Prelude.Generic)

-- |
-- Create a value of 'GetApplicationRevision' 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:
--
-- 'applicationName', 'getApplicationRevision_applicationName' - The name of the application that corresponds to the revision.
--
-- 'revision', 'getApplicationRevision_revision' - Information about the application revision to get, including type and
-- location.
newGetApplicationRevision ::
  -- | 'applicationName'
  Prelude.Text ->
  -- | 'revision'
  RevisionLocation ->
  GetApplicationRevision
newGetApplicationRevision :: Text -> RevisionLocation -> GetApplicationRevision
newGetApplicationRevision
  Text
pApplicationName_
  RevisionLocation
pRevision_ =
    GetApplicationRevision'
      { $sel:applicationName:GetApplicationRevision' :: Text
applicationName =
          Text
pApplicationName_,
        $sel:revision:GetApplicationRevision' :: RevisionLocation
revision = RevisionLocation
pRevision_
      }

-- | The name of the application that corresponds to the revision.
getApplicationRevision_applicationName :: Lens.Lens' GetApplicationRevision Prelude.Text
getApplicationRevision_applicationName :: Lens' GetApplicationRevision Text
getApplicationRevision_applicationName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetApplicationRevision' {Text
applicationName :: Text
$sel:applicationName:GetApplicationRevision' :: GetApplicationRevision -> Text
applicationName} -> Text
applicationName) (\s :: GetApplicationRevision
s@GetApplicationRevision' {} Text
a -> GetApplicationRevision
s {$sel:applicationName:GetApplicationRevision' :: Text
applicationName = Text
a} :: GetApplicationRevision)

-- | Information about the application revision to get, including type and
-- location.
getApplicationRevision_revision :: Lens.Lens' GetApplicationRevision RevisionLocation
getApplicationRevision_revision :: Lens' GetApplicationRevision RevisionLocation
getApplicationRevision_revision = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetApplicationRevision' {RevisionLocation
revision :: RevisionLocation
$sel:revision:GetApplicationRevision' :: GetApplicationRevision -> RevisionLocation
revision} -> RevisionLocation
revision) (\s :: GetApplicationRevision
s@GetApplicationRevision' {} RevisionLocation
a -> GetApplicationRevision
s {$sel:revision:GetApplicationRevision' :: RevisionLocation
revision = RevisionLocation
a} :: GetApplicationRevision)

instance Core.AWSRequest GetApplicationRevision where
  type
    AWSResponse GetApplicationRevision =
      GetApplicationRevisionResponse
  request :: (Service -> Service)
-> GetApplicationRevision -> Request GetApplicationRevision
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 GetApplicationRevision
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetApplicationRevision)))
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 Text
-> Maybe RevisionLocation
-> Maybe GenericRevisionInfo
-> Int
-> GetApplicationRevisionResponse
GetApplicationRevisionResponse'
            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
"applicationName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"revision")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"revisionInfo")
            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 GetApplicationRevision where
  hashWithSalt :: Int -> GetApplicationRevision -> Int
hashWithSalt Int
_salt GetApplicationRevision' {Text
RevisionLocation
revision :: RevisionLocation
applicationName :: Text
$sel:revision:GetApplicationRevision' :: GetApplicationRevision -> RevisionLocation
$sel:applicationName:GetApplicationRevision' :: GetApplicationRevision -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
applicationName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` RevisionLocation
revision

instance Prelude.NFData GetApplicationRevision where
  rnf :: GetApplicationRevision -> ()
rnf GetApplicationRevision' {Text
RevisionLocation
revision :: RevisionLocation
applicationName :: Text
$sel:revision:GetApplicationRevision' :: GetApplicationRevision -> RevisionLocation
$sel:applicationName:GetApplicationRevision' :: GetApplicationRevision -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
applicationName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf RevisionLocation
revision

instance Data.ToHeaders GetApplicationRevision where
  toHeaders :: GetApplicationRevision -> 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
"CodeDeploy_20141006.GetApplicationRevision" ::
                          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 GetApplicationRevision where
  toJSON :: GetApplicationRevision -> Value
toJSON GetApplicationRevision' {Text
RevisionLocation
revision :: RevisionLocation
applicationName :: Text
$sel:revision:GetApplicationRevision' :: GetApplicationRevision -> RevisionLocation
$sel:applicationName:GetApplicationRevision' :: GetApplicationRevision -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"applicationName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
applicationName),
            forall a. a -> Maybe a
Prelude.Just (Key
"revision" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= RevisionLocation
revision)
          ]
      )

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

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

-- | Represents the output of a @GetApplicationRevision@ operation.
--
-- /See:/ 'newGetApplicationRevisionResponse' smart constructor.
data GetApplicationRevisionResponse = GetApplicationRevisionResponse'
  { -- | The name of the application that corresponds to the revision.
    GetApplicationRevisionResponse -> Maybe Text
applicationName :: Prelude.Maybe Prelude.Text,
    -- | Additional information about the revision, including type and location.
    GetApplicationRevisionResponse -> Maybe RevisionLocation
revision :: Prelude.Maybe RevisionLocation,
    -- | General information about the revision.
    GetApplicationRevisionResponse -> Maybe GenericRevisionInfo
revisionInfo :: Prelude.Maybe GenericRevisionInfo,
    -- | The response's http status code.
    GetApplicationRevisionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetApplicationRevisionResponse
-> GetApplicationRevisionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetApplicationRevisionResponse
-> GetApplicationRevisionResponse -> Bool
$c/= :: GetApplicationRevisionResponse
-> GetApplicationRevisionResponse -> Bool
== :: GetApplicationRevisionResponse
-> GetApplicationRevisionResponse -> Bool
$c== :: GetApplicationRevisionResponse
-> GetApplicationRevisionResponse -> Bool
Prelude.Eq, ReadPrec [GetApplicationRevisionResponse]
ReadPrec GetApplicationRevisionResponse
Int -> ReadS GetApplicationRevisionResponse
ReadS [GetApplicationRevisionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetApplicationRevisionResponse]
$creadListPrec :: ReadPrec [GetApplicationRevisionResponse]
readPrec :: ReadPrec GetApplicationRevisionResponse
$creadPrec :: ReadPrec GetApplicationRevisionResponse
readList :: ReadS [GetApplicationRevisionResponse]
$creadList :: ReadS [GetApplicationRevisionResponse]
readsPrec :: Int -> ReadS GetApplicationRevisionResponse
$creadsPrec :: Int -> ReadS GetApplicationRevisionResponse
Prelude.Read, Int -> GetApplicationRevisionResponse -> ShowS
[GetApplicationRevisionResponse] -> ShowS
GetApplicationRevisionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetApplicationRevisionResponse] -> ShowS
$cshowList :: [GetApplicationRevisionResponse] -> ShowS
show :: GetApplicationRevisionResponse -> String
$cshow :: GetApplicationRevisionResponse -> String
showsPrec :: Int -> GetApplicationRevisionResponse -> ShowS
$cshowsPrec :: Int -> GetApplicationRevisionResponse -> ShowS
Prelude.Show, forall x.
Rep GetApplicationRevisionResponse x
-> GetApplicationRevisionResponse
forall x.
GetApplicationRevisionResponse
-> Rep GetApplicationRevisionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetApplicationRevisionResponse x
-> GetApplicationRevisionResponse
$cfrom :: forall x.
GetApplicationRevisionResponse
-> Rep GetApplicationRevisionResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetApplicationRevisionResponse' 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:
--
-- 'applicationName', 'getApplicationRevisionResponse_applicationName' - The name of the application that corresponds to the revision.
--
-- 'revision', 'getApplicationRevisionResponse_revision' - Additional information about the revision, including type and location.
--
-- 'revisionInfo', 'getApplicationRevisionResponse_revisionInfo' - General information about the revision.
--
-- 'httpStatus', 'getApplicationRevisionResponse_httpStatus' - The response's http status code.
newGetApplicationRevisionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetApplicationRevisionResponse
newGetApplicationRevisionResponse :: Int -> GetApplicationRevisionResponse
newGetApplicationRevisionResponse Int
pHttpStatus_ =
  GetApplicationRevisionResponse'
    { $sel:applicationName:GetApplicationRevisionResponse' :: Maybe Text
applicationName =
        forall a. Maybe a
Prelude.Nothing,
      $sel:revision:GetApplicationRevisionResponse' :: Maybe RevisionLocation
revision = forall a. Maybe a
Prelude.Nothing,
      $sel:revisionInfo:GetApplicationRevisionResponse' :: Maybe GenericRevisionInfo
revisionInfo = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetApplicationRevisionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The name of the application that corresponds to the revision.
getApplicationRevisionResponse_applicationName :: Lens.Lens' GetApplicationRevisionResponse (Prelude.Maybe Prelude.Text)
getApplicationRevisionResponse_applicationName :: Lens' GetApplicationRevisionResponse (Maybe Text)
getApplicationRevisionResponse_applicationName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetApplicationRevisionResponse' {Maybe Text
applicationName :: Maybe Text
$sel:applicationName:GetApplicationRevisionResponse' :: GetApplicationRevisionResponse -> Maybe Text
applicationName} -> Maybe Text
applicationName) (\s :: GetApplicationRevisionResponse
s@GetApplicationRevisionResponse' {} Maybe Text
a -> GetApplicationRevisionResponse
s {$sel:applicationName:GetApplicationRevisionResponse' :: Maybe Text
applicationName = Maybe Text
a} :: GetApplicationRevisionResponse)

-- | Additional information about the revision, including type and location.
getApplicationRevisionResponse_revision :: Lens.Lens' GetApplicationRevisionResponse (Prelude.Maybe RevisionLocation)
getApplicationRevisionResponse_revision :: Lens' GetApplicationRevisionResponse (Maybe RevisionLocation)
getApplicationRevisionResponse_revision = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetApplicationRevisionResponse' {Maybe RevisionLocation
revision :: Maybe RevisionLocation
$sel:revision:GetApplicationRevisionResponse' :: GetApplicationRevisionResponse -> Maybe RevisionLocation
revision} -> Maybe RevisionLocation
revision) (\s :: GetApplicationRevisionResponse
s@GetApplicationRevisionResponse' {} Maybe RevisionLocation
a -> GetApplicationRevisionResponse
s {$sel:revision:GetApplicationRevisionResponse' :: Maybe RevisionLocation
revision = Maybe RevisionLocation
a} :: GetApplicationRevisionResponse)

-- | General information about the revision.
getApplicationRevisionResponse_revisionInfo :: Lens.Lens' GetApplicationRevisionResponse (Prelude.Maybe GenericRevisionInfo)
getApplicationRevisionResponse_revisionInfo :: Lens' GetApplicationRevisionResponse (Maybe GenericRevisionInfo)
getApplicationRevisionResponse_revisionInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetApplicationRevisionResponse' {Maybe GenericRevisionInfo
revisionInfo :: Maybe GenericRevisionInfo
$sel:revisionInfo:GetApplicationRevisionResponse' :: GetApplicationRevisionResponse -> Maybe GenericRevisionInfo
revisionInfo} -> Maybe GenericRevisionInfo
revisionInfo) (\s :: GetApplicationRevisionResponse
s@GetApplicationRevisionResponse' {} Maybe GenericRevisionInfo
a -> GetApplicationRevisionResponse
s {$sel:revisionInfo:GetApplicationRevisionResponse' :: Maybe GenericRevisionInfo
revisionInfo = Maybe GenericRevisionInfo
a} :: GetApplicationRevisionResponse)

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

instance
  Prelude.NFData
    GetApplicationRevisionResponse
  where
  rnf :: GetApplicationRevisionResponse -> ()
rnf GetApplicationRevisionResponse' {Int
Maybe Text
Maybe GenericRevisionInfo
Maybe RevisionLocation
httpStatus :: Int
revisionInfo :: Maybe GenericRevisionInfo
revision :: Maybe RevisionLocation
applicationName :: Maybe Text
$sel:httpStatus:GetApplicationRevisionResponse' :: GetApplicationRevisionResponse -> Int
$sel:revisionInfo:GetApplicationRevisionResponse' :: GetApplicationRevisionResponse -> Maybe GenericRevisionInfo
$sel:revision:GetApplicationRevisionResponse' :: GetApplicationRevisionResponse -> Maybe RevisionLocation
$sel:applicationName:GetApplicationRevisionResponse' :: GetApplicationRevisionResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
applicationName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RevisionLocation
revision
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe GenericRevisionInfo
revisionInfo
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus