{-# 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.ResilienceHub.PublishAppVersion
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Publishes a new version of a specific Resilience Hub application.
module Amazonka.ResilienceHub.PublishAppVersion
  ( -- * Creating a Request
    PublishAppVersion (..),
    newPublishAppVersion,

    -- * Request Lenses
    publishAppVersion_appArn,

    -- * Destructuring the Response
    PublishAppVersionResponse (..),
    newPublishAppVersionResponse,

    -- * Response Lenses
    publishAppVersionResponse_appVersion,
    publishAppVersionResponse_httpStatus,
    publishAppVersionResponse_appArn,
  )
where

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 Amazonka.ResilienceHub.Types
import qualified Amazonka.Response as Response

-- | /See:/ 'newPublishAppVersion' smart constructor.
data PublishAppVersion = PublishAppVersion'
  { -- | The Amazon Resource Name (ARN) of the application. The format for this
    -- ARN is: arn:@partition@:resiliencehub:@region@:@account@:app\/@app-id@.
    -- For more information about ARNs, see
    -- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
    -- in the /AWS General Reference/.
    PublishAppVersion -> Text
appArn :: Prelude.Text
  }
  deriving (PublishAppVersion -> PublishAppVersion -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PublishAppVersion -> PublishAppVersion -> Bool
$c/= :: PublishAppVersion -> PublishAppVersion -> Bool
== :: PublishAppVersion -> PublishAppVersion -> Bool
$c== :: PublishAppVersion -> PublishAppVersion -> Bool
Prelude.Eq, ReadPrec [PublishAppVersion]
ReadPrec PublishAppVersion
Int -> ReadS PublishAppVersion
ReadS [PublishAppVersion]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PublishAppVersion]
$creadListPrec :: ReadPrec [PublishAppVersion]
readPrec :: ReadPrec PublishAppVersion
$creadPrec :: ReadPrec PublishAppVersion
readList :: ReadS [PublishAppVersion]
$creadList :: ReadS [PublishAppVersion]
readsPrec :: Int -> ReadS PublishAppVersion
$creadsPrec :: Int -> ReadS PublishAppVersion
Prelude.Read, Int -> PublishAppVersion -> ShowS
[PublishAppVersion] -> ShowS
PublishAppVersion -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PublishAppVersion] -> ShowS
$cshowList :: [PublishAppVersion] -> ShowS
show :: PublishAppVersion -> String
$cshow :: PublishAppVersion -> String
showsPrec :: Int -> PublishAppVersion -> ShowS
$cshowsPrec :: Int -> PublishAppVersion -> ShowS
Prelude.Show, forall x. Rep PublishAppVersion x -> PublishAppVersion
forall x. PublishAppVersion -> Rep PublishAppVersion x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PublishAppVersion x -> PublishAppVersion
$cfrom :: forall x. PublishAppVersion -> Rep PublishAppVersion x
Prelude.Generic)

-- |
-- Create a value of 'PublishAppVersion' 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:
--
-- 'appArn', 'publishAppVersion_appArn' - The Amazon Resource Name (ARN) of the application. The format for this
-- ARN is: arn:@partition@:resiliencehub:@region@:@account@:app\/@app-id@.
-- For more information about ARNs, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
-- in the /AWS General Reference/.
newPublishAppVersion ::
  -- | 'appArn'
  Prelude.Text ->
  PublishAppVersion
newPublishAppVersion :: Text -> PublishAppVersion
newPublishAppVersion Text
pAppArn_ =
  PublishAppVersion' {$sel:appArn:PublishAppVersion' :: Text
appArn = Text
pAppArn_}

-- | The Amazon Resource Name (ARN) of the application. The format for this
-- ARN is: arn:@partition@:resiliencehub:@region@:@account@:app\/@app-id@.
-- For more information about ARNs, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
-- in the /AWS General Reference/.
publishAppVersion_appArn :: Lens.Lens' PublishAppVersion Prelude.Text
publishAppVersion_appArn :: Lens' PublishAppVersion Text
publishAppVersion_appArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PublishAppVersion' {Text
appArn :: Text
$sel:appArn:PublishAppVersion' :: PublishAppVersion -> Text
appArn} -> Text
appArn) (\s :: PublishAppVersion
s@PublishAppVersion' {} Text
a -> PublishAppVersion
s {$sel:appArn:PublishAppVersion' :: Text
appArn = Text
a} :: PublishAppVersion)

instance Core.AWSRequest PublishAppVersion where
  type
    AWSResponse PublishAppVersion =
      PublishAppVersionResponse
  request :: (Service -> Service)
-> PublishAppVersion -> Request PublishAppVersion
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 PublishAppVersion
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse PublishAppVersion)))
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 -> Int -> Text -> PublishAppVersionResponse
PublishAppVersionResponse'
            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
"appVersion")
            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))
            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
"appArn")
      )

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

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

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

instance Data.ToPath PublishAppVersion where
  toPath :: PublishAppVersion -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/publish-app-version"

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

-- | /See:/ 'newPublishAppVersionResponse' smart constructor.
data PublishAppVersionResponse = PublishAppVersionResponse'
  { -- | The version of the application.
    PublishAppVersionResponse -> Maybe Text
appVersion :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    PublishAppVersionResponse -> Int
httpStatus :: Prelude.Int,
    -- | The Amazon Resource Name (ARN) of the application. The format for this
    -- ARN is: arn:@partition@:resiliencehub:@region@:@account@:app\/@app-id@.
    -- For more information about ARNs, see
    -- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
    -- in the /AWS General Reference/.
    PublishAppVersionResponse -> Text
appArn :: Prelude.Text
  }
  deriving (PublishAppVersionResponse -> PublishAppVersionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PublishAppVersionResponse -> PublishAppVersionResponse -> Bool
$c/= :: PublishAppVersionResponse -> PublishAppVersionResponse -> Bool
== :: PublishAppVersionResponse -> PublishAppVersionResponse -> Bool
$c== :: PublishAppVersionResponse -> PublishAppVersionResponse -> Bool
Prelude.Eq, ReadPrec [PublishAppVersionResponse]
ReadPrec PublishAppVersionResponse
Int -> ReadS PublishAppVersionResponse
ReadS [PublishAppVersionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PublishAppVersionResponse]
$creadListPrec :: ReadPrec [PublishAppVersionResponse]
readPrec :: ReadPrec PublishAppVersionResponse
$creadPrec :: ReadPrec PublishAppVersionResponse
readList :: ReadS [PublishAppVersionResponse]
$creadList :: ReadS [PublishAppVersionResponse]
readsPrec :: Int -> ReadS PublishAppVersionResponse
$creadsPrec :: Int -> ReadS PublishAppVersionResponse
Prelude.Read, Int -> PublishAppVersionResponse -> ShowS
[PublishAppVersionResponse] -> ShowS
PublishAppVersionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PublishAppVersionResponse] -> ShowS
$cshowList :: [PublishAppVersionResponse] -> ShowS
show :: PublishAppVersionResponse -> String
$cshow :: PublishAppVersionResponse -> String
showsPrec :: Int -> PublishAppVersionResponse -> ShowS
$cshowsPrec :: Int -> PublishAppVersionResponse -> ShowS
Prelude.Show, forall x.
Rep PublishAppVersionResponse x -> PublishAppVersionResponse
forall x.
PublishAppVersionResponse -> Rep PublishAppVersionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep PublishAppVersionResponse x -> PublishAppVersionResponse
$cfrom :: forall x.
PublishAppVersionResponse -> Rep PublishAppVersionResponse x
Prelude.Generic)

-- |
-- Create a value of 'PublishAppVersionResponse' 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:
--
-- 'appVersion', 'publishAppVersionResponse_appVersion' - The version of the application.
--
-- 'httpStatus', 'publishAppVersionResponse_httpStatus' - The response's http status code.
--
-- 'appArn', 'publishAppVersionResponse_appArn' - The Amazon Resource Name (ARN) of the application. The format for this
-- ARN is: arn:@partition@:resiliencehub:@region@:@account@:app\/@app-id@.
-- For more information about ARNs, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
-- in the /AWS General Reference/.
newPublishAppVersionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'appArn'
  Prelude.Text ->
  PublishAppVersionResponse
newPublishAppVersionResponse :: Int -> Text -> PublishAppVersionResponse
newPublishAppVersionResponse Int
pHttpStatus_ Text
pAppArn_ =
  PublishAppVersionResponse'
    { $sel:appVersion:PublishAppVersionResponse' :: Maybe Text
appVersion =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:PublishAppVersionResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:appArn:PublishAppVersionResponse' :: Text
appArn = Text
pAppArn_
    }

-- | The version of the application.
publishAppVersionResponse_appVersion :: Lens.Lens' PublishAppVersionResponse (Prelude.Maybe Prelude.Text)
publishAppVersionResponse_appVersion :: Lens' PublishAppVersionResponse (Maybe Text)
publishAppVersionResponse_appVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PublishAppVersionResponse' {Maybe Text
appVersion :: Maybe Text
$sel:appVersion:PublishAppVersionResponse' :: PublishAppVersionResponse -> Maybe Text
appVersion} -> Maybe Text
appVersion) (\s :: PublishAppVersionResponse
s@PublishAppVersionResponse' {} Maybe Text
a -> PublishAppVersionResponse
s {$sel:appVersion:PublishAppVersionResponse' :: Maybe Text
appVersion = Maybe Text
a} :: PublishAppVersionResponse)

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

-- | The Amazon Resource Name (ARN) of the application. The format for this
-- ARN is: arn:@partition@:resiliencehub:@region@:@account@:app\/@app-id@.
-- For more information about ARNs, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
-- in the /AWS General Reference/.
publishAppVersionResponse_appArn :: Lens.Lens' PublishAppVersionResponse Prelude.Text
publishAppVersionResponse_appArn :: Lens' PublishAppVersionResponse Text
publishAppVersionResponse_appArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PublishAppVersionResponse' {Text
appArn :: Text
$sel:appArn:PublishAppVersionResponse' :: PublishAppVersionResponse -> Text
appArn} -> Text
appArn) (\s :: PublishAppVersionResponse
s@PublishAppVersionResponse' {} Text
a -> PublishAppVersionResponse
s {$sel:appArn:PublishAppVersionResponse' :: Text
appArn = Text
a} :: PublishAppVersionResponse)

instance Prelude.NFData PublishAppVersionResponse where
  rnf :: PublishAppVersionResponse -> ()
rnf PublishAppVersionResponse' {Int
Maybe Text
Text
appArn :: Text
httpStatus :: Int
appVersion :: Maybe Text
$sel:appArn:PublishAppVersionResponse' :: PublishAppVersionResponse -> Text
$sel:httpStatus:PublishAppVersionResponse' :: PublishAppVersionResponse -> Int
$sel:appVersion:PublishAppVersionResponse' :: PublishAppVersionResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
appVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 Text
appArn