{-# 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.CloudFormation.EstimateTemplateCost
(
EstimateTemplateCost (..),
newEstimateTemplateCost,
estimateTemplateCost_parameters,
estimateTemplateCost_templateBody,
estimateTemplateCost_templateURL,
EstimateTemplateCostResponse (..),
newEstimateTemplateCostResponse,
estimateTemplateCostResponse_url,
estimateTemplateCostResponse_httpStatus,
)
where
import Amazonka.CloudFormation.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 EstimateTemplateCost = EstimateTemplateCost'
{
EstimateTemplateCost -> Maybe [Parameter]
parameters :: Prelude.Maybe [Parameter],
EstimateTemplateCost -> Maybe Text
templateBody :: Prelude.Maybe Prelude.Text,
EstimateTemplateCost -> Maybe Text
templateURL :: Prelude.Maybe Prelude.Text
}
deriving (EstimateTemplateCost -> EstimateTemplateCost -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EstimateTemplateCost -> EstimateTemplateCost -> Bool
$c/= :: EstimateTemplateCost -> EstimateTemplateCost -> Bool
== :: EstimateTemplateCost -> EstimateTemplateCost -> Bool
$c== :: EstimateTemplateCost -> EstimateTemplateCost -> Bool
Prelude.Eq, ReadPrec [EstimateTemplateCost]
ReadPrec EstimateTemplateCost
Int -> ReadS EstimateTemplateCost
ReadS [EstimateTemplateCost]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EstimateTemplateCost]
$creadListPrec :: ReadPrec [EstimateTemplateCost]
readPrec :: ReadPrec EstimateTemplateCost
$creadPrec :: ReadPrec EstimateTemplateCost
readList :: ReadS [EstimateTemplateCost]
$creadList :: ReadS [EstimateTemplateCost]
readsPrec :: Int -> ReadS EstimateTemplateCost
$creadsPrec :: Int -> ReadS EstimateTemplateCost
Prelude.Read, Int -> EstimateTemplateCost -> ShowS
[EstimateTemplateCost] -> ShowS
EstimateTemplateCost -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EstimateTemplateCost] -> ShowS
$cshowList :: [EstimateTemplateCost] -> ShowS
show :: EstimateTemplateCost -> String
$cshow :: EstimateTemplateCost -> String
showsPrec :: Int -> EstimateTemplateCost -> ShowS
$cshowsPrec :: Int -> EstimateTemplateCost -> ShowS
Prelude.Show, forall x. Rep EstimateTemplateCost x -> EstimateTemplateCost
forall x. EstimateTemplateCost -> Rep EstimateTemplateCost x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EstimateTemplateCost x -> EstimateTemplateCost
$cfrom :: forall x. EstimateTemplateCost -> Rep EstimateTemplateCost x
Prelude.Generic)
newEstimateTemplateCost ::
EstimateTemplateCost
newEstimateTemplateCost :: EstimateTemplateCost
newEstimateTemplateCost =
EstimateTemplateCost'
{ $sel:parameters:EstimateTemplateCost' :: Maybe [Parameter]
parameters = forall a. Maybe a
Prelude.Nothing,
$sel:templateBody:EstimateTemplateCost' :: Maybe Text
templateBody = forall a. Maybe a
Prelude.Nothing,
$sel:templateURL:EstimateTemplateCost' :: Maybe Text
templateURL = forall a. Maybe a
Prelude.Nothing
}
estimateTemplateCost_parameters :: Lens.Lens' EstimateTemplateCost (Prelude.Maybe [Parameter])
estimateTemplateCost_parameters :: Lens' EstimateTemplateCost (Maybe [Parameter])
estimateTemplateCost_parameters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EstimateTemplateCost' {Maybe [Parameter]
parameters :: Maybe [Parameter]
$sel:parameters:EstimateTemplateCost' :: EstimateTemplateCost -> Maybe [Parameter]
parameters} -> Maybe [Parameter]
parameters) (\s :: EstimateTemplateCost
s@EstimateTemplateCost' {} Maybe [Parameter]
a -> EstimateTemplateCost
s {$sel:parameters:EstimateTemplateCost' :: Maybe [Parameter]
parameters = Maybe [Parameter]
a} :: EstimateTemplateCost) 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
estimateTemplateCost_templateBody :: Lens.Lens' EstimateTemplateCost (Prelude.Maybe Prelude.Text)
estimateTemplateCost_templateBody :: Lens' EstimateTemplateCost (Maybe Text)
estimateTemplateCost_templateBody = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EstimateTemplateCost' {Maybe Text
templateBody :: Maybe Text
$sel:templateBody:EstimateTemplateCost' :: EstimateTemplateCost -> Maybe Text
templateBody} -> Maybe Text
templateBody) (\s :: EstimateTemplateCost
s@EstimateTemplateCost' {} Maybe Text
a -> EstimateTemplateCost
s {$sel:templateBody:EstimateTemplateCost' :: Maybe Text
templateBody = Maybe Text
a} :: EstimateTemplateCost)
estimateTemplateCost_templateURL :: Lens.Lens' EstimateTemplateCost (Prelude.Maybe Prelude.Text)
estimateTemplateCost_templateURL :: Lens' EstimateTemplateCost (Maybe Text)
estimateTemplateCost_templateURL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EstimateTemplateCost' {Maybe Text
templateURL :: Maybe Text
$sel:templateURL:EstimateTemplateCost' :: EstimateTemplateCost -> Maybe Text
templateURL} -> Maybe Text
templateURL) (\s :: EstimateTemplateCost
s@EstimateTemplateCost' {} Maybe Text
a -> EstimateTemplateCost
s {$sel:templateURL:EstimateTemplateCost' :: Maybe Text
templateURL = Maybe Text
a} :: EstimateTemplateCost)
instance Core.AWSRequest EstimateTemplateCost where
type
AWSResponse EstimateTemplateCost =
EstimateTemplateCostResponse
request :: (Service -> Service)
-> EstimateTemplateCost -> Request EstimateTemplateCost
request Service -> Service
overrides =
forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy EstimateTemplateCost
-> ClientResponse ClientBody
-> m (Either
Error (ClientResponse (AWSResponse EstimateTemplateCost)))
response =
forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
-> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
Text
"EstimateTemplateCostResult"
( \Int
s ResponseHeaders
h [Node]
x ->
Maybe Text -> Int -> EstimateTemplateCostResponse
EstimateTemplateCostResponse'
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Url")
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 EstimateTemplateCost where
hashWithSalt :: Int -> EstimateTemplateCost -> Int
hashWithSalt Int
_salt EstimateTemplateCost' {Maybe [Parameter]
Maybe Text
templateURL :: Maybe Text
templateBody :: Maybe Text
parameters :: Maybe [Parameter]
$sel:templateURL:EstimateTemplateCost' :: EstimateTemplateCost -> Maybe Text
$sel:templateBody:EstimateTemplateCost' :: EstimateTemplateCost -> Maybe Text
$sel:parameters:EstimateTemplateCost' :: EstimateTemplateCost -> Maybe [Parameter]
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Parameter]
parameters
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
templateBody
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
templateURL
instance Prelude.NFData EstimateTemplateCost where
rnf :: EstimateTemplateCost -> ()
rnf EstimateTemplateCost' {Maybe [Parameter]
Maybe Text
templateURL :: Maybe Text
templateBody :: Maybe Text
parameters :: Maybe [Parameter]
$sel:templateURL:EstimateTemplateCost' :: EstimateTemplateCost -> Maybe Text
$sel:templateBody:EstimateTemplateCost' :: EstimateTemplateCost -> Maybe Text
$sel:parameters:EstimateTemplateCost' :: EstimateTemplateCost -> Maybe [Parameter]
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe [Parameter]
parameters
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
templateBody
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
templateURL
instance Data.ToHeaders EstimateTemplateCost where
toHeaders :: EstimateTemplateCost -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
instance Data.ToPath EstimateTemplateCost where
toPath :: EstimateTemplateCost -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery EstimateTemplateCost where
toQuery :: EstimateTemplateCost -> QueryString
toQuery EstimateTemplateCost' {Maybe [Parameter]
Maybe Text
templateURL :: Maybe Text
templateBody :: Maybe Text
parameters :: Maybe [Parameter]
$sel:templateURL:EstimateTemplateCost' :: EstimateTemplateCost -> Maybe Text
$sel:templateBody:EstimateTemplateCost' :: EstimateTemplateCost -> Maybe Text
$sel:parameters:EstimateTemplateCost' :: EstimateTemplateCost -> Maybe [Parameter]
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat
[ ByteString
"Action"
forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"EstimateTemplateCost" :: Prelude.ByteString),
ByteString
"Version"
forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-05-15" :: Prelude.ByteString),
ByteString
"Parameters"
forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a. ToQuery a => a -> QueryString
Data.toQuery
(forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"member" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Parameter]
parameters),
ByteString
"TemplateBody" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
templateBody,
ByteString
"TemplateURL" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
templateURL
]
data EstimateTemplateCostResponse = EstimateTemplateCostResponse'
{
EstimateTemplateCostResponse -> Maybe Text
url :: Prelude.Maybe Prelude.Text,
EstimateTemplateCostResponse -> Int
httpStatus :: Prelude.Int
}
deriving (EstimateTemplateCostResponse
-> EstimateTemplateCostResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EstimateTemplateCostResponse
-> EstimateTemplateCostResponse -> Bool
$c/= :: EstimateTemplateCostResponse
-> EstimateTemplateCostResponse -> Bool
== :: EstimateTemplateCostResponse
-> EstimateTemplateCostResponse -> Bool
$c== :: EstimateTemplateCostResponse
-> EstimateTemplateCostResponse -> Bool
Prelude.Eq, ReadPrec [EstimateTemplateCostResponse]
ReadPrec EstimateTemplateCostResponse
Int -> ReadS EstimateTemplateCostResponse
ReadS [EstimateTemplateCostResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EstimateTemplateCostResponse]
$creadListPrec :: ReadPrec [EstimateTemplateCostResponse]
readPrec :: ReadPrec EstimateTemplateCostResponse
$creadPrec :: ReadPrec EstimateTemplateCostResponse
readList :: ReadS [EstimateTemplateCostResponse]
$creadList :: ReadS [EstimateTemplateCostResponse]
readsPrec :: Int -> ReadS EstimateTemplateCostResponse
$creadsPrec :: Int -> ReadS EstimateTemplateCostResponse
Prelude.Read, Int -> EstimateTemplateCostResponse -> ShowS
[EstimateTemplateCostResponse] -> ShowS
EstimateTemplateCostResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EstimateTemplateCostResponse] -> ShowS
$cshowList :: [EstimateTemplateCostResponse] -> ShowS
show :: EstimateTemplateCostResponse -> String
$cshow :: EstimateTemplateCostResponse -> String
showsPrec :: Int -> EstimateTemplateCostResponse -> ShowS
$cshowsPrec :: Int -> EstimateTemplateCostResponse -> ShowS
Prelude.Show, forall x.
Rep EstimateTemplateCostResponse x -> EstimateTemplateCostResponse
forall x.
EstimateTemplateCostResponse -> Rep EstimateTemplateCostResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep EstimateTemplateCostResponse x -> EstimateTemplateCostResponse
$cfrom :: forall x.
EstimateTemplateCostResponse -> Rep EstimateTemplateCostResponse x
Prelude.Generic)
newEstimateTemplateCostResponse ::
Prelude.Int ->
EstimateTemplateCostResponse
newEstimateTemplateCostResponse :: Int -> EstimateTemplateCostResponse
newEstimateTemplateCostResponse Int
pHttpStatus_ =
EstimateTemplateCostResponse'
{ $sel:url:EstimateTemplateCostResponse' :: Maybe Text
url =
forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:EstimateTemplateCostResponse' :: Int
httpStatus = Int
pHttpStatus_
}
estimateTemplateCostResponse_url :: Lens.Lens' EstimateTemplateCostResponse (Prelude.Maybe Prelude.Text)
estimateTemplateCostResponse_url :: Lens' EstimateTemplateCostResponse (Maybe Text)
estimateTemplateCostResponse_url = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EstimateTemplateCostResponse' {Maybe Text
url :: Maybe Text
$sel:url:EstimateTemplateCostResponse' :: EstimateTemplateCostResponse -> Maybe Text
url} -> Maybe Text
url) (\s :: EstimateTemplateCostResponse
s@EstimateTemplateCostResponse' {} Maybe Text
a -> EstimateTemplateCostResponse
s {$sel:url:EstimateTemplateCostResponse' :: Maybe Text
url = Maybe Text
a} :: EstimateTemplateCostResponse)
estimateTemplateCostResponse_httpStatus :: Lens.Lens' EstimateTemplateCostResponse Prelude.Int
estimateTemplateCostResponse_httpStatus :: Lens' EstimateTemplateCostResponse Int
estimateTemplateCostResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EstimateTemplateCostResponse' {Int
httpStatus :: Int
$sel:httpStatus:EstimateTemplateCostResponse' :: EstimateTemplateCostResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: EstimateTemplateCostResponse
s@EstimateTemplateCostResponse' {} Int
a -> EstimateTemplateCostResponse
s {$sel:httpStatus:EstimateTemplateCostResponse' :: Int
httpStatus = Int
a} :: EstimateTemplateCostResponse)
instance Prelude.NFData EstimateTemplateCostResponse where
rnf :: EstimateTemplateCostResponse -> ()
rnf EstimateTemplateCostResponse' {Int
Maybe Text
httpStatus :: Int
url :: Maybe Text
$sel:httpStatus:EstimateTemplateCostResponse' :: EstimateTemplateCostResponse -> Int
$sel:url:EstimateTemplateCostResponse' :: EstimateTemplateCostResponse -> Maybe Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
url
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus