{-# 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.M2.CreateApplication
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a new application with given parameters. Requires an existing
-- runtime environment and application definition file.
module Amazonka.M2.CreateApplication
  ( -- * Creating a Request
    CreateApplication (..),
    newCreateApplication,

    -- * Request Lenses
    createApplication_clientToken,
    createApplication_description,
    createApplication_kmsKeyId,
    createApplication_tags,
    createApplication_definition,
    createApplication_engineType,
    createApplication_name,

    -- * Destructuring the Response
    CreateApplicationResponse (..),
    newCreateApplicationResponse,

    -- * Response Lenses
    createApplicationResponse_httpStatus,
    createApplicationResponse_applicationArn,
    createApplicationResponse_applicationId,
    createApplicationResponse_applicationVersion,
  )
where

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

-- | /See:/ 'newCreateApplication' smart constructor.
data CreateApplication = CreateApplication'
  { -- | Unique, case-sensitive identifier the service generates to ensure the
    -- idempotency of the request to create an application. The service
    -- generates the clientToken when the API call is triggered. The token
    -- expires after one hour, so if you retry the API within this timeframe
    -- with the same clientToken, you will get the same response. The service
    -- also handles deleting the clientToken after it expires.
    CreateApplication -> Maybe Text
clientToken :: Prelude.Maybe Prelude.Text,
    -- | The description of the application.
    CreateApplication -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The identifier of a customer managed key.
    CreateApplication -> Maybe Text
kmsKeyId :: Prelude.Maybe Prelude.Text,
    -- | A list of tags to apply to the application.
    CreateApplication -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The application definition for this application. You can specify either
    -- inline JSON or an S3 bucket location.
    CreateApplication -> Definition
definition :: Definition,
    -- | The type of the target platform for this application.
    CreateApplication -> EngineType
engineType :: EngineType,
    -- | The unique identifier of the application.
    CreateApplication -> Text
name :: Prelude.Text
  }
  deriving (CreateApplication -> CreateApplication -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateApplication -> CreateApplication -> Bool
$c/= :: CreateApplication -> CreateApplication -> Bool
== :: CreateApplication -> CreateApplication -> Bool
$c== :: CreateApplication -> CreateApplication -> Bool
Prelude.Eq, ReadPrec [CreateApplication]
ReadPrec CreateApplication
Int -> ReadS CreateApplication
ReadS [CreateApplication]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateApplication]
$creadListPrec :: ReadPrec [CreateApplication]
readPrec :: ReadPrec CreateApplication
$creadPrec :: ReadPrec CreateApplication
readList :: ReadS [CreateApplication]
$creadList :: ReadS [CreateApplication]
readsPrec :: Int -> ReadS CreateApplication
$creadsPrec :: Int -> ReadS CreateApplication
Prelude.Read, Int -> CreateApplication -> ShowS
[CreateApplication] -> ShowS
CreateApplication -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateApplication] -> ShowS
$cshowList :: [CreateApplication] -> ShowS
show :: CreateApplication -> String
$cshow :: CreateApplication -> String
showsPrec :: Int -> CreateApplication -> ShowS
$cshowsPrec :: Int -> CreateApplication -> ShowS
Prelude.Show, forall x. Rep CreateApplication x -> CreateApplication
forall x. CreateApplication -> Rep CreateApplication x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateApplication x -> CreateApplication
$cfrom :: forall x. CreateApplication -> Rep CreateApplication x
Prelude.Generic)

-- |
-- Create a value of 'CreateApplication' 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:
--
-- 'clientToken', 'createApplication_clientToken' - Unique, case-sensitive identifier the service generates to ensure the
-- idempotency of the request to create an application. The service
-- generates the clientToken when the API call is triggered. The token
-- expires after one hour, so if you retry the API within this timeframe
-- with the same clientToken, you will get the same response. The service
-- also handles deleting the clientToken after it expires.
--
-- 'description', 'createApplication_description' - The description of the application.
--
-- 'kmsKeyId', 'createApplication_kmsKeyId' - The identifier of a customer managed key.
--
-- 'tags', 'createApplication_tags' - A list of tags to apply to the application.
--
-- 'definition', 'createApplication_definition' - The application definition for this application. You can specify either
-- inline JSON or an S3 bucket location.
--
-- 'engineType', 'createApplication_engineType' - The type of the target platform for this application.
--
-- 'name', 'createApplication_name' - The unique identifier of the application.
newCreateApplication ::
  -- | 'definition'
  Definition ->
  -- | 'engineType'
  EngineType ->
  -- | 'name'
  Prelude.Text ->
  CreateApplication
newCreateApplication :: Definition -> EngineType -> Text -> CreateApplication
newCreateApplication Definition
pDefinition_ EngineType
pEngineType_ Text
pName_ =
  CreateApplication'
    { $sel:clientToken:CreateApplication' :: Maybe Text
clientToken = forall a. Maybe a
Prelude.Nothing,
      $sel:description:CreateApplication' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:kmsKeyId:CreateApplication' :: Maybe Text
kmsKeyId = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateApplication' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:definition:CreateApplication' :: Definition
definition = Definition
pDefinition_,
      $sel:engineType:CreateApplication' :: EngineType
engineType = EngineType
pEngineType_,
      $sel:name:CreateApplication' :: Text
name = Text
pName_
    }

-- | Unique, case-sensitive identifier the service generates to ensure the
-- idempotency of the request to create an application. The service
-- generates the clientToken when the API call is triggered. The token
-- expires after one hour, so if you retry the API within this timeframe
-- with the same clientToken, you will get the same response. The service
-- also handles deleting the clientToken after it expires.
createApplication_clientToken :: Lens.Lens' CreateApplication (Prelude.Maybe Prelude.Text)
createApplication_clientToken :: Lens' CreateApplication (Maybe Text)
createApplication_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateApplication' {Maybe Text
clientToken :: Maybe Text
$sel:clientToken:CreateApplication' :: CreateApplication -> Maybe Text
clientToken} -> Maybe Text
clientToken) (\s :: CreateApplication
s@CreateApplication' {} Maybe Text
a -> CreateApplication
s {$sel:clientToken:CreateApplication' :: Maybe Text
clientToken = Maybe Text
a} :: CreateApplication)

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

-- | The identifier of a customer managed key.
createApplication_kmsKeyId :: Lens.Lens' CreateApplication (Prelude.Maybe Prelude.Text)
createApplication_kmsKeyId :: Lens' CreateApplication (Maybe Text)
createApplication_kmsKeyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateApplication' {Maybe Text
kmsKeyId :: Maybe Text
$sel:kmsKeyId:CreateApplication' :: CreateApplication -> Maybe Text
kmsKeyId} -> Maybe Text
kmsKeyId) (\s :: CreateApplication
s@CreateApplication' {} Maybe Text
a -> CreateApplication
s {$sel:kmsKeyId:CreateApplication' :: Maybe Text
kmsKeyId = Maybe Text
a} :: CreateApplication)

-- | A list of tags to apply to the application.
createApplication_tags :: Lens.Lens' CreateApplication (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createApplication_tags :: Lens' CreateApplication (Maybe (HashMap Text Text))
createApplication_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateApplication' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:CreateApplication' :: CreateApplication -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: CreateApplication
s@CreateApplication' {} Maybe (HashMap Text Text)
a -> CreateApplication
s {$sel:tags:CreateApplication' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: CreateApplication) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The application definition for this application. You can specify either
-- inline JSON or an S3 bucket location.
createApplication_definition :: Lens.Lens' CreateApplication Definition
createApplication_definition :: Lens' CreateApplication Definition
createApplication_definition = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateApplication' {Definition
definition :: Definition
$sel:definition:CreateApplication' :: CreateApplication -> Definition
definition} -> Definition
definition) (\s :: CreateApplication
s@CreateApplication' {} Definition
a -> CreateApplication
s {$sel:definition:CreateApplication' :: Definition
definition = Definition
a} :: CreateApplication)

-- | The type of the target platform for this application.
createApplication_engineType :: Lens.Lens' CreateApplication EngineType
createApplication_engineType :: Lens' CreateApplication EngineType
createApplication_engineType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateApplication' {EngineType
engineType :: EngineType
$sel:engineType:CreateApplication' :: CreateApplication -> EngineType
engineType} -> EngineType
engineType) (\s :: CreateApplication
s@CreateApplication' {} EngineType
a -> CreateApplication
s {$sel:engineType:CreateApplication' :: EngineType
engineType = EngineType
a} :: CreateApplication)

-- | The unique identifier of the application.
createApplication_name :: Lens.Lens' CreateApplication Prelude.Text
createApplication_name :: Lens' CreateApplication Text
createApplication_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateApplication' {Text
name :: Text
$sel:name:CreateApplication' :: CreateApplication -> Text
name} -> Text
name) (\s :: CreateApplication
s@CreateApplication' {} Text
a -> CreateApplication
s {$sel:name:CreateApplication' :: Text
name = Text
a} :: CreateApplication)

instance Core.AWSRequest CreateApplication where
  type
    AWSResponse CreateApplication =
      CreateApplicationResponse
  request :: (Service -> Service)
-> CreateApplication -> Request CreateApplication
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 CreateApplication
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateApplication)))
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 -> Text -> Text -> Natural -> CreateApplicationResponse
CreateApplicationResponse'
            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
"applicationArn")
            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
"applicationId")
            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
"applicationVersion")
      )

instance Prelude.Hashable CreateApplication where
  hashWithSalt :: Int -> CreateApplication -> Int
hashWithSalt Int
_salt CreateApplication' {Maybe Text
Maybe (HashMap Text Text)
Text
Definition
EngineType
name :: Text
engineType :: EngineType
definition :: Definition
tags :: Maybe (HashMap Text Text)
kmsKeyId :: Maybe Text
description :: Maybe Text
clientToken :: Maybe Text
$sel:name:CreateApplication' :: CreateApplication -> Text
$sel:engineType:CreateApplication' :: CreateApplication -> EngineType
$sel:definition:CreateApplication' :: CreateApplication -> Definition
$sel:tags:CreateApplication' :: CreateApplication -> Maybe (HashMap Text Text)
$sel:kmsKeyId:CreateApplication' :: CreateApplication -> Maybe Text
$sel:description:CreateApplication' :: CreateApplication -> Maybe Text
$sel:clientToken:CreateApplication' :: CreateApplication -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
kmsKeyId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Definition
definition
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` EngineType
engineType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name

instance Prelude.NFData CreateApplication where
  rnf :: CreateApplication -> ()
rnf CreateApplication' {Maybe Text
Maybe (HashMap Text Text)
Text
Definition
EngineType
name :: Text
engineType :: EngineType
definition :: Definition
tags :: Maybe (HashMap Text Text)
kmsKeyId :: Maybe Text
description :: Maybe Text
clientToken :: Maybe Text
$sel:name:CreateApplication' :: CreateApplication -> Text
$sel:engineType:CreateApplication' :: CreateApplication -> EngineType
$sel:definition:CreateApplication' :: CreateApplication -> Definition
$sel:tags:CreateApplication' :: CreateApplication -> Maybe (HashMap Text Text)
$sel:kmsKeyId:CreateApplication' :: CreateApplication -> Maybe Text
$sel:description:CreateApplication' :: CreateApplication -> Maybe Text
$sel:clientToken:CreateApplication' :: CreateApplication -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
kmsKeyId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Definition
definition
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf EngineType
engineType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name

instance Data.ToHeaders CreateApplication where
  toHeaders :: CreateApplication -> 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 CreateApplication where
  toJSON :: CreateApplication -> Value
toJSON CreateApplication' {Maybe Text
Maybe (HashMap Text Text)
Text
Definition
EngineType
name :: Text
engineType :: EngineType
definition :: Definition
tags :: Maybe (HashMap Text Text)
kmsKeyId :: Maybe Text
description :: Maybe Text
clientToken :: Maybe Text
$sel:name:CreateApplication' :: CreateApplication -> Text
$sel:engineType:CreateApplication' :: CreateApplication -> EngineType
$sel:definition:CreateApplication' :: CreateApplication -> Definition
$sel:tags:CreateApplication' :: CreateApplication -> Maybe (HashMap Text Text)
$sel:kmsKeyId:CreateApplication' :: CreateApplication -> Maybe Text
$sel:description:CreateApplication' :: CreateApplication -> Maybe Text
$sel:clientToken:CreateApplication' :: CreateApplication -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"clientToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
clientToken,
            (Key
"description" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
description,
            (Key
"kmsKeyId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
kmsKeyId,
            (Key
"tags" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (HashMap Text Text)
tags,
            forall a. a -> Maybe a
Prelude.Just (Key
"definition" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Definition
definition),
            forall a. a -> Maybe a
Prelude.Just (Key
"engineType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= EngineType
engineType),
            forall a. a -> Maybe a
Prelude.Just (Key
"name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
name)
          ]
      )

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

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

-- | /See:/ 'newCreateApplicationResponse' smart constructor.
data CreateApplicationResponse = CreateApplicationResponse'
  { -- | The response's http status code.
    CreateApplicationResponse -> Int
httpStatus :: Prelude.Int,
    -- | The Amazon Resource Name (ARN) of the application.
    CreateApplicationResponse -> Text
applicationArn :: Prelude.Text,
    -- | The unique application identifier.
    CreateApplicationResponse -> Text
applicationId :: Prelude.Text,
    -- | The version number of the application.
    CreateApplicationResponse -> Natural
applicationVersion :: Prelude.Natural
  }
  deriving (CreateApplicationResponse -> CreateApplicationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateApplicationResponse -> CreateApplicationResponse -> Bool
$c/= :: CreateApplicationResponse -> CreateApplicationResponse -> Bool
== :: CreateApplicationResponse -> CreateApplicationResponse -> Bool
$c== :: CreateApplicationResponse -> CreateApplicationResponse -> Bool
Prelude.Eq, ReadPrec [CreateApplicationResponse]
ReadPrec CreateApplicationResponse
Int -> ReadS CreateApplicationResponse
ReadS [CreateApplicationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateApplicationResponse]
$creadListPrec :: ReadPrec [CreateApplicationResponse]
readPrec :: ReadPrec CreateApplicationResponse
$creadPrec :: ReadPrec CreateApplicationResponse
readList :: ReadS [CreateApplicationResponse]
$creadList :: ReadS [CreateApplicationResponse]
readsPrec :: Int -> ReadS CreateApplicationResponse
$creadsPrec :: Int -> ReadS CreateApplicationResponse
Prelude.Read, Int -> CreateApplicationResponse -> ShowS
[CreateApplicationResponse] -> ShowS
CreateApplicationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateApplicationResponse] -> ShowS
$cshowList :: [CreateApplicationResponse] -> ShowS
show :: CreateApplicationResponse -> String
$cshow :: CreateApplicationResponse -> String
showsPrec :: Int -> CreateApplicationResponse -> ShowS
$cshowsPrec :: Int -> CreateApplicationResponse -> ShowS
Prelude.Show, forall x.
Rep CreateApplicationResponse x -> CreateApplicationResponse
forall x.
CreateApplicationResponse -> Rep CreateApplicationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateApplicationResponse x -> CreateApplicationResponse
$cfrom :: forall x.
CreateApplicationResponse -> Rep CreateApplicationResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateApplicationResponse' 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', 'createApplicationResponse_httpStatus' - The response's http status code.
--
-- 'applicationArn', 'createApplicationResponse_applicationArn' - The Amazon Resource Name (ARN) of the application.
--
-- 'applicationId', 'createApplicationResponse_applicationId' - The unique application identifier.
--
-- 'applicationVersion', 'createApplicationResponse_applicationVersion' - The version number of the application.
newCreateApplicationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'applicationArn'
  Prelude.Text ->
  -- | 'applicationId'
  Prelude.Text ->
  -- | 'applicationVersion'
  Prelude.Natural ->
  CreateApplicationResponse
newCreateApplicationResponse :: Int -> Text -> Text -> Natural -> CreateApplicationResponse
newCreateApplicationResponse
  Int
pHttpStatus_
  Text
pApplicationArn_
  Text
pApplicationId_
  Natural
pApplicationVersion_ =
    CreateApplicationResponse'
      { $sel:httpStatus:CreateApplicationResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:applicationArn:CreateApplicationResponse' :: Text
applicationArn = Text
pApplicationArn_,
        $sel:applicationId:CreateApplicationResponse' :: Text
applicationId = Text
pApplicationId_,
        $sel:applicationVersion:CreateApplicationResponse' :: Natural
applicationVersion = Natural
pApplicationVersion_
      }

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

-- | The Amazon Resource Name (ARN) of the application.
createApplicationResponse_applicationArn :: Lens.Lens' CreateApplicationResponse Prelude.Text
createApplicationResponse_applicationArn :: Lens' CreateApplicationResponse Text
createApplicationResponse_applicationArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateApplicationResponse' {Text
applicationArn :: Text
$sel:applicationArn:CreateApplicationResponse' :: CreateApplicationResponse -> Text
applicationArn} -> Text
applicationArn) (\s :: CreateApplicationResponse
s@CreateApplicationResponse' {} Text
a -> CreateApplicationResponse
s {$sel:applicationArn:CreateApplicationResponse' :: Text
applicationArn = Text
a} :: CreateApplicationResponse)

-- | The unique application identifier.
createApplicationResponse_applicationId :: Lens.Lens' CreateApplicationResponse Prelude.Text
createApplicationResponse_applicationId :: Lens' CreateApplicationResponse Text
createApplicationResponse_applicationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateApplicationResponse' {Text
applicationId :: Text
$sel:applicationId:CreateApplicationResponse' :: CreateApplicationResponse -> Text
applicationId} -> Text
applicationId) (\s :: CreateApplicationResponse
s@CreateApplicationResponse' {} Text
a -> CreateApplicationResponse
s {$sel:applicationId:CreateApplicationResponse' :: Text
applicationId = Text
a} :: CreateApplicationResponse)

-- | The version number of the application.
createApplicationResponse_applicationVersion :: Lens.Lens' CreateApplicationResponse Prelude.Natural
createApplicationResponse_applicationVersion :: Lens' CreateApplicationResponse Natural
createApplicationResponse_applicationVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateApplicationResponse' {Natural
applicationVersion :: Natural
$sel:applicationVersion:CreateApplicationResponse' :: CreateApplicationResponse -> Natural
applicationVersion} -> Natural
applicationVersion) (\s :: CreateApplicationResponse
s@CreateApplicationResponse' {} Natural
a -> CreateApplicationResponse
s {$sel:applicationVersion:CreateApplicationResponse' :: Natural
applicationVersion = Natural
a} :: CreateApplicationResponse)

instance Prelude.NFData CreateApplicationResponse where
  rnf :: CreateApplicationResponse -> ()
rnf CreateApplicationResponse' {Int
Natural
Text
applicationVersion :: Natural
applicationId :: Text
applicationArn :: Text
httpStatus :: Int
$sel:applicationVersion:CreateApplicationResponse' :: CreateApplicationResponse -> Natural
$sel:applicationId:CreateApplicationResponse' :: CreateApplicationResponse -> Text
$sel:applicationArn:CreateApplicationResponse' :: CreateApplicationResponse -> Text
$sel:httpStatus:CreateApplicationResponse' :: CreateApplicationResponse -> 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 Text
applicationArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
applicationId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Natural
applicationVersion