{-# 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 #-}
module Amazonka.AppStream.CreateApplication
(
CreateApplication (..),
newCreateApplication,
createApplication_description,
createApplication_displayName,
createApplication_launchParameters,
createApplication_tags,
createApplication_workingDirectory,
createApplication_name,
createApplication_iconS3Location,
createApplication_launchPath,
createApplication_platforms,
createApplication_instanceFamilies,
createApplication_appBlockArn,
CreateApplicationResponse (..),
newCreateApplicationResponse,
createApplicationResponse_application,
createApplicationResponse_httpStatus,
)
where
import Amazonka.AppStream.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
data CreateApplication = CreateApplication'
{
CreateApplication -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
CreateApplication -> Maybe Text
displayName :: Prelude.Maybe Prelude.Text,
CreateApplication -> Maybe Text
launchParameters :: Prelude.Maybe Prelude.Text,
CreateApplication -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
CreateApplication -> Maybe Text
workingDirectory :: Prelude.Maybe Prelude.Text,
CreateApplication -> Text
name :: Prelude.Text,
CreateApplication -> S3Location
iconS3Location :: S3Location,
CreateApplication -> Text
launchPath :: Prelude.Text,
CreateApplication -> [PlatformType]
platforms :: [PlatformType],
CreateApplication -> [Text]
instanceFamilies :: [Prelude.Text],
CreateApplication -> Text
appBlockArn :: 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)
newCreateApplication ::
Prelude.Text ->
S3Location ->
Prelude.Text ->
Prelude.Text ->
CreateApplication
newCreateApplication :: Text -> S3Location -> Text -> Text -> CreateApplication
newCreateApplication
Text
pName_
S3Location
pIconS3Location_
Text
pLaunchPath_
Text
pAppBlockArn_ =
CreateApplication'
{ $sel:description:CreateApplication' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
$sel:displayName:CreateApplication' :: Maybe Text
displayName = forall a. Maybe a
Prelude.Nothing,
$sel:launchParameters:CreateApplication' :: Maybe Text
launchParameters = forall a. Maybe a
Prelude.Nothing,
$sel:tags:CreateApplication' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
$sel:workingDirectory:CreateApplication' :: Maybe Text
workingDirectory = forall a. Maybe a
Prelude.Nothing,
$sel:name:CreateApplication' :: Text
name = Text
pName_,
$sel:iconS3Location:CreateApplication' :: S3Location
iconS3Location = S3Location
pIconS3Location_,
$sel:launchPath:CreateApplication' :: Text
launchPath = Text
pLaunchPath_,
$sel:platforms:CreateApplication' :: [PlatformType]
platforms = forall a. Monoid a => a
Prelude.mempty,
$sel:instanceFamilies:CreateApplication' :: [Text]
instanceFamilies = forall a. Monoid a => a
Prelude.mempty,
$sel:appBlockArn:CreateApplication' :: Text
appBlockArn = Text
pAppBlockArn_
}
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)
createApplication_displayName :: Lens.Lens' CreateApplication (Prelude.Maybe Prelude.Text)
createApplication_displayName :: Lens' CreateApplication (Maybe Text)
createApplication_displayName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateApplication' {Maybe Text
displayName :: Maybe Text
$sel:displayName:CreateApplication' :: CreateApplication -> Maybe Text
displayName} -> Maybe Text
displayName) (\s :: CreateApplication
s@CreateApplication' {} Maybe Text
a -> CreateApplication
s {$sel:displayName:CreateApplication' :: Maybe Text
displayName = Maybe Text
a} :: CreateApplication)
createApplication_launchParameters :: Lens.Lens' CreateApplication (Prelude.Maybe Prelude.Text)
createApplication_launchParameters :: Lens' CreateApplication (Maybe Text)
createApplication_launchParameters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateApplication' {Maybe Text
launchParameters :: Maybe Text
$sel:launchParameters:CreateApplication' :: CreateApplication -> Maybe Text
launchParameters} -> Maybe Text
launchParameters) (\s :: CreateApplication
s@CreateApplication' {} Maybe Text
a -> CreateApplication
s {$sel:launchParameters:CreateApplication' :: Maybe Text
launchParameters = Maybe Text
a} :: CreateApplication)
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
createApplication_workingDirectory :: Lens.Lens' CreateApplication (Prelude.Maybe Prelude.Text)
createApplication_workingDirectory :: Lens' CreateApplication (Maybe Text)
createApplication_workingDirectory = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateApplication' {Maybe Text
workingDirectory :: Maybe Text
$sel:workingDirectory:CreateApplication' :: CreateApplication -> Maybe Text
workingDirectory} -> Maybe Text
workingDirectory) (\s :: CreateApplication
s@CreateApplication' {} Maybe Text
a -> CreateApplication
s {$sel:workingDirectory:CreateApplication' :: Maybe Text
workingDirectory = Maybe Text
a} :: CreateApplication)
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)
createApplication_iconS3Location :: Lens.Lens' CreateApplication S3Location
createApplication_iconS3Location :: Lens' CreateApplication S3Location
createApplication_iconS3Location = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateApplication' {S3Location
iconS3Location :: S3Location
$sel:iconS3Location:CreateApplication' :: CreateApplication -> S3Location
iconS3Location} -> S3Location
iconS3Location) (\s :: CreateApplication
s@CreateApplication' {} S3Location
a -> CreateApplication
s {$sel:iconS3Location:CreateApplication' :: S3Location
iconS3Location = S3Location
a} :: CreateApplication)
createApplication_launchPath :: Lens.Lens' CreateApplication Prelude.Text
createApplication_launchPath :: Lens' CreateApplication Text
createApplication_launchPath = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateApplication' {Text
launchPath :: Text
$sel:launchPath:CreateApplication' :: CreateApplication -> Text
launchPath} -> Text
launchPath) (\s :: CreateApplication
s@CreateApplication' {} Text
a -> CreateApplication
s {$sel:launchPath:CreateApplication' :: Text
launchPath = Text
a} :: CreateApplication)
createApplication_platforms :: Lens.Lens' CreateApplication [PlatformType]
createApplication_platforms :: Lens' CreateApplication [PlatformType]
createApplication_platforms = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateApplication' {[PlatformType]
platforms :: [PlatformType]
$sel:platforms:CreateApplication' :: CreateApplication -> [PlatformType]
platforms} -> [PlatformType]
platforms) (\s :: CreateApplication
s@CreateApplication' {} [PlatformType]
a -> CreateApplication
s {$sel:platforms:CreateApplication' :: [PlatformType]
platforms = [PlatformType]
a} :: CreateApplication) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced
createApplication_instanceFamilies :: Lens.Lens' CreateApplication [Prelude.Text]
createApplication_instanceFamilies :: Lens' CreateApplication [Text]
createApplication_instanceFamilies = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateApplication' {[Text]
instanceFamilies :: [Text]
$sel:instanceFamilies:CreateApplication' :: CreateApplication -> [Text]
instanceFamilies} -> [Text]
instanceFamilies) (\s :: CreateApplication
s@CreateApplication' {} [Text]
a -> CreateApplication
s {$sel:instanceFamilies:CreateApplication' :: [Text]
instanceFamilies = [Text]
a} :: CreateApplication) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced
createApplication_appBlockArn :: Lens.Lens' CreateApplication Prelude.Text
createApplication_appBlockArn :: Lens' CreateApplication Text
createApplication_appBlockArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateApplication' {Text
appBlockArn :: Text
$sel:appBlockArn:CreateApplication' :: CreateApplication -> Text
appBlockArn} -> Text
appBlockArn) (\s :: CreateApplication
s@CreateApplication' {} Text
a -> CreateApplication
s {$sel:appBlockArn:CreateApplication' :: Text
appBlockArn = 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 ->
Maybe Application -> Int -> CreateApplicationResponse
CreateApplicationResponse'
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
"Application")
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 CreateApplication where
hashWithSalt :: Int -> CreateApplication -> Int
hashWithSalt Int
_salt CreateApplication' {[Text]
[PlatformType]
Maybe Text
Maybe (HashMap Text Text)
Text
S3Location
appBlockArn :: Text
instanceFamilies :: [Text]
platforms :: [PlatformType]
launchPath :: Text
iconS3Location :: S3Location
name :: Text
workingDirectory :: Maybe Text
tags :: Maybe (HashMap Text Text)
launchParameters :: Maybe Text
displayName :: Maybe Text
description :: Maybe Text
$sel:appBlockArn:CreateApplication' :: CreateApplication -> Text
$sel:instanceFamilies:CreateApplication' :: CreateApplication -> [Text]
$sel:platforms:CreateApplication' :: CreateApplication -> [PlatformType]
$sel:launchPath:CreateApplication' :: CreateApplication -> Text
$sel:iconS3Location:CreateApplication' :: CreateApplication -> S3Location
$sel:name:CreateApplication' :: CreateApplication -> Text
$sel:workingDirectory:CreateApplication' :: CreateApplication -> Maybe Text
$sel:tags:CreateApplication' :: CreateApplication -> Maybe (HashMap Text Text)
$sel:launchParameters:CreateApplication' :: CreateApplication -> Maybe Text
$sel:displayName:CreateApplication' :: CreateApplication -> Maybe Text
$sel:description:CreateApplication' :: CreateApplication -> Maybe Text
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
displayName
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
launchParameters
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
workingDirectory
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` S3Location
iconS3Location
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
launchPath
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [PlatformType]
platforms
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Text]
instanceFamilies
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
appBlockArn
instance Prelude.NFData CreateApplication where
rnf :: CreateApplication -> ()
rnf CreateApplication' {[Text]
[PlatformType]
Maybe Text
Maybe (HashMap Text Text)
Text
S3Location
appBlockArn :: Text
instanceFamilies :: [Text]
platforms :: [PlatformType]
launchPath :: Text
iconS3Location :: S3Location
name :: Text
workingDirectory :: Maybe Text
tags :: Maybe (HashMap Text Text)
launchParameters :: Maybe Text
displayName :: Maybe Text
description :: Maybe Text
$sel:appBlockArn:CreateApplication' :: CreateApplication -> Text
$sel:instanceFamilies:CreateApplication' :: CreateApplication -> [Text]
$sel:platforms:CreateApplication' :: CreateApplication -> [PlatformType]
$sel:launchPath:CreateApplication' :: CreateApplication -> Text
$sel:iconS3Location:CreateApplication' :: CreateApplication -> S3Location
$sel:name:CreateApplication' :: CreateApplication -> Text
$sel:workingDirectory:CreateApplication' :: CreateApplication -> Maybe Text
$sel:tags:CreateApplication' :: CreateApplication -> Maybe (HashMap Text Text)
$sel:launchParameters:CreateApplication' :: CreateApplication -> Maybe Text
$sel:displayName:CreateApplication' :: CreateApplication -> Maybe Text
$sel:description:CreateApplication' :: CreateApplication -> Maybe Text
..} =
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
displayName
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
launchParameters
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 Maybe Text
workingDirectory
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf S3Location
iconS3Location
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
launchPath
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [PlatformType]
platforms
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [Text]
instanceFamilies
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
appBlockArn
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
"X-Amz-Target"
forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"PhotonAdminProxyService.CreateApplication" ::
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 CreateApplication where
toJSON :: CreateApplication -> Value
toJSON CreateApplication' {[Text]
[PlatformType]
Maybe Text
Maybe (HashMap Text Text)
Text
S3Location
appBlockArn :: Text
instanceFamilies :: [Text]
platforms :: [PlatformType]
launchPath :: Text
iconS3Location :: S3Location
name :: Text
workingDirectory :: Maybe Text
tags :: Maybe (HashMap Text Text)
launchParameters :: Maybe Text
displayName :: Maybe Text
description :: Maybe Text
$sel:appBlockArn:CreateApplication' :: CreateApplication -> Text
$sel:instanceFamilies:CreateApplication' :: CreateApplication -> [Text]
$sel:platforms:CreateApplication' :: CreateApplication -> [PlatformType]
$sel:launchPath:CreateApplication' :: CreateApplication -> Text
$sel:iconS3Location:CreateApplication' :: CreateApplication -> S3Location
$sel:name:CreateApplication' :: CreateApplication -> Text
$sel:workingDirectory:CreateApplication' :: CreateApplication -> Maybe Text
$sel:tags:CreateApplication' :: CreateApplication -> Maybe (HashMap Text Text)
$sel:launchParameters:CreateApplication' :: CreateApplication -> Maybe Text
$sel:displayName:CreateApplication' :: CreateApplication -> Maybe Text
$sel:description:CreateApplication' :: CreateApplication -> Maybe Text
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[ (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
"DisplayName" 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
displayName,
(Key
"LaunchParameters" 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
launchParameters,
(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,
(Key
"WorkingDirectory" 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
workingDirectory,
forall a. a -> Maybe a
Prelude.Just (Key
"Name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
name),
forall a. a -> Maybe a
Prelude.Just
(Key
"IconS3Location" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= S3Location
iconS3Location),
forall a. a -> Maybe a
Prelude.Just (Key
"LaunchPath" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
launchPath),
forall a. a -> Maybe a
Prelude.Just (Key
"Platforms" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= [PlatformType]
platforms),
forall a. a -> Maybe a
Prelude.Just
(Key
"InstanceFamilies" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= [Text]
instanceFamilies),
forall a. a -> Maybe a
Prelude.Just (Key
"AppBlockArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
appBlockArn)
]
)
instance Data.ToPath CreateApplication where
toPath :: CreateApplication -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery CreateApplication where
toQuery :: CreateApplication -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data CreateApplicationResponse = CreateApplicationResponse'
{ CreateApplicationResponse -> Maybe Application
application :: Prelude.Maybe Application,
CreateApplicationResponse -> Int
httpStatus :: Prelude.Int
}
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)
newCreateApplicationResponse ::
Prelude.Int ->
CreateApplicationResponse
newCreateApplicationResponse :: Int -> CreateApplicationResponse
newCreateApplicationResponse Int
pHttpStatus_ =
CreateApplicationResponse'
{ $sel:application:CreateApplicationResponse' :: Maybe Application
application =
forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:CreateApplicationResponse' :: Int
httpStatus = Int
pHttpStatus_
}
createApplicationResponse_application :: Lens.Lens' CreateApplicationResponse (Prelude.Maybe Application)
createApplicationResponse_application :: Lens' CreateApplicationResponse (Maybe Application)
createApplicationResponse_application = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateApplicationResponse' {Maybe Application
application :: Maybe Application
$sel:application:CreateApplicationResponse' :: CreateApplicationResponse -> Maybe Application
application} -> Maybe Application
application) (\s :: CreateApplicationResponse
s@CreateApplicationResponse' {} Maybe Application
a -> CreateApplicationResponse
s {$sel:application:CreateApplicationResponse' :: Maybe Application
application = Maybe Application
a} :: CreateApplicationResponse)
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)
instance Prelude.NFData CreateApplicationResponse where
rnf :: CreateApplicationResponse -> ()
rnf CreateApplicationResponse' {Int
Maybe Application
httpStatus :: Int
application :: Maybe Application
$sel:httpStatus:CreateApplicationResponse' :: CreateApplicationResponse -> Int
$sel:application:CreateApplicationResponse' :: CreateApplicationResponse -> Maybe Application
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Application
application
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus