{-# 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.ELBV2.ModifyRule
(
ModifyRule (..),
newModifyRule,
modifyRule_actions,
modifyRule_conditions,
modifyRule_ruleArn,
ModifyRuleResponse (..),
newModifyRuleResponse,
modifyRuleResponse_rules,
modifyRuleResponse_httpStatus,
)
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.ELBV2.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
data ModifyRule = ModifyRule'
{
ModifyRule -> Maybe [Action]
actions :: Prelude.Maybe [Action],
ModifyRule -> Maybe [RuleCondition]
conditions :: Prelude.Maybe [RuleCondition],
ModifyRule -> Text
ruleArn :: Prelude.Text
}
deriving (ModifyRule -> ModifyRule -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ModifyRule -> ModifyRule -> Bool
$c/= :: ModifyRule -> ModifyRule -> Bool
== :: ModifyRule -> ModifyRule -> Bool
$c== :: ModifyRule -> ModifyRule -> Bool
Prelude.Eq, ReadPrec [ModifyRule]
ReadPrec ModifyRule
Int -> ReadS ModifyRule
ReadS [ModifyRule]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ModifyRule]
$creadListPrec :: ReadPrec [ModifyRule]
readPrec :: ReadPrec ModifyRule
$creadPrec :: ReadPrec ModifyRule
readList :: ReadS [ModifyRule]
$creadList :: ReadS [ModifyRule]
readsPrec :: Int -> ReadS ModifyRule
$creadsPrec :: Int -> ReadS ModifyRule
Prelude.Read, Int -> ModifyRule -> ShowS
[ModifyRule] -> ShowS
ModifyRule -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ModifyRule] -> ShowS
$cshowList :: [ModifyRule] -> ShowS
show :: ModifyRule -> String
$cshow :: ModifyRule -> String
showsPrec :: Int -> ModifyRule -> ShowS
$cshowsPrec :: Int -> ModifyRule -> ShowS
Prelude.Show, forall x. Rep ModifyRule x -> ModifyRule
forall x. ModifyRule -> Rep ModifyRule x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ModifyRule x -> ModifyRule
$cfrom :: forall x. ModifyRule -> Rep ModifyRule x
Prelude.Generic)
newModifyRule ::
Prelude.Text ->
ModifyRule
newModifyRule :: Text -> ModifyRule
newModifyRule Text
pRuleArn_ =
ModifyRule'
{ $sel:actions:ModifyRule' :: Maybe [Action]
actions = forall a. Maybe a
Prelude.Nothing,
$sel:conditions:ModifyRule' :: Maybe [RuleCondition]
conditions = forall a. Maybe a
Prelude.Nothing,
$sel:ruleArn:ModifyRule' :: Text
ruleArn = Text
pRuleArn_
}
modifyRule_actions :: Lens.Lens' ModifyRule (Prelude.Maybe [Action])
modifyRule_actions :: Lens' ModifyRule (Maybe [Action])
modifyRule_actions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyRule' {Maybe [Action]
actions :: Maybe [Action]
$sel:actions:ModifyRule' :: ModifyRule -> Maybe [Action]
actions} -> Maybe [Action]
actions) (\s :: ModifyRule
s@ModifyRule' {} Maybe [Action]
a -> ModifyRule
s {$sel:actions:ModifyRule' :: Maybe [Action]
actions = Maybe [Action]
a} :: ModifyRule) 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
modifyRule_conditions :: Lens.Lens' ModifyRule (Prelude.Maybe [RuleCondition])
modifyRule_conditions :: Lens' ModifyRule (Maybe [RuleCondition])
modifyRule_conditions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyRule' {Maybe [RuleCondition]
conditions :: Maybe [RuleCondition]
$sel:conditions:ModifyRule' :: ModifyRule -> Maybe [RuleCondition]
conditions} -> Maybe [RuleCondition]
conditions) (\s :: ModifyRule
s@ModifyRule' {} Maybe [RuleCondition]
a -> ModifyRule
s {$sel:conditions:ModifyRule' :: Maybe [RuleCondition]
conditions = Maybe [RuleCondition]
a} :: ModifyRule) 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
modifyRule_ruleArn :: Lens.Lens' ModifyRule Prelude.Text
modifyRule_ruleArn :: Lens' ModifyRule Text
modifyRule_ruleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyRule' {Text
ruleArn :: Text
$sel:ruleArn:ModifyRule' :: ModifyRule -> Text
ruleArn} -> Text
ruleArn) (\s :: ModifyRule
s@ModifyRule' {} Text
a -> ModifyRule
s {$sel:ruleArn:ModifyRule' :: Text
ruleArn = Text
a} :: ModifyRule)
instance Core.AWSRequest ModifyRule where
type AWSResponse ModifyRule = ModifyRuleResponse
request :: (Service -> Service) -> ModifyRule -> Request ModifyRule
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 ModifyRule
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ModifyRule)))
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
"ModifyRuleResult"
( \Int
s ResponseHeaders
h [Node]
x ->
Maybe [Rule] -> Int -> ModifyRuleResponse
ModifyRuleResponse'
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
"Rules"
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 ModifyRule where
hashWithSalt :: Int -> ModifyRule -> Int
hashWithSalt Int
_salt ModifyRule' {Maybe [RuleCondition]
Maybe [Action]
Text
ruleArn :: Text
conditions :: Maybe [RuleCondition]
actions :: Maybe [Action]
$sel:ruleArn:ModifyRule' :: ModifyRule -> Text
$sel:conditions:ModifyRule' :: ModifyRule -> Maybe [RuleCondition]
$sel:actions:ModifyRule' :: ModifyRule -> Maybe [Action]
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Action]
actions
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [RuleCondition]
conditions
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
ruleArn
instance Prelude.NFData ModifyRule where
rnf :: ModifyRule -> ()
rnf ModifyRule' {Maybe [RuleCondition]
Maybe [Action]
Text
ruleArn :: Text
conditions :: Maybe [RuleCondition]
actions :: Maybe [Action]
$sel:ruleArn:ModifyRule' :: ModifyRule -> Text
$sel:conditions:ModifyRule' :: ModifyRule -> Maybe [RuleCondition]
$sel:actions:ModifyRule' :: ModifyRule -> Maybe [Action]
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe [Action]
actions
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [RuleCondition]
conditions
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
ruleArn
instance Data.ToHeaders ModifyRule where
toHeaders :: ModifyRule -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
instance Data.ToPath ModifyRule where
toPath :: ModifyRule -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery ModifyRule where
toQuery :: ModifyRule -> QueryString
toQuery ModifyRule' {Maybe [RuleCondition]
Maybe [Action]
Text
ruleArn :: Text
conditions :: Maybe [RuleCondition]
actions :: Maybe [Action]
$sel:ruleArn:ModifyRule' :: ModifyRule -> Text
$sel:conditions:ModifyRule' :: ModifyRule -> Maybe [RuleCondition]
$sel:actions:ModifyRule' :: ModifyRule -> Maybe [Action]
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat
[ ByteString
"Action"
forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"ModifyRule" :: Prelude.ByteString),
ByteString
"Version"
forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2015-12-01" :: Prelude.ByteString),
ByteString
"Actions"
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 [Action]
actions),
ByteString
"Conditions"
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 [RuleCondition]
conditions),
ByteString
"RuleArn" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
ruleArn
]
data ModifyRuleResponse = ModifyRuleResponse'
{
ModifyRuleResponse -> Maybe [Rule]
rules :: Prelude.Maybe [Rule],
ModifyRuleResponse -> Int
httpStatus :: Prelude.Int
}
deriving (ModifyRuleResponse -> ModifyRuleResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ModifyRuleResponse -> ModifyRuleResponse -> Bool
$c/= :: ModifyRuleResponse -> ModifyRuleResponse -> Bool
== :: ModifyRuleResponse -> ModifyRuleResponse -> Bool
$c== :: ModifyRuleResponse -> ModifyRuleResponse -> Bool
Prelude.Eq, ReadPrec [ModifyRuleResponse]
ReadPrec ModifyRuleResponse
Int -> ReadS ModifyRuleResponse
ReadS [ModifyRuleResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ModifyRuleResponse]
$creadListPrec :: ReadPrec [ModifyRuleResponse]
readPrec :: ReadPrec ModifyRuleResponse
$creadPrec :: ReadPrec ModifyRuleResponse
readList :: ReadS [ModifyRuleResponse]
$creadList :: ReadS [ModifyRuleResponse]
readsPrec :: Int -> ReadS ModifyRuleResponse
$creadsPrec :: Int -> ReadS ModifyRuleResponse
Prelude.Read, Int -> ModifyRuleResponse -> ShowS
[ModifyRuleResponse] -> ShowS
ModifyRuleResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ModifyRuleResponse] -> ShowS
$cshowList :: [ModifyRuleResponse] -> ShowS
show :: ModifyRuleResponse -> String
$cshow :: ModifyRuleResponse -> String
showsPrec :: Int -> ModifyRuleResponse -> ShowS
$cshowsPrec :: Int -> ModifyRuleResponse -> ShowS
Prelude.Show, forall x. Rep ModifyRuleResponse x -> ModifyRuleResponse
forall x. ModifyRuleResponse -> Rep ModifyRuleResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ModifyRuleResponse x -> ModifyRuleResponse
$cfrom :: forall x. ModifyRuleResponse -> Rep ModifyRuleResponse x
Prelude.Generic)
newModifyRuleResponse ::
Prelude.Int ->
ModifyRuleResponse
newModifyRuleResponse :: Int -> ModifyRuleResponse
newModifyRuleResponse Int
pHttpStatus_ =
ModifyRuleResponse'
{ $sel:rules:ModifyRuleResponse' :: Maybe [Rule]
rules = forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:ModifyRuleResponse' :: Int
httpStatus = Int
pHttpStatus_
}
modifyRuleResponse_rules :: Lens.Lens' ModifyRuleResponse (Prelude.Maybe [Rule])
modifyRuleResponse_rules :: Lens' ModifyRuleResponse (Maybe [Rule])
modifyRuleResponse_rules = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyRuleResponse' {Maybe [Rule]
rules :: Maybe [Rule]
$sel:rules:ModifyRuleResponse' :: ModifyRuleResponse -> Maybe [Rule]
rules} -> Maybe [Rule]
rules) (\s :: ModifyRuleResponse
s@ModifyRuleResponse' {} Maybe [Rule]
a -> ModifyRuleResponse
s {$sel:rules:ModifyRuleResponse' :: Maybe [Rule]
rules = Maybe [Rule]
a} :: ModifyRuleResponse) 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
modifyRuleResponse_httpStatus :: Lens.Lens' ModifyRuleResponse Prelude.Int
modifyRuleResponse_httpStatus :: Lens' ModifyRuleResponse Int
modifyRuleResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyRuleResponse' {Int
httpStatus :: Int
$sel:httpStatus:ModifyRuleResponse' :: ModifyRuleResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ModifyRuleResponse
s@ModifyRuleResponse' {} Int
a -> ModifyRuleResponse
s {$sel:httpStatus:ModifyRuleResponse' :: Int
httpStatus = Int
a} :: ModifyRuleResponse)
instance Prelude.NFData ModifyRuleResponse where
rnf :: ModifyRuleResponse -> ()
rnf ModifyRuleResponse' {Int
Maybe [Rule]
httpStatus :: Int
rules :: Maybe [Rule]
$sel:httpStatus:ModifyRuleResponse' :: ModifyRuleResponse -> Int
$sel:rules:ModifyRuleResponse' :: ModifyRuleResponse -> Maybe [Rule]
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe [Rule]
rules
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus