{-# 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.ResourceGroups.PutGroupConfiguration
(
PutGroupConfiguration (..),
newPutGroupConfiguration,
putGroupConfiguration_configuration,
putGroupConfiguration_group,
PutGroupConfigurationResponse (..),
newPutGroupConfigurationResponse,
putGroupConfigurationResponse_httpStatus,
)
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import Amazonka.ResourceGroups.Types
import qualified Amazonka.Response as Response
data PutGroupConfiguration = PutGroupConfiguration'
{
PutGroupConfiguration -> Maybe [GroupConfigurationItem]
configuration :: Prelude.Maybe [GroupConfigurationItem],
PutGroupConfiguration -> Maybe Text
group' :: Prelude.Maybe Prelude.Text
}
deriving (PutGroupConfiguration -> PutGroupConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutGroupConfiguration -> PutGroupConfiguration -> Bool
$c/= :: PutGroupConfiguration -> PutGroupConfiguration -> Bool
== :: PutGroupConfiguration -> PutGroupConfiguration -> Bool
$c== :: PutGroupConfiguration -> PutGroupConfiguration -> Bool
Prelude.Eq, ReadPrec [PutGroupConfiguration]
ReadPrec PutGroupConfiguration
Int -> ReadS PutGroupConfiguration
ReadS [PutGroupConfiguration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PutGroupConfiguration]
$creadListPrec :: ReadPrec [PutGroupConfiguration]
readPrec :: ReadPrec PutGroupConfiguration
$creadPrec :: ReadPrec PutGroupConfiguration
readList :: ReadS [PutGroupConfiguration]
$creadList :: ReadS [PutGroupConfiguration]
readsPrec :: Int -> ReadS PutGroupConfiguration
$creadsPrec :: Int -> ReadS PutGroupConfiguration
Prelude.Read, Int -> PutGroupConfiguration -> ShowS
[PutGroupConfiguration] -> ShowS
PutGroupConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutGroupConfiguration] -> ShowS
$cshowList :: [PutGroupConfiguration] -> ShowS
show :: PutGroupConfiguration -> String
$cshow :: PutGroupConfiguration -> String
showsPrec :: Int -> PutGroupConfiguration -> ShowS
$cshowsPrec :: Int -> PutGroupConfiguration -> ShowS
Prelude.Show, forall x. Rep PutGroupConfiguration x -> PutGroupConfiguration
forall x. PutGroupConfiguration -> Rep PutGroupConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PutGroupConfiguration x -> PutGroupConfiguration
$cfrom :: forall x. PutGroupConfiguration -> Rep PutGroupConfiguration x
Prelude.Generic)
newPutGroupConfiguration ::
PutGroupConfiguration
newPutGroupConfiguration :: PutGroupConfiguration
newPutGroupConfiguration =
PutGroupConfiguration'
{ $sel:configuration:PutGroupConfiguration' :: Maybe [GroupConfigurationItem]
configuration =
forall a. Maybe a
Prelude.Nothing,
$sel:group':PutGroupConfiguration' :: Maybe Text
group' = forall a. Maybe a
Prelude.Nothing
}
putGroupConfiguration_configuration :: Lens.Lens' PutGroupConfiguration (Prelude.Maybe [GroupConfigurationItem])
putGroupConfiguration_configuration :: Lens' PutGroupConfiguration (Maybe [GroupConfigurationItem])
putGroupConfiguration_configuration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutGroupConfiguration' {Maybe [GroupConfigurationItem]
configuration :: Maybe [GroupConfigurationItem]
$sel:configuration:PutGroupConfiguration' :: PutGroupConfiguration -> Maybe [GroupConfigurationItem]
configuration} -> Maybe [GroupConfigurationItem]
configuration) (\s :: PutGroupConfiguration
s@PutGroupConfiguration' {} Maybe [GroupConfigurationItem]
a -> PutGroupConfiguration
s {$sel:configuration:PutGroupConfiguration' :: Maybe [GroupConfigurationItem]
configuration = Maybe [GroupConfigurationItem]
a} :: PutGroupConfiguration) 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
putGroupConfiguration_group :: Lens.Lens' PutGroupConfiguration (Prelude.Maybe Prelude.Text)
putGroupConfiguration_group :: Lens' PutGroupConfiguration (Maybe Text)
putGroupConfiguration_group = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutGroupConfiguration' {Maybe Text
group' :: Maybe Text
$sel:group':PutGroupConfiguration' :: PutGroupConfiguration -> Maybe Text
group'} -> Maybe Text
group') (\s :: PutGroupConfiguration
s@PutGroupConfiguration' {} Maybe Text
a -> PutGroupConfiguration
s {$sel:group':PutGroupConfiguration' :: Maybe Text
group' = Maybe Text
a} :: PutGroupConfiguration)
instance Core.AWSRequest PutGroupConfiguration where
type
AWSResponse PutGroupConfiguration =
PutGroupConfigurationResponse
request :: (Service -> Service)
-> PutGroupConfiguration -> Request PutGroupConfiguration
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 PutGroupConfiguration
-> ClientResponse ClientBody
-> m (Either
Error (ClientResponse (AWSResponse PutGroupConfiguration)))
response =
forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
( \Int
s ResponseHeaders
h ()
x ->
Int -> PutGroupConfigurationResponse
PutGroupConfigurationResponse'
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))
)
instance Prelude.Hashable PutGroupConfiguration where
hashWithSalt :: Int -> PutGroupConfiguration -> Int
hashWithSalt Int
_salt PutGroupConfiguration' {Maybe [GroupConfigurationItem]
Maybe Text
group' :: Maybe Text
configuration :: Maybe [GroupConfigurationItem]
$sel:group':PutGroupConfiguration' :: PutGroupConfiguration -> Maybe Text
$sel:configuration:PutGroupConfiguration' :: PutGroupConfiguration -> Maybe [GroupConfigurationItem]
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [GroupConfigurationItem]
configuration
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
group'
instance Prelude.NFData PutGroupConfiguration where
rnf :: PutGroupConfiguration -> ()
rnf PutGroupConfiguration' {Maybe [GroupConfigurationItem]
Maybe Text
group' :: Maybe Text
configuration :: Maybe [GroupConfigurationItem]
$sel:group':PutGroupConfiguration' :: PutGroupConfiguration -> Maybe Text
$sel:configuration:PutGroupConfiguration' :: PutGroupConfiguration -> Maybe [GroupConfigurationItem]
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe [GroupConfigurationItem]
configuration
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
group'
instance Data.ToHeaders PutGroupConfiguration where
toHeaders :: PutGroupConfiguration -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
instance Data.ToJSON PutGroupConfiguration where
toJSON :: PutGroupConfiguration -> Value
toJSON PutGroupConfiguration' {Maybe [GroupConfigurationItem]
Maybe Text
group' :: Maybe Text
configuration :: Maybe [GroupConfigurationItem]
$sel:group':PutGroupConfiguration' :: PutGroupConfiguration -> Maybe Text
$sel:configuration:PutGroupConfiguration' :: PutGroupConfiguration -> Maybe [GroupConfigurationItem]
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[ (Key
"Configuration" 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 [GroupConfigurationItem]
configuration,
(Key
"Group" 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
group'
]
)
instance Data.ToPath PutGroupConfiguration where
toPath :: PutGroupConfiguration -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/put-group-configuration"
instance Data.ToQuery PutGroupConfiguration where
toQuery :: PutGroupConfiguration -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data PutGroupConfigurationResponse = PutGroupConfigurationResponse'
{
PutGroupConfigurationResponse -> Int
httpStatus :: Prelude.Int
}
deriving (PutGroupConfigurationResponse
-> PutGroupConfigurationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutGroupConfigurationResponse
-> PutGroupConfigurationResponse -> Bool
$c/= :: PutGroupConfigurationResponse
-> PutGroupConfigurationResponse -> Bool
== :: PutGroupConfigurationResponse
-> PutGroupConfigurationResponse -> Bool
$c== :: PutGroupConfigurationResponse
-> PutGroupConfigurationResponse -> Bool
Prelude.Eq, ReadPrec [PutGroupConfigurationResponse]
ReadPrec PutGroupConfigurationResponse
Int -> ReadS PutGroupConfigurationResponse
ReadS [PutGroupConfigurationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PutGroupConfigurationResponse]
$creadListPrec :: ReadPrec [PutGroupConfigurationResponse]
readPrec :: ReadPrec PutGroupConfigurationResponse
$creadPrec :: ReadPrec PutGroupConfigurationResponse
readList :: ReadS [PutGroupConfigurationResponse]
$creadList :: ReadS [PutGroupConfigurationResponse]
readsPrec :: Int -> ReadS PutGroupConfigurationResponse
$creadsPrec :: Int -> ReadS PutGroupConfigurationResponse
Prelude.Read, Int -> PutGroupConfigurationResponse -> ShowS
[PutGroupConfigurationResponse] -> ShowS
PutGroupConfigurationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutGroupConfigurationResponse] -> ShowS
$cshowList :: [PutGroupConfigurationResponse] -> ShowS
show :: PutGroupConfigurationResponse -> String
$cshow :: PutGroupConfigurationResponse -> String
showsPrec :: Int -> PutGroupConfigurationResponse -> ShowS
$cshowsPrec :: Int -> PutGroupConfigurationResponse -> ShowS
Prelude.Show, forall x.
Rep PutGroupConfigurationResponse x
-> PutGroupConfigurationResponse
forall x.
PutGroupConfigurationResponse
-> Rep PutGroupConfigurationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep PutGroupConfigurationResponse x
-> PutGroupConfigurationResponse
$cfrom :: forall x.
PutGroupConfigurationResponse
-> Rep PutGroupConfigurationResponse x
Prelude.Generic)
newPutGroupConfigurationResponse ::
Prelude.Int ->
PutGroupConfigurationResponse
newPutGroupConfigurationResponse :: Int -> PutGroupConfigurationResponse
newPutGroupConfigurationResponse Int
pHttpStatus_ =
PutGroupConfigurationResponse'
{ $sel:httpStatus:PutGroupConfigurationResponse' :: Int
httpStatus =
Int
pHttpStatus_
}
putGroupConfigurationResponse_httpStatus :: Lens.Lens' PutGroupConfigurationResponse Prelude.Int
putGroupConfigurationResponse_httpStatus :: Lens' PutGroupConfigurationResponse Int
putGroupConfigurationResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutGroupConfigurationResponse' {Int
httpStatus :: Int
$sel:httpStatus:PutGroupConfigurationResponse' :: PutGroupConfigurationResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: PutGroupConfigurationResponse
s@PutGroupConfigurationResponse' {} Int
a -> PutGroupConfigurationResponse
s {$sel:httpStatus:PutGroupConfigurationResponse' :: Int
httpStatus = Int
a} :: PutGroupConfigurationResponse)
instance Prelude.NFData PutGroupConfigurationResponse where
rnf :: PutGroupConfigurationResponse -> ()
rnf PutGroupConfigurationResponse' {Int
httpStatus :: Int
$sel:httpStatus:PutGroupConfigurationResponse' :: PutGroupConfigurationResponse -> Int
..} =
forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus