{-# 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.GlobalAccelerator.AdvertiseByoipCidr
(
AdvertiseByoipCidr (..),
newAdvertiseByoipCidr,
advertiseByoipCidr_cidr,
AdvertiseByoipCidrResponse (..),
newAdvertiseByoipCidrResponse,
advertiseByoipCidrResponse_byoipCidr,
advertiseByoipCidrResponse_httpStatus,
)
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.GlobalAccelerator.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
data AdvertiseByoipCidr = AdvertiseByoipCidr'
{
AdvertiseByoipCidr -> Text
cidr :: Prelude.Text
}
deriving (AdvertiseByoipCidr -> AdvertiseByoipCidr -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AdvertiseByoipCidr -> AdvertiseByoipCidr -> Bool
$c/= :: AdvertiseByoipCidr -> AdvertiseByoipCidr -> Bool
== :: AdvertiseByoipCidr -> AdvertiseByoipCidr -> Bool
$c== :: AdvertiseByoipCidr -> AdvertiseByoipCidr -> Bool
Prelude.Eq, ReadPrec [AdvertiseByoipCidr]
ReadPrec AdvertiseByoipCidr
Int -> ReadS AdvertiseByoipCidr
ReadS [AdvertiseByoipCidr]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AdvertiseByoipCidr]
$creadListPrec :: ReadPrec [AdvertiseByoipCidr]
readPrec :: ReadPrec AdvertiseByoipCidr
$creadPrec :: ReadPrec AdvertiseByoipCidr
readList :: ReadS [AdvertiseByoipCidr]
$creadList :: ReadS [AdvertiseByoipCidr]
readsPrec :: Int -> ReadS AdvertiseByoipCidr
$creadsPrec :: Int -> ReadS AdvertiseByoipCidr
Prelude.Read, Int -> AdvertiseByoipCidr -> ShowS
[AdvertiseByoipCidr] -> ShowS
AdvertiseByoipCidr -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AdvertiseByoipCidr] -> ShowS
$cshowList :: [AdvertiseByoipCidr] -> ShowS
show :: AdvertiseByoipCidr -> String
$cshow :: AdvertiseByoipCidr -> String
showsPrec :: Int -> AdvertiseByoipCidr -> ShowS
$cshowsPrec :: Int -> AdvertiseByoipCidr -> ShowS
Prelude.Show, forall x. Rep AdvertiseByoipCidr x -> AdvertiseByoipCidr
forall x. AdvertiseByoipCidr -> Rep AdvertiseByoipCidr x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AdvertiseByoipCidr x -> AdvertiseByoipCidr
$cfrom :: forall x. AdvertiseByoipCidr -> Rep AdvertiseByoipCidr x
Prelude.Generic)
newAdvertiseByoipCidr ::
Prelude.Text ->
AdvertiseByoipCidr
newAdvertiseByoipCidr :: Text -> AdvertiseByoipCidr
newAdvertiseByoipCidr Text
pCidr_ =
AdvertiseByoipCidr' {$sel:cidr:AdvertiseByoipCidr' :: Text
cidr = Text
pCidr_}
advertiseByoipCidr_cidr :: Lens.Lens' AdvertiseByoipCidr Prelude.Text
advertiseByoipCidr_cidr :: Lens' AdvertiseByoipCidr Text
advertiseByoipCidr_cidr = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AdvertiseByoipCidr' {Text
cidr :: Text
$sel:cidr:AdvertiseByoipCidr' :: AdvertiseByoipCidr -> Text
cidr} -> Text
cidr) (\s :: AdvertiseByoipCidr
s@AdvertiseByoipCidr' {} Text
a -> AdvertiseByoipCidr
s {$sel:cidr:AdvertiseByoipCidr' :: Text
cidr = Text
a} :: AdvertiseByoipCidr)
instance Core.AWSRequest AdvertiseByoipCidr where
type
AWSResponse AdvertiseByoipCidr =
AdvertiseByoipCidrResponse
request :: (Service -> Service)
-> AdvertiseByoipCidr -> Request AdvertiseByoipCidr
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 AdvertiseByoipCidr
-> ClientResponse ClientBody
-> m (Either
Error (ClientResponse (AWSResponse AdvertiseByoipCidr)))
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 ByoipCidr -> Int -> AdvertiseByoipCidrResponse
AdvertiseByoipCidrResponse'
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
"ByoipCidr")
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 AdvertiseByoipCidr where
hashWithSalt :: Int -> AdvertiseByoipCidr -> Int
hashWithSalt Int
_salt AdvertiseByoipCidr' {Text
cidr :: Text
$sel:cidr:AdvertiseByoipCidr' :: AdvertiseByoipCidr -> Text
..} =
Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
cidr
instance Prelude.NFData AdvertiseByoipCidr where
rnf :: AdvertiseByoipCidr -> ()
rnf AdvertiseByoipCidr' {Text
cidr :: Text
$sel:cidr:AdvertiseByoipCidr' :: AdvertiseByoipCidr -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
cidr
instance Data.ToHeaders AdvertiseByoipCidr where
toHeaders :: AdvertiseByoipCidr -> 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
"GlobalAccelerator_V20180706.AdvertiseByoipCidr" ::
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 AdvertiseByoipCidr where
toJSON :: AdvertiseByoipCidr -> Value
toJSON AdvertiseByoipCidr' {Text
cidr :: Text
$sel:cidr:AdvertiseByoipCidr' :: AdvertiseByoipCidr -> Text
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[forall a. a -> Maybe a
Prelude.Just (Key
"Cidr" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
cidr)]
)
instance Data.ToPath AdvertiseByoipCidr where
toPath :: AdvertiseByoipCidr -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery AdvertiseByoipCidr where
toQuery :: AdvertiseByoipCidr -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data AdvertiseByoipCidrResponse = AdvertiseByoipCidrResponse'
{
AdvertiseByoipCidrResponse -> Maybe ByoipCidr
byoipCidr :: Prelude.Maybe ByoipCidr,
AdvertiseByoipCidrResponse -> Int
httpStatus :: Prelude.Int
}
deriving (AdvertiseByoipCidrResponse -> AdvertiseByoipCidrResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AdvertiseByoipCidrResponse -> AdvertiseByoipCidrResponse -> Bool
$c/= :: AdvertiseByoipCidrResponse -> AdvertiseByoipCidrResponse -> Bool
== :: AdvertiseByoipCidrResponse -> AdvertiseByoipCidrResponse -> Bool
$c== :: AdvertiseByoipCidrResponse -> AdvertiseByoipCidrResponse -> Bool
Prelude.Eq, ReadPrec [AdvertiseByoipCidrResponse]
ReadPrec AdvertiseByoipCidrResponse
Int -> ReadS AdvertiseByoipCidrResponse
ReadS [AdvertiseByoipCidrResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AdvertiseByoipCidrResponse]
$creadListPrec :: ReadPrec [AdvertiseByoipCidrResponse]
readPrec :: ReadPrec AdvertiseByoipCidrResponse
$creadPrec :: ReadPrec AdvertiseByoipCidrResponse
readList :: ReadS [AdvertiseByoipCidrResponse]
$creadList :: ReadS [AdvertiseByoipCidrResponse]
readsPrec :: Int -> ReadS AdvertiseByoipCidrResponse
$creadsPrec :: Int -> ReadS AdvertiseByoipCidrResponse
Prelude.Read, Int -> AdvertiseByoipCidrResponse -> ShowS
[AdvertiseByoipCidrResponse] -> ShowS
AdvertiseByoipCidrResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AdvertiseByoipCidrResponse] -> ShowS
$cshowList :: [AdvertiseByoipCidrResponse] -> ShowS
show :: AdvertiseByoipCidrResponse -> String
$cshow :: AdvertiseByoipCidrResponse -> String
showsPrec :: Int -> AdvertiseByoipCidrResponse -> ShowS
$cshowsPrec :: Int -> AdvertiseByoipCidrResponse -> ShowS
Prelude.Show, forall x.
Rep AdvertiseByoipCidrResponse x -> AdvertiseByoipCidrResponse
forall x.
AdvertiseByoipCidrResponse -> Rep AdvertiseByoipCidrResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AdvertiseByoipCidrResponse x -> AdvertiseByoipCidrResponse
$cfrom :: forall x.
AdvertiseByoipCidrResponse -> Rep AdvertiseByoipCidrResponse x
Prelude.Generic)
newAdvertiseByoipCidrResponse ::
Prelude.Int ->
AdvertiseByoipCidrResponse
newAdvertiseByoipCidrResponse :: Int -> AdvertiseByoipCidrResponse
newAdvertiseByoipCidrResponse Int
pHttpStatus_ =
AdvertiseByoipCidrResponse'
{ $sel:byoipCidr:AdvertiseByoipCidrResponse' :: Maybe ByoipCidr
byoipCidr =
forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:AdvertiseByoipCidrResponse' :: Int
httpStatus = Int
pHttpStatus_
}
advertiseByoipCidrResponse_byoipCidr :: Lens.Lens' AdvertiseByoipCidrResponse (Prelude.Maybe ByoipCidr)
advertiseByoipCidrResponse_byoipCidr :: Lens' AdvertiseByoipCidrResponse (Maybe ByoipCidr)
advertiseByoipCidrResponse_byoipCidr = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AdvertiseByoipCidrResponse' {Maybe ByoipCidr
byoipCidr :: Maybe ByoipCidr
$sel:byoipCidr:AdvertiseByoipCidrResponse' :: AdvertiseByoipCidrResponse -> Maybe ByoipCidr
byoipCidr} -> Maybe ByoipCidr
byoipCidr) (\s :: AdvertiseByoipCidrResponse
s@AdvertiseByoipCidrResponse' {} Maybe ByoipCidr
a -> AdvertiseByoipCidrResponse
s {$sel:byoipCidr:AdvertiseByoipCidrResponse' :: Maybe ByoipCidr
byoipCidr = Maybe ByoipCidr
a} :: AdvertiseByoipCidrResponse)
advertiseByoipCidrResponse_httpStatus :: Lens.Lens' AdvertiseByoipCidrResponse Prelude.Int
advertiseByoipCidrResponse_httpStatus :: Lens' AdvertiseByoipCidrResponse Int
advertiseByoipCidrResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AdvertiseByoipCidrResponse' {Int
httpStatus :: Int
$sel:httpStatus:AdvertiseByoipCidrResponse' :: AdvertiseByoipCidrResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: AdvertiseByoipCidrResponse
s@AdvertiseByoipCidrResponse' {} Int
a -> AdvertiseByoipCidrResponse
s {$sel:httpStatus:AdvertiseByoipCidrResponse' :: Int
httpStatus = Int
a} :: AdvertiseByoipCidrResponse)
instance Prelude.NFData AdvertiseByoipCidrResponse where
rnf :: AdvertiseByoipCidrResponse -> ()
rnf AdvertiseByoipCidrResponse' {Int
Maybe ByoipCidr
httpStatus :: Int
byoipCidr :: Maybe ByoipCidr
$sel:httpStatus:AdvertiseByoipCidrResponse' :: AdvertiseByoipCidrResponse -> Int
$sel:byoipCidr:AdvertiseByoipCidrResponse' :: AdvertiseByoipCidrResponse -> Maybe ByoipCidr
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe ByoipCidr
byoipCidr
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus