{-# 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.BatchDescribeTypeConfigurations
(
BatchDescribeTypeConfigurations (..),
newBatchDescribeTypeConfigurations,
batchDescribeTypeConfigurations_typeConfigurationIdentifiers,
BatchDescribeTypeConfigurationsResponse (..),
newBatchDescribeTypeConfigurationsResponse,
batchDescribeTypeConfigurationsResponse_errors,
batchDescribeTypeConfigurationsResponse_typeConfigurations,
batchDescribeTypeConfigurationsResponse_unprocessedTypeConfigurations,
batchDescribeTypeConfigurationsResponse_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 BatchDescribeTypeConfigurations = BatchDescribeTypeConfigurations'
{
BatchDescribeTypeConfigurations
-> NonEmpty TypeConfigurationIdentifier
typeConfigurationIdentifiers :: Prelude.NonEmpty TypeConfigurationIdentifier
}
deriving (BatchDescribeTypeConfigurations
-> BatchDescribeTypeConfigurations -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BatchDescribeTypeConfigurations
-> BatchDescribeTypeConfigurations -> Bool
$c/= :: BatchDescribeTypeConfigurations
-> BatchDescribeTypeConfigurations -> Bool
== :: BatchDescribeTypeConfigurations
-> BatchDescribeTypeConfigurations -> Bool
$c== :: BatchDescribeTypeConfigurations
-> BatchDescribeTypeConfigurations -> Bool
Prelude.Eq, ReadPrec [BatchDescribeTypeConfigurations]
ReadPrec BatchDescribeTypeConfigurations
Int -> ReadS BatchDescribeTypeConfigurations
ReadS [BatchDescribeTypeConfigurations]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BatchDescribeTypeConfigurations]
$creadListPrec :: ReadPrec [BatchDescribeTypeConfigurations]
readPrec :: ReadPrec BatchDescribeTypeConfigurations
$creadPrec :: ReadPrec BatchDescribeTypeConfigurations
readList :: ReadS [BatchDescribeTypeConfigurations]
$creadList :: ReadS [BatchDescribeTypeConfigurations]
readsPrec :: Int -> ReadS BatchDescribeTypeConfigurations
$creadsPrec :: Int -> ReadS BatchDescribeTypeConfigurations
Prelude.Read, Int -> BatchDescribeTypeConfigurations -> ShowS
[BatchDescribeTypeConfigurations] -> ShowS
BatchDescribeTypeConfigurations -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchDescribeTypeConfigurations] -> ShowS
$cshowList :: [BatchDescribeTypeConfigurations] -> ShowS
show :: BatchDescribeTypeConfigurations -> String
$cshow :: BatchDescribeTypeConfigurations -> String
showsPrec :: Int -> BatchDescribeTypeConfigurations -> ShowS
$cshowsPrec :: Int -> BatchDescribeTypeConfigurations -> ShowS
Prelude.Show, forall x.
Rep BatchDescribeTypeConfigurations x
-> BatchDescribeTypeConfigurations
forall x.
BatchDescribeTypeConfigurations
-> Rep BatchDescribeTypeConfigurations x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep BatchDescribeTypeConfigurations x
-> BatchDescribeTypeConfigurations
$cfrom :: forall x.
BatchDescribeTypeConfigurations
-> Rep BatchDescribeTypeConfigurations x
Prelude.Generic)
newBatchDescribeTypeConfigurations ::
Prelude.NonEmpty TypeConfigurationIdentifier ->
BatchDescribeTypeConfigurations
newBatchDescribeTypeConfigurations :: NonEmpty TypeConfigurationIdentifier
-> BatchDescribeTypeConfigurations
newBatchDescribeTypeConfigurations
NonEmpty TypeConfigurationIdentifier
pTypeConfigurationIdentifiers_ =
BatchDescribeTypeConfigurations'
{ $sel:typeConfigurationIdentifiers:BatchDescribeTypeConfigurations' :: NonEmpty TypeConfigurationIdentifier
typeConfigurationIdentifiers =
forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced
forall t b. AReview t b -> b -> t
Lens.# NonEmpty TypeConfigurationIdentifier
pTypeConfigurationIdentifiers_
}
batchDescribeTypeConfigurations_typeConfigurationIdentifiers :: Lens.Lens' BatchDescribeTypeConfigurations (Prelude.NonEmpty TypeConfigurationIdentifier)
batchDescribeTypeConfigurations_typeConfigurationIdentifiers :: Lens'
BatchDescribeTypeConfigurations
(NonEmpty TypeConfigurationIdentifier)
batchDescribeTypeConfigurations_typeConfigurationIdentifiers = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchDescribeTypeConfigurations' {NonEmpty TypeConfigurationIdentifier
typeConfigurationIdentifiers :: NonEmpty TypeConfigurationIdentifier
$sel:typeConfigurationIdentifiers:BatchDescribeTypeConfigurations' :: BatchDescribeTypeConfigurations
-> NonEmpty TypeConfigurationIdentifier
typeConfigurationIdentifiers} -> NonEmpty TypeConfigurationIdentifier
typeConfigurationIdentifiers) (\s :: BatchDescribeTypeConfigurations
s@BatchDescribeTypeConfigurations' {} NonEmpty TypeConfigurationIdentifier
a -> BatchDescribeTypeConfigurations
s {$sel:typeConfigurationIdentifiers:BatchDescribeTypeConfigurations' :: NonEmpty TypeConfigurationIdentifier
typeConfigurationIdentifiers = NonEmpty TypeConfigurationIdentifier
a} :: BatchDescribeTypeConfigurations) 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
instance
Core.AWSRequest
BatchDescribeTypeConfigurations
where
type
AWSResponse BatchDescribeTypeConfigurations =
BatchDescribeTypeConfigurationsResponse
request :: (Service -> Service)
-> BatchDescribeTypeConfigurations
-> Request BatchDescribeTypeConfigurations
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 BatchDescribeTypeConfigurations
-> ClientResponse ClientBody
-> m (Either
Error
(ClientResponse (AWSResponse BatchDescribeTypeConfigurations)))
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
"BatchDescribeTypeConfigurationsResult"
( \Int
s ResponseHeaders
h [Node]
x ->
Maybe [BatchDescribeTypeConfigurationsError]
-> Maybe [TypeConfigurationDetails]
-> Maybe [TypeConfigurationIdentifier]
-> Int
-> BatchDescribeTypeConfigurationsResponse
BatchDescribeTypeConfigurationsResponse'
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
"Errors"
forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member")
)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"TypeConfigurations"
forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member")
)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"UnprocessedTypeConfigurations"
forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member")
)
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
BatchDescribeTypeConfigurations
where
hashWithSalt :: Int -> BatchDescribeTypeConfigurations -> Int
hashWithSalt
Int
_salt
BatchDescribeTypeConfigurations' {NonEmpty TypeConfigurationIdentifier
typeConfigurationIdentifiers :: NonEmpty TypeConfigurationIdentifier
$sel:typeConfigurationIdentifiers:BatchDescribeTypeConfigurations' :: BatchDescribeTypeConfigurations
-> NonEmpty TypeConfigurationIdentifier
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NonEmpty TypeConfigurationIdentifier
typeConfigurationIdentifiers
instance
Prelude.NFData
BatchDescribeTypeConfigurations
where
rnf :: BatchDescribeTypeConfigurations -> ()
rnf BatchDescribeTypeConfigurations' {NonEmpty TypeConfigurationIdentifier
typeConfigurationIdentifiers :: NonEmpty TypeConfigurationIdentifier
$sel:typeConfigurationIdentifiers:BatchDescribeTypeConfigurations' :: BatchDescribeTypeConfigurations
-> NonEmpty TypeConfigurationIdentifier
..} =
forall a. NFData a => a -> ()
Prelude.rnf NonEmpty TypeConfigurationIdentifier
typeConfigurationIdentifiers
instance
Data.ToHeaders
BatchDescribeTypeConfigurations
where
toHeaders :: BatchDescribeTypeConfigurations -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
instance Data.ToPath BatchDescribeTypeConfigurations where
toPath :: BatchDescribeTypeConfigurations -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery BatchDescribeTypeConfigurations where
toQuery :: BatchDescribeTypeConfigurations -> QueryString
toQuery BatchDescribeTypeConfigurations' {NonEmpty TypeConfigurationIdentifier
typeConfigurationIdentifiers :: NonEmpty TypeConfigurationIdentifier
$sel:typeConfigurationIdentifiers:BatchDescribeTypeConfigurations' :: BatchDescribeTypeConfigurations
-> NonEmpty TypeConfigurationIdentifier
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat
[ ByteString
"Action"
forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ( ByteString
"BatchDescribeTypeConfigurations" ::
Prelude.ByteString
),
ByteString
"Version"
forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-05-15" :: Prelude.ByteString),
ByteString
"TypeConfigurationIdentifiers"
forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList
ByteString
"member"
NonEmpty TypeConfigurationIdentifier
typeConfigurationIdentifiers
]
data BatchDescribeTypeConfigurationsResponse = BatchDescribeTypeConfigurationsResponse'
{
BatchDescribeTypeConfigurationsResponse
-> Maybe [BatchDescribeTypeConfigurationsError]
errors :: Prelude.Maybe [BatchDescribeTypeConfigurationsError],
BatchDescribeTypeConfigurationsResponse
-> Maybe [TypeConfigurationDetails]
typeConfigurations :: Prelude.Maybe [TypeConfigurationDetails],
BatchDescribeTypeConfigurationsResponse
-> Maybe [TypeConfigurationIdentifier]
unprocessedTypeConfigurations :: Prelude.Maybe [TypeConfigurationIdentifier],
BatchDescribeTypeConfigurationsResponse -> Int
httpStatus :: Prelude.Int
}
deriving (BatchDescribeTypeConfigurationsResponse
-> BatchDescribeTypeConfigurationsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BatchDescribeTypeConfigurationsResponse
-> BatchDescribeTypeConfigurationsResponse -> Bool
$c/= :: BatchDescribeTypeConfigurationsResponse
-> BatchDescribeTypeConfigurationsResponse -> Bool
== :: BatchDescribeTypeConfigurationsResponse
-> BatchDescribeTypeConfigurationsResponse -> Bool
$c== :: BatchDescribeTypeConfigurationsResponse
-> BatchDescribeTypeConfigurationsResponse -> Bool
Prelude.Eq, ReadPrec [BatchDescribeTypeConfigurationsResponse]
ReadPrec BatchDescribeTypeConfigurationsResponse
Int -> ReadS BatchDescribeTypeConfigurationsResponse
ReadS [BatchDescribeTypeConfigurationsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BatchDescribeTypeConfigurationsResponse]
$creadListPrec :: ReadPrec [BatchDescribeTypeConfigurationsResponse]
readPrec :: ReadPrec BatchDescribeTypeConfigurationsResponse
$creadPrec :: ReadPrec BatchDescribeTypeConfigurationsResponse
readList :: ReadS [BatchDescribeTypeConfigurationsResponse]
$creadList :: ReadS [BatchDescribeTypeConfigurationsResponse]
readsPrec :: Int -> ReadS BatchDescribeTypeConfigurationsResponse
$creadsPrec :: Int -> ReadS BatchDescribeTypeConfigurationsResponse
Prelude.Read, Int -> BatchDescribeTypeConfigurationsResponse -> ShowS
[BatchDescribeTypeConfigurationsResponse] -> ShowS
BatchDescribeTypeConfigurationsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchDescribeTypeConfigurationsResponse] -> ShowS
$cshowList :: [BatchDescribeTypeConfigurationsResponse] -> ShowS
show :: BatchDescribeTypeConfigurationsResponse -> String
$cshow :: BatchDescribeTypeConfigurationsResponse -> String
showsPrec :: Int -> BatchDescribeTypeConfigurationsResponse -> ShowS
$cshowsPrec :: Int -> BatchDescribeTypeConfigurationsResponse -> ShowS
Prelude.Show, forall x.
Rep BatchDescribeTypeConfigurationsResponse x
-> BatchDescribeTypeConfigurationsResponse
forall x.
BatchDescribeTypeConfigurationsResponse
-> Rep BatchDescribeTypeConfigurationsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep BatchDescribeTypeConfigurationsResponse x
-> BatchDescribeTypeConfigurationsResponse
$cfrom :: forall x.
BatchDescribeTypeConfigurationsResponse
-> Rep BatchDescribeTypeConfigurationsResponse x
Prelude.Generic)
newBatchDescribeTypeConfigurationsResponse ::
Prelude.Int ->
BatchDescribeTypeConfigurationsResponse
newBatchDescribeTypeConfigurationsResponse :: Int -> BatchDescribeTypeConfigurationsResponse
newBatchDescribeTypeConfigurationsResponse
Int
pHttpStatus_ =
BatchDescribeTypeConfigurationsResponse'
{ $sel:errors:BatchDescribeTypeConfigurationsResponse' :: Maybe [BatchDescribeTypeConfigurationsError]
errors =
forall a. Maybe a
Prelude.Nothing,
$sel:typeConfigurations:BatchDescribeTypeConfigurationsResponse' :: Maybe [TypeConfigurationDetails]
typeConfigurations =
forall a. Maybe a
Prelude.Nothing,
$sel:unprocessedTypeConfigurations:BatchDescribeTypeConfigurationsResponse' :: Maybe [TypeConfigurationIdentifier]
unprocessedTypeConfigurations =
forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:BatchDescribeTypeConfigurationsResponse' :: Int
httpStatus = Int
pHttpStatus_
}
batchDescribeTypeConfigurationsResponse_errors :: Lens.Lens' BatchDescribeTypeConfigurationsResponse (Prelude.Maybe [BatchDescribeTypeConfigurationsError])
batchDescribeTypeConfigurationsResponse_errors :: Lens'
BatchDescribeTypeConfigurationsResponse
(Maybe [BatchDescribeTypeConfigurationsError])
batchDescribeTypeConfigurationsResponse_errors = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchDescribeTypeConfigurationsResponse' {Maybe [BatchDescribeTypeConfigurationsError]
errors :: Maybe [BatchDescribeTypeConfigurationsError]
$sel:errors:BatchDescribeTypeConfigurationsResponse' :: BatchDescribeTypeConfigurationsResponse
-> Maybe [BatchDescribeTypeConfigurationsError]
errors} -> Maybe [BatchDescribeTypeConfigurationsError]
errors) (\s :: BatchDescribeTypeConfigurationsResponse
s@BatchDescribeTypeConfigurationsResponse' {} Maybe [BatchDescribeTypeConfigurationsError]
a -> BatchDescribeTypeConfigurationsResponse
s {$sel:errors:BatchDescribeTypeConfigurationsResponse' :: Maybe [BatchDescribeTypeConfigurationsError]
errors = Maybe [BatchDescribeTypeConfigurationsError]
a} :: BatchDescribeTypeConfigurationsResponse) 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
batchDescribeTypeConfigurationsResponse_typeConfigurations :: Lens.Lens' BatchDescribeTypeConfigurationsResponse (Prelude.Maybe [TypeConfigurationDetails])
batchDescribeTypeConfigurationsResponse_typeConfigurations :: Lens'
BatchDescribeTypeConfigurationsResponse
(Maybe [TypeConfigurationDetails])
batchDescribeTypeConfigurationsResponse_typeConfigurations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchDescribeTypeConfigurationsResponse' {Maybe [TypeConfigurationDetails]
typeConfigurations :: Maybe [TypeConfigurationDetails]
$sel:typeConfigurations:BatchDescribeTypeConfigurationsResponse' :: BatchDescribeTypeConfigurationsResponse
-> Maybe [TypeConfigurationDetails]
typeConfigurations} -> Maybe [TypeConfigurationDetails]
typeConfigurations) (\s :: BatchDescribeTypeConfigurationsResponse
s@BatchDescribeTypeConfigurationsResponse' {} Maybe [TypeConfigurationDetails]
a -> BatchDescribeTypeConfigurationsResponse
s {$sel:typeConfigurations:BatchDescribeTypeConfigurationsResponse' :: Maybe [TypeConfigurationDetails]
typeConfigurations = Maybe [TypeConfigurationDetails]
a} :: BatchDescribeTypeConfigurationsResponse) 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
batchDescribeTypeConfigurationsResponse_unprocessedTypeConfigurations :: Lens.Lens' BatchDescribeTypeConfigurationsResponse (Prelude.Maybe [TypeConfigurationIdentifier])
batchDescribeTypeConfigurationsResponse_unprocessedTypeConfigurations :: Lens'
BatchDescribeTypeConfigurationsResponse
(Maybe [TypeConfigurationIdentifier])
batchDescribeTypeConfigurationsResponse_unprocessedTypeConfigurations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchDescribeTypeConfigurationsResponse' {Maybe [TypeConfigurationIdentifier]
unprocessedTypeConfigurations :: Maybe [TypeConfigurationIdentifier]
$sel:unprocessedTypeConfigurations:BatchDescribeTypeConfigurationsResponse' :: BatchDescribeTypeConfigurationsResponse
-> Maybe [TypeConfigurationIdentifier]
unprocessedTypeConfigurations} -> Maybe [TypeConfigurationIdentifier]
unprocessedTypeConfigurations) (\s :: BatchDescribeTypeConfigurationsResponse
s@BatchDescribeTypeConfigurationsResponse' {} Maybe [TypeConfigurationIdentifier]
a -> BatchDescribeTypeConfigurationsResponse
s {$sel:unprocessedTypeConfigurations:BatchDescribeTypeConfigurationsResponse' :: Maybe [TypeConfigurationIdentifier]
unprocessedTypeConfigurations = Maybe [TypeConfigurationIdentifier]
a} :: BatchDescribeTypeConfigurationsResponse) 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
batchDescribeTypeConfigurationsResponse_httpStatus :: Lens.Lens' BatchDescribeTypeConfigurationsResponse Prelude.Int
batchDescribeTypeConfigurationsResponse_httpStatus :: Lens' BatchDescribeTypeConfigurationsResponse Int
batchDescribeTypeConfigurationsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchDescribeTypeConfigurationsResponse' {Int
httpStatus :: Int
$sel:httpStatus:BatchDescribeTypeConfigurationsResponse' :: BatchDescribeTypeConfigurationsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: BatchDescribeTypeConfigurationsResponse
s@BatchDescribeTypeConfigurationsResponse' {} Int
a -> BatchDescribeTypeConfigurationsResponse
s {$sel:httpStatus:BatchDescribeTypeConfigurationsResponse' :: Int
httpStatus = Int
a} :: BatchDescribeTypeConfigurationsResponse)
instance
Prelude.NFData
BatchDescribeTypeConfigurationsResponse
where
rnf :: BatchDescribeTypeConfigurationsResponse -> ()
rnf BatchDescribeTypeConfigurationsResponse' {Int
Maybe [TypeConfigurationDetails]
Maybe [TypeConfigurationIdentifier]
Maybe [BatchDescribeTypeConfigurationsError]
httpStatus :: Int
unprocessedTypeConfigurations :: Maybe [TypeConfigurationIdentifier]
typeConfigurations :: Maybe [TypeConfigurationDetails]
errors :: Maybe [BatchDescribeTypeConfigurationsError]
$sel:httpStatus:BatchDescribeTypeConfigurationsResponse' :: BatchDescribeTypeConfigurationsResponse -> Int
$sel:unprocessedTypeConfigurations:BatchDescribeTypeConfigurationsResponse' :: BatchDescribeTypeConfigurationsResponse
-> Maybe [TypeConfigurationIdentifier]
$sel:typeConfigurations:BatchDescribeTypeConfigurationsResponse' :: BatchDescribeTypeConfigurationsResponse
-> Maybe [TypeConfigurationDetails]
$sel:errors:BatchDescribeTypeConfigurationsResponse' :: BatchDescribeTypeConfigurationsResponse
-> Maybe [BatchDescribeTypeConfigurationsError]
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe [BatchDescribeTypeConfigurationsError]
errors
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [TypeConfigurationDetails]
typeConfigurations
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [TypeConfigurationIdentifier]
unprocessedTypeConfigurations
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus